Skip to content

Commit

Permalink
Add length function to exapnsions
Browse files Browse the repository at this point in the history
This is useful for an error message that includes the number of items we've
expanded to.

Signed-off-by: Rudi Grinberg <rudi.grinberg@gmail.com>
  • Loading branch information
rgrinberg committed Jun 4, 2018
1 parent 0bbbdde commit 846d6d3
Show file tree
Hide file tree
Showing 3 changed files with 12 additions and 4 deletions.
4 changes: 4 additions & 0 deletions src/action.ml
Original file line number Diff line number Diff line change
Expand Up @@ -275,6 +275,10 @@ module Var_expansion = struct
| Paths of Path.t list
| Strings of string list

let length = function
| Paths x -> List.length x
| Strings x -> List.length x

let is_multivalued = function
| Paths [_] -> false
| Strings [_] -> false
Expand Down
10 changes: 6 additions & 4 deletions src/string_with_vars.ml
Original file line number Diff line number Diff line change
Expand Up @@ -106,6 +106,7 @@ let string_of_var syntax v =

module type EXPANSION = sig
type t
val length : t -> int
val is_multivalued : t -> bool
type context
val to_string : context -> t -> string
Expand All @@ -132,12 +133,12 @@ end

module Expand_to(V: EXPANSION) = struct

let check_valid_multivalue syntax ~var t ctx =
if not t.quoted && V.is_multivalued ctx then
Loc.fail t.loc "Variable %s expands to multiple values, \
let check_valid_multivalue syntax ~var t x =
if not t.quoted && V.is_multivalued x then
Loc.fail t.loc "Variable %s expands to %d values, \
however a single value is expected here. \
Please quote this atom. "
(string_of_var syntax var)
(string_of_var syntax var) (V.length x)

let expand ctx t ~f =
match t.items with
Expand Down Expand Up @@ -189,6 +190,7 @@ end

module String_expansion = struct
type t = string
let length _ = 1
let is_multivalued _ = false
type context = unit
let to_string () (s: string) = s
Expand Down
2 changes: 2 additions & 0 deletions src/string_with_vars.mli
Original file line number Diff line number Diff line change
Expand Up @@ -49,6 +49,8 @@ module type EXPANSION = sig
type t
(** The value to which variables are expanded. *)

val length : t -> int

val is_multivalued : t -> bool
(** Report whether the value is a multivalued one (such as for
example ${@}) which much be in quoted strings to be concatenated
Expand Down

0 comments on commit 846d6d3

Please sign in to comment.