Skip to content

Commit 2e8fae5

Browse files
panglesdjonludlam
authored andcommitted
Rename SourceLocationInt to SourceLocationInternal
for more self-explanatoriness Signed-off-by: Paul-Elliot <[email protected]>
1 parent c600fa2 commit 2e8fae5

File tree

9 files changed

+13
-13
lines changed

9 files changed

+13
-13
lines changed

src/.ocamlformat-ignore

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -6,8 +6,8 @@ loader/cmt.ml
66
loader/cmti.ml
77
loader/doc_attr.ml
88
loader/implementation.ml
9-
loader/shape_.ml
10-
loader/shape_.mli
9+
loader/lookup_def.ml
10+
loader/lookup_def.mli
1111
syntax_highlighter/syntax_highlighter.ml
1212
model/*.cppo.ml
1313
html_support_files/*.ml

src/document/generator.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -262,7 +262,7 @@ module Make (Syntax : SYNTAX) = struct
262262
| Definition id -> (
263263
match id.iv with
264264
| `SourceLocation (_, def) -> Some (Anchor (DefName.to_string def))
265-
| `SourceLocationInt (_, local) ->
265+
| `SourceLocationInternal (_, local) ->
266266
Some (Anchor (LocalName.to_string local))
267267
| _ -> None)
268268

src/document/url.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -371,7 +371,7 @@ module Anchor = struct
371371
| { iv = `SourceLocation (parent, loc); _ } ->
372372
let page = Path.from_identifier (parent :> Path.any) in
373373
Ok { page; kind = `SourceAnchor; anchor = DefName.to_string loc }
374-
| { iv = `SourceLocationInt (parent, loc); _ } ->
374+
| { iv = `SourceLocationInternal (parent, loc); _ } ->
375375
let page = Path.from_identifier (parent :> Path.any) in
376376
Ok { page; kind = `SourceAnchor; anchor = LocalName.to_string loc }
377377
| { iv = `SourceLocationMod parent; _ } ->

src/loader/implementation.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -419,7 +419,7 @@ let anchor_of_identifier id =
419419
continue anchor parent
420420
| `SourceLocationMod _ -> assert false
421421
| `Result parent -> anchor_of_identifier acc (parent :> Identifier.t)
422-
| `SourceLocationInt _ -> assert false
422+
| `SourceLocationInternal _ -> assert false
423423
| `Type (parent, name) ->
424424
let anchor = anchor `Type (TypeName.to_string name) in
425425
continue anchor parent

src/model/paths.ml

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -58,7 +58,7 @@ module Identifier = struct
5858
| `SourceLocation (x, anchor) ->
5959
name_aux (x :> t) ^ "#" ^ DefName.to_string anchor
6060
| `SourceLocationMod x -> name_aux (x :> t)
61-
| `SourceLocationInt (x, anchor) ->
61+
| `SourceLocationInternal (x, anchor) ->
6262
name_aux (x :> t) ^ "#" ^ LocalName.to_string anchor
6363
| `AssetFile (_, name) -> name
6464

@@ -519,9 +519,9 @@ module Identifier = struct
519519

520520
let source_location_int :
521521
SourcePage.t * LocalName.t ->
522-
[> `SourceLocationInt of SourcePage.t * LocalName.t ] id =
522+
[> `SourceLocationInternal of SourcePage.t * LocalName.t ] id =
523523
mk_parent LocalName.to_string "sli" (fun (p, n) ->
524-
`SourceLocationInt (p, n))
524+
`SourceLocationInternal (p, n))
525525
end
526526
end
527527

src/model/paths.mli

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -304,7 +304,7 @@ module Identifier : sig
304304

305305
val source_location_int :
306306
SourcePage.t * LocalName.t ->
307-
[> `SourceLocationInt of SourcePage.t * LocalName.t ] id
307+
[> `SourceLocationInternal of SourcePage.t * LocalName.t ] id
308308
end
309309
end
310310

src/model/paths_types.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -43,7 +43,7 @@ module Identifier = struct
4343
type source_location_pv =
4444
[ `SourceLocationMod of source_page
4545
| `SourceLocation of source_page * DefName.t
46-
| `SourceLocationInt of source_page * LocalName.t ]
46+
| `SourceLocationInternal of source_page * LocalName.t ]
4747
(** @canonical Odoc_model.Paths.Identifier.SourceLocation.t *)
4848

4949
and source_location = source_location_pv id

src/model_desc/paths_desc.ml

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -168,9 +168,9 @@ module General_paths = struct
168168
( "`SourceLocation",
169169
((parent :> id_t), name),
170170
Pair (identifier, Names.defname) )
171-
| `SourceLocationInt (parent, name) ->
171+
| `SourceLocationInternal (parent, name) ->
172172
C
173-
( "`SourceLocationInt",
173+
( "`SourceLocationInternal",
174174
((parent :> id_t), name),
175175
Pair (identifier, Names.localname) )
176176
| `SourceLocationMod parent ->

src/xref2/component.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1255,7 +1255,7 @@ module Fmt = struct
12551255
Format.fprintf ppf "%a#%s" model_identifier
12561256
(p :> Odoc_model.Paths.Identifier.t)
12571257
(DefName.to_string def)
1258-
| `SourceLocationInt (p, def) ->
1258+
| `SourceLocationInternal (p, def) ->
12591259
Format.fprintf ppf "%a#%s" model_identifier
12601260
(p :> Odoc_model.Paths.Identifier.t)
12611261
(LocalName.to_string def)

0 commit comments

Comments
 (0)