Skip to content
Open
5 changes: 5 additions & 0 deletions doc/changes/changed/12766.md
Original file line number Diff line number Diff line change
@@ -0,0 +1,5 @@
- Starting with version 3.21 of the Dune language, Dune no longer changes the
Copy link
Member

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Since dune itself is already using 3.21, you should use %{dune-warnings} in our root dune file.

Copy link
Collaborator Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Good catch. Fixed in 5c4861b

default set of compiler warnings. For users that would like to keep the old
behaviour, the variable `%{dune-warnings}` can be used in an `(env)` stanza in
a top-level Dune file: `(env (dev (flags :standard %{dune-warnings})))`.
(#12766, @nojb)
9 changes: 9 additions & 0 deletions doc/concepts/variables.rst
Original file line number Diff line number Diff line change
Expand Up @@ -69,6 +69,15 @@ Dune supports the following variables:
- ``ignoring_promoted_rules`` is ``true`` if
``--ignore-promoted-rules`` was passed on the command line and
``false`` otherwise.
- ``dune-warnings`` is the list of OCaml warnings that Dune used by default up
until version 3.20 of the Dune language when building in the ``dev`` profile.
This was a larger set of warnings than the default one used by the OCaml
compiler, and in version 3.21 of the Dune language the set of warnings used by
the ``dev`` profile was reverted to the default one used by the compiler. This
variable is made available for those users who would like to keep using Dune's
stricter warning set. The old behaviour of Dune can be recovered by using the
following stanza in a top-level ``dune`` file: ``(env (dev (flags :standard
%{dune-warnings})))``.
- ``<ext>:<path>`` where ``<ext>`` is one of ``cmo``, ``cmi``, ``cma``,
``cmx``, or ``cmxa``. See :ref:`variables-for-artifacts`.
- ``env:<var>=<default`` expands to the value of the environment
Expand Down
4 changes: 2 additions & 2 deletions doc/overview.rst
Original file line number Diff line number Diff line change
Expand Up @@ -133,8 +133,8 @@ Terminology
files. The following profiles are standard:

- ``release`` which is the profile used for opam releases
- ``dev`` which is the default profile when none is set explicitly, it has
stricter warnings than the ``release`` one
- ``dev`` which is the default profile when none is set explicitly, and
which has warnings-as-errors turned on.

dialect
An alternative frontend to OCaml (such as ReasonML). It is described
Expand Down
2 changes: 1 addition & 1 deletion dune-file
Original file line number Diff line number Diff line change
Expand Up @@ -46,7 +46,7 @@

(env
(_
(flags :standard -alert -unstable)
(flags :standard %{dune-warnings} -alert -unstable)
(env-vars
; Workaround for #6607
(CLICOLOR_FORCE 0))))
6 changes: 5 additions & 1 deletion src/dune_lang/pform.ml
Original file line number Diff line number Diff line change
Expand Up @@ -137,6 +137,7 @@ module Var = struct
| Toolchain
| Pkg of Pkg.t
| Oxcaml_supported
| Dune_warnings

let compare : t -> t -> Ordering.t = Poly.compare

Expand Down Expand Up @@ -191,7 +192,8 @@ module Var = struct
| Toolchain -> variant "Toolchain" []
| Os os -> Os.to_dyn os
| Pkg pkg -> Pkg.to_dyn pkg
| Oxcaml_supported -> variant "Oxcaml_supported" [])
| Oxcaml_supported -> variant "Oxcaml_supported" []
| Dune_warnings -> variant "Dune_warnings" [])
;;

let of_opam_global_variable_name name =
Expand Down Expand Up @@ -538,6 +540,7 @@ let encode_to_latest_dune_lang_version t =
| Os os -> Some (Var.Os.to_string os)
| Pkg pkg -> Some (Var.Pkg.encode_to_latest_dune_lang_version pkg)
| Oxcaml_supported -> Some "oxcaml_supported"
| Dune_warnings -> Some "dune-warnings"
with
| None -> Pform_was_deleted
| Some name -> Success { name; payload = None })
Expand Down Expand Up @@ -753,6 +756,7 @@ module Env = struct
; "toolchains", since ~version:(3, 0) Var.Toolchain
; ( "oxcaml_supported"
, since ~what:Oxcaml.syntax ~version:(0, 1) Var.Oxcaml_supported )
; "dune-warnings", since ~version:(3, 21) Var.Dune_warnings
]
in
let os =
Expand Down
1 change: 1 addition & 0 deletions src/dune_lang/pform.mli
Original file line number Diff line number Diff line change
Expand Up @@ -91,6 +91,7 @@ module Var : sig
| Toolchain
| Pkg of Pkg.t
| Oxcaml_supported
| Dune_warnings

