Skip to content

Commit c032c44

Browse files
Julowjonludlam
authored andcommitted
Remove Or_error in favor of Odoc_utils
1 parent cd5353e commit c032c44

26 files changed

+32
-55
lines changed

src/odoc/asset.ml

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,5 @@
1-
open Or_error
1+
open Odoc_utils
2+
open ResultMonad
23

34
let compile ~parent_id ~name ~output_dir =
45
let open Odoc_model in

src/odoc/asset.mli

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,4 @@
1-
open Or_error
1+
open Odoc_utils
22

33
val compile :
44
parent_id:string ->

src/odoc/bin/main.ml

Lines changed: 1 addition & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -4,6 +4,7 @@
44
output the result to. *)
55

66
open Odoc_utils
7+
open ResultMonad
78
module List = ListLabels
89
open Odoc_odoc
910
open Cmdliner
@@ -225,7 +226,6 @@ end = struct
225226
let compile hidden directories resolve_fwd_refs dst output_dir package_opt
226227
parent_name_opt parent_id_opt open_modules children input warnings_options
227228
unique_id short_title =
228-
let open Or_error in
229229
let _ =
230230
match unique_id with
231231
| Some id -> Odoc_model.Names.set_unique_ident id
@@ -476,8 +476,6 @@ module Compile_impl = struct
476476
end
477477

478478
module Indexing = struct
479-
open Or_error
480-
481479
let output_file ~dst marshall =
482480
match (dst, marshall) with
483481
| Some file, `JSON
@@ -578,8 +576,6 @@ module Indexing = struct
578576
end
579577

580578
module Sidebar = struct
581-
open Or_error
582-
583579
let output_file ~dst marshall =
584580
match (dst, marshall) with
585581
| Some file, `JSON when not (Fpath.has_ext "json" (Fpath.v file)) ->
@@ -669,8 +665,6 @@ end = struct
669665
| Some file -> Fs.File.of_string file
670666
| None -> Fs.File.(set_ext ".odocl" input)
671667

672-
open Or_error
673-
674668
(** Find the package/library name the output is part of *)
675669
let find_root_of_input l o =
676670
let l =
@@ -1475,7 +1469,6 @@ module Depends = struct
14751469
| Some p -> Format.fprintf pp "%a/" fmt_page p
14761470

14771471
let list_dependencies input_file =
1478-
let open Or_error in
14791472
Depends.for_rendering_step (Fs.Directory.of_string input_file)
14801473
>>= fun depends ->
14811474
List.iter depends ~f:(fun (root : Odoc_model.Root.t) ->
@@ -1559,8 +1552,6 @@ module Targets = struct
15591552
end
15601553

15611554
module Occurrences = struct
1562-
open Or_error
1563-
15641555
let dst_of_string s =
15651556
let f = Fs.File.of_string s in
15661557
if not (Fs.File.has_ext ".odoc-occurrences" f) then
@@ -1652,7 +1643,6 @@ end
16521643
module Odoc_error = struct
16531644
let errors input =
16541645
let open Odoc_odoc in
1655-
let open Or_error in
16561646
let input = Fs.File.of_string input in
16571647
Odoc_file.load input >>= fun unit ->
16581648
Odoc_model.Error.print_errors unit.warnings;

src/odoc/compile.ml

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,7 @@
1+
open Odoc_utils
2+
open ResultMonad
13
open Odoc_model
24
open Odoc_model.Names
3-
open Or_error
4-
open Odoc_utils
55

66
(*
77
* Copyright (c) 2014 Leo White <[email protected]>

src/odoc/compile.mli

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -14,9 +14,9 @@
1414
* OR IN CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE.
1515
*)
1616

17+
open Odoc_utils
1718
open Odoc_model
1819
open Odoc_model.Paths
19-
open Or_error
2020

2121
type package_spec = { package : string; output : Fpath.t }
2222
type parent_spec = {

src/odoc/depends.ml

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -14,8 +14,9 @@
1414
* OR IN CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE.
1515
*)
1616

17+
open Odoc_utils
18+
open ResultMonad
1719
open StdLabels
18-
open Or_error
1920

2021
module Odoc_compile = Compile
2122

src/odoc/depends.mli

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -14,7 +14,7 @@
1414
* OR IN CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE.
1515
*)
1616

17-
open Or_error
17+
open Odoc_utils
1818

1919
(** Computes the dependencies required for each step of the pipeline to work
2020
correctly on a given input. *)

src/odoc/fs.ml

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -16,7 +16,6 @@
1616

1717
open Odoc_utils
1818
open StdLabels
19-
open Or_error
2019

2120
type directory = Fpath.t
2221

src/odoc/fs.mli

Lines changed: 1 addition & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,4 @@
1-
open Or_error
1+
open Odoc_utils
22

