Skip to content

Commit

Permalink
Compile asset: extract compile_asset in its own module
Browse files Browse the repository at this point in the history
Signed-off-by: Paul-Elliot <[email protected]>
  • Loading branch information
panglesd committed Jul 24, 2024
1 parent def5f84 commit 35e6485
Show file tree
Hide file tree
Showing 5 changed files with 28 additions and 28 deletions.
23 changes: 23 additions & 0 deletions src/odoc/asset.ml
Original file line number Diff line number Diff line change
@@ -0,0 +1,23 @@
let compile ~parent_id ~name ~output_dir =
let open Odoc_model in
let parent_id = Compile.mk_id parent_id in
let id =
Paths.Identifier.Mk.asset_file ((parent_id :> Paths.Identifier.Page.t), name)
in
let directory =
Compile.path_of_id output_dir parent_id
|> Fpath.to_string |> Fs.Directory.of_string
in
let name = "asset-" ^ name ^ ".odoc" in
let output = Fs.File.create ~directory ~name in
let digest = Digest.string name in
let root =
Root.
{
id = (id :> Paths.Identifier.OdocId.t);
digest;
file = Odoc_file.asset name;
}
in
let asset = Lang.Asset.{ name = id; root } in
Odoc_file.save_asset output ~warnings:[] asset
1 change: 1 addition & 0 deletions src/odoc/asset.mli
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
val compile : parent_id:string -> name:string -> output_dir:string -> unit
6 changes: 3 additions & 3 deletions src/odoc/bin/main.ml
Original file line number Diff line number Diff line change
Expand Up @@ -345,7 +345,7 @@ end

module Compile_asset = struct
let compile_asset parent_id name output_dir =
Odoc_odoc.Compile.compile_asset ~parent_id ~name ~output_dir
Odoc_odoc.Asset.compile ~parent_id ~name ~output_dir

let output_dir =
let doc = "Output file directory. " in
Expand All @@ -362,14 +362,14 @@ module Compile_asset = struct
& opt (some string) None
& info ~docs ~docv:"NAME" ~doc [ "name" ])
in
let parent_id_opt =
let parent_id =
let doc = "Parent id." in
Arg.(
required
& opt (some string) None
& info ~docs ~docv:"PARENT" ~doc [ "parent-id" ])
in
Term.(const compile_asset $ parent_id_opt $ name_opt $ output_dir)
Term.(const compile_asset $ parent_id $ name_opt $ output_dir)

let info ~docs =
let man =
Expand Down
23 changes: 0 additions & 23 deletions src/odoc/compile.ml
Original file line number Diff line number Diff line change
Expand Up @@ -337,26 +337,3 @@ let compile ~resolver ~hidden ~cli_spec ~warnings_options input =
Error.handle_errors_and_warnings ~warnings_options result >>= fun unit ->
Odoc_file.save_unit output ~warnings unit;
Ok ()

let compile_asset ~parent_id ~name ~output_dir =
let open Odoc_model in
let parent_id = mk_id parent_id in
let id =
Paths.Identifier.Mk.asset_file ((parent_id :> Paths.Identifier.Page.t), name)
in
let directory =
path_of_id output_dir parent_id |> Fpath.to_string |> Fs.Directory.of_string
in
let name = "asset-" ^ name ^ ".odoc" in
let output = Fs.File.create ~directory ~name in
let digest = Digest.string name in
let root =
Root.
{
id = (id :> Paths.Identifier.OdocId.t);
digest;
file = Odoc_file.asset name;
}
in
let asset = Lang.Asset.{ name = id; root } in
Odoc_file.save_asset output ~warnings:[] asset
3 changes: 1 addition & 2 deletions src/odoc/compile.mli
Original file line number Diff line number Diff line change
Expand Up @@ -50,6 +50,7 @@ val resolve_parent_page :
and its children as a list of reference. *)

val mk_id : string -> Identifier.ContainerPage.t
val path_of_id : string -> Comment.Identifier.Id.container_page -> Fpath.t

val compile :
resolver:Resolver.t ->
Expand All @@ -59,5 +60,3 @@ val compile :
Fpath.t ->
(unit, [> msg ]) result
(** Produces .odoc files out of [.cm{i,t,ti}] or .mld files. *)

val compile_asset : parent_id:string -> name:string -> output_dir:string -> unit

0 comments on commit 35e6485

Please sign in to comment.