Skip to content

Commit

Permalink
Source rendering: anchors do not depend on locations
Browse files Browse the repository at this point in the history
Signed-off-by: Paul-Elliot <[email protected]>
  • Loading branch information
panglesd committed Sep 15, 2023
1 parent 9361f0a commit 6a2ba13
Show file tree
Hide file tree
Showing 3 changed files with 13 additions and 8 deletions.
13 changes: 9 additions & 4 deletions src/loader/implementation.ml
Original file line number Diff line number Diff line change
Expand Up @@ -9,6 +9,12 @@ type annotations =
| LocalValue of Ident.t
| DefJmp of Shape.Uid.t

let counter =
let c = ref 0 in
fun () ->
incr c;
!c

module Analysis = struct
open Typedtree
open Odoc_model.Paths
Expand Down Expand Up @@ -331,10 +337,10 @@ let postprocess_poses source_id poses uid_to_id uid_to_loc =
let local_def_anchors =
List.filter_map
(function
| LocalDefinition id, (start, _) ->
| LocalDefinition id, _ ->
let name =
Odoc_model.Names.LocalName.make_std
(Printf.sprintf "local_%s_%d" (Ident.name id) start)
(Printf.sprintf "local_%s_%d" (Ident.name id) (counter ()))
in
let identifier =
Odoc_model.Paths.Identifier.Mk.source_location_int
Expand Down Expand Up @@ -476,8 +482,7 @@ let of_cmt (source_id : Odoc_model.Paths.Identifier.SourcePage.t)
| Item _ ->
let name =
Odoc_model.Names.DefName.make_std
(Printf.sprintf "def_%d_%d" loc.loc_start.pos_cnum
loc.loc_end.pos_cnum)
(Printf.sprintf "def_%d" (counter ()))
in
Some name
| _ -> None)
Expand Down
2 changes: 1 addition & 1 deletion test/sources/source.t/a.ml
Original file line number Diff line number Diff line change
Expand Up @@ -12,7 +12,7 @@ let segr = Yoyo.Aa

let x = 2
let y = x + 1
let z a = if x = 1 || true then x + y else 0
let z a = if x = 1 || true then x + y else a

module A = struct end
module B = A
Expand Down
6 changes: 3 additions & 3 deletions test/sources/source.t/run.t
Original file line number Diff line number Diff line change
Expand Up @@ -15,7 +15,7 @@ Files containing some values:

let x = 2
let y = x + 1
let z a = if x = 1 || true then x + y else 0
let z a = if x = 1 || true then x + y else a

module A = struct end
module B = A
Expand Down Expand Up @@ -273,7 +273,7 @@ Ids generated in the source code:
id="val-{x}2"
id="val-y"
id="val-z"
id="local_a_148"
id="local_a_2"
id="module-A"
id="module-B"
id="module-type-T"
Expand All @@ -295,7 +295,7 @@ Ids generated in the source code:
id="module-F.argument-1-M.module-A"
id="module-F.module-B"
id="module-FM"
id="def_591_612"
id="def_1"
id="module-FF"
id="module-FF2"
id="module-FF2.argument-1-A.module-E"
Expand Down

0 comments on commit 6a2ba13

Please sign in to comment.