Skip to content

Commit

Permalink
draft: compile flags feature
Browse files Browse the repository at this point in the history
  • Loading branch information
lubegasimon committed Aug 12, 2020
1 parent 5e204ce commit 23d8c79
Show file tree
Hide file tree
Showing 15 changed files with 101 additions and 27 deletions.
7 changes: 5 additions & 2 deletions src/dune/cinaps.ml
Original file line number Diff line number Diff line change
Expand Up @@ -9,6 +9,7 @@ type t =
; preprocess : Preprocess.Without_instrumentation.t Preprocess.Per_module.t
; preprocessor_deps : Dep_conf.t list
; flags : Ocaml_flags.Spec.t
; compile_flags : Ocaml_flags.Spec.t
}

let name = "cinaps"
Expand All @@ -32,8 +33,9 @@ let decode =
field "libraries"
(Dune_file.Lib_deps.decode ~allow_re_export:false)
~default:[]
and+ flags = Ocaml_flags.Spec.decode in
{ loc; files; libraries; preprocess; preprocessor_deps; flags })
and+ flags = Ocaml_flags.Spec.decode
and+ compile_flags =Ocaml_flags.Spec.decode in
{ loc; files; libraries; preprocess; preprocessor_deps; flags; compile_flags })

let () =
let open Dune_lang.Decoder in
Expand Down Expand Up @@ -100,6 +102,7 @@ let gen_rules sctx t ~dir ~scope =
~requires_compile:(Lib.Compile.direct_requires compile_info)
~requires_link:(Lib.Compile.requires_link compile_info)
~flags:(Ocaml_flags.of_list [ "-w"; "-24" ])
~compile_flags:(Ocaml_flags.of_list [ "-w"; "-24" ])
~js_of_ocaml:None ~dynlink:false ~package:None
in
Exe.build_and_link cctx
Expand Down
14 changes: 13 additions & 1 deletion src/dune/compilation_context.ml
Original file line number Diff line number Diff line change
Expand Up @@ -56,6 +56,7 @@ type t =
; obj_dir : Path.Build.t Obj_dir.t
; modules : Modules.t
; flags : Ocaml_flags.t
; compile_flags : Ocaml_flags.t
; requires_compile : Lib.t list Or_exn.t
; requires_link : Lib.t list Or_exn.t Lazy.t
; includes : Includes.t
Expand Down Expand Up @@ -84,6 +85,8 @@ let modules t = t.modules

let flags t = t.flags

let compile_flags t = t.compile_flags

let requires_compile t = t.requires_compile

let requires_link t = Lazy.force t.requires_link
Expand All @@ -110,7 +113,7 @@ let modes t = t.modes

let context t = Super_context.context t.super_context

