diff --git a/odoc.opam b/odoc.opam index 230ed5fa7e..9075dd1d95 100644 --- a/odoc.opam +++ b/odoc.opam @@ -25,7 +25,6 @@ depends: [ "fpath" {build} "ocaml" {>= "4.02.0"} "result" {build} - "rresult" {build & >= "0.3.0"} "tyxml" {build & >= "4.3.0"} "alcotest" {dev & >= "0.8.3"} diff --git a/src/odoc/fs.mli b/src/odoc/fs.mli index 4877e542ec..67c45bc26f 100644 --- a/src/odoc/fs.mli +++ b/src/odoc/fs.mli @@ -59,7 +59,7 @@ module File : sig val of_string : string -> t val to_string : t -> string - val read : t -> (string, [> Rresult.R.msg ]) result + val read : t -> (string, [> `Msg of string ]) result module Table : Hashtbl.S with type key = t end diff --git a/src/parser/dune b/src/parser/dune index cf10335b85..31aafe5c61 100644 --- a/src/parser/dune +++ b/src/parser/dune @@ -4,5 +4,5 @@ (name odoc__parser) (public_name odoc.parser) (preprocess (pps bisect_ppx -conditional)) - (libraries astring odoc__alias odoc__compat odoc__model rresult) + (libraries astring odoc__alias odoc__compat odoc__model) (flags (:standard -open Odoc__alias))) diff --git a/src/parser/reference.ml b/src/parser/reference.ml index 6c5be71611..b96bc560ba 100644 --- a/src/parser/reference.ml +++ b/src/parser/reference.ml @@ -364,11 +364,15 @@ let read_path_longident location s = | Some r -> Result.Ok r | None -> Result.Error (Parse_error.expected "a valid path" location) -let read_mod_longident warnings location lid : (Paths.Reference.Module.t, Error.t) Result.result = - let (>>=) = Rresult.(>>=) in - - parse warnings location lid >>= function - | `Root (_, (`TUnknown | `TModule)) - | `Dot (_, _) - | `Module (_, _) as r -> Result.Ok r - | _ -> Result.Error (Parse_error.expected "a reference to a module" location) +let read_mod_longident + warnings location lid : (Paths.Reference.Module.t, Error.t) Result.result + = + match parse warnings location lid with + | Error _ as e -> e + | Ok p -> + match p with + | `Root (_, (`TUnknown | `TModule)) + | `Dot (_, _) + | `Module (_, _) as r -> Result.Ok r + | _ -> + Result.Error (Parse_error.expected "a reference to a module" location) diff --git a/src/parser/syntax.ml b/src/parser/syntax.ml index 20749455e8..ed91e2aaf6 100644 --- a/src/parser/syntax.ml +++ b/src/parser/syntax.ml @@ -770,13 +770,14 @@ let rec block_element_list cooperation to get the real location. *) let r_location = Location.nudge_start (String.length "@canonical ") location in - - let (>>=) = Rresult.(>>=) in - let result = - Reference.read_path_longident r_location s >>= fun path -> - Reference.read_mod_longident - input.warnings r_location s >>= fun module_ -> - Result.Ok (`Canonical (path, module_)) + let result = match Reference.read_path_longident r_location s with + | Error _ as e -> e + | Ok path -> + match + Reference.read_mod_longident input.warnings r_location s + with + | Error _ as e -> e + | Ok module_ -> Result.Ok (`Canonical (path, module_)) in match result with | Result.Ok _ as result -> result