Skip to content

Commit

Permalink
Merge branch 'main' into haiku
Browse files Browse the repository at this point in the history
  • Loading branch information
Sylvain78 authored Sep 25, 2024
2 parents 1a775d5 + 17071ec commit 036a2b9
Show file tree
Hide file tree
Showing 14 changed files with 121 additions and 39 deletions.
3 changes: 3 additions & 0 deletions doc/changes/10923.md
Original file line number Diff line number Diff line change
@@ -0,0 +1,3 @@
- Fix the file referred to in the error/warning message displayed due to the
dune configuration version not supporting a particular configuration
stanza in use. (#10923, @H-ANSEN)
6 changes: 4 additions & 2 deletions src/dune_config_file/dune_config_file.ml
Original file line number Diff line number Diff line change
Expand Up @@ -367,8 +367,10 @@ module Dune_config = struct

let decode_generic ~min_dune_version =
let check min_ver =
let ver = Dune_lang.Syntax.Version.max min_ver min_dune_version in
Dune_lang.Syntax.since Stanza.syntax ver
let module S = Dune_lang.Syntax in
let ver = S.Version.max min_ver min_dune_version in
let* loc, what = S.desc () in
S.since_fmt ~fmt:(S.Error_msg.since_config ~what) Stanza.syntax ver loc
in
let field_o n v d = field_o n (check v >>> d) in
let+ display = field_o "display" (1, 0) (enum Display.all)
Expand Down
32 changes: 20 additions & 12 deletions src/dune_sexp/syntax.ml
Original file line number Diff line number Diff line change
Expand Up @@ -250,18 +250,22 @@ module Key = struct
end

module Error_msg = struct
let since t ver ~what =
let lang_or_using = if t.name = "dune" then "lang" else "using" in
let fmt_error_msg t ver ~what ~file =
let lang_or_using name = if name = "dune" then "lang" else "using" in
Printf.sprintf
"%s is only available since version %s of %s. Please update your dune-project file \
to have (%s %s %s)."
"%s is only available since version %s of %s. Please update your %s file to have \
(%s %s %s)."
what
(Version.to_string ver)
t.desc
lang_or_using
file
(lang_or_using t.name)
t.name
(Version.to_string ver)
;;

let since t ver ~what = fmt_error_msg t ver ~what ~file:"dune-project"
let since_config t ver ~what = fmt_error_msg t ver ~what ~file:"dune config"
end

module Error = struct
Expand Down Expand Up @@ -520,16 +524,20 @@ let renamed_in t ver ~to_ =
Error.renamed_in loc t ver ~what ~to_
;;

let since ?what ?(fatal = true) t ver =
let since_fmt ?(fatal = true) ~fmt t ver loc =
let open Version.Infix in
let* current_ver = get_exn t in
if current_ver >= ver
then return ()
else
let* loc, what_ctx = desc () in
let what = Option.value what ~default:what_ctx in
else (
if fatal
then Error.since loc t ver ~what
else User_warning.emit ~loc [ Pp.text (Error_msg.since t ver ~what) ];
return ()
then User_error.raise ~loc [ Pp.text (fmt t ver) ]
else User_warning.emit ~loc [ Pp.text (fmt t ver) ];
return ())
;;

let since ?what ?(fatal = true) t ver =
let* loc, what_ctx = desc () in
let what = Option.value what ~default:what_ctx in
since_fmt ~fatal ~fmt:(Error_msg.since ~what) t ver loc
;;
20 changes: 20 additions & 0 deletions src/dune_sexp/syntax.mli
Original file line number Diff line number Diff line change
Expand Up @@ -29,7 +29,14 @@ end
type t

module Error_msg : sig
(** [since t ver what] formats an error string indicating that the syntax
[t] described by [what] is only available since [ver] of the dune-project
file. *)
val since : t -> Version.t -> what:string -> string

(** Like [since] but formats an error message relating to the dune config file
rather than the dune-project file. *)
val since_config : t -> Version.t -> what:string -> string
end

module Error : sig
Expand Down Expand Up @@ -71,6 +78,9 @@ val create
(** Return the name of the syntax. *)
val name : t -> string

(** Indicate the location and kind of value being parsed *)
val desc : unit -> (Loc.t * string, 'a) Decoder.parser

(** Check that the given version is supported and raise otherwise. *)
val check_supported : dune_lang_ver:Version.t -> t -> Loc.t * Version.t -> unit

Expand Down Expand Up @@ -98,6 +108,16 @@ val renamed_in : t -> Version.t -> to_:string -> (unit, _) Decoder.parser
[fatal] defaults to true. [what] allows customizing the error message. *)
val since : ?what:string -> ?fatal:bool -> t -> Version.t -> (unit, _) Decoder.parser

(** Like [since] but accepts a function [fmt] allowing custom formatting of the
entire error/warning message. See [Error_msg] for format functions. *)
val since_fmt
: ?fatal:bool
-> fmt:(t -> Version.t -> string)
-> t
-> Version.t
-> Loc.t
-> (unit, 'a) Decoder.parser

(** {2 Low-level functions} *)

module Key : sig
Expand Down
2 changes: 1 addition & 1 deletion test/blackbox-tests/test-cases/config-project-defaults.t
Original file line number Diff line number Diff line change
Expand Up @@ -39,7 +39,7 @@ Change the version of the config file to one which does not support the
4 | (maintainers MaintainerTest)
5 | (license MIT))
Error: 'project_defaults' is only available since version 3.17 of the dune
language. Please update your dune-project file to have (lang dune 3.17).
language. Please update your dune config file to have (lang dune 3.17).
[1]

$ sed -i -e '1s|.*|(lang dune 3.17)|' dune-config
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -19,7 +19,7 @@ Setting such options is not supported with older Dune:
2 | (display short)
^^^^^^^^^^^^^^^
Error: 'display' is only available since version 3.0 of the dune language.
Please update your dune-project file to have (lang dune 3.0).
Please update your dune config file to have (lang dune 3.0).
[1]

But is supported with Dune >= 3.0.0:
Expand Down
49 changes: 49 additions & 0 deletions test/blackbox-tests/test-cases/config/config-version.t
Original file line number Diff line number Diff line change
@@ -0,0 +1,49 @@
Tests verifying that the config file presents accurate error or warning
messages when a stanza is used with a version of dune which does not support
such a stanza.

Create a config file to use in the following tests. We will initialize the
config with a version and a stanza incompatable with that version.

$ export DUNE_CACHE_ROOT=$PWD/dune-cache
$ touch dune-config
$ cat >dune-config <<EOF
> (lang dune 1.0)
> (cache enabled)
> EOF

Attempt to initialize a new project while an invaild stanza due to versioning
exists in the config.

$ dune init proj test --config-file=dune-config
File "$TESTCASE_ROOT/dune-config", line 2, characters 0-15:
2 | (cache enabled)
^^^^^^^^^^^^^^^
Error: 'cache' is only available since version 2.0 of the dune language.
Please update your dune config file to have (lang dune 2.0).
[1]

Update the dune configuration with a version that would support the
'(cache enabled)' stanza and attempt a successful project initialization.

$ cat >dune-config <<EOF
> (lang dune 2.0)
> (cache enabled)
> EOF

$ dune init proj test_vaild --config-file=dune-config
Entering directory 'test_vaild'
Success: initialized project component named test_vaild
Leaving directory 'test_vaild'

Append an invaild stanza to the config file and attempt project initialzation.

$ echo "(cache-check-probability 0.5)" >> dune-config
$ dune init proj test --config-file=dune-config
File "$TESTCASE_ROOT/dune-config", line 3, characters 0-29:
3 | (cache-check-probability 0.5)
^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Error: 'cache-check-probability' is only available since version 2.7 of the
dune language. Please update your dune config file to have (lang dune 2.7).
[1]

6 changes: 3 additions & 3 deletions test/blackbox-tests/test-cases/pkg/depexts/error-message.t
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,7 @@ Make a library that would fail when building it:
$ mkdir foo
$ cat > foo/dune-project <<EOF
> EOF
$ tar -czf foo.tar.gz foo
$ tar cf foo.tar foo
$ rm -rf foo

Make a project that uses the foo library:
Expand All @@ -33,8 +33,8 @@ Make dune.lock files
> (depexts unzip gnupg)
> (source
> (fetch
> (url file://$PWD/foo.tar.gz)
> (checksum md5=$(md5sum foo.tar.gz | cut -f1 -d' '))))
> (url file://$PWD/foo.tar)
> (checksum md5=$(md5sum foo.tar | cut -f1 -d' '))))
> EOF
Build the project, when it fails building 'foo' package, it shows
Expand Down
6 changes: 3 additions & 3 deletions test/blackbox-tests/test-cases/pkg/different-dune-in-path.t
Original file line number Diff line number Diff line change
Expand Up @@ -12,7 +12,7 @@ Clarify the behavior when the `dune` in PATH is not the one used to start the bu
> (allow_empty))
> EOF
> cd ..
> tar -czf $1.tar.gz tmp
> tar cf $1.tar tmp
> rm -rf tmp
> }

