Skip to content

Commit 7b1294d

Browse files
committed
fix compatibility
Signed-off-by: Paul-Elliot <peada@free.fr>
1 parent 4ded6db commit 7b1294d

File tree

6 files changed

+39
-17
lines changed

6 files changed

+39
-17
lines changed

src/document/generator.ml

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1763,7 +1763,7 @@ module Make (Syntax : SYNTAX) = struct
17631763
| None -> None
17641764
in
17651765
let search_assets =
1766-
List.filter_map
1766+
Utils.filter_map
17671767
(function
17681768
| `Resolved (`Identifier id) ->
17691769
Some Url.(from_path @@ Path.from_identifier id)

src/document/utils.ml

Lines changed: 8 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,13 @@
11
let option_of_result = function Result.Ok x -> Some x | Result.Error _ -> None
22

3+
let filter_map f =
4+
let rec aux accu = function
5+
| [] -> List.rev accu
6+
| x :: l -> (
7+
match f x with None -> aux accu l | Some v -> aux (v :: accu) l)
8+
in
9+
aux []
10+
311
let rec flatmap ?sep ~f = function
412
| [] -> []
513
| [ x ] -> f x

src/document/utils.mli

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,4 @@
1+
val filter_map : ('a -> 'b option) -> 'a list -> 'b list
12
val option_of_result : ('a, 'b) Result.result -> 'a option
23
val flatmap : ?sep:'a list -> f:('b -> 'a list) -> 'b list -> 'a list
34
val skip_until : p:('a -> bool) -> 'a list -> 'a list

src/odoc/indexing.ml

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,9 +1,11 @@
11
open Odoc_search
22
open Or_error
33

4+
let map_result f = function Ok v -> Ok (f v) | Error _ as e -> e
5+
46
let handle_file file ~unit ~page =
57
Odoc_file.load file
6-
|> Result.map @@ fun unit' ->
8+
|> map_result @@ fun unit' ->
79
match unit' with
810
| { Odoc_file.content = Unit_content (unit', _); _ } when not unit'.hidden
911
->

src/search/entry.ml

Lines changed: 14 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -1,6 +1,15 @@
11
open Odoc_model.Lang
22
open Odoc_model.Paths
33

4+
let list_concat_map f l =
5+
let rec aux f acc = function
6+
| [] -> List.rev acc
7+
| x :: l ->
8+
let xs = f x in
9+
aux f (List.rev_append xs acc) l
10+
in
11+
aux f [] l
12+
413
type type_decl_entry = {
514
canonical : Path.Type.t option;
615
equation : TypeDecl.Equation.t;
@@ -118,14 +127,14 @@ let entry_of_field id_parent params (field : TypeDecl.Field.t) =
118127
entry ~id:field.id ~doc:field.doc ~kind
119128

120129
let rec entries_of_docs id (d : Odoc_model.Comment.docs) =
121-
List.concat_map (entries_of_doc id) d
130+
list_concat_map (entries_of_doc id) d
122131

123132
and entries_of_doc id d =
124133
match d.value with
125134
| `Paragraph _ -> [ entry ~id ~doc:[ d ] ~kind:(Doc Paragraph) ]
126135
| `Tag _ -> []
127136
| `List (_, ds) ->
128-
List.concat_map (entries_of_docs id) (ds :> Odoc_model.Comment.docs list)
137+
list_concat_map (entries_of_docs id) (ds :> Odoc_model.Comment.docs list)
129138
| `Heading (_, lbl, _) -> [ entry ~id:lbl ~doc:[ d ] ~kind:(Doc Heading) ]
130139
| `Modules _ -> []
131140
| `Code_block (_, _, o) ->
@@ -171,8 +180,9 @@ let entries_of_item id (x : Odoc_model.Fold.item) =
171180
[ entry ~id:v.id ~doc:v.doc ~kind ]
172181
| Exception exc ->
173182
let res =
174-
Option.value exc.res
175-
~default:(TypeExpr.Constr (Odoc_model.Predefined.exn_path, []))
183+
match exc.res with
184+
| None -> TypeExpr.Constr (Odoc_model.Predefined.exn_path, [])
185+
| Some x -> x
176186
in
177187
let kind = Exception { args = exc.args; res } in
178188
[ entry ~id:exc.id ~doc:exc.doc ~kind ]

src/search/generator.ml

Lines changed: 12 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -4,6 +4,8 @@ open Odoc_model
44
open Lang
55
open Printf
66

7+
let map_option f = function Some x -> Some (f x) | None -> None
8+
79
let type_from_path : Paths.Path.Type.t -> string =
810
fun path ->
911
match path with
@@ -79,19 +81,19 @@ let display_constructor_args args =
7981
| _ :: _ :: _ -> Some TypeExpr.(Tuple args)
8082
| [ arg ] -> Some arg
8183
| _ -> None)
82-
|> Option.map type_expr
84+
|> map_option type_expr
8385
| TypeDecl.Constructor.Record fields -> Some (Render.text_of_record fields)
8486

8587
let constructor_rhs ~args ~res =
8688
let args = display_constructor_args args in
87-
let res = Option.map type_expr res in
89+
let res = map_option type_expr res in
8890
match (args, res) with
8991
| None, None -> ""
9092
| None, Some res -> " : " ^ res
9193
| Some args, None -> " of " ^ args
9294
| Some args, Some res -> " : " ^ args ^ " -> " ^ res
9395

94-
let field_rhs Entry.{ mutable_ = _; type_; parent_type = _ } =
96+
let field_rhs ({ mutable_ = _; type_; parent_type = _ } : Entry.field_entry) =
9597
" : " ^ type_expr type_
9698

9799
let typedecl_params ?(delim = `parens) params =
@@ -121,7 +123,7 @@ let typedecl_params ?(delim = `parens) params =
121123
let type_decl_constraint (typ, typ') =
122124
"constraint" ^ " " ^ type_expr typ ^ " = " ^ type_expr typ'
123125

124-
let typedecl_params_of_entry Entry.{ kind; _ } =
126+
let typedecl_params_of_entry ({ kind; _ } : Entry.t) =
125127
match kind with
126128
| Entry.TypeDecl { canonical = _; equation; representation = _ } ->
127129
typedecl_params equation.params
@@ -144,12 +146,10 @@ let typedecl_repr ~private_ (repr : TypeDecl.Representation.t) =
144146
|> String.concat " | "
145147
| Record record -> Render.text_of_record record
146148

147-
let typedecl_rhs Entry.{ equation; representation; _ } =
149+
let typedecl_rhs ({ equation; representation; _ } : Entry.type_decl_entry) =
148150
let TypeDecl.Equation.{ private_; manifest; constraints; _ } = equation in
149151
let repr =
150-
representation
151-
|> Option.map (typedecl_repr ~private_)
152-
|> Option.value ~default:""
152+
match representation with Some r -> typedecl_repr ~private_ r | None -> ""
153153
in
154154
let manifest =
155155
match manifest with None -> "" | Some typ -> " = " ^ type_expr typ
@@ -162,7 +162,8 @@ let typedecl_rhs Entry.{ equation; representation; _ } =
162162
in
163163
match repr ^ manifest ^ constraints with "" -> None | r -> Some r
164164

165-
let constructor_rhs Entry.{ args; res } = constructor_rhs ~args ~res:(Some res)
165+
let constructor_rhs ({ args; res } : Entry.constructor_entry) =
166+
constructor_rhs ~args ~res:(Some res)
166167

167168
(** Kinds *)
168169

@@ -264,12 +265,12 @@ let html_of_doc doc =
264265
let html_string_of_doc doc =
265266
doc |> html_of_doc |> Format.asprintf "%a" (Html.pp_elt ())
266267
let html_of_entry (entry : Entry.t) =
267-
let Entry.{ id; doc; kind } = entry in
268+
let ({ id; doc; kind } : Entry.t) = entry in
268269
let rhs = rhs_of_kind kind in
269270
let prefix_name, name = title_of_id id in
270271
let doc = html_string_of_doc doc in
271272
let kind = string_of_kind kind in
272273
let typedecl_params = typedecl_params_of_entry entry in
273274
html_of_strings ~kind ~prefix_name ~name ~rhs ~doc ~typedecl_params
274275

275-
let with_html entry = Entry.{ entry; html = html_of_entry entry }
276+
let with_html entry : Entry.with_html = { entry; html = html_of_entry entry }

0 commit comments

Comments
 (0)