Skip to content

Commit

Permalink
Add support for environment & build profiles (#419)
Browse files Browse the repository at this point in the history
  • Loading branch information
jeremiedimino authored May 4, 2018
1 parent adde723 commit 4d8ca48
Show file tree
Hide file tree
Showing 41 changed files with 745 additions and 222 deletions.
3 changes: 3 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
Expand Up @@ -25,6 +25,9 @@ next

- Scan the file system lazily (#732, fixes #718 and #228, @diml)

- Add support for setting the default ocaml flags and for build
profiles (#419, @diml)

1.0+beta20 (10/04/2018)
-----------------------

Expand Down
121 changes: 102 additions & 19 deletions bin/main.ml
Original file line number Diff line number Diff line change
Expand Up @@ -11,7 +11,7 @@ type common =
{ debug_dep_path : bool
; debug_findlib : bool
; debug_backtraces : bool
; dev_mode : bool
; profile : string option
; workspace_file : string option
; root : string
; target_prefix : string
Expand All @@ -33,7 +33,6 @@ let set_common c ~targets =
Clflags.debug_dep_path := c.debug_dep_path;
Clflags.debug_findlib := c.debug_findlib;
Clflags.debug_backtraces := c.debug_backtraces;
Clflags.dev_mode := c.dev_mode;
Clflags.capture_outputs := c.capture_outputs;
if c.root <> Filename.current_dir_name then
Sys.chdir c.root;
Expand Down Expand Up @@ -80,6 +79,7 @@ module Main = struct
?only_packages:common.only_packages
?external_lib_deps_mode
?x:common.x
?profile:common.profile
~ignore_promoted_rules:common.ignore_promoted_rules
~capture_outputs:common.capture_outputs
()
Expand Down Expand Up @@ -211,7 +211,6 @@ let common =
debug_dep_path
debug_findlib
debug_backtraces
dev_mode
no_buffer
workspace_file
diff_command
Expand All @@ -221,6 +220,7 @@ let common =
only_packages,
ignore_promoted_rules,
config_file,
profile,
orig)
x
display
Expand All @@ -236,7 +236,7 @@ let common =
in
let orig_args =
List.concat
[ if dev_mode then ["--dev"] else []
[ dump_opt "--profile" profile
; dump_opt "--workspace" workspace_file
; orig
]
Expand Down Expand Up @@ -264,7 +264,7 @@ let common =
{ debug_dep_path
; debug_findlib
; debug_backtraces
; dev_mode
; profile
; capture_outputs = not no_buffer
; workspace_file
; root
Expand Down Expand Up @@ -334,7 +334,27 @@ let common =
Arg.(value
& flag
& info ["dev"] ~docs
~doc:{|Use stricter compilation flags by default.|})
~doc:{|Same as $(b,--profile dev)|})
in
let profile =
Arg.(value
& opt (some string) None
& info ["profile"] ~docs
~doc:{|Select the build profile, for instance $(b,dev) or $(b,release).
The default is $(b,default).|})
in
let profile =
let merge dev profile =
match dev, profile with
| false, x -> `Ok x
| true , None -> `Ok (Some "dev")
| true , Some _ ->
`Error (true,
"Cannot use --dev and --profile simultaneously")
in
Term.(ret (const merge
$ dev
$ profile))
in
let display =
let verbose =
Expand Down Expand Up @@ -440,34 +460,39 @@ let common =
& opt (some string) None
& info ["p"; for_release] ~docs ~docv:"PACKAGES"
~doc:{|Shorthand for $(b,--root . --only-packages PACKAGE
--promote ignore --no-config).
--promote ignore --no-config --profile release).
You must use this option in your $(i,<package>.opam) files, in order
to build only what's necessary when your project contains multiple
packages as well as getting reproducible builds.|})
in
let merge root only_packages ignore_promoted_rules
(config_file_opt, config_file) release =
(config_file_opt, config_file) profile release =
let fail opt = incompatible ("-p/--" ^ for_release) opt in
match release, root, only_packages, ignore_promoted_rules, config_file_opt with
| Some _, Some _, _, _, _ -> fail "--root"
| Some _, _, Some _, _, _ -> fail "--only-packages"
| Some _, _, _, true , _ -> fail "--ignore-promoted-rules"
| Some _, _, _, _ , Some s -> fail s
| Some pkgs, None, None, false, None ->
match release, root, only_packages, ignore_promoted_rules,
profile, config_file_opt with
| Some _, Some _, _, _, _, _ -> fail "--root"
| Some _, _, Some _, _, _, _ -> fail "--only-packages"
| Some _, _, _, true , _, _ -> fail "--ignore-promoted-rules"
| Some _, _, _, _, Some _, _ -> fail "--profile"
| Some _, _, _, _, _, Some s -> fail s
| Some pkgs, None, None, false, None, None ->
`Ok (Some ".",
Some pkgs,
true,
No_config,
Some "release",
["-p"; pkgs]
)
| None, _, _, _, _ ->
| None, _, _, _, _, _ ->
`Ok (root,
only_packages,
ignore_promoted_rules,
config_file,
profile,
List.concat
[ dump_opt "--root" root
; dump_opt "--only-packages" only_packages
; dump_opt "--profile" profile
; if ignore_promoted_rules then
["--ignore-promoted-rules"]
else
Expand All @@ -484,6 +509,7 @@ let common =
$ only_packages
$ ignore_promoted_rules
$ config_file
$ profile
$ frop))
in
let x =
Expand All @@ -503,7 +529,6 @@ let common =
$ ddep_path
$ dfindlib
$ dbacktraces
$ dev
$ no_buffer
$ workspace_file
$ diff_command
Expand All @@ -520,7 +545,11 @@ let installed_libraries =
set_common common ~targets:[];
let env = Main.setup_env ~capture_outputs:common.capture_outputs in
Scheduler.go ~log:(Log.create common) ~common
(Context.create (Default [Native]) ~env >>= fun ctxs ->
(Context.create
(Default { targets = [Native]
; profile = "default" })
~env
>>= fun ctxs ->
let ctx = List.hd ctxs in
let findlib = ctx.findlib in
if na then begin
Expand Down Expand Up @@ -783,8 +812,8 @@ let external_lib_deps =
(Build_system.all_lib_deps_by_context setup.build_system ~request)
~f:(fun context_name lib_deps acc ->
let internals =
Jbuild.Stanzas.lib_names
(match String.Map.find setup.Main.stanzas context_name with
Super_context.internal_lib_names
(match String.Map.find setup.Main.scontexts context_name with
| None -> assert false
| Some x -> x)
in
Expand Down Expand Up @@ -1297,6 +1326,59 @@ let promote =
$ common)
, Term.info "promote" ~doc ~man )

let printenv =
let doc = "Print the environment of a directory" in
let man =
[ `S "DESCRIPTION"
; `P {|$(b,dune printenv DIR) prints the environment of a directory|}
; `Blocks help_secs
] in
let go common dir =
set_common common ~targets:[];
let log = Log.create common in
Scheduler.go ~log ~common (
Main.setup ~log common >>= fun setup ->
let dir = Path.of_string dir in
check_path setup.contexts dir;
let request =
let dump sctx ~dir =
let open Build.O in
Super_context.dump_env sctx ~dir
>>^ fun env ->
((Super_context.context sctx).name, env)
in
Build.all (
match Path.extract_build_context dir with
| Some (ctx, _) ->
let sctx =
String_map.find setup.scontexts ctx |> Option.value_exn
in
[dump sctx ~dir]
| None ->
String_map.values setup.scontexts
|> List.map ~f:(fun sctx ->
let dir =
Path.append (Super_context.context sctx).build_dir dir
in
dump sctx ~dir)
)
in
Build_system.do_build setup.build_system ~request
>>| fun l ->
let pp ppf = Format.fprintf ppf "@[<v1>(@,@[<v>%a@]@]@,)" (Format.pp_print_list Sexp.pp) in
match l with
| [(_, env)] ->
Format.printf "%a@." pp env
| l ->
List.iter l ~f:(fun (name, env) ->
Format.printf "@[<v2>Environment for context %s:@,%a@]@." name pp env)
)
in
( Term.(const go
$ common
$ Arg.(value & pos 0 dir "" & info [] ~docv:"PATH"))
, Term.info "printenv" ~doc ~man )

module Help = struct
let config =
("dune-config", 5, "", "Dune", "Dune manual"),
Expand Down Expand Up @@ -1412,6 +1494,7 @@ let all =
; rules
; utop
; promote
; printenv
; Help.help
]

Expand Down
9 changes: 9 additions & 0 deletions doc/dune.inc
Original file line number Diff line number Diff line change
Expand Up @@ -62,6 +62,15 @@
((section man)
(files (dune-installed-libraries.1))))

(rule
((targets (dune-printenv.1))
(action (with-stdout-to ${@}
(run dune printenv --help=groff)))))

(install
((section man)
(files (dune-printenv.1))))

(rule
((targets (dune-promote.1))
(action (with-stdout-to ${@}
Expand Down
35 changes: 27 additions & 8 deletions doc/jbuild.rst
Original file line number Diff line number Diff line change
Expand Up @@ -711,6 +711,27 @@ With this jbuild file, running jbuilder as follow will replace the
$ jbuilder build @runtest --auto-promote
env
---

The ``env`` stanza allows to modify the environment. The syntax is as
follow:

.. code:: scheme
(env
(<profile1> <settings1>)
(<profile2> <settings2>)
...
(<profilen> <settingsn>))
The first form ``(<profile> <settings>)`` that correspond to the
selected build profile will be used to modify the environment in this
directory. You can use ``_`` to match any build profile.

Currently ``<settings>`` can be any OCaml flags field, see `OCaml
flags`_ for more details.

Common items
============

Expand Down Expand Up @@ -1097,8 +1118,8 @@ The glob syntax is interpreted as follows:
OCaml flags
-----------

In ``library`` and ``executables`` stanzas, you can specify OCaml compilation
flags using the following fields:
In ``library``, ``executable``, ``executables`` and ``env`` stanzas,
you can specify OCaml compilation flags using the following fields:

- ``(flags <flags>)`` to specify flags passed to both ``ocamlc`` and
``ocamlopt``
Expand All @@ -1108,16 +1129,14 @@ flags using the following fields:
For all these fields, ``<flags>`` is specified in the `Ordered set language`_.
These fields all support ``(:include ...)`` forms.

The default value for ``(flags ...)`` includes some ``-w`` options to set
warnings. The exact set depends on whether ``--dev`` is passed to Jbuilder. As a
result it is recommended to write ``(flags ...)`` fields as follows:
The default value for ``(flags ...)`` is taken from the environment,
as a result it is recommended to write ``(flags ...)`` fields as
follows:

::
.. code:: scheme
(flags (:standard <my options>))
.. _jbuild-jsoo:

js_of_ocaml
-----------

Expand Down
21 changes: 21 additions & 0 deletions doc/quick-start.rst
Original file line number Diff line number Diff line change
Expand Up @@ -116,6 +116,27 @@ Outside of the library, module ``Foo`` will be accessible as
You can then use this library in any other directory by adding ``mylib``
to the ``(libraries ...)`` field.

Setting the OCaml compilation flags globally
============================================

Write this jbuild at the root of your project:

.. code:: scheme
(env
(dev
(flags (:standard -w +42)))
(release
(flags (:standard -O3))))
`dev` and `release` correspond to build profiles. The build profile
can be selected from the command line with `--profile foo` or from a
`dune-workspace` file by writing:

.. code:: scheme
(profile foo)
Using cppo
==========

Expand Down
16 changes: 16 additions & 0 deletions doc/terminology.rst
Original file line number Diff line number Diff line change
Expand Up @@ -54,3 +54,19 @@ Terminology
- ``install`` which depends on everything that should be installed
- ``doc`` which depends on the generated HTML
documentation. See :ref:`apidoc` for details

- **environment**: in Jbuilder, each directory has an environment
attached to it. The environment determines the default values of
various parameters, such as the compilation flags. Inside a scope,
each directory inherit the environment from its parent. At the root
of every scope, a default environment is used. At any point, the
environment can be altered using an `env`_ stanza.

- **build profile**: a global setting that influence various
defaults. It can be set from the command line using ``--profile
<profile>`` or from ``jbuild-workspace`` files. The following
profiles are standard:

- ``default`` which is the default profile when none is set explicitely
- ``release`` which is the profile used for opam releases
- ``dev`` which has stricter warnings
Loading

0 comments on commit 4d8ca48

Please sign in to comment.