Expand Down Expand Up @@ -43,7 +43,7 @@ Make lockfiles for the packages.
>
> (source
> (fetch
> (url $PWD/foo.tar.gz)))
> (url $PWD/foo.tar)))
>
> (dev)
> EOF
Expand All @@ -57,7 +57,7 @@ Make lockfiles for the packages.
>
> (source
> (fetch
> (url $PWD/bar.tar.gz)))
> (url $PWD/bar.tar)))
>
> (dev)
> EOF
Expand Down
6 changes: 3 additions & 3 deletions test/blackbox-tests/test-cases/pkg/e2e.t
Original file line number Diff line number Diff line change
Expand Up @@ -19,12 +19,12 @@ Make a library:
> (public_name foo))
> EOF
$ cd ..
$ tar -czf foo.tar.gz foo
$ tar cf foo.tar foo
$ rm -rf foo

Configure our fake curl to serve the tarball

$ echo foo.tar.gz >> fake-curls
$ echo foo.tar >> fake-curls
$ PORT=1

Make a package for the library:
Expand All @@ -46,7 +46,7 @@ Make a package for the library:
> url {
> src: "http://0.0.0.0:$PORT"
> checksum: [
> "md5=$(md5sum foo.tar.gz | cut -f1 -d' ')"
> "md5=$(md5sum foo.tar | cut -f1 -d' ')"
> ]
> }
> EOF
Expand Down
14 changes: 7 additions & 7 deletions test/blackbox-tests/test-cases/pkg/ocamlformat/helpers.sh
Original file line number Diff line number Diff line change
Expand Up @@ -28,7 +28,7 @@ EOF
(executable
(public_name ocamlformat))
EOF
tar -czf ocamlformat-$version.tar.gz ocamlformat
tar cf ocamlformat-$version.tar ocamlformat
rm -rf ocamlformat
}