val compare : t -> t -> Ordering.t
val to_dyn : t -> Dyn.t
Expand Down
8 changes: 8 additions & 0 deletions src/dune_rules/expander.ml
Original file line number Diff line number Diff line change
Expand Up @@ -572,6 +572,14 @@ let expand_pform_var (context : Context.t) ~dir ~source (var : Pform.Var.t) =
let ocaml_version = Ocaml_config.version_string ocaml.ocaml_config in
[ Value.of_bool (Ocaml.Version.supports_oxcaml ocaml_version) ])
|> static
| Dune_warnings ->
Need_full_expander
(fun { scope; _ } ->
Deps.Without
(let open Memo.O in
let+ scope = scope in
let dune_version = Dune_project.dune_version (Scope.project scope) in
Value.L.strings (Ocaml_flags.dune_warnings ~dune_version ~profile:Dev)))
;;

let ocaml_config_macro source macro_invocation context =
Expand Down
15 changes: 12 additions & 3 deletions src/dune_rules/ocaml_flags.ml
Original file line number Diff line number Diff line change
Expand Up @@ -51,19 +51,28 @@ let vendored_warnings = [ "-w"; "-a" ]
let vendored_alerts = [ "-alert"; "-all" ]
let default_warnings = "-40"

let default_flags ~dune_version ~profile =
let dune_warnings ~dune_version ~profile =
if Profile.is_dev profile
then
[ "-w"
; dev_mode_warnings ~dune_version ^ default_warnings
; "-strict-sequence"
; "-strict-formats"
; "-short-paths"
; "-keep-locs"
]
else [ "-w"; default_warnings ]
;;

let default_flags ~dune_version ~profile =
(if dune_version < (3, 21) then dune_warnings ~dune_version ~profile else [])
@
if Profile.is_dev profile
then
"-short-paths"
:: "-keep-locs"
:: (if dune_version >= (3, 21) then [ "-warn-error"; "+a" ] else [])
else []
;;

type t = string list Action_builder.t Dune_lang.Ocaml_flags.t

let empty =
Expand Down
6 changes: 6 additions & 0 deletions src/dune_rules/ocaml_flags.mli
Original file line number Diff line number Diff line change
Expand Up @@ -14,6 +14,12 @@ val make
-> t

val allow_only_melange : t -> t

val dune_warnings
: dune_version:Dune_lang.Syntax.Version.t
-> profile:Profile.t
-> string list

val default : dune_version:Dune_lang.Syntax.Version.t -> profile:Profile.t -> t
val empty : t
val of_list : string list -> t
Expand Down
89 changes: 89 additions & 0 deletions test/blackbox-tests/test-cases/dune-warnings.t
Original file line number Diff line number Diff line change
@@ -0,0 +1,89 @@
Black-box testing: we check that warning 32 (unused-value-declaration) is
enabled by default in the dev profile in Dune version 3.20 but not in 3.21.

$ cat >dune-project <<EOF
> (lang dune 3.20)
> EOF

$ cat >main.ml <<EOF
> let unused = 42
> EOF

$ cat >main.mli <<EOF
> EOF

$ cat >dune <<EOF
> (executable (name main))
> EOF

$ dune build
File "main.ml", line 1, characters 4-10:
1 | let unused = 42
^^^^^^
Error (warning 32 [unused-value-declaration]): unused value unused.
[1]

Now in 3.21...

$ cat >dune-project <<EOF
> (lang dune 3.21)
> EOF

$ dune build

Version check for %{dune-warnings}.

$ cat >dune-project <<EOF
> (lang dune 3.20)
> EOF

$ cat >dune <<EOF
> (executable (name main) (flags :standard %{dune-warnings}))
> EOF

$ dune build
File "dune", line 1, characters 41-57:
1 | (executable (name main) (flags :standard %{dune-warnings}))
^^^^^^^^^^^^^^^^
Error: %{dune-warnings} is only available since version 3.21 of the dune
language. Please update your dune-project file to have (lang dune 3.21).
[1]

$ cat >dune-project <<EOF
> (lang dune 3.21)
> EOF

$ dune build
File "main.ml", line 1, characters 4-10:
1 | let unused = 42
^^^^^^
Error (warning 32 [unused-value-declaration]): unused value unused.
[1]

What _is_ %{dune-warnings} ?

$ cat >dune <<EOF
> (rule (alias show) (action (echo "%{dune-warnings}\n")))
> EOF

$ dune build @show
-w @1..3@5..28@31..39@43@46..47@49..57@61..62@67@69-40 -strict-sequence -strict-formats

Warnings are still fatal in dev mode.

$ cat >main.ml <<EOF
> let f = function 0 -> 1
> EOF

$ cat >dune <<EOF
> (executable (name main))
> EOF

$ dune build
File "main.ml", line 1, characters 8-23:
1 | let f = function 0 -> 1
^^^^^^^^^^^^^^^
Error (warning 8 [partial-match]): this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
1
[1]
Loading