Skip to content

Commit

Permalink
Load the workspace config in two stages
Browse files Browse the repository at this point in the history
So that we don't fail immediately if the context definition is wrong
for instnace.

Signed-off-by: Jeremie Dimino <[email protected]>
  • Loading branch information
jeremiedimino committed Apr 6, 2021
1 parent 2f477a4 commit c04fef6
Show file tree
Hide file tree
Showing 6 changed files with 228 additions and 123 deletions.
6 changes: 3 additions & 3 deletions bin/common.ml
Original file line number Diff line number Diff line change
Expand Up @@ -156,14 +156,14 @@ let set_common ?log_file c =
can interpret errors in the workspace file. *)
print_entering_message c;
Dune_rules.Workspace.Clflags.set c.workspace_config;
let workspace =
let config =
(* Here we make the assumption that this computation doesn't yield. *)
Fiber.run
(Memo.Build.run (Dune_rules.Workspace.workspace ()))
(Memo.Build.run (Dune_rules.Workspace.workspace_config ()))
~iter:(fun () -> assert false)
in
let config =
Dune_config.adapt_display workspace.config
Dune_config.adapt_display config
~output_is_a_tty:(Lazy.force Ansi_color.stderr_supports_color)
in
Dune_config.init config;
Expand Down
4 changes: 4 additions & 0 deletions src/dune_lang/decoder.ml
Original file line number Diff line number Diff line change
Expand Up @@ -264,6 +264,10 @@ let capture ctx state =
let f t = result ctx (t ctx state) in
(f, [])

let lazy_ t =
let+ f = capture in
lazy (f t)

let end_of_list (Values (loc, cstr, _)) =
match cstr with
| None ->
Expand Down
3 changes: 3 additions & 0 deletions src/dune_lang/decoder.mli
Original file line number Diff line number Diff line change
Expand Up @@ -124,6 +124,9 @@ val repeat1 : 'a t -> 'a list t
(** Capture the rest of the input for later parsing *)
val capture : ('a t -> 'a) t

(** Delay the parsing of the rest of the input *)
val lazy_ : 'a t -> 'a Lazy.t t

(** [enter t] expect the next element of the input to be a list and parse its
contents with [t]. *)
val enter : 'a t -> 'a t
Expand Down
Loading

0 comments on commit c04fef6

Please sign in to comment.