Skip to content

Commit

Permalink
Simplify String_with_vars
Browse files Browse the repository at this point in the history
Make it expand only to Value.t since the string only version wasn't really used.
Variable expansions are now Value.t list. Which also gives the flexibility for a
value to expand to a collection of more than 1 value.

Signed-off-by: Rudi Grinberg <rudi.grinberg@gmail.com>
  • Loading branch information
rgrinberg committed Jun 5, 2018
1 parent 1b45114 commit 72277f9
Show file tree
Hide file tree
Showing 13 changed files with 242 additions and 400 deletions.
115 changes: 42 additions & 73 deletions src/action.ml
Original file line number Diff line number Diff line change
Expand Up @@ -270,13 +270,12 @@ module Unresolved = struct
| Search s -> Ok (f s))
end

let var_expansion_to_prog_and_args dir exp : Unresolved.Program.t * string list =
let module P = Unresolved.Program in
match (exp : Var_expansion.t) with
| Paths (x::xs) -> (This x, Var_expansion.to_strings dir (Paths xs))
| Strings (s::xs) -> ( P.of_string ~dir s
, Var_expansion.to_strings dir (Strings xs))
| Paths [] | Strings [] -> (Search "", [])
let var_expansion_to_prog_and_args p ~dir =
match p with
| [] -> (Unresolved.Program.Search "", [])
| Value.Path p :: xs -> (This p, Value.to_strings ~dir xs)
| String s :: xs ->
(Unresolved.Program.of_string ~dir s, Value.to_strings ~dir xs)

module SW = String_with_vars

Expand Down Expand Up @@ -315,43 +314,33 @@ module Unexpanded = struct
include Past

module E = struct
let expand ~generic ~special ~map ~dir ~allow_multivalue ~f = function
| Left x -> map x
| Right template ->
match
Var_expansion.Expand.expand dir template ~f ~allow_multivalue
with
| Expansion e -> special dir e
| String s -> generic dir s
[@@inlined always]

let string ~dir ~f x =
expand ~dir ~f x
~allow_multivalue:false
~generic:(fun _dir x -> x)
~special:Var_expansion.to_string
~map:(fun x -> x)

let strings ~dir ~f x =
expand ~dir ~f x
~allow_multivalue:true
~generic:(fun _dir x -> [x])
~special:Var_expansion.to_strings
~map:(fun x -> [x])

let path ~dir ~f x =
expand ~dir ~f x
~allow_multivalue:false
~generic:Var_expansion.path_of_string
~special:Var_expansion.to_path
~map:(fun x -> x)

let prog_and_args ~dir ~f x =
expand ~dir ~f x
~allow_multivalue:true
~generic:(fun _dir s -> (Program.of_string ~dir s, []))
~special:var_expansion_to_prog_and_args
~map:(fun x -> (x, []))
let expand ~dir ~mode ~f ~l ~r =
Either.either ~l
~r:(fun s -> r (String_with_vars.expand s ~dir ~f ~mode) ~dir)

let string =
expand ~mode:Single
~l:(fun x -> x)
~r:Value.to_string

let strings =
expand ~mode:Many
~l:(fun x -> [x])
~r:Value.to_strings

let path e =
let error_loc =
match e with
| Left _ -> None
| Right r -> Some (String_with_vars.loc r) in
expand ~mode:Single
~l:(fun x -> x)
~r:Value.(to_path ?error_loc) e

let prog_and_args =
expand ~mode:Many
~l:(fun x -> (x, []))
~r:var_expansion_to_prog_and_args
end

let rec expand t ~dir ~map_exe ~f : Unresolved.t =
Expand Down Expand Up @@ -414,37 +403,17 @@ module Unexpanded = struct
end

module E = struct
let expand ~generic ~special ~dir ~allow_multivalue ~f template =
match
Var_expansion.Expand.partial_expand dir template ~allow_multivalue ~f
with
| Expansion e -> Left (special dir e)
| String s -> Left (generic dir s)
let expand ~dir ~mode ~f ~map x =
match String_with_vars.partial_expand ~mode ~dir ~f x with
| Expanded e -> Left (map e ~dir)
| Unexpanded x -> Right x

let string ~dir ~f x =
expand ~dir ~f x
~allow_multivalue:false
~generic:(fun _dir x -> x)
~special:Var_expansion.to_string

let strings ~dir ~f x =
expand ~dir ~f x
~allow_multivalue:true
~generic:(fun _dir x -> [x])
~special:Var_expansion.to_strings

let path ~dir ~f x =
expand ~dir ~f x
~allow_multivalue:false
~generic:Var_expansion.path_of_string
~special:Var_expansion.to_path

let prog_and_args ~dir ~f x =
expand ~dir ~f x
~allow_multivalue:true
~generic:(fun dir s -> (Unresolved.Program.of_string ~dir s, []))
~special:var_expansion_to_prog_and_args
let string = expand ~mode:Single ~map:(Value.to_string)
let strings = expand ~mode:Many ~map:(Value.to_strings)
let path x =
let error_loc = String_with_vars.loc x in
expand ~mode:Single ~map:(Value.to_path ~error_loc) x
let prog_and_args = expand ~mode:Many ~map:(var_expansion_to_prog_and_args)
end

let rec partial_expand t ~dir ~map_exe ~f : Partial.t =
Expand Down
4 changes: 2 additions & 2 deletions src/action.mli
Original file line number Diff line number Diff line change
Expand Up @@ -82,15 +82,15 @@ module Unexpanded : sig
: t
-> dir:Path.t
-> map_exe:(Path.t -> Path.t)
-> f:(Loc.t -> String.t -> Var_expansion.t option)
-> f:(Loc.t -> String.t -> Value.t list option)
-> Unresolved.t
end

val partial_expand
: t
-> dir:Path.t
-> map_exe:(Path.t -> Path.t)
-> f:(Loc.t -> string -> Var_expansion.t option)
-> f:(Loc.t -> string -> Value.t list option)
-> Partial.t
end

Expand Down
4 changes: 2 additions & 2 deletions src/inline_tests.ml
Original file line number Diff line number Diff line change
Expand Up @@ -190,7 +190,7 @@ include Sub_system.Register_end_point(
in

let extra_vars =
String.Map.singleton "library-name" (Var_expansion.Strings [lib.name])
String.Map.singleton "library-name" ([Value.String lib.name])
in

let runner_libs =
Expand All @@ -212,7 +212,7 @@ include Sub_system.Register_end_point(
let target = Path.relative inline_test_dir main_module_filename in
let source_modules = Module.Name.Map.values source_modules in
let files ml_kind =
Var_expansion.Paths (
Value.paths (
List.filter_map source_modules ~f:(fun m ->
Module.file m ~dir ml_kind))
in
Expand Down
5 changes: 5 additions & 0 deletions src/stdune/either.ml
Original file line number Diff line number Diff line change
@@ -1,3 +1,8 @@
type ('a, 'b) t =
| Left of 'a
| Right of 'b

let either t ~l ~r =
match t with
| Left x -> l x
| Right x -> r x
2 changes: 2 additions & 0 deletions src/stdune/either.mli
Original file line number Diff line number Diff line change
Expand Up @@ -3,3 +3,5 @@
type ('a, 'b) t =
| Left of 'a
| Right of 'b

val either : ('a, 'b) t -> l:('a -> 'c) -> r:('b -> 'c) -> 'c
Loading

0 comments on commit 72277f9

Please sign in to comment.