Skip to content

Commit

Permalink
Rename Kind to Var in Pform
Browse files Browse the repository at this point in the history
Signed-off-by: Rudi Grinberg <rudi.grinberg@gmail.com>
  • Loading branch information
rgrinberg committed Jul 8, 2018
1 parent d506bae commit 7a400a5
Show file tree
Hide file tree
Showing 3 changed files with 13 additions and 13 deletions.
12 changes: 6 additions & 6 deletions src/pform.ml
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
open Import

module Kind = struct
module Var = struct
type t =
| Values of Value.t list
| Project_root
Expand Down Expand Up @@ -41,16 +41,16 @@ type 'a t =
module Map = struct
type nonrec 'a t = 'a t String.Map.t

let values v = No_info (Kind.Values v)
let values v = No_info (Var.Values v)
let renamed_in ~new_name ~version = Renamed_in (version, new_name)
let deleted_in ~version kind = Deleted_in (kind, version)
let since ~version v = Since (v, version)

let static_vars =
[ "first-dep", since ~version:(1, 0) Kind.First_dep
; "targets", since ~version:(1, 0) Kind.Targets
; "deps", since ~version:(1, 0) Kind.Deps
; "project_root", since ~version:(1, 0) Kind.Project_root
[ "first-dep", since ~version:(1, 0) Var.First_dep
; "targets", since ~version:(1, 0) Var.Targets
; "deps", since ~version:(1, 0) Var.Deps
; "project_root", since ~version:(1, 0) Var.Project_root

; "<", renamed_in ~version:(1, 0) ~new_name:"first-dep"
; "@", renamed_in ~version:(1, 0) ~new_name:"targets"
Expand Down
6 changes: 3 additions & 3 deletions src/pform.mli
Original file line number Diff line number Diff line change
@@ -1,4 +1,4 @@
module Kind : sig
module Var : sig
type t =
| Values of Value.t list
| Project_root
Expand Down Expand Up @@ -34,11 +34,11 @@ module Map : sig
type 'a var
type 'a t

val create_vars : context:Context.t -> cxx_flags:string list -> Kind.t t
val create_vars : context:Context.t -> cxx_flags:string list -> Var.t t

val macros : Macro.t t

val static_vars : Kind.t t
val static_vars : Var.t t

val expand
: 'a t
Expand Down
8 changes: 4 additions & 4 deletions src/super_context.ml
Original file line number Diff line number Diff line change
Expand Up @@ -45,7 +45,7 @@ type t =
; artifacts : Artifacts.t
; stanzas_to_consider_for_install : Installable.t list
; cxx_flags : string list
; vars : Pform.Kind.t Pform.Map.t
; vars : Pform.Var.t Pform.Map.t
; macros : Pform.Macro.t Pform.Map.t
; chdir : (Action.t, Action.t) Build.t
; host : t option
Expand Down Expand Up @@ -106,7 +106,7 @@ let (expand_vars_string, expand_vars_path) =
| None ->
String.Map.find extra_vars (String_with_vars.Var.full_name var)
| Some v ->
begin match Pform.Kind.to_value_no_deps_or_targets ~scope v with
begin match Pform.Var.to_value_no_deps_or_targets ~scope v with
| Some _ as v -> v
| None ->
Loc.fail (String_with_vars.Var.loc var)
Expand Down Expand Up @@ -710,7 +710,7 @@ module Action = struct
| Static l ->
Some (Value.L.dirs l) (* XXX hack to signal no dep *)
end
| Some v -> Pform.Kind.to_value_no_deps_or_targets v ~scope
| Some v -> Pform.Var.to_value_no_deps_or_targets v ~scope
end
in
Option.iter res ~f:(fun v ->
Expand All @@ -731,7 +731,7 @@ module Action = struct
| None ->
Pform.Map.expand Pform.Map.static_vars ~syntax_version ~var
|> Option.map ~f:(function
| Pform.Kind.Deps -> (Value.L.paths deps_written_by_user)
| Pform.Var.Deps -> (Value.L.paths deps_written_by_user)
| First_dep ->
begin match deps_written_by_user with
| [] ->
Expand Down

0 comments on commit 7a400a5

Please sign in to comment.