Skip to content

Commit

Permalink
Allow use of ppx in dune
Browse files Browse the repository at this point in the history
This adds an `(include_preprocessed_sources)` stanza which generates
rules to promote preprocessed version of sources.
It's used in a `ppx/` folder at the project root.
For any library or executable stanza with a `(preprocess (pps ...))`
field in <path>, it will generate promotion rules for preprocessed
versions in `ppx/<path>`.

It also modifies `duneboot.ml` to use `ppx/<path>.ml(i)` instead of
`<path>.ml(i)` if it exists, allowing us to use ppx in development
without making it a build dependency.

Signed-off-by: Nathan Rebours <[email protected]>
  • Loading branch information
NathanReb committed Nov 20, 2023
1 parent 7debf4e commit 373c949
Show file tree
Hide file tree
Showing 22 changed files with 306 additions and 18 deletions.
6 changes: 5 additions & 1 deletion boot/duneboot.ml
Original file line number Diff line number Diff line change
Expand Up @@ -32,6 +32,7 @@ let concurrency, verbose, _keep_generated_files, debug, secondary, force_byte_co
(** {2 General configuration} *)

let build_dir = "_boot"
let preprocessed_dir = "ppx"

type task =
{ target : string * string
Expand Down Expand Up @@ -875,7 +876,10 @@ module Library = struct
copy "line" fn dst;
Fiber.return [ mangled ]
| Ml | Mli ->
copy "" fn dst ~header;
let preprocessed = preprocessed_dir ^/ fn in
if Sys.file_exists preprocessed
then copy "" preprocessed dst ~header
else copy "" fn dst ~header;
Fiber.return [ mangled ]
| Mll -> copy_lexer fn dst ~header >>> Fiber.return [ mangled ]
| Mly -> copy_parser fn dst ~header >>> Fiber.return [ mangled; mangled ^ "i" ]))
Expand Down
2 changes: 1 addition & 1 deletion chrome-trace.opam
Original file line number Diff line number Diff line change
Expand Up @@ -10,7 +10,7 @@ homepage: "https://github.com/ocaml/dune"
doc: "https://dune.readthedocs.io/"
bug-reports: "https://github.com/ocaml/dune/issues"
depends: [
"dune" {>= "3.5"}
"dune" {>= "3.10"}
"ocaml" {>= "4.08.0"}
"odoc" {with-doc}
]
Expand Down
2 changes: 1 addition & 1 deletion dune-action-plugin.opam
Original file line number Diff line number Diff line change
Expand Up @@ -17,7 +17,7 @@ homepage: "https://github.com/ocaml/dune"
doc: "https://dune.readthedocs.io/"
bug-reports: "https://github.com/ocaml/dune/issues"
depends: [
"dune" {>= "3.5"}
"dune" {>= "3.10"}
"dune-glob" {= version}
"csexp" {>= "1.5.0"}
"ppx_expect" {with-test}
Expand Down
2 changes: 1 addition & 1 deletion dune-build-info.opam
Original file line number Diff line number Diff line change
Expand Up @@ -16,7 +16,7 @@ homepage: "https://github.com/ocaml/dune"
doc: "https://dune.readthedocs.io/"
bug-reports: "https://github.com/ocaml/dune/issues"
depends: [
"dune" {>= "3.5"}
"dune" {>= "3.10"}
"ocaml" {>= "4.08"}
"odoc" {with-doc}
]
Expand Down
2 changes: 1 addition & 1 deletion dune-configurator.opam
Original file line number Diff line number Diff line change
Expand Up @@ -18,7 +18,7 @@ homepage: "https://github.com/ocaml/dune"
doc: "https://dune.readthedocs.io/"
bug-reports: "https://github.com/ocaml/dune/issues"
depends: [
"dune" {>= "3.5"}
"dune" {>= "3.10"}
"ocaml" {>= "4.04.0"}
"base-unix"
"csexp" {>= "1.5.0"}
Expand Down
2 changes: 1 addition & 1 deletion dune-glob.opam
Original file line number Diff line number Diff line change
Expand Up @@ -10,7 +10,7 @@ homepage: "https://github.com/ocaml/dune"
doc: "https://dune.readthedocs.io/"
bug-reports: "https://github.com/ocaml/dune/issues"
depends: [
"dune" {>= "3.5"}
"dune" {>= "3.10"}
"stdune" {= version}
"dyn"
"ordering"
Expand Down
2 changes: 1 addition & 1 deletion dune-private-libs.opam
Original file line number Diff line number Diff line change
Expand Up @@ -17,7 +17,7 @@ homepage: "https://github.com/ocaml/dune"
doc: "https://dune.readthedocs.io/"
bug-reports: "https://github.com/ocaml/dune/issues"
depends: [
"dune" {>= "3.5"}
"dune" {>= "3.10"}
"csexp" {>= "1.5.0"}
"pp" {>= "1.1.0"}
"dyn" {= version}
Expand Down
3 changes: 2 additions & 1 deletion dune-project
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
(lang dune 3.5)
(lang dune 3.10)
; ^^^
; When changing the version, don't forget to regenerate *.opam files
; by running [dune build].
Expand All @@ -12,6 +12,7 @@

; Reserved for Dune itself. This is to help with the bootstrap
(using dune-bootstrap-info 0.1)
(using include_preprocessed_sources 0.1)

(license MIT)
(maintainers "Jane Street Group, LLC <[email protected]>")
Expand Down
2 changes: 1 addition & 1 deletion dune-rpc-lwt.opam
Original file line number Diff line number Diff line change
Expand Up @@ -9,7 +9,7 @@ homepage: "https://github.com/ocaml/dune"
doc: "https://dune.readthedocs.io/"
bug-reports: "https://github.com/ocaml/dune/issues"
depends: [
"dune" {>= "3.5"}
"dune" {>= "3.10"}
"dune-rpc" {= version}
"result" {>= "1.5"}
"csexp" {>= "1.5.0"}
Expand Down
2 changes: 1 addition & 1 deletion dune-rpc.opam
Original file line number Diff line number Diff line change
Expand Up @@ -9,7 +9,7 @@ homepage: "https://github.com/ocaml/dune"
doc: "https://dune.readthedocs.io/"
bug-reports: "https://github.com/ocaml/dune/issues"
depends: [
"dune" {>= "3.5"}
"dune" {>= "3.10"}
"csexp"
"ordering"
"dyn"
Expand Down
2 changes: 1 addition & 1 deletion dune-site.opam
Original file line number Diff line number Diff line change
Expand Up @@ -9,7 +9,7 @@ homepage: "https://github.com/ocaml/dune"
doc: "https://dune.readthedocs.io/"
bug-reports: "https://github.com/ocaml/dune/issues"
depends: [
"dune" {>= "3.5"}
"dune" {>= "3.10"}
"dune-private-libs" {= version}
"odoc" {with-doc}
]
Expand Down
2 changes: 1 addition & 1 deletion dyn.opam
Original file line number Diff line number Diff line change
Expand Up @@ -9,7 +9,7 @@ homepage: "https://github.com/ocaml/dune"
doc: "https://dune.readthedocs.io/"
bug-reports: "https://github.com/ocaml/dune/issues"
depends: [
"dune" {>= "3.5"}
"dune" {>= "3.10"}
"ocaml" {>= "4.08.0"}
"ordering" {= version}
"pp" {>= "1.1.0"}
Expand Down
2 changes: 1 addition & 1 deletion ocamlc-loc.opam
Original file line number Diff line number Diff line change
Expand Up @@ -10,7 +10,7 @@ homepage: "https://github.com/ocaml/dune"
doc: "https://dune.readthedocs.io/"
bug-reports: "https://github.com/ocaml/dune/issues"
depends: [
"dune" {>= "3.5"}
"dune" {>= "3.10"}
"ocaml" {>= "4.08.0"}
"dyn" {= version}
"odoc" {with-doc}
Expand Down
2 changes: 1 addition & 1 deletion ordering.opam
Original file line number Diff line number Diff line change
Expand Up @@ -9,7 +9,7 @@ homepage: "https://github.com/ocaml/dune"
doc: "https://dune.readthedocs.io/"
bug-reports: "https://github.com/ocaml/dune/issues"
depends: [
"dune" {>= "3.5"}
"dune" {>= "3.10"}
"ocaml" {>= "4.08.0"}
"odoc" {with-doc}
]
Expand Down
2 changes: 2 additions & 0 deletions ppx/dune
Original file line number Diff line number Diff line change
@@ -0,0 +1,2 @@
(include_preprocessed_sources
(dirs ../src))
2 changes: 1 addition & 1 deletion src/dune_async_io/async_io.ml
Original file line number Diff line number Diff line change
Expand Up @@ -4,9 +4,9 @@ open Fiber.O
module Fd = struct
type t = Unix.file_descr

let to_dyn = Dyn.opaque
let equal = Poly.equal
let hash = Poly.hash
let to_dyn = Dyn.opaque
end

module type Scheduler = sig
Expand Down
1 change: 1 addition & 0 deletions src/dune_rules/dune_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -61,6 +61,7 @@ module Package = Package
module Dialect = Dialect
module Private_context = Private_context
module Odoc = Odoc
module Include_preprocessed_sources = Include_preprocessed_sources

module Install_rules = struct
let install_file = Install_rules.install_file
Expand Down
14 changes: 13 additions & 1 deletion src/dune_rules/gen_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -178,6 +178,15 @@ end = struct
Expander.eval_blang expander mel.enabled_if
>>= if_available_buildable ~loc:mel.loc (fun () ->
Melange_rules.setup_emit_cmj_rules ~dir_contents ~dir ~scope ~sctx ~expander mel)
| Include_preprocessed_sources.T {dirs_to_include} ->
let+ () =
let* dirs_to_include =
Memo.all
(List.map ~f:(Expander.No_deps.expand_path expander) dirs_to_include)
in
Include_preprocessed_sources.gen_stanza_rules sctx ~dir ~dirs_to_include
in
empty_none
| _ -> Memo.return empty_none
;;

Expand Down Expand Up @@ -562,7 +571,10 @@ let gen_rules_regular_directory sctx ~src_dir ~components ~dir =
| Some opam_rules ->
Gen_rules.map_rules rules ~f:(Gen_rules.Rules.combine_exn opam_rules)
and+ melange_rules = Melange_rules.setup_emit_js_rules sctx ~dir in
Gen_rules.combine melange_rules rules
and+ include_pp_src_rules =
Include_preprocessed_sources.gen_sub_dir_rules ~dir
in
Gen_rules.(combine include_pp_src_rules (combine melange_rules rules))
;;

(* Once [gen_rules] has decided what to do with the directory, it should end
Expand Down
Loading

0 comments on commit 373c949

Please sign in to comment.