Skip to content

Commit

Permalink
WIP: Ocamlformat integration
Browse files Browse the repository at this point in the history
  • Loading branch information
emillon committed Sep 12, 2018
1 parent 2034c78 commit 7b01914
Show file tree
Hide file tree
Showing 19 changed files with 147 additions and 2 deletions.
3 changes: 3 additions & 0 deletions src/dune_file.ml
Original file line number Diff line number Diff line change
Expand Up @@ -680,6 +680,7 @@ module Buildable = struct
; ocamlopt_flags : Ordered_set_lang.Unexpanded.t
; js_of_ocaml : Js_of_ocaml.t
; allow_overlapping_dependencies : bool
; ocamlformat : bool
}

let dparse =
Expand All @@ -700,6 +701,7 @@ module Buildable = struct
field "js_of_ocaml" Js_of_ocaml.dparse ~default:Js_of_ocaml.default
and allow_overlapping_dependencies =
field_b "allow_overlapping_dependencies"
and ocamlformat = field_b "ocamlformat"
in
{ loc
; preprocess
Expand All @@ -713,6 +715,7 @@ module Buildable = struct
; ocamlopt_flags
; js_of_ocaml
; allow_overlapping_dependencies
; ocamlformat
}

let single_preprocess t =
Expand Down
1 change: 1 addition & 0 deletions src/dune_file.mli
Original file line number Diff line number Diff line change
Expand Up @@ -141,6 +141,7 @@ module Buildable : sig
; ocamlopt_flags : Ordered_set_lang.Unexpanded.t
; js_of_ocaml : Js_of_ocaml.t
; allow_overlapping_dependencies : bool
; ocamlformat : bool
}

(** Preprocessing specification used by all modules or [No_preprocessing] *)
Expand Down
1 change: 1 addition & 0 deletions src/lib_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -375,6 +375,7 @@ module Gen (P : Install_rules.Params) = struct
~lib_name:(Some lib.name)
~dir_kind
in
Ocamlformat.gen_rules sctx lib.buildable ~dir ~scope modules;
let modules = Preprocessing.pp_modules pp modules in

let modules =
Expand Down
72 changes: 72 additions & 0 deletions src/ocamlformat.ml
Original file line number Diff line number Diff line change
@@ -0,0 +1,72 @@
open Import

let flag_of_kind : Ml_kind.t -> _ =
function
| Impl -> "--impl"
| Intf -> "--intf"

let add_alias_format sctx loc ~dir ~scope action =
let alias_conf =
{ Dune_file.Alias_conf.name = "format"
; deps = []
; action = Some (loc, action)
; locks = []
; package = None
; enabled_if = None
; loc
}
in
Simple_rules.alias sctx ~dir ~scope alias_conf

let sv = String_with_vars.virt_text __POS__

let target_var = String_with_vars.virt_var __POS__ "targets"

let gen_rules_for_module sctx loc ocamlformat ~dir ~scope m =
Format.printf "dir = %a\n" Path.pp dir;
Module.iter m ~f:(fun kind src ->
let flag = flag_of_kind kind in
let path = Path.basename src.path in
let dep x = String_with_vars.make_macro loc "dep" x in
let formatted = path ^ ".formatted" in
let format_action =
let args = [sv flag; dep path] in
Action.Unexpanded.Redirect
( Stdout
, target_var
, Run (dep @@ Path.to_string ocamlformat, args)
)
in
let format_rule =
{ Dune_file.Rule.targets = Static [formatted]
; deps = []
; action = (loc, format_action)
; mode = Standard
; locks = []
; loc
}
in
let diff_action =
Action.Unexpanded.Diff
{ optional = false
; mode = Text
; file1 = dep path
; file2 = sv formatted
}
in
let _ : Path.t list = Simple_rules.user_rule sctx ~dir ~scope format_rule in
add_alias_format sctx loc ~dir ~scope diff_action
)

let gen_rules sctx (buildable:Dune_file.Buildable.t)
~dir ~scope modules =
if buildable.ocamlformat then
let loc = buildable.loc in
match Bin.which "ocamlformat" with
| None ->
let msg = "Cannot find ocamlformat, skipping.\n" in
add_alias_format sctx loc ~dir ~scope (Echo [sv msg])
| Some ocamlformat ->
Module.Name.Map.iter
modules
~f:(gen_rules_for_module sctx loc ocamlformat ~dir ~scope)
9 changes: 9 additions & 0 deletions src/ocamlformat.mli
Original file line number Diff line number Diff line change
@@ -0,0 +1,9 @@
open Import

val gen_rules :
Super_context.t
-> Dune_file.Buildable.t
-> dir:Path.t
-> scope:Scope.t
-> Module.t Module.Name.Map.t
-> unit
10 changes: 8 additions & 2 deletions src/string_with_vars.ml
Original file line number Diff line number Diff line change
Expand Up @@ -20,16 +20,22 @@ let make ?(quoted=false) loc part =
let make_text ?quoted loc s =
make ?quoted loc (Text s)

let make_var ?quoted loc name =
let make_var_args ?quoted loc name payload =
let var =
{ loc
; name
; payload = None
; payload
; syntax = Percent
}
in
make ?quoted loc (Var var)

