Skip to content

Commit

Permalink
Removing now unused --search-script argument
Browse files Browse the repository at this point in the history
Signed-off-by: Paul-Elliot <[email protected]>
  • Loading branch information
panglesd committed Jul 12, 2023
1 parent 28e13c3 commit 4d93974
Show file tree
Hide file tree
Showing 6 changed files with 7 additions and 21 deletions.
6 changes: 1 addition & 5 deletions src/html/config.ml
Original file line number Diff line number Diff line change
Expand Up @@ -10,11 +10,10 @@ 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 ~search_files () =
~flat ~open_details ~as_json () =
{
semantic_uris;
indent;
Expand All @@ -24,7 +23,6 @@ let v ?(search_result = false) ?theme_uri ?support_uri ~semantic_uris ~indent
support_uri;
as_json;
search_result;
search_files;
}

let theme_uri config =
Expand All @@ -44,5 +42,3 @@ 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
3 changes: 0 additions & 3 deletions src/html/config.mli
Original file line number Diff line number Diff line change
Expand Up @@ -11,7 +11,6 @@ val v :
flat:bool ->
open_details:bool ->
as_json:bool ->
search_files:string list ->
unit ->
t

Expand All @@ -30,5 +29,3 @@ val open_details : t -> bool
val as_json : t -> bool

val search_result : t -> bool

val search_files : t -> string list
13 changes: 3 additions & 10 deletions src/odoc/bin/main.ml
Original file line number Diff line number Diff line change
Expand Up @@ -744,13 +744,6 @@ 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 \
Expand All @@ -771,17 +764,17 @@ 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 search_files =
as_json source_file assets =
let open_details = not closed_details in
let html_config =
Odoc_html.Config.v ~theme_uri ~support_uri ~semantic_uris ~indent ~flat
~open_details ~as_json ~search_files ()
~open_details ~as_json ()
in
{ Html_page.html_config; source_file; assets }
in
Term.(
const config $ semantic_uris $ closed_details $ indent $ theme_uri
$ support_uri $ flat $ as_json $ source_file $ assets $ search_files)
$ support_uri $ flat $ as_json $ source_file $ assets)
end

module Odoc_html = Make_renderer (Odoc_html_args)
Expand Down
2 changes: 1 addition & 1 deletion src/odoc/html_fragment.ml
Original file line number Diff line number Diff line change
Expand Up @@ -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 ~search_files:[] ()
~open_details:false ~as_json:false ()
in
let html = Odoc_html.Generator.doc ~config ~xref_base_uri page in
let oc = open_out (Fs.File.to_string output) in
Expand Down
2 changes: 1 addition & 1 deletion src/search/generator.ml
Original file line number Diff line number Diff line change
Expand Up @@ -163,7 +163,7 @@ let html_of_entry (entry : Odoc_model.Fold.item) =
let html_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:[] ()
~flat:false ~open_details:false ~as_json:false ()
in
Tyxml.Html.div ~a:[]
@@ Odoc_html.Generator.doc ~config ~xref_base_uri:""
Expand Down
2 changes: 1 addition & 1 deletion src/search/render.ml
Original file line number Diff line number Diff line change
Expand Up @@ -130,7 +130,7 @@ 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:[] ()
~flat:false ~open_details:false ~as_json:false ()

let html_of_doc doc =
Tyxml.Html.div ~a:[]
Expand Down

0 comments on commit 4d93974

Please sign in to comment.