Skip to content

Commit

Permalink
Bump latest version to 1.1
Browse files Browse the repository at this point in the history
And make this version a pre-req for the env field in workspaces

Signed-off-by: Rudi Grinberg <[email protected]>
  • Loading branch information
rgrinberg committed Jul 20, 2018
1 parent ecf6167 commit 40ea41a
Show file tree
Hide file tree
Showing 5 changed files with 13 additions and 8 deletions.
2 changes: 1 addition & 1 deletion src/stanza.ml
Original file line number Diff line number Diff line change
Expand Up @@ -9,7 +9,7 @@ end
let syntax =
Syntax.create ~name:"dune" ~desc:"the dune language"
[ (0, 0) (* Jbuild syntax *)
; (1, 0)
; (1, 1)
]

module File_kind = struct
Expand Down
9 changes: 7 additions & 2 deletions src/workspace.ml
Original file line number Diff line number Diff line change
Expand Up @@ -5,6 +5,11 @@ open Stanza.Of_sexp
for simplicity *)
let syntax = Stanza.syntax

let env_field =
field_o "env"
(Syntax.since syntax (1, 1) >>= fun () ->
Dune_env.Stanza.t)

module Context = struct
module Target = struct
type t =
Expand Down Expand Up @@ -49,7 +54,7 @@ module Context = struct
}

let t ~profile =
field_o "env" Dune_env.Stanza.t >>= fun env ->
env_field >>= fun env ->
field "targets" (list Target.t) ~default:[Target.Native]
>>= fun targets ->
field "profile" string ~default:profile
Expand Down Expand Up @@ -155,7 +160,7 @@ include Versioned_file.Make(struct type t = unit end)
let () = Lang.register syntax ()

let t ?x ?profile:cmdline_profile () =
field_o "env" Dune_env.Stanza.t >>= fun env ->
env_field >>= fun env ->
field "profile" string ~default:Config.default_build_profile
>>= fun profile ->
let profile = Option.value cmdline_profile ~default:profile in
Expand Down
6 changes: 3 additions & 3 deletions test/blackbox-tests/test-cases/dune-project-edition/run.t
Original file line number Diff line number Diff line change
Expand Up @@ -4,15 +4,15 @@
$ mkdir src
$ echo '(alias (name runtest) (action (progn)))' > src/dune
$ dune build
Info: creating file dune-project with this contents: (lang dune 1.0)
Info: creating file dune-project with this contents: (lang dune 1.1)
$ cat dune-project
(lang dune 1.0)
(lang dune 1.1)

Test that using menhir automatically update the dune-project file

$ echo '(library (name x)) (menhir (modules x))' >> src/dune
$ dune build
Info: appending this line to dune-project: (using menhir 1.0)
$ cat dune-project
(lang dune 1.0)
(lang dune 1.1)
(using menhir 1.0)
Original file line number Diff line number Diff line change
@@ -1 +1 @@
(lang dune 1.0)
(lang dune 1.1)
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
(lang dune 1.0)
(lang dune 1.1)

(env
(default
Expand Down

0 comments on commit 40ea41a

Please sign in to comment.