@@ -4,6 +4,8 @@ open Odoc_model
44open Lang
55open Printf
66
7+ let map_option f = function Some x -> Some (f x) | None -> None
8+
79let 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
8587let 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
9799let typedecl_params ?(delim = `parens ) params =
@@ -121,7 +123,7 @@ let typedecl_params ?(delim = `parens) params =
121123let 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 =
264265let html_string_of_doc doc =
265266 doc |> html_of_doc |> Format. asprintf " %a" (Html. pp_elt () )
266267let 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