let create ~super_context ~scope ~expander ~obj_dir ~modules ~flags
let create ~super_context ~scope ~expander ~obj_dir ~modules ~flags ~compile_flags
~requires_compile ~requires_link ?(preprocessing = Preprocessing.dummy)
~opaque ?stdlib ~js_of_ocaml ~dynlink ~package ?vimpl ?modes () =
let requires_compile =
Expand Down Expand Up @@ -139,6 +142,7 @@ let create ~super_context ~scope ~expander ~obj_dir ~modules ~flags
; obj_dir
; modules
; flags
; compile_flags
; requires_compile
; requires_link
; includes = Includes.make ~opaque ~requires:requires_compile
Expand All @@ -159,6 +163,11 @@ let for_alias_module t =
let dune_version = Dune_project.dune_version project in
Ocaml_flags.default ~profile:(SC.profile t.super_context) ~dune_version
in
let compile_flags =
let project = Scope.project t.scope in
let dune_version = Dune_project.dune_version project in
Ocaml_flags.default ~profile:(SC.profile t.super_context) ~dune_version
in
let sandbox =
let ctx = Super_context.context t.super_context in
(* If the compiler reads the cmi for module alias even with [-w -49
Expand All @@ -173,6 +182,9 @@ let for_alias_module t =
flags =
Ocaml_flags.append_common flags
[ "-w"; "-49"; "-nopervasives"; "-nostdlib" ]
; compile_flags =
Ocaml_flags.append_common compile_flags
[ "-w"; "-49"; "-nopervasives"; "-nostdlib" ]
; includes = Includes.empty
; stdlib = None
; sandbox
Expand Down
3 changes: 3 additions & 0 deletions src/dune/compilation_context.mli
Original file line number Diff line number Diff line change
Expand Up @@ -28,6 +28,7 @@ val create :
-> obj_dir:Path.Build.t Obj_dir.t
-> modules:Modules.t
-> flags:Ocaml_flags.t
-> compile_flags:Ocaml_flags.t
-> requires_compile:Lib.t list Or_exn.t
-> requires_link:Lib.t list Or_exn.t Lazy.t
-> ?preprocessing:Preprocessing.t
Expand Down Expand Up @@ -60,6 +61,8 @@ val modules : t -> Modules.t

val flags : t -> Ocaml_flags.t

val compile_flags : t -> Ocaml_flags.t

val requires_link : t -> Lib.t list Or_exn.t

val requires_compile : t -> Lib.t list Or_exn.t
Expand Down
8 changes: 5 additions & 3 deletions src/dune/exe_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -87,6 +87,7 @@ let executables_rules ~sctx ~dir ~expander ~dir_contents ~scope ~compile_info
l
in
let flags = SC.ocaml_flags sctx ~dir exes.buildable.flags in
let compile_flags = SC.ocaml_flags sctx ~dir exes.buildable.flags in
let link_deps = Dep_conf_eval.unnamed ~expander exes.link_deps in
let foreign_archives = exes.buildable.foreign_archives |> List.map ~f:snd in
let link_flags =
Expand Down Expand Up @@ -129,8 +130,9 @@ let executables_rules ~sctx ~dir ~expander ~dir_contents ~scope ~compile_info
| _ -> false)
in
Compilation_context.create () ~super_context:sctx ~expander ~scope ~obj_dir
~modules ~flags ~requires_link ~requires_compile ~preprocessing:pp
~js_of_ocaml ~opaque:Inherit_from_settings ~dynlink ~package:exes.package
~modules ~flags ~compile_flags ~requires_link ~requires_compile
~preprocessing:pp ~js_of_ocaml ~opaque:Inherit_from_settings ~dynlink
~package:exes.package
in
let o_files =
if not (Executables.has_foreign exes) then
Expand Down Expand Up @@ -172,7 +174,7 @@ let executables_rules ~sctx ~dir ~expander ~dir_contents ~scope ~compile_info
Exe.build_and_link_many cctx ~programs ~linkages ~link_args ~o_files
~promote:exes.promote ~embed_in_plugin_libraries;
( cctx
, Merlin.make () ~requires:requires_compile ~flags ~modules
, Merlin.make () ~requires:requires_compile ~flags ~modules ~compile_flags
~preprocess:(Preprocess.Per_module.single_preprocess preprocess)
~obj_dir )

Expand Down
8 changes: 5 additions & 3 deletions src/dune/inline_tests.ml
Original file line number Diff line number Diff line change
Expand Up @@ -283,9 +283,11 @@ include Sub_system.Register_end_point (struct
~obj_dir ~modules ~opaque:(Explicit false) ~requires_compile:runner_libs
~requires_link:(lazy runner_libs)
~flags:
(Ocaml_flags.append_common
(Super_context.ocaml_flags sctx ~dir lib.buildable.flags)
[ "-w"; "-24"; "-g" ])
(Ocaml_flags.of_list [ "-w"; "-24"; "-g" ])
~compile_flags:
(Ocaml_flags.append_common
(Super_context.ocaml_flags sctx ~dir lib.buildable.flags)
[ "-w"; "-24"; "-g" ])
~js_of_ocaml:(Some lib.buildable.js_of_ocaml) ~dynlink:false
~package:(Option.map lib.public ~f:Dune_file.Public_lib.package)
in
Expand Down
6 changes: 4 additions & 2 deletions src/dune/lib_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -338,6 +338,7 @@ let cctx (lib : Library.t) ~sctx ~source_modules ~dir ~expander ~scope
Required
in
let flags = Super_context.ocaml_flags sctx ~dir lib.buildable.flags in
let compile_flags = Super_context.ocaml_flags sctx ~dir lib.buildable.flags in
let obj_dir = Library.obj_dir ~dir lib in
let vimpl = Virtual_rules.impl sctx ~lib ~scope in
let ctx = Super_context.context sctx in
Expand Down Expand Up @@ -371,7 +372,7 @@ let cctx (lib : Library.t) ~sctx ~source_modules ~dir ~expander ~scope
~opaque:Inherit_from_settings ~js_of_ocaml:(Some lib.buildable.js_of_ocaml)
~dynlink ?stdlib:lib.stdlib
~package:(Option.map lib.public ~f:Dune_file.Public_lib.package)
?vimpl ~modes
?vimpl ~modes ~compile_flags

let library_rules (lib : Library.t) ~cctx ~source_modules ~dir_contents
~compile_info =
Expand All @@ -383,6 +384,7 @@ let library_rules (lib : Library.t) ~cctx ~source_modules ~dir_contents
let obj_dir = Compilation_context.obj_dir cctx in
let vimpl = Compilation_context.vimpl cctx in
let flags = Compilation_context.flags cctx in
let compile_flags = Compilation_context.compile_flags cctx in
let sctx = Compilation_context.super_context cctx in
let dir = Compilation_context.dir cctx in
let scope = Compilation_context.scope cctx in
Expand Down Expand Up @@ -416,7 +418,7 @@ let library_rules (lib : Library.t) ~cctx ~source_modules ~dir_contents
; compile_info
};
( cctx
, Merlin.make () ~requires:requires_compile ~flags ~modules
, Merlin.make () ~requires:requires_compile ~flags ~compile_flags ~modules
~preprocess:(Preprocess.Per_module.single_preprocess preprocess)
~libname:(snd lib.name) ~obj_dir )

Expand Down
18 changes: 17 additions & 1 deletion src/dune/merlin.ml
Original file line number Diff line number Diff line change
Expand Up @@ -95,13 +95,15 @@ end
type t =
{ requires : Lib.Set.t
; flags : string list Build.t
; compile_flags : string list Build.t
; preprocess : Preprocess.Without_instrumentation.t Preprocess.t
; libname : Lib_name.Local.t option
; source_dirs : Path.Source.Set.t
; objs_dirs : Path.Set.t
}

let make ?(requires = Ok []) ~flags ?(preprocess = Preprocess.No_preprocessing)
let make ?(requires = Ok []) ~flags ~compile_flags
?(preprocess = Preprocess.No_preprocessing)
?libname ?(source_dirs = Path.Source.Set.empty) ~modules ~obj_dir () =
(* Merlin shouldn't cause the build to fail, so we just ignore errors *)
let requires =
Expand All @@ -121,8 +123,18 @@ let make ?(requires = Ok []) ~flags ?(preprocess = Preprocess.No_preprocessing)
flags
|> Ocaml_flags.common
in
let compile_flags =
match Modules.alias_module modules with
| None -> Ocaml_flags.common compile_flags
| Some m ->
Ocaml_flags.prepend_common
[ "-open"; Module_name.to_string (Module.name m) ]
compile_flags
|> Ocaml_flags.common
in
{ requires
; flags = Build.catch flags ~on_error:(fun _ -> [])
; compile_flags = Build.catch compile_flags ~on_error:(fun _ -> [])
; preprocess
; libname
; source_dirs
Expand Down Expand Up @@ -267,6 +279,10 @@ let merge_two ~allow_approx_merlin a b =
(let+ a = a.flags
and+ b = b.flags in
a @ b)
; compile_flags =
(let+ a = a.compile_flags
and+ b = b.compile_flags in
a @ b)
; preprocess = Pp.merge ~allow_approx_merlin a.preprocess b.preprocess
; libname =
( match a.libname with
Expand Down
1 change: 1 addition & 0 deletions src/dune/merlin.mli
Original file line number Diff line number Diff line change
Expand Up @@ -8,6 +8,7 @@ type t
val make :
?requires:Lib.t list Or_exn.t
-> flags:Ocaml_flags.t
-> compile_flags:Ocaml_flags.t
-> ?preprocess:Preprocess.Without_instrumentation.t Preprocess.t
-> ?libname:Lib_name.Local.t
-> ?source_dirs:Path.Source.Set.t
Expand Down
8 changes: 7 additions & 1 deletion src/dune/toplevel.ml
Original file line number Diff line number Diff line change
Expand Up @@ -174,10 +174,16 @@ module Stanza = struct
(Ocaml_flags.default ~dune_version ~profile)
[ "-w"; "-24" ]
in
let compile_flags =
let profile = Super_context.profile sctx in
Ocaml_flags.append_common
(Ocaml_flags.default ~dune_version ~profile)
[ "-w"; "-24" ]
in
let cctx =
Compilation_context.create () ~super_context:sctx ~scope ~obj_dir
~expander
~modules:(Source.modules source preprocessing)
~modules:(Source.modules source preprocessing) ~compile_flags
~opaque:(Explicit false) ~requires_compile ~requires_link ~flags
~js_of_ocaml:None ~dynlink:false ~package:None ~preprocessing
in
Expand Down
9 changes: 8 additions & 1 deletion src/dune/utop.ml
Original file line number Diff line number Diff line change
Expand Up @@ -109,9 +109,16 @@ let setup sctx ~dir =
(Ocaml_flags.default ~dune_version ~profile:(Super_context.profile sctx))
[ "-w"; "-24" ]
in
let compile_flags =
let project = Scope.project scope in
let dune_version = Dune_project.dune_version project in
Ocaml_flags.append_common
(Ocaml_flags.default ~dune_version ~profile:(Super_context.profile sctx))
[ "-w"; "-24" ]
in
let cctx =
Compilation_context.create () ~super_context:sctx ~expander ~scope ~obj_dir
~modules ~opaque:(Explicit false)
~modules ~opaque:(Explicit false) ~compile_flags
~requires_link:(lazy requires)
~requires_compile:requires ~flags ~js_of_ocaml:None ~dynlink:false
~package:None ~preprocessing
Expand Down
13 changes: 13 additions & 0 deletions test/blackbox-tests/dune.inc
Original file line number Diff line number Diff line change
Expand Up @@ -1602,6 +1602,17 @@
test-cases/incremental-rebuilds.t
(progn (run dune-cram run run.t) (diff? run.t run.t.corrected)))))

(rule
(alias inline_tests-compile-flags)
(deps
(package dune)
(source_tree test-cases/inline_tests/compile-flags.t)
(alias test-deps))
(action
(chdir
test-cases/inline_tests/compile-flags.t
(progn (run dune-cram run run.t) (diff? run.t run.t.corrected)))))

(rule
(alias inline_tests-dune-file)
(deps
Expand Down Expand Up @@ -3347,6 +3358,7 @@
(alias include-loop)
(alias include-qualified)
(alias incremental-rebuilds)
(alias inline_tests-compile-flags)
(alias inline_tests-dune-file)
(alias inline_tests-many-backends-choose)
(alias inline_tests-missing-backend)
Expand Down Expand Up @@ -3647,6 +3659,7 @@
(alias include-loop)
(alias include-qualified)
(alias incremental-rebuilds)
(alias inline_tests-compile-flags)
(alias inline_tests-dune-file)
(alias inline_tests-many-backends-choose)
(alias inline_tests-missing-backend)
Expand Down
20 changes: 20 additions & 0 deletions test/blackbox-tests/test-cases/inline_tests/compile-flags.t/run.t
Original file line number Diff line number Diff line change
@@ -0,0 +1,20 @@
$ cat >dune-project <<EOF
> (lang dune 2.7)
> EOF
$ cat >dune <<EOF
> (library
> (name backend_foo)
> (modules ())
> (inline_tests.backend
> (generate_runner (echo "let () = print_endline \"backend_foo\""))))
>
> (library
> (name compile_flags_test)
> (inline_tests
> (backend backend_foo)
> (compile_flags -flag-that-is-not-accepted-by-ocaml)))
> EOF

$ dune runtest
inline_test_runner_compile_flags_test alias runtest
backend_foo

This file was deleted.

This file was deleted.

7 changes: 0 additions & 7 deletions test/blackbox-tests/test-cases/inline_tests/dune-file.t/run.t
Original file line number Diff line number Diff line change
Expand Up @@ -30,10 +30,3 @@ package:
Entering directory 'dune-file-user'
inline_test_runner_foo_tests alias runtest
414243

We run the inline tests with a program that passes in specifc compile flags:

$ export OCAMLPATH=$PWD/_install/lib; dune runtest --root dune-file-compile-flags
Entering directory 'dune-file-compile-flags'
inline_test_runner_compile_flags_test alias runtest
414243

0 comments on commit 23d8c79

Please sign in to comment.