Expand All @@ -55,7 +55,7 @@ build: [
url {
src: "http://127.0.0.1:$port"
checksum: [
"md5=$(md5sum ocamlformat-$version.tar.gz | cut -f1 -d' ')"
"md5=$(md5sum ocamlformat-$version.tar | cut -f1 -d' ')"
]
}
EOF
Expand All @@ -71,9 +71,9 @@ build: [
]
]
url {
src: "file://$PWD/ocamlformat-$version.tar.gz"
src: "file://$PWD/ocamlformat-$version.tar"
checksum: [
"md5=$(md5sum ocamlformat-$version.tar.gz | cut -f1 -d' ')"
"md5=$(md5sum ocamlformat-$version.tar | cut -f1 -d' ')"
]
}
EOF
Expand Down Expand Up @@ -128,7 +128,7 @@ EOF
(library
(public_name printer))
EOF
tar -czf printer.$version.tar.gz printer
tar cf printer.$version.tar printer
rm -r printer
}

Expand All @@ -145,9 +145,9 @@ build: [
]
]
url {
src: "file://$PWD/printer.$version.tar.gz"
src: "file://$PWD/printer.$version.tar"
checksum: [
"md5=$(md5sum printer.$version.tar.gz | cut -f1 -d' ')"
"md5=$(md5sum printer.$version.tar | cut -f1 -d' ')"
]
}
EOF
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -25,7 +25,7 @@ Make a fake OCamlFormat which depends on printer lib:
> (libraries printer))
> EOF
$ cd ..
$ tar -czf ocamlformat.tar.gz ocamlformat
$ tar cf ocamlformat.tar ocamlformat
$ rm -rf ocamlformat

Make a printer lib(version 1) that prints "formatted":
Expand All @@ -51,9 +51,9 @@ Make a package for the fake OCamlFormat library which depends on printer.1.0:
> ]
> ]
> url {
> src: "file://$PWD/ocamlformat.tar.gz"
> src: "file://$PWD/ocamlformat.tar"
> checksum: [
> "md5=$(md5sum ocamlformat.tar.gz | cut -f1 -d' ')"
> "md5=$(md5sum ocamlformat.tar | cut -f1 -d' ')"
> ]
> }
> EOF
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -7,13 +7,13 @@ Exercises end to end, locking and building ocamlformat dev tool.
$ make_fake_ocamlformat "0.26.3"

Add the tar file for the fake curl to copy it:
$ echo ocamlformat-0.26.2.tar.gz > fake-curls
$ echo ocamlformat-0.26.2.tar > fake-curls
$ PORT=1

$ make_ocamlformat_opam_pkg "0.26.2" $PORT

Add the tar file for the fake curl to copy it:
$ echo ocamlformat-0.26.3.tar.gz >> fake-curls
$ echo ocamlformat-0.26.3.tar >> fake-curls
$ PORT=2

We consider this version of OCamlFormat as the latest version:
Expand Down
4 changes: 2 additions & 2 deletions test/blackbox-tests/test-cases/pkg/source-caching.t
Original file line number Diff line number Diff line change
Expand Up @@ -4,10 +4,10 @@ This test demonstrates that fetching package sources should be cached

$ make_lockdir

$ tarball=source.tar.gz
$ tarball=source.tar
$ sources="sources/"
$ mkdir $sources; touch $sources/dummy
$ tar -czf $tarball $sources
$ tar cf $tarball $sources
$ checksum=$(md5sum $tarball | awk '{ print $1 }')
$ echo $tarball > fake-curls
$ port=1
Expand Down

0 comments on commit 036a2b9

Please sign in to comment.