File tree Expand file tree Collapse file tree 4 files changed +8
-6
lines changed Expand file tree Collapse file tree 4 files changed +8
-6
lines changed Original file line number Diff line number Diff line change @@ -453,7 +453,7 @@ and read_module_binding env parent mb =
453453 | _ , _ -> false
454454#else
455455 match canonical with
456- | None -> Odoc_model.Root . contains_double_underscore (Ident. name mb.mb_id)
456+ | None -> Odoc_model.Names . contains_double_underscore (Ident. name mb.mb_id)
457457 | _ -> false
458458#endif
459459 in
Original file line number Diff line number Diff line change @@ -632,7 +632,7 @@ and read_module_declaration env parent md =
632632 | _ ,_ -> false
633633#else
634634 match canonical with
635- | None -> Odoc_model.Root . contains_double_underscore (Ident. name md.md_id)
635+ | None -> Odoc_model.Names . contains_double_underscore (Ident. name md.md_id)
636636 | _ -> false
637637#endif
638638 in
Original file line number Diff line number Diff line change @@ -1111,6 +1111,8 @@ module Targets = struct
11111111end
11121112
11131113module Occurrences = struct
1114+ open Or_error
1115+
11141116 let has_occurrences_prefix input =
11151117 input |> Fs.File. basename |> Fs.File. to_string
11161118 |> Astring.String. is_prefix ~affix: " occurrences-"
@@ -1122,7 +1124,6 @@ module Occurrences = struct
11221124 else if not (has_occurrences_prefix f) then
11231125 Error (`Msg " Output file must be prefixed with 'occurrences-'." )
11241126 else Ok f
1125- open Or_error
11261127 module Count = struct
11271128 let count directories dst warnings_options include_hidden =
11281129 dst_of_string dst >> = fun dst ->
Original file line number Diff line number Diff line change @@ -87,9 +87,10 @@ end = struct
8787 ()
8888
8989 let rec get t id =
90- let ( >> = ) = Option. bind in
9190 let do_ parent =
92- get t (parent :> key ) >> = fun { sub; _ } -> H. find_opt sub id
91+ get t (parent :> key ) |> function
92+ | None -> None
93+ | Some { sub; _ } -> ( try Some (H. find sub id) with Not_found -> None )
9394 in
9495 match id.iv with
9596 | `InstanceVariable (parent , _ ) -> do_ parent
@@ -106,7 +107,7 @@ end = struct
106107 | `Class (parent , _ ) -> do_ parent
107108 | `Value (parent , _ ) -> do_ parent
108109 | `ClassType (parent , _ ) -> do_ parent
109- | `Root _ -> H. find_opt t id
110+ | `Root _ -> ( try Some ( H. find t id) with Not_found -> None )
110111 | `SourcePage _ | `Page _ | `LeafPage _ | `CoreType _ | `SourceLocation _
111112 | `CoreException _ | `Label _ | `SourceLocationMod _ | `Result _
112113 | `AssetFile _ | `SourceDir _ | `SourceLocationInternal _ ->
You can’t perform that action at this time.
0 commit comments