Skip to content

Commit

Permalink
Refactor variable handling (#4184)
Browse files Browse the repository at this point in the history
- move variable name resolution is now done at parsing time
- pform now contains symbolic names rather than a version number and
  variable names as strings
- better error when specific variables such as "library-name" are used
  in the wrong context
- starting from 3.0, unknown variable names are always reported at
  parsing time

Signed-off-by: Jeremie Dimino <[email protected]>
  • Loading branch information
jeremiedimino authored Feb 8, 2021
1 parent 0b95281 commit ae22a86
Show file tree
Hide file tree
Showing 70 changed files with 1,841 additions and 1,426 deletions.
2 changes: 2 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
Expand Up @@ -23,6 +23,8 @@ Unreleased
- Do not pass include directories containing native objects when compiling
bytecode (#4200, @nojb)

- Detect unknown variables more eagerly (#4184, @jeremiedimino)

2.8.2 (21/01/2021)
------------------

Expand Down
4 changes: 3 additions & 1 deletion bin/arg.ml
Original file line number Diff line number Diff line change
Expand Up @@ -57,7 +57,9 @@ module Dep = struct

let dep_parser =
Dune_lang.Syntax.set Stanza.syntax (Active Stanza.latest_version)
Dep_conf.decode
(String_with_vars.set_decoding_env
(Pform.Env.initial Stanza.latest_version)
Dep_conf.decode)

let parser s =
match parse_alias s with
Expand Down
4 changes: 2 additions & 2 deletions bin/top.ml
Original file line number Diff line number Diff line change
Expand Up @@ -57,8 +57,8 @@ let term =
let files_to_load =
List.filter files ~f:(fun p ->
let ext = Path.extension p in
ext = Dune_rules.Mode.compiled_lib_ext Byte
|| ext = Dune_rules.Cm_kind.ext Cmo)
ext = Dune_engine.Mode.compiled_lib_ext Byte
|| ext = Dune_engine.Cm_kind.ext Cmo)
in
Dune_rules.Toplevel.print_toplevel_init_file ~include_paths ~files_to_load;
Fiber.return ())
Expand Down
6 changes: 4 additions & 2 deletions src/dune_engine/action.ml
Original file line number Diff line number Diff line change
Expand Up @@ -14,13 +14,15 @@ module Prog = struct

let create ?hint ~context ~program ~loc () = { hint; context; program; loc }

let raise { context; program; hint; loc } =
let user_message { context; program; hint; loc } =
let hint =
match program with
| "refmt" -> Some (Option.value ~default:"opam install reason" hint)
| _ -> hint
in
Utils.program_not_found ?hint ~loc ~context program
Utils.program_not_found_message ?hint ~loc ~context program

let raise t = raise (User_error.E (user_message t))

let to_dyn { context; program; hint; loc = _ } =
let open Dyn.Encoder in
Expand Down
2 changes: 2 additions & 0 deletions src/dune_engine/action.mli
Original file line number Diff line number Diff line change
Expand Up @@ -31,6 +31,8 @@ module Prog : sig
-> t

val raise : t -> _

val user_message : t -> User_message.t
end

type t = (Path.t, Not_found.t) result
Expand Down
2 changes: 1 addition & 1 deletion src/dune_engine/action_dune_lang.ml
Original file line number Diff line number Diff line change
Expand Up @@ -11,7 +11,7 @@ type target = String_with_vars.t
module String_with_vars = struct
include String_with_vars

let is_dev_null = String_with_vars.is_var ~name:"null"
let is_dev_null t = String_with_vars.is_pform t (Var Dev_null)
end

module type Uast =
Expand Down
1 change: 0 additions & 1 deletion src/dune_rules/cm_kind.ml → src/dune_engine/cm_kind.ml
Original file line number Diff line number Diff line change
@@ -1,4 +1,3 @@
open! Dune_engine
open Import

type t =
Expand Down
1 change: 0 additions & 1 deletion src/dune_rules/cm_kind.mli → src/dune_engine/cm_kind.mli
Original file line number Diff line number Diff line change
@@ -1,4 +1,3 @@
open! Dune_engine
open Import

type t =
Expand Down
4 changes: 3 additions & 1 deletion src/dune_engine/config.ml
Original file line number Diff line number Diff line change
Expand Up @@ -313,7 +313,9 @@ end)

let () = Lang.register syntax ()

let load_config_file p = load_exn p ~f:(fun _lang -> decode)
let load_config_file p =
load_exn p ~f:(fun lang ->
String_with_vars.set_decoding_env (Pform.Env.initial lang.version) decode)

let load_user_config_file () =
if Path.exists user_config_file then
Expand Down
8 changes: 4 additions & 4 deletions src/dune_engine/dialect.ml
Original file line number Diff line number Diff line change
Expand Up @@ -80,11 +80,11 @@ let ocaml =
in
let module S = String_with_vars in
Action_dune_lang.chdir
(S.make_var Loc.none "workspace_root")
(S.make_pform Loc.none (Var Workspace_root))
(Action_dune_lang.run
(S.make_text Loc.none "ocamlformat")
[ S.make_text Loc.none (flag_of_kind kind)
; S.make_var Loc.none "input-file"
; S.make_pform Loc.none (Var Input_file)
])
in
let file_kind kind extension =
Expand All @@ -110,13 +110,13 @@ let reason =
(S.make_text Loc.none "refmt")
[ S.make_text Loc.none "--print"
; S.make_text Loc.none "binary"
; S.make_var Loc.none "input-file"
; S.make_pform Loc.none (Var Input_file)
]
in
let format =
Action_dune_lang.run
(S.make_text Loc.none "refmt")
[ S.make_var Loc.none "input-file" ]
[ S.make_pform Loc.none (Var Input_file) ]
in
{ File_kind.kind
; extension
Expand Down
3 changes: 3 additions & 0 deletions src/dune_engine/dune_engine.ml
Original file line number Diff line number Diff line change
Expand Up @@ -52,3 +52,6 @@ module Hooks = Hooks
module Promotion = Promotion
module Cached_digest = Cached_digest
module Report_error = Report_error
module Pform = Pform
module Cm_kind = Cm_kind
module Mode = Mode
Loading

0 comments on commit ae22a86

Please sign in to comment.