33
(*
44
* Copyright (c) 2016 Thomas Refis <[email protected]>
@@ -23,8 +23,6 @@ type file = Fpath.t
2323
type directory
2424

2525
module Directory : sig
26-
open Or_error
27-
2826
type t = directory
2927

3028
val dirname : t -> t

src/odoc/html_fragment.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,5 @@
11
open Odoc_utils
2-
open Or_error
2+
open ResultMonad
33

44
let from_mld ~xref_base_uri ~resolver ~output ~warnings_options input =
55
(* Internal names, they don't have effect on the output. *)

src/odoc/html_fragment.mli

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -14,7 +14,7 @@
1414
* OR IN CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE.
1515
*)
1616

17-
open Or_error
17+
open Odoc_utils
1818

1919
(** Produces html fragment files from a mld file. *)
2020

src/odoc/indexing.ml

Lines changed: 1 addition & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,6 @@
11
open Odoc_utils
2-
open Astring
2+
open ResultMonad
33
open Odoc_json_index
4-
open Or_error
54
open Odoc_model
65

76
module H = Odoc_model.Paths.Identifier.Hashtbl.Any

src/odoc/indexing.mli

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,4 @@
1-
open Or_error
1+
open Odoc_utils
22

33
val compile :
44
[ `JSON | `Marshall ] ->

src/odoc/occurrences.ml

Lines changed: 1 addition & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,5 @@
11
open Odoc_utils
2-
open Or_error
2+
open ResultMonad
33

44
let handle_file file ~f =
55
if String.is_prefix ~affix:"impl-" (Fpath.filename file) then
@@ -34,9 +34,6 @@ let count ~dst ~warnings_options:_ directories include_hidden =
3434
Io_utils.marshal (Fs.File.to_string dst) htbl;
3535
Ok ()
3636

37-
open Astring
38-
open Or_error
39-
4037
let parse_input_file input =
4138
let is_sep = function '\n' | '\r' -> true | _ -> false in
4239
Fs.File.read input >>= fun content ->

src/odoc/odoc_file.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -15,8 +15,8 @@
1515
*)
1616

1717
open Odoc_utils
18+
open ResultMonad
1819
open Odoc_model
19-
open Or_error
2020

2121
type unit_content = Lang.Compilation_unit.t
2222

src/odoc/odoc_file.mli

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -16,8 +16,8 @@
1616

1717
(** Load and save [.odoc] and [.odocl] files. *)
1818

19+
open Odoc_utils
1920
open Odoc_model
20-
open Or_error
2121

2222
(** Either a page or a module or something else. *)
2323
type content =

src/odoc/odoc_link.ml

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,5 @@
1-
open Or_error
1+
open Odoc_utils
2+
open ResultMonad
23

34
let link_page ~resolver ~filename page =
45
let env = Resolver.build_env_for_page resolver page in

src/odoc/or_error.ml

Lines changed: 0 additions & 7 deletions
This file was deleted.

src/odoc/or_error.mli

Lines changed: 0 additions & 6 deletions
This file was deleted.

src/odoc/rendering.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,6 @@
11
open Odoc_utils
2+
open ResultMonad
23
open Odoc_document
3-
open Or_error
44
open Odoc_model
55

66
let prepare ~extra_suffix ~output_dir filename =

src/odoc/rendering.mli

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,5 @@
1+
open Odoc_utils
12
open Odoc_document
2-
open Or_error
33

44
val render_odoc :
55
resolver:Resolver.t ->
@@ -42,7 +42,7 @@ val generate_asset_odoc :
4242
extra_suffix:string option ->
4343
'a ->
4444
Fs.file ->
45-
(unit, [> Or_error.msg ]) result
45+
(unit, [> msg ]) result
4646

4747
val targets_odoc :
4848
resolver:Resolver.t ->
@@ -62,4 +62,4 @@ val targets_source_odoc :
6262
extra:'a ->
6363
source_file:Fpath.t ->
6464
Fs.file ->
65-
(unit, [> Or_error.msg ]) result
65+
(unit, [> msg ]) result

src/odoc/resolver.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -32,7 +32,7 @@
3232
which will generally fix this issue. *)
3333

3434
open Odoc_utils
35-
open Or_error
35+
open ResultMonad
3636

3737
type named_root = string * Fs.Directory.t
3838
module Named_roots : sig

src/odoc/sidebar.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,5 @@
1-
open Or_error
21
open Odoc_utils
2+
open ResultMonad
33

44
let compile_to_json ~output sidebar =
55
let json = Odoc_html.Sidebar.to_json sidebar in

src/odoc/source.ml

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,6 @@
1+
open Odoc_utils
2+
open ResultMonad
13
open Odoc_model
2-
open Or_error
34

45
let resolve_and_substitute ~resolver ~make_root ~source_id input_file =
56
let filename = Fs.File.to_string input_file in

src/utils/odoc_utils.ml

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,5 @@
1+
type msg = [ `Msg of string ]
2+
13
(** The [result] type and a bind operator. This module is meant to be opened. *)
24
module ResultMonad = struct
35
let map_error f = function Ok _ as ok -> ok | Error e -> Error (f e)

test/odoc_print/odoc_print.ml

Lines changed: 2 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,8 @@
11
(** Print .odocl files. *)
22

3+
open Odoc_utils
4+
open ResultMonad
35
open Odoc_odoc
4-
open Odoc_odoc.Or_error
56
open Odoc_model_desc
67

78
let print_json_desc desc x =

0 commit comments

Comments
 (0)