From 9ea9f0fb186388f6b57953437e88ef3f76ed40ae Mon Sep 17 00:00:00 2001 From: Paul-Elliot Date: Tue, 20 Jun 2023 15:12:35 +0200 Subject: [PATCH 01/61] Add folding for odoc's Lang model to the API. This is useful at least to populate a search index, but also possibly for glossary? Signed-off-by: Paul-Elliot --- src/model/fold.ml | 109 ++++++++++++++++++++++++++++++++++++++++ src/model/fold.mli | 36 +++++++++++++ src/model/odoc_model.ml | 1 + 3 files changed, 146 insertions(+) create mode 100644 src/model/fold.ml create mode 100644 src/model/fold.mli diff --git a/src/model/fold.ml b/src/model/fold.ml new file mode 100644 index 0000000000..dde23df2b3 --- /dev/null +++ b/src/model/fold.ml @@ -0,0 +1,109 @@ +open Lang + +type item = + | CompilationUnit of Compilation_unit.t + | TypeDecl of TypeDecl.t + | Module of Module.t + | Value of Value.t + | Exception of Exception.t + | ClassType of ClassType.t + | Method of Method.t + | Class of Class.t + | Extension of Extension.t + | ModuleType of ModuleType.t + | Doc of Comment.docs_or_stop + +let rec unit ~f acc u = + let acc = f acc (CompilationUnit u) in + match u.content with Module m -> signature ~f acc m | Pack _ -> acc + +and page ~f acc p = + let open Page in + docs ~f acc (`Docs p.content) + +and signature ~f acc (s : Signature.t) = + List.fold_left (signature_item ~f) acc s.items + +and signature_item ~f acc s_item = + match s_item with + | Module (_, m) -> module_ ~f acc m + | ModuleType mt -> module_type ~f acc mt + | ModuleSubstitution _ -> acc + | ModuleTypeSubstitution _ -> acc + | Open _ -> acc + | Type (_, t_decl) -> type_decl ~f acc t_decl + | TypeSubstitution _ -> acc + | TypExt te -> type_extension ~f acc te + | Exception exc -> exception_ ~f acc exc + | Value v -> value ~f acc v + | Class (_, cl) -> class_ ~f acc cl + | ClassType (_, clt) -> class_type ~f acc clt + | Include i -> include_ ~f acc i + | Comment d -> docs ~f acc d + +and docs ~f acc d = f acc (Doc d) + +and include_ ~f acc inc = signature ~f acc inc.expansion.content + +and class_type ~f acc ct = + let acc = f acc (ClassType ct) in + match ct.expansion with None -> acc | Some cs -> class_signature ~f acc cs + +and class_signature ~f acc ct_expr = + List.fold_left (class_signature_item ~f) acc ct_expr.items + +and class_signature_item ~f acc item = + match item with + | Method m -> f acc (Method m) + | InstanceVariable _ -> acc + | Constraint _ -> acc + | Inherit _ -> acc + | Comment d -> docs ~f acc d + +and class_ ~f acc cl = + let acc = f acc (Class cl) in + match cl.expansion with + | None -> acc + | Some cl_signature -> class_signature ~f acc cl_signature + +and exception_ ~f acc exc = f acc (Exception exc) + +and type_extension ~f acc te = f acc (Extension te) + +and value ~f acc v = f acc (Value v) + +and module_ ~f acc m = + let acc = f acc (Module m) in + match m.type_ with + | Alias (_, None) -> acc + | Alias (_, Some s_e) -> simple_expansion ~f acc s_e + | ModuleType mte -> module_type_expr ~f acc mte + +and type_decl ~f acc td = f acc (TypeDecl td) + +and module_type ~f acc mt = + let acc = f acc (ModuleType mt) in + match mt.expr with + | None -> acc + | Some mt_expr -> module_type_expr ~f acc mt_expr + +and simple_expansion ~f acc s_e = + match s_e with + | Signature sg -> signature ~f acc sg + | Functor (_, s_e) -> simple_expansion ~f acc s_e + +and module_type_expr ~f acc mte = + match mte with + | Signature s -> signature ~f acc s + | Functor (fp, mt_expr) -> + let acc = functor_parameter ~f acc fp in + module_type_expr ~f acc mt_expr + | With { w_expansion = Some sg; _ } -> simple_expansion ~f acc sg + | TypeOf { t_expansion = Some sg; _ } -> simple_expansion ~f acc sg + | Path { p_expansion = Some sg; _ } -> simple_expansion ~f acc sg + | Path { p_expansion = None; _ } -> acc + | With { w_expansion = None; _ } -> acc + | TypeOf { t_expansion = None; _ } -> acc + +and functor_parameter ~f acc fp = + match fp with Unit -> acc | Named n -> module_type_expr ~f acc n.expr diff --git a/src/model/fold.mli b/src/model/fold.mli new file mode 100644 index 0000000000..397fbff74b --- /dev/null +++ b/src/model/fold.mli @@ -0,0 +1,36 @@ +open Lang + +type item = + | CompilationUnit of Compilation_unit.t + | TypeDecl of TypeDecl.t + | Module of Module.t + | Value of Value.t + | Exception of Exception.t + | ClassType of ClassType.t + | Method of Method.t + | Class of Class.t + | Extension of Extension.t + | ModuleType of ModuleType.t + | Doc of Comment.docs_or_stop + +val unit : f:('a -> item -> 'a) -> 'a -> Compilation_unit.t -> 'a +val page : f:('a -> item -> 'a) -> 'a -> Page.t -> 'a +val signature : f:('a -> item -> 'a) -> 'a -> Signature.t -> 'a +val signature_item : f:('a -> item -> 'a) -> 'a -> Signature.item -> 'a +val docs : f:('a -> item -> 'a) -> 'a -> Comment.docs_or_stop -> 'a +val include_ : f:('a -> item -> 'a) -> 'a -> Include.t -> 'a +val class_type : f:('a -> item -> 'a) -> 'a -> ClassType.t -> 'a +val class_signature : f:('a -> item -> 'a) -> 'a -> ClassSignature.t -> 'a +val class_signature_item : + f:('a -> item -> 'a) -> 'a -> ClassSignature.item -> 'a +val class_ : f:('a -> item -> 'a) -> 'a -> Class.t -> 'a +val exception_ : f:('a -> item -> 'a) -> 'a -> Exception.t -> 'a +val type_extension : f:('a -> item -> 'a) -> 'a -> Extension.t -> 'a +val value : f:('a -> item -> 'a) -> 'a -> Value.t -> 'a +val module_ : f:('a -> item -> 'a) -> 'a -> Module.t -> 'a +val type_decl : f:('a -> item -> 'a) -> 'a -> TypeDecl.t -> 'a +val module_type : f:('a -> item -> 'a) -> 'a -> ModuleType.t -> 'a +val simple_expansion : + f:('a -> item -> 'a) -> 'a -> ModuleType.simple_expansion -> 'a +val module_type_expr : f:('a -> item -> 'a) -> 'a -> ModuleType.expr -> 'a +val functor_parameter : f:('a -> item -> 'a) -> 'a -> FunctorParameter.t -> 'a diff --git a/src/model/odoc_model.ml b/src/model/odoc_model.ml index 68171ed5cb..11d3fa1918 100644 --- a/src/model/odoc_model.ml +++ b/src/model/odoc_model.ml @@ -1,4 +1,5 @@ module Lang = Lang +module Fold = Fold module Comment = Comment module Paths = Paths module Names = Names From 0640643bf46812fbf6e0172bc7218b8902399c36 Mon Sep 17 00:00:00 2001 From: Paul-Elliot Date: Tue, 13 Jun 2023 18:20:42 +0200 Subject: [PATCH 02/61] Add an option to html generation to not include links This is useful if we want to add the html rendering in another context where links would not make sense, such as search results. Signed-off-by: Paul-Elliot --- src/html/config.ml | 19 ++++++++++++++++--- src/html/config.mli | 3 +++ src/html/generator.ml | 24 ++++++++++++++++++------ 3 files changed, 37 insertions(+), 9 deletions(-) diff --git a/src/html/config.ml b/src/html/config.ml index ea5f93d0f5..b15fa26bea 100644 --- a/src/html/config.ml +++ b/src/html/config.ml @@ -4,15 +4,26 @@ type t = { theme_uri : Types.uri option; support_uri : Types.uri option; semantic_uris : bool; + search_result : bool; + (* Used to not render links, for summary in search results *) indent : bool; flat : bool; open_details : bool; as_json : bool; } -let v ?theme_uri ?support_uri ~semantic_uris ~indent ~flat ~open_details - ~as_json () = - { semantic_uris; indent; flat; open_details; theme_uri; support_uri; as_json } +let v ?(search_result = false) ?theme_uri ?support_uri ~semantic_uris ~indent + ~flat ~open_details ~as_json () = + { + semantic_uris; + indent; + flat; + open_details; + theme_uri; + support_uri; + as_json; + search_result; + } let theme_uri config = match config.theme_uri with None -> Types.Relative None | Some uri -> uri @@ -29,3 +40,5 @@ let flat config = config.flat let open_details config = config.open_details let as_json config = config.as_json + +let search_result config = config.search_result diff --git a/src/html/config.mli b/src/html/config.mli index 97e941358b..74f2168a02 100644 --- a/src/html/config.mli +++ b/src/html/config.mli @@ -3,6 +3,7 @@ type t val v : + ?search_result:bool -> ?theme_uri:Types.uri -> ?support_uri:Types.uri -> semantic_uris:bool -> @@ -26,3 +27,5 @@ val flat : t -> bool val open_details : t -> bool val as_json : t -> bool + +val search_result : t -> bool diff --git a/src/html/generator.ml b/src/html/generator.ml index aca2d5d401..df1ad2bf77 100644 --- a/src/html/generator.ml +++ b/src/html/generator.ml @@ -32,9 +32,10 @@ type non_link_phrasing = Html_types.phrasing_without_interactive let mk_anchor_link id = [ Html.a ~a:[ Html.a_href ("#" ^ id); Html.a_class [ "anchor" ] ] [] ] -let mk_anchor anchor = +let mk_anchor config anchor = match anchor with | None -> ([], [], []) + | _ when Config.search_result config -> ([], [], []) | Some { Url.Anchor.anchor; _ } -> let link = mk_anchor_link anchor in let extra_attr = [ Html.a_id anchor ] in @@ -99,8 +100,13 @@ let rec internallink ~config ~emph_level ~resolve ?(a = []) match target with | Resolved uri -> let href = Link.href ~config ~resolve uri in - let a = (a :> Html_types.a_attrib Html.attrib list) in - Html.a ~a:(Html.a_href href :: a) (inline_nolink ~emph_level content) + let content = inline_nolink ~emph_level content in + if Config.search_result config then Html.span ~a content + else + let a = + Html.a_href href :: (a :> Html_types.a_attrib Html.attrib list) + in + Html.a ~a content | Unresolved -> (* let title = * Html.a_title (Printf.sprintf "unresolved reference to %S" @@ -125,6 +131,9 @@ and inline ~config ?(emph_level = 0) ~resolve (l : Inline.t) : | Styled (style, c) -> let emph_level, app_style = styled style ~emph_level in [ app_style @@ inline ~config ~emph_level ~resolve c ] + | Link (_, c) when Config.search_result config -> + let content = inline_nolink ~emph_level c in + [ Html.span ~a content ] | Link (href, c) -> let a = (a :> Html_types.a_attrib Html.attrib list) in let content = inline_nolink ~emph_level c in @@ -161,6 +170,7 @@ and inline_nolink ?(emph_level = 0) (l : Inline.t) : let heading ~config ~resolve (h : Heading.t) = let a, anchor = match h.label with + | Some _ when Config.search_result config -> ([], []) | Some id -> ([ Html.a_id id ], mk_anchor_link id) | None -> ([], []) in @@ -314,7 +324,7 @@ let rec documentedSrc ~config ~resolve (t : DocumentedSrc.t) : (delim opening @ block ~config ~resolve doc @ delim closing); ] in - let extra_attr, extra_class, link = mk_anchor anchor in + let extra_attr, extra_class, link = mk_anchor config anchor in let content = (content :> any Html.elt list) in Html.li ~a:(extra_attr @ class_ (attrs @ extra_class)) @@ -363,7 +373,9 @@ and items ~config ~resolve l : item Html.elt list = let details ~open' = let open' = if open' then [ Html.a_open () ] else [] in let summary = - let extra_attr, extra_class, anchor_link = mk_anchor anchor in + let extra_attr, extra_class, anchor_link = + mk_anchor config anchor + in let link_to_source = mk_link_to_source ~config ~resolve source_anchor in @@ -387,7 +399,7 @@ and items ~config ~resolve l : item Html.elt list = in (continue_with [@tailcall]) rest content | Declaration { Item.attr; anchor; source_anchor; content; doc } :: rest -> - let extra_attr, extra_class, anchor_link = mk_anchor anchor in + let extra_attr, extra_class, anchor_link = mk_anchor config anchor in let link_to_source = mk_link_to_source ~config ~resolve source_anchor in let a = spec_class (attr @ extra_class) @ extra_attr in let content = From abac5a6ccdabc7de689795d995fd365174b4d081 Mon Sep 17 00:00:00 2001 From: Paul-Elliot Date: Tue, 20 Jun 2023 16:48:27 +0200 Subject: [PATCH 03/61] Add search support in odoc - A new command `odoc compile-index` to generate a json index to give to search engine - A new flag `--search-file` to `odoc html-generate` and `odoc support-files` to specify the search file(s) to execute for search (This will have to be reworked) - A script, html layout and css to display the search results Co-authored-by: Emile Trotignon Signed-off-by: Paul-Elliot --- src/document/ML.mli | 9 + src/document/generator.ml | 8 + src/document/generator_signatures.ml | 8 + src/html/config.ml | 6 +- src/html/config.mli | 3 + src/html/html_page.ml | 91 +- src/html/odoc_html.ml | 1 + src/html_support_files/odoc.css | 125 +- .../odoc_html_support_files.ml | 33 +- src/html_support_files/odoc_search.js | 38 + src/model/paths.ml | 74 + src/model/paths.mli | 4 + src/odoc/bin/main.ml | 71 +- src/odoc/dune | 1 + src/odoc/html_fragment.ml | 2 +- src/odoc/indexing.ml | 42 + src/odoc/indexing.mli | 15 + src/odoc/support_files.ml | 37 +- src/odoc/support_files.mli | 12 +- src/search/dune | 4 + src/search/entry.ml | 212 ++ src/search/entry.mli | 76 + src/search/json_display.ml | 124 + src/search/json_display.mli | 1 + src/search/json_search.ml | 229 ++ src/search/json_search.mli | 4 + src/search/render.ml | 157 ++ src/search/render.mli | 12 + test/generators/html/Functor-F1.html | 12 +- test/generators/html/Functor-F2.html | 12 +- test/generators/html/Functor-F3.html | 12 +- test/generators/html/Functor-F4.html | 12 +- test/generators/html/Functor-F5.html | 12 +- .../html/Functor-module-type-S1.html | 12 +- test/generators/html/Functor2-X.html | 12 +- .../html/Functor2-module-type-XF.html | 12 +- ...nclude_sections-module-type-Something.html | 16 +- test/generators/html/Include_sections.html | 44 +- test/generators/html/Labels-A.html | 8 +- test/generators/html/Labels-class-c.html | 7 +- .../generators/html/Labels-class-type-cs.html | 8 +- .../generators/html/Labels-module-type-S.html | 8 +- test/generators/html/Labels.html | 12 +- test/generators/html/Markup.html | 58 +- .../html/Module_type_alias-module-type-B.html | 12 +- .../html/Module_type_alias-module-type-E.html | 12 +- .../html/Module_type_alias-module-type-G.html | 12 +- .../html/Nested-F-argument-1-Arg1.html | 11 +- .../html/Nested-F-argument-2-Arg2.html | 4 +- test/generators/html/Nested-F.html | 14 +- test/generators/html/Nested-X.html | 11 +- test/generators/html/Nested-class-z.html | 6 +- .../generators/html/Nested-module-type-Y.html | 11 +- test/generators/html/Nested.html | 16 +- test/generators/html/Ocamlary-Aliases.html | 6 +- test/generators/html/Ocamlary-Dep12.html | 12 +- test/generators/html/Ocamlary-Dep2.html | 12 +- test/generators/html/Ocamlary-Dep5.html | 12 +- test/generators/html/Ocamlary-Dep7.html | 12 +- test/generators/html/Ocamlary-Dep9.html | 12 +- .../html/Ocamlary-FunctorTypeOf.html | 12 +- .../html/Ocamlary-Recollection.html | 12 +- test/generators/html/Ocamlary-With7.html | 12 +- ...ule-type-SuperSig-module-type-SubSigA.html | 14 +- ...ule-type-SuperSig-module-type-SubSigB.html | 18 +- test/generators/html/Ocamlary.html | 88 +- .../html/Recent-module-type-S1.html | 12 +- .../html/Recent_impl-module-type-S-F.html | 12 +- test/generators/html/Section.html | 45 +- .../Toplevel_comments-Comments_on_open.html | 4 +- test/generators/html/mld.html | 20 +- test/index/dune | 9 + test/index/index_command.t/fuse.js.js | 2240 +++++++++++++++++ test/index/index_command.t/j.ml | 13 + test/index/index_command.t/main.ml | 59 + test/index/index_command.t/page.mld | 10 + test/index/index_command.t/run.t | 844 +++++++ test/integration/html_support_files.t/run.t | 2 + test/pages/resolution.t/run.t | 1 + test/xref2/github_issue_342.t/run.t | 20 +- test/xref2/labels/ambiguous_label.t/run.t | 26 +- test/xref2/labels/labels.t/run.t | 22 +- test/xref2/module_preamble.t/run.t | 8 +- 83 files changed, 4952 insertions(+), 382 deletions(-) create mode 100644 src/html_support_files/odoc_search.js create mode 100644 src/odoc/indexing.ml create mode 100644 src/odoc/indexing.mli create mode 100644 src/search/dune create mode 100644 src/search/entry.ml create mode 100644 src/search/entry.mli create mode 100644 src/search/json_display.ml create mode 100644 src/search/json_display.mli create mode 100644 src/search/json_search.ml create mode 100644 src/search/json_search.mli create mode 100644 src/search/render.ml create mode 100644 src/search/render.mli create mode 100644 test/index/dune create mode 100644 test/index/index_command.t/fuse.js.js create mode 100644 test/index/index_command.t/j.ml create mode 100644 test/index/index_command.t/main.ml create mode 100644 test/index/index_command.t/page.mld create mode 100644 test/index/index_command.t/run.t diff --git a/src/document/ML.mli b/src/document/ML.mli index 7ff015e1a6..64c6969c72 100644 --- a/src/document/ML.mli +++ b/src/document/ML.mli @@ -30,3 +30,12 @@ val source_page : Lang.Source_info.infos -> string -> Types.Document.t + +val type_expr : ?needs_parentheses:bool -> Lang.TypeExpr.t -> Codefmt.t + +val type_decl : + ?is_substitution:bool -> + Lang.Signature.recursive * Lang.TypeDecl.t -> + Types.Item.t + +val record : Lang.TypeDecl.Field.t list -> Types.DocumentedSrc.one list diff --git a/src/document/generator.ml b/src/document/generator.ml index 5639a3f18c..e92852d71f 100644 --- a/src/document/generator.ml +++ b/src/document/generator.ml @@ -470,6 +470,8 @@ module Make (Syntax : SYNTAX) = struct val extension : Lang.Extension.t -> Item.t + val record : Lang.TypeDecl.Field.t list -> DocumentedSrc.one list + val exn : Lang.Exception.t -> Item.t val format_params : @@ -1888,6 +1890,12 @@ module Make (Syntax : SYNTAX) = struct include Page + let type_expr = type_expr + + let type_decl = type_decl + + let record = record + let source_page id syntax_info infos source_code = Document.Source_page (Source_page.source id syntax_info infos source_code) end diff --git a/src/document/generator_signatures.ml b/src/document/generator_signatures.ml index eb03db7050..e47bd5cd83 100644 --- a/src/document/generator_signatures.ml +++ b/src/document/generator_signatures.ml @@ -114,4 +114,12 @@ module type GENERATOR = sig Lang.Source_info.infos -> string -> Document.t + + val type_expr : ?needs_parentheses:bool -> Lang.TypeExpr.t -> text + val type_decl : + ?is_substitution:bool -> + Lang.Signature.recursive * Lang.TypeDecl.t -> + Types.Item.t + + val record : Lang.TypeDecl.Field.t list -> DocumentedSrc.one list end diff --git a/src/html/config.ml b/src/html/config.ml index b15fa26bea..e015bc4f25 100644 --- a/src/html/config.ml +++ b/src/html/config.ml @@ -10,10 +10,11 @@ type t = { flat : bool; open_details : bool; as_json : bool; + search_files : string list; (* names of JS files to include in the webworker *) } let v ?(search_result = false) ?theme_uri ?support_uri ~semantic_uris ~indent - ~flat ~open_details ~as_json () = + ~flat ~open_details ~as_json ~search_files () = { semantic_uris; indent; @@ -23,6 +24,7 @@ let v ?(search_result = false) ?theme_uri ?support_uri ~semantic_uris ~indent support_uri; as_json; search_result; + search_files; } let theme_uri config = @@ -42,3 +44,5 @@ let open_details config = config.open_details let as_json config = config.as_json let search_result config = config.search_result + +let search_files config = config.search_files diff --git a/src/html/config.mli b/src/html/config.mli index 74f2168a02..d9f0710e1e 100644 --- a/src/html/config.mli +++ b/src/html/config.mli @@ -11,6 +11,7 @@ val v : flat:bool -> open_details:bool -> as_json:bool -> + search_files:string list -> unit -> t @@ -29,3 +30,5 @@ val open_details : t -> bool val as_json : t -> bool val search_result : t -> bool + +val search_files : t -> string list diff --git a/src/html/html_page.ml b/src/html/html_page.ml index da778f13ab..c575d251fc 100644 --- a/src/html/html_page.ml +++ b/src/html/html_page.ml @@ -27,9 +27,30 @@ let html_of_toc toc = |> List.map (fun the_section -> Html.li (section the_section)) |> Html.ul in - match toc with - | [] -> [] - | _ -> [ Html.nav ~a:[ Html.a_class [ "odoc-toc" ] ] [ sections toc ] ] + match toc with [] -> [] | _ -> [ sections toc ] + +let html_of_search () = + let search_bar = + Html.div + ~a:[ Html.a_class [ "search-bar-container" ] ] + [ + Html.input + ~a:[ Html.a_class [ "search-bar" ]; Html.a_placeholder "🔎 Search..." ] + (); + ] + in + let search_result = Html.div ~a:[ Html.a_class [ "search-result" ] ] [] in + [ search_bar; search_result ] + +let sidebar toc = + let toc, has_toc = + match toc with + | [] -> ([], false) + | _ -> + ([ Html.nav ~a:[ Html.a_class [ "odoc-toc" ] ] (html_of_toc toc) ], true) + in + if has_toc then [ Html.div ~a:[ Html.a_class [ "odoc-sidebar" ] ] toc ] + else [] let html_of_breadcrumbs (breadcrumbs : Types.breadcrumb list) = let make_navigation ~up_url rest = @@ -70,26 +91,54 @@ let html_of_breadcrumbs (breadcrumbs : Types.breadcrumb list) = make_navigation ~up_url:up.href (List.rev html @ sep @ [ Html.txt current.name ]) -let page_creator ~config ~url ~uses_katex header breadcrumbs toc content = +let page_creator ~config ~url ~uses_katex ~with_search header breadcrumbs toc + content = let theme_uri = Config.theme_uri config in let support_uri = Config.support_uri config in let path = Link.Path.for_printing url in + let file_uri base file = + match base with + | Types.Absolute uri -> uri ^ "/" ^ file + | Relative uri -> + let page = Url.Path.{ kind = `File; parent = uri; name = file } in + Link.href ~config ~resolve:(Current url) (Url.from_path page) + in let head : Html_types.head Html.elt = let title_string = Printf.sprintf "%s (%s)" url.name (String.concat "." path) in - let file_uri base file = - match base with - | Types.Absolute uri -> uri ^ "/" ^ file - | Relative uri -> - let page = Url.Path.{ kind = `File; parent = uri; name = file } in - Link.href ~config ~resolve:(Current url) (Url.from_path page) - in - let odoc_css_uri = file_uri theme_uri "odoc.css" in let highlight_js_uri = file_uri support_uri "highlight.pack.js" in + let search_scripts = + if Config.search_files config = [] then [] + else + let search_urls = + let search_url name = + Printf.sprintf "'%s'" (file_uri support_uri name) + in + let search_urls = List.map search_url (Config.search_files config) in + "[" ^ String.concat "," search_urls ^ "]" + in + [ + Html.script ~a:[] + (Html.txt + (Format.asprintf "let base_url = '%s'; let search_urls = %s;" + (let page = + Url.Path.{ kind = `File; parent = None; name = "" } + in + Link.href ~config ~resolve:(Current url) (Url.from_path page)) + search_urls)); + Html.script + ~a: + [ + Html.a_src (file_uri support_uri "odoc_search.js"); + Html.a_defer (); + ] + (Html.txt ""); + ] + in let default_meta_elements = [ Html.link ~rel:[ `Stylesheet ] ~href:odoc_css_uri (); @@ -135,15 +184,25 @@ let page_creator ~config ~url ~uses_katex header breadcrumbs toc content = ] else default_meta_elements in + let meta_elements = meta_elements @ search_scripts in Html.head (Html.title (Html.txt title_string)) meta_elements in + let search_bar = + if with_search then + [ Html.div ~a:[ Html.a_class [ "odoc-search" ] ] (html_of_search ()) ] + else [] + in + let body = html_of_breadcrumbs breadcrumbs - @ [ Html.header ~a:[ Html.a_class [ "odoc-preamble" ] ] header ] - @ html_of_toc toc + @ [ + Html.header ~a:[ Html.a_class [ "odoc-preamble" ] ] (search_bar @ header); + ] + @ sidebar toc @ [ Html.div ~a:[ Html.a_class [ "odoc-content" ] ] content ] in + let htmlpp = Html.pp ~indent:(Config.indent config) () in let html = Html.html head (Html.body ~a:[ Html.a_class [ "odoc" ] ] body) in let content ppf = @@ -156,7 +215,9 @@ let page_creator ~config ~url ~uses_katex header breadcrumbs toc content = let make ~config ~url ~header ~breadcrumbs ~toc ~uses_katex content children = let filename = Link.Path.as_filename ~is_flat:(Config.flat config) url in let content = - page_creator ~config ~url ~uses_katex header breadcrumbs toc content + page_creator ~config ~url ~uses_katex + ~with_search:(Config.search_files config != []) + header breadcrumbs toc content in { Odoc_document.Renderer.filename; content; children } diff --git a/src/html/odoc_html.ml b/src/html/odoc_html.ml index a93ed9f58c..e7150f71e5 100644 --- a/src/html/odoc_html.ml +++ b/src/html/odoc_html.ml @@ -9,3 +9,4 @@ module Html_page = Html_page module Generator = Generator module Link = Link +module Json = Utils.Json diff --git a/src/html_support_files/odoc.css b/src/html_support_files/odoc.css index 64eba0fa11..751543e7a8 100644 --- a/src/html_support_files/odoc.css +++ b/src/html_support_files/odoc.css @@ -116,6 +116,7 @@ --toc-color: #1F2D3D; --toc-before-color: #777; --toc-background: #f6f8fa; + --toc-background-emph: #ecf0f5; --toc-list-border: #ccc; --spec-summary-border-color: #5c9cf5; @@ -151,6 +152,7 @@ --li-code-color: #999; --toc-color: #777; --toc-background: #252525; + --toc-background-emph: #2a2a2a; --hljs-link: #999; --hljs-keyword: #cda869; @@ -195,6 +197,7 @@ --toc-color: #777; --toc-before-color: #777; --toc-background: #252525; + --toc-background-emph: #2a2a2a; --toc-list-border: #ccc; --spec-summary-hover-background: #ebeff2; --spec-details-after-background: rgba(0, 4, 15, 0.05); @@ -738,7 +741,7 @@ td.def-doc *:first-child { line-height: 1.2; } -.odoc-toc { +.odoc-sidebar { position: fixed; top: 0px; bottom: 0px; @@ -753,7 +756,7 @@ td.def-doc *:first-child { padding-right: 2ex; } -.odoc-toc ul li a { +.odoc-sidebar ul li a { font-family: "Fira Sans", sans-serif; font-size: 0.95em; color: var(--color); @@ -762,11 +765,127 @@ td.def-doc *:first-child { display: block; } -.odoc-toc ul li a:hover { +.odoc-sidebar ul li a:hover { box-shadow: none; text-decoration: underline; } +.odoc-search { + position: relative; +} + + +.odoc-search:not(:focus-within) .search-result { + display : none; +} + +.odoc-search .search-result:empty { + display : none; +} + +.odoc-search .search-result { + position: absolute; + background: var(--toc-background); + overflow: scroll; + left: 0; + right: 0; + max-height: 40rem; + border:solid; + border-color: var(--pre-border-color); + border-color: var(--pre-border-color); + border-width: 1px; + padding-left: 0.5rem; + padding-right: 0.5rem; + border-radius: 2px; + box-shadow: 5px 5px 5px var(--toc-background); +} + +.search-bar { + width: 100%; +} + +.search-bar-container { + display: flex; +} + +.odoc-search .search-entry { + color: var(--color); + display: block; + margin-top: 10px; + margin-bottom: 10px; + /* border: 3px ridge pink */ + border-left: 2px solid transparent; +} +.odoc-search .search-entry p { + margin:0; +} + +.odoc-search .search-entry:hover { + border: none; + box-shadow: none; + border-left: 2px solid var(--link-color); +} + +.odoc-search .search-entry.value { + /* border: 3px ridge red */ +} + +.odoc-search .search-entry .entry-title .entry-kind { + font-size: 0.75em; + font-weight: 900; + border: 1px solid; + border-color: var(--color); + border-radius: 3px; + margin-right: 0.5em; + margin-left: 0.25em; + padding-right: 0.25em; + padding-left: 0.25em; +} + +.odoc-search .search-entry pre { + border:none; + margin:0; +} + +.odoc-search .search-entry pre code { + font-size: 1em; + background-color: var(--li-code-background); + color: var(--li-code-color); + border-radius: 3px; + padding: 0 0.3ex; +} + +.odoc-search .search-entry .entry-title { + padding-right: 10px; + background-color: var(--toc-background-emph); + width: 100%; + display: block; +} + +.odoc-search.active .search-entry .entry-name { + font-size: 1.2em; +} + +.odoc-search.active .search-entry .prefix-name { + font-size: 1.2em; +} + +.odoc-search .search-entry .prefix-name { + opacity: 0.5; +} + +.odoc-search .search-entry .entry-comment { + margin-left: 10px; + max-height: 100px; + overflow: scroll; + font-size: 0.8em; +} + +.odoc-search.active .search-entry .entry-comment { + max-height: 300px; + font-size: 1rem; +} + /* First level titles */ .odoc-toc>ul>li>a { diff --git a/src/html_support_files/odoc_html_support_files.ml b/src/html_support_files/odoc_html_support_files.ml index d1d0432bc5..48dea2d7cb 100644 --- a/src/html_support_files/odoc_html_support_files.ml +++ b/src/html_support_files/odoc_html_support_files.ml @@ -88,8 +88,6 @@ module Internal = struct let d_30baf6fb746860926fdd280eefc46735 = "\"to\",\"at\",\"if\",\"in\",\"it\",\"on\",/[A-Za-z]+['](d|ve|re|ll|t|s|n)/,/[A-Za-z]+[-][a-z]+/,/[A-Za-z][a-z]{2,}/)\n;return i.contains.push({begin:p(/[ ]+/,\"(\",s,/[.]?[:]?([.][ ]|[ ])/,\"){3}\")}),i\n},S=M(\"//\",\"$\"),R=M(\"/\\\\*\",\"\\\\*/\"),j=M(\"#\",\"$\");var A=Object.freeze({\n__proto__:null,MATCH_NOTHING_RE:/\\b\\B/,IDENT_RE:x,UNDERSCORE_IDENT_RE:w,\nNUMBER_RE:y,C_NUMBER_RE:_,BINARY_NUMBER_RE:O,\nRE_STARTERS_RE:\"!|!=|!==|%|%=|&|&&|&=|\\\\*|\\\\*=|\\\\+|\\\\+=|,|-|-=|/=|/|:|;|<<|<<=|<=|<|===|==|=|>>>=|>>=|>=|>>>|>>|>|\\\\?|\\\\[|\\\\{|\\\\(|\\\\^|\\\\^=|\\\\||\\\\|=|\\\\|\\\\||~\",\nSHEBANG:(e={})=>{const t=/^#![ ]*\\//\n;return e.binary&&(e.begin=p(t,/.*\\b/,e.binary,/\\b.*/)),r({scope:\"meta\",begin:t,\nend:/$/,relevance:0,\"on:begin\":(e,t)=>{0!==e.index&&t.ignoreMatch()}},e)},\nBACKSLASH_ESCAPE:v,APOS_STRING_MODE:N,QUOTE_STRING_MODE:k,PHRASAL_WORDS_MODE:{\nbegin:/\\b(a|an|the|are|I'm|isn't|don't|doesn't|won't|but|just|should|pretty|simply|enough|gonna|going|wtf|so|such|will|you|your|they|like|more)\\b/\n},COMMENT:M,C_LINE_COMMENT_MODE:S,C_BLOCK_COMMENT_MODE:R,HASH_COMMENT_MODE:j,\nNUMBER_MODE:{scope:\"number\",begin:y,relevance:0},C_NUMBER_MODE:{scope:\"number\",\nbegin:_,relevance:0},BINARY_NUMBER_MODE:{scope:\"number\",begin:O,relevance:0},\nREGEXP_MODE:{begin:/(?=\\/[^/\\n]*\\/)/,contains:[{scope:\"regexp\",begin:/\\//,\nend:/\\/[gimuy]*/,illegal:/\\n/,contains:[v,{begin:/\\[/,end:/\\]/,relevance:0,\ncontains:[v]}]}]},TITLE_MODE:{scope:\"title\",begin:x,relevance:0},\nUNDERSCORE_TITLE_MODE:{scope:\"title\",begin:w,relevance:0},METHOD_GUARD:{\nbegin:\"\\\\.\\\\s*[a-zA-Z_]\\\\w*\",relevance:0},END_SAME_AS_BEGIN:e=>Object.assign(e,{\n\"on:begin\":(e,t)=>{t.data._beginMatch=e[1]},\"on:end\":(e,t)=>{\nt.data._beginMatch!==e[1]&&t.ignoreMatch()}})});function I(e,t){\n\".\"===e.input[e.index-1]&&t.ignoreMatch()}function T(e,t){\nvoid 0!==e.className&&(e.scope=e.className,delete e.className)}function L(e,t){\nt&&e.beginKeywords&&(e.begin=\"\\\\b(\"+e.beginKeywords.split(\" \").join(\"|\")+\")(?!\\\\.)(?=\\\\b|\\\\s)\",\ne.__beforeBegin=I,e.keywords=e.keywords||e.beginKeywords,delete e.beginKeywords,\nvoid 0===e.relevance&&(e.relevance=0))}function B(e,t){\nArray.isArray(e.illegal)&&(e.illegal=f(...e.illegal))}function D(e,t){\nif(e.match){\nif(e.begin||e.end)throw Error(\"begin & end are not supported with match\")\n;e.begin=e.match,delete e.match}}function H(e,t){\nvoid 0===e.relevance&&(e.relevance=1)}const P=(e,t)=>{if(!e.beforeMatch)return\n;if(e.starts)throw Error(\"beforeMatch cannot be used with starts\")\n;const n=Object.assign({},e);Object.keys(e).forEach((t=>{delete e[t]\n})),e.keywords=n.keywords,e.begin=p(n.beforeMatch,d(n.begin)),e.starts={\nrelevance:0,contains:[Object.assign(n,{endsParent:!0})]\n},e.relevance=0,delete n.beforeMatch\n},C=[\"of\",\"and\",\"for\",\"in\",\"not\",\"or\",\"if\",\"then\",\"parent\",\"list\",\"value\"]\n;function $(e,t,n=\"keyword\"){const i=Object.create(null)\n;return\"string\"==typeof e?r(n,e.split(\" \")):Array.isArray(e)?r(n,e):Object.keys(e).forEach((n=>{\nObject.assign(i,$(e[n],t,n))})),i;function r(e,n){\nt&&(n=n.map((e=>e.toLowerCase()))),n.forEach((t=>{const n=t.split(\"|\")\n;i[n[0]]=[e,U(n[0],n[1])]}))}}function U(e,t){\nreturn t?Number(t):(e=>C.includes(e.toLowerCase()))(e)?0:1}const z={},K=e=>{\nconsole.error(e)},W=(e,...t)=>{console.log(\"WARN: \"+e,...t)},X=(e,t)=>{\nz[`${e}/${t}`]||(console.log(`Deprecated as of ${e}. ${t}`),z[`${e}/${t}`]=!0)\n},G=Error();function Z(e,t,{key:n}){let i=0;const r=e[n],s={},o={}\n;for(let e=1;e<=t.length;e++)o[e+i]=r[e],s[e+i]=!0,i+=b(t[e-1])\n;e[n]=o,e[n]._emit=s,e[n]._multi=!0}function F(e){(e=>{\ne.scope&&\"object\"==typeof e.scope&&null!==e.scope&&(e.beginScope=e.scope,\ndelete e.scope)})(e),\"string\"==typeof e.beginScope&&(e.beginScope={\n_wrap:e.beginScope}),\"string\"==typeof e.endScope&&(e.endScope={_wrap:e.endScope\n}),(e=>{if(Array.isArray(e.begin)){\nif(e.skip||e.excludeBegin||e.returnBegin)throw K(\"skip, excludeBegin, returnBegin not compatible with beginScope: {}\"),\nG\n;if(\"object\"!=typeof e.beginScope||null===e.beginScope)throw K(\"beginScope must be object\"),\nG;Z(e,e.begin,{key:\"beginScope\"}),e.begin=E(e.begin,{joinWith:\"\"})}})(e),(e=>{\nif(Array.isArray(e.end)){\nif(e.skip||e.excludeEnd||e.returnEnd)throw K(\"skip, exclu" - let d_30ca700678d2ff7e5a1c5981a2e65744 = "include.shadowed-include {\n display: none;\n}\n\n.odoc-include details:after {\n z-index: -100;\n display: block;\n content: \" \";\n position: absolute;\n border-radius: 0 1ex 1ex 0;\n right: -20px;\n top: 1px;\n bottom: 1px;\n width: 15px;\n background: var(--spec-details-after-background, rgba(0, 4, 15, 0.05));\n box-shadow: 0 0px 0 1px var(--spec-details-after-shadow, rgba(204, 204, 204, 0.53));\n}\n\n.odoc-include summary {\n position: relative;\n margin-bottom: 1em;\n cursor: pointer;\n outline: none;\n}\n\n.odoc-include summary:hover {\n background-color: var(--spec-summary-hover-background);\n}\n\n/* FIXME: Does not work in Firefox. */\n.odoc-include summary::-webkit-details-marker {\n color: #888;\n transform: scaleX(-1);\n position: absolute;\n top: calc(50% - 5px);\n height: 11px;\n right: -29px;\n}\n\n/* Records and variants FIXME */\n\ndiv.def table {\n text-indent: 0em;\n padding: 0;\n margin-left: -2ex;\n}\n\ntd.def {\n padding-left: 2ex;\n}\n\ntd.def-doc *:first-child {\n margin-top: 0em;\n}\n\n/* Lists of @tags */\n\n.at-tags { list-style-type: none; margin-left: -3ex; }\n.at-tags li { padding-left: 3ex; text-indent: -3ex; }\n.at-tags .at-tag { text-transform: capitalize }\n\n/* Alert emoji */\n\n.alert::before, .deprecated::before {\n content: '\226\154\160\239\184\143 ';\n}\n\n/* Lists of modules */\n\n.modules { list-style-type: none; margin-left: -3ex; }\n.modules li { padding-left: 3ex; text-indent: -3ex; margin-top: 5px }\n.modules .synopsis { padding-left: 1ch; }\n\n/* Odig package index */\n\n.packages { list-style-type: none; margin-left: -3ex; }\n.packages li { padding-left: 3ex; text-indent: -3ex }\n.packages li a.anchor { padding-right: 0.5ch; padding-left: 3ch; }\n.packages .version { font-size: 10px; color: var(--by-name-version-color); }\n.packages .synopsis { padding-left: 1ch }\n\n.by-name nav a {\n text-transform: uppercase;\n font-size: 18px;\n margin-right: 1ex;\n color: var(--by-name-nav-link-color,);\n display: inline-block;\n}\n\n.by-tag nav a {\n margin-right: 1ex;\n color: var(--by-name-nav-link-color);\n display: inline-block;\n}\n\n.by-tag ol { list-style-type: none; }\n.by-tag ol.tags li { margin-left: 1ch; display: inline-block }\n.by-tag td:first-child { text-transform: uppercase; }\n\n/* Odig package page */\n\n.package nav {\n display: inline;\n font-size: 14px;\n font-weight: normal;\n}\n\n.package .version {\n font-size: 14px;\n}\n\n.package.info {\n margin: 0;\n}\n\n.package.info td:first-child {\n font-style: italic;\n padding-right: 2ex;\n}\n\n.package.info ul {\n list-style-type: none;\n display: inline;\n margin: 0;\n}\n\n.package.info li {\n display: inline-block;\n margin: 0;\n margin-right: 1ex;\n}\n\n#info-authors li, #info-maintainers li {\n display: block;\n}\n\n/* Sidebar and TOC */\n\n.odoc-toc:before {\n display: block;\n content: \"Contents\";\n text-transform: uppercase;\n font-size: 1em;\n margin: 1.414em 0 0.5em;\n font-weight: 500;\n color: var(--toc-before-color);\n line-height: 1.2;\n}\n\n.odoc-toc {\n position: fixed;\n top: 0px;\n bottom: 0px;\n left: 0px;\n max-width: 30ex;\n min-width: 26ex;\n width: 20%;\n background: var(--toc-background);\n overflow: auto;\n color: var(--toc-color);\n padding-left: 2ex;\n padding-right: 2ex;\n}\n\n.odoc-toc ul li a {\n font-family: \"Fira Sans\", sans-serif;\n font-size: 0.95em;\n color: var(--color);\n font-weight: 400;\n line-height: 1.6em;\n display: block;\n}\n\n.odoc-toc ul li a:hover {\n box-shadow: none;\n text-decoration: underline;\n}\n\n/* First level titles */\n\n.odoc-toc>ul>li>a {\n font-weight: 500;\n}\n\n.odoc-toc li ul {\n margin: 0px;\n}\n\n.odoc-toc ul {\n list-style-type: none;\n}\n\n.odoc-toc ul li {\n margin: 0;\n}\n.odoc-toc>ul>li {\n margin-bottom: 0.3em;\n}\n\n.odoc-toc ul li li {\n border-left: 1px solid var(--toc-list-border);\n margin-left: 5px;\n padding-left: 12px;\n}\n\n/* Tables */\n\n.odoc-table {\n margin: 1em;\n}\n\n.odoc-table td, .odoc-table th {\n padding-left: 0.5em;\n padding-right: 0.5em;\n border: 1px solid black;\n}\n\n.odoc-table th {\n font-weight: bold;\n}\n\n/* Mobile adjustements. */\n\n@media only screen and (max-width: 110ex) {\n body {\n margin: 2em;\n }\n .odoc-toc {\n position: static;\n width: auto;\n " - let d_31b1da49571a0b56a6a3d17e63e12b76 = "wOF2\000\001\000\000\000\000a@\000\017\000\000\000\000\245D\000\000`\219\000\001\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\026t\027\129\162&\028\144F\006`\000\133,\b\1300\t\154\022\017\b\n\129\236\\\129\205\025\011\133\016\000\0016\002$\003\138\028\004 \005\132\020\007\142u\012\129U\027\198\225'\208\211\181 \207\2216\128\166\249<\187\250\186^\160\186\165\227\234\182\193eZ\017\207<>\018!l\028@\192\206S\197\255\255\159\1544\226\208\220!\201=\015\172\213\174\219\006&\178\157TC5\007\193T\017\179\139\r\181T\145\014\213\221Y\181\1306L\146\218*\211\162\1578\nu\226J\190\nK\148\157\1699\147R\174\169\031\241I\220~\161\194\014\015XGc\222S>0\179\139\016\250\174X\"\024Y\140\023z\1317\188\007)\028\249w\242\185G\018G\155\193\196\161\237-\217\171C\137\bFEF\230\027\012\225\204\230!\026\226\248\0286\195\248\201\136\223LM\019\185\167\251\b\127\255\225\224\b'\131\161\228\138L\020\b\015}\190>w\188\003{T\254\185SN\233=\2133\176m\228Or\242\018A\227\224\127\246\030D\255d&!d\162JQL\228\253 \234\242\132\212~\tLm\136\169J\137\004\255\255?\246\255\155s\173}\238\187\031\209F\136\148$\026\2257:4\211F\234\016\138h\164D2\163\139\183\187\007h\155-\157\1648\027P\144\020Z\162\004\005\142j\t\2010&\246\176\231\204\229/*\127{\022\2451?\178\246\145\251\138}\016=\127\012\154\221\127\145\164\005\152 Q\\M\022\209\026\005Vz\b/\253\235j\n\001\220\255\127S\205{\239{\239\255\025\000\004\200\172\1567\005hm\003\014\192\142\002\183\225a5\b\130\192\017\014\028R\1496Qv\238\n\149\170+\151\235\255\181\169i;\237\153\250\246Nk\151=\203pcq\211X\n\171\200\n\144\002\244\r\164Z'\195\247E\178\172\239\235\201\000_\177\159\238\167\155dsa.\177B\217\241\181\182\222V\154\007!\218\246\215\246\205\016\177 \182l\004\025\166\0173\219:\201\144\166l7\005NL\127F\161\155\127F\128\210\203h\027 @\000l\001\252\251\240s\254{.\134\168\156r\138)\165\148\199\144O\148\001+ \015\164\246\156\154\144_\249\t;\191\255\167\179G\029\018\159\006\147\142=\215\153KI\203;\194\143\168\166\218b\251.\141\177*>Q\158\145\141i\199\135\169\218?\176\220d[\018\168a\131* \201\165%\215\nI\198+c[\167\251\211x\215\151\225[hK\169ti\007\021\152\245\026\232.@\134\011\233\201\bRPz*\170PQ\171\170\003\163\011\2558\247\150\216\023;D(\216\025w\202 \127\030qq\128-'\205\129\144g\170\239/\249\1654\192\020\203\161\248\150\137S\134\137\137\254\170v0`\157w\173~V\131\006\248'\160\229\005KQ\001\222\219\246\213\172X\021\172\136].\162W\177J*\159\208\147v\250\189\1728\1277\151\207\021\174\163*\2080\166\028X\149+S\171\220\204nb\tpN\000\203\187{\220i\172\228\158f\188\225P\190T\150\022vwU5\186\171\011\r\209M,\027\0001\004\129\153\161\156\025\138\017T\191A\000\228\186\235\190\251\251M\213\171\154\026H\159I\239\004\024\250\0234T/\16201\142XH\157\019\181\235\002\n\212\186\021\198\134\136Z\166\248\212\202l\001\020T\t=`\167\ba:)\207\007\188\245\000\185\030>tJ\011\1443`&P\000:\017@\r\255\255\\Mg\186\231\181\210Le;`\128\235\242\141[\246\015\152@\128\217z\188\012SL4_\214\234\245\133%\1622_&B\132H\183\229\212c}\025\211\222\007\029\203\155\"\135)\141\024\021\173\127O\187\239|\233\2557\173\187\253\217\210U+\250\162\"\"F\1401\198\024#\162\206\223\251\217O\179\026\204\205\r\bN\216\143\169^\218\239>(\001\166\003\180\132b\131\t\012(0`\b\140h\197\130\224)\131T\184\174~\160\219\232\233c\140\133<\r\151M\229A<\182\218\201\128\163\252\128\171\030~\145\146?\146\016\208\\\161c\b\011_\138\214@\228\233\022}%\200\207\247\020U\128\235\149h\189\014,\017\000\245\127\nGf`}\239\024\018\218{G\136\168?4\160!\n\250\1377\245:\200\000i\165\183\014\018\189\021U\237D\206\000\n\002\226\188\017\131\255Y\000\1304\247\007\177\239\238\128Gl\132\129T\000\130\002E\205=(l\232,\157q\204\144=\182\217h\181~\011\2056\213\004ctj\166W\169X\174\012\026\177\194\005Q\242\130b\219>\144\191\r^\003\005\240\211 /\215jP\028;\005\020\247\174\000yk\2473\203|\178\215+\217\255\174\031\130\238/i0&e=9\022\229K\015\250\234\171}L\1739R\0293\237\227BW'\207\234N\225\229&\176%\031\232-\211\163\012\030\195\179]e\129\161\244p@5\"tF7\153\180}j\164J\161\199K%\134Q\025\140\t:hr\250\192\163\184\031w\226f\\\139\179q*\142\199\1458x|_\016zl\194\1681\224\164s\192]\015.F\146\148h\007\169\240}\164;#\224`\162\161A\018g1T]\183%\207\189\139\2231B\248\186*\211\015\0124~\021h\252<\b\230\202B\192\217\172\241\133\211\015\214h\215`\219\198\169g\130\1921\216i5[P\191Q\229)>\185'\227hN\236\t?AXKy\188\142\232\184\030\135\195]\208\028\217\130\142j$\"\016\254\158_\231\238\188X\018\132G\192;x\205\188\1285/\020\194\16992\007f\215\210\017\012\127\236\128V\200\017L\189\017\141\168\025\002\254\175\127\246\231~\215g\024z\208[\189\018\168\175\231z\002x\b\247\225\014\220\140k7Z\222\197\157\219\233\157t\225]\156:n\025\219\221\214\214W\215\225\165\192|\204\194\148\139\1967\178\234\170\234SI\221k\231<\160%\154 \195\162\232A\012\251S,\154#\219\157o\2491\223\172\253Y\238\229F\167\231R\206\228X\197\135\128{p\027n\196\213\131\253Y\152\217\184\247S3!c\210\153\230\011\005\211\1672\205uJqr\147\017Mb\1432\225\192 T\162\215F\162\184\198!\220\152\135\029:FR\020\000\140C\191\252\213\187]\139bk\130B\193X [\000\181\133r\242\160\172\180\031\025\014\180L\201\197aZ\012\011\149;\186f1\241\146Y\243\135hO\227\159\184y\165\189\019\167\129\166q\143\173ax\166T/\205SJT\158\250\168`\182\246\2362ApL\131YV\196\236\178)Jn\r:M\222-\247F\172\011\134\004/\158\233\0066\181\030{\228d\241S\243\227V\174\183\131kx\228zN\156Y\167.sI=wfs\235\203\203z\162\024\152w\215?\017\163S\188\208\132\170KSW\243+\028Rkv\205I\143Bu:_\129\0260\000\192\163YlsJ\254z\226\1505\171\181\141\210\217d\219s\014\181\181\185H\234\146\172\201\173\205\200\012N\\\005\2140\168\233\241|3!\146\247\229\246\014h\001\242\193\185\236[\023\142\153cwb\1819M@\134<05\146\215\150.1tZ07%\255\2437\011X\223\190\233\140\156\re\138\155\011f]f\186:\209\169\011| \187R\176\185\204\235\163w\142\012\213l\240\224\145\167\153\007/\007OFg\2379\227\014\184`\141\168\198\140*\173\170*\181\169\172\201\019\159A\170B\172\005\163\223\186t\2089)\017\154\184V\198X8\165a\175_\165o\218\221\203\161L\177\169`\244\201,?\2555\005\014W\r\156\211\161J\151.\173\024P\216\160\208\001\133\004(\000\241\011\242\005\248\030\248\014\242\br\007r\rr\001r\nr\132\255\183\\\163Z\017\254~\156;'<\150L0 \176\026\138\1650o\231GF\031\019\252'\225\158z\237\015\023\184\025\184\022\184\028\184\0128\011\028\135\020B\178\129\173\192z`%\176\024\152\011L\135\234\209\012\130\234\134s:\179+{\211\198\020\144\021\172\015++\227\201tF\171\243\029\012\025\221\019\188\183\165\244\022\149~\187\193\148/Zs\2487+se\219\188S\015\017\012\174=\240\204p\172 \024@`-\216\131,\160\127\159\145,\199M(2w\240\002\245\230r\180\196\235\253\164\251~9\bOJ\152\240a\001\244\007\242\233\151b\159\251\n\241\171\201\184\169\166\171\177\209\022\245.\167\208\140n\155\005\1449-6\215<\196\"\136\229-\182\213\014\200^\136C-q\220\t\200\169=dx\1619\157\242a\161\005\2378,_@|5\027\251\213\127\184\255M&*J\021\240x\147\236m\182E?\227rxo\016\" \000v\210\166\141\255_\218\219x\156o\024\192\028\255I\016^\127K\194\235\215B<\144\238b#\177\127_0qe\147\026\227\002\205\240\251\183\254\019\144^\247\017`\248\173=\014U\245\019\187w\163\137\184\185\1716'_\162mq\226\248\002\001j\182\243\195\242*n\202\222\195\156z\234^\181\198\216\220\159)n\023\004=\226\133g\216,\137\135\160\141o\161\166\157\161\243E@\209\213)\026\149\221\031\164\203v'\193\023\192\002\168\218\211\198\241m\172\253\196\151\138\148?\195\169c\017\001\247\190/\028(,\021\216\223\031\248\0117\187Pk\134\153f\153m\142\2282\223B\022[\2425+\172\180\218Z[m\179\221\014;\237\178\219\030{\029\146\222\255\163S\206\007\168\001\234%F\195\233t\130\201\018+)\13754\132z&bss\177D\162niIZIM\236\216\161\216\181kj\207\158\134}\007T\135\014i\142\028\137\029\187\148\184r\165\233\198S\137g\158\177<\247\\\226\003\031\234\248\220\231\150\190\244\181\196w\190\147\024\149j\213\140\213\168a\171V-Sz\141<5ib\166Y3s-ZXh\213\206L\135\014\150:ub\232\210E\164\219hE\209\165z\n,\1898\155\000\199D\152&ad2\018}\152\152\170\157\186\136\172\203\236\004\030vA\179\027\204^q\216A\134;r\b\176\029n\029\028q\148\2161p\199qt\002\190\179\026\168\020ez\168cn\016B7\225\185\133\208mx\238\180\200]\015\136=\004y\138\200s\172\188\128\238\149.\253\020\171\168\224\142\253%\027\244\207\252\174,l\004\177\137i\016A8A\215x\131\174gn\223\023{Ol\244\020\022g\140G[\205\243\249\023^z\021\150lM5\211\\+\197\026l{\020\180=\022\028\\\176\148\158t\162\151ERg\174(a\225\020\012zq\208\175\2001\167-\b\177\186\tj:&T\217\254,/\204\142)\199\197\019\228E\178~\167a\204\211g\025{rQ\031\006\172\129h\169\226s\023\233\021B7g)^L\027\146(\0193\241\0191\223\139@\139^\248\198\227b\245\0260\028\249Xr,=Y\245\236\175*)\229M\128t\019dp\1473JY\163\169\226z5\028l\164=\243\252\0286@\011\1752+\186\203\137;H\r\164 C$\129w\030`j\167\165\240c\169\030-\162\158-\024X&\1686\159\186zb\149y\163'\212\231\15316\192!\194\r#\211\024/o^\234\151\014.O*\133\164R\024Q\178H\020\227K\0251CU\227\2222\154\185\207\003\018\015%\017\147\229\192\019\158\148IJ\229\158\166d\194R\141WP2\175\021\227\245\146y\163\132\222,\129\183R\136\140\156P\225\016\"6\019%#\209\204\031\206\219\225\140\205T\236bi2*o\175\163\2074'\167\204W\131\228k[Q\145v{[\135(\250\189?\003\206\163\145\183\019\"\15212\254\159\"\138\215\161\2065\232F\221\251\154\229\143]\232ne\145B\236\244m\208\"G\167\221\029\172O\165\244\238P\169\232\253X\246J\020v\215k\136\184=+G\023\r\244\228\145\237\t.nd\186n\229.V\202x\213\r\brl\1446\199\227\0065D\134\242|H\029O\011g\135JR\16703\127]\212\226E\201\193\190\021\134\007\224\139~\177[\155\150@{\022\192#)\003E,5\002r\241\179N\024uR\252a;\174g!\152n&\184.\130\141\201mb5\157\2518\225\237\019\173\162HJ\205\205\216Dl\130\138\191{\153\173\186;\131z\022\004\137u\250\242l\243-\176P\159\223\188\167\235u\249#\025\232\027\132\r2+\004\203\151s\185\138\232#\150\203\165\136*\022*\225\011\228\020F\225Q\252\170 \201\026z\172\164\154e\021l\005\165\160\020*BZ\201\225\2428\012A\22526\155\146\014\000&P\233\021\153\237\n5\1910\011\n\1830*\208q\1489\183zVS!\214\022\203\250\216\129 \137\137\236\212-\159o\231\175\145\242\147\179\017\242\167\199_\191j\127\162\207\004\145\011\170J\235%\130\031\225\016M*\242\204\184\200A1\231\131\150\027\188\204\173\139\"\031\223!\153\212\147\024WR@\170\194\247\029\231xV\207Z\001FBT\146\168\218?\177\223_\225\164\211\2068\235\146\005\160\254onQ0\145L\2230\140,\152`\b\139\143b\140\000\023\016\147\128<\003m\018\016f\018X\221\129$\t\233As\196\180\132\020\016\007+\193\238,\015\143\210V\024\148\202\157,\163\150\211\206\178\\\154P\2032\216\148\003\201\246\150\015\158\242\157\235r\1451\233\137\227\207\152\207\252\006\196\026\197}&\1617ON\r\\\168T\153\246&\234l\204\196\254\t\239u6rJ7\132\206\233\255\166\249Qc\017NG%\204sEB=\002\004\212z\163w\216\161\166\202}\226\t\174\025\143\212\239zW\031\255\189z7]\156.Lj3K\165T\242\192\019\138\137\230`\248\145_\204^]\167\128\164\250u\232\175\244\1522i\181\183\209y\215\254\148l\251\183\031\003\220\248\193\221\222\168\246\245\235J\16324\253h\2185\027\189\029<\217{r\238\215R\157\179:\022\157\154\163\173q\149>\0071\208o\226\152X\233\198\178\132\237\147\022\186\015e\166\150tX\157bl\001Tb\211\235\216\161`Pb>\213\199\209-\163Ah\239\168RX\220\204\209\179\190u\210C\028J\015\155\179\244\171\179\145cNi\2034\227H\228=0?s.setAttribute(\"height\",V(a)):(s.setAttribute(\"height\",V(a)),s.setAttribute(\"depth\",V(-a))),s.setAttribute(\"voffset\",V(a)),s}});var yn=[\"\\\\tiny\",\"\\\\sixptsize\",\"\\\\scriptsize\",\"\\\\footnotesize\",\"\\\\small\",\"\\\\normalsize\",\"\\\\large\",\"\\\\Large\",\"\\\\LARGE\",\"\\\\huge\",\"\\\\Huge\"];ot({type:\"sizing\",names:yn,props:{numArgs:0,allowedInText:!0},handler:function(e,t){var r=e.breakOnTokenText,n=e.funcName,a=e.parser,i=a.parseExpression(!1,r);return{type:\"sizing\",mode:a.mode,size:yn.indexOf(n)+1,body:i}},htmlBuilder:function(e,t){var r=t.havingSize(e.size);return bn(e.body,r,t)},mathmlBuilder:function(e,t){var r=t.havingSize(e.size),n=Nt(e.body,r),a=new Tt.MathNode(\"mstyle\",n);return a.setAttribute(\"mathsize\",V(r.sizeMultiplier)),a}}),ot({type:\"smash\",names:[\"\\\\smash\"],props:{numArgs:1,numOptionalArgs:1,allowedInText:!0},handler:function(e,t,r){var n=e.parser,a=!1,i=!1,o=r[0]&&Ut(r[0],\"ordgroup\");if(o)for(var s=\"\",l=0;lr.height+r.depth+i&&(i=(i+c-r.height-r.depth)/2);var u=l.height-r.height-i-h;r.style.paddingLeft=V(m);var p=Ke.makeVList({positionType:\"firstBaseline\",children:[{type:\"elem\",elem:r,wrapperClasses:[\"svg-align\"]},{type:\"kern\",size:-(r.height+u)},{type:\"elem\",elem:l},{type:\"kern\",size:h}]},t);if(e.index){var d=t.havingStyle(x.SCRIPTSCRIPT),f=wt(e.index,d,t),g=.6*(p.he" @@ -126,6 +124,8 @@ module Internal = struct let d_4a0d6b1f3fe23870dc64a5c9998fab74 = "wOF2\000\001\000\000\000\000?\020\000\017\000\000\000\000\134\224\000\000>\178\000\001\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\026\028\027\030\028\136$\006`\000\132|\b\129\018\t\151\023\017\b\n\129\201h\129\172t\011\132\026\000\0016\002$\003\135B\004 \005\131T\007\137\028\012\129 \027*u\005\227\152%\224<\000\129\146\245\0192\138`\227\000\146\024\188\027E\176q\128`\191\029\221\252\127=n\012\017\236\136V\181\014%$\184\218T\228\158\166U(Wg\163{\147a:=eRp1\147J^\223\209\2050\133\133\228d\197\175\140\135\219wT\007\025\238^\197\219\016\196\021\023\132\127`{b\209\027R\240Ew\255\224A\173@\130\006%\186\244\193\195\239\004\165\168OFR\248\156\191\220\248\232\b\141}\146\011U,[\247\236\127&$\225\016\158\194\135\168\192\168\168q\022\148@HT\242_\b\159\212\237\146\029\149\193\145n!\232\169J\228\014\192\220\028\130\003F\245\"a\209l\205\130U\177J6bT\140L\005\251\162\024\137\141\145`\005f\222G\164\149\015\255+U}\239\253\191\187\000I\145\162U\154{\191\177\164\168\204\144^\151\170\225\192p\131\145V\024\235\152\243\197\247SB\004\141\177f\015\151\012\161\019E\155y\018Mb\157\140GR\164v\154\254\031<\212^\219\219\250kK\178I\255\185\163\021\133\208\027\154\187u\224\016\150A6\165\025\020H\135D!T\243\159t\234\251\167\147-\019\004\248\146\179\212T\186 +>;\132\176g,\224\180u\0243v\157\218\006\247\223\007\248\1919\255\243^\0250\177$#H\182c;y\196gF\003\152\161v\213.\187\236~\247?\031\234\210S\203\167t\011\179?\192,\217\133u\r\001?C${-lc\136\245\249\159\181\026\"\030\228\135\015\222\221k\214X\198V%A\1471l\214\228p\164r;\189\244:\000!\142e.\212<\000\202\031)S)\006B\185\253\159\174\223\223I6\200\189\025^EoEIQA\143\143DX\194{\001\1949\193e\13429\180n\203\195\190\152U\201\006\241|\207W\249{S\205\246\191]\174\004R\014\132\194\012\229\172\211\197\216\175\194\217\2449\151v\229\162s\251\241\255_\252\221\191X`\177K\222-\022:\029\024\164#A\209\002\b\158D\018\180\006\1297\179\1608\030E\135\016%9\209\174HP\129\162\018%9\166Xt\030W\149K\183eJ\157{\023U\239\162\247\024\250\246\139\213y\243\023\148m\1916c6\029\026\014-El^\185\028\rY\196\146|\239O\200\131\140\229\230i\150\001s\171\237_/\219l6Hjt\168\006\011{a\137\183g\246\134\211{\127\179\255C\023\186\166\215K\144\208\000\145\153\136B{\191\158\\\004\001k\128\017;\019U\014\185\234\1730ijA\026\182\r\155?\157YA\020:S`#`\197\202\155\133\130\231u\238\188\228\229\014\241\166\177\207\156N\011X5\227-\222-\243\231\164+\225\238\185\165\150\186\133\209\173T`u\006\028\243\166$%\219\\\170L\022\233\163:\014B r\138\203\178\019\004\150}Y6\002\178`.\203\138_&\244eY\240\017\131\186,\197K\020\242\178\004\015\017\136Kb\220\132\193\1836\b\023\025\175,\243\247U\002{\146z\127K\167\210\031\163\240 \232%\030\211\142o(]N\148AR\196\"\252'\191\145\159=\"\252u\153s\251\132_.\001\128\216e$\131Ld,\179\202,2\0056,Y\201\137\011w\150\003_\201wI\241\219\193\183\019\127\145g,?}g\141DHa\154\1381E\241\202\012\194G\169M\187\014\157\186t\235\209\171O?\132\023\165\"_\208Z\131\134\012\0271j\204\184\t\147(\170bD\214,\194@v\245\133\154eAT\020\174\138\201\243\003\130\180*\208u\238\023\020F\215\207\1536`H\155~ \005\233U\005\195\003&A\212\196\245\166Y\137\023K*4r\137[\175\162\023\238\189p\204]\130\151\147\031u\204\175~\243;\128rU\143\127\157\143\187\232\015\127\250K\024>\021*U\169V\163V\157z\r\026\029v\196=?\2489: \172pB\004\132\247c;.\196DV6!\134@5\133\139\240:d\201\203L\201\246\160$\152\011\167`\136\221\197\220\b[\253\137\190\211<\159\1702\239\162\178\b\203\212\222\194\203\141/`6\200S\222\r\128\171\188\174{0\"\004\144\014\155tS\031\194S\160\149\179\030m\022\2428/\238?\211\185\225\007\128\251\148F\191\001\240\012 \189\153\006,6\161X\185'\028\nG\148w\031\217CH\017\196\197\209\195\215\239\1274\208\1503\185Zn\151\187#\\\200=Q)jE\131pD\191(\200g\203/\247\138\245\191\251\174A\176\161\228\031\243\0207|\157<\186<\155g\213\214\149\187\162\\T\175\177\239\011\165\127\000p\r\000-\001\134\149LSK\149\027\000\171\143\193\234\193\247\196+\255za\1925\223\185\234e\000\254\253b\187\025\191}\239\185\221\254\216\166\2209K4k\181\133\029\011V\156\216p\224\194KD\178\020\169`\192 \160\018e#\192\194!\193\251\017\017\023\011\027\135\016U\136\156\132\148\146\140\130\138\150Y\001#\019/'\0237\189R\149\202\148\171V\225KU\218\181h\213\166G\157^d5.\187\228\182;na\198\147ANrW\029\144^\000}\184#\231x\172~Q\150X\189\028\165\127:\"\2250\193O\188\021\128V`\217\240\203\020\020\001\171\186`\136\134\014\016_\028B`\249\163Fg\021\0267m\157\252\170\006\179\221\161\005\011\199\021.\011)\129M@s>\003A[\021\131\020\196A=\006ST%\188\155\193\157\143Y#\133u\161R\152\252\164%K\2257\b\011\227Z\1947\130\208+n\234\2214\020\182\029\174\138\198\166V\199\002\169U\180b\209{\014\213\201\127i\n\0206lO\b\169\b\139R7\234\2544\176\198\024\001\242\140a`A\215\140\137a(*\016\184\237\170\004S\143k\152R! \149\144\210\128\014bp\197\146%U\131y\164h\195\198''\015\198A\1921\233\202\129\167\201\159\167\247\135^h5mpgB\219q\225&\141f3N\249S\218\011\225\022\211\029\209\163M\133\160~\157\129\005\007\005\244 f\152\000\215\227\192\142\234\1988\014\030L7\248AEf\230Gt\229\128\227\136\021Y}\223\026pm>9\146\165\178`\004\186\160^\201p\163Py\248ca\154\020y<\200\128\219\182\238\247\242\144\170\177rP\021\207\205\016U\240#\132\173nKb\249Q&\018\025 \137\220\028\160j\138\162\196\165\169\179H\216(j)X\154WR\015\137\169\192X\017'\178\142\024q\021l\"\227\232\193\001\"OO*#!uX\130\024\222\251\018\138\144\012\202\016:\2248\246\242pR\215V\247\001g\152\131x\170\164\026\154\214\129\159\228\205\147O\205\167\188\165\167z\221\019zhj\153\0202\200\153\011\167U@B\207\232\137{\004\232P!\225\025\151\178\204V!\186\130\216\016P)\019\012{\017!|6x3\237\191\156\0319\229J\254\024\173\197\004\002\177\b\209M\174AT\151\016\131H\191\194\197\026\203%\014\193\012z2`\2155\003Y\248e\178\170\138aM5B\002\217\026\154C\\KGX\015]q\145Qiz\195\138\133Dl^qR\247rM\018\154)\251\250e\225\200*\227\227\248\221\171wz\225\163\017z\189qG\230#\244y^\136\020.\187\243\189\135wc\226\181\216EF.=\248l\183\006\144\136\2490\014\190\199\133\031;\199A\030\168\169o<\214\179\011\1430T\228|\148\202\208\t\249\014\185\212\195\220\140\004\159\145\135\140\167\022\250\170~\217\144$q[\2396\242\168\151P\176\002\163\132z\\\248#\024\r\137\205\250\141\209\0250\201\1911\1610\166\164\134\001;\251C\157p\227\231\2552I\153\253\220\177\024\241aPQ\200T\253\005\162\183@\227\162\210=]\241E|\224\234Z\1894\216\163\143\234\184\192\250\004\226\190M\197(\248\207\141\023\171F\"\221<\027\254\158\218\017\004\132\181pN\196\018\169\176\1996p\186\142\196\159\005\147\146\179gfRuV\250\239\130\244\031\140\196a\030\224\182\128?\2279\202\t6\225\250\243\208\176\164\218\184\232=\231\153\028\146\0188z\200F\004\1743=\200\234c\206\184\245]\202i\t.\165>\199(\248\161^LaB\137\212\020\132\127\178\227\232\205q#\209\189\030\193:\225\179\204g\028\150\183G\005L\175\030\191\237 fC\218\173UL\247Ae(\236~\1747\250\183&9\174\150\180|Q\248\225L\131\175\r\194\186\225\214);\197\181\017\140\014u\020Ed`Ai\174X'\247F\164j.\152\134\158v\238\136i\154\"`\130\183i\171\241\151\222\248j\229/&$\129[\222I/\167'\187,j!\239\161\026\167\146\154ro\219\200{}\246\014&\175\244\235zH[\184\160\158A\196p\244OZ2TL}\1499\144\140\217\024\002g\136\177\189.9\174YRG\199\217'\177\000\128\004:&A\031\2507\157\023\248\242\248\023)\156]\004C\201\031\232\217:\200\156y\127:\225,\029w\221\141\242|\024Q\027#\255#`\162F\220e1\1901]\175\131\174}O\185&\007=\253\255\235\140\150W,\222\211f\2187\022\201\229?\150w\2327\130\169\141\254D\166\2370\\\134kJ\r-[\184\231w\211S\177n\n\180\030\232\252a\168G\211\215\194\180\228W\253\173\t\2017\025i\219>n\140Gv\192b2C=\168j%\017z\134\0003\177\202\006\179g\248\141\233\173h\2517\143w\178\237\191\231\232\223B\174Al\221q\154\172H\194pW\007\019\239W\141\004<\245\163Z\025_\199\192c\216b\215\251\203\030\175\203u\213J\155\198\192~V\230z\138=UF\137\168u\\\019q\174\227\156\169\174\146+k\2482:\025\245\229\1715\bW\149\154+\172\237\021{\188\230\004j\224\184\133\179h\225\\\200\026P\169?\001j\r\173C\018w\188\167%\144\139\149=\\\012}\026\011)\155\167\240D\242\020\133\236\137\197\192\190\004,\241TV\226\004\157\2454K\206\173]zi\223u>x\029\248!(\177/\149\183\131w2\133\183\130ghH|\016\186\165\235\1405cW\198\217\159JFUgd\031O\191\140\217\144\200;\143^\181\006\179\178\246\194i\007\2378M\145\157Y\209t\029\148U\243$\184\191\254rY\146\243X\253Mt\029\151\230\200Z#\222\243\171g\221\203r\226q\169\215\239\240\180\215:\197\139\211M\r\2046\137\190\168\133\207\254\170\132M\213c\254y\026\022\170F\151\163c\239\251q\\\137\007K\150\019\"\183\170v\129\1602\018\234\243(\215W\163\233P\007\200'\207\249K\249\229\021f\185c\160m\167P}j\165 \184Tf.\200\139\214b\188YQQE\170\172:\217\201\199\229l(Q\191\204\189Jb\178K`\183\217\144\031_C;\154B\021\188\197\153\230N^CN<\244\204\130\024\011~\167\028\129\239\232\252\007\189J\238\\&\210\023\182rY\005%u\167\208r\165\177\178\139\165\023O\186\217\167\241E/\252\204\015\219E\225\198\158\181\141F\241\158\137h\1577\154\234XmI\020\155\133M`gW%\236$QR\223qG-\159\214\127\186\030\202\175\153\025L\187\179\189\206\1949\216\209\2362\190\132^\189Y\1973\23053\217o\023\195C\143\138\150?b\228mx\199$\219R\221\174\1860Y\231\151\213\210y~\133\1383\214\2364\018^\159\028\133\214\208^\175\166\200\132\229)\196\028]\250\159\014\179F#\019T\2409\241\212\182?\248\"V\147\182Z_\155F9\234\219\005Z\237\243\"ey:\r\254\237\221\017\239\141ZE\243S\245Q_\196&\253\161\201! B\251\139X\226\1384y\189tD\174\214\244\195[\154\024\141\169vyc\141T[\128\235xB\168LQ1\219-\160\022K0\213\210Q\235\179\203I\028\223j\234\232\251\170:\174\252>t\253\248\186Az#\252:+RNP\177\020t`t\237\029\r\134\224\172l\243\219$\011\235\235\1558mRuq=\203'\225\208\245\152\175\222\132\245\190\136\150*\197\185E\236\225y\154\031\n\176o\005s\165\131x\244|\253\167\011\150\164\192\231=|\166\251\031\136\0302\175\135pB-O\t\149@\149\252\189\249\1767\132\250z\t\251\233\145\193U'7\169\249\018\173OW\\\251\245\201\140\255\029Y\173 \147)H\021\2517\178n\161\254\211\189b\221\221Y\201\254\140\180O -\015\184B\153H\152\133rz\231\193\002\224\003\180D)\202-b\143\204\211\253P\128\020-i\134^\002\225\155\219\187F*\201t\208+\163x\236\188\0302\181\210\189\194\193\166S_n\253\215\205*\155~I%\189\217\003F\179\134\222\180\209]N\196\006\201 \001\221\252\210Q\141\242\tX\253\247\127G\021A\190\1512\173*\\\216U\004\187\t?\2462\214\149~\185E\220\213\211h\231\239\025\175k\136\198{\234\139;6?^\223`\233\228nKr\177,X5o\187\139%\197\217\127\127\151\224\019\216\249\011\237Y3l\172\158\022$\127`\029\193/\1945\1960\167\247\235\187p\240)\189\212X\208@\165\188\177\222#\141\024\197\198\130h\025\249\137\025mZ!\231\197\178\155\213\1872W\251*Q\159{x\190\026M\172\135g\145[\226\r\241\158F\187`\207H]\132\239\160,\025\028q\137\007K\145\019~lr\nKs6\148p\132.\160\242\133[\029w\186\131\229\026n\238l\000{\171\0062#\212\150;\173\142\198\176\139wh\1609\196\153-yv\143X \019\234\139\162f\006\024\251\031\244*!j\250k*\213\205ws\014\0145G\152\179\197\207.\136S\134./\136\177\153\015\141\b\156\227^\136\225\132\187%wn4\149\229\027pd\187\167\189\214-Y\156ih\136\135\1855\215\230\193k\194r\193\141\166K\244\197-|\246_0\239N\2281\242\174\203\2242Qy\158\006\245\171!\255\nXQ{\212, o\024B[\149*\231\003Y6\028\165\205\006\225\240\163\200\028\149I\204d:\154\232fu'\149c\182}n\197\239\205\131\172\158\251~T\158L+\1602\141ue\026o\168\233\242\205M\170\0312\026&\227m\149A\139\148\232\016\205\173\203\134n\156{\178\255\025\018\157\234\011\011\r\232\0316\242\235\023\138\b\148b\216\155o\254\157\137\241X\243\225\248\248\226\156\163yfP\155\252\221T\187\194!\255N\237x\227\156\021\192^\r\005m\196\227#?\153\160h\189\201\164\207\198\162~\209\131Z\172\136\248\004\b2~-\162%\234\169\003\203\213\018\b\138\189v\158V\003]#UA\168\028G\153}^\015\153\\i\214\007\252mh\2007\144\235>\2001\204\158\185=r\026\003\186\004\185\n\154\236\159\188\134\129,\172\\X\191\176+c\161w\193\144\014\217\245\247\168\220\019\178\251]\247\207\\\145u\254~\130~\210\127R'Z\145\252\220\183\233\171Z\141@3\245\019\174\019r\016u\250\192\233\131\178\023 \160b \169\t\214\179\027\212\150J\186\004\238\214GxVpx\254\170\030\211\169\236/\026S\155\138\254\159Us_(\196\180\231L\176C\141l\210\162Z\131\156F5E\216P\245O\249(\130S\027.!\188\197\158Af\143\213\006\020\163\227\025\174 tK\1981\150B\028?&W]\195jZ\206j}\192\019\254\203\207t\142\250\209G\193\136;\148\019\030\2223(\200~\131\213\134\182\128\156\193\213)\249v\143\006\146\149J\166$l\143\227\138W\243r2\138\153\170\028h\213`%\136\208\195$R@\208\153UEk\248{/\149z\229\127\189\245\151\221\025\2187S`\230!\145\1595e\246m\203\236\187?\185/\232u\026\132\177f\153\214SS\229x\186^:N\029\177J\166fQ\136>\153\146\1375\131\251\246\131\007\190\212>\025E\163Y7\131\156\172\194\248.\028\190\190\002\134u\165Wn\007E\191\155\247\239X\157Jr\205\135Y\233M\2434\159\254\203\011\1477\240\031\213\0154\143\215\183Nm\018\192U\174k\030\171\207\239\202\020\244.9!\237\162!W\226\127B\031\147v\210lg\015\249\014\237\214%\205{X\029?\2078\131\023\252\020\154\149\201\"\215Nm\024\011\131\147\156G\156\207\232\2161:1Zf\"\162'P\232\011L\151\149\029\231\234\\\163\023\162^\173@\239\181\228\238\208\169%\028a\243\1606`hbg\249M\007N\227\216J\005\031\247\001\157\143h\198\242\r\004D\r\006\171,\161(+\171bDEgn\178\184\220\144\189u7tk!(\239\215k\195\244\135k;K\247O\230\238\175\248\156\241#t\211\167\250rO\176R\"\026\024u\133\r\017\182\196o\005\233%J\151\196e\202]\187\177\145\222\252\216\226\210\019\201A\183\132;\209W]\221\209<\212\213\235xeaL\131\231\172\210\171\163\241\156>\168[)\176\018\"\140f)\241cX\241\198\153\154R~\146\166\236\167C\160F\133n\154Z\154.\004\015\019e\147k\196\234\240\136\192\173\175/\227\216\217[U\182gx0\138`\nq\002\134O@\192\193\170g\193\245\019C\r\130W'\2316\133\162c\195Q\193kS\243\154\248]\162\225\226K\022\225sp\170x]\209E\187\240\005\152}m\207\b\184\231Jf\207\001\254\194n\023\167\233\231\153\025\245\216r:\149jg\178hu\027\183N6\021'9\143x2\163c\231\208\214\245\\\015\t\219\131\197\202Q\024\183%\210\182\2215\176\028\192\211u\020\169\165\198\146\187\211T.\019\202\155\199U\129\242\024G\225/\207p\n\140*\129\181^\129h.\019\n\228\004\248\199\165\006\141T\227i\172\154\238\204J\182\140\171\161\182\249VU\144\145\247\215\179\195>ol\170\192\159\156\204;Ya\002\027#\001\163\241\255\210%I@\2342\229n\184\213\184\130i\222\139h\255={\014\192\141\171\170\169P\tG&*\026\215-\189\144\020\244\2029S}>_K\203p|\192\246\206\222\137M\158YE%\143\206s\133\161>\170\166\004\143i/\235V\016>\132s\217\201a\b\190\130\195\156\196i+\130\211,>\028qe\175\186\152\022\014\135\023\233W\006u\017*\2197\139\212\225oSk\209*2\157\021l\147:\170;\\F\190\208\165D\142~\193!*\177\193\237\143\222\163\224P\004\228o\129\162\012\029\253\240\198[\141\006\135{\183\180\250\210r\233\218\250\027\015\2373\188$-\195%\155k\017\158g,ez*\193\205W\240\134\214:\170%?\163j5\"zH\230\144\011\190q\193\207\234]6\019e\157W\175\208\021\173F\202@\213\255>\160\186K\1994\184\226l\002nL\141+\129Z\248\135\005\135c$N\144G0\029\244Hs\207\234\2294\"E\173\021\0258\167\242<\216\212\248\206\171^\131\197\134\129\216\161y*\141\140\171+\247;\242\207\234x\020\194D\209v\"\129\196P\184\208\1720M\165\226\173\241qj\135\231\220/\193\231[\242K\136\249H\018\229>U\199\247v\212\156HwQ\210\226[R\029\183RM\011\233U\232\161\015\180\b\191'\221\223cv\030\000\026\252h\234i\014\139a\173$\011|t\181\134\251*\025\181\015G\196\023\190g\129\127\145\127\014^t\131\195\162\217\157e,\163\222n0\241G\027L\026\225&\154b\016\134J\186:\203\023\251\2027\184\156\031 \197\175k!\197\169\214\230\198\195\169\166\231kkq\215\153gR]\024\193C\024\018\247\158\027-2\216\165tK\000\141\228 \251\140h\142\210\204\161 \157\143\251F\175\229\129\127\209^j\017A\176\132d\185W\030$2S\255\007\005z9\223[r\214b\144N\156~lw\001\168\175\019\236\165\183Z\246\021Q\223a\211i&\023\137\165z\017\131\190\163\000\023`s\138%\00460=\161\195\215\163\248\222\155\149]r\251M\020\155\186\022\233\n\191n\205\152\167\191\000\220\1460JZ\004||-\163\253p\146\017J\184\147\012\184\1477\155\239\012\199-\180\001\235`\141\165\189n:\143\215\223#Z5k\019avTB\204\186D\003\236\029\217\000\003\204\027\001X\223\184\165\198\239!\160\030\161\t\235\137\176?\222S(X$\130V\141'\178-a\255\234k4x\002\0288\229\208Ce>\245\172}\214\163\188\240\184+q\003\177\132\254\031a\233\136ui(\147\194\2546\159\174\231z\149\249\136W\142\216\174\180S\174h\024w\248\160<\rnv\228\"\161\2100v\150\187\172U1\239\2402*Y\212\232\168!\181d$\203Mv\237\142\215\214\206\253I\011\165\223\176\236M\203&\183\130\129U\214\031\253\163\017\149i79\187'\191\140\178\186\252j\023<\247\181b\137L\236\177F\162\027\231^\155\182\127\128\243w\207\215\171\023\222\n9d,\172\178\226\232\nmW\001\200~rv_\030\133\188&\235\2338<\247\213\018\201\191\030k\164ac\165c/4w\019?\151\r\180\223K\031\135\231:F\198\016\128\128-\224\254\239\178\250q\172{*\246\211|P\158\022\203\127<\196j\228\028WW\134\n@\185Z\204\250\145\139\132\200p\150\155\226;\199C\240\185y\201\244&I(+\184>8\221r\226:\021\140,\188\182&-\175\001\147V\212\224W(s\138\242/\"A\178\249\240\172a,\174\186\220\167\143\162\014\161*\132%X\239\218\147\148,T\193\r\206Cs3\203c\161'b\224\1745)\161\139\248\220C\220\148\248\139k\192\150,\127\238\199\241y\015r\026\006Cy\007|\184\029xC\131\136\160e6!'mC\162G\237\151\170\154\000\160\237\153\204\193\200)\219\160\248Q,\225m\168\214\232\195\225\220\207\133\210\157\004C\147\b\016r\127\224\216\131\208\028\191O\139\199iJ\219\245\157\206\171\1740\128\017?pt9<\145\207\175-\197)\241\177\195\214\001\128\192\172\191Y}\159\128\251`\159\233\171]\165\127OA\001\216~\133G\146l\254Q\198s\017\247y\243\1420\0048FZxW\024z\253\029\143l\225\185A\143\000\241\135;\153\188\207\138=\1796\217\190e-F\142;%\189\166\215\200\207L\005\233zx~fl\224\184M\152\191nJ.\145\212\012Sr\246\156\142\156\1994PS\135KA\157\169k4\130\179w\182A\183\026\210T\175\151\215\223\250\011tu\172A\1656\149\027\165R\177\201\168V\027\203W\203e\171\141\133.\183\154\196R\217\003L*\181\225\207\249\211\173\005lV\001\149V\192b\023\208\234\143\0148}Zk\211@sf\206\178\142\156\221\159e2~\2458\228r/\235\007\"\226xg%\194\238\149Y\155\219k\210\178\231\182\231\204\249\179\228R\171M\206\214\149\177\208%\137\215\252\007\1656\145\247\007\132\253\131T\205\1390\2195\233\155\002\141\149\148Qq\208\b&\198\198\215%\183\185\225610\218\006\183\203J[\142\24677\155E\242\170C\163\232\r\1277\228\132)\200\238\1672:\188\179\169L~\1562\205\166\200\b\166W\2474\134\135%\225\176\226kW\137)\205\149^}9\205\182\004\212F\218\014\189\021\017H\181\141\166j\199\210\146,\184s~22\248\238\135\189T[pDy\208\149\1270\127\239\139\006\251\\]\021\157v\181\r\182e\230\212v\228,t\166\171\173\021n\145\220\199\145\211\168\2407\231\006\194\236UJ*\201\237\021+\128\217K:\236\151W C\161v8v\154\203T\152\146\207\228\185\204>G\1858[\249\011\194\254Q\138\230%\184\237\250\n\205:\190\210J\002U\\4\128I\173k\135\000\221\021\b\1558" let d_4fff47472c2ce7d1d0360d2345161ba6 = "7\217o\133\154d\153\202\187q\218QB\027\029\185\t\143ds\142)F\003\223H\170ma4f\024\0126D\140\149En\006\007\138\180sm\1751\027A\178\178\218\221\2360\173\218\178a\030\130\252\166\004z\148(\146\021\236[\134\138\229\025\220bR\030=I\242PXL\143\226\178\004\175\158\181\180\128V\193\216R)\240\1737 \224\221\025pr\022(\173\214Bo\216\155R\019\200z\004\000\236\160\182\222\239&PP\141\007F\221^\200Q\186cW\128\027wT\153\156\225#\003\130_O\236\248\206\207\186*I\172\244\145\b\213\144\2161\b\199\239\"\246\253\203\234\139\189\239\251\222\178\226q\141'\174\236X\152\133\208\142\153uj\197Aha\161X\242nfa\181\031?\181VQ[\1593T\215\023f\198\244\",\200\248\233\211\224\139l\025&\202J\020a[.\014\029mZ\248Y\139\225l\194P\128\1939 \005\022x\017wg\168\171\007\000\218\128\014 \201o\217!c\178\182l\160\024\026\003\168\244\228\1825\200m\161\174\168\178\232\234\133M\245\243<\178\003\004\137\133`\170{*\252Y\128\162\218:;J\167\238JKd\158\162\158\193<\199\240\002\221K\132W\173\227\181\183\164w\b9\210G\179U\031\251\132\230S_\2081U\232\0140|\143\233\007,?\194\253\164md\227\196\141\023_\023\137\133\237\016\134?\192\254\196\240\151\024\149\215\028\141=\2045\252\169\016\162\029\141\159*\192\017\240s\132\011M\145#\214J\188\207\220,U\017\017/\244\162\021N\015\0143\199\246?\248\192\193=\147?\141I\132\163\154}7\128\153\2204\188\1759\244\183\014\210\235\174|\166\180\243(W\141m\030Q-\143\136\149\014\165\210\177\183\182<\242\168\221\030\223\250\1969\231]p.\151B\030\141l\173\216\253\138\tCR\003|+%\198\127\177\230\194\180\180\211\030\223RiI]\162l\006\127\182\137B\142\227\191h\175H\1483\128a\003\193<\246\141$u\141\255\203\213@7\219\1853U\234\161a\158xH\014Z\135\180\195\196h\171\0306R\140\022\170\201iT0\216t\215\020\163F\1694\169Y\1433\215\230r\174\024\247\244#\222\220\014w\205\146[y~\237@\233\254\023\165\bU\132\150{\242|\005\225$\002\159GKFU6#\158\218\238\156{\166\251\210\152\136\179\026\254\130\164\141\022[\158\245\130x\138\234\016r\"I\242\233\141E\136\0257\139\t\146\246\220 c3\215SSm\1673\160\016X\016\180\022\188M\030\1404gb\235\243\026x\171\182\158\026\028\176V\219\147z(e\021g\204\003\204\140\209\183\209b6\154\002K\168\162\025F\141K\1520Vv\\\151\136\029K< \203\019.\183\174\199\177\178\177I^\171Om\198L\152\228\166\023\212\131W\217\176\181c\230r\155\163\188\132|)$w\148Y\255\150\005E\157\254\187{.F3\"\159)\235\r\\=\167\131\231\"\171_\222x\173>\146\187\004z\132\235S\161eS\0200H\134\021\184KsO\190B\029\220j\247\1333\177\026\203\148\152\188\144#\195a\018nC\129\027\2450j\199w-\143\207\200U\131\200\020 \001\011\226$E$l/\193\177\187\148\n\132\252\161L\189\1278}\024\241\208)\141\245\170\185\128\022\145nJ\193\184w\188b_,is\131Lf\139\151\245\128~\150\023\0270\223\020z\160\1620\172 \173\206\255\212\027\001h\130\250H\158Z\171\219a\145\237\128=2\137>\131\253\226\030Jg\027\r\154\241p\t\177\1739@\147\228\023}\218\151\228\1620\231\1405\213\235\208=\132E\180\237w\195\178\153Qv\249.5\217S\206]F\217@`l\210\168|!\018ECFs\172\028\027\145\248\164\205P&\186\150GI\163}\226n\016\003\218CO[\159[\192\148\130.\217rR\154\154P\162$\182\136\182zY\004\217\2168dq\b6\227)8\006\175\128\200*\2499E\225\206w\148\242\134\213\nL\222\204^\244I\178\\\245\217\1662\158.1\031\250\020\2397=\176Nl\213\007\235-d\bN\003\028iI7\029l\231\194\2061\018E0f\\\210\166Xx]\198\201\177\191\137j\178d6;H\140\167(F$w \240\0303\194\194\130'\1440\182\017\006\161\016\216x\237sI\251\2425\021H\000\211\203^#\225\204\245Sa\157\204\023\163\142\224rX\202(\254W\131\029\028@\018i\200\004\178Z\\\133\\\179\007\017P\175Ac?@U\163\170\2294_\209\031\194\"\025\164\138I\220\192\1916B@5\144$5\024\t\212Aj\233r%\005eP\221\128\2459`\159b\r\223\188\232E\191A\027 \203\240\027\127\130q\180\012\248i\174\217\143Rt/p\b7\211?\207\007P\142b[+\230.}6Nrx\030\161T\203\164\000\135\247\200~ka7\239\231;`ys\220\207\166\183j\207\234)\235\245\129\182\142\026`\0114I\195f\248\217\027\156\134\231\200O~\176M@@\168\218\18422\164\231\223\172\141\197\135\224\133;\151\210\026\181\251\144\021\014\237\153FS0\224\170\235w\159j\136\133\002\199\242#P\151\140-\0191\224CMD\183\214\155G\136\253Y\193sd\234\189m=z\189b>U\184Pp0\237\187bI?AX\201\217\2385\158K\244\196\"uK\170\031Z\\q^j\158[\\1\159Z\177\132\14512\030?\2064\187\138J\004\011\154\244\1476\229\191\232uQ\192t^\140d\163\232\132\231Z\244\204X+\241\164\183-\197A\239y\184\227\255*\177\129\225\006\202\199\130\171n&\247\189\244\154\153\189r\133O-\131y@\225\012\236\001\028\169-j\015\005\135\140\n_\170\199f2\218>g\138\018\185C\185\253\146\006\130\2553\149\167&2\181u\236\198\179\203,l\146n^\225\170\234\154X;r\237\233\203\179\186y\201Q\209\017[:t\229\201\203\147\220\188`+k\027[8p\233\241\2033\023\252\137g\173\150\145\153}\023\030\133;\1830\166\162\166\161=\2312\028\174\127\188\148\161\160a`\215\153\251\2150\161\011\230\226\206\220q\234.p\224W\179\190PO\234\196\173\231\230\225\233\188\202z,\246\252\129ZPU\131\133~$}CW]\133\005\204\253\159My;\197\188>\210\190\213Z\146\135\137.\207\022Tb\1740\014\184\204\177\209\145V\224\148\162_\239\\\165G_\238\223\011\159\020\189\011+\031\157\232\139+\014\187\012\024\168\016\128\195\144\145\016\017P:f\026\232\151\024FMA\154U\028\210\137\193\194\2170\230\203\243\025\185\015\022\240\143:\179\165\213T\153/\153\011\211\023\158\208\149gv\017@\249\167b\130p\1411\022)\141\204\234\023b\129\133\022Yl\137\165\150\2337`\249\223w\253\177T\169\159*\253\r0\208 \131A\184p\014T\146d(\176\194J\171\172\182\198Z\235\172\183\193\198\191\003\1875\1692\189\244\214G_\229*\026%\217\1341&h\205\015g\195\236\254\245\240\154clh\145\128\176\242V\003\136\131\213\b\169\213\233-\n\0213\139[\216\031\132\202p\016\143\210`/\230\\\r\213K\227\138\001\191\213+\000w#h\012\160'\180d/G\248\019R\191T\133V\133P\181\018\017\236\250\159}\202x\165]\133\171\016\0188$\157\194(\bA\166\208\149\1762\225}\186W\014%\201\150d\153I2\018F\171;\019I^*\190\207\2232\166\153n\134\153f\153m\142\185\230\153\239\164\215\222x\235\157\247>d\t\"\"\018\"#\n\162\"\0262@td\136\024\200Z.\024\178\241\166\130G\135\226\169\176\012\127rA )\162\"&\194J@\150\178.\254`\198\235\209k\130\137&\153\172\207\020S\ry\234\153\231\210N&\195\240$\019xqn:\140_\202k\155\131!\154f>\240Z\169M\243\218\007v\b\136\001\172\234,+L\200Ne{ID\158\005\217\170(!\176\194FLl\176\242\000B\";m\186\232\242\201\245;P\229\241&O\027\207\1362T\250\207\252\231\202B7\208\161\028=\136B8G\016\194\016\014\024B\233\225\183\157G\003'\160}\171t;\127\208\004\134F\020\204\195\22031G=(xg\232p\157F\025\r\193\197\2356\018.\217!\0068Ud#\002Y\196\230ZXF+-\131\216\189Vj\203\144\186&\250\233\138\218\144z>#G\133\145\170\004m\015\226N\146\016\138\200/PPnM\218\254\198-?\155 N6\146\248\001\165\005\t\255/\180\209\192\017\160\029\023]pT\029\004#\025\254\191w>\222\198\000\242NH\229\129\030\005(\2372\b\232[\185\128=\219\017\190\127\203'\148\185\128\249\002\016a\012\t\249\234\244\127\225^\147\178/\199r+w\138p\002N\197oD\199\199\152hO\225:na\026sXG\019\031\240\181\243 \137\239\235\186\173\245\203\235\147\203\255\207\023\180\194#\"\1834b\019\1797\211\149\1287\192)\151?Ykj\203v\199\190-\238?\128-\128\138\007\248\255\172'=\161\238\134\003\254o\244\159\031\255\002\240\217o\128\207\030\221\249\240\236\199\141\031K?\250\173\241\245G\163\031~\178\127/z\n\002\230\002;=\001y\204~\142d\030X\197=\167y.[\021\007\0281\228\185\191Y\206Q\188\225\206\218s]3\236\184\189\142\249A\199\236\226\176$g\029\006&S\028f(\254\223|\225\178a\203\142\003w\002B\"b\018\222|\248\146S:c\151\179\025\193\137\248\160\018*L\132(\241\018$J\146!\139V\142\\\005*T\209\169VK\175I\179\022\173:\156\138\005\167\253r\216AO\189\244\204\171Xj\162\183\166\140q\195o;\194\209Ws~\154hK\164\252I\t\187#c\147\177n\218n\155\029\014\235I\nN\208H*\157\165\192\227\011\212U\213\132\028\145\145\190\129\216\208\127\198R\235X'%\163\224\161F\016\127\001\212\002\005\011\017.N\180\024\177\210%K\145*R\190\018\133\138\148)\246\213\139\026\213\169\215\160M\165vn\202\227i\1686:s\213\021w\221s\199\193\175\014\144\157\175\023@\136\188\181\243\243\224P\176e\205\024\024\004r\233\029}\175W\242j\211G?JS\016\175]\203\003;\255`?\223\161|{\229\184\185\226\232=\012\145^;R\139\255\2130B\221\211\174\017!r\226B\1555\b\024lA\002\182\139aA\n\244\193\247?\242\244\170\030E\157\173^\1392;!3\127\252\218\137\138I\239\192g\1357\238\204=\245\166\150vGv\223=\178O_\236sD\154M1I\137\153\208\225\253(\012\145\030b\003t\030t\179M0uSJ!\141\007\127\230\012\137KW\137\1421\200\187^\144\001-\144[\236\131\130\135\142B-\165Z#\226I\138\130\028**\232gQY\184\137\236\136\145A\158\187T\138\212G\246\"#.\145\202m" @@ -160,7 +160,7 @@ module Internal = struct let d_5fcd7eba230acf47d54c1897a9a9c394 = ":t.slice(j-100,j+100),mode:n.mode,resultSoFar:v},_emitter:M};if(o)return{\nlanguage:e,value:Y(t),illegal:!1,relevance:0,errorRaised:n,_emitter:M,_top:N}\n;throw n}}function x(e,t){t=t||g.languages||Object.keys(i);const n=(e=>{\nconst t={value:Y(e),illegal:!1,relevance:0,_top:c,_emitter:new g.__emitter(g)}\n;return t._emitter.addText(e),t})(e),r=t.filter(O).filter(N).map((t=>E(t,e,!1)))\n;r.unshift(n);const s=r.sort(((e,t)=>{\nif(e.relevance!==t.relevance)return t.relevance-e.relevance\n;if(e.language&&t.language){if(O(e.language).supersetOf===t.language)return 1\n;if(O(t.language).supersetOf===e.language)return-1}return 0})),[o,a]=s,l=o\n;return l.secondBest=a,l}function w(e){let t=null;const n=(e=>{\nlet t=e.className+\" \";t+=e.parentNode?e.parentNode.className:\"\"\n;const n=g.languageDetectRe.exec(t);if(n){const t=O(n[1])\n;return t||(W(a.replace(\"{}\",n[1])),\nW(\"Falling back to no-highlight mode for this block.\",e)),t?n[1]:\"no-highlight\"}\nreturn t.split(/\\s+/).find((e=>b(e)||O(e)))})(e);if(b(n))return\n;if(k(\"before:highlightElement\",{el:e,language:n\n}),e.children.length>0&&(g.ignoreUnescapedHTML||(console.warn(\"One of your code blocks includes unescaped HTML. This is a potentially serious security risk.\"),\nconsole.warn(\"https://github.com/highlightjs/highlight.js/wiki/security\"),\nconsole.warn(\"The element with unescaped HTML:\"),\nconsole.warn(e)),g.throwUnescapedHTML))throw new J(\"One of your code blocks includes unescaped HTML.\",e.innerHTML)\n;t=e;const i=t.textContent,s=n?m(i,{language:n,ignoreIllegals:!0}):x(i)\n;e.innerHTML=s.value,((e,t,n)=>{const i=t&&r[t]||n\n;e.classList.add(\"hljs\"),e.classList.add(\"language-\"+i)\n})(e,n,s.language),e.result={language:s.language,re:s.relevance,\nrelevance:s.relevance},s.secondBest&&(e.secondBest={\nlanguage:s.secondBest.language,relevance:s.secondBest.relevance\n}),k(\"after:highlightElement\",{el:e,result:s,text:i})}let y=!1;function _(){\n\"loading\"!==document.readyState?document.querySelectorAll(g.cssSelector).forEach(w):y=!0\n}function O(e){return e=(e||\"\").toLowerCase(),i[e]||i[r[e]]}\nfunction v(e,{languageName:t}){\"string\"==typeof e&&(e=[e]),e.forEach((e=>{\nr[e.toLowerCase()]=t}))}function N(e){const t=O(e)\n;return t&&!t.disableAutodetect}function k(e,t){const n=e;s.forEach((e=>{\ne[n]&&e[n](t)}))}\n\"undefined\"!=typeof window&&window.addEventListener&&window.addEventListener(\"DOMContentLoaded\",(()=>{\ny&&_()}),!1),Object.assign(t,{highlight:m,highlightAuto:x,highlightAll:_,\nhighlightElement:w,\nhighlightBlock:e=>(X(\"10.7.0\",\"highlightBlock will be removed entirely in v12.0\"),\nX(\"10.7.0\",\"Please use highlightElement now.\"),w(e)),configure:e=>{g=Q(g,e)},\ninitHighlighting:()=>{\n_(),X(\"10.6.0\",\"initHighlighting() deprecated. Use highlightAll() now.\")},\ninitHighlightingOnLoad:()=>{\n_(),X(\"10.6.0\",\"initHighlightingOnLoad() deprecated. Use highlightAll() now.\")\n},registerLanguage:(e,n)=>{let r=null;try{r=n(t)}catch(t){\nif(K(\"Language definition for '{}' could not be registered.\".replace(\"{}\",e)),\n!o)throw t;K(t),r=c}\nr.name||(r.name=e),i[e]=r,r.rawDefinition=n.bind(null,t),r.aliases&&v(r.aliases,{\nlanguageName:e})},unregisterLanguage:e=>{delete i[e]\n;for(const t of Object.keys(r))r[t]===e&&delete r[t]},\nlistLanguages:()=>Object.keys(i),getLanguage:O,registerAliases:v,\nautoDetection:N,inherit:Q,addPlugin:e=>{(e=>{\ne[\"before:highlightBlock\"]&&!e[\"before:highlightElement\"]&&(e[\"before:highlightElement\"]=t=>{\ne[\"before:highlightBlock\"](Object.assign({block:t.el},t))\n}),e[\"after:highlightBlock\"]&&!e[\"after:highlightElement\"]&&(e[\"after:highlightElement\"]=t=>{\ne[\"after:highlightBlock\"](Object.assign({block:t.el},t))})})(e),s.push(e)}\n}),t.debugMode=()=>{o=!1},t.safeMode=()=>{o=!0\n},t.versionString=\"11.7.0\",t.regex={concat:p,lookahead:d,either:f,optional:h,\nanyNumberOfTimes:u};for(const t in A)\"object\"==typeof A[t]&&e.exports(A[t])\n;return Object.assign(t,A),t})({});return te}()\n;\"object\"==typeof exports&&\"undefined\"!=typeof module&&(module.exports=hljs);/*! `reasonml` grammar compiled for Highlight.js 11.7.0 */\n(()=>{var e=(()=>{\"use strict\";return e=>{\nconst n=\"~?[a-z$_][0-9a-zA-Z$_]*\",a=\"`?[A-Z$_][0-9a-zA-Z$_]*" - let d_609f576f064dfa5ea1545119859f0158 = "or: #002800;\n --visited-number-color: #252;\n --unvisited-color: #380000;\n --unvisited-number-color: #622;\n --somevisited-color: #303000;\n --highlight-color: #303e3f;\n --line-number-color: rgba(230, 230, 230, 0.3);\n --unvisited-margin-color: #622;\n --border: #333;\n --navbar-border: #333;\n --code-color: #ccc;\n\n --li-code-background: #373737;\n --li-code-color: #999;\n --toc-color: #777;\n --toc-background: #252525;\n\n --hljs-link: #999;\n --hljs-keyword: #cda869;\n --hljs-regexp: #f9ee98;\n --hljs-title: #dcdcaa;\n --hljs-type: #ac885b;\n --hljs-meta: #82aaff;\n --hljs-variable: #cf6a4c;\n\n --spec-label-color: lightgreen;\n}\n\n@media (prefers-color-scheme: dark) {\n :root {\n --main-background: #202020;\n --code-background: #333;\n --line-numbers-background: rgba(0, 0, 0, 0.125);\n --navbar-background: #202020;\n\n --meter-unvisited-color: #622;\n --meter-visited-color: #252;\n --meter-separator-color: black;\n\n --color: #bebebe;\n --dirname-color: #666;\n --underline-color: #444;\n --visited-color: #002800;\n --visited-number-color: #252;\n --unvisited-color: #380000;\n --unvisited-number-color: #622;\n --somevisited-color: #303000;\n --highlight-color: #303e3f;\n --line-number-color: rgba(230, 230, 230, 0.3);\n --unvisited-margin-color: #622;\n --border: #333;\n --navbar-border: #333;\n --code-color: #ccc;\n --by-name-nav-link-color: var(--color);\n\n --li-code-background: #373737;\n --li-code-color: #999;\n --toc-color: #777;\n --toc-before-color: #777;\n --toc-background: #252525;\n --toc-list-border: #ccc;\n --spec-summary-hover-background: #ebeff2;\n --spec-details-after-background: rgba(0, 4, 15, 0.05);\n --spec-details-after-shadow: rgba(204, 204, 204, 0.53);\n\n --hljs-link: #999;\n --hljs-keyword: #cda869;\n --hljs-regexp: #f9ee98;\n --hljs-title: #dcdcaa;\n --hljs-type: #ac885b;\n --hljs-meta: #82aaff;\n --hljs-variable: #cf6a4c;\n\n --spec-label-color: lightgreen;\n }\n}\n\n/* Reset a few things. */\n\nhtml, body, div, span, applet, object, iframe, h1, h2, h3, h4, h5, h6, p, blockquote, pre, a, abbr, acronym, address, big, cite, code, del, dfn, em, img, ins, kbd, q, s, samp, small, strike, strong, sub, sup, tt, var, b, u, i, center, dl, dt, dd, ol, ul, li, fieldset, form, label, legend, table, caption, tbody, tfoot, thead, tr, th, td, article, aside, canvas, details, embed, figure, figcaption, footer, header, hgroup, menu, nav, output, ruby, section, summary, time, mark, audio, video {\n padding: 0;\n border: 0;\n font: inherit;\n vertical-align: baseline;\n\n}\n\ntable {\n border-collapse: collapse;\n border-spacing: 0;\n}\n\n*, *:before, *:after {\n box-sizing: border-box;\n}\n\nhtml {\n font-size: 15px;\n scroll-behavior: smooth;\n}\n\nbody {\n text-align: left;\n background: #FFFFFF;\n color: var(--color);\n background-color: var(--main-background);\n font-family: \"Noticia Text\", Georgia, serif;\n line-height: 1.5;\n}\n\nbody {\n margin-left: calc(10vw + 20ex);\n margin-right: 4ex;\n margin-top: 20px;\n margin-bottom: 50px;\n}\n\nbody.odoc {\n max-width: 100ex;\n}\n\nbody.odoc-src {\n margin-right: calc(10vw + 20ex);\n}\n\nheader {\n margin-bottom: 30px;\n}\n\nnav {\n font-family: \"Fira Sans\", Helvetica, Arial, sans-serif;\n}\n\n/* Basic markup elements */\n\nb, strong {\n font-weight: bold;\n}\n\ni {\n font-style: italic;\n}\n\nem, i em.odd{\n font-style: italic;\n}\n\nem.odd, i em {\n font-style: normal;\n}\n\nsup {\n vertical-align: super;\n}\n\nsub {\n vertical-align: sub;\n}\n\nsup, sub {\n font-size: 12px;\n line-height: 0;\n margin-left: 0.2ex;\n}\n\nul, ol {\n list-style-position: outside\n}\n\nul>li {\n margin-left: 22px;\n}\n\nol>li {\n margin-left: 27.2px;\n}\n\nli>*:first-child {\n margin-top: 0\n}\n\n/* Text alignements, this should be forbidden. */\n\n.left {\n text-align: left;\n}\n\n.right {\n text-align: right;\n}\n\n.center {\n text-align: center;\n}\n\n/* Links and anchors */\n\na {\n text-decoration: none;\n color: var(--link-color);\n}\n\n.odoc-src pre a {\n color: inherit;\n}\n\na:hover {\n box-shadow: 0 1px 0 0 var(--link-color);\n}\n\n/* Linked highlight */\n*:target {\n background-color: var(-" + let d_60fce158c679263a08140618240b48c3 = "\n/* The browsers interpretation of the CORS origin policy prevents to run\n webworkers from javascript files fetched from the file:// protocol. This hack\n is to workaround this restriction. */\nfunction createWebWorker() {\n var searchs = search_urls.map((search_url) => {\n let parts = document.location.href.split(\"/\");\n parts[parts.length - 1] = search_url;\n return parts.join(\"/\");\n });\n blobContents = ['importScripts(\"' + searchs.join(\",\") + '\");'];\n var blob = new Blob(blobContents, { type: \"application/javascript\" });\n var blobUrl = URL.createObjectURL(blob);\n\n var worker = new Worker(blobUrl);\n URL.revokeObjectURL(blobUrl);\n\n return worker;\n}\n\nvar worker = createWebWorker();\n\ndocument.querySelector(\".search-bar\").addEventListener(\"input\", (ev) => {\n worker.postMessage(ev.target.value);\n});\n\nworker.onmessage = (e) => {\n let results = e.data;\n let search_result = document.querySelector(\".search-result\");\n search_result.innerHTML = \"\";\n let f = (entry) => {\n let container = document.createElement(\"a\");\n container.href = base_url + entry.url;\n container.innerHTML = entry.html;\n search_result.appendChild(container);\n };\n results.map(f);\n};\n" let d_62016f2316dffaac5eecc447ca24c81c = "Z\195\229\202C\147\172\201\012\133\016g\129\1363\134A\135z\186\216\000]!\192\004Fk\245\251\253\207\238\128\029\005\186a\196\181\221`\004\1644\\\184\031[ \136\195\144'\139\152w;+\213\0116X%\165t\000^\204\243FG2C \213\004\017\211\208\132\198\r\136\re\205\1838\031Az\225u\148s\250\194?<\151\132\225\209\218\196\203l=\015\006&K\002E_\228!:w\2361\214\027\188\134\201\231\158\002uhH\229\152\160\203\224i\015K\n\130WPh\\\127\018Jv\143\147\026\000+\1348h\207]S\200\143\221]\166\022\216\132\180\171\190@\194c\187\1296\170\164\169\131\174\232y\1423T[\000A,Jz\240\207\029\215\253\174\129R\189\149Tx\251\018\149P\b\rP\185\149;\203\245\238\183\235\218\166*\148\011\0219Y\226&`\165M\232)\148\024R\245A\0067)L\n\156\021F\167\236\157:\211\189Gb\153ot\224A\248\208\151\250\185\159\\w\222\130\017\129\1736m\131\232\240\180VD\024Q\253\004.C\nD\194\193\133\217\030\164\016\192\1536\015+$\207\253\209\140\028\000^\018\1483\165\183LO\182\168\201\016r\150\187n\174\\b\205{c\157\166\183\215\165\235\150\247\203\187\243\177\155\207\242\197\249\017\\l,\016}B\156\145\178u\202[\135h[\163b\132K\207;\189Fg\194\206\225|I\206\215u\014\240\250\226\b\131\216\181\030B\152\211\186\004\151\188~p]\021\203\167\195`V\244\173~d:b\158\169 \022\164\194\183T\t&\129\022\144\152\015x\155\025\136k\018c\142\232ox\149\0274b(\"\017\218\168\254\184\154\028\156\132\025\0118V\250\180+\233\143\205\206\246\159\171\031\007f\194\224\024\243A\"Q\018\180\0196Q(\219aY\247\165L\137\225\147\219\234\137\185S#\206\007>\247\026Sj\215o\218\006\0055-\000hM\247\215}\254\136\r\244\250\tM4r\234\189%\156\020h\172\\2\028\026\011\237\t\178c\211-\180\139@\026\191\019]\158\209\180\219\196\143\135\198\019k\242\025\005\235n\156\028\225s\167\155]\201\239\247\216\215\229\180\227\217@A\168\186\168\251-E\230l\204\237\224\237e\030\026\215\196.S0-F\027\152vkK\\{\128\030\254\020q@*\000^\1846{\1920\n\158\204\220m\200@B\220a\194\002\134\253\188\179\206\194\230\137\197U\145\254\190Wo9\193\172\006_ry\207\181\249\242G\135\206\243\129T\2425HPc/;&\210\208\197\151\"\146\195\249\188Iq\031\129\001\006\000\156p\138\145\165S\n(8_4\183\226K\001\211\230\209;\159\167t\132:t\024\249\130\244^\131%'e\146z\023ua9\173KA\229\143\197\235N\253|\239\254\"J\209\205\003\129\017\236\236\135}&r\031\148\176\129\199\136'\172\1608\014o\141\205\216{\138l1\247;J\189V\229\130Q\158\190A}\160\144$\\m`CP\189J\224\1495V\234\181iB\215k\141\132\232rR\229\178\156\172\243\173\173\127Y\n;\149\166\160\148\255\149j\211K\243\140\134!?j\015\rT\188f\226\254R\242\180\140\158\128\028\222\185\230\193\t\000q\255\241\233\205\229\012G8,\019j\184\169\193C\178)4MH_\014\184\208\165\166\026\241.\255u\217\246\138&\016\241\1918W\2176\0199\228\128\165\188\132\023\024\029V\127\132O\011\215\227\204\210\229\202\186\236:]\159\187\148\005\189\1863q[0Rn\017>w\215\242\192\217\167\241\196:\137\b\0056N\180i\136\155_\182\222\015U\031'y\202\215\221\0267X\1583\235\181\151F\141P\191\137\253T\250w\175k4\152\183$\164\157\002\153@;As+{W\218\190nl\182\020\221\002gX]\184\189^\230\188\169\184\129<(\219\004\218 \160\218\172\026\176\015\1296\019\023\007\001\241\144\251\204\144\"x\rw\184\182\003\248\227V\207Y\145\2394\226\218\204\252(\133L\004\r\159V\170\219\201\003\192@\000\005\188-\024>\020\024\031?\rz\232\245G<\004p\002j\233\220\160E\1432k}\203\007\183\211\030\230\234^\030\244\014 J\001\211\031^\2037\233(\182N\000\019\022\148\158\205\133\140\011\225\153\146\213E\218d\234l&\209\129\031\251\246f\218\243S\187\137t\1302\139\172k]c\139\237\236\015\022\233\180\150N\174q\149#N\159rhk\180d\209\248Y\134V'\001\005\145K\002\151\198Z\132N@v\252\2511zn\243\164L\028{V\0298;\206y*\138\233\253\244\174\240\005\028a\181o\\\018\198\177\015\221\214V\244+0\247\006.\218L]\000\156\018~\248\141\030\154\138\221\175\226s.<\236\128\145\183CS7\135\156\168\225\000\211\135\179\183\186\141GJ\181\193\243\1778\216\209\156\171Y|\186_\149p\182\243i\021n\028.\243\224\212\211,5\211\150^\163\137\246\151~\179q\216a\163\230\155\156\222\149\014N\183\238\232\129\230c&\016\"D&t\144\227O(A\225\144\000\021\236\018 8\015fB@jSR\026\249Gr\1976\023\159\b\170MH\t5\197J\164\137\241\215z\158\250&*\028\140M\231\\h\216Q\163\240\186\000\241w\187\134{\1441c\230\005\203\248V\243[\255\190/\211\133\134\203:\250\t\191.U\181|\\>Ts5\157\252\141W\231'\129\218\176\177P\192 \176\151\026\\\240\202\231\1552\185\183\183\025\026\245hR[\213\028\189\134\245\134\128\130\006U\181\233\210\012*\225\018\157TJ7\166]\241>Wn\232\r\189B\131n,\220\171_\171\218\216o>\144\2354\205\000\238H)\181:-\225\015\227\170\168>9wBP\219\146\222\\_O\214\159\178\136M\130\004\234Q\210pA\211\165g\211h\220\237\224\209\169\226\220Ry\210Fuq\211\161\163Nm\238@\024\212P\248\136\161W\133\223\226cc\227\164V\212\177\219\028\185\133<\1357p\201]>\174+\250>$\232\162\254\138\005\247MFi\247?\149\015\248-\251\255\207\183\222\129i\236\193'#\001\004wu\221\189E\239\146M\194\158\024\225\248\209\226 }7~\170\197\216;\018\128\127|\152\251;/\148\199C\240\130\158\229\027\156\188'\230\214\172z\027\160\229\026 \249\227\n&\161\211T\165H\"8N\202\133rC7\199m,+<\208\158\140l\142d\2030<\246\147\130\1435d\221\250JU\254c\011jmz\004g\190\022\250H\171X\153`5]\232*y9\192*V\174\155\187v]]V\163\128\164\129\206\001\028\136]E\248\171\249B\025\000\242\189\208#\251o\132\218I1\030c\157m\164MD\218D\219\223\189\004'\005\230vM\000 1Y\150\247\0147\188\183R\146v\175\180\133`\1891L\027\181\000\180Q\250\192\196&v\024\231\137\021\170_\178\233\21459\151J\164=\1977\206to\189%h\134{\221u\025e7cr-\214\188\025%++\179\142\022\002\170\166\170UU\021\193\000*\005\185\244\029X\173\028\149\172\169\012=7L\128\006\220gd\133O\229c%\186\227[l\222J\245\1514\144 \n\239\224\001\232a\171\031\205\161\221\184]\029\135\234.\139E\174I\177\168\153\242JiM\182Q\151\250\\>PX\197\195\177\226%\131g\027\n\178\186\138\128\004\195\170\172\134\161\151\128\162:\184\171r\215\".\222m\023\024\209\150\205\218\222\228\184\134\248:\199\196m\209\2249Q\031c\161\185\246\251F\237A\197\152\250\152\187\205\255\002UM\164\192\172\198\218\1485\158yd!\240B\217.\247\131\255\237\247P\149\243\220\228<~\242\198\253\197g\209\183\236]` \014\030\206\250\149\135\172\227\007\163\130$*\132\175i\127\251\243\153\1661\001x\160\195atKbq/\231\153M8\136d\159[c\156T\015d\166\207'\208D\203\174\127\252\189\003\017\168\001\162%\016\192\241\017\030\159$goJ\027\146\018Q\205\005\b\222\b\016\155\158\134\153\143\223\156R&\2363\233\t\241\174vF\190\160\018\228\159\012\021\1398\184\215E\028\149\1462'KJ^\185\020\251n7\166\004i\028\161\206\195\1919\228J\245\1814\131ZE\244\167\204\131\188+\190\004\238\025%\0306\014\160K\012L\203\171 \025\176q_\163\026\214\175+\176qF\241B\196R\016f\164-\220\"\186\139)rpw\2549\1446\144\158\252@8\023\242W'\180\235\220\b\150Mqu\165\184\152`\026/\199\024;\153s\186\206m\200\t\023\237@\231*\227\171\163l\174\167\227\201K\144\251v\031!\1915\151\027\210V\139@\027#\024ev\144\144\168\248iP\153\202}/\233\158\172\\e\172\246\204\229\240!\179\203\2005\144\162\196\229\185n\201/;\178\024\029\184\253\021\007\173\253\160n\238L^\127\150XY\237J\242\t^\167\166\202zLV\219\004\202K\135\182\174\168G\192\200\147\031m\154\011\026\200\136\246\019(\228\142;y\214\207\140\200T\011z&\199\024\139 \246\1770\215\198\018\193Mz\178\247]\206\235\203\156QM\210\014\012\001\200\149\014\127\242\r1PT\170\170f&wm+k\216q\177\168\142\202$\248\154\027\147\012l\193\137KlH\151t=9Kpq\243\2148\201b&\249\227S'\201\005\217[\230\183\212O\240vWc\233R\245\020X\149\133\226\221a\235\245\206\141C6Z\222t\132\027\135\0295\b\165\133\189\244g\237\237\2178\224\181?\180l\145\208J\153\136\165t\019\219K>b\222\134\178-\n\136#\028O\028\147}\168\255\2057\218\212<\0243\163vp?oA*\244\255\240ih/\242};\014\215\162\196\202o\191\251\146\187\159\127\014\192&\152\245\221Bc\178*2H\152\182V\r\001\179L\148\153<\024m\136\182\030\140\187\004\2155\002\177\140\"5u$8x\190\154\228D\129:\ndd\141\149\232\023\195kv\029\133L\198\014G\202\158\194H\238\172K\197%\145d(2'y}\202\193b\\\018\226\222\202\162w\215\199{\135\186\022bWw\127\014\239\223\156\235\181^\220 *QZ\189{\248\227\158\152S\148Z=Sz\017\127\160\022\147\253q;\166|[&\159O8y\014t\026\147,~\255\200\2369\005qL\227{\2221G\201{\031~\215\206\142%\249\194\195%\141\150\175\131(G\170\132o\176R7[-6\139\190\152\018YyH\227\145\204\240q\029\237\174\173\177\203\n\173\186\229i\223\244<\244\136\162\152\176\132{v\251\144\243^\023\151Z\248\011K\226x\172=\181\240\179`\006sj\227$\141\211\139\203\006j\233\227\163\182\014QS\197k\139h\\dd\016\144\133\150X\0064\b(\247\225S\179\226V\146\145\015\186\205G\151\127s\138\235\1737&^I8\226\156\128\140\224\024\011|\170s\177<\221\170\223\171n\011\\\237\147^t\244\130\199g\222\166W\237\236\2387\002wl\250\176\015\161\026\166kw\212\129l\188\019\174h\\\199\243\141\173\155\189\186\r?\232\1568\160c\\\144T\204\209\228`{*\006)?\208\005:v[\199;\018\003\233~\173\189{\227\175W:\255-\137\151\0146\206\180\212\169\134\138\219\13982dZ\nA8\128g\018\211]\165\147\226\"\031\025\t\132\023G\196\r\151\189i\181\248l\n\154:E\235\1453\242\195\160\214\2008\004\237\2279\137\000B\023\207\233\205\025T{u\007\007\196\238c\177\011\245s\255{`\154\231i\141\138\243\183K\163vft\203\016\139G04\127]\139\238zw\171\201\214\242\155X\204\190\145\241\177\211\213\137t\177T\180k\135\216y\239#\153\218G\004\139\024iX\173\193\150\224\254_\140\214w\173\1663\\U\191\252!\189P\188\r\166S.P\031a1,\022\233w\136\237Q\139k\203Z\148\191/\155\022\196T\016\b\027\227\214v-9%\167z\r7>\2337!F\239\196\1908v9<\162/\017\018\245H\142\002 \233UQ\147\198\190\198\160\029\159\153\t\241\187o.\027\157\243#_4o\016\022\201\136\236\020\249\020\248[R\213\139(\164\152\238y\155\174\028\165q\130\219\205\140\175t\240\0283\175&\245\006j:\132>\173\207x\245\007\200\012\135\142\190\t\150\169tLo[6*\198X\154\"\235\014L\r\023\007\215SC\\\246\185tm\011\194x\177c\182\206h\025V\220\161\129L\207qz\186U\243\242*\000\161St\133.v\194\175N\208:\162\003\217*j\232\023\209?wd1\128\164\180\180u>\155\132\026\156\167~A\239\240i1S\179\244\216\133\162\236\229+\241(W\206R\190\210(N\164\012]\154@\209@\1859\164\167\226\184\165u\1843=\tu4\206\183\189\149\152\173`}\022\177d\016a\147\160o\142\200\204\127q>\226\235\140\003\160\246e\202\140]\r'\190g\225\237\001\212#\223\182\222\030\t\002\218\195\003\205\206q\127\198\174\149\002p\215\r\130\228\020e\221\138\235\005\210\219\199\138\131\204\251M\226c&\137s\158)\219\001r\130\000h1d\128\2244\136\1363)\142\172m\231\221\137t\208nsQ4$\235\\\193\221q\157\207\246=\251\142\189\007\219\142\239l\0019\225C\b\144\027\228\005m\177\219A\190\020\249\t\199y|\236P\252\210\b\169\247\028\168\003\228\020So\178\255\239\143\129\\1\128\231\227\254\162\"W\140C\226\180\127\011*f\145\131\139~)\139\1291\027\235\231-\n\139\003\252\143\n\251\208.c\029\133\147\158?'\177\171&\007\211\237\202\212\029|\024\179\232h\206\202\029\166.D\187\239>\168\199\206p\245H\156\225lLS=K=t\167k\236U\223\171w4\215\218\141\017J\252\233J\136\006\148\249\136\159\192\000\243{;\1903\235\153\\\1289\231\174\184\245\023\b\244W\140]f&\160\1981\176\154R`\204mP\2026\180\144\198d\223H\167\b4\204\132\004m'\178\194T\172\196\184\003;h;:\190\156\026\003\189g\207dxJ]\241\207H\238\210I\252d\203\204\212p\172\2273\242\135\007\157\155)_ms\190\135O&:%E\005Ej\156o\181\175\237\230\244\217\134%\230\128Pc\168\149\199x\012\198\241\242\191E\182k^\193\024\027\252T\205\146\148\254\024X\\O\219=S\132:,P\255`\182W\015.\156_9\232b\168\224$\174\202f\153\235Yd5ni\014\153\183,\1789X\147|@\174Y\207\229#6\n>OD\242\177\025\007)\145\254\166\228\249\199\215\244\217\190\130\230\221QP\208\029N\232\165\1759\186f\209\238\233\137UG\199.w\141WT:$a\210\211\179\017s\167\142-\187t\185\179N\158\204(#N<\240\204^\193?U\031\140\025\199~\144\n\127Z\240\206\245\238\203\\\247\142\233M\177.8\225Y_\132;\002\219:\189+\198\133\199\028\143]~\236P\179y\203|\139M\030\192\238\146\200\254\145\128\241\230\138\193\133\031\152\251\237\018\232\185\182\024\2473SA\003R!\221\192\255!\175u\1865\235\135\172\251j\168\247\158Ua\171<\155\191\020\220\1551\239\255\170\239]h\234\247\246\182N\183\222L\245+u\249\005*\189DE\201\253U6a\192\027\226\157\154,C\r\174\138\169(\192\228u\r\158\153\2201z\177\127`dfg\231|\201\176^/\153\179`\190lX\171\151\012/ \162\1828\138Ti\151H\243\246C\244\208\214\233\243q\215;\005\n\182\198\246\167S\161\228\231\147\178\231\138\253\237L\235f\191/_U\160\014\137\205|6b\193\161P3\170\214_\192\021\218k\169\138E>\171P\161\018\022\242\020\020\018\228\138\002\254C\016V\229\247\146\202[\237\247\003\0251\254k\016\240\247*^m\173P\223\212;T\127\191\245\1483\207\154/\201\179:O\181A>\156j\255bj\238\023S\189[\229\144\215\243\229\255\169\254[\232\154\n\177\165\218\167\029\138\167\249\210*\252\228\212\220\215\163\175{\206\t?j\029Z\147\1896\187\231^\1959\025\182\1625\242\151=\131[U\219U\221\191\236\134A\138b\138>\246\006\222\n\002\167}\158W\180\191J\161\206,\1895z\226\1463\155e\246{t\182aO\167\030\2058\203\135j\227\n!\198\000\198[]\237s\252uQ \193\208\218\196\006%\131N\188EV\249`Q\169\144Y@k\174!\023<5L\149\190UB\200\021\012g\188\020\151\171\180xt\246jW\021\025S\229\203\220\027\015V\235\208\249\\\t!\253\165\132H!\153q\170p\199v\128\025\173'\127rWD\167\147\225p\200\206\238\141\130\178\031_\234p\164\242\162esz\027\214\150\185s%\182\224O\141\177\200-\243\133\129\1462\142\143\131\222-}\221+\025\\e\148\145\025jJ\t\154\2135oE\159E\212\223\1701W\023\2283\149\239\1652}\1608\160w\201X\235\030\208/sai|\221\210\144\130\200\167\252\187\253\015;\234!!\255\191\031\127\nFJV\234q\212`p|\200\194\232\243\171$\022~\220\022\1880Pr\190AF\213\191]\152\031\252np\250\207t\147=\254/\149\246\231\189^\161\227\242\018[\222@\163J/\175\205\0197\022h\248\141%\">M\003\191\011m\241I\149j\029&9\r\210\168@\019\217r\179\201\"\179\243%\138\226\000\243\212*\163A\152#K\199\210\228\198 \138\2195\178\170\223\196\239\175Wk\171\187\023\247\1921\001\245/\242\130\b\195\2030\157\192\196\227?~\162\134\163\nr\196\172\012b`*\214\186}uhu\167\173\179\136\193\208\251\bB?\227\229\r\r\144\249\146&\165\177\024&?EB\217\181\243X\028^Z\200s\229\208eD\211<\231\160\167\"\155\168\226\149\193K\199\184f%\022\139,\165\249\212\026>\025\242`\2347\162\138\197\229\218\131T\137\003P\150\181\b7\236e0k\216\012>\167\182r\253\245\187\175\2368\154Vk6\012\133B4\030\030#!\023w\135~l\140!\166^J\153\015\135\207C\162:\224\b\213c8?f\221xn]\183\198\026U\218i\169}n\162\178RR:\016\240\014\020r\030\028>\031\233\220\182t\255\234C\136$\199@\198`u\149\243\190Ub\184\029\250\1691v\254\237?0\011~@>|4\140\148,\149\155\241S\144\130z\139\201\2376\190\217dM\208D\191\132q\229\214\249\193.\242\133t\"k\185O\248\168\150%\218;\135\153\217\170\020\217@sv\161;\161$R\017\233&\230j\181\022\253PH\155\187\253\r2[B*\238\ti]\207e\224\132\137\191\241v\017\184n\007\028,\131\224~D/\163ku(\202x\175\223\232\131\019\176\158\021\131\131}+\155\154{\151\015\247\247\175n\018:\133\254\146RA\161H$\240\151\150\224@!\249\187/\248\189\142^u\211e\217\221\206,|\1599\175\207\201\254\027I\147\229\18093\241\221\167YB\127i{m}\209S\144p@\224\015\182{\234\003OA\170\020\152it\b\146\253\015\208F\215\211\179\134\134\169\210wr0\177\134\\H\254\159\173\029cs\135\029\227n\222\0198\190\168\152d\198\170\"\028\155\194,\b\029\129\022\129\241\150W\162]$XD\188US\142\246\016w\129ai}\213kJm\1327\141\177\191\149\000\229\159\026\t\020\169c\173\229u\1414\143\239+-gz\217\181\215?\220\166\199\146\206\231\250\153\176\179\t\143\250\183\147\184\020\198\148\006K~k\140\157\205Vy\203\252cs{\235\214\150\184\028\231\131,/;{\158\244m\183\164\2465\180.\249\162\185\174\216\236\200(\184\\c\198\155\141!\163y[J\023\\\238\150\201\254.P_Ae@\221~g\154S!U6YK\218lB\154JE5\149\229\165V\183782\236J\149e\196\026\156\227\208\230\201\163\205p2\171\251I\208&\197\252\245E\153.%#\137\235y\139\150\209x\012\139\147\192\209\022\227\244\n\028\233+2nj\255G\198\015\016\1683k\203K3\224\030<#N\001\t\165\21464U,\127\030eJ#{K\n\205\2406k[{c\236\156\195\177\150I\024\233\004\157}\029\167e\\\159\160j\176\2172B~\127(\177\004(?\230!\208\rz\139a \164\173\031>\149\2085wzt\186\005R#h\207o_\224N\168\227\220\208\142\134\228\163\156\027U\142\004*\233l\218\174\183C\181'kO\246l\127q\022\244g\031\216\190\007t\188\248\132\149\252\131?\250\188N\200u2\233\165\n\165\168\1661O7`\243H\197y\018\139DmPi\132\018V\230\205[\182\2109\162EW\\\185\204\160Z\155\215X!\148\245\182L\175o\145\236\235\t\216M\191\019\213_\177U\182\225\240f\161\185$\163\143o\211,\173\198+\136#a!~\149T\179 %R)t\2397'\212\195f}\197U\143)\224\026\191\136\151\231m`\234\ruL\174\155\219>\"\232\205\213\240\005Bk)\129+(\198\231\153\248R\220\231\222'\167\0288Z;\147\217\150\251G\142U\130\248\216K-\230H\132b\177L\204\192\175>\215\177\180\127\177\233\208d\213bt\166ya\246\178\238\232\202|\141\023\1923lFP\174\021VWs\229\176\230\135Sa\173\156RE\158P\175S\243\165l\030\228Y\250\255q\t\255\003]\014\139O\171\181\022\234tV\159Vk\241\233\188\172\191Q\210`\153\020\249\031\027&\253\209M]\179\204\170\145\186 G\207\221\149\147\191\222\003Rd\138\1724}\238\165\212\212c\153\185y\235\004\n\159D\157G%7\169Tt<\0200v\172\tC\177qtd\011\228\140a\187\0005;%\237\007d\238p\014\007\141eC\030\015\127#a\186\229\171\236\188#\220\161/\181\144\186\163\142h\171\206\198\1482\201\023\216V\129\2107\"jb#\222d\164\031\003C\254\021\031{\023)\221\196\165 Y\018\014\179\191*\130`\158\237\184\194g*\152\185l\187Dj\180y\180:_\145]\244GY\200\219\212\251\029\002\246G:\141\153\1275k\229\0153\n\024os\018\250\244\199\249\179\247\237@P\156\028\131\193\202\162\240\141)\191?\128\229\024i\018Y\001\rs-\233[W\135).\246\030\020:\019\211\223\1915\n\014\207V\161m\t\216p\153=[\253\237]\bK\206\200eyD2\189U\147\239\237\247\207\137O\149\172ie\000\180\002\134K'\bx\209R\187\155\18264\231P\239\200" - let d_716cf074e5806616f6d61aeb32dbe70e = "@charset \"UTF-8\";\n/* Copyright (c) 2016 The odoc contributors. All rights reserved.\n Distributed under the ISC license, see terms at the end of the file.\n %%NAME%% %%VERSION%% */\n\n/* Fonts */\n/* noticia-text-regular - latin */\n@font-face {\n font-family: 'Noticia Text';\n font-style: normal;\n font-weight: 400;\n src: url('fonts/noticia-text-v15-latin-regular.woff2') format('woff2'); /* Chrome 36+, Opera 23+, Firefox 39+, Safari 12+, iOS 10+ */\n}\n\n/* noticia-text-italic - latin */\n@font-face {\n font-family: 'Noticia Text';\n font-style: italic;\n font-weight: 400;\n src: url('fonts/noticia-text-v15-latin-italic.woff2') format('woff2'); /* Chrome 36+, Opera 23+, Firefox 39+, Safari 12+, iOS 10+ */\n}\n\n/* noticia-text-700 - latin */\n@font-face {\n font-family: 'Noticia Text';\n font-style: normal;\n font-weight: 700;\n src: url('fonts/noticia-text-v15-latin-700.woff2') format('woff2'); /* Chrome 36+, Opera 23+, Firefox 39+, Safari 12+, iOS 10+ */\n}\n\n/* fira-mono-regular - latin */\n@font-face {\n font-family: 'Fira Mono';\n font-style: normal;\n font-weight: 400;\n src: url('fonts/fira-mono-v14-latin-regular.woff2') format('woff2'); /* Chrome 36+, Opera 23+, Firefox 39+, Safari 12+, iOS 10+ */\n}\n\n/* fira-mono-500 - latin */\n@font-face {\n font-family: 'Fira Mono';\n font-style: normal;\n font-weight: 500;\n src: url('fonts/fira-mono-v14-latin-500.woff2') format('woff2'); /* Chrome 36+, Opera 23+, Firefox 39+, Safari 12+, iOS 10+ */\n}\n\n/* fira-sans-regular - latin */\n@font-face {\n font-family: 'Fira Sans';\n font-style: normal;\n font-weight: 400;\n src: url('fonts/fira-sans-v17-latin-regular.woff2') format('woff2'); /* Chrome 36+, Opera 23+, Firefox 39+, Safari 12+, iOS 10+ */\n}\n\n/* fira-sans-italic - latin */\n@font-face {\n font-family: 'Fira Sans';\n font-style: italic;\n font-weight: 400;\n src: url('fonts/fira-sans-v17-latin-italic.woff2') format('woff2'); /* Chrome 36+, Opera 23+, Firefox 39+, Safari 12+, iOS 10+ */\n}\n\n/* fira-sans-500 - latin */\n@font-face {\n font-family: 'Fira Sans';\n font-style: normal;\n font-weight: 500;\n src: url('fonts/fira-sans-v17-latin-500.woff2') format('woff2'); /* Chrome 36+, Opera 23+, Firefox 39+, Safari 12+, iOS 10+ */\n}\n\n/* fira-sans-500italic - latin */\n@font-face {\n font-family: 'Fira Sans';\n font-style: italic;\n font-weight: 500;\n src: url('fonts/fira-sans-v17-latin-500italic.woff2') format('woff2'); /* Chrome 36+, Opera 23+, Firefox 39+, Safari 12+, iOS 10+ */\n}\n\n/* fira-sans-700 - latin */\n@font-face {\n font-family: 'Fira Sans';\n font-style: normal;\n font-weight: 700;\n src: url('fonts/fira-sans-v17-latin-700.woff2') format('woff2'); /* Chrome 36+, Opera 23+, Firefox 39+, Safari 12+, iOS 10+ */\n}\n\n/* fira-sans-700italic - latin */\n@font-face {\n font-family: 'Fira Sans';\n font-style: italic;\n font-weight: 700;\n src: url('fonts/fira-sans-v17-latin-700italic.woff2') format('woff2'); /* Chrome 36+, Opera 23+, Firefox 39+, Safari 12+, iOS 10+ */\n}\n\n\n:root,\n.light:root {\n --main-background: #FFFFFF;\n\n --color: #333333;\n --link-color: #2C94BD;\n --source-color: grey;\n --anchor-hover: #555;\n --anchor-color: #d5d5d5;\n --xref-shadow: #cc6666;\n --header-shadow: #ddd;\n --by-name-version-color: #aaa;\n --by-name-nav-link-color: #222;\n --target-background: rgba(187, 239, 253, 0.3);\n --target-shadow: rgba(187, 239, 253, 0.8);\n --pre-border-color: #eee;\n --code-background: #f6f8fa;\n\n --li-code-background: #f6f8fa;\n --li-code-color: #0d2b3e;\n --toc-color: #1F2D3D;\n --toc-before-color: #777;\n --toc-background: #f6f8fa;\n --toc-list-border: #ccc;\n\n --spec-summary-border-color: #5c9cf5;\n --spec-label-color: green;\n --spec-summary-background: var(--code-background);\n --spec-summary-hover-background: #ebeff2;\n --spec-details-after-background: rgba(0, 4, 15, 0.05);\n --spec-details-after-shadow: rgba(204, 204, 204, 0.53);\n}\n\n.dark:root {\n --main-background: #202020;\n --code-background: #222;\n --line-numbers-background: rgba(0, 0, 0, 0.125);\n --navbar-background: #202020;\n\n --color: #bebebe;\n --dirname-color: #666;\n --underline-color: #444;\n --visited-col" - let d_725c52bce5d22dff34816d0cea74cf51 = "positionData:g,children:[{type:\"elem\",elem:e},{type:\"kern\",size:h.kern},{type:\"elem\",elem:h.elem,marginLeft:V(i)},{type:\"kern\",size:n.fontMetrics().bigOpSpacing5}]},n)}var v=[m];if(s&&0!==i&&!c){var b=Ke.makeSpan([\"mspace\"],[],n);b.style.marginRight=V(i),v.unshift(b)}return Ke.makeSpan([\"mop\",\"op-limits\"],v,n)},un=[\"\\\\smallint\"],pn=function(e,t){var r,n,a,i=!1;\"supsub\"===e.type?(r=e.sup,n=e.sub,a=Ut(e.base,\"op\"),i=!0):a=Ut(e,\"op\");var o,s=t.style,h=!1;if(s.size===x.DISPLAY.size&&a.symbol&&!l.contains(un,a.name)&&(h=!0),a.symbol){var m=h?\"Size2-Regular\":\"Size1-Regular\",c=\"\";if(\"\\\\oiint\"!==a.name&&\"\\\\oiiint\"!==a.name||(c=a.name.substr(1),a.name=\"oiint\"===c?\"\\\\iint\":\"\\\\iiint\"),o=Ke.makeSymbol(a.name,m,\"math\",t,[\"mop\",\"op-symbol\",h?\"large-op\":\"small-op\"]),c.length>0){var u=o.italic,p=Ke.staticSvg(c+\"Size\"+(h?\"2\":\"1\"),t);o=Ke.makeVList({positionType:\"individualShift\",children:[{type:\"elem\",elem:o,shift:0},{type:\"elem\",elem:p,shift:h?.08:0}]},t),a.name=\"\\\\\"+c,o.classes.unshift(\"mop\"),o.italic=u}}else if(a.body){var d=ft(a.body,t,!0);1===d.length&&d[0]instanceof Z?(o=d[0]).classes[0]=\"mop\":o=Ke.makeSpan([\"mop\"],d,t)}else{for(var f=[],g=1;g0){for(" let d_7302b0e4baf62f448250e8f2ceec4e57 = "wOF2\000\001\000\000\000\000]\212\000\017\000\000\000\000\240\192\000\000]p\000\001\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\026t\027\129\159N\028\146J\006`\000\133,\b\1300\t\154\022\017\b\n\129\229(\129\198w\011\133\n\000\0016\002$\003\138\016\004 \005\131P\007\142O\012\129U\027\218\221\023\208\211v \207\2216`\232\240\228z\251\254\160@9\182\139\2206\000%+kx\030X\192\141\161\027tGB.\251)z\242\255\255i\201\137\012%\212A\210Z\157N\253\247C\2046\205rL\167zIp\202a\192\169D\173\024\168\172\154\189WWLl|\127G\135co-n\156L\r;\255\240.\236\251U\225\152\204\166\018\155\166\018\213\164\158\151\134\214\027\005!1Q\209[\016\140u\030p\205\254\192P\225'\\\161ox\160\166\237\247\1987\150!\161\134i\138\221P\163?\248K\222E\190\219\129;\190s@\177\162\162xG\135\241a\163\197-\138O\171[\006\203\197\255\249\192\021\r\243\007j=\151\202\138R[=gb@H\017\1453\b\018\213rs\188\232*\160\028\155S#Y9y\242%\168\214\194\158\185\015\001*@\148\169( \007\128\150\216\1368T\209,\017$\216\220\254\234+\218x\137X\195\184(N\255\249O=\237\171\212\011\251\170\003\252>]\1753\002\195\140d\b\148\000P4Nj\155gw\005\031X~Q\128?\168\145\146Nz\238\194x\254\001f\233\206\192p\170\154\191\142\153\214,\251/\131\182L\233\220\210\026S;\191\n\207\175\002\206\149\241E\005\132\2062\t\134gEL\129\239/\195\1991\2060,\247Iu\164J\145jC\164h\211\180\229\244?\000\187\193\235\231>\247M\221>}H\028\176\149\157JV\226\128\224\019%\249\012\0230\162-\128\127p21@\151\247\175\015oW\223\159\139\186.\161\171\026\026\168\167g\252\200\254\152]\247\231Z\209w\bF!\025\017\249\250g\138\192\254_\157\213\151B\182\227\216\002\019\138\156\196\225\225E-UG\220\213W63\139uu\239\160\194ij\174\200Z\223\219)\173\000\028\000EA\014\245z(\169\166M\026\223\024\150T\186/d\161\174\164\162LX\205(\0276\004\232\193!\217\190{\004mP:*\234\020\181\186j\228\176i\182\220}\000\b8`y\031\127\149\214\148N\247\004\249,2`\169\029\192\132\144\213{Wz\163\255\164\209\1503'\025\143\199\173OZ\219\248d$\141v\180r/(\233(0\208\r\165t\228\004@\163\028\030@:\128\tC\t4\r33\225\129z\255$m2\153x\243\243\tJ\182\b\143\154\172\156R\147\003)\240\169\156\201\178\212#\192\132\141\157\162*Z\153\005A\242\235u\253j*\169\234(\207L\005\001+32\203\178\n+\127\031\159\2139\246D\250\255\221\177\131\247\217\156\15395UQQ\017\017\017Q5\183\191wa\005\206\021\168\007\002\004Yoo\255[\150\17919\243yM(%-\001\130L\190gjN\221\128\221v\004.{\004\143\231\172\200)\188\145\000\166\000\180\134B\128=\012H\024\224\030\211\173\137\026\208\002\148w\131\181\149\192G\002\148?\012\142\202F\154\139\161`\204E\200\232?\0064\2080w<\174\174\132|\164\167hU`\168\141\168XI\242-@\"!oC\012\254\189\131@\153\249p\213\218\189\245\158\178\014\022J\002\004\026\020\137<\128\194\017&\190sN\232\178W\187VV\027\173\182T\1399\026L2N5\139\193J\2293J\151(\154^ \228r\159\129\172\031\003@v\2449\200\166\161\005\185>\184 W\135\\\215\028\131\204\213\2500\135\214a\165\217]\025[\252&q\176\213~\160t\247\137r\246V:F\155\\\176V\027q\1806\187\222f9[\158;Z\158\249\026\248 <-\192N~\004s\155\236Q\137R\229*T\246\189\240\001\244\213O\173\001\006\026\164\206`C\213\027f\164QF\195\004\205\150\t\011\152\197\020\1981\150\222t\165=-\165\241\144\154\214 \204n{\160\196t/\022N^\167\253<$\1428\024\024\144\021\019\007T\014\237\190\003T\166\151\031\b)<\244\212\223\0160\208\244.\208\244:\b\214\216\003\137c\164i\235\236\002kJ\172\159\176hK\171\176\145\213,\165\1339/k\152\147\230\184\2177\171\167e\014\158\165\219\184\252i\156\2333qFO\253F >(GK\167h:O\222d\146)d\192\134\241\003t\243\129W\163\158\140{\227\198\1844\206\140c\253\004\209\131c\247\2169\254\027[\151\174\031+\199\2265M\156F\166Q\207\152QUc\248(\155\162Q\234\157^\219\184\192)\142\176\159\206\145\219\251O7wm\151oH\228\197r!b\187~^\213\137\153\157\210:\162\150J\134\190|P\011\155\211\204&7\182\225\213\213oC\141\012b\r_>a_\022NC\020\195\239\228Wz\243i\252\155<\203\131\220\202\149\156\203\t}\188k\182\206\023\216\146\189(\219A\235.knI7n\204\234,MK\230`~\r\153\148q\213\165:\150\012Ni\242cL\250F\"\209\232_\030\024\159(#\141(\206\225\133\137Q6\129\177\232\135\221~\000yRnvwA\248\007\231\162\157\248\157\220l\025\249\159u\175\0234bd3\170\0124\245\015\148F\023D\147`\229h\189\200bDK,\239L\243f\147ov\243q\147w\186\213^\185\190\252Be\158\027n\243V\177K4\183\129\145\230Y>=\174\201\154\172+YrEk,\150'\207#\001\250\167\246\207\157TO\190\173\177\223\195:@nxe\030>\2104\132X'\225\149\021tE\243\202\200\023\237\187\243+\190\"\172\215\156{\248d\2161\223\241k\132\168\238\173F\030Qs\r\207\149k.\224\145\198\235U\021\187\186\240\244\245h\129\254S\219\016c\228a\226\003\142\142\213R\\F\190hcX0\134\151\182!\003\140[\173#\006riqiS\182\t\191$\245$\183\249\152\216-\216YWHD\143\142\177\007R\139\229\177\228 w\194\137)l\211\228\228\252\189\130Z\151\230\242;)\148/\191|K\185$\171Y\244\220\028L\147\1838\150\132]\228\155\254\182\007Zg\244\149\197\249\154%W,Z\243\206\186\226\213Lv\021\200\004y;\241u\139\018\006K\020\149\128\136\128 \029\232S\213\188g\248\194+\017\229\166D\015a\253Q\214&\182\\\205\195=Y?R2\2107\164\031\160\255\174\n\216i\146\202\231\246\135\220\016~U\226?\227\212d\b|\246X\014;\238\186<\011\175\011D\238\216\241\255UpO\188\244\007&\144F\2004H=d\012\164\n2\028\216\bl\128\228B\012\144TH<$\018\018\002\149\134\180\129\138\149\161\169R\1392\007\129e\242`\193\197=@\1363%G\217\025\214\135H\252!\206\242aR\166\211\181n3\225).\029\217\233\244+oA\214\202\003_\014\028\219\127\205D\004\016\012h\014\147\139\004\1882\015\029I\217i\233\173\193\217n\229AyY\254\150\224O\251[\141\255+\017t\190\000C\211\192np\214\1414^>\1529\230\195-\183\r\213\014m\196\206\186\192\221G\221d06:77\178{\243\152=\246\194\029t\227\142n\030s\2175\200m7\238\193fq=z!}\232y\218\165?\138\177\237\206Sx2D\002\185I\230\186q\243\199\199,\183\001\213F\219\208\226@\170|N\133\207\187\208t\127\244y\196\023\221h\211Ul\184e\254s9\191c\249\161B\249\173\164J\250\141D\165\147S\019\242]\162i=\138t\210\176&\192\016\2522\204\015\134j\233\193Q\144\200`\177r4-\237]\173(Q\246Y\200\236\157 \132\192$\177+\025\157y\134\227\241)\153H\215\162ro\225}\189\0014\218\201\148\182\195*\212\202\027dS\166B\199\170ba\174\162(\193d)\2023\251X\173\143/T\178:\017OSK\148\154\022\183\138\241m\232\228\217\147\225X\153\168\154\238\127>\156*\221\164\022\254\191A\166#Se \180\235\208i\151\221~M\197}\129\217\231\192\028\210\245\127\233\152\019N:\237\178+\174\186\230\186\027n\186\229\182\007z\244\234\243;\236\192\164\195\209\14500\1441\217Rp\228HAH\136OJM\193\1557\005_\190\\\249\241C\225/\136\146\142\014U\176`*!B\b\132\210\163\t\019\134.\\\028\161\004\025|d\202d+K\022/\249\n\016LL|\153\141\224\163R%\031U\170\240T\171f\175\198X\254\198\025\199\209x\2279\169S\199\217\004\0199\154d\018\023\147M1\012\155\214\012\030\142\153#3k\0284\014\219\236a\1533~\230\142\157\249\185\153\007\001[\128v\140Z\1990t\014fw8\174\131\028\220\144C\024\174\174\179\018\135\029\225\235\232\224\142\141\212\137\241t&\027\019R\128\221\2170\215i\188\221\024\177\155\227\237\214\136\221>\139\220q\159\175\007\211\148\196\0273\245\2144\222\030\231\207\173\218\152\014\186\022\181Jh\\&\r\b\012\019\1342t\147\148\177\149\180\140\205d\006K^\016\220\194\221\r{,\153\005\192\176]\254r\002\128'\000\132(\128A*\210QI\189\131\214\246\130\130\133\202\224\003\189\202m]\159\195\215<\151\0013}\t\212\b\018\129_#/\190\253\156\178\208\012rI\228\r7}\234o\251\147?' !I\204\204m\153S\000\250\248\004y|\138\162\011Mug\243\252\137\019=\250P%\192;\160]\136\225\255\161LN\015\193\211\2509\164eY\186\230\161\250\154e\025Kd\n\241v.\189Q\188%\171\216\222\234\207cu@\163\188r\196\170\233\024\250\189 \201\195\170\164\t\139.\209:\150\014\189Zh\221}J\135\211o\128|\231\029\201\246\148\007->\002 Z\134t\026\147Bn\206vtg\003\024]S02>\132\019;=\016\175\211'\016\131\181K\223m\b\000\170G\232\136\208\237\017I\130\026\202\182,\226=e(A\251\213\007\184\018\245\212\251\186\167}k\193\031j\177(#\197\005,l\030i\234\019ECA|\164\182t\130/\144\203\017\185\028\197\180q\154G\b\165*f+\220\205gK\247\184Of^\166\028\231#\031\244\128R?6\233!\170T\145\173\242\012\166\244\220T\158\159\210\011\019{\169ZQ\180(\rGI2\154\145\021\249\164D'\197Y\181Q\011>)\185zm\252\237\027\222\246\209&\210\163\234\243>\225\011\226[\199\199\012\127\255I\132\225\251x\005D\015\166\236\r\234\251\127\148di\133y\025\203\233\139\134\255g\151M\027\249\218\151\018\159K\203.\192o\221Jw\194\007\127\193\150\172\175\237nAP^\183\189\225\217\174d\182\183\183\168\146\1351\203w\218\199\253\230\194\159\243\228\172\144\159\128S\tJ\176H\135\212\139\161t~1\206-\215 \156A\0070\223\185(N8PiJ\235\180\221\239i\007w\207>\229\238\006\127rA~\203\128\173W\207\132:;\208\189\209K3\027(\157>#b\238\152\003\0227\2330\001\217t\007\235$\252#\023\161\015\2464\207\\]!\207\0171\153w\179\167u\t\144 \241\225\172fDf\186_\248M\223\245=\2237\219\1786~c\178\143\016na\t\181-\156\196\b\170:_ii$\127R\149J\142\233\224<\153PD\208d-\249TS\212\022{?\215\021Q5\163\166\213\180Z\195js|\001\167$\021\012C\203\191\174Q\177\229\222\136o\210x\190;\194\247F\250~&q\2496[\176\133~B\195\252l\184\223d\019ES\209u\186\019T\174\139\243\197\205\209G\206\163T\203\175?]t_3\132\2082_\222\026\139\024\031\136\132M0\240\017\175\176\216\231\150s\204\188\250\162l\214\209Gi\180o'n\178d\177\238\217\186P\243\188\163\251P\178\151\229\242\144\168]e\178\168Ygv\029\199?\252\203\191\253'L;1\236\003\015-\007F\185_*\149\138(c0\\\200#H\209\171\138\007+\003\138\168\127\026\185\208b\186\179\156\148\149Q\143\175E\165V,2uJnW\174!,\253\131W\205\253\203\127\240\128\128\231#\176w\168\150\241++\153\245\234&\137S\154\240,>Pid\253\145J\"\227\021\157\240\157\250t\240Q\175\207zO\252\152\177\185m[U\160\222k13s&\212T}v\133\169%\016\182G\191\144\219SOa\168\238]\254C\187<7\003\254\172\137l\178Y\219u\221\217\2288\187|wZ{\246fm\155\213\012\243 \141\180\156\185\225\209qyB\00025w\136V\211\142\014\012|\153\227\231\147\163\133\189M\030\162\183\134c\000t'\244\229o\200\195\205\196.?$\252\155[\195\127\157C\252_\211\245\220\223\158\142\172}y\185\237\255k\005\217\200\163<\140\178\179H\182\021\006\241\2319)E}h\164&\030\237\172\235tv\224d\222\232\192x\003\141\239\246\214\188b\228iD\029\019w\185\145\211_\202\031\022\201\190\152\238\1367n*w\031\245T\144Zz6\172\254\022\182\150IU\169\250K\1523}\227`;Nq\146\186S\023V\253\217\244\237\234\196\197\011\1787\249\141\219\237\203\156\146\158\014\178\022\246\000\002H\253\127\133\183\174\228\146\170RQ$\031\019N\021\006\154&\140\1634\140\162\189\020\209\019_3\200\141i_\017!\219\252_\134D\131,\229R\006\"(\200" @@ -198,6 +196,8 @@ module Internal = struct let d_79c029f6f746a52f4a8bc8b6280c5c88 = "ment,t)])}}),ot({type:\"textord\",names:[\"\\\\@char\"],props:{numArgs:1,allowedInText:!0},handler:function(e,t){for(var r=e.parser,a=Ut(t[0],\"ordgroup\").body,i=\"\",o=0;o=1114111)throw new n(\"\\\\@char with invalid code point \"+i);return l<=65535?s=String.fromCharCode(l):(l-=65536,s=String.fromCharCode(55296+(l>>10),56320+(1023&l))),{type:\"textord\",mode:r.mode,text:s}}});var Qt=function(e,t){var r=ft(e.body,t.withColor(e.color),!1);return Ke.makeFragment(r)},er=function(e,t){var r=Nt(e.body,t.withColor(e.color)),n=new Tt.MathNode(\"mstyle\",r);return n.setAttribute(\"mathcolor\",e.color),n};ot({type:\"color\",names:[\"\\\\textcolor\"],props:{numArgs:2,allowedInText:!0,argTypes:[\"color\",\"original\"]},handler:function(e,t){var r=e.parser,n=Ut(t[0],\"color-token\").color,a=t[1];return{type:\"color\",mode:r.mode,color:n,body:ht(a)}},htmlBuilder:Qt,mathmlBuilder:er}),ot({type:\"color\",names:[\"\\\\color\"],props:{numArgs:1,allowedInText:!0,argTypes:[\"color\"]},handler:function(e,t){var r=e.parser,n=e.breakOnTokenText,a=Ut(t[0],\"color-token\").color;r.gullet.macros.set(\"\\\\current@color\",a);var i=r.parseExpression(!0,n);return{type:\"color\",mode:r.mode,color:a,body:i}},htmlBuilder:Qt,mathmlBuilder:er}),ot({type:\"cr\",names:[\"\\\\\\\\\"],props:{numArgs:0,numOptionalArgs:1,argTypes:[\"size\"],allowedInText:!0},handler:function(e,t,r){var n=e.parser,a=r[0],i=!n.settings.displayMode||!n.settings.useStrictBehavior(\"newLineInDisplayMode\",\"In LaTeX, \\\\\\\\ or \\\\newline does nothing in display mode\");return{type:\"cr\",mode:n.mode,newLine:i,size:a&&Ut(a,\"size\").value}},htmlBuilder:function(e,t){var r=Ke.makeSpan([\"mspace\"],[],t);return e.newLine&&(r.classes.push(\"newline\"),e.size&&(r.style.marginTop=V(F(e.size,t)))),r},mathmlBuilder:function(e,t){var r=new Tt.MathNode(\"mspace\");return e.newLine&&(r.setAttribute(\"linebreak\",\"newline\"),e.size&&r.setAttribute(\"height\",V(F(e.size,t)))),r}});var tr={\"\\\\global\":\"\\\\global\",\"\\\\long\":\"\\\\\\\\globallong\",\"\\\\\\\\globallong\":\"\\\\\\\\globallong\",\"\\\\def\":\"\\\\gdef\",\"\\\\gdef\":\"\\\\gdef\",\"\\\\edef\":\"\\\\xdef\",\"\\\\xdef\":\"\\\\xdef\",\"\\\\let\":\"\\\\\\\\globallet\",\"\\\\futurelet\":\"\\\\\\\\globalfuture\"},rr=function(e){var t=e.text;if(/^(?:[\\\\{}$&#^_]|EOF)$/.test(t))throw new n(\"Expected a control sequence\",e);return t},nr=function(e,t,r,n){var a=e.gullet.macros.get(r.text);null==a&&(r.noexpand=!0,a={tokens:[r],numArgs:0,unexpandable:!e.gullet.isExpandable(r.text)}),e.gullet.macros.set(t,a,n)};ot({type:\"internal\",names:[\"\\\\global\",\"\\\\long\",\"\\\\\\\\globallong\"],props:{numArgs:0,allowedInText:!0},handler:function(e){var t=e.parser,r=e.funcName;t.consumeSpaces();var a=t.fetch();if(tr[a.text])return\"\\\\global\"!==r&&\"\\\\\\\\globallong\"!==r||(a.text=tr[a.text]),Ut(t.parseFunction(),\"internal\");throw new n(\"Invalid token after macro prefix\",a)}}),ot({type:\"internal\",names:[\"\\\\def\",\"\\\\gdef\",\"\\\\edef\",\"\\\\xdef\"],props:{numArgs:0,allowedInText:!0,primitive:!0},handler:function(e){var t=e.parser,r=e.funcName,a=t.gullet.popToken(),i=a.text;if(/^(?:[\\\\{}$&#^_]|EOF)$/.test(i))throw new n(\"Expected a control sequence\",a);for(var o,s=0,l=[[]];\"{\"!==t.gullet.future().text;)if(\"#\"===(a=t.gullet.popToken()).text){if(\"{\"===t.gullet.future().text){o=t.gullet.future(),l[s].push(\"{\");break}if(a=t.gullet.popToken(),!/^[1-9]$/.test(a.text))throw new n('Invalid argument number \"'+a.text+'\"');if(parseInt(a.text)!==s+1)throw new n('Argument number \"'+a.text+'\" out of order');s++,l.push([])}else{if(\"EOF\"===a.text)throw new n(\"Expected a macro definition\");l[s].push(a.text)}var h=t.gullet.consumeArg().tokens;return o&&h.unshift(o),\"\\\\edef\"!==r&&\"\\\\xdef\"!==r||(h=t.gullet.expandTokens(h)).reverse(),t.gullet.macros.set(i,{tokens:h,numArgs:s,delimiters:l},r===tr[r]),{type:\"internal\",mode:t.mode}}}),ot({type:\"internal\",names:[\"\\\\let\",\"\\\\\\\\globallet\"],props:{numArgs:0,allowedInText:!0,primitive:!0},handler:function(e){var t=e.parser,r=e.funcName,n=rr(t.gullet.popToken());t.gullet.consumeSpaces();var a=function(e){var t=e.gullet.popToken();return\"=\"===t.text&&\" \"===(t=e.gullet.popToken()).text&" + let d_7c0643b7c2e32bfa6170f0023c969756 = " box-shadow: 0 1px 0 0 var(--link-color);\n}\n\n/* Linked highlight */\n*:target {\n background-color: var(--target-background) !important;\n box-shadow: 0 0px 0 1px var(--target-shadow) !important;\n border-radius: 1px;\n}\n\n*:hover > a.anchor {\n visibility: visible;\n}\n\na.anchor:before {\n content: \"#\";\n}\n\na.anchor:hover {\n box-shadow: none;\n text-decoration: none;\n color: var(--anchor-hover);\n}\n\na.anchor {\n visibility: hidden;\n position: absolute;\n /* top: 0px; */\n /* margin-left: -3ex; */\n margin-left: -1.3em;\n font-weight: normal;\n font-style: normal;\n padding-right: 0.4em;\n padding-left: 0.4em;\n /* To remain selectable */\n color: var(--anchor-color);\n}\n\n.spec > a.anchor {\n margin-left: -2.3em;\n padding-right: 0.9em;\n}\n\n.xref-unresolved {\n color: #2C94BD;\n}\n.xref-unresolved:hover {\n box-shadow: 0 1px 0 0 var(--xref-shadow);\n}\n\n/* Source links float inside preformated text or headings. */\na.source_link {\n float: right;\n color: var(--source-color);\n font-family: \"Fira Sans\", Helvetica, Arial, sans-serif;\n font-size: initial;\n}\n\n/* Section and document divisions.\n Until at least 4.03 many of the modules of the stdlib start at .h7,\n we restart the sequence there like h2 */\n\nh1, h2, h3, h4, h5, h6, .h7, .h8, .h9, .h10 {\n font-family: \"Fira Sans\", Helvetica, Arial, sans-serif;\n font-weight: 400;\n padding-top: 0.1em;\n line-height: 1.2;\n overflow-wrap: break-word;\n}\n\nh1 {\n font-weight: 500;\n font-size: 2.441em;\n}\n\nh1 {\n font-weight: 500;\n font-size: 1.953em;\n box-shadow: 0 1px 0 0 var(--header-shadow);\n}\n\nh2 {\n font-size: 1.563em;\n}\n\nh3 {\n font-size: 1.25em;\n}\n\nsmall, .font_small {\n font-size: 0.8em;\n}\n\nh1 code, h1 tt {\n font-size: inherit;\n font-weight: inherit;\n}\n\nh2 code, h2 tt {\n font-size: inherit;\n font-weight: inherit;\n}\n\nh3 code, h3 tt {\n font-size: inherit;\n font-weight: inherit;\n}\n\nh3 code, h3 tt {\n font-size: inherit;\n font-weight: inherit;\n}\n\nh4 {\n font-size: 1.12em;\n}\n\n/* Comment delimiters, hidden but accessible to screen readers and \n selected for copy/pasting */\n\n/* Taken from bootstrap */\n/* See also https://stackoverflow.com/a/27769435/4220738 */\n.comment-delim {\n position: absolute;\n width: 1px;\n height: 1px;\n padding: 0;\n margin: -1px;\n overflow: hidden;\n clip: rect(0, 0, 0, 0);\n white-space: nowrap;\n border: 0;\n}\n\n/* Preformatted and code */\n\ntt, code, pre {\n font-family: \"Fira Mono\", courier;\n font-weight: 400;\n}\n\n.odoc pre {\n padding: 0.1em;\n border: 1px solid var(--pre-border-color);\n border-radius: 5px;\n overflow-x: auto;\n}\n\n.odoc p code,\n.odoc li code {\n background-color: var(--li-code-background);\n color: var(--li-code-color);\n border-radius: 3px;\n padding: 0 0.3ex;\n}\n\np a > code, li a > code {\n color: var(--link-color);\n}\n\n.odoc code {\n white-space: pre-wrap;\n}\n\n/* Code blocks (e.g. Examples) */\n\n.odoc pre code {\n font-size: 0.893rem;\n}\n\n/* Code lexemes */\n\n.keyword {\n font-weight: 500;\n}\n\n.arrow { white-space: nowrap }\n\n/* Module member specification */\n\n.spec {\n background-color: var(--spec-summary-background);\n border-radius: 3px;\n border-left: 4px solid var(--spec-summary-border-color);\n border-right: 5px solid transparent;\n padding: 0.35em 0.5em;\n}\n\n.spec .label, .spec .optlabel {\n color: var(--spec-label-color);\n}\n\nli:not(:last-child) > .def-doc {\n margin-bottom: 15px;\n}\n\n/* Spacing between items */\ndiv.odoc-spec,.odoc-include {\n margin-bottom: 2em;\n}\n\n.spec.type .variant p, .spec.type .record p {\n margin: 5px;\n}\n\n.spec.type .variant, .spec.type .record {\n margin-left: 2ch;\n}\n\n.spec.type li.variant, .spec.type li.record {\n list-style: none;\n}\n\n.spec.type .record > code, .spec.type .variant > code {\n min-width: 40%;\n}\n\n.spec.type > ol {\n margin-top: 0;\n margin-bottom: 0;\n}\n\n.spec.type .record > .def-doc, .spec.type .variant > .def-doc {\n min-width:50%;\n padding: 0.25em 0.5em;\n margin-left: 10%;\n border-radius: 3px;\n background: var(--main-background);\n box-shadow: 1px 1px 2px lightgrey;\n}\n\ndiv.def {\n margin-top: 0;\n text-indent: -2ex;\n padding-left: 2ex;\n}\n\ndiv.def-doc>*:first-child {\n margin-top: 0;\n" + let d_7c6039a5e3afeddb9778822422cc7ab3 = "\228\017\146*Y\224\131DEW0\202\138\027\177K\204 \155\028l]\169{,n3\205\168\1664\1612\012lQ\201`i\130e\011\023\np\253\180\1985\154\216\015\131\135\b\024\141.\155Q\251\184\251\145\\\021#\168\204\244\198\141\253\139-\021_\021\180O\197\141\182\157\226\244\024l\018\236E\203IaV\030_\026\019Aw\196Qf5\223H\209\145\178<\\i\007\179\171=\193\186&\195Iyd\018\211n\tq\017\130?\131\tQ\219)\158\134p\023\164\170f\194[ke\135}\167/\166\t6\195x@U\186\192n\255\020t\005\180\240\226\164\235\192(\252\143\142#y \216\221\221\163\176\206q\007\185\190u(t\143\197\135\221\023 -)#\022gD\209\213\004\025/k\205fqW\171u\218\012\212\191\023\233\018\230\031o\006R]\181WU\136\n\187\202\230\208\165\" \136\209\218$\244Ay\136x\194e\156\218]\229\029!\0140f\164\157:s\017\184J\197i\181\027}T\194(\\6\n\005\140\024\018@i\176\025?\212\015\207\252\007\221qw\182\185\227@\241\221\153\214\019?\200\179\193<\162ki0\024\219\r\182\165E\"\216\028\173\171\021\229PWn\199\182\019\204\153\178\226\200\198\182\1759\164\027\188x\150\134v\143\251\169\250\130W\223\218\221$\169]0\128]}(\n\165\149~\213\165\203\1659g\199v\207%I\029(&\015](\178\191\151\014&\002\254\006(b\205\134\143k[l^\198\138C[\164\007\151\r)\171\207%\135{J\212\204V\0215X\203\137w\030V[\025\235\241!\236E\019\169Z\002\202G\225\244\155e\n-5\206\158\222\209\133\224S;f\171Yy\162\128A\229\238\141R\237\15881:Db\182\145C4\246\029\185\192\017\015\178U)\145kL.\1834\190\200\166\213T'\182\189\192\197+\021\014Xq\200\246\026y^T\252\212@|L\150\217~n\221\155\173\180\012\208\172\190\127\249\136\005\155\030\218\147\152\162\030\202\201|\027\1348i\210\225\020\197\t\197,>\224-%)\237\198\255\166\254\221*\239&\227\177\198\150^\199\168\209\014\162\127\156\003>\231]3:\220s?4\157\157x\233\189}\190\206\175\127\216:}|\021#/\143\219\185\248\234\167\b6\174\240\003W\254|\135\150u\222l\245\021\181\"\245\214{1\235\186\\\212\210\159\1510\003D\n\208\0075G\143N\215$V\165\220\022\169\158\2389i\154\000\155c\235\226\212\146Z\210\167kg5\007\144\149{\150Yq\143<|\177\180\134\230\144s\172C\155\166\019y\193\153\168/\030\211\17115,\173\159\1483\012pk\181K2\184w\236\217\1742W\249\223\183\193Dd\240\028vo\011\021\251\139n \133y<\170\163\t?\140\1347\198k\147\171\141\154\132\145\1777\185\146\027\210\161\210\027}\186\149H\t\134ic.Fq\214\158z\141\2131U\022\198\237\141\146\133\238\251$\011&U\146\150M\134\012\185\007\027A\181\180,\217\182iwq\195\184\217\2483\246\027\128\231\242\156\191\011,\192\186O\138\197\182(\135\221\181&g\207\171r\166\240GT\165A\024T\204\253a\158w\182\176\206cj\224\169\234~\000,e\179r\145\213\147q\210\001\239\239C\148\1874\221\175\210\158\178\019c\207E\206\239\205;\011f\145\200\003\143fv\185=\190\212[\241\147\015\159x\235\179\249/\218a\019\239\165\230W\t.\181\131\027v\231\245\237\187\210\019D\015\182\031\233/<\213\195\174\026\204\166r\185N8\209s\158\127,S\218\027x\238.v\231\218\141oM\142\235\193\221\130\187\215\219\221^\185.\030\203\219MO\023%\238>\249#\244b\163iI=\162\145\014\199{,f@\195\011\0312t\2174\172\168\220\186SW\152\207\216\239y\253O:?\224h\219\029\199lB\027\012%\152\141\235@S\194b\t\175~\029\140x\217!\027\214\159W\239\004q['\184\155\223\195F\019\139\193\130\212\005\141H\169\223\217#4\189:\212=L\220\023\007\165\222\004V\163\236\210=\214d[g9r*\128Z-ZY~Q\223\025'8\212=\128e\003k\202>\0281\192+\161\179\151\179\217A\140\156\148\022\004:\223Ix\003\190\205\007\r{\138\233\208\215\228U\135X\004\004B\020\021\1814\219\198%\012`\225\165\012g\162\199\1605\167\215\0262\231\172\144!3\194\179\174.h\141\252Nf&Ks\132@U\219\159\141\003\212\179\191 \136ipj\012\155\194L\225\137,N\137\223_\181\252S\149VE\214F+X\157>\143s\228m\149\221\253?H\005\0259\220\211\r\186\162\206\201\157*\157\164\012\172\137m\028\029\134\146%\132\222=\200\005\002\027\019\031_p\132\015\175\246C\243\245\243\007\157\163o=g[\188\151\251\242\223\195\215tw\186j]\191\190\164\162_\248\158\000\250\138\238\b\217\251p\203\166\152\231\170\"\004\000\174\bx:n\237\248\026\202\179\242\189b\247R\247\254\248\001\\X\002\212@|\011H*\129\165\187\140\181\229EW\213R\137*\213\216\023K,bW\184-s\015\203\157Y\165,\153\019\tP\bpI\135\2382\134=~\196\249\132q-\174\025\151\t\244\179\011\157\135\\\168\177\160\208\020ro\030\140\217\1471\143\155\255e~\190Pba%2rH,\004<\185\148I\240\1336a K\"\194\141\181\170\168\214!\191\235\187D\236c\191\245\217\136E\157\248.@\144E\139\176\178O,\214\184\248\2265\t,\018\176\130\204$x\017W\0024.\147\192\016BZjI\024\142\252\202TO\003\232\132\215V\005x\158p\238\027P\135\177\156\235RA\165r\243\179hpa\129L\136\135\176t#\185\0001X\192FZ\244\023v\145\169\028\003\129\024!\026\003\227\138P\131E\"D* \140{o\021\017\213\219AA\134\157\\\014D*\225bm\019\224G;\136p\223!\201\021\b\027\019\136\237\197\204\nMh\029JVO\r\175f\005\131%?\241\144\162\225:\192\188zA\172\"'\241\222\180\028\1942\244\167\154A\196-\017\253\162*\143$\131\r|\003\027\170\1370wxUH6%\021\163Z&\141]\136c\175\001(\1861\019\217h\002\243<\130\021|HV\136\161\015\183\240\225\154{\248\200\023UC\228\221\250\237\246l!e\212\186M6\177$\228u\130\230\1701l\151\181f(\018+\150\023o\163B5\204\205\012\133\025q\219\190\rY\210\184\197\026\148\134\192%\237[\b\131\218b\019@\168\138\245C\171\208V\180\214\162\214\217\149ew*\0165t\253\145\186\167\247\241gi\151 \186\170\024\165@\017\022a\185\231\182\210\215D\193vq\224\2024#c\131\163\020\133\182\131\027\195\214Z\2376\136\168\154\129\214D8\147u\188Ua`\020\1505>\130\\\006\165\016\014X43Ah9\129M\131\146U\030\2408\197\211fC\031\204h\152.\151q\172\233=\247\233O\248\150SY\246]!S\002b\225\213G\174V\127\195\178\248u\026\030\175\132\224B\137\024DLs\158cg\170Z\186\194\205\174\140\216rK#\022\165\246\199\000\165h{\219B\003\195\160\180\154\192n\217\130H9\165\001\169K\202\169X\162\1915\202\134\031\137r\217\176\b\018\211\214\218B<_.\005\028]h4\0208\201i\239}\206\243&\136\205\143\140\006\181\192\186ZK\030w\141\195n\135\221\143\1987%\175\169\246\"#\019x-y\140\186(\246\208\015D\n\1656\136DM,\135\199\134F\004P\2190%\026\185\244\170I\236\179sKvE\165\r7\"A\n\016\225\216C\161]g\175\209\229\005\218\180\169L\150\243\192m\159s\239\251\147>9?\0268\213fy\160\184j\246\145\183G\147\024m\243r\191*\196\031\004\b%\029\022\198=\180*\197\138\143|\165\005M\142\000\214r{r\182\250\221\198L3d\015J\186Q\179\1274\195\236\145;O\169\164\025B\186.\209\169y\146\182\217E\163\176n\2276\209+\131\029\t\173\128?\180\250=\239\163\006\139\188\255z\179\233i\153\003N\191n\211}z\251\2469\251\204\244\204\239\233\250\235ET\168\160\2371\219\231\201\218\225J\150\185\133O\150\185\127\237\242\131:\207\212U@\003\149\151\229V\193\127\167y\246\232\137\201g\029\r\219j\178,\155\252\207\187\170\251x\006O\169\1647\146=)d\165 \187\201a\176+\217w\141\223\233\197(\211\157\2201\215\242\209\n\231\248s\231}D\138\227\007\231\1919\028\246f2t\163\246\252\246\244\177\235\153\219\211\224{\238\222\179\247\031,\215\249fW\187\161\026\230\202T)\204SM\199T\214f\248?d\131\176y\253\030\137\028RxK\030\180\250g\015\239\221L\026\251\"o\246\232l\rM\"\205\220\222\155o\169\156\185\007\179\143[\131s\230\144\195xs\182\007|\253{\170&\232\202\147u\1467?Z\169\185\183\018P\204\"f\173\203\007P\203\180\193\1500\199\148\127\150\128r\2019m\t\0248\0110!\003\002b\229\028:\016@\240\172\149I\185av\242e\216B\218d\150\240\226m\216\196\2177U\138\016\194\182\141\253\195M\246\144@\005M\176\151\025\017\165\177\185\021\208\159\202x\231\137C\000\224\004\184Y\134\156r\190\001\021c\n\240\173>K\219\230\252I\1290\019ar\218w\221\137\206}\219iZ\231\004e\159\189\019\020\171>\151}\160,\148@;0\230\236!L\212\144 \000\021R\028'TVbb\158\138\169\206O\020!\003\168\231\221\182[\244\142\016\164\144 \136Ch\182\028d\002\148^\212\185.\165\180\239\180\237i+!f\186\181\250\194\020T\025\bBP\019\196\023\169\172\222B\137\017Q\129xwD\027O{#\226\012\017o\"(!\016\207\017\137\025E\b\026\135\128\148\017\233\022\165\178!\000Q\194\028\187p\173\189\031g\249Pv\146\005\222Q\152\016\207\227\173\230N\140\239nv6t2\019c!\145e\148NR\230\b\128@H\184m\219\022cR\146\1441(\0171\0172\005=\016!ZPW\151s\014\129\247=o5&\160\173\213\187p0\019`\bAK\178\248`\026>\201Rb6b\217[8\027A\218X\0040\241\166\202\022\002\211\180\196*\164*84Ff\192\150[\212o\027\194\251\166J|\215\015\229\222\230\188?\234\007\249\131=J\020S\164d!)\031\172\020I\155:w\241Z\\M\138]E\224!E5\019\138\200\b\239\152(\165\\\196\"P,/\169\143\190X\238D\223\202.\218\188\174\002\196(!\192\222S&\217[}7\141\238\198\164\177\029yj\170\243\162\200C\028@\196E-\012\0226\150]\205\144\178\238\165\168\199((\178\022\227\189\159\142\146\146\170\190\221[*\183b\207\011+\233\170\028U\215<\207\199S\251\160\250$\030\021\"Qi9\164\133\232t\163\252\208\218\250\n3-\229\142F|j6`B!8\145\018R\001\152FR_\202\177<\152k\000\202*\007\181\tH[\134Y\172\216BT*C\t\017\153xB\131U\171X\137Sb\171`\r\179\130\012P1\194\0291\180\018w\227S\177\155\235\150\253\016w\135S\127\172\235z}\155\147\187\191Z\203%\153\023\230\178\187XM\239V4kY\222\245(}\180\238^j}\025Fo\165\149\138\"\170\246K\011q\166\156\177\021\207\164\185\153Y\217\144\181\240\170z\195\168s]'J\169\164D\225\000\146\018\2185\015\247\220\187C\014\246t\241\002*[\1407\235D\165t-5]V\172Z\t^++\150\208Z\2339\023\1700onM\173\173\143\006P\138\148R\128\190\197Y\1417\194Y\234\195\228\209\237~>=\255\252u}\232\227\151/h\224\189\169\209\2004\252\165\182\002\222\174~\248\189\029\199:\251\168c\252XU~\213\217\006\023\243\226^\205\181\000D\153u\128\020\152\238\222k\245\2380\127\150\178\2051\188p}\239\"\000-gI\015\018kq\161\191\143\014\1991\160\003\004\143p\027\149\202\230\253\171.\145\214\206\218F~\174\173\014\175\177\143n.=\206\217\1432\165O\145\218\231\168ku\127\155\136\189Y\239-\210\218SL9\2059\137\016\223V{}~\127\255\251\223\211\135\185\254\181\011\007\1825\205y!\175\254\222g\2296\159\231\213_\230u?\239\243\152\199\250{\239\229\2238\199\146\234\189\173\180\156\199e\214c,\180\138G\195\164\179\2476\027\030\127k\221'\b^A\142\245\204\016\007\160\229\023V\159\t\233_\142\201\215u\192\004\014^\225qt*\155\215\127\253R\029\227\222\215\129o}\244\163\1414\215\225Mg\170\183\1742\154\231Sy\158G?\207\213~\156\204s\249\156#\201\021r\202\144\207\243df>\150M\138\165\144\243\237\238/\217\156\204\212Pq\132\174'\178\162\200\023\014c\205\192\131eQ\026\171\172D\129x\024\222\157\160\133l\134\129\141\140q\254\012\001\133\180J\200\186\027k\197\024S\217\001\182\014\185\141\227\003]\017Q\159\201\174\171k\168\170\238\217;i{\249\180\213\191#\212\198\"\000\212\138\001\155\020\232\1319\193\157\155\182\005\176Lb5q\193\145\t\165'\236Y\011O\239\nL]\003M\203\165B\174\181dE\017\002\178\015\189\167\170'<\242\224\015V\200\007j\209\144\167m{\241*]\208\191\020\158 \001\141\195\216h\210\026\216\0009\021*)\015\147\n\193\006\173\209\232\231^\014/\209\162\234\216(8\b\128+]\169iz+\r\2339\177\226GS\224(\177\022^p\254h\130\224\156H\\\175\239\t\193\186\030\174?\155\158\169+\210\255\208\138\006\175A\001U\002x\015\181\212y)\240\149\244}\143\024@\153\186\000\130\017\242z\215z\020\189\186>[\229\t\241\252|@Y\r\206iq\216\166Q\138)\133\207\138\127\130\128,\0166\191}\186\236\030\247\229<\223\188\203\023\138oel4E\171\025o-\233\028\222PC#M6Q\022\147&\159\172U\206\190\142j|\171\1316\0030)\165D\172\234\170n\219\193+\219\140\208x)\165FD-\027\255\026\224\177\2146\175/\2058R\170\t\025\171\210\014\194T\173\190X\211\164h\193@\163$\136K\170\173B\164T\191Sq\024\180Nh<\221Q\163CU\025k\185\028t\229\189\142M\163\245c>X\012\227\016y\015m\171\141\b\183\\k|J\028&uP\218\027\243L\230\220^\188\248\250\253\184H\249\230J\023:\155\130\196qj\199\217\189q\193\2446\222\226j\239\180\1285oi\242\211\252\165x\248\022JH\\\1635\214:\155q\199\029\0061\251\169\003\211\205\142dlx'+\027\243\212\027U\234\155\004\208u\161m\129\222G\161\"\193\250\251\020\251u\157 B\031\\\139a\242\206\209\188\191\251\"D\b\155\139s\251\210\0057[O\2104\161\017\145\204s,eJ\159\222.\229\201-\203d\222\229q\140Q\197\024jV\174JhK\151e\025\199ax\183\2487\175>|\252\251\255\229\197\206\255\233dyH%\027'\202\000k\250\148r\224\177\188.gz\147\207\231\251\189ly[\255\156\147\254\159\143\\\208\219\020bJ\177\237\218\142s\220\231\141" let d_7c6224318441e0f011798056247ac8ce = "\128v\233\233\165I\014y\212,\135\024*\006\166+\027\195f\002-\rW\164\027\237J\146\004[rs\216\187\138U\131.J\205\005\225\205\194KenIT\173q\229\250*\141\168\165\175s\230\248O\164z\012\251@\156\147\000S \227\180>\022\031\173\249f[w\2148\193\b\162\244W!\144 `\031\000>OG\025\214\165\162\239U\127\130\152\222\211\195C\208w\243>l\148\221:\240\133\246\tL;\182f;\178\195\231_\229\192\169_'~\197\002\241\207\011js\255\215\140\250^\031\190\201j\152M\230\147\127\184\242\014nu\245\185\"\232\149m\192[,\171\199+\n\249\182\228F\195\232\161y>U\138\019\152\206\208sT\179f\195\222\141Iq\157\140\153\138\245\190\134\197\143\247\140]\175\252\202i\028\214\141\024\027\140{\218ZF?\021\216\166T\1661\211\1763\029F\161\193\232\211\145W\239L\2481\196\004[V4\217M\012\1701\1361\1366\206\014\156)n\223!Na\022\163\140r\185\186Z\024B\016<\208\134\027\224\148\139\029H\171f]hj\185\238\215\145>\229=\152W\187%f\198\225~\241`\194\210p\205\003\215\202\180\017\002\027\022\140ba\211\t_n\186\137\173-\191\2111T\178\156\154\0203^\1946\166\217\136\145\015I\254\012\018\152g%`\007\027\174o9\239\237\155\174G\1768uYa\202\167\179\129I;\221x\015\178A\240\027\135\237\214\162#\227\251H)~\206)\028wx\020C.\141z\129\134:$\246\180\196\221\226\223t\011\163S>\209\205\209d\185eR\204\184\154mB\179\017!\223\145\005\246\150`?+\001[h\1641'C\023\139\027\155S \026\178\244\018{\252\248+\232\230w\244:T\196\185\235M\rN\232Hg\185$\162\027\ru\176\248c`%\209\218\201\218\2274oi\025\234=\162Q\249\250{\155k\177\031\254y\011\nJ\n\1307\189G\177|m\141dV\017A\177_\153\002!\2033\145\0029#\187PI\209\210)o\177\167\005lv\205u\171\159m\203\198o\143\178\1543\022\131\185;\225\193\134\206`\012\230\250\132\006\244\254\004\198Z\243\167U\226\185a\172k\204\196\186fAB\175\147\198F;\164s\194\196\229\190\214\201\150an~\206\201)\172>\\\188\172\014\246'k\016\174\149\133\026O^\233\246\215\177s\146\233}\230\205Ey{I\016\248\129(n\135(\153\017@.\012\b\149\210\018|#Dk\222} \004\217{X&\197\004\014\208\011C\203a\251\176b\164V6r\\6\152\240\148\226\"\209] \239L\247\014\018#\240\176 \247r\158\229\227`\171\213\243@<\228\133\n\193=\130\246\211\167y\023\1533\163\200\231\nT[O\028\175\017t\146\002-\020\\Z\132\233\225'f\194z\191@Q\146\183\026+\195\0113/\229\250Gw\178\028\130\024)\210i\225\171\147t\223\1644\175\173\206\168\216@\185\006k\1852\151\024\022\142L\n\030\179 \141\235P\025\166\246\179\145\2338\131,\229\149\188\148\015j\159\149\246\014\133'\248[+?\197\199\173\155\185\157\208\237\026\175\127\225G\181o\252\226\219\236\012\211\208\025\170\1871\255\018l(\161N\205:\160\202mw\014\165\249\233\127\247\234\136\006m\180\2482\153\167_\244\141=\t\180B\161\180n\2168\182\029u\241\208'^|>$\030Z\164#[\182BM\002\217\207~p\200\211GY\146'\202\129o&\159N\198\002\241\166\022\181@\016\154\170\199{\239\166C*\175`cU\137q\129\237\224\249\138K\233\026\017\160xppPpn\200I\139\237\248sS\229\177\nA?h\170\226$W\131\007\148\026\252\028\184\163k\235}\007h\003\007\232E,\215\131\227.\245\216\127\216\224\179\130\173\0310\020\239\229Dx\181\030\233\196\231\1651/\219!CXo\135M>\136\195\214\192Z\146-C\236\172*\022!H\135\242NI\217\025\173Q\214D\202~\174\195\018\244\180\190\b\160\247\178\200\216\200\167(\226\017\175\031\1828H\226\171\2294\\N\216\141nx\182\179\"\228e6E<\023\151\156\210\166\137\233\198+$N\136\2162\143\133\194\129C\145\133\185\195\204\156|\215mI1\029\188{\165\189\195A\t6qh\255\138\192b\244\175\226\239\212L\2316\185(\029\239l\227\015\217\240;G{v\031\164&\1888\150Q/\147\165[\186\209\004\144=\191\183jL\239\129\172\142\\g^[\150\003\1286\020\182I\188vq\223\188E\147\247\014X\154\195F\152\165\249\157\166w\172k\239\1544\173\029Y\130\138\197\254\142\2067=\189\176\1586\253<\030}\184\019\171\167\n;\216\211\161`\002\214\133^V\201\001\001\201V^B\005\133`\189\195U/\218 \233#\0077\207\175\133\166pxX\132m\t\129\235\135\192Z\177\238\215F\177\173;\1821x\0116\212\173p\015\254\210\015\248\030\006f\195\138\176\183\215\127\169E\184I\248\167\231\200-EK`\254\227\251\208/\023_'\174!~\158\247J2\022\236a\230\2279\187m\182\167\196\022\185\158\204\169\217\203+\024\136\210|I=\195\139\203\003\195q\236u9\202\030\007\233\228\138/=\158\199\214\231z\157\164\2507-\199\213\153\225@_\146\019V\206ef\017CWk\133\168\004\128\014c\189W/>\236l\168m\146\185\183\180\201Q\161r\222\173\142\173\245\186Y\208\183G\172\242V\027\141G;\167\205\137DH\165\182\240\1641\022NN1T\191\189\146{N\234\155\190\218Xg)d\137~\232\215\209\003\224\242\128f\016\227D\154\240#\2077\142\209\151\150\190\205=+\176\150\016\031\232^\026! \0222\147e\209\244\1313U\023^\004\t\165N\225h\133G\b\163Kjx\151\217\149\228\249\219\225t\023\205\187\171\200u\218r\149\184\137\152\169\255\235\194\227\234\181\021\025\151\176-\006B}}a+\214\185\133\228F\146\253\b\1950H\225\208\024L\012A\140aA\161P\225e\012\182\000h\231L\144\142Kp\142\1320\168\018\147H\b\199\240\160\016X\202\"\028\155\t\164\025Bc\181\007\\r\147\189\251Rb\218\150\192\179\247#\129g\007G\134\208\024S[\152\131^\205\216\224\153\029\020S4\014\011\1709\244\229\235\016NIY\248\151\213\243\229\011\129\159\174\175a[6\200\186d|\017fZv\022l\142\225\007\131\205\166d\139`sC^\144\241a\177+w\204?\r\198tv\134\139\219\144\023\152\146\252\174\t\250\180g\172kL\134\201_\175\180j\015\142S\217q\233<\131\250\1854\131)\142\145u\227\246\235\135\161p\243[\159\2017\211YA:b\006\151\129\241\127PoNb\025\245\221\222'=dxA\b\182g&\227\252}\173\018xg\194\018\252\247UU\237\243OH\168\240\134\143cKx=Zs\252j\197\242\208\208r\220\234\213\n+5nY\196e_\191\138\213\178\001\235\134\144\236\236\144\006\235\1290\221\154\177\143\156\145fiCoS\\/\015T\175\147\146\022\026\198\241\020\141\175*\187\226gT?\176\001\2329\2033\174\255\\\2073.\1859\229\134\128\029\153\223a\229e\026\012\161\200}\006\244\206hT\252\223\197|\137\219\018\"\172\198%I#\016\212\251\227\156\129\206\132\193\159^\226p\203\255v\149W\233\220\tV<\017\234\232\242A\252;|\245t\191\127\189\185 `35\206\195p\216\214`\216c\191\153&` \232\159\135\221\199f\237\222O\197d\183C\127\1596\2418T\187\143\000U\254\133\187\031\n\142=,Jm\221\211R|\1403\238\023\215\155Y\223\136\023\235R<\231\149@\179\209C\248\200\203s\163\147#\223z\159Q\166N\154\248Q%\170\152\136\192\142\000\139b8td\209S\216+\207\2167~\127)\022\254\219\235\186\252\181\149\020\001 \220z\252\224\132\251\212\183\191lo\017\175#<\234<\176\022\196ff\146\191\005Z^\204O\196\174\211p\196Y1\255\250\214%\142\242\181\220\175qC\220G\199\189q\030F19\189\251b\020`.F\2191\129\216\193\191\023\194_%Y N\237\168\191\131\212S\184+$5\173\217]\146O\220_\160\174\012Jp\175\149\139\146\1376\158)\208\1507\213\138\221\241\015\170L\133\222*D\140}@@\173\030\147\027\195\172\178\150\177T\132P\022=.'\208=\129\018\228\136W\195\004q\254e;\2246\147\208\028)\171\006o\143c\251s\160D\014sjw78E\155sZ\014\171\178\149\005\209\220h\028H\243\165=\134u\254;ik\219S\176\015\145\128\2412\206a\189\159\025{u)\012\237\179H\138\"\255@[\249}\017#\133\192\182\225\130<\188\247\247\216\191\027\129\003H+\16364\021\141/\244\226\200L\157\220c)\150eZ\201\159\255\007\212\168M\170N\002=\203\021\142\185\177C\018A@\174;\019Y\228\140\2099\151\134\128Q\022>\2230S\005h\015\\\245|)\002\219\219\ta%o\173\237\232\138\192\164\248t>\236\b5\205O_\255\191\235b\030\175X\029\150b\031\2061\225:X\241\r\142\233\237\029\018\232\160\211n@\031\203\016\200\205\0064s\162\143\249\027\012]j\235De\1846\218\128\023\142\204\143\160\211\004:;\154\190\245\n\012h\170Li0\137\251\213\255{\241\018_Bt!\135\176\157\163\209R\131\217\234|P\160\222\132\209\236j\189\003\237\221\213\221r\003\158\018\228\031\007\002r\217\209\216O-Q w\151\190\169\168\217\224\2514Y b\251(\006\146\247\019\208\201L\159h\023\129\005\248\225\182k\219\204\243\185\218\251\146\207\214\178\245h\217e\146\228\2425\012\129A\209q4\197\138\133!_!\162\231\r\152`6\2481\173\188\1648\201\214\159\156\197\014\136\162\184\184F\153\178\\H2\015;&.\221G\024Kg\177\236*\165&(\200\143\0297v\173\011\147\180PLC\t\252\159\206\178\029)\228 W\215\221\187*\216\031\149\193\162N\211\200\127\198\150\230\143\228}\030\173\247\228\209\161l/\200\139\246\161\014}v\144\192\246\129\227=\014\000\148):\224\150^\207U\155\182\006*\234\020]\023\248O'\179\255\253\187K\147\206\026\172\2382\177N\161\136\031h2!qH\129\210L\028K}\252\198H\252\251\243\210'|~\160(\170\\dZ\165\192p\182\155w5\189/\138F\209\142\t\012\179\162\249\240k\174\158\164{\168$\1576z\155\216\219\252\163\159\143N4\177\165\163\137%B\177\212/\162\022*)\018B\226\177\204\170\002\146\203l(\018A\182\159\231lcV\195\235^\169[\206W,@\128@(\177\237R\030%\028_\011\150\195d\226\214f\174\244\175\254]\031$8G\b!VWT\198\186\016\012woL\136\192\155\244n\016\180\229\182\193gZ\007\187:\2488\208\015\184;\223y{\018_\025\137\015\237\239I\187\210\226{V\181\160\237o\016\129\197\247$\b\210\194/1\004\226b%\232\191\157\025\208\197\172\021-s\168-\011ia\t\007\130\194d\173\202\019\235\150\213\235\184W\249\253\191_?\229\235\153\133\251\028\248\233\202\140\127wLZ\209\204x\213_\210\221\187\222\240\146C\211\019\131^\145\165IS\220\253\253\127\247\140b\141\027\002\208\021_M$o>/\239\143{\233\185\170\234\204\173\004\004?\183\031l\237\174n7\229\181\227\226l\191(\021\218Y\214\232\238\223\024]K6\016\170\015}\005V\175 \193\205*\209\187_\129y\007\180\188\1961r\2533aO\215\152`\146\030\201\145\177\150P3\161\160\244Z\bH0zG\000j\235\216\017\134X\177\142\b\208\156\"\155\183&|\151$\017\163/\240f\215\023\211\004\ts\239\004\228\025avSC\198\245I\011w:\140\158\186\241\003\219;\178\021lM\158>\192h\132\248\150L\027\145fB(\017\142\181\165RG1a\148 A\tC[ \197\238\192\225\006\rx\197\194V\249WkIK\236\143\250DK\176\169>\215\157\223\001G\154\220\164L\\\191q_\149,\232\232/xQ\0201+5\180@\162\211\136\233\014tL W\134a\140\188)\141\b\135\199\tje\144\211\161\187\137\219\139\170+m\b;y\028\017J\006B\149\175\220\218\150\001]S\1709KW\184\140$\215r\197\148n\213&)A\168:Bt\003IQ\188:2\129>\200\240\212\128,\186\234\145e\158\152yc\237j\174:\162~7\144DXXC\143\006\236\182\141\029\240\224\017\174\251,2\007\214\245\220\137\172\253?1\025\1971\229d\228\237\016\183L\218\209 j\021\244\221\005D\131O\194\164\0219\178@6;-\004\135\155`\143\2076/ d\240\137\240pL\240}E\200\0268\178\001\208#\005\028]1\164\219\027\239\202WU\184\177\215\172\142\131\150\189,\193\190\127m\tD\184\149\132\178y\139eA\200\031\193\182\128\136_X\252XJ\134\251\188\t\234g\225\003+\235\201.\219\200\0178.\233W\175R\200\225f\212\248t9A\171%\148\163\022\b\186!=\002\018*mAJ\159\175\155\004\019\005\\\246\002E\230\209\167\192<\249F\184z\196K\217\238\164\016\0197&\188\247H\016\241\006\019\180\"\158\rn\238\028\138\198\216\004\223\182A\141\202\159[{3\231\239\207\180\152\224\135\187O\130v\254>\196\135\155\232\208\162G1\160\024QL(f\148L\020\011J\022\138\021=s\128\154\184\202\189F\202*\1862\014\141\221\208B6bN\234\206\231\000s\131\185\1316\134\0060\172\030\213@\210\156T\248\218%\209\160@\156\236-(\130\233\146x\205H\015\n3m\245\195[u\214q\249\169f\217\\\030\240\201\129i\249\152\016'Rt\251\004\001\169j\127\000Qg\208U\164\247M\230J^\218r\249.q\0035\134nx\132\130\252)r\244\160\186S;\022\140\153E\192\209\218\252\133(\176P\207P5E\200P4\189\203y\211\208D\152\016\142\012\251\206o\190-Hi\235\230k\024Y\004B\020\165w\154\225O:\188u\225I\128\\v\142s\142\001u.\248L\164\184\019\213\178\221D\205OR`'\183\204\239\187\t\167\012\157U\163\194<\187\175\158q\139\028\"\027&z2\136|\130\204[\140\172\1996\167:\012\198F\200dj\014c\152N\00612\222r\167f\147 \213(\203 \205\025!\135\131\141\203\229P\219\153F\180(\130K\000cPn\152\233\137\204\197\021\025\217\024\2219\162\018\140\186\140NK\239\148\023\019\142i\134\153\133'\245\156g\171\018\151\0289kP@9D3U*C\173b\136\027\147\253\212\133\n\181Xc\190#\2249\140\129i\212\205\227-\031aX0\171&}\"jh\212?n\025\160\020\195\134q\167\179\\\219\147\161\014}\016Th\026\178\181\148a\203\236h@\173Uq\164\205NhB\255\145w\204\214\137\007\150\168y\226M\014\130E\1618\026\002\139#k\181N\181\179\152\011\198\140 \202\138\014\016a\219!M\237\028\001/\145w0\031\192\247\156\130\026\149\204\233)\143\160p&\221\143=\134\169\253\171\024&3\184\006|v\221Z\230\140M\155\140U\184$:\029*\234\160\195\203M\227\204X\185$\1562}\161\197lI\254\203\022*t\235\198<\230\030LNEo%\n\004\134iz\208\170\138\242\194o\172Fs\201\190\160\194 \027\026j\178\006\196N\179z\004s\137\163\197\012A\145F\194@\181\029@$\rfJ\150\168\235\134P}\007\016\r\006\215F\219)\b\130\130DS\0005/\000\162%\192l\1497p\155\129\219\r\220a0g\232&\236\206\209\168\171\003\136n\131\153\150\165\220=C\168\183\003\136>\131\163\031\030\161\024 \0203\t\197,B1\155P\204!\020s\t\197\133V\240\b\004i\187!\200\244\007te\225\028\131\175':}\024\002\031\014\252\202\017\214`\218Tk\152\212\137\195\253\230\131\217a\202T_T@\002t\234\136\249\168\195\230\228\241\017\n\192\188\165\175\230DS\215\191\028\006\003W\186\195\201\"fU6Yl\194I\187\"&\202\019\016\149\153\146\153\221mK]E\147\222\1936\137\196+\178k\004iI\186\174\189b\209\154\214X\030i\147\228\148\146&aS\177\164A\224\229\021\0128\0234PdT\156'*\tE\154\003]\233\166f\031\197\150IL\149v\171\181-\220:\131 \198z\221\"\139]\024t\145\017n\005\191\\.\192-\173yQz>\198\167\200h\134\164X'\180W{\137\186t\172\159,\018\n\243\r^I\1617\159\2034\168\185\145i\179l\255y\159B\203\1569\025e\149\216\223\007&\224\176C\014\019uM\163Y\bbPR\028\1657G\1794W\206\149\011en2\137\247TN\170y]H\017\232\231\021\176D\019pd.\001d\029A\177\002\230K\181\252u\n{W\205\019\026\220 V\018\201\166y\132\135\145757\209\1503\1420\136B\192\2052s\176\208&J}\133\143(\188\012H\174\193\137\2361q\181\217\015\239j\166jc\244\250\166\135\155,\187\028\153 \134\135\n\232{\130\226\006\2115\"\001\197\"\130a\1750\181K\138d#&4\148\210\203r|\137/\253o\232:\208\021F\195\1608+\148\255\245\183\016\176\164\149\253\227\b`\246\210\182\0300\226\151\163\168\255\198\136'\155P\226\181$f\1401~j\030\217\014\021p\207& +\199q1\142X6\159\208\154\203\002\147\192ap\150\153\160B\180\244\169\247\205\012\196K\165J\012\133\229\014\1580\237~@\168M\203\192\029\021\133\212\210T\180\244\195\011\017\253\174\160\130\235\196\154\232\026SX\210\225\209,Y\207\2061\185\166\190H\004\225)\017\135\b\134\023\129\151\003\130\022rJ\142\192\"B(Dz'\147jjm\157\236\170O\209,Sk\027\199M\231\153\170\132\176\136q\\\181GvUR\239\209\220\199\212\135\152\006\162\129o\174#\031\237c\154&\232\019\158\184l:Ab\157\168\186)Sf\160e\1418\236H\128{\250?h\183w\212\127\202d\176h\249V*\142\128nx#J\"K4o\210\0024\218&,\2062\247\202\007\018)\002\rF\n\027\160\213\253\166X\173f,\\\022\249\202\0237LN&\012\131T \029\199\248\015\154\137\1947k\151&\182\198;Q\b,\192\155\136>\209\143[\254\209\163\007\015\150J\165\028M(\188:\147X\171\229\190v\226\146\203\252\028\178QK\137\160\136F`P\148\244dZ\1335e\131[m\208-\227\198\164\026g\005\215\178\189\207Dq\177\144Jg\220C\029\150?M\236\236\200\237Q\162W\019\196j7~A^\136xq\020\254\006\001\020\235b\168\028 \026\163\2329s\234?\213a,\135+\170\148\152\007\250\163;\129>!\r\0182\210q\165\207\155\156\021\134y\190'86\251w\159\226z\231\218^\030\238J\250'N\169\197\017M\243'\242\182\1387\218\132\231\027\022\189L\017*\249\141\231'\130\bY7\160d\017\031\2291\177\193\184R\206\220\193\222\145\196+F\251\185T\203e\192\199\1418\169N\161DZ\178FY\180\146\n\207\028\240%Y\220H\004\253`bI\024\155\247\1880&\195i\012S\135\213&\167l\202\186\240\140(\204\"~\152\026\200.\133\217\255n\206d\1570\237\190s^cm\205\234\130AQ;\138r\166 \238\135%\133j\195\237\182+_P.0\022Z\237q_\169\196O\130\139\132\193\217k\028\203f\139Ygv\150\2197\136`v\185\003xT\251\143P\196\"\019\207O\216\200+C#\236\012$gaH\017\238n$7un\131QII\215\187A/\223\135G8\025\158\196g\217\216;\236_c\247\135A\230\003`Ze\139\235y\213\216\175\234tK.\223\"\146\239B\005\195m\144\242gP\189\b\253\236\2330\030Z\178\1832+\175Q\166\218zou\0251\2009{\195\1361\155m\219\017\225\030\127\165\029\\\236+\227+2\159(D\254@\128<\221~\141\228c\127\130'\n\139}\163{\222\1658\030\203\192f;\202y\2092We\179\224\132J\131\187\204F\173sP\020\193\164\178 }\022\150/\200\025\173\245\204T\134\223h\t\024\011\200\007\173\\E\251\241\167\253\026\207\025\004\195\220\159\r\225\223\b\168r\200\247\189/\r\030\"\189]\186oq\t\\\195\231\172\251ZS\223\165)QG 3\236\175\165\004\\z\190\132P\127\230\197\254/k3oc\227\178\149\r~\231\254=\249\210\127\249\229\161\192\006\166\216\r8\199\145-\b\012?\247" - let d_92d67c153383d8a5d46ba6d9247ee68d = "-target-background) !important;\n box-shadow: 0 0px 0 1px var(--target-shadow) !important;\n border-radius: 1px;\n}\n\n*:hover > a.anchor {\n visibility: visible;\n}\n\na.anchor:before {\n content: \"#\";\n}\n\na.anchor:hover {\n box-shadow: none;\n text-decoration: none;\n color: var(--anchor-hover);\n}\n\na.anchor {\n visibility: hidden;\n position: absolute;\n /* top: 0px; */\n /* margin-left: -3ex; */\n margin-left: -1.3em;\n font-weight: normal;\n font-style: normal;\n padding-right: 0.4em;\n padding-left: 0.4em;\n /* To remain selectable */\n color: var(--anchor-color);\n}\n\n.spec > a.anchor {\n margin-left: -2.3em;\n padding-right: 0.9em;\n}\n\n.xref-unresolved {\n color: #2C94BD;\n}\n.xref-unresolved:hover {\n box-shadow: 0 1px 0 0 var(--xref-shadow);\n}\n\n/* Source links float inside preformated text or headings. */\na.source_link {\n float: right;\n color: var(--source-color);\n font-family: \"Fira Sans\", Helvetica, Arial, sans-serif;\n font-size: initial;\n}\n\n/* Section and document divisions.\n Until at least 4.03 many of the modules of the stdlib start at .h7,\n we restart the sequence there like h2 */\n\nh1, h2, h3, h4, h5, h6, .h7, .h8, .h9, .h10 {\n font-family: \"Fira Sans\", Helvetica, Arial, sans-serif;\n font-weight: 400;\n padding-top: 0.1em;\n line-height: 1.2;\n overflow-wrap: break-word;\n}\n\nh1 {\n font-weight: 500;\n font-size: 2.441em;\n}\n\nh1 {\n font-weight: 500;\n font-size: 1.953em;\n box-shadow: 0 1px 0 0 var(--header-shadow);\n}\n\nh2 {\n font-size: 1.563em;\n}\n\nh3 {\n font-size: 1.25em;\n}\n\nsmall, .font_small {\n font-size: 0.8em;\n}\n\nh1 code, h1 tt {\n font-size: inherit;\n font-weight: inherit;\n}\n\nh2 code, h2 tt {\n font-size: inherit;\n font-weight: inherit;\n}\n\nh3 code, h3 tt {\n font-size: inherit;\n font-weight: inherit;\n}\n\nh3 code, h3 tt {\n font-size: inherit;\n font-weight: inherit;\n}\n\nh4 {\n font-size: 1.12em;\n}\n\n/* Comment delimiters, hidden but accessible to screen readers and \n selected for copy/pasting */\n\n/* Taken from bootstrap */\n/* See also https://stackoverflow.com/a/27769435/4220738 */\n.comment-delim {\n position: absolute;\n width: 1px;\n height: 1px;\n padding: 0;\n margin: -1px;\n overflow: hidden;\n clip: rect(0, 0, 0, 0);\n white-space: nowrap;\n border: 0;\n}\n\n/* Preformatted and code */\n\ntt, code, pre {\n font-family: \"Fira Mono\", courier;\n font-weight: 400;\n}\n\n.odoc pre {\n padding: 0.1em;\n border: 1px solid var(--pre-border-color);\n border-radius: 5px;\n overflow-x: auto;\n}\n\n.odoc p code,\n.odoc li code {\n background-color: var(--li-code-background);\n color: var(--li-code-color);\n border-radius: 3px;\n padding: 0 0.3ex;\n}\n\np a > code, li a > code {\n color: var(--link-color);\n}\n\n.odoc code {\n white-space: pre-wrap;\n}\n\n/* Code blocks (e.g. Examples) */\n\n.odoc pre code {\n font-size: 0.893rem;\n}\n\n/* Code lexemes */\n\n.keyword {\n font-weight: 500;\n}\n\n.arrow { white-space: nowrap }\n\n/* Module member specification */\n\n.spec {\n background-color: var(--spec-summary-background);\n border-radius: 3px;\n border-left: 4px solid var(--spec-summary-border-color);\n border-right: 5px solid transparent;\n padding: 0.35em 0.5em;\n}\n\n.spec .label, .spec .optlabel {\n color: var(--spec-label-color);\n}\n\nli:not(:last-child) > .def-doc {\n margin-bottom: 15px;\n}\n\n/* Spacing between items */\ndiv.odoc-spec,.odoc-include {\n margin-bottom: 2em;\n}\n\n.spec.type .variant p, .spec.type .record p {\n margin: 5px;\n}\n\n.spec.type .variant, .spec.type .record {\n margin-left: 2ch;\n}\n\n.spec.type li.variant, .spec.type li.record {\n list-style: none;\n}\n\n.spec.type .record > code, .spec.type .variant > code {\n min-width: 40%;\n}\n\n.spec.type > ol {\n margin-top: 0;\n margin-bottom: 0;\n}\n\n.spec.type .record > .def-doc, .spec.type .variant > .def-doc {\n min-width:50%;\n padding: 0.25em 0.5em;\n margin-left: 10%;\n border-radius: 3px;\n background: var(--main-background);\n box-shadow: 1px 1px 2px lightgrey;\n}\n\ndiv.def {\n margin-top: 0;\n text-indent: -2ex;\n padding-left: 2ex;\n}\n\ndiv.def-doc>*:first-child {\n margin-top: 0;\n}\n\n/* Collapsible inlined include and module */\n\n.odoc-include details {\n position: relative;\n}\n\n.odoc-" - let d_92e0c0a734f49413d685531ad3f0a03e = "7],9125:[-99e-5,.601,0,0,.66667],9126:[.64502,1.155,0,0,.66667],9127:[1e-5,.9,0,0,.88889],9128:[.65002,1.15,0,0,.88889],9129:[.90001,0,0,0,.88889],9130:[0,.3,0,0,.88889],9131:[1e-5,.9,0,0,.88889],9132:[.65002,1.15,0,0,.88889],9133:[.90001,0,0,0,.88889],9143:[.88502,.915,0,0,1.05556],10216:[1.25003,1.75,0,0,.80556],10217:[1.25003,1.75,0,0,.80556],57344:[-.00499,.605,0,0,1.05556],57345:[-.00499,.605,0,0,1.05556],57680:[0,.12,0,0,.45],57681:[0,.12,0,0,.45],57682:[0,.12,0,0,.45],57683:[0,.12,0,0,.45]},\"Typewriter-Regular\":{32:[0,0,0,0,.525],33:[0,.61111,0,0,.525],34:[0,.61111,0,0,.525],35:[0,.61111,0,0,.525],36:[.08333,.69444,0,0,.525],37:[.08333,.69444,0,0,.525],38:[0,.61111,0,0,.525],39:[0,.61111,0,0,.525],40:[.08333,.69444,0,0,.525],41:[.08333,.69444,0,0,.525],42:[0,.52083,0,0,.525],43:[-.08056,.53055,0,0,.525],44:[.13889,.125,0,0,.525],45:[-.08056,.53055,0,0,.525],46:[0,.125,0,0,.525],47:[.08333,.69444,0,0,.525],48:[0,.61111,0,0,.525],49:[0,.61111,0,0,.525],50:[0,.61111,0,0,.525],51:[0,.61111,0,0,.525],52:[0,.61111,0,0,.525],53:[0,.61111,0,0,.525],54:[0,.61111,0,0,.525],55:[0,.61111,0,0,.525],56:[0,.61111,0,0,.525],57:[0,.61111,0,0,.525],58:[0,.43056,0,0,.525],59:[.13889,.43056,0,0,.525],60:[-.05556,.55556,0,0,.525],61:[-.19549,.41562,0,0,.525],62:[-.05556,.55556,0,0,.525],63:[0,.61111,0,0,.525],64:[0,.61111,0,0,.525],65:[0,.61111,0,0,.525],66:[0,.61111,0,0,.525],67:[0,.61111,0,0,.525],68:[0,.61111,0,0,.525],69:[0,.61111,0,0,.525],70:[0,.61111,0,0,.525],71:[0,.61111,0,0,.525],72:[0,.61111,0,0,.525],73:[0,.61111,0,0,.525],74:[0,.61111,0,0,.525],75:[0,.61111,0,0,.525],76:[0,.61111,0,0,.525],77:[0,.61111,0,0,.525],78:[0,.61111,0,0,.525],79:[0,.61111,0,0,.525],80:[0,.61111,0,0,.525],81:[.13889,.61111,0,0,.525],82:[0,.61111,0,0,.525],83:[0,.61111,0,0,.525],84:[0,.61111,0,0,.525],85:[0,.61111,0,0,.525],86:[0,.61111,0,0,.525],87:[0,.61111,0,0,.525],88:[0,.61111,0,0,.525],89:[0,.61111,0,0,.525],90:[0,.61111,0,0,.525],91:[.08333,.69444,0,0,.525],92:[.08333,.69444,0,0,.525],93:[.08333,.69444,0,0,.525],94:[0,.61111,0,0,.525],95:[.09514,0,0,0,.525],96:[0,.61111,0,0,.525],97:[0,.43056,0,0,.525],98:[0,.61111,0,0,.525],99:[0,.43056,0,0,.525],100:[0,.61111,0,0,.525],101:[0,.43056,0,0,.525],102:[0,.61111,0,0,.525],103:[.22222,.43056,0,0,.525],104:[0,.61111,0,0,.525],105:[0,.61111,0,0,.525],106:[.22222,.61111,0,0,.525],107:[0,.61111,0,0,.525],108:[0,.61111,0,0,.525],109:[0,.43056,0,0,.525],110:[0,.43056,0,0,.525],111:[0,.43056,0,0,.525],112:[.22222,.43056,0,0,.525],113:[.22222,.43056,0,0,.525],114:[0,.43056,0,0,.525],115:[0,.43056,0,0,.525],116:[0,.55358,0,0,.525],117:[0,.43056,0,0,.525],118:[0,.43056,0,0,.525],119:[0,.43056,0,0,.525],120:[0,.43056,0,0,.525],121:[.22222,.43056,0,0,.525],122:[0,.43056,0,0,.525],123:[.08333,.69444,0,0,.525],124:[.08333,.69444,0,0,.525],125:[.08333,.69444,0,0,.525],126:[0,.61111,0,0,.525],127:[0,.61111,0,0,.525],160:[0,0,0,0,.525],176:[0,.61111,0,0,.525],184:[.19445,0,0,0,.525],305:[0,.43056,0,0,.525],567:[.22222,.43056,0,0,.525],711:[0,.56597,0,0,.525],713:[0,.56555,0,0,.525],714:[0,.61111,0,0,.525],715:[0,.61111,0,0,.525],728:[0,.61111,0,0,.525],730:[0,.61111,0,0,.525],770:[0,.61111,0,0,.525],771:[0,.61111,0,0,.525],776:[0,.61111,0,0,.525],915:[0,.61111,0,0,.525],916:[0,.61111,0,0,.525],920:[0,.61111,0,0,.525],923:[0,.61111,0,0,.525],926:[0,.61111,0,0,.525],928:[0,.61111,0,0,.525],931:[0,.61111,0,0,.525],933:[0,.61111,0,0,.525],934:[0,.61111,0,0,.525],936:[0,.61111,0,0,.525],937:[0,.61111,0,0,.525],8216:[0,.61111,0,0,.525],8217:[0,.61111,0,0,.525],8242:[0,.61111,0,0,.525],9251:[.11111,.21944,0,0,.525]}},B={slant:[.25,.25,.25],space:[0,0,0],stretch:[0,0,0],shrink:[0,0,0],xHeight:[.431,.431,.431],quad:[1,1.171,1.472],extraSpace:[0,0,0],num1:[.677,.732,.925],num2:[.394,.384,.387],num3:[.444,.471,.504],denom1:[.686,.752,1.025],denom2:[.345,.344,.532],sup1:[.413,.503,.504],sup2:[.363,.431,.404],sup3:[.289,.286,.294],sub1:[.15,.143,.2],sub2:[.247,.286,.4],supDrop:[.386,.353,.494],subDrop:[.05,.071,.1],delim1:[2.39,1.7,1.98],delim2:[1.01,1.157,1.42],axisHeight:[.25,.25,.25],defaultRuleThickness:[.04,.049,.049],bi" let d_957d4df68963704d1e67c9a5d435c28f = "/\166#\255\241\201M\179p\217\244\235 d\242\246\200\237u\016\226}\229'\200\253,\1543\239\021\208`\184\218\025\199w\021\132y%W\184O\012\012b)\\\131\136!\175\227\240\182\226\185\"\174m\208N\205\236\166sx\208\\\152\206\147\127\196\157b\141\131\241\226\000\251\239\142f\253i\168,\000\185G\182bg~fs~\031r\212 \150\180L$-\198\220g\134\018t\167\1935P5\230\203\007\141\229\031K\241\239\1357\188\212\243\132\2166\024\n\194\233)\236\179\197\023\136\020.\001\181\200N\139,;@\191\021f\228\204Q\160\004\014\150\018\1505\210\215\206W\018\196<\186\203\225\203\233>\002>\249\166\024\233`\203\133\164\182\211D\015\182\192\172\195\249&k\1870\t\233\003\148b\177g\026\207\203,\209;>=\195Oxt9\232\238\026H\248\158\242\127\161.\190@\180\b!\195/Z\134G\148\029\160/\134\025\011\250\012\236\159\\;\1377\147=\022#\022J\196w\197\014t|F?\185X\224\153\228\237\137Sx\199\166\167I\005\1395h\166\018\240\016\246\245\006i\167i/\210\1892\182\162ut?\147\136\r\235\199\138Krb\240?U\168\186\"?\178\007\b\217\\[\251\2153UOOo\231\216\189k\247\140\237\148\168L\199\173\138\148D\251\012\015G\\\144B\2340\235F\210}G]\243\183\238g\244j\184\237\1379\004\170\029=\017\254d\147\191\014\139\021\160\219\191\028\142a`\233&\024\179 \135:\175xF\028\1895<&\206&\147k\143\247\247\246em:\192I\022\1861S\n$\147\244\182\152V\248\239\234\r(\212\022\212D\216\145b\145\174\173\149H\183\239\243f\026\029\227n\138\030\229Y\231;3uN\165\185\140\221\132\144-7\127\206r\015\178\166G1\213\187\213D\146@\030\227\154o\245L\251&\156\188\002u\019Nr\156\001\2247Wb.\145\004I[=\175<\t\210\203;\169\156w4\190\240\243\234\177\019=0>\249\001H\017\18742\165(\248\228\176[\184\133\212\136O\000D\188\202\170\248c.%\137\235-\019\133\246\241\238H\015\219\020E\194\198\196T\023\255\208\206\221~\190.@4[\183\151\004\168\006\017\143\252;\242<\018\164SS\1779\215a\024;\0184\185>\005\174uL\028\020\224\133\222\250\004ysm\136l\r\193 \208Z\153\152\198K)\017\214\150pyx\181S\148\200\137&R\017\194Y\014>\180cD\233\020\249\011DB5>\220\201Ad\252\157\194jx\225g&\189dM\179\224s\237b\176\174L?\232\152\254\254\194\137\023[~\017-\249=\235uQH\002\216\2286\188`\208\214\135\211\205\241|\205\196\186\254\b>@\148\224M\255\236A\250\030\215y\140\179\139E\130\000>\254bVn\247\134\2546\238.\219WJ?F*\214\199D\162\141\243\227\252E\202*g+\144\016\\\155sY\249\231\225\181He\017\129\142\214\197I\135\184\014\212\172;\240\138\188\142\022\189R\203\166\147\253\250\173\223\248\024\b\002\141\213\027\181.\171wQ\153\190\012\127\023m\233\131)Zg\151\016h\012\132\127\239\205\213\175\143\165\029=q\0162\191\247\255\189\235 D]\242}\200o\012\221p\224sMS\181\146\223D+wH\163\145\025\2169\162fys1g%\173\209\161\144f\129\178\218|\150\208\199m.S/i}|\134p\135\233\252\192\149d\141X\163,X\189\186\149N\239\208\201\198\166\155Kj\139\204\018\2362\254o`\202O\211\023\146\b\189\233?\221\221\221\001\011\216pQ;\2365i\196w\020\160\016j\215\241\140\004KL\228\228TQk\191\199\247\214\211HF/\\\135\236b@\026)d\239\012\214>7\")W\139N\201i\130\020\153\129\228\244M\029+\227\240\230\221 \240\206\221F\203\222\187\163\190\168\253\228\197\003\202?\023\020\177\129\185\156\029\172L\219x\225\199\"W\245XD\176\162(\160\198\181\213Xb\159 \167 \021\021\188\249\198\237\231\162\155\234Nx\214\020{\245\164\198\173\015\184\215\218~\220?\2236\026Av\016e./+\143#\211l\155|\002\162\b\012\210\190\136\014\233\226@\151QCHI\020\163Z,\139\178d\154oK\239\200Z\232]e\\\029\214\234\222Q\245\001\004\028j\184\241\202\255t\151\242\143\177=\137@\176\194O\195)\1443\195\247<\246,\014\127\164\017\198\156\165>\225.=5\188\144\240\174\015\191\252=\1894A\232\150\138\176\175n[\130'\2003\219\195:M*M\179\246\152R\"b\002\003cX^\152\224ur\156>N\190\014\019\236\197\218\207#\148S\030 \021\164*\225\145-~2\018\252\238YQ}\030\225\131O\177P\250(\214)\252\226R\173\250~\198)QM\152\225\255\133\241\255\204\018<\143\215\019fg\014\219'f\b\185\023\237\012G\139\172\223\183\235\255\225+w\177\239j\200\222\015{>\\\249\147\216\178M\191\127\184WH*\137\217)U\197\163\180\154P~]T\170\255\182\186\204\189lE\235\190{\005h\"\231\0112\157\134]\247\179\149\128\251\191\172\168\148\249\129}\168N\216\240{\201\022\190\245\016v\014\245\252\135\016\242\005\160>\200&\t\239\017\211j\175\200\180\027,Q4\139o7o\251/\180\1946Jo\016x9j\238\151\184%b\204mO@U\218J\184x\154\173\220\134\203\1746\237\177\206\132\185\145\174\148\236^u`K\r\180Q\182\194`n\224\162\233Sp+7\222\189\163\175\209\133\1339\020\241\248NX(k<\190\022\026Z{\138'\023\136\2201\215\201nt\186\027\249:\198\189{,\211\200\178\030S\148\211>\191u\"^#:]{\235\235\186\243\173\244\150tw\247\177lN@b\203+\031\017\206\191\178\132\189\180\188@\224\172\242t\181\n\019\186)p\174\212\024 \001\151H\n\199\t\0018\016\248?\142\208\002Id\147Cy\156hs\023\139\024 \r\151N\138\197\249\000\000<}\001A\168\133X\229\190f\182m\203-=`\246w\199\247\250\201p\227\210\006\237\139Q\006\151\018\161\140\150\164\r\133\r&H\203\195s\253\233\\?\157\000G6\007\1449~\197Q\133\208\142\151\219\021C\184K2\019G\161\146\022\230g\159#*\227\196\bv\168\213;\0041\209\029\241\154`\007\219]\017\0293\222PTM\194\210\192\192R|M\r\017\210\226\151D|\243\141\155P\019\182\157\177\"(??h\005c{\184\214\244\209.\231f(t\160\247\236\153U\"\024\152\203S\150\203\021|\251\000\186\174\223\233\t0\247\140B\219\253\168\200\b\204\229\128\185\"\163\147\211\195X\011\199\158B\134\167Y\128\te\136\221\169\175\133\223\246\230\172\195\rLu=>+\244\155\031\012\194%\141\220=p\215\206\147Mh\\\011\251\187I\231\175X*oX\221\016\195\180\185\239\229\222\142\251n9\157\022\239\163ox\152op\216\145\213M\251\2428px|\127\216?\155\242\2379\236\1790\202u\209\027\140\188\214%\002>\242<\197\019\225\217\155\186\026\171O\240\143{\1975FW\166\209}\193\003\238s\187 v\161\168y|\202\139\251c\147$\141\148\253\230?\198L\1646\254\1582\142w\181\127]\129\153\252\252\130\183x\1674zzx\241\129\194\004\203\253\144\165\229\144j\001\210\177\r:\127\146\193\028\233\216\029\180=\222\1892\132\197\235\177\206\133\177\2331(\007S_\212h\182\130\254]\252%\167\204g\026\183.{C\207J\174\210\215\172[K\250\145TL\252W\144\248\218w\184\162k\221>\183\137\167Ca\251\227\226P{\221\210\197\182\145x\023\011E\234\174\244\205\246wH\b\144N\158\187\170wJ\142\201\181\229\190\178t\148Q\207\027\244\r\177o\191\182\175\"\15447\181\165\194\230\n}\143\186*E)0H`\182'\210\153\237H\165\192\169\243\2037\204r\021\218\131\239+\1761&\206N\017\240\151L\134\173M\188_rR\154\b\190\137\150\025\163\175?\2433D$*)\141H\183\143\020\024-;\208\252\rn\186\254:\020\171\131\201\188\1615'\130\211G\156HF\151+Q\206\nWz\163#\243&\197d\254\240\220\017Lf\172\206\193\031>_e\006\182\234\210\208\000J\nu%x\0116\173\216\194\217:\200\159\157\129\241\215ol+\134\249\129\r|QC]\166\157E9#9\225\006A\1370I<\012\018\168\204 \206m\142\153\255\151pK\031\227[\186x\238\144e`<\223;\165'\2530\014\213\161\b63\238\233\025^\143/N\210\030\029E\156\145\129\0298\n\128\199 \139Y\007\155\173[(a\207\1694.\198\242*\006\145\252\011\175\017j\242\152.N#\b\221H\193\142L\137u\158T\154F\245\244J\195J\156ia\028;O\139,q`\150\141%\207\134\163\185\006a4\2087=\016\226\226\020Eq\183r\209\170EB7\247\0299+sfEX\210]>M]\1677\127\192\000\031M\135S\2382\252\018\156~\214\167\170s\239\160\217\215\001.\014\241\177\205[\255d\182\031K[,\206\004\210\231\145aS\128^\003\187\029\164\155\026[\029\021\244\1646\244i\173K\196U\031\159\148?\238\028\246\182'\030$\178\208\200\020?\159\154\252\187++\031$o\251\183\020u\180\172j|\1458~4=jsS\184\143\012\014\238N+\255&\169\026E\216m\224\205N\195\197\143\250\217\253\191/\006M\005\152\239<\2539y\016\231\184\222i\2074\1563\213\229\178\243\199\185\192\227\129\230\221\167\191$\233\011\031x\196\194\127+NC\r}\014\154\244)\154\n\216}\011\000p=\229\137h\162\216\182\187\001 _+e\184\199\192\r\021s\127\r}\015\154\244\198\230\178\017\196Y\239\171\003p\254\2056f\235\236\150\184\245\129\247\218\218\255\243W\162g\146\184\215\007\224\226G\163\241\018~\n\165N\022\012\188\199\154\182_\140\006'\127\180\156\140\232\144\222\222\189\206hedI N\217\249\230K\238\245\028\031D6\250\217\131f<\229rz\135\244\198\224\026\227\166\232\\\146\170\146@\011\029\233\204B\173]=hNjP\003ju\190\209\252\201\182\160T\129DyA\233\223\135\219\171\234\234OJ4\160js\172G\t\236\248\023\188\214\191e\198\217V\005\248\167\018]\157\179\128I\219GJ\204\172l=6ZX\n\207`\200\133\247\181E\158\169\174u4\255\173]\141\213\209>\235:S>\177\247\249\181\198W'\154;Y\200Ma\243c\204\235u\212ZX\152z\196~7\143\221\195JPu\185+JiG\203\234]\175?3\229\133I\194KM\178\238^\171\141\144\175$\211\221u\186\209\142\017\214|\167.\193\182\222\237*\227\028M~t\132Q\0219\184\157N\201\182\138\236\n4-\019\213_\029\173\214\023\229\146\151\224s\208u\250Cr\191W\142>=al\167t*\nv\137\129\227\170\031\189\253\250*v\029L\200\169f\137E\185p\136v\162UO\001S{\158\174D\223:\157G\198lT\190@f\210\226\128\210'\138\b&q\197\181\212\021\155\132a\030\212\221\235D\132$\135\217\023C`\175\024J\173\186\004Q{]\169\b\201w\182u\025\214\181\245|\159\242\178i\150\159\005\002\129\002\"\172\136\238\130\131\196G-&AV\227 \206(\144\164\242\166\146\198\148\180\164I\021\253\r\004\181$\136]\174%Ff\245y\208\252\140\rYa\172:r\233>K\162p\1722\242\170\143-\214\129\195\212\193e*\149\167`a\218\235\237p\023\234SB\202Smr\165P\128\015F\182\1358:\002u\164\129\172\014\007\205\163\174\199\204\161.5\152\171\015l\150\197\131\163\151\141\\=\171^l:\164)&\250$UgUt\023\146\r!\241OR[\017\017\219\220\2144I\n\165\250\186\194m\216\134\148\006\142\141A\170\170^*$$\191(\b\137\175\030\215\205\rG\017\163\192\255\193\139w\233\195\006\233\r\160g\253^?z\000T\202\170\141?\003#\211\148\023\168}0i\003\215\171\252\020" @@ -266,8 +264,6 @@ module Internal = struct let d_9c62ce25963b0733dee65c540c429af6 = "\191\210\164\160\254\211\139\246\246\220\162\217\015\209p\231\226\144\004Y\184d\144\164'hr\144\167\136JwUU\026\017\149\154\247]\014\028?@S\237K\n\173\242\015\165/?\230\019]\007\179T\182\230\228\203\207:\150v\138>\127\252\252\246\147E[\192\169-\132\138\r\229\229O\228\231\133X\149\182\192\250\226\030b\169\222\199U\160\213=.[u\026=\167\205\173A8\"\220\201\168\196\211\151v\181\b\229\130AF~\233%n\137\1849\203QP\151\2442\141+\222e\233\143Y~\1588\198q\164P\186\231\162\029GG\"Z\185 \214\215\154l\023\2005\221\160$\016P\202\239\015\202\168\193R\019\168\235\175\233C>\161Tl\168\192\015|\011\180S\180\183\206W\151\020[R\186\n\215\185\004ru\221\200\201\213$}\209\160\202\233\025O\243\237\152\14539\026?\026\031vM\238\254\b\224\024\205\019\031\197\229\210\129\131.\147\235`\128\190(\151@_\246\246\160'\018\173\139\142,\211)&\020\186e\194MKMEmL\2401\173Iw\165\231\2294\166\155\231\199\172\162\016\000!\170\140#\180?P\180g\183#-\196\170\232\199A\233\132\212\220N\197\218\220\030\219\253\202\255\191\138N\214\245\154F\234\014\231\030\174{\201\204\254NF\175\254\127l\227\004\186=\224$\014\132\180\129\134]\149O\203\149\197\179\219\223\136;A\147\131\132\205:\231\230\011dB\213\199\253\155BJ\173u\198hG\235\172\240x\220IY-R\223\198\174\128\179K\226/\016l\254\248\167{\031\207(\016.*\016\206\248\248\222Ov\205\254\231\023\150\188\203\r\146\029\179_\235y\245\212ty\170j\249k\179\167;\003\216H\154\007\021\249\234b\152\234\151X\153\198\005\226\161\000jwu8\t\205\222\154j\023V\225s?'g\219\145\190\163^\223\0217uE\197\209\220\175r\143V\172\152\138\157\154)<\235l\139\016o\157\179;\193\140\183\139\206\137\154\160\002\239O\031\023St#\203\183\022\221\t\223\185\243\2068d)\229I\191\196uZ;\240o\216\005\155>\016\022krKTy\178)o\207\136|\"\014D9\202\020\014n\015?J\196\220\249\0272ux\243\015\190\188;\029\234\164\144x\231\019\016\240B\195[B\"\190<\027\231Z1\170xc\200\020\250\139L\178:\163\155\241n6\r\141\190\245\15731\238\168\029?\247Sd\003\227\241\031\196\143\015\028\028_\210K\154\244\216\242\023\209\1745q\131k:\231\221?a\027\209X\215\004\170\243\170\002)-\201\149\191\236\249\226T\016UtP{(\2183l\031^&\016\183\179\229M\209][Y\161\252\2075q\223\149\017\005\248`\187\167\193\005\02346\187\1760\209\1779\005\134\006\210V\028\192\152A*\020cI\170\030U\200\135\151\163#2\203\170\211\190\137^C\148:R\172_\190\174\140\003\003\014x\224\242\153\160.x\230\242@>\000O\141\239\254\163#.\237\218\132\254/\151\189\199J\169\211x\145;\243\1438>\002sb3\127\183\017\197g))s\143%\231\220|\174\1953I\197\151\146\141\167I\153\0038`\170\231\186\203\225\186\222C9\224<@\146\167\027I\169\182\006\148\150l\174lA\2312J\t\171bC\243C\172\202x\0213\192\170\2353j\190\197i\218up\174e\133y\175\025\131\000f1\191\190\1942\247\160\139\166\241okf\168\174\027`\236\170Q[`uF\139\171\204J\1484\"\242\202\014\139\166 \197\"(I\214$).9Xp\176DR,kJ\130D-:E\211\236EP\220R\207\133a\179f\167\246M\131S\187\211\186Y\2182\162\165\165\140_\012\227q\012\030\187}\251\197\143\151\242\1273\018\171o\149\150\224\169\162U\177\182nk7\226\152\149?'\204\196\128O\198VVV\1635^\029\001\2302\139\133a\012e\144\021%>\163\1365\167\208} s^n\173;\026f\232\246bc\149\149\202\249\226\025~\231CY\r\254m4\007\2300\190g\223\130\248\196%J\186\021^xs\011!\023\180\211L\216\185\237\214\151=\242\229+\0007V\1478\133\196\190\231\219\247\169\011\156\023\151K*pc<}\132\216#\171\021`{\027\127NH(@\017_A\026?\250c\240\247\142\169\211\200\178\019\174\190>\248y\165\213L\168\"8\016\172\b\177\233\245h\214\006\137\t\167\199z\138\246Q,\"N\147\176\155\2303\157\017\022\205\015N\202\220}\2550jM\186\171\175O\158\127\203\197E\031\134\245X\216o\252\1873\022l\198\005kG6\221\220\r\230\207\007\189y\208\238\155\155F\214\n\240\205\250\021\005hfu\251\241\225\230oQ&\201\165c\175<\142o\246x\222y\206\134\141\223\187 \232\216\030\177:t\158\141\249\148\209x\238Ug\245\191\\\227\155\142\244\245,A/w\175 U\172\205\1480\244\216\208\r6\159(\247\212\215\228\026\199\n\181%\196\129\rR.Wq\1982b0Z\2094\203\157w\023\153\176\017xI)\161\173\181$\186\012\171h\204\196\245\228\152\165V\229P)\248O\212\231\017\173\166\0278r\148\243;\163\181ui{a\202\023s\232\146)\0225g\219wo\134\018}\031\231xk\178\012\155\238\164\207yp7.\181,\132\025\184\r\203\230\133+R\157\025\174\026\129\149\135\2032\031\216\189\026\230S\134\254\137\230\174\131\182\243\217+q\249\165\217\249mAg\n\217\242-M\218,\148pcb#\170\189U\223\183\184\214\017\181t\020\247\195fS\255\227\252&\133\186\206\145ocY\254\178zW\180\180\2065\181\210\159\237\173I\241\026\253\230Ax\024:\182\159\016:\255v\150c\127\191\185N\128VA\225n\180\006\021\017[\222|\022<\027{\175>77'\163X\191\2478K\n\198\138\026\172\153\129Y\021\n\247\149X\135k\218\028\221\171/\173,-\172\144\219\"\207\238\192\226V\130\149gz\181\209\193\239\1553\028\199ka\150\158\160e\167\162\016\129\2476G\171\241\184\154\241\141\\\0306'\187\216\254\015\232\186\177Z\166bC\2179lFz\136Es\boGsQb\232\244\210\219\241\198\1595\212k\148\234;\011\012\144pF{\146\187\1735\016[\190$\011#\148\210\176\011\146~N\249\193\198\007e\158\\Gw\160@\176X\191\192\235\246%\187\022y2DfylC\023\018\027\147\028c\254\213\018--\147\130\159\251\251\rO\221\139h\216k\021\129\244V\211*\154\203\254\234\023\164\169\1668&tt\t\218Za\137\203|e\161\186\147\169s\131\160\134\156\173\190\208\2515\229\128\020\211?\003\137?\028\149Qr\172[\001\154[\246\220ZW\"\232\185$V#g\146hF\203*$\011\127'\214\156^\197\186\157\160&\183\006\180\181\138,\212\238\221y\185|77\212`\200\145{1.\138Qh\183\207`/2h\191^\217v\239D\025w\236|q!\168\213hk8\028\161DG\201E\221\"\011\245\245\239]\194\213ZTJl\190\223+V|\128\201\218\227W\180{r\2508\015\141\031\232q\159\027\228\148\191\144_\149\1791\240k5Z\234s\221\248\227\215\023\214\214\234\162\242\245\186/\"\210m\003\017B\167\159\248\251\135\170\146RswY\179\210C\187\178\141\227`\239\171\183Q{.yW\158\255xS\242H\171\235\230\212j\146\133\181q\130\198[\020]\018h{\196h\252\171#Z\250\241\000\193\018\184K WM\137\141\t\157r&\2333\215T\141\230\153\235\"m\028\176h\001\129\014\253\244\187\205\184\1597\189K\222\244$\161\159\148\193m\174\223~'P\206\168j\138#7\196\210\b\244V\2544C\172)\178h\019\213\250\23936\234\243\b:}\216\237(\179\205\232\180\203fF\201\178\215X\195\147e\191Jrl\229)xW\148)J\024puf\249\131\025i\254\202\140<_s\166\166\226\230\004\134\189\031\134\226.m\031m\174'\156\030\250bs\170:T\183]\159\242\161\198&\\\248\207\237\221\1801l/\155\254f\227\180\2252\012\190\140\248\ng\ne\132\156\254\174%I\249\230\157\229\225\217\218\002\207|\206[>m\154\168\148\023R8\202Ci\210\129w?\030\209\176Rm\184\134_ST\138]|\003\239\194\18923\015Ce\030O[\254\236f\017\253\030Mn\182\195c\197\2376\127\t\215\229p\230\135X\149\198\159\025\209*\167\182\1796\240\199\205\130r|ssX0\213/\240\t\253MQE\241\247\186kx\2408\127\231+\139\160\200\17983H\217m\128\252a\201\170`$:\206\150v\239yJ|v\193\215\173\210\255\0055\018\150\192\004\158\159Z\236\133\254\239g@&\243\193\132A*/\141\136\140*\232\153\149}\140\027}\234\144\226!\237j\175\243d{\r\205\220\129i\182\228\016\171\001+\207\180\217\225i\255P\184\247\236\218f\027\031.\\\130ZP7\165\007A\157\2179\1302h\217\016\2023'\160\241\158r.\225\187\1671\2542f\202\136\239\129\r\246\246\221\143\235\0068w\220+\181\026\234\146^\b\197\187\174M\254\249g'O\255)\173\241\191rr\141L\220R\185\217\157V\152Z\b\245\236\178\185\012\1866\182\1662\004\026\250\222\207C\127\000\144}\169{\239}\213:\153\014\170\170\132\217\019\149\225\016M/\203\242\030\tr\227^r\159\131\242a\238\203\213\245/1u\191\200\149P\249\138\151\169\232N\191\220\207\024\127\179\176\231\025\250\014\205\145Q\022\130\151\186*S\030@\251\175\207\163y<\132C\152\136\200\195\031\171/\211\234i\205\173`\149\246_C\185\164\018\152\018\232w\137%\006\031-\224\t\248p\141\012<\250\233\149/U\250\021\163\173\164\149\154\006\004\030f\175\163*-\171\177\184t\253'\166HI\175\002tFL\247\1381k\b\223PD\201\b\170h\003\030\178\022c\247\204]\160\139lx\022\221.\194t\195\1631\163\195\234\222{\160\179\131~}h\198\204\161\215\216v\208q\t\253\242\249\017\2283\234F\218\162\132#\168\247\128M\031>\241\204\199\203\161\229\208\193r\140sl=NkpK\209\006|\2531N)v\rZ\014)H\239\020\233\129~\245\177\200(M-\031VO\251\222\212\217\206\19064\211f\031z\157\238\2322~?M=\188\156\162G\171\209\203\240z\174\241\200qDz\255?q^\240\201\005\137 \226t\238\140{\230\223\179\136\242\194/c\031\162\221\169\204a\150r\022\027\168s\012/\227\195Db\210o\176\019\002\162\254[LR&\143\249\016C\235z0Q\141\235\162\135\128\2365t\204$P!\192\023HD\183\031\234\2486\2296l\223\181M\157-bjy\228\138\245\242\215~\002w\175_\183\243\137F\189\017N\250\195EJ\007\255\229\nv\r\020/P\016,\237\237\021\030\200B\253\230\140\179\183\162\029\rYfLTY\153\003\233\207\242y\183\222<\127'\243\196\221\246\011\002\230\238\226E\t\178e\137\238\187\012\255=\180\245\247\131[\128>\205\181g\247\178\170>\161\186\030\253\242\174\212\136\147_/\029\141\129F8D-.<\180\200PD\251\025tz\166\148\190\006\245s6\199y\191&q\163T\224g\138hC\017\250t\187\197@\233]\141\164$\255\187%2\133,\145\218\217bG\0303\0066\132j\188\162e\186\147/\135\205\250\027\178&h\214\183\239\202\229\198(\249\209\132\217\152T\014 R\179\163\179S\255\226\243M\015\151\2519O\131?U\217\1971\238\177K\005\127\227;\241\191\005\210=v\227\147\169\131\156$\b\001\176\212\182\215\251K\230?P\244\170\252\155X\167\188\0299\214\137\250o\164FO,\158\019\175(\235Q?\188\131{Jb(\235\242e<\024\134y\203\134\228\244\233y\157=\183h\249\208\191\155\191)\021X\155\149\171E\200`\144\0012\017\211|\138\203\253\133\167-M'\179\144\012\b\130d\248`\011}\181\183OR\147+\186GH\024:@\004\173\169\247\163Q\000\161\230\212GV\"x\000\130\201\017\248|\249\235\209\203\237\250\153z/b\022\n\005jud\200>4\138cJ\012\143$C\244:s\207\241\244\177\163UNK2[PJN\177\240r\168&*\135g\153BrWr\255\217v\250\206\176\152\022\026\230\244\160V\005^\193-\215\027\205\006\019\167\233oA\191\189\211>\251t@\180\234\137\227\019\189O\023\237P\250\185(\165\214E'1\167\141\248\188\191\127\255\221=\149l\n\204\187\245\179A\171\137\196\184\220l\252\\k\235h\140\"6?\224\"\207\252E\163\230\159l9\1903\252\180$\207\011\028\015\151\233(J\241\005R\229\152\139T\252\200D=\166\248\161\199X\131\029\188\177+\029\\\233\015\030\150\182\011z\003\225\rYC2W@\135>\180?DWjsk\184(\213\175\151v\130\186W\186\172m\129q\216\t\015\181\228\158\145Kq\246ls\238rv\002\135\225d\180\229^q\162FK\1729\157\211\002\195\184\021^\222\146s\142\197\165\242\179UL]m\133\241\215\210\030\205\254*\027&GW\172\020\t&\243gm@\224\142\129\253pv\014,{\134\0207\222DPr\199$\014\194J\129\154X\192G\160'\159T\173+\0233 \220b\242\208vU\248\213 \142b\001\174\017(\225\160\216\020\030\026\165d\151\238:8\137iQ\1582r\017\023\014;\247\232a\152\187\168\140\140\242\164%\202a\020\249\128\162\238\161\209\027\235\231\1434*\198\n%\157\131Ay\250\244\184\182\215\183\172Ca\138\020\154L\196\015`\018\216\127\172\162\162\235\141$\017%-\016\171T\222\167\022k3\242\139\177}\2264\191c[\002\161]\252\148\202\171\190/\245\224\196\132\175\235\159\173\136\133Z\1720\154\132\020\t\163\235\182\188n\237/A\191\242\187\200O\241~3\175\2300\231\153\168\135\025b\017\183\149\219\016]\016\025\208\rD\n\162\185\r\220J\244\179\153\253'V|\221\012^\174\149)h\161\128KBz0*\022\142\166@\006\157\233k\231\21529%\192L\016A\140\202G\t\143\144\208\131\211\157\135(\169\000\134\237\241\135\180\180\144\171\127\162\175J\249\186\135[\154\202J\221j\142=\222)\n" - let d_9cd2127654bad2ec912e7f568f5fc008 = " min-width: unset;\n max-width: unset;\n border: none;\n padding: 0.2em 1em;\n border-radius: 5px;\n margin-bottom: 2em;\n }\n}\n\n/* Print adjustements. */\n\n@media print {\n body {\n color: black;\n background: white;\n }\n body nav:first-child {\n visibility: hidden;\n }\n}\n\n/* Source code. */\n\n.source_container {\n display: flex;\n}\n\n.source_line_column {\n padding-right: 0.5em;\n text-align: right;\n background: #eee8d5;\n}\n\n.source_line {\n padding: 0 1em;\n}\n\n.source_code {\n flex-grow: 1;\n background: #fdf6e3;\n padding: 0 0.3em;\n color: #657b83;\n}\n\n/* Source directories */\n\n.odoc-directory::before {\n content: \"\240\159\147\129\";\n margin: 0.3em;\n font-size: 1.3em;\n}\n\n.odoc-file::before {\n content: \"\240\159\147\132\";\n margin: 0.3em;\n font-size: 1.3em;\n}\n\n.odoc-folder-list {\n list-style: none;\n}\n\n/* Syntax highlighting (based on github-gist) */\n\n.hljs {\n display: block;\n background: var(--code-background);\n padding: 0.5em;\n color: var(--color);\n overflow-x: auto;\n}\n\n.hljs-comment,\n.hljs-meta {\n color: #969896;\n}\n\n.hljs-string,\n.hljs-variable,\n.hljs-template-variable,\n.hljs-strong,\n.hljs-emphasis,\n.hljs-quote {\n color: #df5000;\n}\n\n.hljs-keyword,\n.hljs-selector-tag {\n color: #a71d5d;\n}\n\n.hljs-type,\n.hljs-class .hljs-title {\n color: #458;\n font-weight: 500;\n}\n\n.hljs-literal,\n.hljs-symbol,\n.hljs-bullet,\n.hljs-attribute {\n color: #0086b3;\n}\n\n.hljs-section,\n.hljs-name {\n color: #63a35c;\n}\n\n.hljs-tag {\n color: #333333;\n}\n\n.hljs-attr,\n.hljs-selector-id,\n.hljs-selector-class,\n.hljs-selector-attr,\n.hljs-selector-pseudo {\n color: #795da3;\n}\n\n.hljs-addition {\n color: #55a532;\n background-color: #eaffea;\n}\n\n.hljs-deletion {\n color: #bd2c00;\n background-color: #ffecec;\n}\n\n.hljs-link {\n text-decoration: underline;\n}\n\n.VAL, .TYPE, .LET, .REC, .IN, .OPEN, .NONREC, .MODULE, .METHOD, .LETOP, .INHERIT, .INCLUDE, .FUNCTOR, .EXTERNAL, .CONSTRAINT, .ASSERT, .AND, .END, .CLASS, .STRUCT, .SIG {\n color: #859900;;\n}\n\n.WITH, .WHILE, .WHEN, .VIRTUAL, .TRY, .TO, .THEN, .PRIVATE, .OF, .NEW, .MUTABLE, .MATCH, .LAZY, .IF, .FUNCTION, .FUN, .FOR, .EXCEPTION, .ELSE, .TO, .DOWNTO, .DO, .DONE, .BEGIN, .AS {\n color: #cb4b16;\n}\n\n.TRUE, .FALSE {\n color: #b58900;\n}\n\n.failwith, .INT, .SEMISEMI, .LIDENT {\n color: #2aa198;\n}\n\n.STRING, .CHAR, .UIDENT {\n color: #b58900;\n}\n\n.DOCSTRING {\n color: #268bd2;\n}\n\n.COMMENT {\n color: #93a1a1;\n}\n\n/*---------------------------------------------------------------------------\n Copyright (c) 2016 The odoc contributors\n\n Permission to use, copy, modify, and/or distribute this software for any\n purpose with or without fee is hereby granted, provided that the above\n copyright notice and this permission notice appear in all copies.\n\n THE SOFTWARE IS PROVIDED \"AS IS\" AND THE AUTHOR DISCLAIMS ALL WARRANTIES\n WITH REGARD TO THIS SOFTWARE INCLUDING ALL IMPLIED WARRANTIES OF\n MERCHANTABILITY AND FITNESS. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR\n ANY SPECIAL, DIRECT, INDIRECT, OR CONSEQUENTIAL DAMAGES OR ANY DAMAGES\n WHATSOEVER RESULTING FROM LOSS OF USE, DATA OR PROFITS, WHETHER IN AN\n ACTION OF CONTRACT, NEGLIGENCE OR OTHER TORTIOUS ACTION, ARISING OUT OF\n OR IN CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE.\n ---------------------------------------------------------------------------*/\n" - let d_9f8d31b592653b489fe7600729009383 = "\228\151\194y<\246\011(\018MJv\229\135\236D\021\026\157\199\255\250h\189n\214wu\016\154sD\203\161\181\238\154\151\005<\185io\200!\228!\184\198\249m,-\025\142\213V\187l\196X\026\235\193\165\139\129\231\240\184\202\243\206s\182\1471\213\132\165\145z\0295 \000\181\128\186[Z\193Mv\238\203=:o\135\028k\244D\248\199R\186\200\0210\231\143%\155~+l\024\222\133L7\"\146\197\158~4\206,LV\143\204\168\247\201ML*\240\017x\138\016\023\160\176\216#\137\208\246MH\019A\206&\235N<\15020\185\143\188\240NS\031\207\239\217\1784N\202\192V\251\212\167\214c,\165\240\196p\171\\\154C\015\015U\184\018p)s\179\154\131\139\228\201\249\190\141\226<'AW\153\1793k\255\203\141g\183\142\224\019J\022\148\173\029\201!\1848\239\159\218t\234\240\b\158\159N\221O\184\014\178\203n}Ey\133\204\164\205\134\196\239\024\0246P\\\192u\249>\235*\029\\\204jx\129Sh\200\1589\247y\127Ywa\031\b\144\025Zn\212u\152\016 \214\132{\bB\021\142\136\211w\003gsPpVwI[\190\207\182\238\173\213\144\250\206\213C\249z\239|\220\190\154\136\240\192\133\184\"\2488hhY\255\205\234\028\127M^m\241\"/\177\242\143^\142S\148s\173\240\245a{!\231\130\214\192}\161\199\147\196\215\251\183\198\237\153]\1946\187\248\012q\223a\150\248\206\216\225\187\226\127\223\029g}O\028\171\189q.\020}\252\020\133]\162\240C\020\206w\218\191\216\177\179\245(\028\150\189\137\239\242\186v\219\t\187\246d'\222\190#\234|g2}W\214\250\238\140\173=\025\150@\r\180+\144\016\0052O\129H\195\241\012\015^\152\246\138\159\244\141C\214\127'\255\2521gr\185j\190iG\199\174\012\019\128\200\189jT\211\030\160Z\019\191\131\197\214\194\138$\230\141\031*V\135\187\170Q\139b\028\233K\028\161\003\0020\1369\233\003\153&{\192\016h\246\135n3\212\132Y\151YjYH\021/\211-\210\132\165\007'\016\b0@\197\204\003\017\173\193\001r\249f'H?\187|\129\b\019\244\158k\182\201\207-\183\136\134-\255(\1370A\014\177f\011\177\007\201\151\016\020\218Y&\172u\tp{\202\186\177l:\222\226;\223\012\023\206\152D\152H\246^\179\213\221\210A\175@\130D\152 \132.\177w\160\231\187\137\238B\129\199\239\001\242\021\166q\135\130b\196\187\159\20012\137[\248\159]\199\0022\231\017\199\029T\244!A\168\159p\252\167\213\210?\230\223\1407b\1942.\169\150\2120>\004\014\028\164.\1315\139\201p\129\159YoO\144\023\231\208,7\012\2022+\132\161\219\137\027ujV\130\204l\t(\219{C\219|G\20178\208\204\026\147\224\134\020 \023\neR\0011\005\193|\189av\247\244\029t*\129\000 \254BP\028R7\133\231\154\011\171+pZj\161\021R\1678\012W\1347\2550S_\183\030\226\166d\022\153g\023\232\188\"H\211\018\194\153\209\011l\14257\211N:\178&\0146h\178\156\138\244\020\159y\1563`\240\142\166e)\182\020\012F1\242\153\221/\026\026\223X\223\203b\246\247G\242\144\209=\230\222d\199\216`d\162\185\231\128\031\128\149\184\016\"\027<\018\015\000\155\146\232\214\240\240\\\251\029Y\026\031\152\242}\168+\227\130[&@6\215<\170\163\014\211%\1344\236\019\234k\215\rBZ\132&R\171\251\022I\160\187Y\139\134Y\173A+8>L\233\172\189\t\019R\196\2102\003\178\165\\\029\24800$\017\"\195`\136@QXU\234\020 \006\151\028\128\249\217w\152ad\000\189\173\174,mG\018\230!\030\230nP\228R\199cH\"\024\206\b\141f\192)\025\219\211[\012\137\253W\014\251`\bn\210Q\209\230\235K?\215%\166\225\137\1641\165W\2399\154t\"\220\026\166H\rO\240\186\174\172\246\213\031*(\208\005\139;(\134\186\r\197jR\155\164\251\198\188\196\n\221%wK\0266\020\243\162h\165\228;\030\r\021\193uJ\218-\163I\019I\027h\195v\249\224\192>\238\025\206\134I\128\158\028\253\184A^\024j\024z\237P\014\156Y\170a\018'\172\227\154\206B\007\136^{\240\214\135\224&BK\130\001\014\005\028\163\128\196E\210\230iV\127L\214\142\249\199:\221\216\198^,\194\145\161\249\r\250:\196\012\167\028\206\165\131\227\227\236%V(?,C\023\129!\172\183\177\017\018w;\209(\170]\006h\166\200p\246\004\160 ZIK\n\0299t\225Y\155\240\154ok\139<\230\132y\192\230d\156\232`\011 \178L6\"\019\003\220m!\180:w\217\180\026\144W\184`\178Vhnd\n\019\020\210\171\148\195D\222)9u\172\233\174rW\221Q\144p\r\184\rl\023\003L\173\216R\193\205\253[z\bLD\128\134\148Pln\133\183vU\217#\006@3T\250XfA\n\169\240\165e\b@\018\014{\146.\"\172\183\226\150\133\164)\188L\029\244\168\016\135\024`\020e,\1531\251\004\163\018\137\247\137 \172t@$\225[\211\210\"\139\018\230\128\153J[b\224\170L\1818d\017\182\142\220\182\0190\212\007--\140\215Y0\183u\213\206\003\241\162\142\2100\248\248*M_\1814\149\bnYK\t/2\133\173\156\199\\\028P\020\016N \\\130X\128\213\186\135\165P/\214\"5H\154J\001\249\204\198%\199+#\t\218\197\233 S\164y4H\180\177%,\006x!\157\165a\128m\020\004,\214*\028\211\236\208\248\213a\172,h\025L\004\178\223\157U\b;Z\130\247\192\030,\016-\196aKt)\199\246\174\224X\128/\030\020\130\214\0008.\015\232b\174\011\2243\187\171\143OR~\185\13711\237\249\216\200s\238\151j\026\165\232}\250r\230uf\156\027|\128\171]\152IZ\130\187\"\227f.\029\005\204XC\232'\134\138\213\226*\159\152\180\018W\025YG\210\200\1445\243U\177PQ\005p\129\226,\002\202:\237\216\029\017\023dxP\015\133!^K\1967\023\016aG\235w\169D\214\237}\219\021\023\216,E\149Y*l\1327\180\177\1656}\172\243\011H\203!\212:\027\235\181y\016\238G\211 E\"\rs\000\154K\135o\191\2270V\251\157x\165\168X_9\000I]\"\179\254(\221d\026\231\187R\147aiw\163z\250\243\2328\250t\011\026!\2162\161\168#d^.\0295\018\148\178\011\204\020\197\133\215#@\003I\166\139\190\187\172<\231\1881\019.>\031=\127\019w\031\023\016s\207b^\167x\236\234\0192\167<(\174w\253u\225\179M\236j\241M\242q\158\187\153\198\018\140\n\224l\244\2378>\221xz\b\231\214\140\167\027\1835\020\195:\175\215\235f&\155\222\213_P\173Z\179\188\181\223o+\026\152\145c\208\239\244\231\143^\158\148\238\157\207<\234\028-\220\147Y\221\191\2213\186\234]Sv=3U\217\151Y\139\171\229{\016\142\204wB\143\255\174\206\240\135\137\152\002?tT\181W\213\177\173\192:\220\026JD\161\218\229\175c\021\150\249oq\214\169\202\182\187\153.\137yZ\127Z\015n\206\145\141\012\"\162\2244_\136\134]\173\000A\189\006\213V\225\186>\186\198A\129\248\140\026\004\018\255U\179\211\234N\239\155\2012\253u\136\161\211b.G\203#z'(\192`\007\204\128p9L\187\200\215\248\1759\157\001\239\215i\168\b\237=\234\023Pp\015v\202\r\158\159?_\001d\239\222\030\030\206\211\"9\165\167\137\r\201\152d\2104\228cO:\245\027\185\147\193d\226Y\146\2292c\016\194\"\129\131)\203\171L\014\232Q\000\161\206\b\174n\221\163\236\150\186\029\011\011\215\002\135\1428P\163\164\182v\222NJ\0264$\214\014A~\143\239\167\255\020\134\236\192\219\178\230\214\184|\137i=lx\157\215}\219%\225\185\157t\161\180\236:\230\015){\237\205\204\226x\136\195K%~\019\023c&\024\193\127p\240\227\251\030\130\155\243\165\175\196L\144\242*\223\216[\143p\203\222!\135\230.0\154\199\138\195\2523\224\018\254\017\149\218M\221\158\150\250\137\207\173\007\173\191\161&IS\016\224Y&\007\164\130x}\208\020\192\238\247\023#\001{\248\242\182h\184\177\194\253\138\1692\160K`\169\203\150\241ABy:+4\192\172\218;R\156\2044\015\154CL\164\160Ff\184\143<\246\155S,\219\241@\234\150\238\001.\132\166\219\207\190Z\024\023\r1\161y\1796x\174u\174\183\193|\178\180\\(\244\152_\n\251Al\224\204)\204Y\195\249\242\002\211\019\027\163\219\169\030\030\251\253\200\199\016\218pP\021\235\153\"\246\029\185Q\022\176\155tIg\005s\138\016\249\012\209\021=ys4\170\251\167+\135\188\211\252&\232\243\155\015\1803B\239P=\"\169\028\0248>\196m\223\230\240\186\151\207\204\b1p\205\181JE\195\026\181\180fS\001\230\024\208\r'\140^~\197\229\173x\1766\184\153\223\172\019I\242\144Ad5\017\138\141s\165\181C\021\246\215\137\018\028\176y-k\142\014\155\213aN\136*\"\215\130\182\154%V\172b\157S3)\184h\198O\173O\232\179C\156Z\183\132-\0311\225\147\249+\128\153\127\029\192\027\241\r\222\195=o$\172\004\247\155%\255\024\143_\249\215h\239n|\225t\234b\029)\243\135\028$^\226\030\254\031\150\242c\177R\129\186;&\136X\171\191\254\015;)\001\235\200|\003\152\011\223\244ouz4\218Y\142\171\142\213\"y\205d\181k/\015\250\2280I\222f{\137\249\004\185\225F\152\138M\bL~\222\213\014\n*+\19763\133I\226\231\167n\193\174\243O\240\006\0121B\181Ix\130\235j+G\165\172u\133\255\204\221kH\"\004&jS[\017/nJ\bM\1742\190\195\241\230x\216\226p\208\199Q\132)\209>I\255\127\\\175\232t\156\157\201\020\135\252+d\201\002N3B-T\232\240t\146\023\204\133\241\228y\252+\176\238u\173\178J\017\166\160\179\248)]\234\011\151\184\128\189`\027\174e\163\193M\180\203\183\188\154\224\227q\135\140\217\227#4Rt@\247\194qd\bT\219^g\168\166\234\227D\\z\tg*\141s\027\178\193\209\148\145\003FL\209\250\005\181\243Yh\189\181V\030\143\142\183\006,3\188x\236\177\1393\180\027\005\242\011\029?\130\238l\168@\190\160\015\230U.\b\1366A\147\244L\208$\137\219Nn#s\233\000\139\142\193\023Z?9\026\214\r\014=i7\156\207}\198\156O\151Q*\185\160\1739V{b\241\023n\159os\011N\214\006\031\241\1454\151\237\145\173\0301\141\201\211\184\237\188\176\001\229\175y\243\166?\251\218\232\157\159\014\232\163\255\186\142\207\186\184\022ZL\219Q\177\134\146\197\022\170\179\198\128\176\t\159\195\165\154W\231\018j&\147\213y\012\212\022)\151\003\"n3zy\221\174\220j\015kD\195\20481\183.\162\133\023\210\232\206\187\231&\005\149O\250\168\030i8J#K\227[\168\207\167l?\183@\216vq\166\150/]\"\207\171\024\203Q\182US\216/\245\247\b\027\190\236\164\203\211_!\252q\0258\173>\018P{\177\n\143_\244\210\183\203_&R~\231Y,\031Nr\212\135\162\222\"Ty\235\216 \199 \211f{\026B\167\207\016\023~&\018)\163\246)a\196\193\2415\242\156\161\020\241\189\t\161\151J\022\132kwG\207)\014b\233 E\210\012]-6\002\236\177\165\182\143\254V'\201\025v)B\215z=\187\184\"\007\227]\215g\247\015r;i@g\023\222/\205iFgv\147\158\235Jv\160uUo\163\145\027\024{&4\166\162\156\207\248\172tw\180\128\246$\140\014\158\233\142\209\165\175\236\176\158\140\193\2217?\140\176`\195\209\197\171\166n\217\153\224\196\2398,\167`\255Het\221\220~\201]x\228\208\232U\200\220\201\147+1\0231\215t@\142nJq\254\185$WN\161\181\209\225Mt\201x\149\137H\174\236\b\r\138\012\rT[\0032\252\r\248\169\012\220\127\023sb}\173\\\173-\026\185\210\130\244/\025\005\011I\207\174\b\030\b\183\189=r\198\t\007\134HX\180\141rD6hm\252\0023\024S&4\232\015t\184{\150\022\209\196caWe\159o\001;5\\\171\187\173\220\135K\127bp3\210\233v\170)\224\028[b\253\205\212xI>C\246\144\003\001\244\t\242\230\"\127b\191\155L\185\136U\233]\128\151p\236\140s|\239\221\031h\237LZ\001e\1408\028x2\026\015\215\227\198/\221\164K~2\217~\184\162\173\209\213\189h\149>\158\196\231\189\029S\140\208'W\142\006\005\218\128\214\190\165Ar\206m\195v^\026l\183\210\154N\177\1979\161\014\184\027Zn\211\169\132\228\183\224\134\r[N\128\238\138\221\185\246\194\r\187\200\203\229\138\213\002a=+m\208M\178V.hl\195u\018\212.T\171[6\188\202\202\1681\218\006\147\002\186}v\003\181\221\005\204Y\006tg\177\231\163P\185=\238\000\169U\218\231\191\171\224\249\193h\019\171\245\024^\183\206\012)\164oK:\003\151\000\166\211\186\203\030\173C\227\198U \237\254D_\163\234\188\197\132\1398\028\030\194\168\019-\179\214\148\167\218\146\171\160M\178\139\160\017.\137\016\n\t\195\137\173R@\132\158X\138\024\236\199\204Uy\238X\248%q\186\179\254y`\255\199\143/\\O\250\167\127\237\127\172\1996C \248m\181\141\130@\248\253P\231/\255\175\247\239z\249z\029[0\182 \b\144\207\198-7>\139t\014\028\248\025\196\230\020{D\007\216^\248\246[n\243,\144\181\015\012u\134\252~\1713\173\006\187\023\175\214\136\174-\"\187\011\175e\226\187m\222\237\183\154j5f\167r\204\132\003\031\241,c\173\164\169\195(\139\007J\027t\246~\153\245\029\238z0\231\2369\240\134{g\246:\208\238\2279\"\182\138\003l\027\001\227\253\163\141m\236\179\133}5\161\247\023\168\240+\199\181dq|\\6\022\001\223\214\128\142d\236\222\003\218.\168\141\1340G\145\142\190!j\237o\236~5\207v\028\251\174\131\206\022\139\243\185\139\149\232bW\026\201V\169\245\201XfH\237h\251\179DC\140\018g)^\187\138\202gF\214$\204\190\025\000\249\137\000\215\001\129\169\206\196^\158\187\252<\149^O\231\151z\201\182\254\133lg\164v#\168\133T\237\004\1616E\208\136\197\238h1K&\2038\006\149\231\148\230\145Y\174-\198\170|^\207m\202r\018\221\127\161\170D[q$\230\235\n\213^\156\249<\153 \253\022\133\015\227;\162\172\206K\234\127\t\186J{\159>0)\014\1819F\170\195\024\18474\022~\237\131(\153~\198T\169%k\1291]j\245\029\\\227Q\252\169!_\150\168\016#\016\212\249\216\000=f\015\007\b\188/p\204" let d_9ff5a6ec97f55e01b81f13d9d3f0ff67 = "in\"===e.family){var n=qt(e,t);\"bold-italic\"===n&&r.setAttribute(\"mathvariant\",n)}else\"punct\"===e.family?r.setAttribute(\"separator\",\"true\"):\"open\"!==e.family&&\"close\"!==e.family||r.setAttribute(\"stretchy\",\"false\");return r}});var kn={mi:\"italic\",mn:\"normal\",mtext:\"normal\"};st({type:\"mathord\",htmlBuilder:function(e,t){return Ke.makeOrd(e,t,\"mathord\")},mathmlBuilder:function(e,t){var r=new Tt.MathNode(\"mi\",[Bt(e.text,e.mode,t)]),n=qt(e,t)||\"italic\";return n!==kn[r.type]&&r.setAttribute(\"mathvariant\",n),r}}),st({type:\"textord\",htmlBuilder:function(e,t){return Ke.makeOrd(e,t,\"textord\")},mathmlBuilder:function(e,t){var r,n=Bt(e.text,e.mode,t),a=qt(e,t)||\"normal\";return r=\"text\"===e.mode?new Tt.MathNode(\"mtext\",[n]):/[0-9]/.test(e.text)?new Tt.MathNode(\"mn\",[n]):\"\\\\prime\"===e.text?new Tt.MathNode(\"mo\",[n]):new Tt.MathNode(\"mi\",[n]),a!==kn[r.type]&&r.setAttribute(\"mathvariant\",a),r}});var Sn={\"\\\\nobreak\":\"nobreak\",\"\\\\allowbreak\":\"allowbreak\"},Mn={\" \":{},\"\\\\ \":{},\"~\":{className:\"nobreak\"},\"\\\\space\":{},\"\\\\nobreakspace\":{className:\"nobreak\"}};st({type:\"spacing\",htmlBuilder:function(e,t){if(Mn.hasOwnProperty(e.text)){var r=Mn[e.text].className||\"\";if(\"text\"===e.mode){var a=Ke.makeOrd(e,t,\"textord\");return a.classes.push(r),a}return Ke.makeSpan([\"mspace\",r],[Ke.mathsym(e.text,e.mode,t)],t)}if(Sn.hasOwnProperty(e.text))return Ke.makeSpan([\"mspace\",Sn[e.text]],[],t);throw new n('Unknown type of space \"'+e.text+'\"')},mathmlBuilder:function(e,t){if(!Mn.hasOwnProperty(e.text)){if(Sn.hasOwnProperty(e.text))return new Tt.MathNode(\"mspace\");throw new n('Unknown type of space \"'+e.text+'\"')}return new Tt.MathNode(\"mtext\",[new Tt.TextNode(\"\\xa0\")])}});var zn=function(){var e=new Tt.MathNode(\"mtd\",[]);return e.setAttribute(\"width\",\"50%\"),e};st({type:\"tag\",mathmlBuilder:function(e,t){var r=new Tt.MathNode(\"mtable\",[new Tt.MathNode(\"mtr\",[zn(),new Tt.MathNode(\"mtd\",[It(e.body,t)]),zn(),new Tt.MathNode(\"mtd\",[It(e.tag,t)])])]);return r.setAttribute(\"width\",\"100%\"),r}});var An={\"\\\\text\":void 0,\"\\\\textrm\":\"textrm\",\"\\\\textsf\":\"textsf\",\"\\\\texttt\":\"texttt\",\"\\\\textnormal\":\"textrm\"},Tn={\"\\\\textbf\":\"textbf\",\"\\\\textmd\":\"textmd\"},Bn={\"\\\\textit\":\"textit\",\"\\\\textup\":\"textup\"},Cn=function(e,t){var r=e.font;return r?An[r]?t.withTextFontFamily(An[r]):Tn[r]?t.withTextFontWeight(Tn[r]):t.withTextFontShape(Bn[r]):t};ot({type:\"text\",names:[\"\\\\text\",\"\\\\textrm\",\"\\\\textsf\",\"\\\\texttt\",\"\\\\textnormal\",\"\\\\textbf\",\"\\\\textmd\",\"\\\\textit\",\"\\\\textup\"],props:{numArgs:1,argTypes:[\"text\"],allowedInArgument:!0,allowedInText:!0},handler:function(e,t){var r=e.parser,n=e.funcName,a=t[0];return{type:\"text\",mode:r.mode,body:ht(a),font:n}},htmlBuilder:function(e,t){var r=Cn(e,t),n=ft(e.body,r,!0);return Ke.makeSpan([\"mord\",\"text\"],n,r)},mathmlBuilder:function(e,t){var r=Cn(e,t);return It(e.body,r)}}),ot({type:\"underline\",names:[\"\\\\underline\"],props:{numArgs:1,allowedInText:!0},handler:function(e,t){return{type:\"underline\",mode:e.parser.mode,body:t[0]}},htmlBuilder:function(e,t){var r=wt(e.body,t),n=Ke.makeLineSpan(\"underline-line\",t),a=t.fontMetrics().defaultRuleThickness,i=Ke.makeVList({positionType:\"top\",positionData:r.height,children:[{type:\"kern\",size:a},{type:\"elem\",elem:n},{type:\"kern\",size:3*a},{type:\"elem\",elem:r}]},t);return Ke.makeSpan([\"mord\",\"underline\"],[i],t)},mathmlBuilder:function(e,t){var r=new Tt.MathNode(\"mo\",[new Tt.TextNode(\"\\u203e\")]);r.setAttribute(\"stretchy\",\"true\");var n=new Tt.MathNode(\"munder\",[Rt(e.body,t),r]);return n.setAttribute(\"accentunder\",\"true\"),n}}),ot({type:\"vcenter\",names:[\"\\\\vcenter\"],props:{numArgs:1,argTypes:[\"original\"],allowedInText:!1},handler:function(e,t){return{type:\"vcenter\",mode:e.parser.mode,body:t[0]}},htmlBuilder:function(e,t){var r=wt(e.body,t),n=t.fontMetrics().axisHeight,a=.5*(r.height-n-(r.depth+n));return Ke.makeVList({positionType:\"shift\",positionData:a,children:[{type:\"elem\",elem:r}]},t)},mathmlBuilder:function(e,t){return new Tt.MathNode(\"mpadded\",[Rt(e.body,t)],[\"vcenter\"])}}),ot({type:\"verb\",names:[\"\\\\verb\"],props:{numArgs:0,allowedInText:!0},handler:function(e,t,r){throw new n(\"\\\\verb ended by end of line instead of matching" @@ -292,6 +288,8 @@ module Internal = struct let d_a8b5fa32242a1d360076af4bdc9dafbe = "n o.height=r,o.depth=n,o},mathmlBuilder:function(e,t){var r=new Tt.MathNode(\"mglyph\",[]);r.setAttribute(\"alt\",e.alt);var n=F(e.height,t),a=0;if(e.totalheight.number>0&&(a=F(e.totalheight,t)-n,r.setAttribute(\"valign\",V(-a))),r.setAttribute(\"height\",V(n+a)),e.width.number>0){var i=F(e.width,t);r.setAttribute(\"width\",V(i))}return r.setAttribute(\"src\",e.src),r}}),ot({type:\"kern\",names:[\"\\\\kern\",\"\\\\mkern\",\"\\\\hskip\",\"\\\\mskip\"],props:{numArgs:1,argTypes:[\"size\"],primitive:!0,allowedInText:!0},handler:function(e,t){var r=e.parser,n=e.funcName,a=Ut(t[0],\"size\");if(r.settings.strict){var i=\"m\"===n[1],o=\"mu\"===a.value.unit;i?(o||r.settings.reportNonstrict(\"mathVsTextUnits\",\"LaTeX's \"+n+\" supports only mu units, not \"+a.value.unit+\" units\"),\"math\"!==r.mode&&r.settings.reportNonstrict(\"mathVsTextUnits\",\"LaTeX's \"+n+\" works only in math mode\")):o&&r.settings.reportNonstrict(\"mathVsTextUnits\",\"LaTeX's \"+n+\" doesn't support mu units\")}return{type:\"kern\",mode:r.mode,dimension:a.value}},htmlBuilder:function(e,t){return Ke.makeGlue(e.dimension,t)},mathmlBuilder:function(e,t){var r=F(e.dimension,t);return new Tt.SpaceNode(r)}}),ot({type:\"lap\",names:[\"\\\\mathllap\",\"\\\\mathrlap\",\"\\\\mathclap\"],props:{numArgs:1,allowedInText:!0},handler:function(e,t){var r=e.parser,n=e.funcName,a=t[0];return{type:\"lap\",mode:r.mode,alignment:n.slice(5),body:a}},htmlBuilder:function(e,t){var r;\"clap\"===e.alignment?(r=Ke.makeSpan([],[wt(e.body,t)]),r=Ke.makeSpan([\"inner\"],[r],t)):r=Ke.makeSpan([\"inner\"],[wt(e.body,t)]);var n=Ke.makeSpan([\"fix\"],[]),a=Ke.makeSpan([e.alignment],[r,n],t),i=Ke.makeSpan([\"strut\"]);return i.style.height=V(a.height+a.depth),a.depth&&(i.style.verticalAlign=V(-a.depth)),a.children.unshift(i),a=Ke.makeSpan([\"thinbox\"],[a],t),Ke.makeSpan([\"mord\",\"vbox\"],[a],t)},mathmlBuilder:function(e,t){var r=new Tt.MathNode(\"mpadded\",[Rt(e.body,t)]);if(\"rlap\"!==e.alignment){var n=\"llap\"===e.alignment?\"-1\":\"-0.5\";r.setAttribute(\"lspace\",n+\"width\")}return r.setAttribute(\"width\",\"0px\"),r}}),ot({type:\"styling\",names:[\"\\\\(\",\"$\"],props:{numArgs:0,allowedInText:!0,allowedInMath:!1},handler:function(e,t){var r=e.funcName,n=e.parser,a=n.mode;n.switchMode(\"math\");var i=\"\\\\(\"===r?\"\\\\)\":\"$\",o=n.parseExpression(!1,i);return n.expect(i),n.switchMode(a),{type:\"styling\",mode:n.mode,style:\"text\",body:o}}}),ot({type:\"text\",names:[\"\\\\)\",\"\\\\]\"],props:{numArgs:0,allowedInText:!0,allowedInMath:!1},handler:function(e,t){throw new n(\"Mismatched \"+e.funcName)}});var mn=function(e,t){switch(t.style.size){case x.DISPLAY.size:return e.display;case x.TEXT.size:return e.text;case x.SCRIPT.size:return e.script;case x.SCRIPTSCRIPT.size:return e.scriptscript;default:return e.text}};ot({type:\"mathchoice\",names:[\"\\\\mathchoice\"],props:{numArgs:4,primitive:!0},handler:function(e,t){return{type:\"mathchoice\",mode:e.parser.mode,display:ht(t[0]),text:ht(t[1]),script:ht(t[2]),scriptscript:ht(t[3])}},htmlBuilder:function(e,t){var r=mn(e,t),n=ft(r,t,!1);return Ke.makeFragment(n)},mathmlBuilder:function(e,t){var r=mn(e,t);return It(r,t)}});var cn=function(e,t,r,n,a,i,o){e=Ke.makeSpan([],[e]);var s,h,m,c=r&&l.isCharacterBox(r);if(t){var u=wt(t,n.havingStyle(a.sup()),n);h={elem:u,kern:Math.max(n.fontMetrics().bigOpSpacing1,n.fontMetrics().bigOpSpacing3-u.depth)}}if(r){var p=wt(r,n.havingStyle(a.sub()),n);s={elem:p,kern:Math.max(n.fontMetrics().bigOpSpacing2,n.fontMetrics().bigOpSpacing4-p.height)}}if(h&&s){var d=n.fontMetrics().bigOpSpacing5+s.elem.height+s.elem.depth+s.kern+e.depth+o;m=Ke.makeVList({positionType:\"bottom\",positionData:d,children:[{type:\"kern\",size:n.fontMetrics().bigOpSpacing5},{type:\"elem\",elem:s.elem,marginLeft:V(-i)},{type:\"kern\",size:s.kern},{type:\"elem\",elem:e},{type:\"kern\",size:h.kern},{type:\"elem\",elem:h.elem,marginLeft:V(i)},{type:\"kern\",size:n.fontMetrics().bigOpSpacing5}]},n)}else if(s){var f=e.height-o;m=Ke.makeVList({positionType:\"top\",positionData:f,children:[{type:\"kern\",size:n.fontMetrics().bigOpSpacing5},{type:\"elem\",elem:s.elem,marginLeft:V(-i)},{type:\"kern\",size:s.kern},{type:\"elem\",elem:e}]},n)}else{if(!h)return e;var g=e.depth+o;m=Ke.makeVList({positionType:\"bottom\"," + let d_ab2604284e190ff3f5212ebfbc51a704 = "rline-color: #444;\n --visited-color: #002800;\n --visited-number-color: #252;\n --unvisited-color: #380000;\n --unvisited-number-color: #622;\n --somevisited-color: #303000;\n --highlight-color: #303e3f;\n --line-number-color: rgba(230, 230, 230, 0.3);\n --unvisited-margin-color: #622;\n --border: #333;\n --navbar-border: #333;\n --code-color: #ccc;\n\n --li-code-background: #373737;\n --li-code-color: #999;\n --toc-color: #777;\n --toc-background: #252525;\n --toc-background-emph: #2a2a2a;\n\n --hljs-link: #999;\n --hljs-keyword: #cda869;\n --hljs-regexp: #f9ee98;\n --hljs-title: #dcdcaa;\n --hljs-type: #ac885b;\n --hljs-meta: #82aaff;\n --hljs-variable: #cf6a4c;\n\n --spec-label-color: lightgreen;\n}\n\n@media (prefers-color-scheme: dark) {\n :root {\n --main-background: #202020;\n --code-background: #333;\n --line-numbers-background: rgba(0, 0, 0, 0.125);\n --navbar-background: #202020;\n\n --meter-unvisited-color: #622;\n --meter-visited-color: #252;\n --meter-separator-color: black;\n\n --color: #bebebe;\n --dirname-color: #666;\n --underline-color: #444;\n --visited-color: #002800;\n --visited-number-color: #252;\n --unvisited-color: #380000;\n --unvisited-number-color: #622;\n --somevisited-color: #303000;\n --highlight-color: #303e3f;\n --line-number-color: rgba(230, 230, 230, 0.3);\n --unvisited-margin-color: #622;\n --border: #333;\n --navbar-border: #333;\n --code-color: #ccc;\n --by-name-nav-link-color: var(--color);\n\n --li-code-background: #373737;\n --li-code-color: #999;\n --toc-color: #777;\n --toc-before-color: #777;\n --toc-background: #252525;\n --toc-background-emph: #2a2a2a;\n --toc-list-border: #ccc;\n --spec-summary-hover-background: #ebeff2;\n --spec-details-after-background: rgba(0, 4, 15, 0.05);\n --spec-details-after-shadow: rgba(204, 204, 204, 0.53);\n\n --hljs-link: #999;\n --hljs-keyword: #cda869;\n --hljs-regexp: #f9ee98;\n --hljs-title: #dcdcaa;\n --hljs-type: #ac885b;\n --hljs-meta: #82aaff;\n --hljs-variable: #cf6a4c;\n\n --spec-label-color: lightgreen;\n }\n}\n\n/* Reset a few things. */\n\nhtml, body, div, span, applet, object, iframe, h1, h2, h3, h4, h5, h6, p, blockquote, pre, a, abbr, acronym, address, big, cite, code, del, dfn, em, img, ins, kbd, q, s, samp, small, strike, strong, sub, sup, tt, var, b, u, i, center, dl, dt, dd, ol, ul, li, fieldset, form, label, legend, table, caption, tbody, tfoot, thead, tr, th, td, article, aside, canvas, details, embed, figure, figcaption, footer, header, hgroup, menu, nav, output, ruby, section, summary, time, mark, audio, video {\n padding: 0;\n border: 0;\n font: inherit;\n vertical-align: baseline;\n\n}\n\ntable {\n border-collapse: collapse;\n border-spacing: 0;\n}\n\n*, *:before, *:after {\n box-sizing: border-box;\n}\n\nhtml {\n font-size: 15px;\n scroll-behavior: smooth;\n}\n\nbody {\n text-align: left;\n background: #FFFFFF;\n color: var(--color);\n background-color: var(--main-background);\n font-family: \"Noticia Text\", Georgia, serif;\n line-height: 1.5;\n}\n\nbody {\n margin-left: calc(10vw + 20ex);\n margin-right: 4ex;\n margin-top: 20px;\n margin-bottom: 50px;\n}\n\nbody.odoc {\n max-width: 100ex;\n}\n\nbody.odoc-src {\n margin-right: calc(10vw + 20ex);\n}\n\nheader {\n margin-bottom: 30px;\n}\n\nnav {\n font-family: \"Fira Sans\", Helvetica, Arial, sans-serif;\n}\n\n/* Basic markup elements */\n\nb, strong {\n font-weight: bold;\n}\n\ni {\n font-style: italic;\n}\n\nem, i em.odd{\n font-style: italic;\n}\n\nem.odd, i em {\n font-style: normal;\n}\n\nsup {\n vertical-align: super;\n}\n\nsub {\n vertical-align: sub;\n}\n\nsup, sub {\n font-size: 12px;\n line-height: 0;\n margin-left: 0.2ex;\n}\n\nul, ol {\n list-style-position: outside\n}\n\nul>li {\n margin-left: 22px;\n}\n\nol>li {\n margin-left: 27.2px;\n}\n\nli>*:first-child {\n margin-top: 0\n}\n\n/* Text alignements, this should be forbidden. */\n\n.left {\n text-align: left;\n}\n\n.right {\n text-align: right;\n}\n\n.center {\n text-align: center;\n}\n\n/* Links and anchors */\n\na {\n text-decoration: none;\n color: var(--link-color);\n}\n\n.odoc-src pre a {\n color: inherit;\n}\n\na:hover {\n " + let d_ad152fcf832897f8629ca758460f3d22 = "ize10.size11{font-size:1.19961427em}.katex .fontsize-ensurer.reset-size11.size1,.katex .sizing.reset-size11.size1{font-size:.20096463em}.katex .fontsize-ensurer.reset-size11.size2,.katex .sizing.reset-size11.size2{font-size:.24115756em}.katex .fontsize-ensurer.reset-size11.size3,.katex .sizing.reset-size11.size3{font-size:.28135048em}.katex .fontsize-ensurer.reset-size11.size4,.katex .sizing.reset-size11.size4{font-size:.32154341em}.katex .fontsize-ensurer.reset-size11.size5,.katex .sizing.reset-size11.size5{font-size:.36173633em}.katex .fontsize-ensurer.reset-size11.size6,.katex .sizing.reset-size11.size6{font-size:.40192926em}.katex .fontsize-ensurer.reset-size11.size7,.katex .sizing.reset-size11.size7{font-size:.48231511em}.katex .fontsize-ensurer.reset-size11.size8,.katex .sizing.reset-size11.size8{font-size:.57877814em}.katex .fontsize-ensurer.reset-size11.size9,.katex .sizing.reset-size11.size9{font-size:.69453376em}.katex .fontsize-ensurer.reset-size11.size10,.katex .sizing.reset-size11.size10{font-size:.83360129em}.katex .fontsize-ensurer.reset-size11.size11,.katex .sizing.reset-size11.size11{font-size:1em}.katex .delimsizing.size1{font-family:KaTeX_Size1}.katex .delimsizing.size2{font-family:KaTeX_Size2}.katex .delimsizing.size3{font-family:KaTeX_Size3}.katex .delimsizing.size4{font-family:KaTeX_Size4}.katex .delimsizing.mult .delim-size1>span{font-family:KaTeX_Size1}.katex .delimsizing.mult .delim-size4>span{font-family:KaTeX_Size4}.katex .nulldelimiter{display:inline-block;width:.12em}.katex .delimcenter,.katex .op-symbol{position:relative}.katex .op-symbol.small-op{font-family:KaTeX_Size1}.katex .op-symbol.large-op{font-family:KaTeX_Size2}.katex .accent>.vlist-t,.katex .op-limits>.vlist-t{text-align:center}.katex .accent .accent-body{position:relative}.katex .accent .accent-body:not(.accent-full){width:0}.katex .overlay{display:block}.katex .mtable .vertical-separator{display:inline-block;min-width:1px}.katex .mtable .arraycolsep{display:inline-block}.katex .mtable .col-align-c>.vlist-t{text-align:center}.katex .mtable .col-align-l>.vlist-t{text-align:left}.katex .mtable .col-align-r>.vlist-t{text-align:right}.katex .svg-align{text-align:left}.katex svg{fill:currentColor;stroke:currentColor;fill-rule:nonzero;fill-opacity:1;stroke-width:1;stroke-linecap:butt;stroke-linejoin:miter;stroke-miterlimit:4;stroke-dasharray:none;stroke-dashoffset:0;stroke-opacity:1;display:block;height:inherit;position:absolute;width:100%}.katex svg path{stroke:none}.katex img{border-style:none;max-height:none;max-width:none;min-height:0;min-width:0}.katex .stretchy{display:block;overflow:hidden;position:relative;width:100%}.katex .stretchy:after,.katex .stretchy:before{content:\"\"}.katex .hide-tail{overflow:hidden;position:relative;width:100%}.katex .halfarrow-left{left:0;overflow:hidden;position:absolute;width:50.2%}.katex .halfarrow-right{overflow:hidden;position:absolute;right:0;width:50.2%}.katex .brace-left{left:0;overflow:hidden;position:absolute;width:25.1%}.katex .brace-center{left:25%;overflow:hidden;position:absolute;width:50%}.katex .brace-right{overflow:hidden;position:absolute;right:0;width:25.1%}.katex .x-arrow-pad{padding:0 .5em}.katex .cd-arrow-pad{padding:0 .55556em 0 .27778em}.katex .mover,.katex .munder,.katex .x-arrow{text-align:center}.katex .boxpad{padding:0 .3em}.katex .fbox,.katex .fcolorbox{border:.04em solid;box-sizing:border-box}.katex .cancel-pad{padding:0 .2em}.katex .cancel-lap{margin-left:-.2em;margin-right:-.2em}.katex .sout{border-bottom-style:solid;border-bottom-width:.08em}.katex .angl{border-right:.049em solid;border-top:.049em solid;box-sizing:border-box;margin-right:.03889em}.katex .anglpad{padding:0 .03889em}.katex .eqn-num:before{content:\"(\" counter(katexEqnNo) \")\";counter-increment:katexEqnNo}.katex .mml-eqn-num:before{content:\"(\" counter(mmlEqnNo) \")\";counter-increment:mmlEqnNo}.katex .mtr-glue{width:50%}.katex .cd-vert-arrow{display:inline-block;position:relative}.katex .cd-label-left{display:inline-block;position:absolute;right:calc(50% + .3em);text-align:left}.katex .cd-label-right{display:" let d_ad48849637d7c8349cb3e6952d5c8699 = "0.7 8.3 195.3 44 280 108 55.3 42 101.7 93 139 153l9 14c2.7-4 5.7-8.7 9-14\\n 53.3-86.7 123.7-153 211-199 66.7-36 137.3-56.3 212-62h199568v120H200432c-178.3\\n 11.7-311.7 78.3-403 201-6 8-9.7 12-11 12-.7.7-6.7 1-18 1s-17.3-.3-18-1c-1.3 0\\n-5-4-11-12-44.7-59.3-101.3-106.3-170-141s-145.3-54.3-229-60H0V214z\",oiintSize1:\"M512.6 71.6c272.6 0 320.3 106.8 320.3 178.2 0 70.8-47.7 177.6\\n-320.3 177.6S193.1 320.6 193.1 249.8c0-71.4 46.9-178.2 319.5-178.2z\\nm368.1 178.2c0-86.4-60.9-215.4-368.1-215.4-306.4 0-367.3 129-367.3 215.4 0 85.8\\n60.9 214.8 367.3 214.8 307.2 0 368.1-129 368.1-214.8z\",oiintSize2:\"M757.8 100.1c384.7 0 451.1 137.6 451.1 230 0 91.3-66.4 228.8\\n-451.1 228.8-386.3 0-452.7-137.5-452.7-228.8 0-92.4 66.4-230 452.7-230z\\nm502.4 230c0-111.2-82.4-277.2-502.4-277.2s-504 166-504 277.2\\nc0 110 84 276 504 276s502.4-166 502.4-276z\",oiiintSize1:\"M681.4 71.6c408.9 0 480.5 106.8 480.5 178.2 0 70.8-71.6 177.6\\n-480.5 177.6S202.1 320.6 202.1 249.8c0-71.4 70.5-178.2 479.3-178.2z\\nm525.8 178.2c0-86.4-86.8-215.4-525.7-215.4-437.9 0-524.7 129-524.7 215.4 0\\n85.8 86.8 214.8 524.7 214.8 438.9 0 525.7-129 525.7-214.8z\",oiiintSize2:\"M1021.2 53c603.6 0 707.8 165.8 707.8 277.2 0 110-104.2 275.8\\n-707.8 275.8-606 0-710.2-165.8-710.2-275.8C311 218.8 415.2 53 1021.2 53z\\nm770.4 277.1c0-131.2-126.4-327.6-770.5-327.6S248.4 198.9 248.4 330.1\\nc0 130 128.8 326.4 772.7 326.4s770.5-196.4 770.5-326.4z\",rightarrow:\"M0 241v40h399891c-47.3 35.3-84 78-110 128\\n-16.7 32-27.7 63.7-33 95 0 1.3-.2 2.7-.5 4-.3 1.3-.5 2.3-.5 3 0 7.3 6.7 11 20\\n 11 8 0 13.2-.8 15.5-2.5 2.3-1.7 4.2-5.5 5.5-11.5 2-13.3 5.7-27 11-41 14.7-44.7\\n 39-84.5 73-119.5s73.7-60.2 119-75.5c6-2 9-5.7 9-11s-3-9-9-11c-45.3-15.3-85\\n-40.5-119-75.5s-58.3-74.8-73-119.5c-4.7-14-8.3-27.3-11-40-1.3-6.7-3.2-10.8-5.5\\n-12.5-2.3-1.7-7.5-2.5-15.5-2.5-14 0-21 3.7-21 11 0 2 2 10.3 6 25 20.7 83.3 67\\n 151.7 139 205zm0 0v40h399900v-40z\",rightbrace:\"M400000 542l\\n-6 6h-17c-12.7 0-19.3-.3-20-1-4-4-7.3-8.3-10-13-35.3-51.3-80.8-93.8-136.5-127.5\\ns-117.2-55.8-184.5-66.5c-.7 0-2-.3-4-1-18.7-2.7-76-4.3-172-5H0V214h399571l6 1\\nc124.7 8 235 61.7 331 161 31.3 33.3 59.7 72.7 85 118l7 13v35z\",rightbraceunder:\"M399994 0l6 6v35l-6 11c-56 104-135.3 181.3-238 232-57.3\\n 28.7-117 45-179 50H-300V214h399897c43.3-7 81-15 113-26 100.7-33 179.7-91 237\\n-174 2.7-5 6-9 10-13 .7-1 7.3-1 20-1h17z\",rightgroup:\"M0 80h399565c371 0 266.7 149.4 414 180 5.9 1.2 18 0 18 0 2 0\\n 3-1 3-3v-38c-76-158-257-219-435-219H0z\",rightgroupunder:\"M0 262h399565c371 0 266.7-149.4 414-180 5.9-1.2 18 0 18\\n 0 2 0 3 1 3 3v38c-76 158-257 219-435 219H0z\",rightharpoon:\"M0 241v40h399993c4.7-4.7 7-9.3 7-14 0-9.3\\n-3.7-15.3-11-18-92.7-56.7-159-133.7-199-231-3.3-9.3-6-14.7-8-16-2-1.3-7-2-15-2\\n-10.7 0-16.7 2-18 6-2 2.7-1 9.7 3 21 15.3 42 36.7 81.8 64 119.5 27.3 37.7 58\\n 69.2 92 94.5zm0 0v40h399900v-40z\",rightharpoonplus:\"M0 241v40h399993c4.7-4.7 7-9.3 7-14 0-9.3-3.7-15.3-11\\n-18-92.7-56.7-159-133.7-199-231-3.3-9.3-6-14.7-8-16-2-1.3-7-2-15-2-10.7 0-16.7\\n 2-18 6-2 2.7-1 9.7 3 21 15.3 42 36.7 81.8 64 119.5 27.3 37.7 58 69.2 92 94.5z\\nm0 0v40h399900v-40z m100 194v40h399900v-40zm0 0v40h399900v-40z\",rightharpoondown:\"M399747 511c0 7.3 6.7 11 20 11 8 0 13-.8 15-2.5s4.7-6.8\\n 8-15.5c40-94 99.3-166.3 178-217 13.3-8 20.3-12.3 21-13 5.3-3.3 8.5-5.8 9.5\\n-7.5 1-1.7 1.5-5.2 1.5-10.5s-2.3-10.3-7-15H0v40h399908c-34 25.3-64.7 57-92 95\\n-27.3 38-48.7 77.7-64 119-3.3 8.7-5 14-5 16zM0 241v40h399900v-40z\",rightharpoondownplus:\"M399747 705c0 7.3 6.7 11 20 11 8 0 13-.8\\n 15-2.5s4.7-6.8 8-15.5c40-94 99.3-166.3 178-217 13.3-8 20.3-12.3 21-13 5.3-3.3\\n 8.5-5.8 9.5-7.5 1-1.7 1.5-5.2 1.5-10.5s-2.3-10.3-7-15H0v40h399908c-34 25.3\\n-64.7 57-92 95-27.3 38-48.7 77.7-64 119-3.3 8.7-5 14-5 16zM0 435v40h399900v-40z\\nm0-194v40h400000v-40zm0 0v40h400000v-40z\",righthook:\"M399859 241c-764 0 0 0 0 0 40-3.3 68.7-15.7 86-37 10-12 15-25.3\\n 15-40 0-22.7-9.8-40.7-29.5-54-19.7-13.3-43.5-21-71.5-23-17.3-1.3-26-8-26-20 0\\n-13.3 8.7-20 26-20 38 0 71 11.2 99 33.5 0 0 7 5.6 21 16.7 14 11.2 21 33.5 21\\n 66.8s-14 61.2-42 83.5c-28 22.3-61 33.5-99 33.5L0 241z M0 281v-40h399859v40z\",rightlinesegment:\"M399960 241 V94 h" @@ -314,6 +312,8 @@ module Internal = struct let d_b93e718b1ddefad06d18d9736584ad78 = ",67:[0,.68611,.06979,0,.81694],68:[0,.68611,.03194,0,.93812],69:[0,.68611,.05451,0,.81007],70:[0,.68611,.15972,0,.68889],71:[0,.68611,0,0,.88673],72:[0,.68611,.08229,0,.98229],73:[0,.68611,.07778,0,.51111],74:[0,.68611,.10069,0,.63125],75:[0,.68611,.06979,0,.97118],76:[0,.68611,0,0,.75555],77:[0,.68611,.11424,0,1.14201],78:[0,.68611,.11424,0,.95034],79:[0,.68611,.03194,0,.83666],80:[0,.68611,.15972,0,.72309],81:[.19444,.68611,0,0,.86861],82:[0,.68611,.00421,0,.87235],83:[0,.68611,.05382,0,.69271],84:[0,.68611,.15972,0,.63663],85:[0,.68611,.11424,0,.80027],86:[0,.68611,.25555,0,.67778],87:[0,.68611,.15972,0,1.09305],88:[0,.68611,.07778,0,.94722],89:[0,.68611,.25555,0,.67458],90:[0,.68611,.06979,0,.77257],97:[0,.44444,0,0,.63287],98:[0,.69444,0,0,.52083],99:[0,.44444,0,0,.51342],100:[0,.69444,0,0,.60972],101:[0,.44444,0,0,.55361],102:[.19444,.69444,.11042,0,.56806],103:[.19444,.44444,.03704,0,.5449],104:[0,.69444,0,0,.66759],105:[0,.69326,0,0,.4048],106:[.19444,.69326,.0622,0,.47083],107:[0,.69444,.01852,0,.6037],108:[0,.69444,.0088,0,.34815],109:[0,.44444,0,0,1.0324],110:[0,.44444,0,0,.71296],111:[0,.44444,0,0,.58472],112:[.19444,.44444,0,0,.60092],113:[.19444,.44444,.03704,0,.54213],114:[0,.44444,.03194,0,.5287],115:[0,.44444,0,0,.53125],116:[0,.63492,0,0,.41528],117:[0,.44444,0,0,.68102],118:[0,.44444,.03704,0,.56666],119:[0,.44444,.02778,0,.83148],120:[0,.44444,0,0,.65903],121:[.19444,.44444,.03704,0,.59028],122:[0,.44444,.04213,0,.55509],160:[0,0,0,0,.25],915:[0,.68611,.15972,0,.65694],916:[0,.68611,0,0,.95833],920:[0,.68611,.03194,0,.86722],923:[0,.68611,0,0,.80555],926:[0,.68611,.07458,0,.84125],928:[0,.68611,.08229,0,.98229],931:[0,.68611,.05451,0,.88507],933:[0,.68611,.15972,0,.67083],934:[0,.68611,0,0,.76666],936:[0,.68611,.11653,0,.71402],937:[0,.68611,.04835,0,.8789],945:[0,.44444,0,0,.76064],946:[.19444,.69444,.03403,0,.65972],947:[.19444,.44444,.06389,0,.59003],948:[0,.69444,.03819,0,.52222],949:[0,.44444,0,0,.52882],950:[.19444,.69444,.06215,0,.50833],951:[.19444,.44444,.03704,0,.6],952:[0,.69444,.03194,0,.5618],953:[0,.44444,0,0,.41204],954:[0,.44444,0,0,.66759],955:[0,.69444,0,0,.67083],956:[.19444,.44444,0,0,.70787],957:[0,.44444,.06898,0,.57685],958:[.19444,.69444,.03021,0,.50833],959:[0,.44444,0,0,.58472],960:[0,.44444,.03704,0,.68241],961:[.19444,.44444,0,0,.6118],962:[.09722,.44444,.07917,0,.42361],963:[0,.44444,.03704,0,.68588],964:[0,.44444,.13472,0,.52083],965:[0,.44444,.03704,0,.63055],966:[.19444,.44444,0,0,.74722],967:[.19444,.44444,0,0,.71805],968:[.19444,.69444,.03704,0,.75833],969:[0,.44444,.03704,0,.71782],977:[0,.69444,0,0,.69155],981:[.19444,.69444,0,0,.7125],982:[0,.44444,.03194,0,.975],1009:[.19444,.44444,0,0,.6118],1013:[0,.44444,0,0,.48333],57649:[0,.44444,0,0,.39352],57911:[.19444,.44444,0,0,.43889]},\"Math-Italic\":{32:[0,0,0,0,.25],48:[0,.43056,0,0,.5],49:[0,.43056,0,0,.5],50:[0,.43056,0,0,.5],51:[.19444,.43056,0,0,.5],52:[.19444,.43056,0,0,.5],53:[.19444,.43056,0,0,.5],54:[0,.64444,0,0,.5],55:[.19444,.43056,0,0,.5],56:[0,.64444,0,0,.5],57:[.19444,.43056,0,0,.5],65:[0,.68333,0,.13889,.75],66:[0,.68333,.05017,.08334,.75851],67:[0,.68333,.07153,.08334,.71472],68:[0,.68333,.02778,.05556,.82792],69:[0,.68333,.05764,.08334,.7382],70:[0,.68333,.13889,.08334,.64306],71:[0,.68333,0,.08334,.78625],72:[0,.68333,.08125,.05556,.83125],73:[0,.68333,.07847,.11111,.43958],74:[0,.68333,.09618,.16667,.55451],75:[0,.68333,.07153,.05556,.84931],76:[0,.68333,0,.02778,.68056],77:[0,.68333,.10903,.08334,.97014],78:[0,.68333,.10903,.08334,.80347],79:[0,.68333,.02778,.08334,.76278],80:[0,.68333,.13889,.08334,.64201],81:[.19444,.68333,0,.08334,.79056],82:[0,.68333,.00773,.08334,.75929],83:[0,.68333,.05764,.08334,.6132],84:[0,.68333,.13889,.08334,.58438],85:[0,.68333,.10903,.02778,.68278],86:[0,.68333,.22222,0,.58333],87:[0,.68333,.13889,0,.94445],88:[0,.68333,.07847,.08334,.82847],89:[0,.68333,.22222,0,.58056],90:[0,.68333,.07153,.08334,.68264],97:[0,.43056,0,0,.52859],98:[0,.69444,0,0,.42917],99:[0,.43056,0,.05556,.43276],100:[0,.69444,0,.16667,.52049],101:[0,.43056,0,.05556,.46563],102:[.19444,.69444,.10764" + let d_b99316dbe0d494e759ac0178687672ce = "idth: 100%;\n}\n\n.search-bar-container {\n display: flex;\n}\n\n.odoc-search .search-entry {\n color: var(--color);\n display: block;\n margin-top: 10px;\n margin-bottom: 10px;\n /* border: 3px ridge pink */\n border-left: 2px solid transparent;\n}\n.odoc-search .search-entry p {\n margin:0;\n}\n\n.odoc-search .search-entry:hover {\n border: none;\n box-shadow: none;\n border-left: 2px solid var(--link-color);\n}\n\n.odoc-search .search-entry.value {\n /* border: 3px ridge red */\n}\n\n.odoc-search .search-entry .entry-title .entry-kind {\n font-size: 0.75em;\n font-weight: 900;\n border: 1px solid;\n border-color: var(--color);\n border-radius: 3px;\n margin-right: 0.5em;\n margin-left: 0.25em;\n padding-right: 0.25em;\n padding-left: 0.25em;\n}\n\n.odoc-search .search-entry pre {\n border:none;\n margin:0;\n}\n\n.odoc-search .search-entry pre code {\n font-size: 1em;\n background-color: var(--li-code-background);\n color: var(--li-code-color);\n border-radius: 3px;\n padding: 0 0.3ex;\n}\n\n.odoc-search .search-entry .entry-title {\n padding-right: 10px;\n background-color: var(--toc-background-emph);\n width: 100%;\n display: block;\n}\n\n.odoc-search.active .search-entry .entry-name {\n font-size: 1.2em;\n}\n\n.odoc-search.active .search-entry .prefix-name {\n font-size: 1.2em;\n}\n\n.odoc-search .search-entry .prefix-name {\n opacity: 0.5;\n}\n\n.odoc-search .search-entry .entry-comment {\n margin-left: 10px;\n max-height: 100px;\n overflow: scroll;\n font-size: 0.8em;\n}\n\n.odoc-search.active .search-entry .entry-comment {\n max-height: 300px;\n font-size: 1rem;\n}\n\n/* First level titles */\n\n.odoc-toc>ul>li>a {\n font-weight: 500;\n}\n\n.odoc-toc li ul {\n margin: 0px;\n}\n\n.odoc-toc ul {\n list-style-type: none;\n}\n\n.odoc-toc ul li {\n margin: 0;\n}\n.odoc-toc>ul>li {\n margin-bottom: 0.3em;\n}\n\n.odoc-toc ul li li {\n border-left: 1px solid var(--toc-list-border);\n margin-left: 5px;\n padding-left: 12px;\n}\n\n/* Tables */\n\n.odoc-table {\n margin: 1em;\n}\n\n.odoc-table td, .odoc-table th {\n padding-left: 0.5em;\n padding-right: 0.5em;\n border: 1px solid black;\n}\n\n.odoc-table th {\n font-weight: bold;\n}\n\n/* Mobile adjustements. */\n\n@media only screen and (max-width: 110ex) {\n body {\n margin: 2em;\n }\n .odoc-toc {\n position: static;\n width: auto;\n min-width: unset;\n max-width: unset;\n border: none;\n padding: 0.2em 1em;\n border-radius: 5px;\n margin-bottom: 2em;\n }\n}\n\n/* Print adjustements. */\n\n@media print {\n body {\n color: black;\n background: white;\n }\n body nav:first-child {\n visibility: hidden;\n }\n}\n\n/* Source code. */\n\n.source_container {\n display: flex;\n}\n\n.source_line_column {\n padding-right: 0.5em;\n text-align: right;\n background: #eee8d5;\n}\n\n.source_line {\n padding: 0 1em;\n}\n\n.source_code {\n flex-grow: 1;\n background: #fdf6e3;\n padding: 0 0.3em;\n color: #657b83;\n}\n\n/* Source directories */\n\n.odoc-directory::before {\n content: \"\240\159\147\129\";\n margin: 0.3em;\n font-size: 1.3em;\n}\n\n.odoc-file::before {\n content: \"\240\159\147\132\";\n margin: 0.3em;\n font-size: 1.3em;\n}\n\n.odoc-folder-list {\n list-style: none;\n}\n\n/* Syntax highlighting (based on github-gist) */\n\n.hljs {\n display: block;\n background: var(--code-background);\n padding: 0.5em;\n color: var(--color);\n overflow-x: auto;\n}\n\n.hljs-comment,\n.hljs-meta {\n color: #969896;\n}\n\n.hljs-string,\n.hljs-variable,\n.hljs-template-variable,\n.hljs-strong,\n.hljs-emphasis,\n.hljs-quote {\n color: #df5000;\n}\n\n.hljs-keyword,\n.hljs-selector-tag {\n color: #a71d5d;\n}\n\n.hljs-type,\n.hljs-class .hljs-title {\n color: #458;\n font-weight: 500;\n}\n\n.hljs-literal,\n.hljs-symbol,\n.hljs-bullet,\n.hljs-attribute {\n color: #0086b3;\n}\n\n.hljs-section,\n.hljs-name {\n color: #63a35c;\n}\n\n.hljs-tag {\n color: #333333;\n}\n\n.hljs-attr,\n.hljs-selector-id,\n.hljs-selector-class,\n.hljs-selector-attr,\n.hljs-selector-pseudo {\n color: #795da3;\n}\n\n.hljs-addition {\n color: #55a532;\n background-color: #eaffea;\n}\n\n.hljs-deletion {\n color: #bd2c00;\n background-color: #ffecec;\n}\n\n.hljs-link {\n text-decoration: underline;\n}\n\n.VAL, .TYPE, .LET, .REC, .IN, .OPEN, .NONREC, .MODULE, .METHOD, .LETOP, .INHERIT, .INCLUDE" + let d_b9a406e0bd34a5c3cd79d4001e684519 = "wOF2\000\001\000\000\000\000\020X\000\014\000\000\000\000-\020\000\000\020\001\000\001\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\000\006`\000\129D\b\014\t\156\012\017\b\n\1700\161\022\0016\002$\003\129\030\011R\000\004 \005\137\000\007\130$\012\129\028\0273'#\017vs\180\194S\252\229\001O\198o\170\0020!\182e\132\229Q{\159\216\2258\014Vo\246\234\011\140TE~\132$\179\199\211\182~\222\238\146)&K(K/\224!6`&X\129\222\023\206\232\203(\184\252\217-\0010\206n`iB\169\014\209q\153I\254V\161\206V\160\254\007\024\135=\191\\o\208:\204T\145\154\203I\"u\189\233\188\\`\215\201vO@FVE\018\168\234\225\246\1974[\218\001BK\150\239a\167\168\0024\001\130\163W\1594e B[\202E\149\176\002\171l\128t\0012\160\158\140 \005%\255\217E\237\162\190\174\026\157!I\002bU\250\255\191Vi\223\253U\181\012v9D\030H'\194\198\152?\175\186\230\212\255\191\155\003U\195\r\131='[\213\187a\228\158\014\016*V{|N4\030\015$I\152\200M,;\029\023!\\\164\206r8\250\209+l~\127\175\245f[u\197JL\016&\012\177\245J\251\188G\001\024>\129\182\001\003\000\219\128\221\011\000\155\164KF\031\130#\128\129X\2272\128\031\196\240\237w\240|j\135E}\224E\150\15389\227\209\026\169\197;I\128\173\1578\136\205H7\023nQrh\208r\"\001\209\144B\214\239\"\027HFv\029\022Z\236\024\2468\246.\142k%\218\004\173M\251\136\142g\248\202\132\153\b\019sf&\000\018\197\174\r?\017\211\138Vo\214>\168c\027\1904\1937\247\238\"\239\r[m1\248_\201\127\206\255\004\239c\239\253\253\222\215\239\181\188\167x3\243u\221\235\218\2155\128@\252\195\212\240(@\128\167\208\139\"\235\255`\236n\029\230\195\247@\2502\212[:\147&\240\n\022\249?[\006\164\026\234\137\177\022x\003\168\221\022T\152\188\003\0012?s`P\171\214\129C\234\011|\230\214\136\239 \163\164\228\0116\211\241%\181\155`<8\023\248\014\198N\174!n\207[\172\171\139\201\163\233<\176m\241V8;z\240@BL}+\211i\197\237)p\027Nc\171\212\174~\137\136\225\t\005C\146\147\164\244\244\158\170\145Zx\240\022\"\251\222R:\202\222\176\007\243(X\240\136{?\130%n\154f\163\246\182\161\188{\030\143<\232y\139R\160\152k\168\232\169\164J\208\154\198\211\131\0179\147fC\193\016W%Y\147\b\205\149\133\155\220A\138\209\208\000,\224s\b\220\007\224b\169\172\232\155(RjS.\242?\177\012q\247\241\143!e\140u\142\160\020c\028\020_\n\148T\031\029\012HO \"\215\002\139;\001\150{\216\238\141\181\198r\238`&]&J\003\133Uz\209\225A'\205 \248e\000\228k\017F\219\142\1574\179\166\211\219\156\221\028xs\166\003/T\205\\JP?\142a\199\236\197 s\177*\180\206\188\209\172\213\183\225=\179\179\255~\007{\216\236\002\023\128\172\212o\180\016d\167\134\220\185\210\142`\227\233 UEV\208sTT\128\185*Mf\252\015f\248\238\019\192\227\212Wc\183T:\229%^\140\194\237\t\239\247\242\145\189T\012j\153#\227\155\2179\231t\202\216\170\217\212F\178T\210\001\027o\184Q\165\146\2207\181:\231\152v\149\b\148%g\207\254|\011\151\185\127\163;\194\221^7\229}\021(\160\\\142\140T\172\004\153\136\170\238\n\230z*\149\244\027]\193Y\190\026\227:G\021\019\171A\011R\\P+\148\234F!A\189P\221\128D\137hd\160\192($\b\n\1417\225\002\004\n2\154-\165\150\209H\208j\169nC\011$\218\133\138\014\161\162S\168\238\242\140\"\209\141#\209\131#\209\139#\029B\162T\244\225\020L\253\174\154f[\200\220A\014\133\214\000\203\020\030\141\000\017\011\1539\192\128A\011\209\208h\004\024\182\208\194\017K\012r\242hFU\185\168\151\177\199\224\211\227\169w'\240\251\019\237$B\142\136N:\200\154r\016Mo\014\185\1741\215\206\197<;\215\204\007\247\128\005\222\129\022:\136\0229H-\190\134\231a\137\157\135\165v\030\150\217yX\238\001\173p\016\173t\144Z\229\135\231c\181\157\1435v>\214\218\249X\231\001\173w\016mpPy\163\229\026\239\253m$\202L\188F`\244\254\155u\154DMK\139\223\028e\247Gq}\237\188{\246mX\001\001\154\153I\004b\020eD\173;\152\005\152W\0008\025 F\177a\012\006\251\133\230\027\r\128&b\128\175\019\154\136\003\163\030\006\136 \226\019\133l\017\187\182BF\187j\026\149\149\156\015\171hQ\200S\146\237\014\2306\019T)ja\n_,\188\151l\169X\"u\184n\204\012\220\030\183\139p[tB\016\228\\\228\160\140/\196\216\000A\222\024w\182\205\003\251L\"3\140\139\",\128\224l\128\148\133\025\191\211\254\254\205o\141\177\219^\130\178\149g\248E \154\136\222\150`\128*\024\156\016H1\219\194l\134Sj\154\019\197\021\004qr\130 \197\\T\127*\138X\029\215\183Vf\220\199Y_\030K\232y\006\215\151\230\243\181\025\198\020\208\228\131Qy@\002\001r\162A\030\252B\b-BAM(@X\006^\157n\012 \215\149\210_gW\170\201\214\132u_\174f\011x\161K\003\209\011\182|\178J\007-\213\242y*\252w?4\187\192\159\247s?\159\203\153\139^\235S\127*r\2369\183\198>?\t\142\168\171H=\005S\127c\2305*\158@\202\185#8->\156^L78\141\127\159\155e\156\027Jg\2299R+^Z\227fX\164\130_fiM\136el\174_\235\015[Z?O\198+\005\198\160\004g\206\201;\151\218mSm\187\254\218\136\143\016\130=\129\209\197\238\187G\171(\031{k\187\178rII\178\174]\195Z\241$E\204E.\250iw\137\222\163\134\028\023\248\204L\031\251\248\245\137X\007\193\209\199\153\133\146/\252\218\199w\152t.\218\207d\146\225\180\183h\154\164\017\178}\220\246\234\168qv\204\216\239\023n\184\020^h\189\176M,3\244Ul\248\255\177\143\175\236\240O\253\177\159\227\180\024,\222@\2345(W2kk\012)\242B\144\167\220\197\173\240\195r\2097H\185\001\242m\156\190j\229W\251\024\133\165e\215\016\006\026\190\175[r\193\250\239\011!\030xA>\129\223\175\204\028\214T\159\169\146b\241e\236\191\195\133\168\223\217\198.\236?\233\164\225=Gj\214'\249\160\170\232]\132\195S\222\240{d\164\137~&'\213\028H\239\143\028\188\1678\171\136W\144\234c/_fM\164\218[\192\179\214\t\169\217^o\211LM\"_\151M\239\134\234\171@\016\173\173\251\\\017\144\004EX|\186j\197\166\251z\254+\127\200\253\238\219\222\207\156C*\200\243@\183Y\220\242\005\238c\159d\175\227\244\213\222\198\251tRR\029S\144\166\1287^o\017\205\159%\145=\248\028\169\017\206\173wQ\221m\190\127[R\006\168\146\192r\005%B\tW0x\249\146\149`\012\183\\\136\02785\004\148\231\147&m\218\004\214H\245q\155\183)\203\225\150-\242\252yf\199r\212\012,\214Y\162\147\151\003voz\236\173\250\129\154\225\174\223\028}\255VwY\164\134Q\200\003\131\210/&\136\131\252L\240P\158\143\220A\249?\254\240_\224\031\164\190\234c->\236m\237\209\007\211\242\179A\021\136\242\145\151\016kW>\003\161\181\240Z\028=\221\190\244\024\000&\235\194\202\"\167d\169\212\142\247v\226\222\143\027a\202L\164\241'\160\b\1958\150s\220A\183_-zgR\216\145\218\2487\177Otry\216A\177/]\250\254T\015e\244\214i\023\169\155\192\159\180\b_\140\233\168\205\254\206\130\191\207\198\179<\000\233\188\227W\129\024\166\145\250\t! \170u\016\212!D\254\015\235\029\178\151\160|\157g\024C\153t\172\182k\215\189\253\131\238\131\222\1923\170\016~\030o\t\128\2340]\218\253R\031(\253('}\239\223\"8\133ZjCC\014g\204\t\244\006\015$\245\007\247\254M\237v\221\253\225\007\174{\027\156/\223H\n\224\196s/\254\241\154z\198+\163\158\003,}\156=!\016`\199|\244\254\147\017\bCl\184O\150\230\255\2395\205\159\031\220\007UWuJ\030\245\250\027Z\163d#.\189\249\148\225\131u\192b}\225\186\001\204\2277\\\240\211\168*Nl\212Q\175\191Mp\191\231\241[\1803[\003DT\184\190\152\252\127\012\180\251\128@p\253Z^\202\004\205\129\231\225\167\132\146aM\227\128s\135[\149\177c\192\169i\028.M\128\031\245\153p \023C\242\2026\207\185\211c\145\148\252\149\212\246}\1630b@\030n*\211\163\219D#\141e\238\238\195\130\230J\168\183\244\029'oiO\211\248\189\015p8\219>y\245TYQ\252\144a\195u\214\b\231\129{q\250\180\246\022\137?\001Op\227\030\222:\189t\000\240\149[\213g\164\146\1553*_\235\224(;\241(\185-i\021\229[v\148F\156s-\159\006x\135\234\143t\133\229k\252&\030\t\019\212\174o\205\171W\127\168\181\235\0207\187r\255\183.\248'P\140K\255\193\195\200\1910v\229\224DB\225J\145\224\251x\214\181\168\161\167\243\147@\224\218\019\189\202\226\190\207\019\157\236KM\020F\174\1843\028VC\174\015\006\197.^\187\174\228\188\200\019\015\194\173;o\220\016\222\184\137^?\024" let d_b9d119cedb5c92b84ce5ee8095fa698a = "\253\213@\237\250\152t2\150\222n\228\205y\1343\197Q\186N7(Q\028p\149\212O\029\255Py4\234%Ku\230\182\232\250a>C\203<\213\001\184\030v\185u\210U\028*nK\150\227\239\160\255%\006\215\137X\b\143\015O\004\171\202\021\022\178\242\176\128\017\240a`?k\127\190iv\147\030t\157\031\174\\\175\000/\253a\214\132\141\220\197\229\0197R#\157\242-\226|\135\018\020\219\135#G\156H\162Rr>\249\249\014\139\031\020\232\149,\184t\226A{-KL\131\156\1879\211\"\161\b\164N\004\145\199\152\241\187XJ<\201\128\202\206\002#G-\177P\227\215\152\250q9'\235I)\165_,\211\242\249\210:\226\206Kd\139\194#|\237P(\172je`a\000&C\186\150\200\012\1302\172?\012\246\168\237\141\133gu\028\227\171\192%\138\020\130?\208\170-\017N\t\246\162\209\227\134$\248\155\192\212`3\229\246\215\150\156\253Cv\139~\1770%\2013\0000\021F\161\143\192N\207\025\216\247+\146\2442\176gY\000\018Vt\159\186\164\1996\243\160\148RkZ\022t%\135\163\024n\180\169p\141\184\2492?\165\025`b\129\243(\1968\214\233\244\024%\016\202Q\187\214;\192O\158\023\2390-2L\1336c\158^\206\1961:Q\229\1888\189I\001\135\206(\208\167\146\176\145\172g\227\212\020%.{\228\210\248y\185m\029t&\129\137e\001\211\147\211_\165K\192\129\2294(\012/B:\243\236W\209\138\173\018rODmwE\028\165\216k*qx\134\147\018*se\236$\006\248\205\005\253\027q\004(\159\n\143Af\208pM\153\231\147\023\026\183\166\021\240y\160\220P\239\223\012\179\172\130\133\003\197\r\174\152\179\231\2447mb\030K\253\204\027p\2502`m|\173\029k\028)J\2405\028Z\163\135\209\208\188+s\204\185\156\212\174\230y\137\228\171TRS\000#\137(z8\235E\023\026z\1964\193fs\228ay\140\1656%@y\223\221\146\237\137\174b\001\188\236\027\003\2155\216\169\251\215\152n\017\194\224\2107\t\182gJ\006\247F5\176|\195k\005MV\230C\023\175@K\031\017pE\200\241\173\147P\166Ef\192T\173\179\145\143\186s\195\027\225\006\186\027\151\172\011Y\0291\173\172\227M\203\252)\135\250\017\144\225\246\151\232\t\2366C\144ZceF\251d\ru\027\167\181\2418er\141\185\"my\139\179\\\205\229\172\174\172F\231\244\129^\001\225\156\202\175\226\160\217\007\014\015\133\2500\232\0035\206\143\155\221m\134\204\185\153\182\158\153\226.D\1852Y%\019\245Oi\137 \029]1\012\132\167\235\198=\1760.\188\025&~\218.Q\021\254\004\162s\131\216\189t|?\254\231*!\021\216\182(\202{\241\006\184\156\157\004\138\161P\238\206\246$\133\154\002\167m5\159\129\137\128\178k\179\222\b\229p\156W9\236\196S\012\211\254h/S\166\212\026\197\210\249\152\152+A\255\245x\216\252\011\141\156`\175\172Kc$\211\176\207\t\214\151\r\231g\194\002p\180\145\226\248\236)$3>E\000\000\251\154O\209\127H\192a\180\142\242\235\004\176L)\004b\130\r2\131\230\146,\203\192\214\166\228\135\213\193\021\0301/\136\015\194\140\023>\0148\214r\230z^\131Rh\183\165\180-\239y\186\233\000\246\133)\221\1411\197\208b%c\152\171\241)V\020\250\144\019\152\141\190l\004\190)\004\b\188\187my\171\173e\214\196K\214\137?&/\149\219m\016sf#9\1514\142/(N\246s\021\023\129\163\171\230]\206\020\145\229hh\018N\210\1903\237\208T\182\183\2082\223\162\n\195\175R\160J\191\208\177\132\1475o\196\029\221]\173Q\000{O\196]:\135\n\231\157\026\b\203\169\254\181`\165^6\221\185suz\">\240,\228Y|\150\240\134N!\215\166\234\014\247Lq-\253\231\147\"\249E\254K\023\027\182\138\211j\211\252\138\214\150\2244\141G\151t\179\164\025&YCT\218\187\194\240\"\021\216\245\018\233b`]\168\001\203\204u\252\240\194\233<\130|\207\235\1788\178 +\201V2\140J\134\019:\148\004\241\020\135\142\159t\235k\181\252\240\254\163\245j<\160\173&\129\150\239\t\176\169\210p\231\194:\235\214\025\159\133N\24480\167f\156\221\208\253\190\247\253\220T1ln\164K\239'0\154\189\222r\245\152\182\220\145HY\140\014\157\154SC\179\001\140(1\237\128\194K3V1\181=\\6\rZ\2436\189\bT\192\179 \133\157\183\004sZj\147\139\021\017Jd\006\133\129X\199\219\026\rJ$:$\186_\173\174\249\190\135j\184M\t\235\213\014\153}\192\005\016\030[\181\012\137K\209Q\234\210\172f^<=\201\002?D+\188\206-\233tAz\001\185\229\137[\1578k\174\002fb.P\025\158\023\022\012\132\165=\213\157U\003\139\021,\132\154\211\178[1\177\155\214L+\154\135\190\233vGS6\142@\163\173Z\139\1808&K\027\187%\209\018&\134\226~\162\024\239\244\014]5v\026\182\156\185\161\215\175\207\232 \234\2074\145\158\018\n\223\148?4Eg\002\182ic\140\241\011\024\187PkD\n\219e\144\215PH-\177\158+\215\152\249\004\169j\176\030b\196=\r|\153\030\182\192I\210\250\019rj\199P\202qav\138\142]\209&0x7\179[\199\213\227\178{\168:\230\153\165+\175\\B\163\148\151\231y\158\209\253\207$\248\207(\192D2\000\011\0214\217\004\203yx\028'1\208\167\164\231D6j\248>\173\248\176\145\255\199\136^\r\027T\183\246b\138\211~\219}u\245j\197fR,\2427\022\188\202\156\140I\236y?\190\015\236r\130Mq\255dO\144\t\004f-\167p$\229\218\020-\222\202@F@`Q,\207\023\2309V\185\194\139\169\132\252$Z\185\244\157P\012!\133)\252\248\020\242\228\187\206\230.\130\174H\133\255l\030@\230\173\024!\b\n.F\018\168\r,Z\210z\2296\231\022\t`\151(\129eV\017K\144[\255\180\021\171\195\1359\000j\150\221\1938\230\246\018\214\155e\183\025\199{\r\023\174D@\024\189_\230F\196\211\175J\\8\200\225\219\248:}\"\143P\140\202\214\031\194\133\026.Z\"\145\152\209+\149SR\2115\220\175\192\171\204\213\158\198~\217\208\160!%\022\128\177,f\235y\186e\234\162\213\247*\224ys\163u\2310\166\0158\130\243\247xnf\178\007\142\239\180\186\248\159\b\240\205\157O\029|\243\165\206\190\031\023\223\026T\192Js\132\181\234KX\219\130\211\240\236\019~\149\141n\019]\177\210\012\214\237|\030-I\189\211$\138[\187Y\"\139\168tE\231\202 ?\163\229\018\195Xf\n\023\169\\\191\190eS{\153\155\\\023\251\225M\184\246\012\219w6\204\171$\214\233\139\2320\252\157$\029\163\190J\159\135\027\187\172\135\226P\183K7\152\231\147\1615\127\208\172Fw\146}\224\002B1b\136\019\207\189F&\220\153\144\165\203oR\128\234\156\030\208\005\229H\217\016\183\178\226\027\142\225\213\b\000\255\207\194\222\243^L\020EIG\241i^:\216\146\153\211\242\154F0\179\185)\171\135?\197\210\194f\"\131\131~-G\011\205S\244\231\219&\197t\017dlRTR\228\138\183HW\2451\017$\154\226\134\144\150\129\247\027\220\248\202R\002\182w\212)\"g(\253z\154\196`k\017\132\027\213\018\018\240\150\253.\152\230\175\020\022\191yh\024\132\160H\206i\205c\135F\192\152@\138J\r\172_k\245'\129\227\166\205U\174\189&\026\160\221%:!o\2274\245f5tA\017\148o\\z<&\"\243\233\194\231\253\229\174\\S\195\221o\222,>0my.\223^\246\189e\240\140\195\147\1476CI\223p\135X\137\182s\253\203\169C\135\202\251>'l\160S\163\210(&\251\027\012p)T\231\155e\143\152;\224\004\140q\211v\148\245\235)\002\014\223\219MnRH\183<\185\252\155\014\248\203NWa\181\030\211\206A\243\020\133Y{|\209\005\226U\225\218\129\031\139\020}I\166\215\024r\150GS\232v\194\169\250\229R\137\251\002\236PA\230I\029\228D\019s\129j\143\144\159\186\245\216\160\147\162{\195\233\201\195\146\156T\2394\216\154\135G\016.F\156}j\028g\147\187Z\178\011\186\179\016\185\190\135\020\001\141y\175\138@\158$\027\253,\241UZ\130\238@\145\238\186\158\203\140\150\206\014|\201q\242~\207\177P4\200\001?\232?\171N\201nI\154vN;\161\007\241{#\243\151\r\212\012\215\t\023\202\197\244x\154\22328\180\236\160\238\137b\199\216\197q.C@\148\203\137\234\219\143\220\174&\228\229\132\128\193\029\199\226\019(\139\137\184@\026\151\173,7\157a\225\133\228\213+^/\189\139D\137\217\002j\0164\204\007R\193l\002\149\028\214y\139\247\236\006\015\004\144\031\0071\211N\011:\149\153\007\020\170\183\0076xO\244s\255J{2\002\227+Sv--\1575\235Q\232:w\249\128v7I\208kX,\205~\177$I\191\246\186\174\187\144\160\130\174\193P\218\251\195\247\144\209\027\151\252a\181\177\000\177\149T\160'\022\193\014C\127\168_O\148\190\219\031\168\168\158\229h;\175\166\239~\248\212\169/\235\196K\135rC'\127\158k\241\215\143Wp\252L\174\241a\179\241\239z\235\011P \000\165\2333\221\249\225\236QO\229\188+\155~\2015\211=b\176\246'\226\244v\214\168%\151e\181\163\031^\221\233!\217\130\181~\007\189f\221Z:i\018I)Ob3\173G\024\140\235\168B\1514\146\215^0g\210S\142):\211\188\198\156\169;\"\019\205\225\139\154\129\177k<\244\127x\199\211\177\186\185\016\246\202\235\002\133\144\016/\142\197\230\240\127\"M$2\006z\212\129\210\238\220'\"\225\222\169\225\161\214Wo{u\253\006?\171\148\144\158\248\208/\210\175w69\202W\220\169\239<'\206\173\031X\178F(\173\016=\211V\239\135@\192\020Q\212\197\171\149\239\160S\137B\134\139k\011f\t[\225~\0011\215f\237<\190\175\175:\152\142\189\023)\031\025\172\184\181\205\215\024\237\221\192%\138\127\bf$4.o\1582\147u#\224\1515\189~\169/\144\154\247\171!p}`\004\138\245c\007_a\2331\130\t\166\192Z\252\170JD\144\137\182D\187\167\130=\225\2259\165A\175T\230\r\163R\198\003\141\155\158\246\134\197\140\217[\161\192\200\134\1683$&\2325,\134\225[2\243\001\\\018\014\160\135\202)G\220^p{z\205\241\209\027\012\024G;\230\166\162\201x\238Bx\216[\220\158\223\181~\206\156\172W\"xU\147\223\002\014\023~@\007\\\005\173@U\197U\127u\239\185H\230\159\245\201\225\135K\202m\185,\243\134=Q\243\031\235\166v\177\246]*\241Vz9\1997\2076\023\165\022\1451\184\006\007\145\007\230\152\148\029\151\238+#\1586\148\249\021\233\224wj\215\030\179\017\223\029\168\221\020\170h*\245k\242\188yj\211\166_\250\172\230\192\157\1419\236\138J\182\228\225\253J\241\198\163\247\217A\182\173\172\200\138\249\197\"b\194=$T\146D\024\188\152\247r\129\190\255\029\t[\188\t\182y\237\222\003\217\151\152e\174E\132\168\029\152\140]\128\148\018\228\196\006\022\232\228\170\184\128)\152\201\128\161r3\227\011|h5G<\017\234\134\028\021\n?\184\245s\b\243\207m\17689,\004\129\001HM\212\173\234\131\006\176\131%\204\1764D\192M\254\238,FY}7\253\2455\232\199\223\026\249,\227w\182\134%\026dH\011\163CH\"\206\143\183YMp\134\127uM3s\252\2067\135\139hF\253\127LW\127[p\162\011\234V\143i\198\224\186\020t\176\00574\029p)\195\135}\179\161Y\2185\2185\016\220\211\003M{\003\021{\180\028\222\179b[g\171\224\240\141+\218Z\004{\te\148A\"\227\132\1967$&1B\016\2426,\029W\236k\237\216\167\2403\149\131\133\168(t\240\221\182\1586\182\237\224hK\23575\011\172\1864\198\176P\137m\203;e\151\242{\246\134j,u\141\217-\158\145O\183\161\246<\237\143n\141\207d-\031\224ubZ\t*|\248\229\015v\202\190\250\2362t\211\130\191\142m\015\133*\130!\206`\nJ\132\165\017)\156\215W\027cw\223r\165D\225\155\143\239\196\014\249\193\006\003\004\219\236\186#\\\2302\145~$\241.\151I}jl\162\164\209|\177ERp\185\177\179\029j.\205\255\000\006&-:\176{W\217n\146\152*d\248\217\250(%\186\198ae\181\224\234\209\195x\214Q\235\211G\225X\211\151\181\0244f\2372V\137z&9T\163\t\176\n\214\\\190L\174\2382\236\140iT\247\004\190\247W\173'*\162\252\158v(\137 \1541\245\152\225\250\175\207\226Q\199n1A\175e\161>\134\216=\132K\163\158\220Y\"\165\251\1803\161Y4K\224++\133" @@ -338,6 +338,8 @@ module Internal = struct let d_c0cf7351fa27f73a72840e453c4b15f3 = "6,0,0,.76042],8911:[0,.54986,0,0,.76042],8912:[.03517,.54986,0,0,.77778],8913:[.03517,.54986,0,0,.77778],8914:[0,.54986,0,0,.66667],8915:[0,.54986,0,0,.66667],8916:[0,.69224,0,0,.66667],8918:[.0391,.5391,0,0,.77778],8919:[.0391,.5391,0,0,.77778],8920:[.03517,.54986,0,0,1.33334],8921:[.03517,.54986,0,0,1.33334],8922:[.38569,.88569,0,0,.77778],8923:[.38569,.88569,0,0,.77778],8926:[.13667,.63667,0,0,.77778],8927:[.13667,.63667,0,0,.77778],8928:[.30274,.79383,0,0,.77778],8929:[.30274,.79383,0,0,.77778],8934:[.23222,.74111,0,0,.77778],8935:[.23222,.74111,0,0,.77778],8936:[.23222,.74111,0,0,.77778],8937:[.23222,.74111,0,0,.77778],8938:[.20576,.70576,0,0,.77778],8939:[.20576,.70576,0,0,.77778],8940:[.30274,.79383,0,0,.77778],8941:[.30274,.79383,0,0,.77778],8994:[.19444,.69224,0,0,.77778],8995:[.19444,.69224,0,0,.77778],9416:[.15559,.69224,0,0,.90222],9484:[0,.69224,0,0,.5],9488:[0,.69224,0,0,.5],9492:[0,.37788,0,0,.5],9496:[0,.37788,0,0,.5],9585:[.19444,.68889,0,0,.88889],9586:[.19444,.74111,0,0,.88889],9632:[0,.675,0,0,.77778],9633:[0,.675,0,0,.77778],9650:[0,.54986,0,0,.72222],9651:[0,.54986,0,0,.72222],9654:[.03517,.54986,0,0,.77778],9660:[0,.54986,0,0,.72222],9661:[0,.54986,0,0,.72222],9664:[.03517,.54986,0,0,.77778],9674:[.11111,.69224,0,0,.66667],9733:[.19444,.69224,0,0,.94445],10003:[0,.69224,0,0,.83334],10016:[0,.69224,0,0,.83334],10731:[.11111,.69224,0,0,.66667],10846:[.19444,.75583,0,0,.61111],10877:[.13667,.63667,0,0,.77778],10878:[.13667,.63667,0,0,.77778],10885:[.25583,.75583,0,0,.77778],10886:[.25583,.75583,0,0,.77778],10887:[.13597,.63597,0,0,.77778],10888:[.13597,.63597,0,0,.77778],10889:[.26167,.75726,0,0,.77778],10890:[.26167,.75726,0,0,.77778],10891:[.48256,.98256,0,0,.77778],10892:[.48256,.98256,0,0,.77778],10901:[.13667,.63667,0,0,.77778],10902:[.13667,.63667,0,0,.77778],10933:[.25142,.75726,0,0,.77778],10934:[.25142,.75726,0,0,.77778],10935:[.26167,.75726,0,0,.77778],10936:[.26167,.75726,0,0,.77778],10937:[.26167,.75726,0,0,.77778],10938:[.26167,.75726,0,0,.77778],10949:[.25583,.75583,0,0,.77778],10950:[.25583,.75583,0,0,.77778],10955:[.28481,.79383,0,0,.77778],10956:[.28481,.79383,0,0,.77778],57350:[.08167,.58167,0,0,.22222],57351:[.08167,.58167,0,0,.38889],57352:[.08167,.58167,0,0,.77778],57353:[0,.43056,.04028,0,.66667],57356:[.25142,.75726,0,0,.77778],57357:[.25142,.75726,0,0,.77778],57358:[.41951,.91951,0,0,.77778],57359:[.30274,.79383,0,0,.77778],57360:[.30274,.79383,0,0,.77778],57361:[.41951,.91951,0,0,.77778],57366:[.25142,.75726,0,0,.77778],57367:[.25142,.75726,0,0,.77778],57368:[.25142,.75726,0,0,.77778],57369:[.25142,.75726,0,0,.77778],57370:[.13597,.63597,0,0,.77778],57371:[.13597,.63597,0,0,.77778]},\"Caligraphic-Regular\":{32:[0,0,0,0,.25],65:[0,.68333,0,.19445,.79847],66:[0,.68333,.03041,.13889,.65681],67:[0,.68333,.05834,.13889,.52653],68:[0,.68333,.02778,.08334,.77139],69:[0,.68333,.08944,.11111,.52778],70:[0,.68333,.09931,.11111,.71875],71:[.09722,.68333,.0593,.11111,.59487],72:[0,.68333,.00965,.11111,.84452],73:[0,.68333,.07382,0,.54452],74:[.09722,.68333,.18472,.16667,.67778],75:[0,.68333,.01445,.05556,.76195],76:[0,.68333,0,.13889,.68972],77:[0,.68333,0,.13889,1.2009],78:[0,.68333,.14736,.08334,.82049],79:[0,.68333,.02778,.11111,.79611],80:[0,.68333,.08222,.08334,.69556],81:[.09722,.68333,0,.11111,.81667],82:[0,.68333,0,.08334,.8475],83:[0,.68333,.075,.13889,.60556],84:[0,.68333,.25417,0,.54464],85:[0,.68333,.09931,.08334,.62583],86:[0,.68333,.08222,0,.61278],87:[0,.68333,.08222,.08334,.98778],88:[0,.68333,.14643,.13889,.7133],89:[.09722,.68333,.08222,.08334,.66834],90:[0,.68333,.07944,.13889,.72473],160:[0,0,0,0,.25]},\"Fraktur-Regular\":{32:[0,0,0,0,.25],33:[0,.69141,0,0,.29574],34:[0,.69141,0,0,.21471],38:[0,.69141,0,0,.73786],39:[0,.69141,0,0,.21201],40:[.24982,.74947,0,0,.38865],41:[.24982,.74947,0,0,.38865],42:[0,.62119,0,0,.27764],43:[.08319,.58283,0,0,.75623],44:[0,.10803,0,0,.27764],45:[.08319,.58283,0,0,.75623],46:[0,.10803,0,0,.27764],47:[.24982,.74947,0,0,.50181],48:[0,.47534,0,0,.50181],49:[0,.47534,0,0,.50181],50:[0,.47534,0,0,.50181],51:[.18906,.47534,0,0,.50181],52:[.18906," + let d_c3421d028da161fbb9179ce80677e91f = "}\n\n/* Collapsible inlined include and module */\n\n.odoc-include details {\n position: relative;\n}\n\n.odoc-include.shadowed-include {\n display: none;\n}\n\n.odoc-include details:after {\n z-index: -100;\n display: block;\n content: \" \";\n position: absolute;\n border-radius: 0 1ex 1ex 0;\n right: -20px;\n top: 1px;\n bottom: 1px;\n width: 15px;\n background: var(--spec-details-after-background, rgba(0, 4, 15, 0.05));\n box-shadow: 0 0px 0 1px var(--spec-details-after-shadow, rgba(204, 204, 204, 0.53));\n}\n\n.odoc-include summary {\n position: relative;\n margin-bottom: 1em;\n cursor: pointer;\n outline: none;\n}\n\n.odoc-include summary:hover {\n background-color: var(--spec-summary-hover-background);\n}\n\n/* FIXME: Does not work in Firefox. */\n.odoc-include summary::-webkit-details-marker {\n color: #888;\n transform: scaleX(-1);\n position: absolute;\n top: calc(50% - 5px);\n height: 11px;\n right: -29px;\n}\n\n/* Records and variants FIXME */\n\ndiv.def table {\n text-indent: 0em;\n padding: 0;\n margin-left: -2ex;\n}\n\ntd.def {\n padding-left: 2ex;\n}\n\ntd.def-doc *:first-child {\n margin-top: 0em;\n}\n\n/* Lists of @tags */\n\n.at-tags { list-style-type: none; margin-left: -3ex; }\n.at-tags li { padding-left: 3ex; text-indent: -3ex; }\n.at-tags .at-tag { text-transform: capitalize }\n\n/* Alert emoji */\n\n.alert::before, .deprecated::before {\n content: '\226\154\160\239\184\143 ';\n}\n\n/* Lists of modules */\n\n.modules { list-style-type: none; margin-left: -3ex; }\n.modules li { padding-left: 3ex; text-indent: -3ex; margin-top: 5px }\n.modules .synopsis { padding-left: 1ch; }\n\n/* Odig package index */\n\n.packages { list-style-type: none; margin-left: -3ex; }\n.packages li { padding-left: 3ex; text-indent: -3ex }\n.packages li a.anchor { padding-right: 0.5ch; padding-left: 3ch; }\n.packages .version { font-size: 10px; color: var(--by-name-version-color); }\n.packages .synopsis { padding-left: 1ch }\n\n.by-name nav a {\n text-transform: uppercase;\n font-size: 18px;\n margin-right: 1ex;\n color: var(--by-name-nav-link-color,);\n display: inline-block;\n}\n\n.by-tag nav a {\n margin-right: 1ex;\n color: var(--by-name-nav-link-color);\n display: inline-block;\n}\n\n.by-tag ol { list-style-type: none; }\n.by-tag ol.tags li { margin-left: 1ch; display: inline-block }\n.by-tag td:first-child { text-transform: uppercase; }\n\n/* Odig package page */\n\n.package nav {\n display: inline;\n font-size: 14px;\n font-weight: normal;\n}\n\n.package .version {\n font-size: 14px;\n}\n\n.package.info {\n margin: 0;\n}\n\n.package.info td:first-child {\n font-style: italic;\n padding-right: 2ex;\n}\n\n.package.info ul {\n list-style-type: none;\n display: inline;\n margin: 0;\n}\n\n.package.info li {\n display: inline-block;\n margin: 0;\n margin-right: 1ex;\n}\n\n#info-authors li, #info-maintainers li {\n display: block;\n}\n\n/* Sidebar and TOC */\n\n.odoc-toc:before {\n display: block;\n content: \"Contents\";\n text-transform: uppercase;\n font-size: 1em;\n margin: 1.414em 0 0.5em;\n font-weight: 500;\n color: var(--toc-before-color);\n line-height: 1.2;\n}\n\n.odoc-sidebar {\n position: fixed;\n top: 0px;\n bottom: 0px;\n left: 0px;\n max-width: 30ex;\n min-width: 26ex;\n width: 20%;\n background: var(--toc-background);\n overflow: auto;\n color: var(--toc-color);\n padding-left: 2ex;\n padding-right: 2ex;\n}\n\n.odoc-sidebar ul li a {\n font-family: \"Fira Sans\", sans-serif;\n font-size: 0.95em;\n color: var(--color);\n font-weight: 400;\n line-height: 1.6em;\n display: block;\n}\n\n.odoc-sidebar ul li a:hover {\n box-shadow: none;\n text-decoration: underline;\n}\n\n.odoc-search {\n position: relative;\n}\n\n\n.odoc-search:not(:focus-within) .search-result {\n display : none;\n}\n\n.odoc-search .search-result:empty {\n display : none;\n}\n\n.odoc-search .search-result {\n position: absolute;\n background: var(--toc-background);\n overflow: scroll;\n left: 0;\n right: 0;\n max-height: 40rem;\n border:solid;\n border-color: var(--pre-border-color);\n border-color: var(--pre-border-color);\n border-width: 1px;\n padding-left: 0.5rem;\n padding-right: 0.5rem;\n border-radius: 2px;\n box-shadow: 5px 5px 5px var(--toc-background);\n}\n\n.search-bar {\n w" + let d_c476e59e9197afb4d57b64eef2d37d5b = "\141\252\198\162\016\159.4C\182\212\2253<\203s\023S\198c_\255\222\161>\240\178\162]\244\244\n\195hw\187\165\142\230!\005\222\154\182\133W\235\227\214\195\181\141\243F\2198\239@\206\232\163\1593\164\220\187\227]<{\216.\143w\149\171z;\028\195\187\014\174\241\137v2i^\182\201\b\157\246\239\171\183g\185=V\128\1913\242\127y\179\131{\211\014\201y/\227/\163lk$\017\225\149\250\240&$w\185\232F\192\001\192\191\222\250\191>vF\255\173\250\164\253\255}3\229\159\244?\000y\247\240\020\165/gjC\241\161=~\214\031}M\166\153\240\143\235u_T\226C\210\135\240\212dl?g\160>\006\001\200\135\194\186\250`\145~\220\240\203\185\216\231r\253z6I\016\202\025\b\130\252\"I\150$w\000\1449\188C2\1854ItMgoH\206\\\154\131\016\192\243y\028\249\016\228)\222\140\243\029\136\234t\247g.\205\141sq\180\183\173\144\156\1854\251\161\143\235%\128\250$\1625\236[^\223\151\232~x\234\n\000\240\176J\nY|>\175D\011\155N\249\163\212\213\255\228\237\246Z\000t\196\\\211?:\158\158\242\tEu\016\004\138\169OP`\012\206\1360j\144\127\203\217\001|\253\003 k\002\219\189\159;A\001\154\149\200*}A\000y\",\005*\223\245\193\166\169\150\219\025Yk\248$@\0010\0162ut4\154\234U\242\200\144\136\027\226\"dD\n\018l\004\147\168-\245\007\002!\016\004q\0061\234z=\136\134h,&\136=\246\142\030l\006j\217\001\164\189\237\024#1\247\174\192\142\219\134X\019F+\030\000C\140\147\157\219'\202H)\200xc\243`\024~\127\232~xp\153t$\175\143\241\184\188t\141\222\180^\195)\191\171\t\225\164\233\244R,\168k<\196\185\204\205\243\028\233\130\234OF\017\254K\134\192\172\019\254\238\174\201\158A\154?\228\181\000\026\003c-\":\002:\245f'6\213\202\023O\183\136:\166\133\210\004\195\179I\140\188S\023\169\183\170\165\220Q\029\242\182\165W,:\134\236\150\196\198\216b\2280\221\205\017\215=\235\162o\186XK;V\1434@N\148\160\169(\000\007\249T\189\228N\022\180\138Die5z\173\169_e\131n\0273vdM\028\188\157b\226\239Z\014Y$\174\132\014,\198\142\tw\240AR7\234\248\147\205\166_z\167KJ\147\245\2331\215\174v\007\128\018\137\018\147%!\160k%]\169\238#fHi\135\167\027\157\233\223g\204\150\171:\133M\213\164\024\181\253\218Uya\194\170\018R\149\131\t\215\029XFK\196\174\\\226\212\210q\214j\216io\016\194\166\249Bh[\142\003H\004(\012LK8#uT\137\132\215\029\0221\157\168]\147P\219p\011n\156\003'\201Q\181t\180\215\180\238\2254\006\031\026m\228\208a\218fI\150<\011S[v@\197\132L\201z\153/\188\017?\176-\003#Li\161b\135'\144\b\154I\\\128\161\221D6\203\177\020\146\017^\b\011\t\rXFU(\019\195\151[\224v\206\135\005\030LC\234A\226 \249^I\003%\007a\021\250V\160\200\150\211\137\189$ht\200\n\164\177\t\156\136\026\193\165\n\255\142*#\198\208A\132\134R\020\163\241\003y=\006\192\161\\Y\144a*y\247{\019\\P]\237\170E\231X\200(95\1357T\201\151\186\215\213'\161A\014\215K\243\188|\246Uo\164\017Dc\201\232\219\254\163\170\233\255\230M\239\160\186\169UR \027$gP\252\179\155\239\211\245\003\247\022\127B\190s\137\n\241u\239&\187Z!\137\207\134\011\187\222\139\252\141T\133B\176\224\193\159|@\217\248\026\028\031h\186k\235B\173\231.\023\174zgl\215kV\026\030\176cG\131\137\1337\172\236}\2094.\2187\004K\001\179\195z\218pN&\163\220X\168\2394\201Vz\022\189\t\189\185\165\147\189\218\151X\027\2270\143~\160\165Y\155M^\227\159\161\014#d\1813\173\247O\179qN\231+3\220\029\133\136\237\250\178\243\236\027\139\200\139\127\133\159\136m\190\167\169\196\131\022\249\247\248\204\202\250$7\146%\1652\207P\003?\208\017\170@k\nQO\1821\162J\196\166\150\188WQ\029!\006\223\129u\029\146Y\212~\2432\247*,\2140Rtxj\020\173\143\150g\2374\221\191\155@\007\196\181\2207\004\026\250\014\200R)\005\172\151\174\245\006MO\201\228\142P\021^\139\245;\172\187\be\2512j\172jU\022\to\180E\191\234X\129\237\136\244j\210!Z\136\220uVL\166z4\bs\240\161\250}\190|\030\211\180\208r/\021#\225\205\220fWu\169\216\187Z\242%\210\139V\021g\216#&\148\140\175QJ\011^\223R\144\180m\001L\219\b'\193\246Q\189\020\012{\179\187\163y\189qEFU\155)3\243QI\176\131\223\1711d\022\004\201p\t\171\218\213H\"\152_\226\030{\184\215\213\167\187\144\212;w{\011 \164o1\018\000\162\029C\003)\165\182\024\226\208\r\017\179\146@\233\148\151\r\234\177\001{\196\162`\165Z\004\150JT\205\246\162\231zo\206\190\012\2032\242\171\205\196m/\031\187C\191\206\183\213\000|\241\168\136jV6Z\252q\191%\155\177\198\191*\171\129!\228\229\177!\189Q\163\145\146\165\130\003\202\"\241\231\140\215\0275P\181\143\141\171\143)b$P\022\2522!\169iAF\147\248\129\1676\020\153QU\137\181sm\028\006\170DR\011\011\227\160\140k\145Ol?\016\175\151\180M\183\027\168O\"\t\244?{ul\135\146\205\026/\176y(\140?\217\017hW\197\\\146\164\023\014\177IY(%3\251=]\200#\028N\028\136\166\163_\1530\024Q\240ZH\219\169\211w\149\159w\t\130W\241\207\197$\195\232\209\199hQ\162\027\002\020\203\011\134\242\245\003q\240z=\2155\194]\177bB\228*W\153\156$\n\229\244\"\006\255Ttf\250\212T!\197\243\212\155\025\176\019\190\216\128\232y\182?\200\185\254\140\203\182\002U\169\020.\026\206\244\171\173u\n\1570\1804{\1773i\182\204\184T\b\004\215c\211\194x\147\236$\020\185[\136nD\167\229\220\017VQ\163E\219\170\183\166Z\031\242\243\223\229\006\212\234\196\020{\149\218\236\198\165#m*0\rj\177A\202*\127\221C!!\017j\1385g^l,L\151\220\201\146\139^\152c\159\196\251V#\243uS\188\173\164\027eqW5\016\142\135\237h\242r\003\191\241[P\019E\\\145|\154nyl\192-I\206\172\247\188\142l\003n\132\r\174\014\184\029;)\153\231e\172v\179\152\157\164l+\151\184\208\2261\254FO\154\026(ZG{\239\170\186[\2448c\254\160e\189j\141?V\004\239'P\020C,\255Qn\134\2018\250\218N3\164\r\186\019\2049]\170\186\224\244\187\236r\229\186\b\r\2450M\244J,\209\130N\141*V\149i\158F\015\142\138-\128\152p\212g\r\223r\246\189H\253\025mU\002\208\227\194:.w\221\205:\213\021\156\143\001E\142~\176\231\143J\229\213z%\147\020\239*\231\229\237g\208.\231\214\240\216\229p\234\182\024\156=\211\175\241\194}\b\239pi~\011H\te\248Il\007\146i\232\249\235\194\215\150\194F\002\162Rh\232\149\197\143o\\\"\193\145Y\174\162\230s)\245k\004\139\131\153\138\198\183i\230\243)\1558\022\005\206`\170(\184\245\193Vj\222\233\252\145t\167\152\157\155\218\252u|;d\n}\182W\207\249Gd\146\1575 \155\141P\230N\197n\028\163\172\218\181\017\229u\163\158\007\142\188\192H?19\231\227c\164\242n\006\132\178\177\210q\150\148\157;\149\tK\140H\158=\161dd\217\226\150$\006\142\133\027?`\016_a\224\150)e\005D\214\248\1942f\n\136v\148V\020|\191\207wn(\176V\000\214\219\175M\137\196c\214\244\b-\146\240{{s\140x\207K\254t\217s\021V\025j^\175\n\221XF\146\006\002\019|?\189Lv$\175?\198\141Ks\140\014p\r\014\177N\139\212\231|\138\143\020\195\212\000\021\030\186Bp\146#-2/8O\224\160\005M\t\148{\198>\15529\131\226\245j\2062rV\182\179\169#\218\1333~tc\028.\205\226\202\140b\221\155:f.\208\007\2449\007Z\030\196\218\012O\243t\225*\179\167\178]B\230|\015H&E\166\130;\202\157\189\147\169\012\168`\246\146k\164\234'\231\246>\154\223\192\132k\204\1812ul\226\020\242o\213K/\232\173U9\140\026\182\211\212P\162\151\241\007\000WD\149\028\024\254\249\021f\1611\218j\129\150\198\179\152\202I\132\018s\152zx\208>\188\188\178M{\021\175\217\139\244FhUi'\137\rdh\130\029\204\b\132G8+h\0057K\208\17271\192\rm\213\157D\128\163\n\007;\220\139\003Dn\029\1919\217\212}p\251o\247BW\247b`*4\219K\164O\171\216\198\199_\021X \169'\027\236U;B\1807\016\164\006\196\0253\138cH\144%\173M\189[\011\243\1278\181\022\169\208\128\158\204\163\172Je\149|\165t\179\162\216\005\168\182:HU\185\169\024P)y\241\152\200>\133KZ@3\216E\194\251-b\221l\162\244\000\244\1636\236\nPf)q\021\130\021\016l!\156B\n\203\030\161 b\179\179\165\b\014B$4K\b\156\192u\\m\n\149\181%:\191\240\142\140\018\247J\024\148c\020\016\133\162g\213\t\r\188\194\006\019a\141\195\004\133\224\019\224,P\175A\n|" let d_c5a269addda7c271815b135239839fc8 = "P\241\232h\024\250\163\217\020\144c\016\250/2\253\209\012\193\209\2098\029]\191\029e\226\225a\208\2147\011\230\243\243\001\028\022\142\231~W\011\162\150k\151\1935\255B\020\245B\252\203\199\253nbG\250\231B\001\151\196\171\024\150\130\235\207\127\186k\242\127)\164q\138\163\249\031\252\133{u\187[\"G\162\171\202K\127v\185\192@\005\230s\1713\159\223\000\026\153\213\213`\160\152G3\012\162\155n\1894\155mP^\2343\195\233\184\022\213\002\003[\190\198\144\003\180\017\218\026j^REO}\252:\1393F\175\136\209[\156\235\253ZK\217\145\182\207\180t\143\191eN\004^\188\169@\152\171N\1587g\002\179\139Y \2088WQ\nuq'\163\211lb\237n\133\204\192-nr\200\247&V[,DJ+\169\250\255\154\205\0079ZTk\020\031\023\025\229|\158\214\195\164\166y\242\\\186\163\017R\239s\195v\185\236E^9\205\224\207\011\250!\164y9\175_\209a\r\171\129\157\202\022DE\011P^\027\135Os\133KH\239\201D\130\014\242~A\246\"\188\159!\004G\168\181\006\141\031\1775,p+\206i\127\231\237v\014\19050\172\149\232\1671Pk\017\028I8\018\247\157\250\224\026\153\226\025oo\127\219\217X]\138|\252~\018\147\247)x@\165\232\211\227\211\143\1386P\192\141\235^\028\201>b\\\2329N\193=+\162\155\255\2447t\026\162r:\253\r'\240_\027<8]\177j\007\202\196\011\203\031T|\242\198Ym\135\190\252~!\142$\232^QtS8\232\209/`2^\210\017\233cM\218)\201\130\029\157\006\129p\168\023u\134-Z\168X\168\b[\228Dm\216\004\149%\208\174p\192\146\172\164\157>\214\246\200R\156\142\014\142\0152\241\240ph\215\238\148\233\148\233\188\247\154c\003\237\220\r\213\226\136\173z\176\243+\026n\248\169z\184zU\184!.\187ftAM\165u{P\011\142\132\220\196\156E3P-F\156\254\213\234\206\159\169\248\128\1715\167\021\250\230fJ\225\190\142\253^(\185\022\143Jc\169\206\\\152\209\144\209\b\133G\224H\153b\203\214,0p\219;\189\228\141\230\185\150b\221\180\206J\250\171{\194-)\005C'8 \149\026\167\161\0295s\020\188\185yo\239\235\183\022P\179\006\144\026I\1474\154vB\200\001P_\002$\131\217\012&\199\153N\019,\255\163\169\006\146J)0G\000QPT;#\226b\189\137D\200\148\t&\151\138\024c$\n\140\244\253\245t_JCKC\n\146\250!S\198\196Z\253/}}p\027\133\1292yC\144\b;\128\136\142\166\236k\255\193@\150%\236Y\202\217\181\024\230@\132S\143\030\157\"@\028$%\n\143B^\200\020\139\227\020\135rK\211\234\205\137J\218t\150\172\159\132\242\018~\141U\232H\143\005R\171\\j\242K\168\142(\029x\211\186$\019\174\236y\168\225\141\bD3\242\165\139\164\135\2415\183\176vh\001\161\012a-\163H\143\020\019\138\t\016\226o\t*\168]\212\219`\140\171\250vSN\129)1\189\224\011ix8O\175e\226\187\242\235\178\146h\221\191\228\1750\132}X_lwR\212\235\141\017.w\134\202%Q\251Q\147\252\244\233\029<\190\188\154\n'(+\019\237\197\151+\146\250\234\239\027\205\221\199k\228&\189[&>Oz\129\148\031\129\172H!Z\173\185\241\151J\161\159J\225/)\144@0\245\171}\"\174\187\018\023T\179-\213y\233\180~\223\188\215**6\250#\139g\003[\232\167\030\134A\031\170\249I\188\223\137Yo7P\186'\191/\014iu\209\011\027\139\185\147\218\173[\168Y)if\146\147\174\218\247v\218\004W\202!A\191\226\199\028\222\149\r\172b)\214Un\160-+\245}\186\247/%\243cJ\244\220\210\0057\168\184Eo\194MI4\241_\011\240L\018\220\138l\234+TH\187\018;\165\190\215\b\193Z+1!\182\029\247\234\243q\164\134\021\026\025\209\222\216]\151\1448U\227u\252q\242F\028v[\023\204?'\192\1985\134.\142\012\214\175\228\162\235\163\189\234\012_\t%e\162\179\195x\167\153\193+\011\200)\168\004\173\185\212\018kfX\133).\194\020W\030\198\"\214D\213\173\030\0062\0024\1490\185f\024Q\211c\165\198 \203\164\191L\nW|!\019F\202\248\219q\132\150^1\169\228\011\155\2141\003\143@\175\145!d\026\236Y\212\150\2039&\178\218\"\015\248\128\145\017\011N\157kmq!\135\021#H\228\002\223([\202.\017X\176@\170r\163e\161\b\139E\\\004\196V\245\222\132\130x\160\136\176ZFV\2248\229x\253\130\185\138M\028\159$\132\014\139\0258\165~:\163\222$#\255_a\167\152~KJ\235J\204\141\138\1444H\253\135\165\216?\1321z\002+\157\251\193\237\006S\180@\128'\205\205p\186>7Q\138S\191j\"\143\178\244{ \004\207\127\245\204\2388\235\194\141v\156r\188\164\t\165\226\236/\226\172\241\182J}\139\005\167\20457\221\160\160\227\011I\b\238E\014E\\\224\157\219r\194\129\175\031%CH\030\023w-\172\127\186\007\129\183\197Z\155\172\142\200\205\238\211\221t\006\\\217/\129&&\012w\179Pjy5F*k\221\185Cy\151\021T\185\147\027\182\226\138*\175\164%\131\023\175\171\030\246$\246\021\225\t\230f\154\179\219=m\012\190\224|\158f:r\237X\247\177kGL\250-\020\233\235T\029\132`\184\211\168t\215t-\187:\223\169^\243\192\240\254\235.\251\219o\023\209r\199\172\210z\181\251E\254\208r\165)\221\228\161l\011\0309\021Q\253\223\223\141um\157\149T\182\244\133\149\254\197\136\179'\222\138\246\162^z,G\227|%\237\171\141j<\161*\195\018V\186VC\025\015\192\173\254\220\133\n\1522\174\199\168\203\200\165\005\0058m\174w\129\023S\151p\152L\n (\173\019\207~\241\245C\030\133\215\224\234\207/\022\026\233\231\172\1387\137\244\144\156eK\163\174\137\002\1694\185QZ,}\200\194\206\138\208\134\215\198\248(\2455\\C\141P\\$\230M\156\201H\127\165\148V\176dr[!\163\142\199\215\234*\030\156A\166\189,\252\237\181\248\218\141`\"\b\194\238\251\005v\019\003d\184B%p\007\020\207\137\151\n\221\134\241\213iQD\249\239\143U\005H\224\235e\132r\002r\236$\002\154\199o\007\176\003\138wCIl\002\201\135\179`+MU\238G(\167O\223mh`\155I\024\228\022\175\217\151\156\025\174\160w}\192P\191pA$\019GF\207\206\229\216\218\017\220*\140K\\\145\172k\015\2324DhW\004\232\218\147\019W\196\t\1738\229\184\167u\142\138k\162\187t\237\004\168\238\027\b\018\137pd\225\217\185<\164?q9C\194\245\203\170\127_\015\162\184\n\142\150` \145\137\188\011\197\\z\212\128\175\185A\183|)(\190\0164\179X\170e\192\201\199+S\021\214\132z\215\153N\150)\011\249g\249\1698y\176\176\026\165\224b1L({\006\185}\012\145\139\018p\228\235\1852\247 \025\175<\246Np\130\193i)\200\197)\199\171\026P*\238\023\"\134\224\164 U(|\163\180\200\170\"9\217\166Hu\186k\251\131\167\248\161\236j\016\179tZ\134\226Hn-\255\144\160:ji21\190\175\227?OJ\215,\204P$\132\027\190\233\248(\170C\131\147]_\020\235\0315\127\011+\141\2318\001\025b}\025_\162\240\023g\007Q\204H$\t\166\031$P\222yG\187\151\199\128\176\193\151\007\015\135\182\230\165i\022\166\163\144T\138\000\206\021\024\185tI>\195g\162\001\003\135\245y\006w\136\254\215\183\232f\171\b~Z\245\014}\007_\163\248j=\024Z\007\170\137\173i\220\250~\210a\189\156\195\128 \192\224p\019\\$\192+3\005\228\128:\020\243hE\131w\011\206\136\193J\182\212G\012\177\136D \201?v]\249b\149P\1618+\211mQpS,u\018\153O~\177\127~E\174 \167\2009:$\223\169\025\148\253L\012\t\222\202\130\226\181\0302a\018\138\t\144\017H\234\137@\129uiY\014!T\158\175\012\207^\156)\020?\023\250dM:\129\005{\017\135\127{\217\175\021s\0018$\012\012PICXtT8\150\193s\n\131\243^\249!XrgI\200\184\208?:&\244\235\138\140'N\166\223\182\003\235\158O~\019\153#\166\196#\244w(\255\143\152\191\151)\030(\019O\180\177^x3\021\223\027\031*\002\190\r\248\242\003Jn\171!(\144\161\230\017y\030\001\223\195km\229\243@#\143\143\236_\185\178\160v\191\151#\r\177L\251%\240b\213\156\183\217~\189\001\200O\176(G\232sy\159k\223eJ\190\"\014'\160\140\200\245l\031\152\153\196xC\184\029\175\242\231\028C\030&E\137+\191\160\005\017\225\151r\005\250\172\173\172qY\226\023QD\142t[${\0225\"\193s\139\234\143S\240h\153\186tK\183\170T\143\247\018\185\190?\195>\227\"O\203\143OwP \007d$\007\\#\213^\188\020\193\192\131pF\030\131\255N\192\247)E\148\140i\132\219\128a\004\156\000\133\n\001A\135\231|\1270\178+\178\011\n\011\195_m +\163\007c\006!\027\229\130\175\191\132\194\139ik\235h\239\232\232\236\134TdA\157\235\027mGG\152n{g\167\236\228E\001\159 \228u|S\232\228\t\t\012_<)\019ie\215\184\182\214\021\028\0022+\215fA\016\252\251\030\137Aj\201o\140\204\r\207>\148\223Si\245\229h h\238\241\214\135D]\250\233\158l\254\182x\217\128\163\236\215\191\235\178v\185l\002\"\151\176\245\144\237\196\030#\167\131\030\23363J\\\249\220\138\215\224\237\191\238\252\133\243q\183\164\bm\156Kx\004\017\014\2393o\213.\186A\182\209\182\192\181\174\004d\177\159$\220\238\156o\136\203\136\218\179\006\245)\021\161\225\237\174;\019\157\226z\011qCi[Mi\244\199\205r1[,\154\023\011\t\228\175\177\238\216,\223\252\140o\020\180b\022j\214r\243\145\198\200\222\b7bAd~D\168\255'\154\030I\173\242\188\211\162\215p\221\223\151U7xk\185\147\218-[\152\196\172\180\140,\135\208\156>\193\229[\140TNytz{\131-&*\164\140vS\178V^\030\202\210\201\028\186\195$\190\130\156\153\150\161\254\025\004\146*\203\199\178\154\201\189\244\143\136\137\007[\239Hd3\202\024U\157\140\026w[L\224\244OR\151\243i\005?\132\156\r\r\219\016\024\246\172Oc'x\214\200\227\199\026\234\235\214B\246\031\222\tZ\031\030|9<\232Hh\2243\154\252\130\182,\131\224\205\016\252;2\236I\2373{F\180\246\019!!\007n\\=y\141\203\138pk\206E\003\018\196*\216q='{\183\155P0\230^?l|30u\190\165\228\135xH\231\206\160\133\191\014C\166\030b\131$\220`!\135\240\217w5.\146x\234\202z\209\178\213!\165\234L\247\129\2078\194\136L\162\251\155;D\200\247gt\173\229T\162\154]\244\164\202\248}T\171\179[\174\161\181\247\0244\141\188\219\217\026E\206\202\005\149\233TK\006;s?\t\015@7B\173\251>7\174\174:\234v-\206K\208\181\180\188\245&EI\234\218\176hA|y\202\178\151\023Z\019\187\187M\137\141\243,\180\212lF\019D\179\170\022\230\137\028;M\197\216\179\244Z\180\220FH\250u\025m\227\130\150\249\186\243\228\172[oq\176$'\006\232\133\127\252a\r\153\029\016\188-\031\223\149\"\217\190\166]&d\229y\191\245>\254cS\246\128\244\192\192x`\246\191\151wk\012i[\236\183\221\151\031\025o\1383C >0=\208\03005" @@ -348,6 +350,8 @@ module Internal = struct let d_c7561e7d22eb89e10083cfba7680012c = "-1,6,4,11,10,11z\",baraboveleftarrow:\"M400000 620h-399890l3 -3c68.7 -52.7 113.7 -120 135 -202\\nc4 -14.7 6 -23 6 -25c0 -7.3 -7 -11 -21 -11c-8 0 -13.2 0.8 -15.5 2.5\\nc-2.3 1.7 -4.2 5.8 -5.5 12.5c-1.3 4.7 -2.7 10.3 -4 17c-12 48.7 -34.8 92 -68.5 130\\ns-74.2 66.3 -121.5 85c-10 4 -16 7.7 -18 11c0 8.7 6 14.3 18 17c47.3 18.7 87.8 47\\n121.5 85s56.5 81.3 68.5 130c0.7 2 1.3 5 2 9s1.2 6.7 1.5 8c0.3 1.3 1 3.3 2 6\\ns2.2 4.5 3.5 5.5c1.3 1 3.3 1.8 6 2.5s6 1 10 1c14 0 21 -3.7 21 -11\\nc0 -2 -2 -10.3 -6 -25c-20 -79.3 -65 -146.7 -135 -202l-3 -3h399890z\\nM100 620v40h399900v-40z M0 241v40h399900v-40zM0 241v40h399900v-40z\",rightarrowabovebar:\"M0 241v40h399891c-47.3 35.3-84 78-110 128-16.7 32\\n-27.7 63.7-33 95 0 1.3-.2 2.7-.5 4-.3 1.3-.5 2.3-.5 3 0 7.3 6.7 11 20 11 8 0\\n13.2-.8 15.5-2.5 2.3-1.7 4.2-5.5 5.5-11.5 2-13.3 5.7-27 11-41 14.7-44.7 39\\n-84.5 73-119.5s73.7-60.2 119-75.5c6-2 9-5.7 9-11s-3-9-9-11c-45.3-15.3-85-40.5\\n-119-75.5s-58.3-74.8-73-119.5c-4.7-14-8.3-27.3-11-40-1.3-6.7-3.2-10.8-5.5\\n-12.5-2.3-1.7-7.5-2.5-15.5-2.5-14 0-21 3.7-21 11 0 2 2 10.3 6 25 20.7 83.3 67\\n151.7 139 205zm96 379h399894v40H0zm0 0h399904v40H0z\",baraboveshortleftharpoon:\"M507,435c-4,4,-6.3,8.7,-7,14c0,5.3,0.7,9,2,11\\nc1.3,2,5.3,5.3,12,10c90.7,54,156,130,196,228c3.3,10.7,6.3,16.3,9,17\\nc2,0.7,5,1,9,1c0,0,5,0,5,0c10.7,0,16.7,-2,18,-6c2,-2.7,1,-9.7,-3,-21\\nc-32,-87.3,-82.7,-157.7,-152,-211c0,0,-3,-3,-3,-3l399351,0l0,-40\\nc-398570,0,-399437,0,-399437,0z M593 435 v40 H399500 v-40z\\nM0 281 v-40 H399908 v40z M0 281 v-40 H399908 v40z\",rightharpoonaboveshortbar:\"M0,241 l0,40c399126,0,399993,0,399993,0\\nc4.7,-4.7,7,-9.3,7,-14c0,-9.3,-3.7,-15.3,-11,-18c-92.7,-56.7,-159,-133.7,-199,\\n-231c-3.3,-9.3,-6,-14.7,-8,-16c-2,-1.3,-7,-2,-15,-2c-10.7,0,-16.7,2,-18,6\\nc-2,2.7,-1,9.7,3,21c15.3,42,36.7,81.8,64,119.5c27.3,37.7,58,69.2,92,94.5z\\nM0 241 v40 H399908 v-40z M0 475 v-40 H399500 v40z M0 475 v-40 H399500 v40z\",shortbaraboveleftharpoon:\"M7,435c-4,4,-6.3,8.7,-7,14c0,5.3,0.7,9,2,11\\nc1.3,2,5.3,5.3,12,10c90.7,54,156,130,196,228c3.3,10.7,6.3,16.3,9,17c2,0.7,5,1,9,\\n1c0,0,5,0,5,0c10.7,0,16.7,-2,18,-6c2,-2.7,1,-9.7,-3,-21c-32,-87.3,-82.7,-157.7,\\n-152,-211c0,0,-3,-3,-3,-3l399907,0l0,-40c-399126,0,-399993,0,-399993,0z\\nM93 435 v40 H400000 v-40z M500 241 v40 H400000 v-40z M500 241 v40 H400000 v-40z\",shortrightharpoonabovebar:\"M53,241l0,40c398570,0,399437,0,399437,0\\nc4.7,-4.7,7,-9.3,7,-14c0,-9.3,-3.7,-15.3,-11,-18c-92.7,-56.7,-159,-133.7,-199,\\n-231c-3.3,-9.3,-6,-14.7,-8,-16c-2,-1.3,-7,-2,-15,-2c-10.7,0,-16.7,2,-18,6\\nc-2,2.7,-1,9.7,3,21c15.3,42,36.7,81.8,64,119.5c27.3,37.7,58,69.2,92,94.5z\\nM500 241 v40 H399408 v-40z M500 435 v40 H400000 v-40z\"},A=function(){function e(e){this.children=void 0,this.classes=void 0,this.height=void 0,this.depth=void 0,this.maxFontSize=void 0,this.style=void 0,this.children=e,this.classes=[],this.height=0,this.depth=0,this.maxFontSize=0,this.style={}}var t=e.prototype;return t.hasClass=function(e){return l.contains(this.classes,e)},t.toNode=function(){for(var e=document.createDocumentFragment(),t=0;t\149xn\012F,\006\026\237\230p\239K$\244(\137\175\182b\250\165+L\141G1\2555\025\019/\163\237\154m\193\134_\153\213\184\197,\167C\028Hf\0072\166\134=\227\153\b/\178\204\1864\025*\142\172\b\155\224\142n/\23321^\127Fh\228w\210w\178\011l\141\225\136\221\213\021\183\240\014vu\184, \"\248a\182\220\142\234\019eu\164\183\022\163_\170<\133\142\190\022\149n\bt\201/N$\003\210 \155\023\148\003\188\201v\151\201\185TM\178\199523Y\175\012\173\173\2454#Z\029\166\231TM\022\141j\186\176\171B\171i\2327\011\174P\026\254a\220\240\239-Z\188\"NP\148\139\217\2140\208\218\150\237K\219${V\165\019\018\254\219\220\231=q\t\183\236\"\182I\019\135\232i\245\155\2514}\163U\254.\193,\216,\138y$\000\1786\184\n\015\139\t\215\186\161~\215z\144!\237u\027\190\162[=\012\255ML\152\163zy\249\228\170\222\030V\170z\142\214\178\200PN\016\233\005`\203\224\188\158L\181{W\004\154e{\167S)qP\175\175\205JE=x\220\185\167\200\255\146\151\150Y\158\196(T\178r\020\127x\140\147*)\168I\151jt\179u\204\177\244\1571(]\250\147G\204\165\221E\232\017czD\149{t\130\240oL\245\197\024p\007l\022\199\220\018\021\178\248\206mC(%3\168\132M\198\144\017\217\246\205\186\021\011\243!\255>,Ntqob\2283\151\149]\030\147^vyuB\248\230\221I\029\247\254\159\023}\214\231g\155\202\213t\187Y\200|]\211\135\015C<\2385J\183x\003\147vB^\239u\235B\250c<\155\180\251Z4\205Y\136\187\003\\t\011:\028\210:V\157r\229\220\149\004\142[\230!\021\251Vsx\003\220R\164\014\244\2559Q\158\202\163\026sP5\181\018\250moI!\236,t\2154X\169\224\202\162\246^\022\166zie\030\203V\149\149Xlh\187Q/i\002\149\149lZ\n\134\028x\028k\194\221<\003\182;\157\127\021*\136\245\151k(\148\183\195\240\2284<\185q2\031\2409t\162\238\140\\\2372\191\001I\220\220\168\198!\231s\227\026[\019\198\015O\174\135'S\239\1421\232\233>pR\128\022\185\173\172\017u%&\011\139\012A3_\143q{\171\151\242y\000\199V\2236\198\014\170\191>\183z\189\240\249\204`rU\164u\t\188\152\206U\199F\218T.\236\253\154\001!\185\003\240x\254\159s\232\219\015\005\015\141\026\203\015\249\168\161o\166\197+\207e\"f~}r\253\150\217\021\200\133\168\196~Hx\207\2185k\217\014F\221;$\242O|\029P\154\229\002\244\129sq\175Fb\240\153K\167\180\154F\129\184-\167\241\170R\156\"\171|\243\007d\153\209,\167\001\166\129Nq\b\229\130\\\175\197\137\136*\200\151,\229\178m\012\1658%gn\192s\183\194c\019#\025\209\155\019[3\225\216*\128\248_\170\182\165\165\017\2058\246\170Kk$\t5\163\152+n\157\137D\207\196fa\177\227\176\216\017\2493\007Zh\222\175\167\186\240\251\2313q\171\144\215\182y\231\218n\210BT\22624\188of\231V~\128E\249\128JQ\225U:`I\015WG\031\152\015\212\177\180t\1333\170_>m655\002\237\227\n\183&\203E\216\026\187\2125T\165\203\170d\206\n\228(?\141v\236\169j\162\142FUc\172\r\250\164{TYp\015\0265\151\237\030.\219\141\002{\254wy\221\157}\187\136\151;+/\211=pC\216\"\255\222.\000\004h\0275\224A\158y>\184\128\147^\131\014.\168\188P'1\250\194.\165h|\220\149\208\156y\198\023\242\200y3\189\254\150\214\204X\239\176\249\189\237\179\233\230}B\227\016G\017\206\149\182\169\245\030\196\160pL\199r\019\137\000\233\001=Y\253\002SE\203CZ\002\237]T\181\128\002\139\213,\016w\242\132\241\1562\000\196X<\007orO\227n\"\192\172\231\005\219\164\022g\214e\148\202\028j\236\232\031B\128N\186\185\176'D\148\147\137\187I\184\202\203\207`\234\254;>\184\142a\165\209\148L\222\249\249\182\\\242\161y\196\"\022\194?]\1873\139\1406\200]L\003\147\226\018)\004#}v\143\229.\166\199\169j\200\170\216\027\b*\177\142\137>\171n\182\026i\163\030C\019\144L\230\233i\179f\154\189\130\181\254\215\159\137\166\172\160\178\142H\142Dh\202\184\b\167\220\239\170]~V\221XOe\233\141\n\131\232\129RS\021H\023\242\155\028-u\165S\229\149\137T\151R\235g\148\158U\139h\212\004\164\023B\1662\021vB}\189\022\215y\145T\143\191\134\175\186SK,\005\202k\187\209%\147\021\204;W\001\129\019\240\030\005\235YPo\b\226\189Y\168<\b\183\212\204~\229F\197\172\176\152\213\0208\002\2454\018\153\231x\\\150\197I\019\186\185\138\151\222`\145\239\208\216L\244\127\026\204'\160\177\138\202\155\002\030\195fc\212\235\212v\189\137?\1450\003\194\245k\1788R\219\019\219\248\168\247\136\nj%\175\140\160l\168\192\201+\149\137#\133\192+\025'\230\182\226\018\216@\224<\143\193\145\158\183\227\132\026[#\219\030!\176\005\252\022\181Nf\0170\128fb\203\218{\200R\237\220\209\243\227\2294\206\018\250fT\217\153\1915{\185\229_\1639\168\179z]\227=\174\020\174u\151\132%\128\253Q4\243\003\030\155e\178Q\234\205oR\168\021\146\138\154L%v\011\131\015r\229\227\247\182\018?\244nF\151\220z\023\169\198/\189mz:^u\021hm\190M\156\026\208\1957+\214\207\026\"\022\143\209\017\011^\194mC\185\218c\000\127\162e\194\174\236Y\177\030\201L\143I\023\236XY\183}M#\021q\135Vpt\188\179\162`\235x\129\251\206\026\012\017O\196\2300D\002\177\230\251\215>d\147\137\242\223Hlcc\"\0064\185e\014S\246\167\218\185\197\170<\183\r?\250\253\172n\248\133\245\240\156\229\225\236\"\255W\166'\157\182\219\132\1393\031\1563?h\171\190\169\019<\219\b\245\232\235v\182\190\137\225\231M\164P\143\150\255\236@\139\150\184\190\r0\012\173Md\191\226\005\207\014\175\028\177p\253\214\173Z=\031n\150s\136\202\212U\\\235v\020\152\153-\158E2d%3\160w\137(S\173\022\000t@$9\189\229e\207W\022\179\239\217v\225\185\183\194\142F.Q\233\186\134k=\129\134\210\179\197\211(\006\157\216\255\215?\1344\226\180\n\165~7_\012\222\150\163e\240A\001\188\nT9\201h\175*\007\198\219\145\005\204\253\176\212W\176\020\137\241\184V\244zM.i\131\134\160F\244\186,\167#ok{\131ahm\"\253\157!~}\248\162C\161\175\153\007\148\213\175\012.\172\241j(\165\168\250\247\003K\193U\139)\133\254PK\163\162\012\137|\002\011C\030\195\021eH\002\031\234\201\1494\165\015cix\200\239\173f\193\183S\222\203\131\197\251\210\159\245\193b\223\022\002\231\234\202\030\227\189\140\239\180T_\230\243\206\163QW\129Gw\206\164\016G#\148\2374\155\139M\209\213gj\167\172\227\r\207f/\250\219\011\224%`Nnb\027\147>\215y\225\b\163\184s6U\228\241\b8\217\005\146\247\021\174\166\007\162\138\138`\207k$5\169S\215\221|\205\153(\016\187\020\158\166\139Q\249\237[\236}u4\bT\185\020\150|\247\205\1721\240\005d\183\164\253\142\183\b\167\227\029x)\241\178\157\187\243]\176\163`/n\231{`\199\203\239\234\184\007_N\188T\208\251N\028U\154\007y6\232\228\251\182\224\176\223\226\142ZO\169Z\222W\240U\248\160\145\209\165ok\237o\186\234\211T\r[_P\186)Z\182C]l\202\186\000\230\186D\155\177\168t{\164t\179\017\\\252\249\229\223\194\232?\"\240F\195]\179\145\t\200Yf\211]\147i9\160Xb\180\2205[Xr\128i6\2235\154\240\170#\131\002\185D\146\229\243\199%\r\227\252\182m\189->\173\173}\168\029V\182#Z\186\237\137\016k\169Q-U\196\027\140B>\225\1917Zj\154[\228\182\182\214 \168ts\180l\155\023\006\200U*@h\230\222\164\225\193\1382n\159\209\173\170R\253\142\210}\003\182\190\141\210>\182\208\208\164T\144\181\229\205\224\244\017}1m\197\208\200\210\030\015J\171\000[\029(\157\138\148=0\148J\155%|\243\235[\136v\189\222\030\134\197o\131\180\183\161\193lA3\023\021\187\006\t\251;\233\026h@\t\214*\224\025\136\167'\029\202I\131\014!j\007F\0228\244\t\144\006\233f\192\214i\144v\0261<\142\024\206\146\220\031\ru\233\025`&\129\185\140i\127:n\223\140\015\142y\253zgv\168\003V\182'V\186\187\011\162\177\234\181\031\155\177\\\153Y(\198c>\247\161\157^\021\131\214\236\149\200\151\149\237\142\150\237.0\147\1395\154\239UH\nW\206``\027\1282.;B\223v\015\165\251\014d}\007\169}\220\209\160V\144\212\229\241(\\\163\189w|\201`\139\004\186\141J\252\224\222\225\246\140Q\204\177\252\186\133d\015\133\155\003E]O.\129'\225\233\167I\208\177\135\238\017,\165\000i\149E}P" let d_cabefc6c9607b95a33af32a8c8832767 = "gOpSpacing1:[.111,.111,.111],bigOpSpacing2:[.166,.166,.166],bigOpSpacing3:[.2,.2,.2],bigOpSpacing4:[.6,.611,.611],bigOpSpacing5:[.1,.143,.143],sqrtRuleThickness:[.04,.04,.04],ptPerEm:[10,10,10],doubleRuleSep:[.2,.2,.2],arrayRuleWidth:[.04,.04,.04],fboxsep:[.3,.3,.3],fboxrule:[.04,.04,.04]},C={\"\\xc5\":\"A\",\"\\xd0\":\"D\",\"\\xde\":\"o\",\"\\xe5\":\"a\",\"\\xf0\":\"d\",\"\\xfe\":\"o\",\"\\u0410\":\"A\",\"\\u0411\":\"B\",\"\\u0412\":\"B\",\"\\u0413\":\"F\",\"\\u0414\":\"A\",\"\\u0415\":\"E\",\"\\u0416\":\"K\",\"\\u0417\":\"3\",\"\\u0418\":\"N\",\"\\u0419\":\"N\",\"\\u041a\":\"K\",\"\\u041b\":\"N\",\"\\u041c\":\"M\",\"\\u041d\":\"H\",\"\\u041e\":\"O\",\"\\u041f\":\"N\",\"\\u0420\":\"P\",\"\\u0421\":\"C\",\"\\u0422\":\"T\",\"\\u0423\":\"y\",\"\\u0424\":\"O\",\"\\u0425\":\"X\",\"\\u0426\":\"U\",\"\\u0427\":\"h\",\"\\u0428\":\"W\",\"\\u0429\":\"W\",\"\\u042a\":\"B\",\"\\u042b\":\"X\",\"\\u042c\":\"B\",\"\\u042d\":\"3\",\"\\u042e\":\"X\",\"\\u042f\":\"R\",\"\\u0430\":\"a\",\"\\u0431\":\"b\",\"\\u0432\":\"a\",\"\\u0433\":\"r\",\"\\u0434\":\"y\",\"\\u0435\":\"e\",\"\\u0436\":\"m\",\"\\u0437\":\"e\",\"\\u0438\":\"n\",\"\\u0439\":\"n\",\"\\u043a\":\"n\",\"\\u043b\":\"n\",\"\\u043c\":\"m\",\"\\u043d\":\"n\",\"\\u043e\":\"o\",\"\\u043f\":\"n\",\"\\u0440\":\"p\",\"\\u0441\":\"c\",\"\\u0442\":\"o\",\"\\u0443\":\"y\",\"\\u0444\":\"b\",\"\\u0445\":\"x\",\"\\u0446\":\"n\",\"\\u0447\":\"n\",\"\\u0448\":\"w\",\"\\u0449\":\"w\",\"\\u044a\":\"a\",\"\\u044b\":\"m\",\"\\u044c\":\"a\",\"\\u044d\":\"e\",\"\\u044e\":\"m\",\"\\u044f\":\"r\"};function q(e,t,r){if(!T[t])throw new Error(\"Font metrics not found for font: \"+t+\".\");var n=e.charCodeAt(0),a=T[t][n];if(!a&&e[0]in C&&(n=C[e[0]].charCodeAt(0),a=T[t][n]),a||\"text\"!==r||S(n)&&(a=T[t][77]),a)return{depth:a[0],height:a[1],italic:a[2],skew:a[3],width:a[4]}}var N={};var I=[[1,1,1],[2,1,1],[3,1,1],[4,2,1],[5,2,1],[6,3,1],[7,4,2],[8,6,3],[9,7,6],[10,8,7],[11,10,9]],R=[.5,.6,.7,.8,.9,1,1.2,1.44,1.728,2.074,2.488],O=function(e,t){return t.size<2?e:I[e-1][t.size-1]},H=function(){function e(t){this.style=void 0,this.color=void 0,this.size=void 0,this.textSize=void 0,this.phantom=void 0,this.font=void 0,this.fontFamily=void 0,this.fontWeight=void 0,this.fontShape=void 0,this.sizeMultiplier=void 0,this.maxSize=void 0,this.minRuleThickness=void 0,this._fontMetrics=void 0,this.style=t.style,this.color=t.color,this.size=t.size||e.BASESIZE,this.textSize=t.textSize||this.size,this.phantom=!!t.phantom,this.font=t.font||\"\",this.fontFamily=t.fontFamily||\"\",this.fontWeight=t.fontWeight||\"\",this.fontShape=t.fontShape||\"\",this.sizeMultiplier=R[this.size-1],this.maxSize=t.maxSize,this.minRuleThickness=t.minRuleThickness,this._fontMetrics=void 0}var t=e.prototype;return t.extend=function(t){var r={style:this.style,size:this.size,textSize:this.textSize,color:this.color,phantom:this.phantom,font:this.font,fontFamily:this.fontFamily,fontWeight:this.fontWeight,fontShape:this.fontShape,maxSize:this.maxSize,minRuleThickness:this.minRuleThickness};for(var n in t)t.hasOwnProperty(n)&&(r[n]=t[n]);return new e(r)},t.havingStyle=function(e){return this.style===e?this:this.extend({style:e,size:O(this.textSize,e)})},t.havingCrampedStyle=function(){return this.havingStyle(this.style.cramp())},t.havingSize=function(e){return this.size===e&&this.textSize===e?this:this.extend({style:this.style.text(),size:e,textSize:e,sizeMultiplier:R[e-1]})},t.havingBaseStyle=function(t){t=t||this.style.text();var r=O(e.BASESIZE,t);return this.size===r&&this.textSize===e.BASESIZE&&this.style===t?this:this.extend({style:t,size:r})},t.havingBaseSizing=function(){var e;switch(this.style.id){case 4:case 5:e=3;break;case 6:case 7:e=1;break;default:e=6}return this.extend({style:this.style.text(),size:e})},t.withColor=function(e){return this.extend({color:e})},t.withPhantom=function(){return this.extend({phantom:!0})},t.withFont=function(e){return this.extend({font:e})},t.withTextFontFamily=function(e){return this.extend({fontFamily:e,font:\"\"})},t.withTextFontWeight=function(e){return this.extend({fontWeight:e,font:\"\"})},t.withTextFontShape=function(e){return this.extend({fontShape:e,font:\"\"})},t.sizingClasses=function(e){return e.size!==this.size?[\"sizing\",\"reset-size\"+e.size,\"size\"+this.size]:[]},t.baseSizingClasses=function(){return this.size!==e.BASESIZE?[\"sizing\",\"reset-size\"+this.size,\"size\"+e.BASESIZE]:[]},t.fontMetrics=function(){return this._fontMetrics||(this._fontMetrics=function(e){var " @@ -499,10 +503,11 @@ module Internal = struct | "highlight.pack.js" | "/highlight.pack.js" -> Some [ d_6b9eea5bd2cdd91f629293ab3b8808d1; d_30baf6fb746860926fdd280eefc46735; d_7df05ceea77c14d78f1f1df8f98def4f; d_106b469c9254e3a72af1bc5085256cca; d_5fcd7eba230acf47d54c1897a9a9c394; d_df9507781455088adf4ca1bd7fc0a321; d_b223e3337242ba6cf0905995918760a5; d_d6a1be8caf2478248edb48ee82070d9e; d_98850966979dd224456f716b44220d69; d_9873a9ace25bcd721b8eeb6b8dad71cf; d_b23657c0bc089d459bc6099791f97c23; d_f9c0b1a6ea9c119cb0f7ead5c3dac542; d_80a0027403c5ad56c7da4589713b2348; d_fe8f6a1f53d067d447bae579dc60d6f0; ] | "katex.min.css" | "/katex.min.css" -> Some [ d_2d798108ddda42cb699f6ad4421e720e; d_b128d6f091a42be5d7a929703f09ac36; d_1476b6e94be68e530a90bd0723d69c88; d_e357f75b8a7d9a6031bbdc38adcf1422; d_ad152fcf832897f8629ca758460f3d22; d_7c9075f31df2a532c3135ae327c84a92; ] | "katex.min.js" | "/katex.min.js" -> Some [ d_0c2c3443b618aef3ac4519dd2b159bbe; d_a2070486fb8e9102cd1537ebd1216a96; d_48a6338945c47ceb84d335248c3d6873; d_ad48849637d7c8349cb3e6952d5c8699; d_32baa17e8a53bbd439c58b0d89bc0503; d_c7561e7d22eb89e10083cfba7680012c; d_d04b09d89ef0b9af8a297a3592a2e4b1; d_c0cf7351fa27f73a72840e453c4b15f3; d_fadfd470a088dde5c3755136ac4b6188; d_326148c9e075f26f4dd5ee3862f61cf6; d_a55141bd5690b03d71c9675038f73b3f; d_225bdd9918928e02697ef5570454bf56; d_bf8e1c09c2162b9bb4b6578a59cc8069; d_bb5a8ed07dc95fa6f9f51938da398a35; d_b93e718b1ddefad06d18d9736584ad78; d_e12a510e69c6b3e0210294eedc2c3be3; d_bf043adf1d8ba761903c6f3447bae9d3; d_80ae3e22d162129b593049c0dc7f2407; d_d7b447b6bfc36721f581470728505547; d_92e0c0a734f49413d685531ad3f0a03e; d_cabefc6c9607b95a33af32a8c8832767; d_a03f60fbbac88837b2763d52df2c0820; d_5795c26325c462426548bd12ff6ef7a1; d_c0939c104021af2b0d9b24c7102061f2; d_3a7455b94742964a6cc5e84e314a6cfb; d_dc2a908015f68e5bff245fff4e602604; d_96c4d8e2622ac6552ccf67643b20f09c; d_37935d98135b118d937e895f4bb55add; d_efe21915ced6043dcaa8ff576e7948c7; d_fe0aa5b4043d6894e289163dd38508b7; d_dc29762de1ae6c28b3b3cc202f52ac6f; d_2c5af911fa1596ad2eef3a7e342be949; d_01738333fc004372ab1ae8bc7d370677; d_0d6ec6387686b4173900d29c91f338ee; d_5f9942b4d85184e45b9addfc25ca6fd4; d_105a9e030400f28a404c6badd930fe01; d_79c029f6f746a52f4a8bc8b6280c5c88; d_3a50124eae7017a15bb92024b9f6c8ad; d_d1d8d575696cbb5a4994efc9e2862948; d_a6e92521674c97f4d1bd649490d8a987; d_8f38ae17980f4039d715823515fd56d0; d_a841840589a3efb0465e49e0d8f985b5; d_e33d592534625de6438003412e1d8813; d_5b12b53efc1e6da3a434634e81c2251b; d_c7270ab94b84005c36e6e864e6ea5b10; d_5e57240b8ff6745d663ebd2060201199; d_02c9bc01125e92ce389d2ac93e62d14b; d_0d4c13a0e6487657499a2f37795ab83b; d_8ff622534e1e1348711c11358657050b; d_a8b5fa32242a1d360076af4bdc9dafbe; d_725c52bce5d22dff34816d0cea74cf51; d_a6db9cb29ea27586d2138cf4f8710b12; d_31ee9944b6c75c4351486bc790988371; d_1005d4f63119125aeb03e8a2fa265969; d_9ff5a6ec97f55e01b81f13d9d3f0ff67; d_f361846717ba3e91093152df70d5aab3; d_e462cdcfecbc18ac1f1e447bf1ed3697; d_0d5bde992f9fa1c53103cd024ff5833b; d_1b66f4e8c1fbc1c74875f8da050cc1d0; d_bad0217136fdcd657898ee631bd512d1; d_428c2b0f069b4ffaef294dc85aef1e4b; d_cb988ca0480d611a7c52551adcc9ed48; d_cdc6e947cdb2e0bb7fae7f338ffa12a0; d_f56cd226d59f4d3190a095998f97ac56; d_f5d214c6b91ee7f61f5a433fcdd70682; d_f4caf2cb8610b6735641c064e6453b79; d_da739bd79e1901a19d34fbf2d1a16298; ] - | "odoc.css" | "/odoc.css" -> Some [ d_716cf074e5806616f6d61aeb32dbe70e; d_609f576f064dfa5ea1545119859f0158; d_92d67c153383d8a5d46ba6d9247ee68d; d_30ca700678d2ff7e5a1c5981a2e65744; d_9cd2127654bad2ec912e7f568f5fc008; ] + | "odoc.css" | "/odoc.css" -> Some [ d_4c80472ddf58cd79287c7fd4b4d8e58d; d_ab2604284e190ff3f5212ebfbc51a704; d_7c0643b7c2e32bfa6170f0023c969756; d_c3421d028da161fbb9179ce80677e91f; d_b99316dbe0d494e759ac0178687672ce; d_c87bd155089ec1d2c63c3379d3561c35; ] + | "odoc_search.js" | "/odoc_search.js" -> Some [ d_60fce158c679263a08140618240b48c3; ] | _ -> None - let file_list = [ "fonts/KaTeX_AMS-Regular.woff2"; "fonts/KaTeX_Caligraphic-Bold.woff2"; "fonts/KaTeX_Caligraphic-Regular.woff2"; "fonts/KaTeX_Fraktur-Bold.woff2"; "fonts/KaTeX_Fraktur-Regular.woff2"; "fonts/KaTeX_Main-Bold.woff2"; "fonts/KaTeX_Main-BoldItalic.woff2"; "fonts/KaTeX_Main-Italic.woff2"; "fonts/KaTeX_Main-Regular.woff2"; "fonts/KaTeX_Math-BoldItalic.woff2"; "fonts/KaTeX_Math-Italic.woff2"; "fonts/KaTeX_SansSerif-Bold.woff2"; "fonts/KaTeX_SansSerif-Italic.woff2"; "fonts/KaTeX_SansSerif-Regular.woff2"; "fonts/KaTeX_Script-Regular.woff2"; "fonts/KaTeX_Size1-Regular.woff2"; "fonts/KaTeX_Size2-Regular.woff2"; "fonts/KaTeX_Size3-Regular.woff2"; "fonts/KaTeX_Size4-Regular.woff2"; "fonts/KaTeX_Typewriter-Regular.woff2"; "fonts/fira-mono-v14-latin-500.woff2"; "fonts/fira-mono-v14-latin-regular.woff2"; "fonts/fira-sans-v17-latin-500.woff2"; "fonts/fira-sans-v17-latin-500italic.woff2"; "fonts/fira-sans-v17-latin-700.woff2"; "fonts/fira-sans-v17-latin-700italic.woff2"; "fonts/fira-sans-v17-latin-italic.woff2"; "fonts/fira-sans-v17-latin-regular.woff2"; "fonts/noticia-text-v15-latin-700.woff2"; "fonts/noticia-text-v15-latin-italic.woff2"; "fonts/noticia-text-v15-latin-regular.woff2"; "highlight.pack.js"; "katex.min.css"; "katex.min.js"; "odoc.css"; ] + let file_list = [ "fonts/KaTeX_AMS-Regular.woff2"; "fonts/KaTeX_Caligraphic-Bold.woff2"; "fonts/KaTeX_Caligraphic-Regular.woff2"; "fonts/KaTeX_Fraktur-Bold.woff2"; "fonts/KaTeX_Fraktur-Regular.woff2"; "fonts/KaTeX_Main-Bold.woff2"; "fonts/KaTeX_Main-BoldItalic.woff2"; "fonts/KaTeX_Main-Italic.woff2"; "fonts/KaTeX_Main-Regular.woff2"; "fonts/KaTeX_Math-BoldItalic.woff2"; "fonts/KaTeX_Math-Italic.woff2"; "fonts/KaTeX_SansSerif-Bold.woff2"; "fonts/KaTeX_SansSerif-Italic.woff2"; "fonts/KaTeX_SansSerif-Regular.woff2"; "fonts/KaTeX_Script-Regular.woff2"; "fonts/KaTeX_Size1-Regular.woff2"; "fonts/KaTeX_Size2-Regular.woff2"; "fonts/KaTeX_Size3-Regular.woff2"; "fonts/KaTeX_Size4-Regular.woff2"; "fonts/KaTeX_Typewriter-Regular.woff2"; "fonts/fira-mono-v14-latin-500.woff2"; "fonts/fira-mono-v14-latin-regular.woff2"; "fonts/fira-sans-v17-latin-500.woff2"; "fonts/fira-sans-v17-latin-500italic.woff2"; "fonts/fira-sans-v17-latin-700.woff2"; "fonts/fira-sans-v17-latin-700italic.woff2"; "fonts/fira-sans-v17-latin-italic.woff2"; "fonts/fira-sans-v17-latin-regular.woff2"; "fonts/noticia-text-v15-latin-700.woff2"; "fonts/noticia-text-v15-latin-italic.woff2"; "fonts/noticia-text-v15-latin-regular.woff2"; "highlight.pack.js"; "katex.min.css"; "katex.min.js"; "odoc.css"; "odoc_search.js"; ] end let file_list = Internal.file_list @@ -547,7 +552,8 @@ let hash = function | "highlight.pack.js" | "/highlight.pack.js" -> Some "f7f17015c0de1023c93929e3725a9248" | "katex.min.css" | "/katex.min.css" -> Some "1a262c83aa48d3ba34dd01c2ec6087d8" | "katex.min.js" | "/katex.min.js" -> Some "0376fd70eef224e946e13788118db3d1" - | "odoc.css" | "/odoc.css" -> Some "dac4c780c0c77d757354e248b160dc77" + | "odoc.css" | "/odoc.css" -> Some "6cd2de31223fdf524ccacf6f4c57568f" + | "odoc_search.js" | "/odoc_search.js" -> Some "60fce158c679263a08140618240b48c3" | _ -> None let size = function @@ -585,5 +591,6 @@ let size = function | "highlight.pack.js" | "/highlight.pack.js" -> Some 54535 | "katex.min.css" | "/katex.min.css" -> Some 20978 | "katex.min.js" | "/katex.min.js" -> Some 270376 - | "odoc.css" | "/odoc.css" -> Some 19671 + | "odoc.css" | "/odoc.css" -> Some 21926 + | "odoc_search.js" | "/odoc_search.js" -> Some 1194 | _ -> None diff --git a/src/html_support_files/odoc_search.js b/src/html_support_files/odoc_search.js new file mode 100644 index 0000000000..c636709f58 --- /dev/null +++ b/src/html_support_files/odoc_search.js @@ -0,0 +1,38 @@ + +/* The browsers interpretation of the CORS origin policy prevents to run + webworkers from javascript files fetched from the file:// protocol. This hack + is to workaround this restriction. */ +function createWebWorker() { + var searchs = search_urls.map((search_url) => { + let parts = document.location.href.split("/"); + parts[parts.length - 1] = search_url; + return parts.join("/"); + }); + blobContents = ['importScripts("' + searchs.join(",") + '");']; + var blob = new Blob(blobContents, { type: "application/javascript" }); + var blobUrl = URL.createObjectURL(blob); + + var worker = new Worker(blobUrl); + URL.revokeObjectURL(blobUrl); + + return worker; +} + +var worker = createWebWorker(); + +document.querySelector(".search-bar").addEventListener("input", (ev) => { + worker.postMessage(ev.target.value); +}); + +worker.onmessage = (e) => { + let results = e.data; + let search_result = document.querySelector(".search-result"); + search_result.innerHTML = ""; + let f = (entry) => { + let container = document.createElement("a"); + container.href = base_url + entry.url; + container.innerHTML = entry.html; + search_result.appendChild(container); + }; + results.map(f); +}; diff --git a/src/model/paths.ml b/src/model/paths.ml index abcdd92fd5..8c56851b6c 100644 --- a/src/model/paths.ml +++ b/src/model/paths.ml @@ -63,8 +63,82 @@ module Identifier = struct name_aux (x :> t) ^ "#" ^ LocalName.to_string anchor | `AssetFile (_, name) -> name + let rec is_internal : t -> bool = + fun x -> + match x.iv with + | `Root (_, name) -> ModuleName.is_internal name + | `Page (_, _) -> false + | `LeafPage (_, _) -> false + | `Module (_, name) -> ModuleName.is_internal name + | `Parameter (_, name) -> ModuleName.is_internal name + | `Result x -> is_internal (x :> t) + | `ModuleType (_, name) -> ModuleTypeName.is_internal name + | `Type (_, name) -> TypeName.is_internal name + | `CoreType name -> TypeName.is_internal name + | `Constructor (parent, _) -> is_internal (parent :> t) + | `Field (parent, _) -> is_internal (parent :> t) + | `Extension (parent, _) -> is_internal (parent :> t) + | `Exception (parent, _) -> is_internal (parent :> t) + | `CoreException _ -> false + | `Value (_, name) -> ValueName.is_internal name + | `Class (_, name) -> ClassName.is_internal name + | `ClassType (_, name) -> ClassTypeName.is_internal name + | `Method (parent, _) -> is_internal (parent :> t) + | `InstanceVariable (parent, _) -> is_internal (parent :> t) + | `Label (parent, _) -> is_internal (parent :> t) + | `SourceDir _ | `SourceLocationMod _ | `SourceLocation _ | `SourcePage _ + | `SourceLocationInternal _ | `AssetFile _ -> + false + let name : [< t_pv ] id -> string = fun n -> name_aux (n :> t) + let rec full_name_aux : t -> string list = + fun x -> + match x.iv with + | `Root (_, name) -> [ ModuleName.to_string name ] + | `Page (_, name) -> [ PageName.to_string name ] + | `LeafPage (_, name) -> [ PageName.to_string name ] + | `Module (parent, name) -> + ModuleName.to_string name :: full_name_aux (parent :> t) + | `Parameter (parent, name) -> + ModuleName.to_string name :: full_name_aux (parent :> t) + | `Result x -> full_name_aux (x :> t) + | `ModuleType (parent, name) -> + ModuleTypeName.to_string name :: full_name_aux (parent :> t) + | `Type (parent, name) -> + TypeName.to_string name :: full_name_aux (parent :> t) + | `CoreType name -> [ TypeName.to_string name ] + | `Constructor (parent, name) -> + ConstructorName.to_string name :: full_name_aux (parent :> t) + | `Field (parent, name) -> + FieldName.to_string name :: full_name_aux (parent :> t) + | `Extension (parent, name) -> + ExtensionName.to_string name :: full_name_aux (parent :> t) + | `Exception (parent, name) -> + ExceptionName.to_string name :: full_name_aux (parent :> t) + | `CoreException name -> [ ExceptionName.to_string name ] + | `Value (parent, name) -> + ValueName.to_string name :: full_name_aux (parent :> t) + | `Class (parent, name) -> + ClassName.to_string name :: full_name_aux (parent :> t) + | `ClassType (parent, name) -> + ClassTypeName.to_string name :: full_name_aux (parent :> t) + | `Method (parent, name) -> + MethodName.to_string name :: full_name_aux (parent :> t) + | `InstanceVariable (parent, name) -> + InstanceVariableName.to_string name :: full_name_aux (parent :> t) + | `Label (parent, name) -> + LabelName.to_string name :: full_name_aux (parent :> t) + | `AssetFile (parent, name) -> name :: full_name_aux (parent :> t) + | `SourceDir _ | `SourceLocationMod _ | `SourceLocation _ | `SourcePage _ + | `SourceLocationInternal _ -> + [] + + let fullname : [< t_pv ] id -> string list = + fun n -> List.rev @@ full_name_aux (n :> t) + + let is_internal : [< t_pv ] id -> bool = fun n -> is_internal (n :> t) + let rec label_parent_aux = let open Id in fun (n : non_src) -> diff --git a/src/model/paths.mli b/src/model/paths.mli index f8fd9aa972..5fc19fe377 100644 --- a/src/model/paths.mli +++ b/src/model/paths.mli @@ -200,6 +200,10 @@ module Identifier : sig (* val root : [< t_pv ] id -> RootModule.t_pv id option *) + val fullname : [< t_pv ] id -> string list + + val is_internal : [< t_pv ] id -> bool + val compare : t -> t -> int val equal : ([< t_pv ] id as 'a) -> 'a -> bool diff --git a/src/odoc/bin/main.ml b/src/odoc/bin/main.ml index 83c79bf2e6..b7cd6c241e 100644 --- a/src/odoc/bin/main.ml +++ b/src/odoc/bin/main.ml @@ -395,15 +395,56 @@ module Source_tree = struct Term.info "source-tree" ~docs ~doc end +module Indexing = struct + let output_file ~dst = + match dst with + | Some file -> Fs.File.of_string file + | None -> Fs.File.of_string "index.json" + + let index directories dst warnings_options = + let output = output_file ~dst in + Indexing.compile ~output ~warnings_options ~resolver:() ~parent:() + directories + + let cmd = + let dst = + let doc = + "Output file path. Non-existing intermediate directories are created. \ + Defaults to index.json" + in + Arg.( + value & opt (some string) None & info ~docs ~docv:"PATH" ~doc [ "o" ]) + in + Term.( + const handle_error + $ (const index $ odoc_file_directories $ dst $ warnings_options)) + + let info ~docs = + let doc = + "Generate an index of all identified entries in the .odocl files found \ + in the given directories." + in + Term.info "compile-index" ~docs ~doc +end + module Support_files_command = struct - let support_files without_theme output_dir = - Support_files.write ~without_theme output_dir + let support_files without_theme search_files output_dir = + Support_files.write ~without_theme ~search_files output_dir let without_theme = let doc = "Don't copy the default theme to output directory." in Arg.(value & flag & info ~doc [ "without-theme" ]) - let cmd = Term.(const support_files $ without_theme $ dst ~create:true ()) + let search_files = + let doc = + "Path to the search files. The name must match one given in \ + $(i,--search-file) from the $(i,html-generate) command." + in + Arg.(value & opt_all convert_fpath [] & info ~doc [ "search-file" ]) + + let cmd = + Term.( + const support_files $ without_theme $ search_files $ dst ~create:true ()) let info ~docs = let doc = @@ -723,6 +764,13 @@ module Odoc_html_args = struct in Arg.(value & flag & info ~doc [ "as-json" ]) + let search_files = + let doc = + "The name of a javascript file to use for search. Will be run in a \ + webworker. Using this option adds a search-bar in the generated html." + in + Arg.(value & opt_all string [] & info ~doc [ "search-file" ]) + let source_file = let doc = "Source code for the compilation unit. It must have been compiled with \ @@ -754,7 +802,7 @@ module Odoc_html_args = struct let extra_args = let config semantic_uris closed_details indent theme_uri support_uri flat - as_json source_file assets source_root = + as_json source_file assets search_files source_root = let open_details = not closed_details in let source = match (source_root, source_file) with @@ -767,13 +815,14 @@ module Odoc_html_args = struct in let html_config = Odoc_html.Config.v ~theme_uri ~support_uri ~semantic_uris ~indent ~flat - ~open_details ~as_json () + ~open_details ~as_json ~search_files () in { Html_page.html_config; source; assets } in Term.( const config $ semantic_uris $ closed_details $ indent $ theme_uri - $ support_uri $ flat $ as_json $ source_file $ assets $ source_root) + $ support_uri $ flat $ as_json $ source_file $ assets $ search_files + $ source_root) end module Odoc_html = Make_renderer (Odoc_html_args) @@ -994,11 +1043,14 @@ module Targets = struct end module Support_files = struct - let list_targets without_theme output_directory = - Support_files.print_filenames ~without_theme output_directory + let list_targets without_theme search_files output_directory = + Support_files.print_filenames ~without_theme ~search_files + output_directory let cmd = - Term.(const list_targets $ Support_files_command.without_theme $ dst ()) + Term.( + const list_targets $ Support_files_command.without_theme + $ Support_files_command.search_files $ dst ()) let info ~docs = Term.info "support-files-targets" ~docs @@ -1052,6 +1104,7 @@ let () = Odoc_html.generate ~docs:section_pipeline; Support_files_command.(cmd, info ~docs:section_pipeline); Source_tree.(cmd, info ~docs:section_pipeline); + Indexing.(cmd, info ~docs:section_pipeline); Odoc_manpage.generate ~docs:section_generators; Odoc_latex.generate ~docs:section_generators; Odoc_html_url.(cmd, info ~docs:section_support); diff --git a/src/odoc/dune b/src/odoc/dune index 2f73d465f0..37ed2b5d39 100644 --- a/src/odoc/dune +++ b/src/odoc/dune @@ -10,6 +10,7 @@ odoc_loader odoc_manpage odoc_model + odoc_search odoc_xref2 tyxml unix) diff --git a/src/odoc/html_fragment.ml b/src/odoc/html_fragment.ml index cff1441b54..82cc427e4d 100644 --- a/src/odoc/html_fragment.ml +++ b/src/odoc/html_fragment.ml @@ -26,7 +26,7 @@ let from_mld ~xref_base_uri ~resolver ~output ~warnings_options input = let page = Odoc_document.Comment.to_ir resolved.content in let config = Odoc_html.Config.v ~semantic_uris:false ~indent:false ~flat:false - ~open_details:false ~as_json:false () + ~open_details:false ~as_json:false ~search_files:[] () in let html = Odoc_html.Generator.doc ~config ~xref_base_uri page in let oc = open_out (Fs.File.to_string output) in diff --git a/src/odoc/indexing.ml b/src/odoc/indexing.ml new file mode 100644 index 0000000000..399a5fc126 --- /dev/null +++ b/src/odoc/indexing.ml @@ -0,0 +1,42 @@ +open Odoc_search +open Or_error + +let handle_file file ~unit ~page = + Odoc_file.load file + |> Result.map @@ fun unit' -> + match unit' with + | { Odoc_file.content = Unit_content unit'; _ } when not unit'.hidden -> + Some (unit unit') + | { Odoc_file.content = Page_content page'; _ } -> Some (page page') + | _ -> None + +let fold_dirs ~dirs ~unit ~page ~init = + dirs + |> List.fold_left + (fun acc dir -> + acc >>= fun acc -> + Fs.Directory.fold_files_rec_result ~ext:"odocl" + (fun acc file -> + file |> handle_file ~unit:(unit acc) ~page:(page acc) >>= function + | None -> Ok acc + | Some acc -> Ok acc) + acc dir) + (Ok init) + +let compile ~resolver:_ ~parent:_ ~output ~warnings_options:_ dirs = + let output_channel = + Fs.Directory.mkdir_p (Fs.File.dirname output); + open_out_bin (Fs.File.to_string output) + in + let output = Format.formatter_of_out_channel output_channel in + let print f first up = + if not first then Format.fprintf output ","; + f output up; + false + in + Format.fprintf output "["; + fold_dirs ~dirs ~unit:(print Json_search.unit) ~page:(print Json_search.page) + ~init:true + >>= fun _ -> + Format.fprintf output "]"; + Ok () diff --git a/src/odoc/indexing.mli b/src/odoc/indexing.mli new file mode 100644 index 0000000000..a9f138abb9 --- /dev/null +++ b/src/odoc/indexing.mli @@ -0,0 +1,15 @@ +open Or_error + +val handle_file : + Fpath.t -> + unit:(Odoc_model.Lang.Compilation_unit.t -> 'a) -> + page:(Odoc_model.Lang.Page.t -> 'a) -> + ('a option, [> msg ]) result + +val compile : + resolver:'a -> + parent:'b -> + output:Fs.file -> + warnings_options:Odoc_model.Error.warnings_options -> + Fs.directory list -> + (unit, [> msg ]) result diff --git a/src/odoc/support_files.ml b/src/odoc/support_files.ml index 606e358bb7..24d5f4d44f 100644 --- a/src/odoc/support_files.ml +++ b/src/odoc/support_files.ml @@ -7,10 +7,11 @@ let should_include ~without_theme file = | _ -> true else true -let iter_files f ?(without_theme = false) output_directory = +let iter_files ~write ~copy ?(without_theme = false) ~search_files + output_directory = let file name content = let name = Fs.File.create ~directory:output_directory ~name in - f name content + write name content in let files = Odoc_html_support_files.file_list in List.iter @@ -18,16 +19,42 @@ let iter_files f ?(without_theme = false) output_directory = match Odoc_html_support_files.read f with | Some content when should_include ~without_theme f -> file f content | _ -> ()) - files + files; + List.iter + (fun filepath -> + let origin = filepath in + let destination = + Fs.File.create ~directory:output_directory + ~name:(Fpath.filename filepath) + in + copy ~origin ~destination) + search_files let write = - iter_files (fun name content -> + iter_files + ~write:(fun name content -> let dir = Fs.File.dirname name in Fs.Directory.mkdir_p dir; let name = Fs.File.to_string name in let channel = open_out name in output_string channel content; close_out channel) + ~copy:(fun ~origin ~destination -> + let dir = Fs.File.dirname destination in + Fs.Directory.mkdir_p dir; + let destination = Fs.File.to_string destination + and origin = Fs.File.to_string origin in + let oc = open_out destination and ic = open_in origin in + try + while true do + output_string oc (input_line ic ^ "\n") + done + with End_of_file -> + close_in ic; + close_out oc) let print_filenames = - iter_files (fun name _content -> print_endline (Fs.File.to_string name)) + iter_files + ~write:(fun name _content -> print_endline (Fs.File.to_string name)) + ~copy:(fun ~origin:_ ~destination -> + print_endline (Fs.File.to_string destination)) diff --git a/src/odoc/support_files.mli b/src/odoc/support_files.mli index f61a81b558..c04cf2028e 100644 --- a/src/odoc/support_files.mli +++ b/src/odoc/support_files.mli @@ -1,11 +1,13 @@ (** Copies odoc's support files (default theme and JS files) to a specified location. *) -val write : ?without_theme:bool -> Fs.Directory.t -> unit -(** [write ?without_theme output_dir] copies the support files to the - [output_dir]. If [without_theme] is [true] the theme will {e not} be - copied, the default value is [false]. *) +val write : + ?without_theme:bool -> search_files:Fs.File.t list -> Fs.Directory.t -> unit +(** [write ?without_theme search_files output_dir] copies the support and search + files to the [output_dir]. If [without_theme] is [true] the theme will {e + not} be copied, the default value is [false]. *) -val print_filenames : ?without_theme:bool -> Fs.Directory.t -> unit +val print_filenames : + ?without_theme:bool -> search_files:Fs.File.t list -> Fs.Directory.t -> unit (** Prints, to STDOUT, the names of the files that calling [Support_files.write] would output, one filename per line. *) diff --git a/src/search/dune b/src/search/dune new file mode 100644 index 0000000000..9f1c2d5f02 --- /dev/null +++ b/src/search/dune @@ -0,0 +1,4 @@ +(library + (name odoc_search) + (public_name odoc.search) + (libraries odoc_html odoc_model tyxml)) diff --git a/src/search/entry.ml b/src/search/entry.ml new file mode 100644 index 0000000000..13c00ab63b --- /dev/null +++ b/src/search/entry.ml @@ -0,0 +1,212 @@ +open Odoc_model.Lang +open Odoc_model.Paths + +type type_decl_entry = { + txt : string; + canonical : Path.Type.t option; + equation : TypeDecl.Equation.t; + representation : TypeDecl.Representation.t option; +} + +type exception_entry = { + args : TypeDecl.Constructor.argument; + res : TypeExpr.t option; +} + +type class_type_entry = { virtual_ : bool; params : TypeDecl.param list } + +type method_entry = { private_ : bool; virtual_ : bool; type_ : TypeExpr.t } + +type class_entry = { virtual_ : bool; params : TypeDecl.param list } + +type type_extension_entry = { + type_path : Path.Type.t; + type_params : TypeDecl.param list; + private_ : bool; +} + +type extension_constructor_entry = { + args : TypeDecl.Constructor.argument; + res : TypeExpr.t option; +} + +type constructor_entry = { + args : TypeDecl.Constructor.argument; + res : TypeExpr.t; +} + +type field_entry = { + mutable_ : bool; + type_ : TypeExpr.t; + parent_type : TypeExpr.t; +} + +type instance_variable_entry = { + mutable_ : bool; + virtual_ : bool; + type_ : TypeExpr.t; +} + +type doc_entry = Paragraph | Heading | CodeBlock | MathBlock | Verbatim + +type value_entry = { value : Value.value; type_ : TypeExpr.t } + +type extra = + | TypeDecl of type_decl_entry + | Module + | Value of value_entry + | Doc of doc_entry + | Exception of exception_entry + | Class_type of class_type_entry + | Method of method_entry + | Class of class_entry + | TypeExtension of type_extension_entry + | ExtensionConstructor of extension_constructor_entry + | ModuleType + | Constructor of constructor_entry + | Field of field_entry + +module Html = Tyxml.Html + +type t = { + id : Odoc_model.Paths.Identifier.Any.t; + doc : Odoc_model.Comment.docs; + extra : extra; +} + +let entry ~id ~doc ~extra = + let id = (id :> Odoc_model.Paths.Identifier.Any.t) in + { id; extra; doc } + +let varify_params = + List.mapi (fun i param -> + match param.TypeDecl.desc with + | Var name -> TypeExpr.Var name + | Any -> Var (Printf.sprintf "tv_%i" i)) + +let entry_of_constructor id_parent params (constructor : TypeDecl.Constructor.t) + = + let args = constructor.args in + let res = + match constructor.res with + | Some res -> res + | None -> + let params = varify_params params in + TypeExpr.Constr + ( `Identifier + ((id_parent :> Odoc_model.Paths.Identifier.Path.Type.t), false), + params ) + in + let extra = Constructor { args; res } in + entry ~id:constructor.id ~doc:constructor.doc ~extra + +let entry_of_field id_parent params (field : TypeDecl.Field.t) = + let params = varify_params params in + let parent_type = + TypeExpr.Constr + ( `Identifier + ((id_parent :> Odoc_model.Paths.Identifier.Path.Type.t), false), + params ) + in + let extra = + Field { mutable_ = field.mutable_; type_ = field.type_; parent_type } + in + entry ~id:field.id ~doc:field.doc ~extra + +let rec entries_of_docs id (d : Odoc_model.Comment.docs) = + List.concat_map (entries_of_doc id) d + +and entries_of_doc id d = + match d.value with + | `Paragraph _ -> [ entry ~id ~doc:[ d ] ~extra:(Doc Paragraph) ] + | `Tag _ -> [] + | `List (_, ds) -> + List.concat_map (entries_of_docs id) (ds :> Odoc_model.Comment.docs list) + | `Heading (_, lbl, _) -> [ entry ~id:lbl ~doc:[ d ] ~extra:(Doc Heading) ] + | `Modules _ -> [] + | `Code_block (_, _, o) -> + let o = + match o with + | None -> [] + | Some o -> entries_of_docs id (o :> Odoc_model.Comment.docs) + in + entry ~id ~doc:[ d ] ~extra:(Doc CodeBlock) :: o + | `Verbatim _ -> [ entry ~id ~doc:[ d ] ~extra:(Doc Verbatim) ] + | `Math_block _ -> [ entry ~id ~doc:[ d ] ~extra:(Doc MathBlock) ] + | `Table _ -> [] + +let entries_of_item id (x : Odoc_model.Fold.item) = + match x with + | CompilationUnit u -> ( + match u.content with + | Module m -> [ entry ~id:u.id ~doc:m.doc ~extra:Module ] + | Pack _ -> []) + | TypeDecl td -> + let txt = Render.text_of_typedecl td in + let extra = + TypeDecl + { + txt; + canonical = td.canonical; + equation = td.equation; + representation = td.representation; + } + in + let td_entry = entry ~id:td.id ~doc:td.doc ~extra in + let subtype_entries = + match td.representation with + | None -> [] + | Some (Variant li) -> + List.map (entry_of_constructor td.id td.equation.params) li + | Some (Record fields) -> + List.map (entry_of_field td.id td.equation.params) fields + | Some Extensible -> [] + in + td_entry :: subtype_entries + | Module m -> [ entry ~id:m.id ~doc:m.doc ~extra:Module ] + | Value v -> + let extra = Value { value = v.value; type_ = v.type_ } in + [ entry ~id:v.id ~doc:v.doc ~extra ] + | Exception exc -> + let extra = Exception { args = exc.args; res = exc.res } in + [ entry ~id:exc.id ~doc:exc.doc ~extra ] + | ClassType ct -> + let extra = Class_type { virtual_ = ct.virtual_; params = ct.params } in + [ entry ~id:ct.id ~doc:ct.doc ~extra ] + | Method m -> + let extra = + Method { virtual_ = m.virtual_; private_ = m.private_; type_ = m.type_ } + in + [ entry ~id:m.id ~doc:m.doc ~extra ] + | Class cl -> + let extra = Class { virtual_ = cl.virtual_; params = cl.params } in + [ entry ~id:cl.id ~doc:cl.doc ~extra ] + | Extension te -> ( + match te.constructors with + | [] -> [] + | c :: _ -> + (* Type extension do not have an ID yet... we use the first + constructor for the url. Unfortunately, this breaks the uniqueness + of the ID in the search index... *) + let type_entry = + let extra = + TypeExtension + { + type_path = te.type_path; + type_params = te.type_params; + private_ = te.private_; + } + in + entry ~id:c.id ~doc:te.doc ~extra + in + let extension_constructor (ext_constr : Extension.Constructor.t) = + let extra = + ExtensionConstructor + { args = ext_constr.args; res = ext_constr.res } + in + entry ~id:ext_constr.id ~doc:ext_constr.doc ~extra + in + type_entry :: List.map extension_constructor te.constructors) + | ModuleType mt -> [ entry ~id:mt.id ~doc:mt.doc ~extra:ModuleType ] + | Doc `Stop -> [] + | Doc (`Docs d) -> entries_of_docs id d diff --git a/src/search/entry.mli b/src/search/entry.mli new file mode 100644 index 0000000000..b82a96d50e --- /dev/null +++ b/src/search/entry.mli @@ -0,0 +1,76 @@ +open Odoc_model.Lang +open Odoc_model.Paths + +type type_decl_entry = { + txt : string; + canonical : Path.Type.t option; + equation : TypeDecl.Equation.t; + representation : TypeDecl.Representation.t option; +} + +type exception_entry = { + args : TypeDecl.Constructor.argument; + res : TypeExpr.t option; +} + +type class_type_entry = { virtual_ : bool; params : TypeDecl.param list } + +type method_entry = { private_ : bool; virtual_ : bool; type_ : TypeExpr.t } + +type class_entry = { virtual_ : bool; params : TypeDecl.param list } + +type type_extension_entry = { + type_path : Path.Type.t; + type_params : TypeDecl.param list; + private_ : bool; +} + +type extension_constructor_entry = { + args : TypeDecl.Constructor.argument; + res : TypeExpr.t option; +} + +type constructor_entry = { + args : TypeDecl.Constructor.argument; + res : TypeExpr.t; +} + +type field_entry = { + mutable_ : bool; + type_ : TypeExpr.t; + parent_type : TypeExpr.t; +} + +type instance_variable_entry = { + mutable_ : bool; + virtual_ : bool; + type_ : TypeExpr.t; +} + +type doc_entry = Paragraph | Heading | CodeBlock | MathBlock | Verbatim + +type value_entry = { value : Value.value; type_ : TypeExpr.t } + +type extra = + | TypeDecl of type_decl_entry + | Module + | Value of value_entry + | Doc of doc_entry + | Exception of exception_entry + | Class_type of class_type_entry + | Method of method_entry + | Class of class_entry + | TypeExtension of type_extension_entry + | ExtensionConstructor of extension_constructor_entry + | ModuleType + | Constructor of constructor_entry + | Field of field_entry + +type t = { + id : Odoc_model.Paths.Identifier.Any.t; + doc : Odoc_model.Comment.docs; + extra : extra; +} + +val entries_of_item : + Odoc_model.Paths.Identifier.Any.t -> Odoc_model.Fold.item -> t list diff --git a/src/search/json_display.ml b/src/search/json_display.ml new file mode 100644 index 0000000000..3fff4933a7 --- /dev/null +++ b/src/search/json_display.ml @@ -0,0 +1,124 @@ +module Html = Tyxml.Html + +let display_expression_rhs args res = + let open Odoc_model.Lang in + match res with + | Some res -> ( + " : " + ^ + match args with + | TypeDecl.Constructor.Tuple args -> + let type_ = + match args with + | _ :: _ :: _ -> TypeExpr.(Arrow (None, Tuple args, res)) + | [ arg ] -> TypeExpr.(Arrow (None, arg, res)) + | _ -> res + in + Render.text_of_type type_ + | TypeDecl.Constructor.Record fields -> + let fields = Render.text_of_record fields in + let res = Render.text_of_type res in + fields ^ " -> " ^ res) + | None -> ( + match args with + | TypeDecl.Constructor.Tuple args -> ( + match args with + | _ :: _ :: _ -> " of " ^ Render.text_of_type (TypeExpr.Tuple args) + | [ arg ] -> " of " ^ Render.text_of_type arg + | _ -> "") + | TypeDecl.Constructor.Record fields -> + let fields = Render.text_of_record fields in + " of " ^ fields) +let display_constructor_type args res = + let open Odoc_model.Lang in + match args with + | TypeDecl.Constructor.Tuple args -> + let type_ = + match args with + | _ :: _ :: _ -> TypeExpr.(Arrow (None, Tuple args, res)) + | [ arg ] -> TypeExpr.(Arrow (None, arg, res)) + | _ -> res + in + Render.text_of_type type_ + | TypeDecl.Constructor.Record fields -> + let fields = Render.text_of_record fields in + let res = Render.text_of_type res in + fields ^ " -> " ^ res + +let of_entry ({ id; doc; extra } : Entry.t) : Odoc_html.Json.json = + let j_url = `String (Render.url id) in + let kind_s = + match extra with + | TypeDecl _ -> "type" + | Module -> "module" + | Value _ -> "val" + | Doc _ -> "doc" + | Exception _ -> "exn" + | Class_type _ -> "class type" + | Method _ -> "method" + | Class _ -> "class" + | TypeExtension _ -> "type ext" + | ExtensionConstructor _ -> "extension constructor" + | ModuleType -> "module type" + | Constructor _ -> "constructor" + | Field _ -> "field" + in + let kind_html = + Html.span ~a:[ Html.a_class [ "entry-kind" ] ] [ Html.txt kind_s ] + in + let rhs = + let s = + match extra with + | TypeDecl { canonical = _; equation = _; representation = _; txt } -> + let segments = String.split_on_char '=' txt in + if List.length segments > 1 then + segments |> List.tl |> String.concat "=" |> String.trim + |> ( ^ ) " = " |> Option.some + else None + | Constructor { args; res } -> + Some (" : " ^ display_constructor_type args res) + | Field { mutable_ = _; type_; parent_type = _ } -> + Some (" : " ^ Render.text_of_type type_) + | Exception { args; res } -> Some (display_expression_rhs args res) + | Value { value = _; type_ } -> Some (" : " ^ Render.text_of_type type_) + | Module | Doc _ | Class_type _ | Method _ | Class _ | TypeExtension _ + | ExtensionConstructor _ | ModuleType -> + None + in + match s with + | None -> [] + | Some s -> [ Html.code ~a:[ Html.a_class [ "entry-rhs" ] ] [ Html.txt s ] ] + in + let title = + let prefixname, name = + let rec loop acc id = + match id with + | [] -> ("", "") + | [ name ] -> (acc, name) + | hd :: tl -> loop (acc ^ hd ^ ".") tl + in + let prefixname, name = + loop "" (Odoc_model.Paths.Identifier.fullname id) + in + ( Html.span ~a:[ Html.a_class [ "prefix-name" ] ] [ Html.txt prefixname ], + Html.span ~a:[ Html.a_class [ "entry-name" ] ] [ Html.txt name ] ) + in + Html.code + ~a:[ Html.a_class [ "entry-title" ] ] + ([ kind_html; prefixname; name ] @ rhs) + in + let comment = + let doc = Render.html_of_doc doc in + Html.div ~a:[ Html.a_class [ "entry-comment" ] ] [ doc ] + in + let container = + let class_ = String.map (function ' ' -> '-' | c -> c) kind_s in + Html.div + ~a:[ Html.a_class [ "search-entry"; class_ ] ] + (title :: [ comment ]) + in + `Object + [ + ("html", `String (Format.asprintf "%a" (Tyxml.Html.pp_elt ()) container)); + ("url", j_url); + ] diff --git a/src/search/json_display.mli b/src/search/json_display.mli new file mode 100644 index 0000000000..0c3c529a98 --- /dev/null +++ b/src/search/json_display.mli @@ -0,0 +1 @@ +val of_entry : Entry.t -> Odoc_html.Json.json diff --git a/src/search/json_search.ml b/src/search/json_search.ml new file mode 100644 index 0000000000..a7d716e755 --- /dev/null +++ b/src/search/json_search.ml @@ -0,0 +1,229 @@ +let json_of_args (args : Odoc_model.Lang.TypeDecl.Constructor.argument) = + match args with + | Tuple tel -> + `Object + [ + ("kind", `String "Tuple"); + ( "vals", + `Array (List.map (fun te -> `String (Render.text_of_type te)) tel) + ); + ] + | Record fl -> + `Object + [ + ("kind", `String "Record"); + ( "fields", + `Array + (List.map + (fun { + Odoc_model.Lang.TypeDecl.Field.id; + mutable_; + type_; + doc = _; + } -> + `Object + [ + ("name", `String (Odoc_model.Paths.Identifier.name id)); + ("mutable", `Bool mutable_); + ("type", `String (Render.text_of_type type_)); + ]) + fl) ); + ] + +let rec of_id x = + let open Odoc_model.Names in + let open Odoc_model.Paths.Identifier in + let ret kind name = + `Object [ ("kind", `String kind); ("name", `String name) ] + in + match x.iv with + | `Root (_, name) -> [ ret "Root" (ModuleName.to_string name) ] + | `Page (_, name) -> [ ret "Page" (PageName.to_string name) ] + | `LeafPage (_, name) -> [ ret "Page" (PageName.to_string name) ] + | `Module (parent, name) -> + ret "Module" (ModuleName.to_string name) :: of_id (parent :> t) + | `Parameter (parent, name) -> + ret "Parameter" (ModuleName.to_string name) :: of_id (parent :> t) + | `Result x -> of_id (x :> t) + | `ModuleType (parent, name) -> + ret "ModuleType" (ModuleTypeName.to_string name) :: of_id (parent :> t) + | `Type (parent, name) -> + ret "Type" (TypeName.to_string name) :: of_id (parent :> t) + | `CoreType name -> [ ret "CoreType" (TypeName.to_string name) ] + | `Constructor (parent, name) -> + ret "Constructor" (ConstructorName.to_string name) :: of_id (parent :> t) + | `Field (parent, name) -> + ret "Field" (FieldName.to_string name) :: of_id (parent :> t) + | `Extension (parent, name) -> + ret "Extension" (ExtensionName.to_string name) :: of_id (parent :> t) + | `Exception (parent, name) -> + ret "Exception" (ExceptionName.to_string name) :: of_id (parent :> t) + | `CoreException name -> + [ ret "CoreException" (ExceptionName.to_string name) ] + | `Value (parent, name) -> + ret "Value" (ValueName.to_string name) :: of_id (parent :> t) + | `Class (parent, name) -> + ret "Class" (ClassName.to_string name) :: of_id (parent :> t) + | `ClassType (parent, name) -> + ret "ClassType" (ClassTypeName.to_string name) :: of_id (parent :> t) + | `Method (parent, name) -> + ret "Method" (MethodName.to_string name) :: of_id (parent :> t) + | `InstanceVariable (parent, name) -> + ret "InstanceVariable" (InstanceVariableName.to_string name) + :: of_id (parent :> t) + | `Label (parent, name) -> + ret "Label" (LabelName.to_string name) :: of_id (parent :> t) + | `SourceDir _ | `SourceLocationMod _ | `SourceLocation _ | `SourcePage _ + | `SourceLocationInternal _ | `AssetFile _ -> + [ `Null ] +(* TODO *) + +let of_id n = `Array (List.rev @@ of_id (n :> Odoc_model.Paths.Identifier.t)) + +let of_doc (doc : Odoc_model.Comment.docs) = + let txt = Render.text_of_doc doc in + `String txt + +let of_entry ({ id; doc; extra } as entry : Entry.t) : Odoc_html.Json.json = + let j_id = of_id id in + let doc = of_doc doc in + let display = Json_display.of_entry entry in + let extra = + let return kind arr = `Object (("kind", `String kind) :: arr) in + match extra with + | TypeDecl { canonical = _; equation; representation = _; txt = _ } -> + let { + Odoc_model.Lang.TypeDecl.Equation.params = _; + private_; + manifest; + constraints; + } = + equation + in + let private_ = `Bool private_ in + let manifest = + match manifest with + | None -> `Null + | Some te -> `String (Render.text_of_type te) + in + let constraints = + `Array + (List.map + (fun (lhs, rhs) -> + `Object + [ + ("lhs", `String (Render.text_of_type lhs)); + ("rhs", `String (Render.text_of_type rhs)); + ]) + constraints) + in + return "TypeDecl" + [ + ("private", private_); + ("manifest", manifest); + ("constraints", constraints); + ] + | Module -> return "Module" [] + | Value { value = _; type_ } -> + return "Value" [ ("type", `String (Render.text_of_type type_)) ] + | Doc Paragraph -> return "Doc" [ ("subkind", `String "Paragraph") ] + | Doc Heading -> return "Doc" [ ("subkind", `String "Heading") ] + | Doc CodeBlock -> return "Doc" [ ("subkind", `String "CodeBlock") ] + | Doc MathBlock -> return "Doc" [ ("subkind", `String "MathBlock") ] + | Doc Verbatim -> return "Doc" [ ("subkind", `String "Verbatim") ] + | Exception { args; res } -> + let args = json_of_args args in + let res = + match res with + | None -> `Null + | Some res -> `String (Render.text_of_type res) + in + return "Exception" [ ("args", args); ("res", res) ] + | Class_type { virtual_; params = _ } -> + return "ClassType" [ ("virtual", `Bool virtual_) ] + | Method { private_; virtual_; type_ } -> + return "Method" + [ + ("virtual", `Bool virtual_); + ("private", `Bool private_); + ("type", `String (Render.text_of_type type_)); + ] + | Class { virtual_; params = _ } -> + return "Class" [ ("virtual", `Bool virtual_) ] + | TypeExtension { type_path = _; type_params = _; private_ } -> + (* TODO: include type_path and type_params *) + return "TypeExtension" [ ("private", `Bool private_) ] + | ExtensionConstructor { args; res } -> + let args = json_of_args args in + let res = + match res with + | None -> `Null + | Some res -> `String (Render.text_of_type res) + in + return "ExtensionConstructor" [ ("args", args); ("res", res) ] + | ModuleType -> return "ModuleType" [] + | Constructor { args; res } -> + let args = json_of_args args in + let res = `String (Render.text_of_type res) in + return "Constructor" [ ("args", args); ("res", res) ] + | Field { mutable_; type_; parent_type } -> + return "Field" + [ + ("mutable", `Bool mutable_); + ("type", `String (Render.text_of_type type_)); + ("parent_type", `String (Render.text_of_type parent_type)); + ] + in + `Object [ ("id", j_id); ("doc", doc); ("extra", extra); ("display", display) ] + +let output_json ppf first entries = + let output_json json = + let str = Odoc_html.Json.to_string json in + Format.fprintf ppf "%s\n" str + in + List.fold_left + (fun first entry -> + let json = of_entry entry in + if not first then Format.fprintf ppf ","; + output_json json; + false) + first entries + +let unit ppf u = + let f (first, id) i = + let entries = Entry.entries_of_item id i in + let id = + match i with + | CompilationUnit u -> (u.id :> Odoc_model.Paths.Identifier.t) + | TypeDecl _ -> id + | Module m -> (m.id :> Odoc_model.Paths.Identifier.t) + | Value _ -> id + | Exception _ -> id + | ClassType ct -> (ct.id :> Odoc_model.Paths.Identifier.t) + | Method _ -> id + | Class c -> (c.id :> Odoc_model.Paths.Identifier.t) + | Extension _ -> id + | ModuleType mt -> (mt.id :> Odoc_model.Paths.Identifier.t) + | Doc _ -> id + in + let first = output_json ppf first entries in + (first, id) + in + let _first = + Odoc_model.Fold.unit ~f + ( true, + (u.Odoc_model.Lang.Compilation_unit.id :> Odoc_model.Paths.Identifier.t) + ) + u + in + () + +let page ppf (page : Odoc_model.Lang.Page.t) = + let f first i = + let entries = + Entry.entries_of_item (page.name :> Odoc_model.Paths.Identifier.t) i + in + output_json ppf first entries + in + let _first = Odoc_model.Fold.page ~f true page in + () diff --git a/src/search/json_search.mli b/src/search/json_search.mli new file mode 100644 index 0000000000..2b132af07c --- /dev/null +++ b/src/search/json_search.mli @@ -0,0 +1,4 @@ +(** This module generates json intended to be consumed by search engines. *) + +val unit : Format.formatter -> Odoc_model.Lang.Compilation_unit.t -> unit +val page : Format.formatter -> Odoc_model.Lang.Page.t -> unit diff --git a/src/search/render.ml b/src/search/render.ml new file mode 100644 index 0000000000..a1403921cb --- /dev/null +++ b/src/search/render.ml @@ -0,0 +1,157 @@ +type html = Html_types.div Tyxml.Html.elt + +module Of_document = struct + (** Get plain text doc-comment from a doc comment *) + + let rec source s = + let token = function + | Odoc_document.Types.Source.Elt e -> inline e + | Tag (_, t) -> source t + in + String.concat "" @@ List.map token s + + and inline i = + let one o = + match o.Odoc_document.Types.Inline.desc with + | Text t -> t + | Entity "#45" -> "-" + | Entity "gt" -> ">" + | Entity e -> "&" ^ e + | Linebreak -> "\n" + | Styled (_, t) -> inline t + | Link (_, t) -> inline t + | InternalLink { content; _ } -> inline content + | Source s -> source s + | Math m -> m + | Raw_markup _ -> "" + in + String.concat "" @@ List.map one i + + let rec item i = + match i with + | Odoc_document.Types.Item.Text t -> block t + | Heading h -> heading h + | Declaration { content; _ } -> documented_src content + | Include { content; _ } -> include_ content + + and block b = + let one o = + match o.Odoc_document.Types.Block.desc with + | Inline i -> inline i + | Paragraph p -> inline p + | List (_, bl) -> String.concat "" @@ List.map block bl + | Description d -> description d + | Source (_, s) -> source s + | Math m -> m + | Verbatim v -> v + | Raw_markup _ -> "" + | Table _ -> "" + in + String.concat "" @@ List.map one b + + and description d = + let one { Odoc_document.Types.Description.key; definition; _ } = + inline key ^ block definition + in + String.concat "" @@ List.map one d + + and heading { title; _ } = inline title + + and documented_src d = + let one o = + match o with + | Odoc_document.Types.DocumentedSrc.Code c -> source c + | Documented { code; _ } -> inline code + | Nested { code; _ } -> documented_src code + | Subpage _ -> "" + | Alternative (Expansion { summary; _ }) -> source summary + in + String.concat "" @@ List.map one d + + and include_ { summary; _ } = source summary +end + +module Of_comments = struct + (** Get plain text doc-comment from a doc comment *) + + let get_value x = x.Odoc_model.Location_.value + + let rec string_of_doc (doc : Odoc_model.Comment.docs) = + doc |> List.map get_value + |> List.map s_of_block_element + |> String.concat "\n" + + and s_of_block_element (be : Odoc_model.Comment.block_element) = + match be with + | `Paragraph is -> inlines is + | `Tag _ -> "" + | `List (_, ls) -> + List.map (fun x -> x |> List.map get_value |> List.map nestable) ls + |> List.concat |> String.concat " " + | `Heading (_, _, h) -> inlines h + | `Modules _ -> "" + | `Code_block (_, s, _todo) -> s |> get_value + | `Verbatim v -> v + | `Math_block m -> m + | `Table _ -> (* TODO *) "" + + and nestable (n : Odoc_model.Comment.nestable_block_element) = + s_of_block_element (n :> Odoc_model.Comment.block_element) + + and inlines is = + is |> List.map get_value |> List.map inline |> String.concat "" + + and inline (i : Odoc_model.Comment.inline_element) = + match i with + | `Code_span s -> s + | `Word w -> w + | `Math_span m -> m + | `Space -> " " + | `Reference (_, c) -> link_content c + | `Link (_, c) -> link_content c + | `Styled (_, b) -> inlines b + | `Raw_markup (_, _) -> "" + + and link_content l = + l |> List.map get_value + |> List.map non_link_inline_element + |> String.concat "" + + and non_link_inline_element (n : Odoc_model.Comment.non_link_inline_element) = + inline (n :> Odoc_model.Comment.inline_element) +end + +let text_of_type te = + let te_text = Odoc_document.ML.type_expr te in + let te_doc = Odoc_document.Codefmt.render te_text in + Of_document.source te_doc + +let text_of_doc doc = Of_comments.string_of_doc doc + +let config = + Odoc_html.Config.v ~search_result:true ~semantic_uris:false ~indent:false + ~flat:false ~open_details:false ~as_json:false ~search_files:[] () + +let html_of_doc doc = + Tyxml.Html.div ~a:[] + @@ Odoc_html.Generator.doc ~config ~xref_base_uri:"" + @@ Odoc_document.Comment.to_ir doc + +let url id = + match + Odoc_document.Url.from_identifier ~stop_before:false + (id :> Odoc_model.Paths.Identifier.t) + with + | Ok url -> + let url = Odoc_html.Link.href ~config ~resolve:(Base "") url in + url + | Error _ -> assert false + +let text_of_record fields = + let te_text = Odoc_document.ML.record fields in + Of_document.documented_src te_text +let text_of_typedecl td = + let te_text = + Odoc_document.ML.type_decl (Odoc_model.Lang.Signature.Ordinary, td) + in + Of_document.item te_text diff --git a/src/search/render.mli b/src/search/render.mli new file mode 100644 index 0000000000..0f637735d9 --- /dev/null +++ b/src/search/render.mli @@ -0,0 +1,12 @@ +type html = Html_types.div Tyxml.Html.elt + +val text_of_type : Odoc_model.Lang.TypeExpr.t -> string + +val html_of_doc : Odoc_model.Comment.docs -> html +val text_of_doc : Odoc_model.Comment.docs -> string + +val text_of_typedecl : Odoc_model.Lang.TypeDecl.t -> string + +val text_of_record : Odoc_model.Lang.TypeDecl.Field.t list -> string + +val url : Odoc_model.Paths.Identifier.Any.t -> string diff --git a/test/generators/html/Functor-F1.html b/test/generators/html/Functor-F1.html index b582623cda..619cdb7995 100644 --- a/test/generators/html/Functor-F1.html +++ b/test/generators/html/Functor-F1.html @@ -13,11 +13,13 @@

Module Functor.F1

- +
+ +

Parameters

diff --git a/test/generators/html/Functor-F2.html b/test/generators/html/Functor-F2.html index 844c9ca3c0..75bd311dc1 100644 --- a/test/generators/html/Functor-F2.html +++ b/test/generators/html/Functor-F2.html @@ -13,11 +13,13 @@

Module Functor.F2

- +
+ +

Parameters

diff --git a/test/generators/html/Functor-F3.html b/test/generators/html/Functor-F3.html index 2e65ab6665..d9991c9244 100644 --- a/test/generators/html/Functor-F3.html +++ b/test/generators/html/Functor-F3.html @@ -13,11 +13,13 @@

Module Functor.F3

- +
+ +

Parameters

diff --git a/test/generators/html/Functor-F4.html b/test/generators/html/Functor-F4.html index 7d34da42ab..0792222adc 100644 --- a/test/generators/html/Functor-F4.html +++ b/test/generators/html/Functor-F4.html @@ -13,11 +13,13 @@

Module Functor.F4

- +
+ +

Parameters

diff --git a/test/generators/html/Functor-F5.html b/test/generators/html/Functor-F5.html index 21a4496828..8043c56398 100644 --- a/test/generators/html/Functor-F5.html +++ b/test/generators/html/Functor-F5.html @@ -13,11 +13,13 @@

Module Functor.F5

- +
+ +

Parameters

diff --git a/test/generators/html/Functor-module-type-S1.html b/test/generators/html/Functor-module-type-S1.html index 8f977a711a..7d592cc56d 100644 --- a/test/generators/html/Functor-module-type-S1.html +++ b/test/generators/html/Functor-module-type-S1.html @@ -13,11 +13,13 @@

Module type Functor.S1

- +
+ +

Parameters

diff --git a/test/generators/html/Functor2-X.html b/test/generators/html/Functor2-X.html index 3dfd4b4322..9645c93d46 100644 --- a/test/generators/html/Functor2-X.html +++ b/test/generators/html/Functor2-X.html @@ -13,11 +13,13 @@

Module Functor2.X

- +
+ +

Parameters

diff --git a/test/generators/html/Functor2-module-type-XF.html b/test/generators/html/Functor2-module-type-XF.html index 10f9879263..078a8a399d 100644 --- a/test/generators/html/Functor2-module-type-XF.html +++ b/test/generators/html/Functor2-module-type-XF.html @@ -14,11 +14,13 @@

Module type Functor2.XF

- +
+ +

Parameters

diff --git a/test/generators/html/Include_sections-module-type-Something.html b/test/generators/html/Include_sections-module-type-Something.html index ffd1e615c2..2aa8d79f30 100644 --- a/test/generators/html/Include_sections-module-type-Something.html +++ b/test/generators/html/Include_sections-module-type-Something.html @@ -15,13 +15,15 @@

Module type Include_sections.Something

A module type.

- +
diff --git a/test/generators/html/Include_sections.html b/test/generators/html/Include_sections.html index 2bfc6ac8e8..7689a0461d 100644 --- a/test/generators/html/Include_sections.html +++ b/test/generators/html/Include_sections.html @@ -11,27 +11,29 @@

Module Include_sections

- +
diff --git a/test/generators/html/Labels-A.html b/test/generators/html/Labels-A.html index b7eb026d73..72f5e4cff6 100644 --- a/test/generators/html/Labels-A.html +++ b/test/generators/html/Labels-A.html @@ -13,9 +13,11 @@

Module Labels.A

- +

Attached to module

diff --git a/test/generators/html/Labels-class-c.html b/test/generators/html/Labels-class-c.html index 1b56931814..94d3ec9867 100644 --- a/test/generators/html/Labels-class-c.html +++ b/test/generators/html/Labels-class-c.html @@ -13,8 +13,11 @@

Class Labels.c

- +

Attached to class

diff --git a/test/generators/html/Labels-class-type-cs.html b/test/generators/html/Labels-class-type-cs.html index 4750770d18..57e3d80ebb 100644 --- a/test/generators/html/Labels-class-type-cs.html +++ b/test/generators/html/Labels-class-type-cs.html @@ -13,9 +13,11 @@

Class type Labels.cs

- +

Attached to class type

diff --git a/test/generators/html/Labels-module-type-S.html b/test/generators/html/Labels-module-type-S.html index 02c3292cb8..1be1e47f1e 100644 --- a/test/generators/html/Labels-module-type-S.html +++ b/test/generators/html/Labels-module-type-S.html @@ -13,9 +13,11 @@

Module type Labels.S

- +

Attached to module type

diff --git a/test/generators/html/Labels.html b/test/generators/html/Labels.html index ee1fc3d2c4..6689b6fe65 100644 --- a/test/generators/html/Labels.html +++ b/test/generators/html/Labels.html @@ -10,11 +10,13 @@

Module Labels

- +

Attached to unit

Attached to nothing

diff --git a/test/generators/html/Markup.html b/test/generators/html/Markup.html index cd38385dca..394ac5db27 100644 --- a/test/generators/html/Markup.html +++ b/test/generators/html/Markup.html @@ -33,34 +33,36 @@

Module Markup

Here, we test the rendering of comment markup.

- +

Sections

Let's get these done first, because sections will be used to break diff --git a/test/generators/html/Module_type_alias-module-type-B.html b/test/generators/html/Module_type_alias-module-type-B.html index be45fd002e..3d31c08286 100644 --- a/test/generators/html/Module_type_alias-module-type-B.html +++ b/test/generators/html/Module_type_alias-module-type-B.html @@ -14,11 +14,13 @@

Module type Module_type_alias.B

- +
+ +

Parameters

diff --git a/test/generators/html/Module_type_alias-module-type-E.html b/test/generators/html/Module_type_alias-module-type-E.html index 63048fef0f..0fba8fbaff 100644 --- a/test/generators/html/Module_type_alias-module-type-E.html +++ b/test/generators/html/Module_type_alias-module-type-E.html @@ -14,11 +14,13 @@

Module type Module_type_alias.E

- +
+ +

Parameters

diff --git a/test/generators/html/Module_type_alias-module-type-G.html b/test/generators/html/Module_type_alias-module-type-G.html index bf773d6342..4141ad9192 100644 --- a/test/generators/html/Module_type_alias-module-type-G.html +++ b/test/generators/html/Module_type_alias-module-type-G.html @@ -14,11 +14,13 @@

Module type Module_type_alias.G

- +
+ +

Parameters

diff --git a/test/generators/html/Nested-F-argument-1-Arg1.html b/test/generators/html/Nested-F-argument-1-Arg1.html index c71d953347..c70a36131b 100644 --- a/test/generators/html/Nested-F-argument-1-Arg1.html +++ b/test/generators/html/Nested-F-argument-1-Arg1.html @@ -15,10 +15,13 @@

Parameter F.Arg1

- +
+ +

Type

diff --git a/test/generators/html/Nested-F-argument-2-Arg2.html b/test/generators/html/Nested-F-argument-2-Arg2.html index 86df8b8b7f..1ef6a43e49 100644 --- a/test/generators/html/Nested-F-argument-2-Arg2.html +++ b/test/generators/html/Nested-F-argument-2-Arg2.html @@ -15,7 +15,9 @@

Parameter F.Arg2

- +
+ +

Type

diff --git a/test/generators/html/Nested-F.html b/test/generators/html/Nested-F.html index 34877afd6d..db74df8a58 100644 --- a/test/generators/html/Nested-F.html +++ b/test/generators/html/Nested-F.html @@ -14,12 +14,14 @@

Module Nested.F

This is a functor F.

Some additional comments.

- +
+ +

Parameters

diff --git a/test/generators/html/Nested-X.html b/test/generators/html/Nested-X.html index ebd1b378b1..66bf0e7952 100644 --- a/test/generators/html/Nested-X.html +++ b/test/generators/html/Nested-X.html @@ -14,10 +14,13 @@

Module Nested.X

This is module X.

Some additional comments.

- +
+ +

Type

diff --git a/test/generators/html/Nested-class-z.html b/test/generators/html/Nested-class-z.html index 9b317ef6c4..cc493e813e 100644 --- a/test/generators/html/Nested-class-z.html +++ b/test/generators/html/Nested-class-z.html @@ -14,8 +14,10 @@

Class Nested.z

This is class z.

Some additional comments.

- +
+ +
diff --git a/test/generators/html/Nested-module-type-Y.html b/test/generators/html/Nested-module-type-Y.html index 0f847780ee..f5be1176e8 100644 --- a/test/generators/html/Nested-module-type-Y.html +++ b/test/generators/html/Nested-module-type-Y.html @@ -14,10 +14,13 @@

Module type Nested.Y

This is module type Y.

Some additional comments.

- +
+ +

Type

diff --git a/test/generators/html/Nested.html b/test/generators/html/Nested.html index 6a490bf140..3f52e37d7a 100644 --- a/test/generators/html/Nested.html +++ b/test/generators/html/Nested.html @@ -11,13 +11,15 @@

Module Nested

This comment needs to be here before #235 is fixed.

- +
+ +

Module

diff --git a/test/generators/html/Ocamlary-Aliases.html b/test/generators/html/Ocamlary-Aliases.html index 171b0d549f..a7831cc14b 100644 --- a/test/generators/html/Ocamlary-Aliases.html +++ b/test/generators/html/Ocamlary-Aliases.html @@ -15,8 +15,10 @@

Module Ocamlary.Aliases

Let's imitate jst's layout.

- +
diff --git a/test/generators/html/Ocamlary-Dep12.html b/test/generators/html/Ocamlary-Dep12.html index 575de18470..e6d69c9ae2 100644 --- a/test/generators/html/Ocamlary-Dep12.html +++ b/test/generators/html/Ocamlary-Dep12.html @@ -14,11 +14,13 @@

Module Ocamlary.Dep12

- +
+ +

Parameters

diff --git a/test/generators/html/Ocamlary-Dep2.html b/test/generators/html/Ocamlary-Dep2.html index b8bd5e9613..61f91ba5d8 100644 --- a/test/generators/html/Ocamlary-Dep2.html +++ b/test/generators/html/Ocamlary-Dep2.html @@ -14,11 +14,13 @@

Module Ocamlary.Dep2

- +
+ +

Parameters

diff --git a/test/generators/html/Ocamlary-Dep5.html b/test/generators/html/Ocamlary-Dep5.html index 8c80fff452..377724d8de 100644 --- a/test/generators/html/Ocamlary-Dep5.html +++ b/test/generators/html/Ocamlary-Dep5.html @@ -14,11 +14,13 @@

Module Ocamlary.Dep5

- +
+ +

Parameters

diff --git a/test/generators/html/Ocamlary-Dep7.html b/test/generators/html/Ocamlary-Dep7.html index 99c36fcb27..63e1226e03 100644 --- a/test/generators/html/Ocamlary-Dep7.html +++ b/test/generators/html/Ocamlary-Dep7.html @@ -14,11 +14,13 @@

Module Ocamlary.Dep7

- +
+ +

Parameters

diff --git a/test/generators/html/Ocamlary-Dep9.html b/test/generators/html/Ocamlary-Dep9.html index eef699639b..7679bb12f2 100644 --- a/test/generators/html/Ocamlary-Dep9.html +++ b/test/generators/html/Ocamlary-Dep9.html @@ -14,11 +14,13 @@

Module Ocamlary.Dep9

- +
+ +

Parameters

diff --git a/test/generators/html/Ocamlary-FunctorTypeOf.html b/test/generators/html/Ocamlary-FunctorTypeOf.html index 84d05ce6cc..4c836584dc 100644 --- a/test/generators/html/Ocamlary-FunctorTypeOf.html +++ b/test/generators/html/Ocamlary-FunctorTypeOf.html @@ -15,11 +15,13 @@

Module Ocamlary.FunctorTypeOf

This comment is for FunctorTypeOf.

- +
+ +

Parameters

diff --git a/test/generators/html/Ocamlary-Recollection.html b/test/generators/html/Ocamlary-Recollection.html index 8fbc7722c4..458d72cbd3 100644 --- a/test/generators/html/Ocamlary-Recollection.html +++ b/test/generators/html/Ocamlary-Recollection.html @@ -14,11 +14,13 @@

Module Ocamlary.Recollection

- +
+ +

Parameters

diff --git a/test/generators/html/Ocamlary-With7.html b/test/generators/html/Ocamlary-With7.html index 2cd8ecaee9..1bfb6542ec 100644 --- a/test/generators/html/Ocamlary-With7.html +++ b/test/generators/html/Ocamlary-With7.html @@ -14,11 +14,13 @@

Module Ocamlary.With7

- +
+ +

Parameters

diff --git a/test/generators/html/Ocamlary-module-type-SuperSig-module-type-SubSigA.html b/test/generators/html/Ocamlary-module-type-SuperSig-module-type-SubSigA.html index adf812aba4..e714ad7bcf 100644 --- a/test/generators/html/Ocamlary-module-type-SuperSig-module-type-SubSigA.html +++ b/test/generators/html/Ocamlary-module-type-SuperSig-module-type-SubSigA.html @@ -16,12 +16,14 @@

Module type SuperSig.SubSigA

- +

A Labeled Section Header Inside of a Signature diff --git a/test/generators/html/Ocamlary-module-type-SuperSig-module-type-SubSigB.html b/test/generators/html/Ocamlary-module-type-SuperSig-module-type-SubSigB.html index 090e14fbc7..94021da9b0 100644 --- a/test/generators/html/Ocamlary-module-type-SuperSig-module-type-SubSigB.html +++ b/test/generators/html/Ocamlary-module-type-SuperSig-module-type-SubSigB.html @@ -16,14 +16,16 @@

Module type SuperSig.SubSigB

- +

Another Labeled Section Header Inside of a Signature diff --git a/test/generators/html/Ocamlary.html b/test/generators/html/Ocamlary.html index 167e5d6b2b..ff34c2ad31 100644 --- a/test/generators/html/Ocamlary.html +++ b/test/generators/html/Ocamlary.html @@ -27,49 +27,51 @@

Module Ocamlary

  • author David Sheets
  • - +

    You may find more information about this HTML documentation renderer at diff --git a/test/generators/html/Recent-module-type-S1.html b/test/generators/html/Recent-module-type-S1.html index fc6b3a9db8..19d3e514a3 100644 --- a/test/generators/html/Recent-module-type-S1.html +++ b/test/generators/html/Recent-module-type-S1.html @@ -13,11 +13,13 @@

    Module type Recent.S1

    - +
    + +

    Parameters

    diff --git a/test/generators/html/Recent_impl-module-type-S-F.html b/test/generators/html/Recent_impl-module-type-S-F.html index 203541bc53..02a9f7f483 100644 --- a/test/generators/html/Recent_impl-module-type-S-F.html +++ b/test/generators/html/Recent_impl-module-type-S-F.html @@ -14,11 +14,13 @@

    Module S.F

    - +
    + +

    Parameters

    diff --git a/test/generators/html/Section.html b/test/generators/html/Section.html index 45cbbf2113..57891b034d 100644 --- a/test/generators/html/Section.html +++ b/test/generators/html/Section.html @@ -14,27 +14,30 @@

    Module Section

    in it.

    - +

    Empty section diff --git a/test/generators/html/Toplevel_comments-Comments_on_open.html b/test/generators/html/Toplevel_comments-Comments_on_open.html index 3a09f82c09..2a8676ddb2 100644 --- a/test/generators/html/Toplevel_comments-Comments_on_open.html +++ b/test/generators/html/Toplevel_comments-Comments_on_open.html @@ -16,7 +16,9 @@

    Module Toplevel_comments.Comments_on_open

    - +
    + +
    diff --git a/test/generators/html/mld.html b/test/generators/html/mld.html index 54b100972a..f3851a4412 100644 --- a/test/generators/html/mld.html +++ b/test/generators/html/mld.html @@ -13,15 +13,17 @@

    Mld Page

    title, like modules and other pages generated fully by odoc do.

    It will have a TOC generated from section headings.

    - +

    Section

    This is a section.

    Another paragraph in section.

    diff --git a/test/index/dune b/test/index/dune new file mode 100644 index 0000000000..9a0e1c5412 --- /dev/null +++ b/test/index/dune @@ -0,0 +1,9 @@ +; Tests related to linking to source code + +(env + (_ + (binaries + (../odoc_print/odoc_print.exe as odoc_print)))) + +(cram + (deps %{bin:odoc} %{bin:odoc_print})) diff --git a/test/index/index_command.t/fuse.js.js b/test/index/index_command.t/fuse.js.js new file mode 100644 index 0000000000..42e7d3b7f0 --- /dev/null +++ b/test/index/index_command.t/fuse.js.js @@ -0,0 +1,2240 @@ +/** + * Fuse.js v6.6.2 - Lightweight fuzzy-search (http://fusejs.io) + * + * Copyright (c) 2022 Kiro Risk (http://kiro.me) + * All Rights Reserved. Apache Software License 2.0 + * + * http://www.apache.org/licenses/LICENSE-2.0 + */ + +(function (global, factory) { + typeof exports === 'object' && typeof module !== 'undefined' ? module.exports = factory() : + typeof define === 'function' && define.amd ? define(factory) : + (global = typeof globalThis !== 'undefined' ? globalThis : global || self, global.Fuse = factory()); +})(this, (function () { 'use strict'; + + function ownKeys(object, enumerableOnly) { + var keys = Object.keys(object); + + if (Object.getOwnPropertySymbols) { + var symbols = Object.getOwnPropertySymbols(object); + enumerableOnly && (symbols = symbols.filter(function (sym) { + return Object.getOwnPropertyDescriptor(object, sym).enumerable; + })), keys.push.apply(keys, symbols); + } + + return keys; + } + + function _objectSpread2(target) { + for (var i = 1; i < arguments.length; i++) { + var source = null != arguments[i] ? arguments[i] : {}; + i % 2 ? ownKeys(Object(source), !0).forEach(function (key) { + _defineProperty(target, key, source[key]); + }) : Object.getOwnPropertyDescriptors ? Object.defineProperties(target, Object.getOwnPropertyDescriptors(source)) : ownKeys(Object(source)).forEach(function (key) { + Object.defineProperty(target, key, Object.getOwnPropertyDescriptor(source, key)); + }); + } + + return target; + } + + function _typeof(obj) { + "@babel/helpers - typeof"; + + return _typeof = "function" == typeof Symbol && "symbol" == typeof Symbol.iterator ? function (obj) { + return typeof obj; + } : function (obj) { + return obj && "function" == typeof Symbol && obj.constructor === Symbol && obj !== Symbol.prototype ? "symbol" : typeof obj; + }, _typeof(obj); + } + + function _classCallCheck(instance, Constructor) { + if (!(instance instanceof Constructor)) { + throw new TypeError("Cannot call a class as a function"); + } + } + + function _defineProperties(target, props) { + for (var i = 0; i < props.length; i++) { + var descriptor = props[i]; + descriptor.enumerable = descriptor.enumerable || false; + descriptor.configurable = true; + if ("value" in descriptor) descriptor.writable = true; + Object.defineProperty(target, descriptor.key, descriptor); + } + } + + function _createClass(Constructor, protoProps, staticProps) { + if (protoProps) _defineProperties(Constructor.prototype, protoProps); + if (staticProps) _defineProperties(Constructor, staticProps); + Object.defineProperty(Constructor, "prototype", { + writable: false + }); + return Constructor; + } + + function _defineProperty(obj, key, value) { + if (key in obj) { + Object.defineProperty(obj, key, { + value: value, + enumerable: true, + configurable: true, + writable: true + }); + } else { + obj[key] = value; + } + + return obj; + } + + function _inherits(subClass, superClass) { + if (typeof superClass !== "function" && superClass !== null) { + throw new TypeError("Super expression must either be null or a function"); + } + + Object.defineProperty(subClass, "prototype", { + value: Object.create(superClass && superClass.prototype, { + constructor: { + value: subClass, + writable: true, + configurable: true + } + }), + writable: false + }); + if (superClass) _setPrototypeOf(subClass, superClass); + } + + function _getPrototypeOf(o) { + _getPrototypeOf = Object.setPrototypeOf ? Object.getPrototypeOf : function _getPrototypeOf(o) { + return o.__proto__ || Object.getPrototypeOf(o); + }; + return _getPrototypeOf(o); + } + + function _setPrototypeOf(o, p) { + _setPrototypeOf = Object.setPrototypeOf || function _setPrototypeOf(o, p) { + o.__proto__ = p; + return o; + }; + + return _setPrototypeOf(o, p); + } + + function _isNativeReflectConstruct() { + if (typeof Reflect === "undefined" || !Reflect.construct) return false; + if (Reflect.construct.sham) return false; + if (typeof Proxy === "function") return true; + + try { + Boolean.prototype.valueOf.call(Reflect.construct(Boolean, [], function () {})); + return true; + } catch (e) { + return false; + } + } + + function _assertThisInitialized(self) { + if (self === void 0) { + throw new ReferenceError("this hasn't been initialised - super() hasn't been called"); + } + + return self; + } + + function _possibleConstructorReturn(self, call) { + if (call && (typeof call === "object" || typeof call === "function")) { + return call; + } else if (call !== void 0) { + throw new TypeError("Derived constructors may only return object or undefined"); + } + + return _assertThisInitialized(self); + } + + function _createSuper(Derived) { + var hasNativeReflectConstruct = _isNativeReflectConstruct(); + + return function _createSuperInternal() { + var Super = _getPrototypeOf(Derived), + result; + + if (hasNativeReflectConstruct) { + var NewTarget = _getPrototypeOf(this).constructor; + + result = Reflect.construct(Super, arguments, NewTarget); + } else { + result = Super.apply(this, arguments); + } + + return _possibleConstructorReturn(this, result); + }; + } + + function _toConsumableArray(arr) { + return _arrayWithoutHoles(arr) || _iterableToArray(arr) || _unsupportedIterableToArray(arr) || _nonIterableSpread(); + } + + function _arrayWithoutHoles(arr) { + if (Array.isArray(arr)) return _arrayLikeToArray(arr); + } + + function _iterableToArray(iter) { + if (typeof Symbol !== "undefined" && iter[Symbol.iterator] != null || iter["@@iterator"] != null) return Array.from(iter); + } + + function _unsupportedIterableToArray(o, minLen) { + if (!o) return; + if (typeof o === "string") return _arrayLikeToArray(o, minLen); + var n = Object.prototype.toString.call(o).slice(8, -1); + if (n === "Object" && o.constructor) n = o.constructor.name; + if (n === "Map" || n === "Set") return Array.from(o); + if (n === "Arguments" || /^(?:Ui|I)nt(?:8|16|32)(?:Clamped)?Array$/.test(n)) return _arrayLikeToArray(o, minLen); + } + + function _arrayLikeToArray(arr, len) { + if (len == null || len > arr.length) len = arr.length; + + for (var i = 0, arr2 = new Array(len); i < len; i++) arr2[i] = arr[i]; + + return arr2; + } + + function _nonIterableSpread() { + throw new TypeError("Invalid attempt to spread non-iterable instance.\nIn order to be iterable, non-array objects must have a [Symbol.iterator]() method."); + } + + function isArray(value) { + return !Array.isArray ? getTag(value) === '[object Array]' : Array.isArray(value); + } // Adapted from: https://github.com/lodash/lodash/blob/master/.internal/baseToString.js + + var INFINITY = 1 / 0; + function baseToString(value) { + // Exit early for strings to avoid a performance hit in some environments. + if (typeof value == 'string') { + return value; + } + + var result = value + ''; + return result == '0' && 1 / value == -INFINITY ? '-0' : result; + } + function toString(value) { + return value == null ? '' : baseToString(value); + } + function isString(value) { + return typeof value === 'string'; + } + function isNumber(value) { + return typeof value === 'number'; + } // Adapted from: https://github.com/lodash/lodash/blob/master/isBoolean.js + + function isBoolean(value) { + return value === true || value === false || isObjectLike(value) && getTag(value) == '[object Boolean]'; + } + function isObject(value) { + return _typeof(value) === 'object'; + } // Checks if `value` is object-like. + + function isObjectLike(value) { + return isObject(value) && value !== null; + } + function isDefined(value) { + return value !== undefined && value !== null; + } + function isBlank(value) { + return !value.trim().length; + } // Gets the `toStringTag` of `value`. + // Adapted from: https://github.com/lodash/lodash/blob/master/.internal/getTag.js + + function getTag(value) { + return value == null ? value === undefined ? '[object Undefined]' : '[object Null]' : Object.prototype.toString.call(value); + } + + var EXTENDED_SEARCH_UNAVAILABLE = 'Extended search is not available'; + var INCORRECT_INDEX_TYPE = "Incorrect 'index' type"; + var LOGICAL_SEARCH_INVALID_QUERY_FOR_KEY = function LOGICAL_SEARCH_INVALID_QUERY_FOR_KEY(key) { + return "Invalid value for key ".concat(key); + }; + var PATTERN_LENGTH_TOO_LARGE = function PATTERN_LENGTH_TOO_LARGE(max) { + return "Pattern length exceeds max of ".concat(max, "."); + }; + var MISSING_KEY_PROPERTY = function MISSING_KEY_PROPERTY(name) { + return "Missing ".concat(name, " property in key"); + }; + var INVALID_KEY_WEIGHT_VALUE = function INVALID_KEY_WEIGHT_VALUE(key) { + return "Property 'weight' in key '".concat(key, "' must be a positive integer"); + }; + + var hasOwn = Object.prototype.hasOwnProperty; + + var KeyStore = /*#__PURE__*/function () { + function KeyStore(keys) { + var _this = this; + + _classCallCheck(this, KeyStore); + + this._keys = []; + this._keyMap = {}; + var totalWeight = 0; + keys.forEach(function (key) { + var obj = createKey(key); + totalWeight += obj.weight; + + _this._keys.push(obj); + + _this._keyMap[obj.id] = obj; + totalWeight += obj.weight; + }); // Normalize weights so that their sum is equal to 1 + + this._keys.forEach(function (key) { + key.weight /= totalWeight; + }); + } + + _createClass(KeyStore, [{ + key: "get", + value: function get(keyId) { + return this._keyMap[keyId]; + } + }, { + key: "keys", + value: function keys() { + return this._keys; + } + }, { + key: "toJSON", + value: function toJSON() { + return JSON.stringify(this._keys); + } + }]); + + return KeyStore; + }(); + function createKey(key) { + var path = null; + var id = null; + var src = null; + var weight = 1; + var getFn = null; + + if (isString(key) || isArray(key)) { + src = key; + path = createKeyPath(key); + id = createKeyId(key); + } else { + if (!hasOwn.call(key, 'name')) { + throw new Error(MISSING_KEY_PROPERTY('name')); + } + + var name = key.name; + src = name; + + if (hasOwn.call(key, 'weight')) { + weight = key.weight; + + if (weight <= 0) { + throw new Error(INVALID_KEY_WEIGHT_VALUE(name)); + } + } + + path = createKeyPath(name); + id = createKeyId(name); + getFn = key.getFn; + } + + return { + path: path, + id: id, + weight: weight, + src: src, + getFn: getFn + }; + } + function createKeyPath(key) { + return isArray(key) ? key : key.split('.'); + } + function createKeyId(key) { + return isArray(key) ? key.join('.') : key; + } + + function get(obj, path) { + var list = []; + var arr = false; + + var deepGet = function deepGet(obj, path, index) { + if (!isDefined(obj)) { + return; + } + + if (!path[index]) { + // If there's no path left, we've arrived at the object we care about. + list.push(obj); + } else { + var key = path[index]; + var value = obj[key]; + + if (!isDefined(value)) { + return; + } // If we're at the last value in the path, and if it's a string/number/bool, + // add it to the list + + + if (index === path.length - 1 && (isString(value) || isNumber(value) || isBoolean(value))) { + list.push(toString(value)); + } else if (isArray(value)) { + arr = true; // Search each item in the array. + + for (var i = 0, len = value.length; i < len; i += 1) { + deepGet(value[i], path, index + 1); + } + } else if (path.length) { + // An object. Recurse further. + deepGet(value, path, index + 1); + } + } + }; // Backwards compatibility (since path used to be a string) + + + deepGet(obj, isString(path) ? path.split('.') : path, 0); + return arr ? list : list[0]; + } + + var MatchOptions = { + // Whether the matches should be included in the result set. When `true`, each record in the result + // set will include the indices of the matched characters. + // These can consequently be used for highlighting purposes. + includeMatches: false, + // When `true`, the matching function will continue to the end of a search pattern even if + // a perfect match has already been located in the string. + findAllMatches: false, + // Minimum number of characters that must be matched before a result is considered a match + minMatchCharLength: 1 + }; + var BasicOptions = { + // When `true`, the algorithm continues searching to the end of the input even if a perfect + // match is found before the end of the same input. + isCaseSensitive: false, + // When true, the matching function will continue to the end of a search pattern even if + includeScore: false, + // List of properties that will be searched. This also supports nested properties. + keys: [], + // Whether to sort the result list, by score + shouldSort: true, + // Default sort function: sort by ascending score, ascending index + sortFn: function sortFn(a, b) { + return a.score === b.score ? a.idx < b.idx ? -1 : 1 : a.score < b.score ? -1 : 1; + } + }; + var FuzzyOptions = { + // Approximately where in the text is the pattern expected to be found? + location: 0, + // At what point does the match algorithm give up. A threshold of '0.0' requires a perfect match + // (of both letters and location), a threshold of '1.0' would match anything. + threshold: 0.6, + // Determines how close the match must be to the fuzzy location (specified above). + // An exact letter match which is 'distance' characters away from the fuzzy location + // would score as a complete mismatch. A distance of '0' requires the match be at + // the exact location specified, a threshold of '1000' would require a perfect match + // to be within 800 characters of the fuzzy location to be found using a 0.8 threshold. + distance: 100 + }; + var AdvancedOptions = { + // When `true`, it enables the use of unix-like search commands + useExtendedSearch: false, + // The get function to use when fetching an object's properties. + // The default will search nested paths *ie foo.bar.baz* + getFn: get, + // When `true`, search will ignore `location` and `distance`, so it won't matter + // where in the string the pattern appears. + // More info: https://fusejs.io/concepts/scoring-theory.html#fuzziness-score + ignoreLocation: false, + // When `true`, the calculation for the relevance score (used for sorting) will + // ignore the field-length norm. + // More info: https://fusejs.io/concepts/scoring-theory.html#field-length-norm + ignoreFieldNorm: false, + // The weight to determine how much field length norm effects scoring. + fieldNormWeight: 1 + }; + var Config = _objectSpread2(_objectSpread2(_objectSpread2(_objectSpread2({}, BasicOptions), MatchOptions), FuzzyOptions), AdvancedOptions); + + var SPACE = /[^ ]+/g; // Field-length norm: the shorter the field, the higher the weight. + // Set to 3 decimals to reduce index size. + + function norm() { + var weight = arguments.length > 0 && arguments[0] !== undefined ? arguments[0] : 1; + var mantissa = arguments.length > 1 && arguments[1] !== undefined ? arguments[1] : 3; + var cache = new Map(); + var m = Math.pow(10, mantissa); + return { + get: function get(value) { + var numTokens = value.match(SPACE).length; + + if (cache.has(numTokens)) { + return cache.get(numTokens); + } // Default function is 1/sqrt(x), weight makes that variable + + + var norm = 1 / Math.pow(numTokens, 0.5 * weight); // In place of `toFixed(mantissa)`, for faster computation + + var n = parseFloat(Math.round(norm * m) / m); + cache.set(numTokens, n); + return n; + }, + clear: function clear() { + cache.clear(); + } + }; + } + + var FuseIndex = /*#__PURE__*/function () { + function FuseIndex() { + var _ref = arguments.length > 0 && arguments[0] !== undefined ? arguments[0] : {}, + _ref$getFn = _ref.getFn, + getFn = _ref$getFn === void 0 ? Config.getFn : _ref$getFn, + _ref$fieldNormWeight = _ref.fieldNormWeight, + fieldNormWeight = _ref$fieldNormWeight === void 0 ? Config.fieldNormWeight : _ref$fieldNormWeight; + + _classCallCheck(this, FuseIndex); + + this.norm = norm(fieldNormWeight, 3); + this.getFn = getFn; + this.isCreated = false; + this.setIndexRecords(); + } + + _createClass(FuseIndex, [{ + key: "setSources", + value: function setSources() { + var docs = arguments.length > 0 && arguments[0] !== undefined ? arguments[0] : []; + this.docs = docs; + } + }, { + key: "setIndexRecords", + value: function setIndexRecords() { + var records = arguments.length > 0 && arguments[0] !== undefined ? arguments[0] : []; + this.records = records; + } + }, { + key: "setKeys", + value: function setKeys() { + var _this = this; + + var keys = arguments.length > 0 && arguments[0] !== undefined ? arguments[0] : []; + this.keys = keys; + this._keysMap = {}; + keys.forEach(function (key, idx) { + _this._keysMap[key.id] = idx; + }); + } + }, { + key: "create", + value: function create() { + var _this2 = this; + + if (this.isCreated || !this.docs.length) { + return; + } + + this.isCreated = true; // List is Array + + if (isString(this.docs[0])) { + this.docs.forEach(function (doc, docIndex) { + _this2._addString(doc, docIndex); + }); + } else { + // List is Array + this.docs.forEach(function (doc, docIndex) { + _this2._addObject(doc, docIndex); + }); + } + + this.norm.clear(); + } // Adds a doc to the end of the index + + }, { + key: "add", + value: function add(doc) { + var idx = this.size(); + + if (isString(doc)) { + this._addString(doc, idx); + } else { + this._addObject(doc, idx); + } + } // Removes the doc at the specified index of the index + + }, { + key: "removeAt", + value: function removeAt(idx) { + this.records.splice(idx, 1); // Change ref index of every subsquent doc + + for (var i = idx, len = this.size(); i < len; i += 1) { + this.records[i].i -= 1; + } + } + }, { + key: "getValueForItemAtKeyId", + value: function getValueForItemAtKeyId(item, keyId) { + return item[this._keysMap[keyId]]; + } + }, { + key: "size", + value: function size() { + return this.records.length; + } + }, { + key: "_addString", + value: function _addString(doc, docIndex) { + if (!isDefined(doc) || isBlank(doc)) { + return; + } + + var record = { + v: doc, + i: docIndex, + n: this.norm.get(doc) + }; + this.records.push(record); + } + }, { + key: "_addObject", + value: function _addObject(doc, docIndex) { + var _this3 = this; + + var record = { + i: docIndex, + $: {} + }; // Iterate over every key (i.e, path), and fetch the value at that key + + this.keys.forEach(function (key, keyIndex) { + var value = key.getFn ? key.getFn(doc) : _this3.getFn(doc, key.path); + + if (!isDefined(value)) { + return; + } + + if (isArray(value)) { + (function () { + var subRecords = []; + var stack = [{ + nestedArrIndex: -1, + value: value + }]; + + while (stack.length) { + var _stack$pop = stack.pop(), + nestedArrIndex = _stack$pop.nestedArrIndex, + _value = _stack$pop.value; + + if (!isDefined(_value)) { + continue; + } + + if (isString(_value) && !isBlank(_value)) { + var subRecord = { + v: _value, + i: nestedArrIndex, + n: _this3.norm.get(_value) + }; + subRecords.push(subRecord); + } else if (isArray(_value)) { + _value.forEach(function (item, k) { + stack.push({ + nestedArrIndex: k, + value: item + }); + }); + } else ; + } + + record.$[keyIndex] = subRecords; + })(); + } else if (isString(value) && !isBlank(value)) { + var subRecord = { + v: value, + n: _this3.norm.get(value) + }; + record.$[keyIndex] = subRecord; + } + }); + this.records.push(record); + } + }, { + key: "toJSON", + value: function toJSON() { + return { + keys: this.keys, + records: this.records + }; + } + }]); + + return FuseIndex; + }(); + function createIndex(keys, docs) { + var _ref2 = arguments.length > 2 && arguments[2] !== undefined ? arguments[2] : {}, + _ref2$getFn = _ref2.getFn, + getFn = _ref2$getFn === void 0 ? Config.getFn : _ref2$getFn, + _ref2$fieldNormWeight = _ref2.fieldNormWeight, + fieldNormWeight = _ref2$fieldNormWeight === void 0 ? Config.fieldNormWeight : _ref2$fieldNormWeight; + + var myIndex = new FuseIndex({ + getFn: getFn, + fieldNormWeight: fieldNormWeight + }); + myIndex.setKeys(keys.map(createKey)); + myIndex.setSources(docs); + myIndex.create(); + return myIndex; + } + function parseIndex(data) { + var _ref3 = arguments.length > 1 && arguments[1] !== undefined ? arguments[1] : {}, + _ref3$getFn = _ref3.getFn, + getFn = _ref3$getFn === void 0 ? Config.getFn : _ref3$getFn, + _ref3$fieldNormWeight = _ref3.fieldNormWeight, + fieldNormWeight = _ref3$fieldNormWeight === void 0 ? Config.fieldNormWeight : _ref3$fieldNormWeight; + + var keys = data.keys, + records = data.records; + var myIndex = new FuseIndex({ + getFn: getFn, + fieldNormWeight: fieldNormWeight + }); + myIndex.setKeys(keys); + myIndex.setIndexRecords(records); + return myIndex; + } + + function computeScore$1(pattern) { + var _ref = arguments.length > 1 && arguments[1] !== undefined ? arguments[1] : {}, + _ref$errors = _ref.errors, + errors = _ref$errors === void 0 ? 0 : _ref$errors, + _ref$currentLocation = _ref.currentLocation, + currentLocation = _ref$currentLocation === void 0 ? 0 : _ref$currentLocation, + _ref$expectedLocation = _ref.expectedLocation, + expectedLocation = _ref$expectedLocation === void 0 ? 0 : _ref$expectedLocation, + _ref$distance = _ref.distance, + distance = _ref$distance === void 0 ? Config.distance : _ref$distance, + _ref$ignoreLocation = _ref.ignoreLocation, + ignoreLocation = _ref$ignoreLocation === void 0 ? Config.ignoreLocation : _ref$ignoreLocation; + + var accuracy = errors / pattern.length; + + if (ignoreLocation) { + return accuracy; + } + + var proximity = Math.abs(expectedLocation - currentLocation); + + if (!distance) { + // Dodge divide by zero error. + return proximity ? 1.0 : accuracy; + } + + return accuracy + proximity / distance; + } + + function convertMaskToIndices() { + var matchmask = arguments.length > 0 && arguments[0] !== undefined ? arguments[0] : []; + var minMatchCharLength = arguments.length > 1 && arguments[1] !== undefined ? arguments[1] : Config.minMatchCharLength; + var indices = []; + var start = -1; + var end = -1; + var i = 0; + + for (var len = matchmask.length; i < len; i += 1) { + var match = matchmask[i]; + + if (match && start === -1) { + start = i; + } else if (!match && start !== -1) { + end = i - 1; + + if (end - start + 1 >= minMatchCharLength) { + indices.push([start, end]); + } + + start = -1; + } + } // (i-1 - start) + 1 => i - start + + + if (matchmask[i - 1] && i - start >= minMatchCharLength) { + indices.push([start, i - 1]); + } + + return indices; + } + + // Machine word size + var MAX_BITS = 32; + + function search(text, pattern, patternAlphabet) { + var _ref = arguments.length > 3 && arguments[3] !== undefined ? arguments[3] : {}, + _ref$location = _ref.location, + location = _ref$location === void 0 ? Config.location : _ref$location, + _ref$distance = _ref.distance, + distance = _ref$distance === void 0 ? Config.distance : _ref$distance, + _ref$threshold = _ref.threshold, + threshold = _ref$threshold === void 0 ? Config.threshold : _ref$threshold, + _ref$findAllMatches = _ref.findAllMatches, + findAllMatches = _ref$findAllMatches === void 0 ? Config.findAllMatches : _ref$findAllMatches, + _ref$minMatchCharLeng = _ref.minMatchCharLength, + minMatchCharLength = _ref$minMatchCharLeng === void 0 ? Config.minMatchCharLength : _ref$minMatchCharLeng, + _ref$includeMatches = _ref.includeMatches, + includeMatches = _ref$includeMatches === void 0 ? Config.includeMatches : _ref$includeMatches, + _ref$ignoreLocation = _ref.ignoreLocation, + ignoreLocation = _ref$ignoreLocation === void 0 ? Config.ignoreLocation : _ref$ignoreLocation; + + if (pattern.length > MAX_BITS) { + throw new Error(PATTERN_LENGTH_TOO_LARGE(MAX_BITS)); + } + + var patternLen = pattern.length; // Set starting location at beginning text and initialize the alphabet. + + var textLen = text.length; // Handle the case when location > text.length + + var expectedLocation = Math.max(0, Math.min(location, textLen)); // Highest score beyond which we give up. + + var currentThreshold = threshold; // Is there a nearby exact match? (speedup) + + var bestLocation = expectedLocation; // Performance: only computer matches when the minMatchCharLength > 1 + // OR if `includeMatches` is true. + + var computeMatches = minMatchCharLength > 1 || includeMatches; // A mask of the matches, used for building the indices + + var matchMask = computeMatches ? Array(textLen) : []; + var index; // Get all exact matches, here for speed up + + while ((index = text.indexOf(pattern, bestLocation)) > -1) { + var score = computeScore$1(pattern, { + currentLocation: index, + expectedLocation: expectedLocation, + distance: distance, + ignoreLocation: ignoreLocation + }); + currentThreshold = Math.min(score, currentThreshold); + bestLocation = index + patternLen; + + if (computeMatches) { + var i = 0; + + while (i < patternLen) { + matchMask[index + i] = 1; + i += 1; + } + } + } // Reset the best location + + + bestLocation = -1; + var lastBitArr = []; + var finalScore = 1; + var binMax = patternLen + textLen; + var mask = 1 << patternLen - 1; + + for (var _i = 0; _i < patternLen; _i += 1) { + // Scan for the best match; each iteration allows for one more error. + // Run a binary search to determine how far from the match location we can stray + // at this error level. + var binMin = 0; + var binMid = binMax; + + while (binMin < binMid) { + var _score2 = computeScore$1(pattern, { + errors: _i, + currentLocation: expectedLocation + binMid, + expectedLocation: expectedLocation, + distance: distance, + ignoreLocation: ignoreLocation + }); + + if (_score2 <= currentThreshold) { + binMin = binMid; + } else { + binMax = binMid; + } + + binMid = Math.floor((binMax - binMin) / 2 + binMin); + } // Use the result from this iteration as the maximum for the next. + + + binMax = binMid; + var start = Math.max(1, expectedLocation - binMid + 1); + var finish = findAllMatches ? textLen : Math.min(expectedLocation + binMid, textLen) + patternLen; // Initialize the bit array + + var bitArr = Array(finish + 2); + bitArr[finish + 1] = (1 << _i) - 1; + + for (var j = finish; j >= start; j -= 1) { + var currentLocation = j - 1; + var charMatch = patternAlphabet[text.charAt(currentLocation)]; + + if (computeMatches) { + // Speed up: quick bool to int conversion (i.e, `charMatch ? 1 : 0`) + matchMask[currentLocation] = +!!charMatch; + } // First pass: exact match + + + bitArr[j] = (bitArr[j + 1] << 1 | 1) & charMatch; // Subsequent passes: fuzzy match + + if (_i) { + bitArr[j] |= (lastBitArr[j + 1] | lastBitArr[j]) << 1 | 1 | lastBitArr[j + 1]; + } + + if (bitArr[j] & mask) { + finalScore = computeScore$1(pattern, { + errors: _i, + currentLocation: currentLocation, + expectedLocation: expectedLocation, + distance: distance, + ignoreLocation: ignoreLocation + }); // This match will almost certainly be better than any existing match. + // But check anyway. + + if (finalScore <= currentThreshold) { + // Indeed it is + currentThreshold = finalScore; + bestLocation = currentLocation; // Already passed `loc`, downhill from here on in. + + if (bestLocation <= expectedLocation) { + break; + } // When passing `bestLocation`, don't exceed our current distance from `expectedLocation`. + + + start = Math.max(1, 2 * expectedLocation - bestLocation); + } + } + } // No hope for a (better) match at greater error levels. + + + var _score = computeScore$1(pattern, { + errors: _i + 1, + currentLocation: expectedLocation, + expectedLocation: expectedLocation, + distance: distance, + ignoreLocation: ignoreLocation + }); + + if (_score > currentThreshold) { + break; + } + + lastBitArr = bitArr; + } + + var result = { + isMatch: bestLocation >= 0, + // Count exact matches (those with a score of 0) to be "almost" exact + score: Math.max(0.001, finalScore) + }; + + if (computeMatches) { + var indices = convertMaskToIndices(matchMask, minMatchCharLength); + + if (!indices.length) { + result.isMatch = false; + } else if (includeMatches) { + result.indices = indices; + } + } + + return result; + } + + function createPatternAlphabet(pattern) { + var mask = {}; + + for (var i = 0, len = pattern.length; i < len; i += 1) { + var _char = pattern.charAt(i); + + mask[_char] = (mask[_char] || 0) | 1 << len - i - 1; + } + + return mask; + } + + var BitapSearch = /*#__PURE__*/function () { + function BitapSearch(pattern) { + var _this = this; + + var _ref = arguments.length > 1 && arguments[1] !== undefined ? arguments[1] : {}, + _ref$location = _ref.location, + location = _ref$location === void 0 ? Config.location : _ref$location, + _ref$threshold = _ref.threshold, + threshold = _ref$threshold === void 0 ? Config.threshold : _ref$threshold, + _ref$distance = _ref.distance, + distance = _ref$distance === void 0 ? Config.distance : _ref$distance, + _ref$includeMatches = _ref.includeMatches, + includeMatches = _ref$includeMatches === void 0 ? Config.includeMatches : _ref$includeMatches, + _ref$findAllMatches = _ref.findAllMatches, + findAllMatches = _ref$findAllMatches === void 0 ? Config.findAllMatches : _ref$findAllMatches, + _ref$minMatchCharLeng = _ref.minMatchCharLength, + minMatchCharLength = _ref$minMatchCharLeng === void 0 ? Config.minMatchCharLength : _ref$minMatchCharLeng, + _ref$isCaseSensitive = _ref.isCaseSensitive, + isCaseSensitive = _ref$isCaseSensitive === void 0 ? Config.isCaseSensitive : _ref$isCaseSensitive, + _ref$ignoreLocation = _ref.ignoreLocation, + ignoreLocation = _ref$ignoreLocation === void 0 ? Config.ignoreLocation : _ref$ignoreLocation; + + _classCallCheck(this, BitapSearch); + + this.options = { + location: location, + threshold: threshold, + distance: distance, + includeMatches: includeMatches, + findAllMatches: findAllMatches, + minMatchCharLength: minMatchCharLength, + isCaseSensitive: isCaseSensitive, + ignoreLocation: ignoreLocation + }; + this.pattern = isCaseSensitive ? pattern : pattern.toLowerCase(); + this.chunks = []; + + if (!this.pattern.length) { + return; + } + + var addChunk = function addChunk(pattern, startIndex) { + _this.chunks.push({ + pattern: pattern, + alphabet: createPatternAlphabet(pattern), + startIndex: startIndex + }); + }; + + var len = this.pattern.length; + + if (len > MAX_BITS) { + var i = 0; + var remainder = len % MAX_BITS; + var end = len - remainder; + + while (i < end) { + addChunk(this.pattern.substr(i, MAX_BITS), i); + i += MAX_BITS; + } + + if (remainder) { + var startIndex = len - MAX_BITS; + addChunk(this.pattern.substr(startIndex), startIndex); + } + } else { + addChunk(this.pattern, 0); + } + } + + _createClass(BitapSearch, [{ + key: "searchIn", + value: function searchIn(text) { + var _this$options = this.options, + isCaseSensitive = _this$options.isCaseSensitive, + includeMatches = _this$options.includeMatches; + + if (!isCaseSensitive) { + text = text.toLowerCase(); + } // Exact match + + + if (this.pattern === text) { + var _result = { + isMatch: true, + score: 0 + }; + + if (includeMatches) { + _result.indices = [[0, text.length - 1]]; + } + + return _result; + } // Otherwise, use Bitap algorithm + + + var _this$options2 = this.options, + location = _this$options2.location, + distance = _this$options2.distance, + threshold = _this$options2.threshold, + findAllMatches = _this$options2.findAllMatches, + minMatchCharLength = _this$options2.minMatchCharLength, + ignoreLocation = _this$options2.ignoreLocation; + var allIndices = []; + var totalScore = 0; + var hasMatches = false; + this.chunks.forEach(function (_ref2) { + var pattern = _ref2.pattern, + alphabet = _ref2.alphabet, + startIndex = _ref2.startIndex; + + var _search = search(text, pattern, alphabet, { + location: location + startIndex, + distance: distance, + threshold: threshold, + findAllMatches: findAllMatches, + minMatchCharLength: minMatchCharLength, + includeMatches: includeMatches, + ignoreLocation: ignoreLocation + }), + isMatch = _search.isMatch, + score = _search.score, + indices = _search.indices; + + if (isMatch) { + hasMatches = true; + } + + totalScore += score; + + if (isMatch && indices) { + allIndices = [].concat(_toConsumableArray(allIndices), _toConsumableArray(indices)); + } + }); + var result = { + isMatch: hasMatches, + score: hasMatches ? totalScore / this.chunks.length : 1 + }; + + if (hasMatches && includeMatches) { + result.indices = allIndices; + } + + return result; + } + }]); + + return BitapSearch; + }(); + + var BaseMatch = /*#__PURE__*/function () { + function BaseMatch(pattern) { + _classCallCheck(this, BaseMatch); + + this.pattern = pattern; + } + + _createClass(BaseMatch, [{ + key: "search", + value: function + /*text*/ + search() {} + }], [{ + key: "isMultiMatch", + value: function isMultiMatch(pattern) { + return getMatch(pattern, this.multiRegex); + } + }, { + key: "isSingleMatch", + value: function isSingleMatch(pattern) { + return getMatch(pattern, this.singleRegex); + } + }]); + + return BaseMatch; + }(); + + function getMatch(pattern, exp) { + var matches = pattern.match(exp); + return matches ? matches[1] : null; + } + + var ExactMatch = /*#__PURE__*/function (_BaseMatch) { + _inherits(ExactMatch, _BaseMatch); + + var _super = _createSuper(ExactMatch); + + function ExactMatch(pattern) { + _classCallCheck(this, ExactMatch); + + return _super.call(this, pattern); + } + + _createClass(ExactMatch, [{ + key: "search", + value: function search(text) { + var isMatch = text === this.pattern; + return { + isMatch: isMatch, + score: isMatch ? 0 : 1, + indices: [0, this.pattern.length - 1] + }; + } + }], [{ + key: "type", + get: function get() { + return 'exact'; + } + }, { + key: "multiRegex", + get: function get() { + return /^="(.*)"$/; + } + }, { + key: "singleRegex", + get: function get() { + return /^=(.*)$/; + } + }]); + + return ExactMatch; + }(BaseMatch); + + var InverseExactMatch = /*#__PURE__*/function (_BaseMatch) { + _inherits(InverseExactMatch, _BaseMatch); + + var _super = _createSuper(InverseExactMatch); + + function InverseExactMatch(pattern) { + _classCallCheck(this, InverseExactMatch); + + return _super.call(this, pattern); + } + + _createClass(InverseExactMatch, [{ + key: "search", + value: function search(text) { + var index = text.indexOf(this.pattern); + var isMatch = index === -1; + return { + isMatch: isMatch, + score: isMatch ? 0 : 1, + indices: [0, text.length - 1] + }; + } + }], [{ + key: "type", + get: function get() { + return 'inverse-exact'; + } + }, { + key: "multiRegex", + get: function get() { + return /^!"(.*)"$/; + } + }, { + key: "singleRegex", + get: function get() { + return /^!(.*)$/; + } + }]); + + return InverseExactMatch; + }(BaseMatch); + + var PrefixExactMatch = /*#__PURE__*/function (_BaseMatch) { + _inherits(PrefixExactMatch, _BaseMatch); + + var _super = _createSuper(PrefixExactMatch); + + function PrefixExactMatch(pattern) { + _classCallCheck(this, PrefixExactMatch); + + return _super.call(this, pattern); + } + + _createClass(PrefixExactMatch, [{ + key: "search", + value: function search(text) { + var isMatch = text.startsWith(this.pattern); + return { + isMatch: isMatch, + score: isMatch ? 0 : 1, + indices: [0, this.pattern.length - 1] + }; + } + }], [{ + key: "type", + get: function get() { + return 'prefix-exact'; + } + }, { + key: "multiRegex", + get: function get() { + return /^\^"(.*)"$/; + } + }, { + key: "singleRegex", + get: function get() { + return /^\^(.*)$/; + } + }]); + + return PrefixExactMatch; + }(BaseMatch); + + var InversePrefixExactMatch = /*#__PURE__*/function (_BaseMatch) { + _inherits(InversePrefixExactMatch, _BaseMatch); + + var _super = _createSuper(InversePrefixExactMatch); + + function InversePrefixExactMatch(pattern) { + _classCallCheck(this, InversePrefixExactMatch); + + return _super.call(this, pattern); + } + + _createClass(InversePrefixExactMatch, [{ + key: "search", + value: function search(text) { + var isMatch = !text.startsWith(this.pattern); + return { + isMatch: isMatch, + score: isMatch ? 0 : 1, + indices: [0, text.length - 1] + }; + } + }], [{ + key: "type", + get: function get() { + return 'inverse-prefix-exact'; + } + }, { + key: "multiRegex", + get: function get() { + return /^!\^"(.*)"$/; + } + }, { + key: "singleRegex", + get: function get() { + return /^!\^(.*)$/; + } + }]); + + return InversePrefixExactMatch; + }(BaseMatch); + + var SuffixExactMatch = /*#__PURE__*/function (_BaseMatch) { + _inherits(SuffixExactMatch, _BaseMatch); + + var _super = _createSuper(SuffixExactMatch); + + function SuffixExactMatch(pattern) { + _classCallCheck(this, SuffixExactMatch); + + return _super.call(this, pattern); + } + + _createClass(SuffixExactMatch, [{ + key: "search", + value: function search(text) { + var isMatch = text.endsWith(this.pattern); + return { + isMatch: isMatch, + score: isMatch ? 0 : 1, + indices: [text.length - this.pattern.length, text.length - 1] + }; + } + }], [{ + key: "type", + get: function get() { + return 'suffix-exact'; + } + }, { + key: "multiRegex", + get: function get() { + return /^"(.*)"\$$/; + } + }, { + key: "singleRegex", + get: function get() { + return /^(.*)\$$/; + } + }]); + + return SuffixExactMatch; + }(BaseMatch); + + var InverseSuffixExactMatch = /*#__PURE__*/function (_BaseMatch) { + _inherits(InverseSuffixExactMatch, _BaseMatch); + + var _super = _createSuper(InverseSuffixExactMatch); + + function InverseSuffixExactMatch(pattern) { + _classCallCheck(this, InverseSuffixExactMatch); + + return _super.call(this, pattern); + } + + _createClass(InverseSuffixExactMatch, [{ + key: "search", + value: function search(text) { + var isMatch = !text.endsWith(this.pattern); + return { + isMatch: isMatch, + score: isMatch ? 0 : 1, + indices: [0, text.length - 1] + }; + } + }], [{ + key: "type", + get: function get() { + return 'inverse-suffix-exact'; + } + }, { + key: "multiRegex", + get: function get() { + return /^!"(.*)"\$$/; + } + }, { + key: "singleRegex", + get: function get() { + return /^!(.*)\$$/; + } + }]); + + return InverseSuffixExactMatch; + }(BaseMatch); + + var FuzzyMatch = /*#__PURE__*/function (_BaseMatch) { + _inherits(FuzzyMatch, _BaseMatch); + + var _super = _createSuper(FuzzyMatch); + + function FuzzyMatch(pattern) { + var _this; + + var _ref = arguments.length > 1 && arguments[1] !== undefined ? arguments[1] : {}, + _ref$location = _ref.location, + location = _ref$location === void 0 ? Config.location : _ref$location, + _ref$threshold = _ref.threshold, + threshold = _ref$threshold === void 0 ? Config.threshold : _ref$threshold, + _ref$distance = _ref.distance, + distance = _ref$distance === void 0 ? Config.distance : _ref$distance, + _ref$includeMatches = _ref.includeMatches, + includeMatches = _ref$includeMatches === void 0 ? Config.includeMatches : _ref$includeMatches, + _ref$findAllMatches = _ref.findAllMatches, + findAllMatches = _ref$findAllMatches === void 0 ? Config.findAllMatches : _ref$findAllMatches, + _ref$minMatchCharLeng = _ref.minMatchCharLength, + minMatchCharLength = _ref$minMatchCharLeng === void 0 ? Config.minMatchCharLength : _ref$minMatchCharLeng, + _ref$isCaseSensitive = _ref.isCaseSensitive, + isCaseSensitive = _ref$isCaseSensitive === void 0 ? Config.isCaseSensitive : _ref$isCaseSensitive, + _ref$ignoreLocation = _ref.ignoreLocation, + ignoreLocation = _ref$ignoreLocation === void 0 ? Config.ignoreLocation : _ref$ignoreLocation; + + _classCallCheck(this, FuzzyMatch); + + _this = _super.call(this, pattern); + _this._bitapSearch = new BitapSearch(pattern, { + location: location, + threshold: threshold, + distance: distance, + includeMatches: includeMatches, + findAllMatches: findAllMatches, + minMatchCharLength: minMatchCharLength, + isCaseSensitive: isCaseSensitive, + ignoreLocation: ignoreLocation + }); + return _this; + } + + _createClass(FuzzyMatch, [{ + key: "search", + value: function search(text) { + return this._bitapSearch.searchIn(text); + } + }], [{ + key: "type", + get: function get() { + return 'fuzzy'; + } + }, { + key: "multiRegex", + get: function get() { + return /^"(.*)"$/; + } + }, { + key: "singleRegex", + get: function get() { + return /^(.*)$/; + } + }]); + + return FuzzyMatch; + }(BaseMatch); + + var IncludeMatch = /*#__PURE__*/function (_BaseMatch) { + _inherits(IncludeMatch, _BaseMatch); + + var _super = _createSuper(IncludeMatch); + + function IncludeMatch(pattern) { + _classCallCheck(this, IncludeMatch); + + return _super.call(this, pattern); + } + + _createClass(IncludeMatch, [{ + key: "search", + value: function search(text) { + var location = 0; + var index; + var indices = []; + var patternLen = this.pattern.length; // Get all exact matches + + while ((index = text.indexOf(this.pattern, location)) > -1) { + location = index + patternLen; + indices.push([index, location - 1]); + } + + var isMatch = !!indices.length; + return { + isMatch: isMatch, + score: isMatch ? 0 : 1, + indices: indices + }; + } + }], [{ + key: "type", + get: function get() { + return 'include'; + } + }, { + key: "multiRegex", + get: function get() { + return /^'"(.*)"$/; + } + }, { + key: "singleRegex", + get: function get() { + return /^'(.*)$/; + } + }]); + + return IncludeMatch; + }(BaseMatch); + + var searchers = [ExactMatch, IncludeMatch, PrefixExactMatch, InversePrefixExactMatch, InverseSuffixExactMatch, SuffixExactMatch, InverseExactMatch, FuzzyMatch]; + var searchersLen = searchers.length; // Regex to split by spaces, but keep anything in quotes together + + var SPACE_RE = / +(?=(?:[^\"]*\"[^\"]*\")*[^\"]*$)/; + var OR_TOKEN = '|'; // Return a 2D array representation of the query, for simpler parsing. + // Example: + // "^core go$ | rb$ | py$ xy$" => [["^core", "go$"], ["rb$"], ["py$", "xy$"]] + + function parseQuery(pattern) { + var options = arguments.length > 1 && arguments[1] !== undefined ? arguments[1] : {}; + return pattern.split(OR_TOKEN).map(function (item) { + var query = item.trim().split(SPACE_RE).filter(function (item) { + return item && !!item.trim(); + }); + var results = []; + + for (var i = 0, len = query.length; i < len; i += 1) { + var queryItem = query[i]; // 1. Handle multiple query match (i.e, once that are quoted, like `"hello world"`) + + var found = false; + var idx = -1; + + while (!found && ++idx < searchersLen) { + var searcher = searchers[idx]; + var token = searcher.isMultiMatch(queryItem); + + if (token) { + results.push(new searcher(token, options)); + found = true; + } + } + + if (found) { + continue; + } // 2. Handle single query matches (i.e, once that are *not* quoted) + + + idx = -1; + + while (++idx < searchersLen) { + var _searcher = searchers[idx]; + + var _token = _searcher.isSingleMatch(queryItem); + + if (_token) { + results.push(new _searcher(_token, options)); + break; + } + } + } + + return results; + }); + } + + // to a singl match + + var MultiMatchSet = new Set([FuzzyMatch.type, IncludeMatch.type]); + /** + * Command-like searching + * ====================== + * + * Given multiple search terms delimited by spaces.e.g. `^jscript .python$ ruby !java`, + * search in a given text. + * + * Search syntax: + * + * | Token | Match type | Description | + * | ----------- | -------------------------- | -------------------------------------- | + * | `jscript` | fuzzy-match | Items that fuzzy match `jscript` | + * | `=scheme` | exact-match | Items that are `scheme` | + * | `'python` | include-match | Items that include `python` | + * | `!ruby` | inverse-exact-match | Items that do not include `ruby` | + * | `^java` | prefix-exact-match | Items that start with `java` | + * | `!^earlang` | inverse-prefix-exact-match | Items that do not start with `earlang` | + * | `.js$` | suffix-exact-match | Items that end with `.js` | + * | `!.go$` | inverse-suffix-exact-match | Items that do not end with `.go` | + * + * A single pipe character acts as an OR operator. For example, the following + * query matches entries that start with `core` and end with either`go`, `rb`, + * or`py`. + * + * ``` + * ^core go$ | rb$ | py$ + * ``` + */ + + var ExtendedSearch = /*#__PURE__*/function () { + function ExtendedSearch(pattern) { + var _ref = arguments.length > 1 && arguments[1] !== undefined ? arguments[1] : {}, + _ref$isCaseSensitive = _ref.isCaseSensitive, + isCaseSensitive = _ref$isCaseSensitive === void 0 ? Config.isCaseSensitive : _ref$isCaseSensitive, + _ref$includeMatches = _ref.includeMatches, + includeMatches = _ref$includeMatches === void 0 ? Config.includeMatches : _ref$includeMatches, + _ref$minMatchCharLeng = _ref.minMatchCharLength, + minMatchCharLength = _ref$minMatchCharLeng === void 0 ? Config.minMatchCharLength : _ref$minMatchCharLeng, + _ref$ignoreLocation = _ref.ignoreLocation, + ignoreLocation = _ref$ignoreLocation === void 0 ? Config.ignoreLocation : _ref$ignoreLocation, + _ref$findAllMatches = _ref.findAllMatches, + findAllMatches = _ref$findAllMatches === void 0 ? Config.findAllMatches : _ref$findAllMatches, + _ref$location = _ref.location, + location = _ref$location === void 0 ? Config.location : _ref$location, + _ref$threshold = _ref.threshold, + threshold = _ref$threshold === void 0 ? Config.threshold : _ref$threshold, + _ref$distance = _ref.distance, + distance = _ref$distance === void 0 ? Config.distance : _ref$distance; + + _classCallCheck(this, ExtendedSearch); + + this.query = null; + this.options = { + isCaseSensitive: isCaseSensitive, + includeMatches: includeMatches, + minMatchCharLength: minMatchCharLength, + findAllMatches: findAllMatches, + ignoreLocation: ignoreLocation, + location: location, + threshold: threshold, + distance: distance + }; + this.pattern = isCaseSensitive ? pattern : pattern.toLowerCase(); + this.query = parseQuery(this.pattern, this.options); + } + + _createClass(ExtendedSearch, [{ + key: "searchIn", + value: function searchIn(text) { + var query = this.query; + + if (!query) { + return { + isMatch: false, + score: 1 + }; + } + + var _this$options = this.options, + includeMatches = _this$options.includeMatches, + isCaseSensitive = _this$options.isCaseSensitive; + text = isCaseSensitive ? text : text.toLowerCase(); + var numMatches = 0; + var allIndices = []; + var totalScore = 0; // ORs + + for (var i = 0, qLen = query.length; i < qLen; i += 1) { + var searchers = query[i]; // Reset indices + + allIndices.length = 0; + numMatches = 0; // ANDs + + for (var j = 0, pLen = searchers.length; j < pLen; j += 1) { + var searcher = searchers[j]; + + var _searcher$search = searcher.search(text), + isMatch = _searcher$search.isMatch, + indices = _searcher$search.indices, + score = _searcher$search.score; + + if (isMatch) { + numMatches += 1; + totalScore += score; + + if (includeMatches) { + var type = searcher.constructor.type; + + if (MultiMatchSet.has(type)) { + allIndices = [].concat(_toConsumableArray(allIndices), _toConsumableArray(indices)); + } else { + allIndices.push(indices); + } + } + } else { + totalScore = 0; + numMatches = 0; + allIndices.length = 0; + break; + } + } // OR condition, so if TRUE, return + + + if (numMatches) { + var result = { + isMatch: true, + score: totalScore / numMatches + }; + + if (includeMatches) { + result.indices = allIndices; + } + + return result; + } + } // Nothing was matched + + + return { + isMatch: false, + score: 1 + }; + } + }], [{ + key: "condition", + value: function condition(_, options) { + return options.useExtendedSearch; + } + }]); + + return ExtendedSearch; + }(); + + var registeredSearchers = []; + function register() { + registeredSearchers.push.apply(registeredSearchers, arguments); + } + function createSearcher(pattern, options) { + for (var i = 0, len = registeredSearchers.length; i < len; i += 1) { + var searcherClass = registeredSearchers[i]; + + if (searcherClass.condition(pattern, options)) { + return new searcherClass(pattern, options); + } + } + + return new BitapSearch(pattern, options); + } + + var LogicalOperator = { + AND: '$and', + OR: '$or' + }; + var KeyType = { + PATH: '$path', + PATTERN: '$val' + }; + + var isExpression = function isExpression(query) { + return !!(query[LogicalOperator.AND] || query[LogicalOperator.OR]); + }; + + var isPath = function isPath(query) { + return !!query[KeyType.PATH]; + }; + + var isLeaf = function isLeaf(query) { + return !isArray(query) && isObject(query) && !isExpression(query); + }; + + var convertToExplicit = function convertToExplicit(query) { + return _defineProperty({}, LogicalOperator.AND, Object.keys(query).map(function (key) { + return _defineProperty({}, key, query[key]); + })); + }; // When `auto` is `true`, the parse function will infer and initialize and add + // the appropriate `Searcher` instance + + + function parse(query, options) { + var _ref3 = arguments.length > 2 && arguments[2] !== undefined ? arguments[2] : {}, + _ref3$auto = _ref3.auto, + auto = _ref3$auto === void 0 ? true : _ref3$auto; + + var next = function next(query) { + var keys = Object.keys(query); + var isQueryPath = isPath(query); + + if (!isQueryPath && keys.length > 1 && !isExpression(query)) { + return next(convertToExplicit(query)); + } + + if (isLeaf(query)) { + var key = isQueryPath ? query[KeyType.PATH] : keys[0]; + var pattern = isQueryPath ? query[KeyType.PATTERN] : query[key]; + + if (!isString(pattern)) { + throw new Error(LOGICAL_SEARCH_INVALID_QUERY_FOR_KEY(key)); + } + + var obj = { + keyId: createKeyId(key), + pattern: pattern + }; + + if (auto) { + obj.searcher = createSearcher(pattern, options); + } + + return obj; + } + + var node = { + children: [], + operator: keys[0] + }; + keys.forEach(function (key) { + var value = query[key]; + + if (isArray(value)) { + value.forEach(function (item) { + node.children.push(next(item)); + }); + } + }); + return node; + }; + + if (!isExpression(query)) { + query = convertToExplicit(query); + } + + return next(query); + } + + function computeScore(results, _ref) { + var _ref$ignoreFieldNorm = _ref.ignoreFieldNorm, + ignoreFieldNorm = _ref$ignoreFieldNorm === void 0 ? Config.ignoreFieldNorm : _ref$ignoreFieldNorm; + results.forEach(function (result) { + var totalScore = 1; + result.matches.forEach(function (_ref2) { + var key = _ref2.key, + norm = _ref2.norm, + score = _ref2.score; + var weight = key ? key.weight : null; + totalScore *= Math.pow(score === 0 && weight ? Number.EPSILON : score, (weight || 1) * (ignoreFieldNorm ? 1 : norm)); + }); + result.score = totalScore; + }); + } + + function transformMatches(result, data) { + var matches = result.matches; + data.matches = []; + + if (!isDefined(matches)) { + return; + } + + matches.forEach(function (match) { + if (!isDefined(match.indices) || !match.indices.length) { + return; + } + + var indices = match.indices, + value = match.value; + var obj = { + indices: indices, + value: value + }; + + if (match.key) { + obj.key = match.key.src; + } + + if (match.idx > -1) { + obj.refIndex = match.idx; + } + + data.matches.push(obj); + }); + } + + function transformScore(result, data) { + data.score = result.score; + } + + function format(results, docs) { + var _ref = arguments.length > 2 && arguments[2] !== undefined ? arguments[2] : {}, + _ref$includeMatches = _ref.includeMatches, + includeMatches = _ref$includeMatches === void 0 ? Config.includeMatches : _ref$includeMatches, + _ref$includeScore = _ref.includeScore, + includeScore = _ref$includeScore === void 0 ? Config.includeScore : _ref$includeScore; + + var transformers = []; + if (includeMatches) transformers.push(transformMatches); + if (includeScore) transformers.push(transformScore); + return results.map(function (result) { + var idx = result.idx; + var data = { + item: docs[idx], + refIndex: idx + }; + + if (transformers.length) { + transformers.forEach(function (transformer) { + transformer(result, data); + }); + } + + return data; + }); + } + + var Fuse$1 = /*#__PURE__*/function () { + function Fuse(docs) { + var options = arguments.length > 1 && arguments[1] !== undefined ? arguments[1] : {}; + var index = arguments.length > 2 ? arguments[2] : undefined; + + _classCallCheck(this, Fuse); + + this.options = _objectSpread2(_objectSpread2({}, Config), options); + + if (this.options.useExtendedSearch && !true) { + throw new Error(EXTENDED_SEARCH_UNAVAILABLE); + } + + this._keyStore = new KeyStore(this.options.keys); + this.setCollection(docs, index); + } + + _createClass(Fuse, [{ + key: "setCollection", + value: function setCollection(docs, index) { + this._docs = docs; + + if (index && !(index instanceof FuseIndex)) { + throw new Error(INCORRECT_INDEX_TYPE); + } + + this._myIndex = index || createIndex(this.options.keys, this._docs, { + getFn: this.options.getFn, + fieldNormWeight: this.options.fieldNormWeight + }); + } + }, { + key: "add", + value: function add(doc) { + if (!isDefined(doc)) { + return; + } + + this._docs.push(doc); + + this._myIndex.add(doc); + } + }, { + key: "remove", + value: function remove() { + var predicate = arguments.length > 0 && arguments[0] !== undefined ? arguments[0] : function + /* doc, idx */ + () { + return false; + }; + var results = []; + + for (var i = 0, len = this._docs.length; i < len; i += 1) { + var doc = this._docs[i]; + + if (predicate(doc, i)) { + this.removeAt(i); + i -= 1; + len -= 1; + results.push(doc); + } + } + + return results; + } + }, { + key: "removeAt", + value: function removeAt(idx) { + this._docs.splice(idx, 1); + + this._myIndex.removeAt(idx); + } + }, { + key: "getIndex", + value: function getIndex() { + return this._myIndex; + } + }, { + key: "search", + value: function search(query) { + var _ref = arguments.length > 1 && arguments[1] !== undefined ? arguments[1] : {}, + _ref$limit = _ref.limit, + limit = _ref$limit === void 0 ? -1 : _ref$limit; + + var _this$options = this.options, + includeMatches = _this$options.includeMatches, + includeScore = _this$options.includeScore, + shouldSort = _this$options.shouldSort, + sortFn = _this$options.sortFn, + ignoreFieldNorm = _this$options.ignoreFieldNorm; + var results = isString(query) ? isString(this._docs[0]) ? this._searchStringList(query) : this._searchObjectList(query) : this._searchLogical(query); + computeScore(results, { + ignoreFieldNorm: ignoreFieldNorm + }); + + if (shouldSort) { + results.sort(sortFn); + } + + if (isNumber(limit) && limit > -1) { + results = results.slice(0, limit); + } + + return format(results, this._docs, { + includeMatches: includeMatches, + includeScore: includeScore + }); + } + }, { + key: "_searchStringList", + value: function _searchStringList(query) { + var searcher = createSearcher(query, this.options); + var records = this._myIndex.records; + var results = []; // Iterate over every string in the index + + records.forEach(function (_ref2) { + var text = _ref2.v, + idx = _ref2.i, + norm = _ref2.n; + + if (!isDefined(text)) { + return; + } + + var _searcher$searchIn = searcher.searchIn(text), + isMatch = _searcher$searchIn.isMatch, + score = _searcher$searchIn.score, + indices = _searcher$searchIn.indices; + + if (isMatch) { + results.push({ + item: text, + idx: idx, + matches: [{ + score: score, + value: text, + norm: norm, + indices: indices + }] + }); + } + }); + return results; + } + }, { + key: "_searchLogical", + value: function _searchLogical(query) { + var _this = this; + + var expression = parse(query, this.options); + + var evaluate = function evaluate(node, item, idx) { + if (!node.children) { + var keyId = node.keyId, + searcher = node.searcher; + + var matches = _this._findMatches({ + key: _this._keyStore.get(keyId), + value: _this._myIndex.getValueForItemAtKeyId(item, keyId), + searcher: searcher + }); + + if (matches && matches.length) { + return [{ + idx: idx, + item: item, + matches: matches + }]; + } + + return []; + } + + var res = []; + + for (var i = 0, len = node.children.length; i < len; i += 1) { + var child = node.children[i]; + var result = evaluate(child, item, idx); + + if (result.length) { + res.push.apply(res, _toConsumableArray(result)); + } else if (node.operator === LogicalOperator.AND) { + return []; + } + } + + return res; + }; + + var records = this._myIndex.records; + var resultMap = {}; + var results = []; + records.forEach(function (_ref3) { + var item = _ref3.$, + idx = _ref3.i; + + if (isDefined(item)) { + var expResults = evaluate(expression, item, idx); + + if (expResults.length) { + // Dedupe when adding + if (!resultMap[idx]) { + resultMap[idx] = { + idx: idx, + item: item, + matches: [] + }; + results.push(resultMap[idx]); + } + + expResults.forEach(function (_ref4) { + var _resultMap$idx$matche; + + var matches = _ref4.matches; + + (_resultMap$idx$matche = resultMap[idx].matches).push.apply(_resultMap$idx$matche, _toConsumableArray(matches)); + }); + } + } + }); + return results; + } + }, { + key: "_searchObjectList", + value: function _searchObjectList(query) { + var _this2 = this; + + var searcher = createSearcher(query, this.options); + var _this$_myIndex = this._myIndex, + keys = _this$_myIndex.keys, + records = _this$_myIndex.records; + var results = []; // List is Array + + records.forEach(function (_ref5) { + var item = _ref5.$, + idx = _ref5.i; + + if (!isDefined(item)) { + return; + } + + var matches = []; // Iterate over every key (i.e, path), and fetch the value at that key + + keys.forEach(function (key, keyIndex) { + matches.push.apply(matches, _toConsumableArray(_this2._findMatches({ + key: key, + value: item[keyIndex], + searcher: searcher + }))); + }); + + if (matches.length) { + results.push({ + idx: idx, + item: item, + matches: matches + }); + } + }); + return results; + } + }, { + key: "_findMatches", + value: function _findMatches(_ref6) { + var key = _ref6.key, + value = _ref6.value, + searcher = _ref6.searcher; + + if (!isDefined(value)) { + return []; + } + + var matches = []; + + if (isArray(value)) { + value.forEach(function (_ref7) { + var text = _ref7.v, + idx = _ref7.i, + norm = _ref7.n; + + if (!isDefined(text)) { + return; + } + + var _searcher$searchIn2 = searcher.searchIn(text), + isMatch = _searcher$searchIn2.isMatch, + score = _searcher$searchIn2.score, + indices = _searcher$searchIn2.indices; + + if (isMatch) { + matches.push({ + score: score, + key: key, + value: text, + idx: idx, + norm: norm, + indices: indices + }); + } + }); + } else { + var text = value.v, + norm = value.n; + + var _searcher$searchIn3 = searcher.searchIn(text), + isMatch = _searcher$searchIn3.isMatch, + score = _searcher$searchIn3.score, + indices = _searcher$searchIn3.indices; + + if (isMatch) { + matches.push({ + score: score, + key: key, + value: text, + norm: norm, + indices: indices + }); + } + } + + return matches; + } + }]); + + return Fuse; + }(); + + Fuse$1.version = '6.6.2'; + Fuse$1.createIndex = createIndex; + Fuse$1.parseIndex = parseIndex; + Fuse$1.config = Config; + + { + Fuse$1.parseQuery = parse; + } + + { + register(ExtendedSearch); + } + + var Fuse = Fuse$1; + + return Fuse; + +})); diff --git a/test/index/index_command.t/j.ml b/test/index/index_command.t/j.ml new file mode 100644 index 0000000000..9eddf84ad3 --- /dev/null +++ b/test/index/index_command.t/j.ml @@ -0,0 +1,13 @@ +(** + + a paragraph one + +*) + +let uu = 2 + +(** + + a paragraph two + +*) diff --git a/test/index/index_command.t/main.ml b/test/index/index_command.t/main.ml new file mode 100644 index 0000000000..2b444be801 --- /dev/null +++ b/test/index/index_command.t/main.ml @@ -0,0 +1,59 @@ +type t = int +(** A comment *) + +(** {1 this is a title} + + and this is a paragraph + + *) + +module M = struct + type t + (** dsdsd *) +end + +(** a reference {!t}, and some {e formatted} {b content} with [code] and + +{[ + code blocks +]} + + *) +let v = 9 + +(** lorem 1 and a {{:http://perdu.com}link} + *) +let lorem = 1 + +(** lorem 2 + *) +let lorem2 = 1 + +(** lorem 3 + *) +let lorem3 = 1 + +(** lorem 4 + *) +let lorem4 = 1 + +module I = struct + let x = 1 + + (** a paragraph + + and another + + {v verbatim v} + + {m x + 1} + + {[blibli]} + *) + + let y = 1 +end + +include I + +include J diff --git a/test/index/index_command.t/page.mld b/test/index/index_command.t/page.mld new file mode 100644 index 0000000000..37fe4527d8 --- /dev/null +++ b/test/index/index_command.t/page.mld @@ -0,0 +1,10 @@ +{0 A title} + +A paragraph + +{v some verbatim v} + +{[and code]} + +- a list {e of} things +- bliblib diff --git a/test/index/index_command.t/run.t b/test/index/index_command.t/run.t new file mode 100644 index 0000000000..9373938fd3 --- /dev/null +++ b/test/index/index_command.t/run.t @@ -0,0 +1,844 @@ +Make sure wrapped libraries don't interfere with generating the source code. +Test both canonical paths and hidden units. +It's a simpler case than Dune's wrapping. + +$ odoc compile -c module-main -c src-source root.mld + + $ ocamlc -c j.ml -bin-annot -I . + $ ocamlc -c main.ml -bin-annot -I . + + $ odoc compile -I . j.cmt + $ odoc compile -I . main.cmt + $ odoc compile -I . page.mld + + $ odoc link -I . j.odoc + $ odoc link -I . main.odoc + $ odoc link -I . page-page.odoc + + $ odoc compile-index -I . + + $ cat index.json | jq + [ + { + "id": [ + { + "kind": "Root", + "name": "Main" + } + ], + "doc": "", + "extra": { + "kind": "Module" + }, + "display": { + "html": "
    moduleMain
    ", + "url": "Main/index.html" + } + }, + { + "id": [ + { + "kind": "Root", + "name": "Main" + }, + { + "kind": "Type", + "name": "t" + } + ], + "doc": "A comment", + "extra": { + "kind": "TypeDecl", + "private": false, + "manifest": "int", + "constraints": [] + }, + "display": { + "html": "
    typeMain.t = int

    A comment

    ", + "url": "Main/index.html#type-t" + } + }, + { + "id": [ + { + "kind": "Root", + "name": "Main" + }, + { + "kind": "Label", + "name": "this-is-a-title" + } + ], + "doc": "this is a title", + "extra": { + "kind": "Doc", + "subkind": "Heading" + }, + "display": { + "html": "
    docMain.this-is-a-title

    this is a title

    ", + "url": "Main/index.html#this-is-a-title" + } + }, + { + "id": [ + { + "kind": "Root", + "name": "Main" + } + ], + "doc": "and this is a paragraph", + "extra": { + "kind": "Doc", + "subkind": "Paragraph" + }, + "display": { + "html": "
    docMain

    and this is a paragraph

    ", + "url": "Main/index.html" + } + }, + { + "id": [ + { + "kind": "Root", + "name": "Main" + }, + { + "kind": "Module", + "name": "M" + } + ], + "doc": "", + "extra": { + "kind": "Module" + }, + "display": { + "html": "
    moduleMain.M
    ", + "url": "Main/M/index.html" + } + }, + { + "id": [ + { + "kind": "Root", + "name": "Main" + }, + { + "kind": "Module", + "name": "M" + }, + { + "kind": "Type", + "name": "t" + } + ], + "doc": "dsdsd", + "extra": { + "kind": "TypeDecl", + "private": false, + "manifest": null, + "constraints": [] + }, + "display": { + "html": "
    typeMain.M.t

    dsdsd

    ", + "url": "Main/M/index.html#type-t" + } + }, + { + "id": [ + { + "kind": "Root", + "name": "Main" + }, + { + "kind": "Value", + "name": "v" + } + ], + "doc": "a reference , and some formatted content with code and\ncode blocks", + "extra": { + "kind": "Value", + "type": "int" + }, + "display": { + "html": "
    valMain.v : int

    a reference t, and some formatted content with code and

    code blocks
    ", + "url": "Main/index.html#val-v" + } + }, + { + "id": [ + { + "kind": "Root", + "name": "Main" + }, + { + "kind": "Value", + "name": "lorem" + } + ], + "doc": "lorem 1 and a link", + "extra": { + "kind": "Value", + "type": "int" + }, + "display": { + "html": "
    valMain.lorem : int

    lorem 1 and a link

    ", + "url": "Main/index.html#val-lorem" + } + }, + { + "id": [ + { + "kind": "Root", + "name": "Main" + }, + { + "kind": "Value", + "name": "lorem2" + } + ], + "doc": "lorem 2", + "extra": { + "kind": "Value", + "type": "int" + }, + "display": { + "html": "
    valMain.lorem2 : int

    lorem 2

    ", + "url": "Main/index.html#val-lorem2" + } + }, + { + "id": [ + { + "kind": "Root", + "name": "Main" + }, + { + "kind": "Value", + "name": "lorem3" + } + ], + "doc": "lorem 3", + "extra": { + "kind": "Value", + "type": "int" + }, + "display": { + "html": "
    valMain.lorem3 : int

    lorem 3

    ", + "url": "Main/index.html#val-lorem3" + } + }, + { + "id": [ + { + "kind": "Root", + "name": "Main" + }, + { + "kind": "Value", + "name": "lorem4" + } + ], + "doc": "lorem 4", + "extra": { + "kind": "Value", + "type": "int" + }, + "display": { + "html": "
    valMain.lorem4 : int

    lorem 4

    ", + "url": "Main/index.html#val-lorem4" + } + }, + { + "id": [ + { + "kind": "Root", + "name": "Main" + }, + { + "kind": "Module", + "name": "I" + } + ], + "doc": "", + "extra": { + "kind": "Module" + }, + "display": { + "html": "
    moduleMain.I
    ", + "url": "Main/I/index.html" + } + }, + { + "id": [ + { + "kind": "Root", + "name": "Main" + }, + { + "kind": "Module", + "name": "I" + }, + { + "kind": "Value", + "name": "x" + } + ], + "doc": "", + "extra": { + "kind": "Value", + "type": "int" + }, + "display": { + "html": "
    valMain.I.x : int
    ", + "url": "Main/I/index.html#val-x" + } + }, + { + "id": [ + { + "kind": "Root", + "name": "Main" + }, + { + "kind": "Module", + "name": "I" + } + ], + "doc": "a paragraph", + "extra": { + "kind": "Doc", + "subkind": "Paragraph" + }, + "display": { + "html": "
    docMain.I

    a paragraph

    ", + "url": "Main/I/index.html" + } + }, + { + "id": [ + { + "kind": "Root", + "name": "Main" + }, + { + "kind": "Module", + "name": "I" + } + ], + "doc": "and another", + "extra": { + "kind": "Doc", + "subkind": "Paragraph" + }, + "display": { + "html": "
    docMain.I

    and another

    ", + "url": "Main/I/index.html" + } + }, + { + "id": [ + { + "kind": "Root", + "name": "Main" + }, + { + "kind": "Module", + "name": "I" + } + ], + "doc": "verbatim", + "extra": { + "kind": "Doc", + "subkind": "Verbatim" + }, + "display": { + "html": "
    docMain.I
    verbatim
    ", + "url": "Main/I/index.html" + } + }, + { + "id": [ + { + "kind": "Root", + "name": "Main" + }, + { + "kind": "Module", + "name": "I" + } + ], + "doc": "x + 1", + "extra": { + "kind": "Doc", + "subkind": "Paragraph" + }, + "display": { + "html": "
    docMain.I

    x + 1

    ", + "url": "Main/I/index.html" + } + }, + { + "id": [ + { + "kind": "Root", + "name": "Main" + }, + { + "kind": "Module", + "name": "I" + } + ], + "doc": "blibli", + "extra": { + "kind": "Doc", + "subkind": "CodeBlock" + }, + "display": { + "html": "
    docMain.I
    blibli
    ", + "url": "Main/I/index.html" + } + }, + { + "id": [ + { + "kind": "Root", + "name": "Main" + }, + { + "kind": "Module", + "name": "I" + }, + { + "kind": "Value", + "name": "y" + } + ], + "doc": "", + "extra": { + "kind": "Value", + "type": "int" + }, + "display": { + "html": "
    valMain.I.y : int
    ", + "url": "Main/I/index.html#val-y" + } + }, + { + "id": [ + { + "kind": "Root", + "name": "Main" + }, + { + "kind": "Value", + "name": "x" + } + ], + "doc": "", + "extra": { + "kind": "Value", + "type": "int" + }, + "display": { + "html": "
    valMain.x : int
    ", + "url": "Main/index.html#val-x" + } + }, + { + "id": [ + { + "kind": "Root", + "name": "Main" + }, + { + "kind": "Module", + "name": "I" + } + ], + "doc": "a paragraph", + "extra": { + "kind": "Doc", + "subkind": "Paragraph" + }, + "display": { + "html": "
    docMain.I

    a paragraph

    ", + "url": "Main/I/index.html" + } + }, + { + "id": [ + { + "kind": "Root", + "name": "Main" + }, + { + "kind": "Module", + "name": "I" + } + ], + "doc": "and another", + "extra": { + "kind": "Doc", + "subkind": "Paragraph" + }, + "display": { + "html": "
    docMain.I

    and another

    ", + "url": "Main/I/index.html" + } + }, + { + "id": [ + { + "kind": "Root", + "name": "Main" + }, + { + "kind": "Module", + "name": "I" + } + ], + "doc": "verbatim", + "extra": { + "kind": "Doc", + "subkind": "Verbatim" + }, + "display": { + "html": "
    docMain.I
    verbatim
    ", + "url": "Main/I/index.html" + } + }, + { + "id": [ + { + "kind": "Root", + "name": "Main" + }, + { + "kind": "Module", + "name": "I" + } + ], + "doc": "x + 1", + "extra": { + "kind": "Doc", + "subkind": "Paragraph" + }, + "display": { + "html": "
    docMain.I

    x + 1

    ", + "url": "Main/I/index.html" + } + }, + { + "id": [ + { + "kind": "Root", + "name": "Main" + }, + { + "kind": "Module", + "name": "I" + } + ], + "doc": "blibli", + "extra": { + "kind": "Doc", + "subkind": "CodeBlock" + }, + "display": { + "html": "
    docMain.I
    blibli
    ", + "url": "Main/I/index.html" + } + }, + { + "id": [ + { + "kind": "Root", + "name": "Main" + }, + { + "kind": "Value", + "name": "y" + } + ], + "doc": "", + "extra": { + "kind": "Value", + "type": "int" + }, + "display": { + "html": "
    valMain.y : int
    ", + "url": "Main/index.html#val-y" + } + }, + { + "id": [ + { + "kind": "Root", + "name": "Main" + }, + { + "kind": "Value", + "name": "uu" + } + ], + "doc": "", + "extra": { + "kind": "Value", + "type": "int" + }, + "display": { + "html": "
    valMain.uu : int
    ", + "url": "Main/index.html#val-uu" + } + }, + { + "id": [ + { + "kind": "Root", + "name": "Main" + }, + { + "kind": "Module", + "name": "I" + } + ], + "doc": "a paragraph two", + "extra": { + "kind": "Doc", + "subkind": "Paragraph" + }, + "display": { + "html": "
    docMain.I

    a paragraph two

    ", + "url": "Main/I/index.html" + } + }, + { + "id": [ + { + "kind": "Root", + "name": "J" + } + ], + "doc": "a paragraph one", + "extra": { + "kind": "Module" + }, + "display": { + "html": "
    moduleJ

    a paragraph one

    ", + "url": "J/index.html" + } + }, + { + "id": [ + { + "kind": "Root", + "name": "J" + }, + { + "kind": "Value", + "name": "uu" + } + ], + "doc": "", + "extra": { + "kind": "Value", + "type": "int" + }, + "display": { + "html": "
    valJ.uu : int
    ", + "url": "J/index.html#val-uu" + } + }, + { + "id": [ + { + "kind": "Root", + "name": "J" + } + ], + "doc": "a paragraph two", + "extra": { + "kind": "Doc", + "subkind": "Paragraph" + }, + "display": { + "html": "
    docJ

    a paragraph two

    ", + "url": "J/index.html" + } + }, + { + "id": [ + { + "kind": "Page", + "name": "page" + }, + { + "kind": "Label", + "name": "a-title" + } + ], + "doc": "A title", + "extra": { + "kind": "Doc", + "subkind": "Heading" + }, + "display": { + "html": "
    docpage.a-title

    A title

    ", + "url": "page.html#a-title" + } + }, + { + "id": [ + { + "kind": "Page", + "name": "page" + } + ], + "doc": "A paragraph", + "extra": { + "kind": "Doc", + "subkind": "Paragraph" + }, + "display": { + "html": "
    docpage

    A paragraph

    ", + "url": "page.html" + } + }, + { + "id": [ + { + "kind": "Page", + "name": "page" + } + ], + "doc": "some verbatim", + "extra": { + "kind": "Doc", + "subkind": "Verbatim" + }, + "display": { + "html": "
    docpage
    some verbatim
    ", + "url": "page.html" + } + }, + { + "id": [ + { + "kind": "Page", + "name": "page" + } + ], + "doc": "and code", + "extra": { + "kind": "Doc", + "subkind": "CodeBlock" + }, + "display": { + "html": "
    docpage
    and code
    ", + "url": "page.html" + } + }, + { + "id": [ + { + "kind": "Page", + "name": "page" + } + ], + "doc": "a list of things", + "extra": { + "kind": "Doc", + "subkind": "Paragraph" + }, + "display": { + "html": "
    docpage

    a list of things

    ", + "url": "page.html" + } + }, + { + "id": [ + { + "kind": "Page", + "name": "page" + } + ], + "doc": "bliblib", + "extra": { + "kind": "Doc", + "subkind": "Paragraph" + }, + "display": { + "html": "
    docpage

    bliblib

    ", + "url": "page.html" + } + } + ] + +The index.js file need to provide a odoc_search command, from a + + $ cat fuse.js.js > index.js + $ echo "\n\nlet documents = " >> index.js + $ cat index.json >> index.js + + $ echo "\n\nconst options = { keys: ['id', 'doc'] };" >> index.js + $ echo "\nvar idx_fuse = new Fuse(documents, options);" >> index.js + $ echo "\nonmessage = (m) => {\n let query = m.data;\n let result = idx_fuse.search(query);\n postMessage(result.slice(0,200).map(a => a.item.display));};" >> index.js + + $ odoc html-generate --search-file index.js -o html j.odocl + $ odoc html-generate --search-file index.js -o html main.odocl + $ odoc html-generate --search-file index.js -o html page-page.odocl + $ odoc support-files --search-file index.js -o html + + $ find html | sort + html + html/J + html/J/index.html + html/Main + html/Main/I + html/Main/I/index.html + html/Main/M + html/Main/M/index.html + html/Main/index.html + html/fonts + html/fonts/KaTeX_AMS-Regular.woff2 + html/fonts/KaTeX_Caligraphic-Bold.woff2 + html/fonts/KaTeX_Caligraphic-Regular.woff2 + html/fonts/KaTeX_Fraktur-Bold.woff2 + html/fonts/KaTeX_Fraktur-Regular.woff2 + html/fonts/KaTeX_Main-Bold.woff2 + html/fonts/KaTeX_Main-BoldItalic.woff2 + html/fonts/KaTeX_Main-Italic.woff2 + html/fonts/KaTeX_Main-Regular.woff2 + html/fonts/KaTeX_Math-BoldItalic.woff2 + html/fonts/KaTeX_Math-Italic.woff2 + html/fonts/KaTeX_SansSerif-Bold.woff2 + html/fonts/KaTeX_SansSerif-Italic.woff2 + html/fonts/KaTeX_SansSerif-Regular.woff2 + html/fonts/KaTeX_Script-Regular.woff2 + html/fonts/KaTeX_Size1-Regular.woff2 + html/fonts/KaTeX_Size2-Regular.woff2 + html/fonts/KaTeX_Size3-Regular.woff2 + html/fonts/KaTeX_Size4-Regular.woff2 + html/fonts/KaTeX_Typewriter-Regular.woff2 + html/fonts/fira-mono-v14-latin-500.woff2 + html/fonts/fira-mono-v14-latin-regular.woff2 + html/fonts/fira-sans-v17-latin-500.woff2 + html/fonts/fira-sans-v17-latin-500italic.woff2 + html/fonts/fira-sans-v17-latin-700.woff2 + html/fonts/fira-sans-v17-latin-700italic.woff2 + html/fonts/fira-sans-v17-latin-italic.woff2 + html/fonts/fira-sans-v17-latin-regular.woff2 + html/fonts/noticia-text-v15-latin-700.woff2 + html/fonts/noticia-text-v15-latin-italic.woff2 + html/fonts/noticia-text-v15-latin-regular.woff2 + html/highlight.pack.js + html/index.js + html/katex.min.css + html/katex.min.js + html/odoc.css + html/odoc_search.js + html/page.html + +Run + $ firefox html/Main/index.html +to manually test the search diff --git a/test/integration/html_support_files.t/run.t b/test/integration/html_support_files.t/run.t index 06f4ac8559..4bfa5b8b4c 100644 --- a/test/integration/html_support_files.t/run.t +++ b/test/integration/html_support_files.t/run.t @@ -37,6 +37,7 @@ with-theme/katex.min.css with-theme/katex.min.js with-theme/odoc.css + with-theme/odoc_search.js $ odoc support-files --without-theme -o without-theme $ find without-theme | sort @@ -76,4 +77,5 @@ without-theme/highlight.pack.js without-theme/katex.min.css without-theme/katex.min.js + without-theme/odoc_search.js diff --git a/test/pages/resolution.t/run.t b/test/pages/resolution.t/run.t index 29486d8edc..d0a6539edf 100644 --- a/test/pages/resolution.t/run.t +++ b/test/pages/resolution.t/run.t @@ -132,6 +132,7 @@ Let's also check the hierarchy of files produced: html/katex.min.css html/katex.min.js html/odoc.css + html/odoc_search.js html/top1/index.html html/top1/sub1/M1/index.html html/top1/sub1/index.html diff --git a/test/xref2/github_issue_342.t/run.t b/test/xref2/github_issue_342.t/run.t index 750bac24a9..1364f31872 100644 --- a/test/xref2/github_issue_342.t/run.t +++ b/test/xref2/github_issue_342.t/run.t @@ -10,16 +10,16 @@ A quick test to repro the issue found in #342 The table of content: $ cat html/Foo/index.html | grep "odoc-toc" -A 9 -