diff --git a/odoc-parser.opam b/odoc-parser.opam index 1458575222..efff0d8f1b 100644 --- a/odoc-parser.opam +++ b/odoc-parser.opam @@ -17,7 +17,6 @@ depends: [ "dune" {>= "3.7"} "ocaml" {>= "4.08.0" & < "5.4"} "astring" - "result" "camlp-streams" "ppx_expect" {with-test} "sexplib0" {with-test} diff --git a/odoc.opam b/odoc.opam index 5169c7dea1..f4e5d5ab1e 100644 --- a/odoc.opam +++ b/odoc.opam @@ -47,7 +47,6 @@ depends: [ "dune" {>= "3.7.0"} "fpath" "ocaml" {>= "4.08.0" & < "5.4"} - "result" "tyxml" {>= "4.4.0"} "fmt" "crunch" {>= "1.4.1"} diff --git a/src/document/codefmt.ml b/src/document/codefmt.ml index 729a2d1423..a6fc05f56c 100644 --- a/src/document/codefmt.ml +++ b/src/document/codefmt.ml @@ -42,6 +42,27 @@ module State = struct flush state) end +let rec compute_length_source (t : Types.Source.t) : int = + let f (acc : int) = function + | Types.Source.Elt t -> acc + compute_length_inline t + | Types.Source.Tag (_, t) -> acc + compute_length_source t + in + List.fold_left f 0 t + +and compute_length_inline (t : Types.Inline.t) : int = + let f (acc : int) { Types.Inline.desc; _ } = + match desc with + | Text s -> acc + String.length s + | Entity _e -> acc + 1 + | Linebreak -> 0 (* TODO *) + | Styled (_, t) | Link { content = t; _ } -> acc + compute_length_inline t + | Source s -> acc + compute_length_source s + | Math _ -> assert false + | Raw_markup _ -> assert false + (* TODO *) + in + List.fold_left f 0 t + (** Modern implementation using semantic tags, Only for 4.08+ *) (* @@ -79,7 +100,7 @@ module Tag = struct let elt ppf elt = Format.pp_open_stag ppf (Elt elt); - Format.pp_print_as ppf (Utils.compute_length_inline elt) ""; + Format.pp_print_as ppf (compute_length_inline elt) ""; Format.pp_close_stag ppf () let ignore ppf txt = @@ -140,7 +161,7 @@ module Tag = struct let elt ppf (elt : Inline.t) = Format.fprintf ppf "@{%t@}" (Marshal.to_string elt []) (fun fmt -> - Format.pp_print_as fmt (Utils.compute_length_inline elt) "") + Format.pp_print_as fmt (compute_length_inline elt) "") let ignore ppf txt = Format.fprintf ppf "@{%t@}" txt end diff --git a/src/document/comment.ml b/src/document/comment.ml index 7f0375b823..145b141c41 100644 --- a/src/document/comment.ml +++ b/src/document/comment.ml @@ -14,6 +14,7 @@ * OR IN CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE. *) +open Odoc_utils open Types module Comment = Odoc_model.Comment open Odoc_model.Names @@ -67,7 +68,7 @@ module Reference = struct | `TAbsolutePath -> "/" | `TCurrentPackage -> "//" in - tag ^ String.concat "/" cs + tag ^ String.concat ~sep:"/" cs let rec render_unresolved : Reference.t -> string = let open Reference in @@ -412,11 +413,11 @@ let synopsis ~decl_doc ~expansion_doc = match Comment.synopsis docs with Some p -> [ paragraph p ] | None -> [] let standalone docs = - Utils.flatmap ~f:item_element + List.concat_map item_element @@ List.map (fun x -> x.Odoc_model.Location_.value) docs let to_ir (docs : Comment.elements) = - Utils.flatmap ~f:block_element + List.concat_map block_element @@ List.map (fun x -> x.Odoc_model.Location_.value) docs let has_doc docs = docs <> [] diff --git a/src/document/doctree.ml b/src/document/doctree.ml index d48ff41bb6..02eb782266 100644 --- a/src/document/doctree.ml +++ b/src/document/doctree.ml @@ -1,3 +1,4 @@ +open Odoc_utils open Types module Take = struct @@ -97,19 +98,23 @@ module Subpages : sig val compute : Page.t -> Subpage.t list end = struct let rec walk_documentedsrc (l : DocumentedSrc.t) = - Utils.flatmap l ~f:(function - | DocumentedSrc.Code _ -> [] - | Documented _ -> [] - | Nested { code; _ } -> walk_documentedsrc code - | Subpage p -> [ p ] - | Alternative (Expansion r) -> walk_documentedsrc r.expansion) + List.concat_map + (function + | DocumentedSrc.Code _ -> [] + | Documented _ -> [] + | Nested { code; _ } -> walk_documentedsrc code + | Subpage p -> [ p ] + | Alternative (Expansion r) -> walk_documentedsrc r.expansion) + l let rec walk_items (l : Item.t list) = - Utils.flatmap l ~f:(function - | Item.Text _ -> [] - | Heading _ -> [] - | Declaration { content; _ } -> walk_documentedsrc content - | Include i -> walk_items i.content.content) + List.concat_map + (function + | Item.Text _ -> [] + | Heading _ -> [] + | Declaration { content; _ } -> walk_documentedsrc content + | Include i -> walk_items i.content.content) + l let compute (p : Page.t) = walk_items (p.preamble @ p.items) end diff --git a/src/document/generator.ml b/src/document/generator.ml index 14f8c662f1..70c5d82be7 100644 --- a/src/document/generator.ml +++ b/src/document/generator.ml @@ -14,6 +14,7 @@ * OR IN CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE. *) +open Odoc_utils open Odoc_model.Names module Location = Odoc_model.Location_ module Paths = Odoc_model.Paths @@ -76,7 +77,7 @@ let mk_heading ?(level = 1) ?label text = rest is inserted into [items]. *) let prepare_preamble comment items = let preamble, first_comment = - Utils.split_at + List.split_at ~f:(function | { Odoc_model.Location_.value = `Heading _; _ } -> true | _ -> false) comment @@ -213,7 +214,7 @@ module Make (Syntax : SYNTAX) = struct let in_bound x = min (max x 0) (String.length src) in let a = in_bound a and b = in_bound b in let a, b = (min a b, max a b) in - String.sub src a (b - a) + String.with_range src ~first:a ~len:(b - a) in let plain_code = function | "" -> [] @@ -358,7 +359,7 @@ module Make (Syntax : SYNTAX) = struct | Open -> O.txt "[> " ++ elements ++ O.txt " ]" | Closed [] -> O.txt "[< " ++ elements ++ O.txt " ]" | Closed lst -> - let constrs = String.concat " " lst in + let constrs = String.concat ~sep:" " lst in O.txt "[< " ++ elements ++ O.txt (" " ^ constrs ^ " ]")) and te_object (t : Odoc_model.Lang.TypeExpr.Object.t) = @@ -461,7 +462,7 @@ module Make (Syntax : SYNTAX) = struct format_type_path ~delim:`brackets args (Link.from_path (path :> Paths.Path.t)) | Poly (polyvars, t) -> - O.txt ("'" ^ String.concat " '" polyvars ^ ". ") ++ type_expr t + O.txt ("'" ^ String.concat ~sep:" '" polyvars ^ ". ") ++ type_expr t | Package pkg -> enclose ~l:"(" ~r:")" (O.keyword "module" ++ O.txt " " @@ -747,7 +748,7 @@ module Make (Syntax : SYNTAX) = struct | Closed [] -> (O.documentedSrc (O.txt "[< "), O.documentedSrc (O.txt " ]")) | Closed lst -> - let constrs = String.concat " " lst in + let constrs = String.concat ~sep:" " lst in ( O.documentedSrc (O.txt "[< "), O.documentedSrc (O.txt (" " ^ constrs ^ " ]")) ) in @@ -773,14 +774,14 @@ module Make (Syntax : SYNTAX) = struct | Some Odoc_model.Lang.TypeDecl.Neg -> "-" :: desc in let final = if injectivity then "!" :: var_desc else var_desc in - String.concat "" final + String.concat ~sep:"" final in O.txt (match params with | [] -> "" | [ x ] -> format_param x |> Syntax.Type.handle_format_params | lst -> ( - let params = String.concat ", " (List.map format_param lst) in + let params = String.concat ~sep:", " (List.map format_param lst) in (match delim with `parens -> "(" | `brackets -> "[") ^ params ^ match delim with `parens -> ")" | `brackets -> "]")) @@ -1077,7 +1078,7 @@ module Make (Syntax : SYNTAX) = struct | Constraint cst -> continue @@ constraint_ cst | Comment `Stop -> let rest = - Utils.skip_until rest ~p:(function + List.skip_until rest ~p:(function | Lang.ClassSignature.Comment `Stop -> true | _ -> false) in @@ -1268,7 +1269,7 @@ module Make (Syntax : SYNTAX) = struct loop rest (List.rev_append items acc_items) | Comment `Stop -> let rest = - Utils.skip_until rest ~p:(function + List.skip_until rest ~p:(function | Lang.Signature.Comment `Stop -> true | _ -> false) in @@ -1376,18 +1377,19 @@ module Make (Syntax : SYNTAX) = struct | Some params, sg -> let sg_doc, content = signature sg in let params = - Utils.flatmap params ~f:(fun arg -> - let content = functor_parameter arg in - let attr = [ "parameter" ] in - let anchor = - Some - (Url.Anchor.from_identifier (arg.id :> Paths.Identifier.t)) - in - let doc = [] in - [ - Item.Declaration - { content; anchor; attr; doc; source_anchor = None }; - ]) + let decl_of_arg arg = + let content = functor_parameter arg in + let attr = [ "parameter" ] in + let anchor = + Some (Url.Anchor.from_identifier (arg.id :> Paths.Identifier.t)) + in + let doc = [] in + [ + Item.Declaration + { content; anchor; attr; doc; source_anchor = None }; + ] + in + List.concat_map decl_of_arg params in let prelude = mk_heading ~label:"parameters" "Parameters" :: params and content = mk_heading ~label:"signature" "Signature" :: content in diff --git a/src/document/utils.ml b/src/document/utils.ml deleted file mode 100644 index 49286b8cb2..0000000000 --- a/src/document/utils.ml +++ /dev/null @@ -1,42 +0,0 @@ -let option_of_result = function Result.Ok x -> Some x | Result.Error _ -> None - -let rec flatmap ?sep ~f = function - | [] -> [] - | [ x ] -> f x - | x :: xs -> ( - let hd = f x in - let tl = flatmap ?sep ~f xs in - match sep with None -> hd @ tl | Some sep -> hd @ sep @ tl) - -let rec skip_until ~p = function - | [] -> [] - | h :: t -> if p h then t else skip_until ~p t - -let split_at ~f lst = - let rec loop acc = function - | hd :: _ as rest when f hd -> (List.rev acc, rest) - | [] -> (List.rev acc, []) - | hd :: tl -> loop (hd :: acc) tl - in - loop [] lst - -let rec compute_length_source (t : Types.Source.t) : int = - let f (acc : int) = function - | Types.Source.Elt t -> acc + compute_length_inline t - | Types.Source.Tag (_, t) -> acc + compute_length_source t - in - List.fold_left f 0 t - -and compute_length_inline (t : Types.Inline.t) : int = - let f (acc : int) { Types.Inline.desc; _ } = - match desc with - | Text s -> acc + String.length s - | Entity _e -> acc + 1 - | Linebreak -> 0 (* TODO *) - | Styled (_, t) | Link { content = t; _ } -> acc + compute_length_inline t - | Source s -> acc + compute_length_source s - | Math _ -> assert false - | Raw_markup _ -> assert false - (* TODO *) - in - List.fold_left f 0 t diff --git a/src/document/utils.mli b/src/document/utils.mli deleted file mode 100644 index 4ead7e29aa..0000000000 --- a/src/document/utils.mli +++ /dev/null @@ -1,6 +0,0 @@ -val option_of_result : ('a, 'b) Result.result -> 'a option -val flatmap : ?sep:'a list -> f:('b -> 'a list) -> 'b list -> 'a list -val skip_until : p:('a -> bool) -> 'a list -> 'a list -val split_at : f:('a -> bool) -> 'a list -> 'a list * 'a list -val compute_length_source : Types.Source.t -> int -val compute_length_inline : Types.Inline.t -> int diff --git a/src/driver/dune b/src/driver/dune index a1e00c794b..2998e24f66 100644 --- a/src/driver/dune +++ b/src/driver/dune @@ -14,5 +14,4 @@ logs logs.fmt eio_main - sexplib - odoc_utils)) + sexplib)) diff --git a/src/driver/util.ml b/src/driver/util.ml index 08b8a56311..8228a3f958 100644 --- a/src/driver/util.ml +++ b/src/driver/util.ml @@ -1,6 +1,7 @@ -open Odoc_utils open Bos +let ( >>= ) = Result.bind + module StringSet = Set.Make (String) module StringMap = Map.Make (String) @@ -26,7 +27,6 @@ let lines_of_process cmd = (** Opens a file for writing and calls [f]. The destination directory is created if needed. *) let with_out_to filename f = - let open ResultMonad in let filename = Fpath.normalize filename in OS.Dir.create (Fpath.parent filename) >>= fun _ -> OS.File.with_oc filename @@ -35,6 +35,5 @@ let with_out_to filename f = Ok ()) () |> Result.join - >>= fun () -> Ok () let cp src dst = assert (lines_of_process Cmd.(v "cp" % src % dst) = []) diff --git a/src/loader/odoc_loader.mli b/src/loader/odoc_loader.mli index c593e3c9a9..b9ecd1ecfd 100644 --- a/src/loader/odoc_loader.mli +++ b/src/loader/odoc_loader.mli @@ -1,4 +1,3 @@ -open Result open Odoc_model open Odoc_model.Paths diff --git a/src/manpage/generator.ml b/src/manpage/generator.ml index 2853760ee8..679d69a69b 100644 --- a/src/manpage/generator.ml +++ b/src/manpage/generator.ml @@ -1,3 +1,4 @@ +open Odoc_utils module ManLink = Link open Odoc_document open Types @@ -299,7 +300,7 @@ and inline (l : Inline.t) = | { Inline.desc = Text s; _ } -> Accum [ s ] | _ -> Stop_and_keep) in - str {|%s|} (String.concat "" l) ++ inline rest + str {|%s|} (String.concat ~sep:"" l) ++ inline rest | Entity e -> let x = entity e in x ++ inline rest @@ -343,7 +344,7 @@ let table pp { Table.data; align } = | Default -> "l") align in - Align_line (String.concat "" alignment) + Align_line (String.concat ~sep:"" alignment) in env "TS" "TE" "" (str "allbox;" ++ alignment @@ -408,7 +409,7 @@ let next_heading, reset_heading = | 1, n :: _ -> [ n + 1 ] | i, n :: t -> n :: succ_heading (i - 1) t in - let print_heading l = String.concat "." @@ List.map string_of_int l in + let print_heading l = String.concat ~sep:"." @@ List.map string_of_int l in let next level = let new_heading = succ_heading level !heading_stack in heading_stack := new_heading; @@ -547,7 +548,7 @@ let page p = let i = Shift.compute ~on_sub p.items in macro "TH" {|%s 3 "" "Odoc" "OCaml Library"|} p.url.name ++ macro "SH" "Name" - ++ str "%s" (String.concat "." @@ Link.for_printing p.url) + ++ str "%s" (String.concat ~sep:"." @@ Link.for_printing p.url) ++ macro "SH" "Synopsis" ++ vspace ++ item ~nested:false header ++ macro "SH" "Documentation" ++ vspace ++ macro "nf" "" ++ item ~nested:false i @@ -558,7 +559,7 @@ let rec subpage subp = and render_page (p : Page.t) = let p = Doctree.Labels.disambiguate_page ~enter_subpages:true p - and children = Utils.flatmap ~f:subpage @@ Subpages.compute p in + and children = List.concat_map subpage (Subpages.compute p) in let content ppf = Format.fprintf ppf "%a@." Roff.pp (page p) in let filename = Link.as_filename p.url in { Renderer.filename; content; children; path = p.url } diff --git a/src/model/dune b/src/model/dune index 81db5d9a0a..762fd475f5 100644 --- a/src/model/dune +++ b/src/model/dune @@ -16,4 +16,4 @@ (backend landmarks --auto)) (instrumentation (backend bisect_ppx)) - (libraries result compiler-libs.common odoc-parser odoc_utils)) + (libraries compiler-libs.common odoc-parser odoc_utils)) diff --git a/src/model/error.ml b/src/model/error.ml index 4902952970..90fdf7bc43 100644 --- a/src/model/error.ml +++ b/src/model/error.ml @@ -1,5 +1,3 @@ -open Result - let enable_missing_root_warning = ref false type full_location_payload = Odoc_parser.Warning.t = { @@ -90,7 +88,7 @@ let catch_warnings f = let warnings = List.rev !raised_warnings in { value; warnings }) -type 'a with_errors_and_warnings = ('a, t) Result.result with_warnings +type 'a with_errors_and_warnings = ('a, t) result with_warnings let raise_errors_and_warnings we = match raise_warnings we with Ok x -> x | Error e -> raise_exception e diff --git a/src/model/error.mli b/src/model/error.mli index 83916370f4..47260488ac 100644 --- a/src/model/error.mli +++ b/src/model/error.mli @@ -16,7 +16,7 @@ val raise_exception : t -> _ (** Raise a {!t} as an exception. Can be caught with {!catch} or {!catch_errors_and_warnings}. *) -val catch : (unit -> 'a) -> ('a, t) Result.result +val catch : (unit -> 'a) -> ('a, t) result type 'a with_warnings @@ -30,7 +30,7 @@ val raise_warnings : 'a with_warnings -> 'a val catch_warnings : (unit -> 'a) -> 'a with_warnings (** Catch warnings accumulated by [raise_warning]. Safe to nest. *) -type 'a with_errors_and_warnings = ('a, t) Result.result with_warnings +type 'a with_errors_and_warnings = ('a, t) result with_warnings (** Subtype of [with_warnings]. *) val raise_errors_and_warnings : 'a with_errors_and_warnings -> 'a @@ -48,14 +48,14 @@ type warnings_options = { val handle_warnings : warnings_options:warnings_options -> 'a with_warnings -> - ('a, [> `Msg of string ]) Result.result + ('a, [> `Msg of string ]) result (** Print warnings to stderr. If [warn_error] is [true] and there was warnings, returns an [Error]. *) val handle_errors_and_warnings : warnings_options:warnings_options -> 'a with_errors_and_warnings -> - ('a, [> `Msg of string ]) Result.result + ('a, [> `Msg of string ]) result (** Like [handle_warnings] but works on the output of [catch_errors_and_warnings]. Error case is converted into a [`Msg]. *) diff --git a/src/model/frontmatter.ml b/src/model/frontmatter.ml index 408873a202..fd6aa5d3b9 100644 --- a/src/model/frontmatter.ml +++ b/src/model/frontmatter.ml @@ -74,7 +74,7 @@ type tag_payload = Comment.nestable_block_element Location_.with_location list let parse_children_order loc (co : tag_payload) = let rec parse_words acc words = match words with - | [] -> Result.Ok (Location_.at loc (Children_order (List.rev acc))) + | [] -> Ok (Location_.at loc (Children_order (List.rev acc))) | ({ Location_.value = `Word word; _ } as w) :: tl -> parse_words ({ w with value = parse_child word } :: acc) tl | { Location_.value = `Space; _ } :: tl -> parse_words acc tl @@ -93,7 +93,7 @@ let parse_short_title loc (t : tag_payload) = match t with | [ { Location_.value = `Paragraph words; _ } ] -> let short_title = Comment.link_content_of_inline_elements words in - Result.Ok (Location_.at loc (Short_title short_title)) + Ok (Location_.at loc (Short_title short_title)) | _ -> Error (Error.make @@ -104,14 +104,14 @@ let parse_toc_status loc (t : tag_payload) = | [ { Location_.value = `Paragraph [ { Location_.value = `Word "open"; _ } ]; _ }; ] -> - Result.Ok (Location_.at loc (Toc_status `Open)) + Ok (Location_.at loc (Toc_status `Open)) | [ { Location_.value = `Paragraph [ { Location_.value = `Word "hidden"; _ } ]; _; }; ] -> - Result.Ok (Location_.at loc (Toc_status `Hidden)) + Ok (Location_.at loc (Toc_status `Hidden)) | _ -> Error (Error.make "@toc_status can only take the 'open' and 'hidden' value" @@ -121,7 +121,7 @@ let parse_order_category loc (t : tag_payload) = match t with | [ { Location_.value = `Paragraph [ { Location_.value = `Word w; _ } ]; _ } ] -> - Result.Ok (Location_.at loc (Order_category w)) + Ok (Location_.at loc (Order_category w)) | _ -> Error (Error.make "@order_category can only take a single word as value" loc) diff --git a/src/model/frontmatter.mli b/src/model/frontmatter.mli index 900179b530..ef1204e226 100644 --- a/src/model/frontmatter.mli +++ b/src/model/frontmatter.mli @@ -20,21 +20,21 @@ type tag_payload = Comment.nestable_block_element Location_.with_location list val parse_children_order : Location_.span -> tag_payload -> - (line Location_.with_location, Error.t) Result.result + (line Location_.with_location, Error.t) result val parse_short_title : Location_.span -> tag_payload -> - (line Location_.with_location, Error.t) Result.result + (line Location_.with_location, Error.t) result val parse_toc_status : Location_.span -> tag_payload -> - (line Location_.with_location, Error.t) Result.result + (line Location_.with_location, Error.t) result val parse_order_category : Location_.span -> tag_payload -> - (line Location_.with_location, Error.t) Result.result + (line Location_.with_location, Error.t) result val of_lines : line Location_.with_location list -> t Error.with_warnings diff --git a/src/model/reference.ml b/src/model/reference.ml index 052a2c90bd..bd162fee4a 100644 --- a/src/model/reference.ml +++ b/src/model/reference.ml @@ -590,8 +590,8 @@ let read_path_longident location s = in Error.catch_warnings (fun () -> match loop s (String.length s - 1) with - | Some r -> Result.Ok (r :> path) - | None -> Result.Error (expected_err_str "a valid path" location)) + | Some r -> Ok (r :> path) + | None -> Error (expected_err_str "a valid path" location)) let read_mod_longident location lid = Error.catch_warnings (fun () -> @@ -601,7 +601,5 @@ let read_mod_longident location lid = match p with | (`Root (_, (`TUnknown | `TModule)) | `Dot (_, _) | `Module (_, _)) as r -> - Result.Ok r - | _ -> - Result.Error (expected_err_str "a reference to a module" location) - )) + Ok r + | _ -> Error (expected_err_str "a reference to a module" location))) diff --git a/src/model/semantics.ml b/src/model/semantics.ml index 0f66efee47..6c522f4305 100644 --- a/src/model/semantics.ml +++ b/src/model/semantics.ml @@ -192,10 +192,10 @@ let rec inline_element : | { value = `Reference (kind, target, content) as value; location } -> ( let { Location.value = target; location = target_location } = target in match Error.raise_warnings (Reference.parse target_location target) with - | Result.Ok target -> + | Ok target -> let content = non_link_inline_elements ~surrounding:value content in Location.at location (`Reference (target, content)) - | Result.Error error -> + | Error error -> Error.raise_warning error; let placeholder = match kind with @@ -238,9 +238,9 @@ let rec nestable_block_element : match Error.raise_warnings (Reference.read_mod_longident location value) with - | Result.Ok r -> + | Ok r -> { Comment.module_reference = r; module_synopsis = None } :: acc - | Result.Error error -> + | Error error -> Error.raise_warning error; acc) [] modules @@ -278,9 +278,9 @@ let rec nestable_block_element : |> Location.at location in match Error.raise_warnings (Reference.parse_asset href_location href) with - | Result.Ok target -> + | Ok target -> `Media (`Reference target, m, content) |> Location.at location - | Result.Error error -> fallback error) + | Error error -> fallback error) and nestable_block_elements elements = List.map nestable_block_element elements @@ -290,13 +290,13 @@ let tag : Ast.ocamldoc_tag -> ( Comment.block_element with_location, internal_tags_removed with_location ) - Result.result = + result = fun ~location status tag -> if not status.tags_allowed then (* Trigger a warning but do not remove the tag. Avoid turning tags into text that would render the same. *) Error.raise_warning (tags_not_allowed location); - let ok t = Result.Ok (Location.at location (`Tag t)) in + let ok t = Ok (Location.at location (`Tag t)) in match tag with | (`Author _ | `Since _ | `Version _) as tag -> ok tag | `Deprecated content -> ok (`Deprecated (nestable_block_elements content)) @@ -305,9 +305,9 @@ let tag : | `Raise (name, content) -> ( match Error.raise_warnings (Reference.parse location name) with (* TODO: location for just name *) - | Result.Ok target -> + | Ok target -> ok (`Raise (`Reference (target, []), nestable_block_elements content)) - | Result.Error error -> + | Error error -> Error.raise_warning error; let placeholder = `Code_span name in ok (`Raise (placeholder, nestable_block_elements content))) @@ -455,11 +455,11 @@ let top_level_block_elements status ast_elements = ast_elements | { value = `Tag the_tag; location } -> ( match tag ~location status the_tag with - | Result.Ok element -> + | Ok element -> traverse ~top_heading_level (element :: comment_elements_acc) ast_elements - | Result.Error placeholder -> + | Error placeholder -> traverse ~top_heading_level comment_elements_acc (placeholder :: ast_elements)) | { value = `Heading _ as heading; _ } -> @@ -500,8 +500,8 @@ let strip_internal_tags ast : internal_tags_removed with_location list * _ = match Error.raise_warnings (Reference.read_path_longident r_location s) with - | Result.Ok path -> next (`Canonical path) - | Result.Error e -> + | Ok path -> next (`Canonical path) + | Error e -> Error.raise_warning e; loop ~start tags ast' tl)) | ({ diff --git a/src/odoc/asset.ml b/src/odoc/asset.ml index 57222e26d9..e87fa4c7c6 100644 --- a/src/odoc/asset.ml +++ b/src/odoc/asset.ml @@ -1,4 +1,5 @@ -open Or_error +open Odoc_utils +open ResultMonad let compile ~parent_id ~name ~output_dir = let open Odoc_model in diff --git a/src/odoc/asset.mli b/src/odoc/asset.mli index 8ac413ec54..03f6404412 100644 --- a/src/odoc/asset.mli +++ b/src/odoc/asset.mli @@ -1,4 +1,4 @@ -open Or_error +open Odoc_utils val compile : parent_id:string -> diff --git a/src/odoc/bin/main.ml b/src/odoc/bin/main.ml index eea2b62cdc..9452d2d434 100644 --- a/src/odoc/bin/main.ml +++ b/src/odoc/bin/main.ml @@ -4,6 +4,7 @@ output the result to. *) open Odoc_utils +open ResultMonad module List = ListLabels open Odoc_odoc open Compatcmdliner @@ -35,7 +36,7 @@ let convert_directory ?(create = false) () : Fs.Directory.t Arg.conv = let convert_fpath = let parse inp = match Arg.(conv_parser file) inp with - | Ok s -> Result.Ok (Fs.File.of_string s) + | Ok s -> Ok (Fs.File.of_string s) | Error _ as e -> e and print = Fpath.pp in Arg.conv (parse, print) @@ -43,7 +44,7 @@ let convert_fpath = let convert_named_root = let parse inp = match String.cuts inp ~sep:":" with - | [ s1; s2 ] -> Result.Ok (s1, Fs.Directory.of_string s2) + | [ s1; s2 ] -> Ok (s1, Fs.Directory.of_string s2) | _ -> Error (`Msg "") in let print ppf (s, t) = @@ -52,7 +53,7 @@ let convert_named_root = Arg.conv (parse, print) let handle_error = function - | Result.Ok () -> () + | Ok () -> () | Error (`Cli_error msg) -> Printf.eprintf "%s\n%!" msg; exit 2 @@ -84,7 +85,7 @@ module Antichain = struct rest && check rest in - if check l then Result.Ok () + if check l then Ok () else let msg = Format.sprintf "Paths given to all %s options must be disjoint" opt @@ -223,7 +224,6 @@ end = struct let compile hidden directories resolve_fwd_refs dst output_dir package_opt parent_name_opt parent_id_opt open_modules children input warnings_options unique_id short_title = - let open Or_error in let _ = match unique_id with | Some id -> Odoc_model.Names.set_unique_ident id @@ -474,8 +474,6 @@ module Compile_impl = struct end module Indexing = struct - open Or_error - let output_file ~dst marshall = match (dst, marshall) with | Some file, `JSON @@ -576,8 +574,6 @@ module Indexing = struct end module Sidebar = struct - open Or_error - let output_file ~dst marshall = match (dst, marshall) with | Some file, `JSON when not (Fpath.has_ext "json" (Fpath.v file)) -> @@ -667,8 +663,6 @@ end = struct | Some file -> Fs.File.of_string file | None -> Fs.File.(set_ext ".odocl" input) - open Or_error - (** Find the package/library name the output is part of *) let find_root_of_input l o = let l = @@ -1271,7 +1265,7 @@ module Odoc_html_args = struct let convert_remap = let parse inp = match String.cut ~sep:":" inp with - | Some (orig, mapped) -> Result.Ok (orig, mapped) + | Some (orig, mapped) -> Ok (orig, mapped) | _ -> Error (`Msg "Map must be of the form ':https://...'") and print fmt (orig, mapped) = Format.fprintf fmt "%s:%s" orig mapped in Arg.conv (parse, print) @@ -1473,7 +1467,6 @@ module Depends = struct | Some p -> Format.fprintf pp "%a/" fmt_page p let list_dependencies input_file = - let open Or_error in Depends.for_rendering_step (Fs.Directory.of_string input_file) >>= fun depends -> List.iter depends ~f:(fun (root : Odoc_model.Root.t) -> @@ -1557,8 +1550,6 @@ module Targets = struct end module Occurrences = struct - open Or_error - let dst_of_string s = let f = Fs.File.of_string s in if not (Fs.File.has_ext ".odoc-occurrences" f) then @@ -1650,7 +1641,6 @@ end module Odoc_error = struct let errors input = let open Odoc_odoc in - let open Or_error in let input = Fs.File.of_string input in Odoc_file.load input >>= fun unit -> Odoc_model.Error.print_errors unit.warnings; diff --git a/src/odoc/compile.ml b/src/odoc/compile.ml index 70cbadfe83..1f2278714f 100644 --- a/src/odoc/compile.ml +++ b/src/odoc/compile.ml @@ -1,7 +1,7 @@ +open Odoc_utils +open ResultMonad open Odoc_model open Odoc_model.Names -open Or_error -open Odoc_utils (* * Copyright (c) 2014 Leo White diff --git a/src/odoc/compile.mli b/src/odoc/compile.mli index 6447a2f6c0..62e6af2b06 100644 --- a/src/odoc/compile.mli +++ b/src/odoc/compile.mli @@ -14,9 +14,9 @@ * OR IN CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE. *) +open Odoc_utils open Odoc_model open Odoc_model.Paths -open Or_error type package_spec = { package : string; output : Fpath.t } type parent_spec = { diff --git a/src/odoc/depends.ml b/src/odoc/depends.ml index d6c8f521a8..d1eb392431 100644 --- a/src/odoc/depends.ml +++ b/src/odoc/depends.ml @@ -14,8 +14,9 @@ * OR IN CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE. *) +open Odoc_utils +open ResultMonad open StdLabels -open Or_error module Odoc_compile = Compile diff --git a/src/odoc/depends.mli b/src/odoc/depends.mli index 0a773d6cce..1b022a14da 100644 --- a/src/odoc/depends.mli +++ b/src/odoc/depends.mli @@ -14,7 +14,7 @@ * OR IN CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE. *) -open Or_error +open Odoc_utils (** Computes the dependencies required for each step of the pipeline to work correctly on a given input. *) diff --git a/src/odoc/fs.ml b/src/odoc/fs.ml index 7cd189f036..3b79417bc5 100644 --- a/src/odoc/fs.ml +++ b/src/odoc/fs.ml @@ -16,7 +16,6 @@ open Odoc_utils open StdLabels -open Or_error type directory = Fpath.t @@ -51,23 +50,22 @@ module File = struct let create ~directory ~name = match Fpath.of_string name with - | Result.Error (`Msg e) -> invalid_arg ("Odoc.Fs.File.create: " ^ e) - | Result.Ok psuf -> Fpath.(normalize @@ (directory // psuf)) + | Error (`Msg e) -> invalid_arg ("Odoc.Fs.File.create: " ^ e) + | Ok psuf -> Fpath.(normalize @@ (directory // psuf)) let to_string = Fpath.to_string - let segs = Fpath.segs let of_string s = match Fpath.of_string s with - | Result.Error (`Msg e) -> invalid_arg ("Odoc.Fs.File.of_string: " ^ e) - | Result.Ok p -> p + | Error (`Msg e) -> invalid_arg ("Odoc.Fs.File.of_string: " ^ e) + | Ok p -> p let read file = let input_one_shot len ic = let buf = Bytes.create len in really_input ic buf 0 len; close_in ic; - Result.Ok (Bytes.unsafe_to_string buf) + Ok (Bytes.unsafe_to_string buf) in let input_stream file ic = let bsize = @@ -78,9 +76,9 @@ module File = struct let rec loop () = match Buffer.add_channel buf ic bsize with | () -> loop () - | exception End_of_file -> Result.Ok (Buffer.contents buf) + | exception End_of_file -> Ok (Buffer.contents buf) | exception Failure _ -> - Result.Error (`Msg (Printf.sprintf "%s: input too large" file)) + Error (`Msg (Printf.sprintf "%s: input too large" file)) in loop () in @@ -95,8 +93,8 @@ module File = struct | len when len <= Sys.max_string_length -> input_one_shot len ic | len -> let err = Printf.sprintf "%s: file too large (%d bytes)" file len in - Result.Error (`Msg err) - with Sys_error e -> Result.Error (`Msg e) + Error (`Msg err) + with Sys_error e -> Error (`Msg e) let copy ~src ~dst = try @@ -112,7 +110,7 @@ module File = struct loop ()) in Ok (loop ()))) - with Sys_error e -> Result.Error (`Msg e) + with Sys_error e -> Error (`Msg e) let exists file = Sys.file_exists (Fpath.to_string file) @@ -124,16 +122,6 @@ module File = struct | [] -> invalid_arg "Fs.File.of_segs" | "" :: rest -> of_segs_tl (Fpath.v "/") rest | first :: rest -> of_segs_tl (Fpath.v first) rest - - let append_segs path segs = of_segs_tl path segs - - module Table = Hashtbl.Make (struct - type nonrec t = t - - let equal = Fpath.equal - - let hash = Hashtbl.hash - end) end module Directory = struct @@ -145,21 +133,6 @@ module Directory = struct let append = Fpath.append - let make_path p name = - match Fpath.of_string name with - | Result.Error _ as e -> e - | Result.Ok psuf -> - Result.Ok Fpath.(normalize @@ to_dir_path @@ (p // psuf)) - - let reach_from ~dir path = - match make_path dir path with - | Result.Error (`Msg e) -> invalid_arg ("Odoc.Fs.Directory.create: " ^ e) - | Result.Ok path -> - let pstr = Fpath.to_string path in - if Sys.file_exists pstr && not (Sys.is_directory pstr) then - invalid_arg "Odoc.Fs.Directory.create: not a directory"; - path - let contains ~parentdir f = Fpath.is_rooted ~root:parentdir f let compare = Fpath.compare @@ -172,8 +145,8 @@ module Directory = struct let of_string s = match Fpath.of_string s with - | Result.Error (`Msg e) -> invalid_arg ("Odoc.Fs.Directory.of_string: " ^ e) - | Result.Ok p -> Fpath.to_dir_path p + | Error (`Msg e) -> invalid_arg ("Odoc.Fs.Directory.of_string: " ^ e) + | Ok p -> Fpath.to_dir_path p let of_file f = Fpath.to_dir_path f @@ -207,12 +180,4 @@ module Directory = struct in try Ok (fold_files_rec ?ext f acc d) with Stop_iter (`Msg _ as e) -> Error e - - module Table = Hashtbl.Make (struct - type nonrec t = t - - let equal = Fpath.equal - - let hash = Hashtbl.hash - end) end diff --git a/src/odoc/fs.mli b/src/odoc/fs.mli index 935ebc8800..3756a750db 100644 --- a/src/odoc/fs.mli +++ b/src/odoc/fs.mli @@ -1,4 +1,4 @@ -open Or_error +open Odoc_utils (* * Copyright (c) 2016 Thomas Refis @@ -23,8 +23,6 @@ type file = Fpath.t type directory module Directory : sig - open Or_error - type t = directory val dirname : t -> t @@ -33,9 +31,6 @@ module Directory : sig val append : t -> t -> t - val reach_from : dir:t -> string -> t - (** @raise Invalid_argument if [parent/name] exists but is not a directory. *) - val contains : parentdir:t -> file -> bool val compare : t -> t -> int @@ -64,8 +59,6 @@ module Directory : sig (** [fold_files_rec_result ~ext f acc d] recursively folds [f] over the files with extension matching [ext] (defaults to [""]) contained in [d] and its sub directories. Stop as soon as [f] returns [Error _]. *) - - module Table : Hashtbl.S with type key = t end module File : sig @@ -89,8 +82,6 @@ module File : sig val to_string : t -> string - val segs : t -> string list - val read : t -> (string, [> msg ]) result val copy : src:t -> dst:t -> (unit, [> msg ]) result @@ -100,9 +91,4 @@ module File : sig val of_segs : string list -> t (** [of_segs segs] Returns an absolute path if [segs] starts with an empty segment. Raises [Invalid_argument] if [segs] is empty. *) - - val append_segs : t -> string list -> t - (** Append a list of segments to a path. Do not raise. *) - - module Table : Hashtbl.S with type key = t end diff --git a/src/odoc/html_fragment.ml b/src/odoc/html_fragment.ml index 7189f8b1c7..07902c73f1 100644 --- a/src/odoc/html_fragment.ml +++ b/src/odoc/html_fragment.ml @@ -1,5 +1,5 @@ open Odoc_utils -open Or_error +open ResultMonad let from_mld ~xref_base_uri ~resolver ~output ~warnings_options input = (* Internal names, they don't have effect on the output. *) diff --git a/src/odoc/html_fragment.mli b/src/odoc/html_fragment.mli index 78b0d3f465..9bf67c3b3a 100644 --- a/src/odoc/html_fragment.mli +++ b/src/odoc/html_fragment.mli @@ -14,7 +14,7 @@ * OR IN CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE. *) -open Or_error +open Odoc_utils (** Produces html fragment files from a mld file. *) diff --git a/src/odoc/indexing.ml b/src/odoc/indexing.ml index fb2874c2cc..70bde8968b 100644 --- a/src/odoc/indexing.ml +++ b/src/odoc/indexing.ml @@ -1,7 +1,6 @@ open Odoc_utils -open Astring +open ResultMonad open Odoc_json_index -open Or_error open Odoc_model module H = Odoc_model.Paths.Identifier.Hashtbl.Any diff --git a/src/odoc/indexing.mli b/src/odoc/indexing.mli index e1ffab4766..4ebf089a6f 100644 --- a/src/odoc/indexing.mli +++ b/src/odoc/indexing.mli @@ -1,4 +1,4 @@ -open Or_error +open Odoc_utils val compile : [ `JSON | `Marshall ] -> diff --git a/src/odoc/occurrences.ml b/src/odoc/occurrences.ml index 330a50fc4b..655e84fbc4 100644 --- a/src/odoc/occurrences.ml +++ b/src/odoc/occurrences.ml @@ -1,5 +1,5 @@ open Odoc_utils -open Or_error +open ResultMonad let handle_file file ~f = if String.is_prefix ~affix:"impl-" (Fpath.filename file) then @@ -34,9 +34,6 @@ let count ~dst ~warnings_options:_ directories include_hidden = Io_utils.marshal (Fs.File.to_string dst) htbl; Ok () -open Astring -open Or_error - let parse_input_file input = let is_sep = function '\n' | '\r' -> true | _ -> false in Fs.File.read input >>= fun content -> diff --git a/src/odoc/odoc_file.ml b/src/odoc/odoc_file.ml index d07f1cf824..67f9b07098 100644 --- a/src/odoc/odoc_file.ml +++ b/src/odoc/odoc_file.ml @@ -15,8 +15,8 @@ *) open Odoc_utils +open ResultMonad open Odoc_model -open Or_error type unit_content = Lang.Compilation_unit.t diff --git a/src/odoc/odoc_file.mli b/src/odoc/odoc_file.mli index 6f2c39ed58..474c1e886c 100644 --- a/src/odoc/odoc_file.mli +++ b/src/odoc/odoc_file.mli @@ -16,8 +16,8 @@ (** Load and save [.odoc] and [.odocl] files. *) +open Odoc_utils open Odoc_model -open Or_error (** Either a page or a module or something else. *) type content = diff --git a/src/odoc/odoc_link.ml b/src/odoc/odoc_link.ml index 141304c8ba..f51f1fa144 100644 --- a/src/odoc/odoc_link.ml +++ b/src/odoc/odoc_link.ml @@ -1,4 +1,5 @@ -open Or_error +open Odoc_utils +open ResultMonad let link_page ~resolver ~filename page = let env = Resolver.build_env_for_page resolver page in diff --git a/src/odoc/or_error.ml b/src/odoc/or_error.ml deleted file mode 100644 index 6eaae71b4c..0000000000 --- a/src/odoc/or_error.ml +++ /dev/null @@ -1,9 +0,0 @@ -type ('a, 'e) result = ('a, 'e) Result.result = Ok of 'a | Error of 'e - -type msg = [ `Msg of string ] - -let ( >>= ) r f = match r with Ok v -> f v | Error _ as e -> e - -let rec fold_list f acc = function - | [] -> Ok acc - | hd :: tl -> f acc hd >>= fun acc -> fold_list f acc tl diff --git a/src/odoc/or_error.mli b/src/odoc/or_error.mli deleted file mode 100644 index 67a51c6f7e..0000000000 --- a/src/odoc/or_error.mli +++ /dev/null @@ -1,9 +0,0 @@ -(** Re-export for compatibility with 4.02 *) -type ('a, 'e) result = ('a, 'e) Result.result = Ok of 'a | Error of 'e - -type msg = [ `Msg of string ] - -val ( >>= ) : ('a, 'e) result -> ('a -> ('b, 'e) result) -> ('b, 'e) result - -val fold_list : - ('acc -> 'a -> ('acc, 'e) result) -> 'acc -> 'a list -> ('acc, 'e) result diff --git a/src/odoc/rendering.ml b/src/odoc/rendering.ml index cccae2143b..1574e132f8 100644 --- a/src/odoc/rendering.ml +++ b/src/odoc/rendering.ml @@ -1,6 +1,6 @@ open Odoc_utils +open ResultMonad open Odoc_document -open Or_error open Odoc_model let prepare ~extra_suffix ~output_dir filename = diff --git a/src/odoc/rendering.mli b/src/odoc/rendering.mli index 69c7baa704..859d20d6f2 100644 --- a/src/odoc/rendering.mli +++ b/src/odoc/rendering.mli @@ -1,5 +1,5 @@ +open Odoc_utils open Odoc_document -open Or_error val render_odoc : resolver:Resolver.t -> @@ -42,7 +42,7 @@ val generate_asset_odoc : extra_suffix:string option -> 'a -> Fs.file -> - (unit, [> Or_error.msg ]) result + (unit, [> msg ]) result val targets_odoc : resolver:Resolver.t -> @@ -62,4 +62,4 @@ val targets_source_odoc : extra:'a -> source_file:Fpath.t -> Fs.file -> - (unit, [> Or_error.msg ]) result + (unit, [> msg ]) result diff --git a/src/odoc/resolver.ml b/src/odoc/resolver.ml index 991d91b2ce..0e7eb188c4 100644 --- a/src/odoc/resolver.ml +++ b/src/odoc/resolver.ml @@ -32,7 +32,7 @@ which will generally fix this issue. *) open Odoc_utils -open Or_error +open ResultMonad type named_root = string * Fs.Directory.t module Named_roots : sig diff --git a/src/odoc/sidebar.ml b/src/odoc/sidebar.ml index eaed81956c..c6e0cbaeaa 100644 --- a/src/odoc/sidebar.ml +++ b/src/odoc/sidebar.ml @@ -1,5 +1,5 @@ -open Or_error open Odoc_utils +open ResultMonad let compile_to_json ~output sidebar = let json = Odoc_html.Sidebar.to_json sidebar in diff --git a/src/odoc/source.ml b/src/odoc/source.ml index fa1d79418c..aee313b15d 100644 --- a/src/odoc/source.ml +++ b/src/odoc/source.ml @@ -1,5 +1,6 @@ +open Odoc_utils +open ResultMonad open Odoc_model -open Or_error let resolve_and_substitute ~resolver ~make_root ~source_id input_file = let filename = Fs.File.to_string input_file in diff --git a/src/parser/dune b/src/parser/dune index e7a3d1ce4c..7d930d123d 100644 --- a/src/parser/dune +++ b/src/parser/dune @@ -9,4 +9,4 @@ (backend bisect_ppx)) (flags (:standard -w -50)) - (libraries astring result camlp-streams)) + (libraries astring camlp-streams)) diff --git a/src/utils/dune b/src/utils/dune index 598934910b..0d749d5316 100644 --- a/src/utils/dune +++ b/src/utils/dune @@ -1,4 +1,4 @@ (library (name odoc_utils) (public_name odoc.odoc_utils) - (libraries result astring)) + (libraries astring)) diff --git a/src/utils/odoc_list.ml b/src/utils/odoc_list.ml index 36abfa6238..057a243d77 100644 --- a/src/utils/odoc_list.ml +++ b/src/utils/odoc_list.ml @@ -8,6 +8,7 @@ let rec concat_map_sep ~sep ~f = function let tl = concat_map_sep ~sep ~f xs in hd @ (sep :: tl) +(* Since 4.10 *) let concat_map f l = let rec aux f acc = function | [] -> rev acc @@ -17,28 +18,29 @@ let concat_map f l = in aux f [] l -let rec filter_map acc f = function - | hd :: tl -> - let acc = match f hd with Some x -> x :: acc | None -> acc in - filter_map acc f tl - | [] -> List.rev acc - -let filter_map f x = filter_map [] f x - (** @raise Failure if the list is empty. *) let rec last = function | [] -> failwith "Odoc_utils.List.last" | [ x ] -> x | _ :: tl -> last tl -(* From ocaml/ocaml *) +(* Since 4.10. Copied ocaml/ocaml *) let rec find_map f = function | [] -> None | x :: l -> ( match f x with Some _ as result -> result | None -> find_map f l) -let rec find_opt p = function - | [] -> None - | x :: l -> if p x then Some x else find_opt p l - +(* Since 5.1 *) let is_empty = function [] -> true | _ :: _ -> false + +let rec skip_until ~p = function + | [] -> [] + | h :: t -> if p h then t else skip_until ~p t + +let split_at ~f lst = + let rec loop acc = function + | hd :: _ as rest when f hd -> (List.rev acc, rest) + | [] -> (List.rev acc, []) + | hd :: tl -> loop (hd :: acc) tl + in + loop [] lst diff --git a/src/utils/odoc_utils.ml b/src/utils/odoc_utils.ml index 2f8c11888f..c3edc618ad 100644 --- a/src/utils/odoc_utils.ml +++ b/src/utils/odoc_utils.ml @@ -1,80 +1,24 @@ -(** Re-export for compatibility with 4.02. *) -type ('a, 'b) result = ('a, 'b) Result.result = Ok of 'a | Error of 'b +type msg = [ `Msg of string ] (** The [result] type and a bind operator. This module is meant to be opened. *) module ResultMonad = struct - (** Re-export for compat *) - type ('a, 'b) result = ('a, 'b) Result.result = Ok of 'a | Error of 'b - let map_error f = function Ok _ as ok -> ok | Error e -> Error (f e) let of_option ~error = function Some x -> Ok x | None -> Error error - let bind m f = match m with Ok x -> f x | Error _ as e -> e - - let ( >>= ) = bind + let ( >>= ) = Result.bind end (** A bind operator for the [option] type. This module is meant to be opened. *) module OptionMonad = struct (* The error case become [None], the error value is ignored. *) - let of_result = function Result.Ok x -> Some x | Error _ -> None - - let return x = Some x + let of_result = function Ok x -> Some x | Error _ -> None - let bind m f = match m with Some x -> f x | None -> None - - let ( >>= ) = bind -end - -module EitherMonad = struct - type ('a, 'b) t = Left of 'a | Right of 'b - - let return x = Right x - - let return_left x = Left x - - let bind m f = match m with Right x -> f x | Left y -> Left y - - let bind_left m f = match m with Left x -> f x | Right y -> Right y - - let ( >>= ) = bind - - let of_option ~left = function Some x -> Right x | None -> Left left - - let of_result = function Result.Ok x -> Right x | Error y -> Left y + let ( >>= ) = Option.bind end module List = Odoc_list -module Option = struct - let map f = function None -> None | Some x -> Some (f x) - - let is_some = function None -> false | Some _ -> true -end - -module Result = struct - include Result - - let join = function Ok r -> r | Error _ as e -> e -end - -module Fun = struct - exception Finally_raised of exn - - let protect ~(finally : unit -> unit) work = - let finally_no_exn () = - try finally () with e -> raise (Finally_raised e) - in - match work () with - | result -> - finally_no_exn (); - result - | exception work_exn -> - finally_no_exn (); - raise work_exn -end - module Tree = Tree module Forest = Tree.Forest module Json = Json diff --git a/src/xref2/env.ml b/src/xref2/env.ml index c3f5b28ecc..0ef9963fe3 100644 --- a/src/xref2/env.ml +++ b/src/xref2/env.ml @@ -479,7 +479,7 @@ type 'a scope = { root : string -> t -> 'a option; } -type 'a maybe_ambiguous = ('a, [ 'a amb_err | `Not_found ]) Result.result +type 'a maybe_ambiguous = ('a, [ 'a amb_err | `Not_found ]) result let make_scope ?(root = fun _ _ -> None) ?check (filter : _ -> ([< Component.Element.any ] as 'a) option) : 'a scope = @@ -503,12 +503,10 @@ let lookup_by_name scope name env = with | ([ x ] as results), Some c -> ( record_lookup_results env results; - match c env x with - | Some (`Ambiguous _ as e) -> Result.Error e - | None -> Result.Ok x) + match c env x with Some (`Ambiguous _ as e) -> Error e | None -> Ok x) | ([ x ] as results), None -> record_lookup_results env results; - Result.Ok x + Ok x | (x :: tl as results), _ -> record_lookup_results env results; Error (`Ambiguous (x, tl)) diff --git a/src/xref2/env.mli b/src/xref2/env.mli index d43fe8f9f3..fdb1b36bd7 100644 --- a/src/xref2/env.mli +++ b/src/xref2/env.mli @@ -2,7 +2,6 @@ open Odoc_model open Odoc_model.Paths -open Odoc_utils type lookup_unit_result = Forward_reference | Found of Lang.Compilation_unit.t @@ -116,7 +115,7 @@ type 'a scope constraint 'a = [< Component.Element.any ] (** Target of a lookup *) type 'a maybe_ambiguous = - ('a, [ `Ambiguous of 'a * 'a list | `Not_found ]) Result.result + ('a, [ `Ambiguous of 'a * 'a list | `Not_found ]) result val lookup_by_name : 'a scope -> string -> t -> 'a maybe_ambiguous (** Lookup an element in Env depending on the given [scope]. Return diff --git a/src/xref2/expand_tools.ml b/src/xref2/expand_tools.ml index c452ff64ab..81d0280782 100644 --- a/src/xref2/expand_tools.ml +++ b/src/xref2/expand_tools.ml @@ -25,7 +25,7 @@ let handle_expansion env id expansion = (env', Subst.module_type_expr subst expr) in let rec expand id env expansion : - (Env.t * Component.ModuleType.simple_expansion, _) Result.result = + (Env.t * Component.ModuleType.simple_expansion, _) result = match expansion with | Tools.Signature sg -> Ok diff --git a/src/xref2/link.ml b/src/xref2/link.ml index bb3d0eec90..f8c55a9d5f 100644 --- a/src/xref2/link.ml +++ b/src/xref2/link.ml @@ -761,7 +761,7 @@ and handle_fragments env id sg subs = List.fold_left (fun (sg_res, subs) lsub -> match (sg_res, lsub) with - | Result.Ok sg, ModuleEq (frag, decl) -> + | Ok sg, ModuleEq (frag, decl) -> let frag' = match frag with | `Resolved f -> diff --git a/src/xref2/ref_tools.ml b/src/xref2/ref_tools.ml index b00b73d444..7fae1614e6 100644 --- a/src/xref2/ref_tools.ml +++ b/src/xref2/ref_tools.ml @@ -39,8 +39,7 @@ type label_parent_lookup_result = type fragment_type_parent_lookup_result = [ `S of signature_lookup_result | `T of datatype_lookup_result ] -type 'a ref_result = - ('a, Errors.Tools_error.reference_lookup_error) Result.result +type 'a ref_result = ('a, Errors.Tools_error.reference_lookup_error) result (** The result type for every functions in this module. *) let kind_of_find_result = function diff --git a/src/xref2/ref_tools.mli b/src/xref2/ref_tools.mli index 5b0924641f..24366c70bb 100644 --- a/src/xref2/ref_tools.mli +++ b/src/xref2/ref_tools.mli @@ -5,8 +5,7 @@ type module_lookup_result = type asset_lookup_result = Resolved.Asset.t -type 'a ref_result = - ('a, Errors.Tools_error.reference_lookup_error) Result.result +type 'a ref_result = ('a, Errors.Tools_error.reference_lookup_error) result val resolve_module_reference : Env.t -> diff --git a/src/xref2/tools.ml b/src/xref2/tools.ml index 82eac8ca8d..fbd85602b6 100644 --- a/src/xref2/tools.ml +++ b/src/xref2/tools.ml @@ -214,25 +214,23 @@ open Errors.Tools_error type resolve_module_result = ( Cpath.Resolved.module_ * Component.Module.t Component.Delayed.t, simple_module_lookup_error ) - Result.result + result type resolve_module_type_result = ( Cpath.Resolved.module_type * Component.ModuleType.t, simple_module_type_lookup_error ) - Result.result + result type resolve_type_result = - ( Cpath.Resolved.type_ * Find.careful_type, - simple_type_lookup_error ) - Result.result + (Cpath.Resolved.type_ * Find.careful_type, simple_type_lookup_error) result type resolve_value_result = - (Cpath.Resolved.value * Find.value, simple_value_lookup_error) Result.result + (Cpath.Resolved.value * Find.value, simple_value_lookup_error) result type resolve_class_type_result = ( Cpath.Resolved.class_type * Find.careful_class, simple_type_lookup_error ) - Result.result + result type ('a, 'b, 'c) sig_map = { type_ : 'a; module_ : 'b; module_type : 'c } @@ -285,7 +283,7 @@ module LookupModuleMemo = MakeMemo (struct type result = ( Component.Module.t Component.Delayed.t, simple_module_lookup_error ) - Result.result + Result.t let equal = ( = ) @@ -298,7 +296,7 @@ module LookupParentMemo = MakeMemo (struct type result = ( Component.Signature.t * Component.Substitution.t, [ `Parent of parent_lookup_error ] ) - Result.result + Result.t let equal = ( = ) @@ -328,7 +326,7 @@ end) module ExpansionOfModuleMemo = MakeMemo (struct type t = Cpath.Resolved.module_ - type result = (expansion, expansion_of_module_error) Result.result + type result = (expansion, expansion_of_module_error) Result.t let equal = ( = ) @@ -552,9 +550,8 @@ and handle_class_type_lookup id p sg = and lookup_module_gpath : Env.t -> Odoc_model.Paths.Path.Resolved.Module.t -> - ( Component.Module.t Component.Delayed.t, - simple_module_lookup_error ) - Result.result = + (Component.Module.t Component.Delayed.t, simple_module_lookup_error) result + = fun env path -> match path with | `Identifier i -> @@ -589,9 +586,8 @@ and lookup_module_gpath : and lookup_module : Env.t -> Cpath.Resolved.module_ -> - ( Component.Module.t Component.Delayed.t, - simple_module_lookup_error ) - Result.result = + (Component.Module.t Component.Delayed.t, simple_module_lookup_error) result + = fun env' path' -> let lookup env (path : ExpansionOfModuleMemo.M.key) = match path with @@ -630,7 +626,7 @@ and lookup_module : and lookup_module_type_gpath : Env.t -> Odoc_model.Paths.Path.Resolved.ModuleType.t -> - (Component.ModuleType.t, simple_module_type_lookup_error) Result.result = + (Component.ModuleType.t, simple_module_type_lookup_error) result = fun env path -> match path with | `Identifier i -> @@ -655,7 +651,7 @@ and lookup_module_type_gpath : and lookup_module_type : Env.t -> Cpath.Resolved.module_type -> - (Component.ModuleType.t, simple_module_type_lookup_error) Result.result = + (Component.ModuleType.t, simple_module_type_lookup_error) result = fun env path -> let lookup env = match path with @@ -682,7 +678,7 @@ and lookup_parent : Cpath.Resolved.parent -> ( Component.Signature.t * Component.Substitution.t, [ `Parent of parent_lookup_error ] ) - Result.result = + result = fun env' parent' -> let lookup env parent = match parent with @@ -714,7 +710,7 @@ and lookup_parent_gpath : Odoc_model.Paths.Path.Resolved.Module.t -> ( Component.Signature.t * Component.Substitution.t, [ `Parent of parent_lookup_error ] ) - Result.result = + result = fun env parent -> lookup_module_gpath env parent |> map_error (fun e -> `Parent (`Parent_module e)) @@ -728,7 +724,7 @@ and lookup_parent_gpath : and lookup_type_gpath : Env.t -> Odoc_model.Paths.Path.Resolved.Type.t -> - (Find.careful_type, simple_type_lookup_error) Result.result = + (Find.careful_type, simple_type_lookup_error) result = fun env p -> let do_type p name = lookup_parent_gpath env p @@ -774,7 +770,7 @@ and lookup_type_gpath : and lookup_value_gpath : Env.t -> Odoc_model.Paths.Path.Resolved.Value.t -> - (Find.value, simple_value_lookup_error) Result.result = + (Find.value, simple_value_lookup_error) result = fun env p -> let do_value p name = lookup_parent_gpath env p @@ -797,7 +793,7 @@ and lookup_value_gpath : and lookup_class_type_gpath : Env.t -> Odoc_model.Paths.Path.Resolved.ClassType.t -> - (Find.careful_class, simple_type_lookup_error) Result.result = + (Find.careful_class, simple_type_lookup_error) result = fun env p -> let do_type p name = lookup_parent_gpath env p @@ -831,7 +827,7 @@ and lookup_class_type_gpath : and lookup_type : Env.t -> Cpath.Resolved.type_ -> - (Find.careful_type, simple_type_lookup_error) Result.result = + (Find.careful_type, simple_type_lookup_error) result = fun env p -> let do_type p name = lookup_parent env p |> map_error (fun e -> (e :> simple_type_lookup_error)) @@ -862,9 +858,7 @@ and lookup_type : res and lookup_value : - Env.t -> - Cpath.Resolved.value -> - (_, simple_value_lookup_error) Result.result = + Env.t -> Cpath.Resolved.value -> (_, simple_value_lookup_error) result = fun env p -> match p with | `Value (p, id) -> @@ -878,7 +872,7 @@ and lookup_value : and lookup_class_type : Env.t -> Cpath.Resolved.class_type -> - (Find.careful_class, simple_type_lookup_error) Result.result = + (Find.careful_class, simple_type_lookup_error) result = fun env p -> let do_type p name = lookup_parent env p |> map_error (fun e -> (e :> simple_type_lookup_error)) @@ -1522,9 +1516,8 @@ and reresolve_parent : Env.t -> Cpath.Resolved.parent -> Cpath.Resolved.parent = and module_type_expr_of_module_decl : Env.t -> Component.Module.decl -> - ( Component.ModuleType.expr, - simple_module_type_expr_of_module_error ) - Result.result = + (Component.ModuleType.expr, simple_module_type_expr_of_module_error) result + = fun env decl -> match decl with | Component.Module.Alias (`Resolved r, _) -> @@ -1545,16 +1538,15 @@ and module_type_expr_of_module_decl : and module_type_expr_of_module : Env.t -> Component.Module.t -> - ( Component.ModuleType.expr, - simple_module_type_expr_of_module_error ) - Result.result = + (Component.ModuleType.expr, simple_module_type_expr_of_module_error) result + = fun env m -> module_type_expr_of_module_decl env m.type_ and expansion_of_module_path : Env.t -> strengthen:bool -> Cpath.module_ -> - (expansion, expansion_of_module_error) Result.result = + (expansion, expansion_of_module_error) result = fun env ~strengthen path -> match resolve_module env path with | Ok (p', m) -> ( @@ -1578,7 +1570,7 @@ and handle_signature_with_subs : Env.t -> Component.Signature.t -> Component.ModuleType.substitution list -> - (Component.Signature.t, expansion_of_module_error) Result.result = + (Component.Signature.t, expansion_of_module_error) result = fun env sg subs -> let open Odoc_utils.ResultMonad in List.fold_left @@ -1586,7 +1578,7 @@ and handle_signature_with_subs : (Ok sg) subs and assert_not_functor : type err. - expansion -> (Component.Signature.t, err) Result.result = function + expansion -> (Component.Signature.t, err) result = function | Signature sg -> Ok sg | _ -> assert false @@ -1605,7 +1597,7 @@ and signature_of_module_type_of : Env.t -> Component.ModuleType.type_of_desc -> original_path:Cpath.module_ -> - (expansion, expansion_of_module_error) Result.result = + (expansion, expansion_of_module_error) result = fun env desc ~original_path:_ -> let p, strengthen = match desc with ModPath p -> (p, false) | StructInclude p -> (p, true) @@ -1625,7 +1617,7 @@ and signature_of_module_type_of : and signature_of_u_module_type_expr : Env.t -> Component.ModuleType.U.expr -> - (Component.Signature.t, expansion_of_module_error) Result.result = + (Component.Signature.t, expansion_of_module_error) result = fun env m -> match m with | Component.ModuleType.U.Path p -> ( @@ -1655,7 +1647,7 @@ and expansion_of_simple_expansion : and expansion_of_module_type_expr : Env.t -> Component.ModuleType.expr -> - (expansion, expansion_of_module_error) Result.result = + (expansion, expansion_of_module_error) result = fun env m -> match m with | Component.ModuleType.Path { p_expansion = Some e; _ } -> @@ -1685,7 +1677,7 @@ and expansion_of_module_type_expr : and expansion_of_module_type : Env.t -> Component.ModuleType.t -> - (expansion, expansion_of_module_error) Result.result = + (expansion, expansion_of_module_error) result = fun env m -> match m.expr with | None -> Error `OpaqueModule @@ -1694,7 +1686,7 @@ and expansion_of_module_type : and expansion_of_module_decl : Env.t -> Component.Module.decl -> - (expansion, expansion_of_module_error) Result.result = + (expansion, expansion_of_module_error) result = fun env decl -> match decl with (* | Component.Module.Alias (_, Some e) -> Ok (expansion_of_simple_expansion e) *) @@ -1703,9 +1695,8 @@ and expansion_of_module_decl : | Component.Module.ModuleType expr -> expansion_of_module_type_expr env expr and expansion_of_module : - Env.t -> - Component.Module.t -> - (expansion, expansion_of_module_error) Result.result = + Env.t -> Component.Module.t -> (expansion, expansion_of_module_error) result + = fun env m -> expansion_of_module_decl env m.type_ >>= function | Signature sg -> @@ -1723,7 +1714,7 @@ and expansion_of_module_cached : Env.t -> Cpath.Resolved.module_ -> Component.Module.t -> - (expansion, expansion_of_module_error) Result.result = + (expansion, expansion_of_module_error) result = fun env' path m -> let id = path in let run env _id = expansion_of_module env m in @@ -1773,7 +1764,7 @@ and fragmap : Env.t -> Component.ModuleType.substitution -> Component.Signature.t -> - (Component.Signature.t, expansion_of_module_error) Result.result = + (Component.Signature.t, expansion_of_module_error) result = fun env sub sg -> (* Used when we haven't finished the substitution. For example, if the substitution is `M.t = u`, this function is used to map the declaration @@ -2117,9 +2108,8 @@ and find_module_with_replacement : Env.t -> Component.Signature.t -> ModuleName.t -> - ( Component.Module.t Component.Delayed.t, - simple_module_lookup_error ) - Result.result = + (Component.Module.t Component.Delayed.t, simple_module_lookup_error) result + = fun env sg name -> match Find.careful_module_in_sig sg name with | Some (`FModule (_, m)) -> Ok (Component.Delayed.put_val m) @@ -2133,7 +2123,7 @@ and find_module_type_with_replacement : ModuleTypeName.t -> ( Component.ModuleType.t Component.Delayed.t, simple_module_type_lookup_error ) - Result.result = + result = fun _env sg name -> match Find.careful_module_type_in_sig sg name with | Some (`FModuleType (_, m)) -> Ok (Component.Delayed.put_val m) diff --git a/src/xref2/tools.mli b/src/xref2/tools.mli index b5d17fe7bb..0a0c78c886 100644 --- a/src/xref2/tools.mli +++ b/src/xref2/tools.mli @@ -46,23 +46,21 @@ type expansion = val lookup_module : Env.t -> Cpath.Resolved.module_ -> - ( Component.Module.t Component.Delayed.t, - simple_module_lookup_error ) - Result.result + (Component.Module.t Component.Delayed.t, simple_module_lookup_error) result (** [lookup_module ~mark_substituted env p] takes a resolved module cpath [p] and an environment and returns a representation of the module. *) val lookup_module_type : Env.t -> Cpath.Resolved.module_type -> - (Component.ModuleType.t, simple_module_type_lookup_error) Result.result + (Component.ModuleType.t, simple_module_type_lookup_error) result (** [lookup_module_type ~mark_substituted env p] takes a resolved module type cpath and an environment and returns a representation of the module type. *) val lookup_type : Env.t -> Cpath.Resolved.type_ -> - (Find.careful_type, simple_type_lookup_error) Result.result + (Find.careful_type, simple_type_lookup_error) result (** [lookup_type env p] takes a resolved type path and an environment and returns a representation of the type. The type can be an ordinary type, a class type or a class. If the type has been destructively substituted, the @@ -71,7 +69,7 @@ val lookup_type : val lookup_class_type : Env.t -> Cpath.Resolved.class_type -> - (Find.careful_class, simple_type_lookup_error) Result.result + (Find.careful_class, simple_type_lookup_error) result (** [lookup_class_type env p] takes a resolved class type path and an environment and returns a representation of the class type. The type can be a class type or a class. *) @@ -81,7 +79,7 @@ val resolve_module : Cpath.module_ -> ( Cpath.Resolved.module_ * Component.Module.t Component.Delayed.t, simple_module_lookup_error ) - Result.result + result (** [resolve_module ~mark_substituted ~add_canonical env p] takes an unresolved module path and an environment and returns a tuple of the resolved module path alongside a representation of the module itself. *) @@ -91,7 +89,7 @@ val resolve_module_type : Cpath.module_type -> ( Cpath.Resolved.module_type * Component.ModuleType.t, simple_module_type_lookup_error ) - Result.result + result (** [resolve_module_type ~mark_substituted ~add_canonical env p] takes an unresolved module type path and an environment and returns a tuple of the resolved module type path alongside a representation of the module type @@ -100,9 +98,7 @@ val resolve_module_type : val resolve_type : Env.t -> Cpath.type_ -> - ( Cpath.Resolved.type_ * Find.careful_type, - simple_type_lookup_error ) - Result.result + (Cpath.Resolved.type_ * Find.careful_type, simple_type_lookup_error) result (** [resolve_type env p] takes an unresolved type path and an environment and returns a tuple of the resolved type path alongside a representation of the type itself. As with {!val:lookup_type} the returned type is either the @@ -114,7 +110,7 @@ val resolve_class_type : Cpath.class_type -> ( Cpath.Resolved.class_type * Find.careful_class, simple_type_lookup_error ) - Result.result + result (** [resolve_class_type env p] takes an unresolved class type path and an environment and returns a tuple of the resolved class type path alongside a representation of the class type itself. As with {!val:lookup_type} the @@ -132,27 +128,27 @@ val resolve_class_type : val resolve_module_path : Env.t -> Cpath.module_ -> - (Cpath.Resolved.module_, simple_module_lookup_error) Result.result + (Cpath.Resolved.module_, simple_module_lookup_error) result val resolve_module_type_path : Env.t -> Cpath.module_type -> - (Cpath.Resolved.module_type, simple_module_type_lookup_error) Result.result + (Cpath.Resolved.module_type, simple_module_type_lookup_error) result val resolve_type_path : Env.t -> Cpath.type_ -> - (Cpath.Resolved.type_, simple_type_lookup_error) Result.result + (Cpath.Resolved.type_, simple_type_lookup_error) result val resolve_value_path : Env.t -> Cpath.value -> - (Cpath.Resolved.value, simple_value_lookup_error) Result.result + (Cpath.Resolved.value, simple_value_lookup_error) result val resolve_class_type_path : Env.t -> Cpath.class_type -> - (Cpath.Resolved.class_type, simple_type_lookup_error) Result.result + (Cpath.Resolved.class_type, simple_type_lookup_error) result (** {2 Re-resolve functions} *) @@ -203,24 +199,21 @@ val get_module_type_path_modifiers : val prefix_signature : Cpath.Resolved.parent * Component.Signature.t -> Component.Signature.t -val assert_not_functor : - expansion -> (Component.Signature.t, 'err) Result.result +val assert_not_functor : expansion -> (Component.Signature.t, 'err) result val expansion_of_module_path : Env.t -> strengthen:bool -> Cpath.module_ -> - (expansion, expansion_of_module_error) Result.result + (expansion, expansion_of_module_error) result val expansion_of_module : - Env.t -> - Component.Module.t -> - (expansion, expansion_of_module_error) Result.result + Env.t -> Component.Module.t -> (expansion, expansion_of_module_error) result val expansion_of_module_type : Env.t -> Component.ModuleType.t -> - (expansion, expansion_of_module_error) Result.result + (expansion, expansion_of_module_error) result val class_signature_of_class_type : Env.t -> Component.ClassType.t -> Component.ClassSignature.t option @@ -233,7 +226,7 @@ val class_signature_of_class : val expansion_of_module_type_expr : Env.t -> Component.ModuleType.expr -> - (expansion, expansion_of_module_error) Result.result + (expansion, expansion_of_module_error) result (** The following functions are use for the resolution of {{!type:Odoc_model.Paths.Fragment.t}Fragments} Whilst resolving fragments it is necessary to process them in order, applying the 'with' expression of @@ -247,7 +240,7 @@ val expansion_of_module_type_expr : val signature_of_u_module_type_expr : Env.t -> Component.ModuleType.U.expr -> - (Component.Signature.t, expansion_of_module_error) Result.result + (Component.Signature.t, expansion_of_module_error) result (** The following functions are use for the resolution of {{!type:Odoc_model.Paths.Fragment.t}Fragments} Whilst resolving fragments it is necessary to process them in order, applying the 'with' expression of @@ -320,7 +313,7 @@ val fragmap : Env.t -> Component.ModuleType.substitution -> Component.Signature.t -> - (Component.Signature.t, expansion_of_module_error) Result.result + (Component.Signature.t, expansion_of_module_error) result (** [fragmap ~mark_substituted env sub sg] takes an environment [env] and signature [sg], and a fragment substitution (e.g. [ModuleSubst] to destructively substitute a module), and returns the substituted signature. @@ -330,7 +323,7 @@ val handle_signature_with_subs : Env.t -> Component.Signature.t -> Component.ModuleType.substitution list -> - (Component.Signature.t, expansion_of_module_error) Result.result + (Component.Signature.t, expansion_of_module_error) result (** [handle_signature_with_subs ~mark_substituted env sg subs] applies the fragment modifiers [subs], in order, to the supplied signature [sg]. *) diff --git a/test/odoc_print/odoc_print.ml b/test/odoc_print/odoc_print.ml index f29a1e0f49..40bb8a38cd 100644 --- a/test/odoc_print/odoc_print.ml +++ b/test/odoc_print/odoc_print.ml @@ -1,7 +1,8 @@ (** Print .odocl files. *) +open Odoc_utils +open ResultMonad open Odoc_odoc -open Odoc_odoc.Or_error open Odoc_model_desc let print_json_desc desc x = diff --git a/test/odoc_print/print_index.ml b/test/odoc_print/print_index.ml index 0f104ca137..69451fdd86 100644 --- a/test/odoc_print/print_index.ml +++ b/test/odoc_print/print_index.ml @@ -4,7 +4,7 @@ let run inp = let inp = Fpath.v inp in let index = Odoc_odoc.Odoc_file.load_index inp |> function - | Result.Ok x -> x + | Ok x -> x | _ -> failwith "failed to load index" in let rec tree_to_yojson diff --git a/test/xref2/resolve/test.md b/test/xref2/resolve/test.md index e9e8100065..8f2288adf7 100644 --- a/test/xref2/resolve/test.md +++ b/test/xref2/resolve/test.md @@ -62,7 +62,7 @@ which takes a `Model.Lang.Signature.t` and runs the resolve mapping functions over the tree. For this example the interesting point comes when we get to looking at the manifest for type `u`. We see that we have a `Constr` that has a path in it, so we look up the component from the path via the function -`Tools.lookup_type_from_model_path`. This returns us a `Result.result` +`Tools.lookup_type_from_model_path`. This returns us a `result` containing the resolved path and the `Component.Type.t` that represents the type `t`. We don't particularly care about this, but the returned path we use in place of the path we had before.