let make_var ?quoted loc name =
make_var_args ?quoted loc name None

let make_macro ?quoted loc macro param =
make_var_args ?quoted loc macro (Some param)

let literal ~quoted ~loc s =
{ parts = [Text s]
; quoted
Expand Down
1 change: 1 addition & 0 deletions src/string_with_vars.mli
Original file line number Diff line number Diff line change
Expand Up @@ -27,6 +27,7 @@ val virt_var : ?quoted: bool -> (string * int * int * int) -> string -> t
val virt_text : (string * int * int * int) -> string -> t
val make_var : ?quoted: bool -> Loc.t -> string -> t
val make_text : ?quoted: bool -> Loc.t -> string -> t
val make_macro : ?quoted: bool -> Loc.t -> string -> string -> t

val is_var : t -> name:string -> bool

Expand Down
10 changes: 10 additions & 0 deletions test/blackbox-tests/dune.inc
Original file line number Diff line number Diff line change
Expand Up @@ -610,6 +610,14 @@
test-cases/ocamldep-multi-stanzas
(progn (run %{exe:cram.exe} -test run.t) (diff? run.t run.t.corrected)))))

(alias
(name ocamlformat)
(deps (package dune) (source_tree test-cases/ocamlformat))
(action
(chdir
test-cases/ocamlformat
(progn (run %{exe:cram.exe} -test run.t) (diff? run.t run.t.corrected)))))

(alias
(name ocamllex-jbuild)
(deps (package dune) (source_tree test-cases/ocamllex-jbuild))
Expand Down Expand Up @@ -960,6 +968,7 @@
(alias ocaml-config-macro)
(alias ocaml-syntax)
(alias ocamldep-multi-stanzas)
(alias ocamlformat)
(alias ocamllex-jbuild)
(alias odoc)
(alias odoc-unique-mlds)
Expand Down Expand Up @@ -1064,6 +1073,7 @@
(alias ocaml-config-macro)
(alias ocaml-syntax)
(alias ocamldep-multi-stanzas)
(alias ocamlformat)
(alias ocamllex-jbuild)
(alias output-obj)
(alias package-dep)
Expand Down
3 changes: 3 additions & 0 deletions test/blackbox-tests/test-cases/ocamlformat/dune
Original file line number Diff line number Diff line change
@@ -0,0 +1,3 @@
(executable
(name ignored)
)
1 change: 1 addition & 0 deletions test/blackbox-tests/test-cases/ocamlformat/dune-project
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
(lang dune 1.2)
3 changes: 3 additions & 0 deletions test/blackbox-tests/test-cases/ocamlformat/ignored.ml
Original file line number Diff line number Diff line change
@@ -0,0 +1,3 @@
let () =
print_endline
"hello"
Empty file.
4 changes: 4 additions & 0 deletions test/blackbox-tests/test-cases/ocamlformat/lib/dune
Original file line number Diff line number Diff line change
@@ -0,0 +1,4 @@
(library
(name lib)
(ocamlformat)
)
1 change: 1 addition & 0 deletions test/blackbox-tests/test-cases/ocamlformat/lib/lib.ml.orig
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
let x = 1
1 change: 1 addition & 0 deletions test/blackbox-tests/test-cases/ocamlformat/lib/lib.mli
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
val x : int
4 changes: 4 additions & 0 deletions test/blackbox-tests/test-cases/ocamlformat/lib2/dune
Original file line number Diff line number Diff line change
@@ -0,0 +1,4 @@
(library
(name lib2)
(ocamlformat)
)
1 change: 1 addition & 0 deletions test/blackbox-tests/test-cases/ocamlformat/lib2/lib2.ml
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
let y=()
2 changes: 2 additions & 0 deletions test/blackbox-tests/test-cases/ocamlformat/lib2/lib2.mli
Original file line number Diff line number Diff line change
@@ -0,0 +1,2 @@
val y :
unit
22 changes: 22 additions & 0 deletions test/blackbox-tests/test-cases/ocamlformat/run.t
Original file line number Diff line number Diff line change
@@ -0,0 +1,22 @@
Formatting can be checked using the @format target:

$ cp lib/lib.ml.orig lib/lib.ml
$ dune build @format --diff-command false
sh (internal) (exit 1)
(cd _build/default && /bin/sh -c 'false lib/lib.ml lib/lib.ml.formatted')
sh (internal) (exit 1)
(cd _build/default && /bin/sh -c 'false lib/lib.mli lib/lib.mli.formatted')
sh (internal) (exit 1)
(cd _build/default && /bin/sh -c 'false lib2/lib2.mli lib2/lib2.mli.formatted')
sh (internal) (exit 1)
(cd _build/default && /bin/sh -c 'false lib2/lib2.ml lib2/lib2.ml.formatted')
dir = _build/default/lib2
dir = _build/default/lib
[1]

And fixable files can be promoted:

$ dune promote lib/lib.ml
Promoting _build/default/lib/lib.ml.formatted to lib/lib.ml.
$ cat lib/lib.ml
let x = 1

0 comments on commit 7b01914

Please sign in to comment.