Commit b57fe47 1 parent 126063d commit b57fe47 Copy full SHA for b57fe47
File tree 5 files changed +22
-18
lines changed
5 files changed +22
-18
lines changed Original file line number Diff line number Diff line change @@ -25,7 +25,6 @@ depends: [
25
25
"fpath" {build}
26
26
"ocaml" {>= "4.02.0"}
27
27
"result" {build}
28
- "rresult" {build & >= "0.3.0"}
29
28
"tyxml" {build & >= "4.3.0"}
30
29
31
30
"alcotest" {dev & >= "0.8.3"}
Original file line number Diff line number Diff line change @@ -59,7 +59,7 @@ module File : sig
59
59
val of_string : string -> t
60
60
val to_string : t -> string
61
61
62
- val read : t -> (string , [> Rresult .R .msg ]) result
62
+ val read : t -> (string , [> `Msg of string ]) result
63
63
64
64
module Table : Hashtbl .S with type key = t
65
65
end
Original file line number Diff line number Diff line change 4
4
(name odoc__parser)
5
5
(public_name odoc.parser)
6
6
(preprocess (pps bisect_ppx -conditional))
7
- (libraries astring odoc__alias odoc__compat odoc__model rresult )
7
+ (libraries astring odoc__alias odoc__compat odoc__model)
8
8
(flags (:standard -open Odoc__alias)))
Original file line number Diff line number Diff line change @@ -364,11 +364,15 @@ let read_path_longident location s =
364
364
| Some r -> Result. Ok r
365
365
| None -> Result. Error (Parse_error. expected " a valid path" location)
366
366
367
- let read_mod_longident warnings location lid : (Paths.Reference.Module.t, Error.t) Result.result =
368
- let (>> = ) = Rresult. (>> = ) in
369
-
370
- parse warnings location lid >> = function
371
- | `Root (_, (`TUnknown | `TModule ))
372
- | `Dot (_, _)
373
- | `Module (_ , _ ) as r -> Result. Ok r
374
- | _ -> Result. Error (Parse_error. expected " a reference to a module" location)
367
+ let read_mod_longident
368
+ warnings location lid : (Paths.Reference.Module. t , Error. t ) Result. result
369
+ =
370
+ match parse warnings location lid with
371
+ | Error _ as e -> e
372
+ | Ok p ->
373
+ match p with
374
+ | `Root (_, (`TUnknown | `TModule ))
375
+ | `Dot (_, _)
376
+ | `Module (_ , _ ) as r -> Result. Ok r
377
+ | _ ->
378
+ Result. Error (Parse_error. expected " a reference to a module" location)
Original file line number Diff line number Diff line change @@ -770,13 +770,14 @@ let rec block_element_list
770
770
cooperation to get the real location. *)
771
771
let r_location =
772
772
Location. nudge_start (String. length " @canonical " ) location in
773
-
774
- let (>> = ) = Rresult. (>> = ) in
775
- let result =
776
- Reference. read_path_longident r_location s >> = fun path ->
777
- Reference. read_mod_longident
778
- input.warnings r_location s >> = fun module_ ->
779
- Result. Ok (`Canonical (path, module_))
773
+ let result = match Reference. read_path_longident r_location s with
774
+ | Error _ as e -> e
775
+ | Ok path ->
776
+ match
777
+ Reference. read_mod_longident input.warnings r_location s
778
+ with
779
+ | Error _ as e -> e
780
+ | Ok module_ -> Result. Ok (`Canonical (path, module_))
780
781
in
781
782
match result with
782
783
| Result. Ok _ as result -> result
You can’t perform that action at this time.
0 commit comments