Skip to content

Commit

Permalink
Extracted SC.PP as Preprocessing (#560)
Browse files Browse the repository at this point in the history
  • Loading branch information
jeremiedimino committed Feb 28, 2018
1 parent 8fd3335 commit 45535f7
Show file tree
Hide file tree
Showing 9 changed files with 419 additions and 417 deletions.
4 changes: 4 additions & 0 deletions src/build.ml
Original file line number Diff line number Diff line change
Expand Up @@ -166,6 +166,10 @@ let fail ?targets x =
| None -> Fail x
| Some l -> Targets l >>> Fail x

let of_result = function
| Ok x -> return x
| Error e -> fail { fail = fun () -> raise e }

let memoize name t =
Memo { name; t; state = Unevaluated }

Expand Down
2 changes: 2 additions & 0 deletions src/build.mli
Original file line number Diff line number Diff line change
Expand Up @@ -78,6 +78,8 @@ val file_exists_opt : Path.t -> ('a, 'b) t -> ('a, 'b option) t
backtrace *)
val fail : ?targets:Path.t list -> fail -> (_, _) t

val of_result : ('a, exn) Result.t -> (unit, 'a) t

(** [memoize name t] is an arrow that behaves like [t] except that its
result is computed only once. *)
val memoize : string -> (unit, 'a) t -> (unit, 'a) t
Expand Down
6 changes: 3 additions & 3 deletions src/gen_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -505,7 +505,7 @@ module Gen(P : Install_rules.Params) = struct
(* Preprocess before adding the alias module as it doesn't need
preprocessing *)
let modules =
SC.PP.pp_and_lint_modules sctx ~dir ~dep_kind ~modules ~scope
Preprocessing.pp_and_lint_modules sctx ~dir ~dep_kind ~modules ~scope
~preprocess:lib.buildable.preprocess
~preprocessor_deps:
(SC.Deps.interpret sctx ~scope ~dir
Expand Down Expand Up @@ -754,7 +754,7 @@ module Gen(P : Install_rules.Params) = struct
SC.Deps.interpret sctx exes.buildable.preprocessor_deps
~scope ~dir
in
SC.PP.pp_and_lint_modules sctx ~dir ~dep_kind:Required ~modules ~scope
Preprocessing.pp_and_lint_modules sctx ~dir ~dep_kind:Required ~modules ~scope
~preprocess:exes.buildable.preprocess
~preprocessor_deps
~lint:exes.buildable.lint
Expand Down Expand Up @@ -920,7 +920,7 @@ module Gen(P : Install_rules.Params) = struct
| ".js" :: rest -> Js_of_ocaml_rules.setup_separate_compilation_rules
sctx rest
| "_doc" :: rest -> Odoc.gen_rules sctx rest ~dir
| ".ppx" :: rest -> SC.PP.gen_rules sctx rest
| ".ppx" :: rest -> Preprocessing.gen_rules sctx rest
| _ ->
match Path.Map.find stanzas_per_dir dir with
| Some x -> gen_rules x
Expand Down
2 changes: 1 addition & 1 deletion src/install_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -189,7 +189,7 @@ module Gen(P : Install_params) = struct
else
pps
in
let ppx_exe = SC.PP.get_ppx_driver sctx ~scope pps in
let ppx_exe = Preprocessing.get_ppx_driver sctx ~scope pps in
[ppx_exe]
in
List.concat
Expand Down
4 changes: 2 additions & 2 deletions src/merlin.ml
Original file line number Diff line number Diff line change
Expand Up @@ -16,11 +16,11 @@ type t =
let ppx_flags sctx ~dir:_ ~scope ~src_dir:_ { preprocess; libname; _ } =
match preprocess with
| Pps { pps; flags } ->
let exe = SC.PP.get_ppx_driver sctx ~scope pps in
let exe = Preprocessing.get_ppx_driver sctx ~scope pps in
let command =
List.map (Path.to_absolute_filename exe
:: "--as-ppx"
:: SC.PP.cookie_library_name libname
:: Preprocessing.cookie_library_name libname
@ flags)
~f:quote_for_shell
|> String.concat ~sep:" "
Expand Down

0 comments on commit 45535f7

Please sign in to comment.