Skip to content

Commit

Permalink
Add model, architecture, system as enabled_if vars
Browse files Browse the repository at this point in the history
Now these variables can be used along with os_type in the enabled_if
field of libraries

Signed-off-by: Rudi Grinberg <rudi.grinberg@gmail.com>
  • Loading branch information
rgrinberg committed May 22, 2019
1 parent 4ba609d commit 0fd1014
Show file tree
Hide file tree
Showing 9 changed files with 63 additions and 6 deletions.
3 changes: 2 additions & 1 deletion CHANGES.md
Original file line number Diff line number Diff line change
Expand Up @@ -69,7 +69,8 @@ unreleased
`%{ocaml-config:os_type}` (#1764, @diml)

- Allow `enabled_if` fields in `library` stanzas, restricted to the
`%{os_type}` variable (#1764, @diml)
`%{os_type}`, `%{model}`, `%{architecture}`, `%{system}` variables (#1764,
#2164 @diml, @rgrinberg)

1.9.3 (06/05/2019)
------------------
Expand Down
6 changes: 6 additions & 0 deletions doc/dune-files.rst
Original file line number Diff line number Diff line change
Expand Up @@ -1097,6 +1097,12 @@ Dune supports the following variables:
workspace file)
- ``os_type`` is the type of the OS the build is targetting. This is
the same as ``ocaml-config:os_type``
- ``architecture`` is the type of the architecture the build is targetting. This
is the same as ``ocaml-config:architecture``
- ``model`` is the type of the cpu the build is targetting. This is
the same as ``ocaml-config:model``
- ``system`` is the name of the OS the build is targetting. This is the same as
``ocaml-config:system``

In addition, ``(action ...)`` fields support the following special variables:

Expand Down
5 changes: 5 additions & 0 deletions src/context.ml
Original file line number Diff line number Diff line change
Expand Up @@ -85,6 +85,7 @@ type t =
; ext_dll : string
; ext_exe : string
; os_type : string
; model : string
; default_executable_name : string
; host : string
; target : string
Expand Down Expand Up @@ -473,6 +474,7 @@ let create ~(kind : Kind.t) ~path ~env ~env_nodes ~name ~merlin ~targets
; ext_dll = Ocaml_config.ext_dll ocfg
; ext_exe = Ocaml_config.ext_exe ocfg
; os_type = Ocaml_config.os_type ocfg
; model = Ocaml_config.model ocfg
; default_executable_name = Ocaml_config.default_executable_name ocfg
; host = Ocaml_config.host ocfg
; target = Ocaml_config.target ocfg
Expand Down Expand Up @@ -703,4 +705,7 @@ let lib_config t =
; ext_obj = t.ext_obj
; ext_lib = t.ext_lib
; os_type = t.os_type
; architecture = t.architecture
; system = t.system
; model = t.model
}
1 change: 1 addition & 0 deletions src/context.mli
Original file line number Diff line number Diff line change
Expand Up @@ -109,6 +109,7 @@ type t =
; ext_dll : string
; ext_exe : string
; os_type : string
; model : string
; default_executable_name : string
; host : string
; target : string
Expand Down
9 changes: 6 additions & 3 deletions src/dune_file.ml
Original file line number Diff line number Diff line change
Expand Up @@ -1028,11 +1028,14 @@ module Library = struct
Blang.fold_vars enabled_if ~init:() ~f:(fun var () ->
match String_with_vars.Var.name var,
String_with_vars.Var.payload var with
| "os_type", None -> ()
| var, None when
List.mem var ~set:Lib_config.allowed_in_enabled_if -> ()
| _ ->
Errors.fail (String_with_vars.Var.loc var)
"Only the 'os_type' variable is allowed in the 'enabled_if' \
field of libraries.");
"Only %s are allowed in the 'enabled_if' \
field of libraries."
(String.enumerate_and Lib_config.allowed_in_enabled_if)
);
{ name
; public
; synopsis
Expand Down
19 changes: 19 additions & 0 deletions src/lib_config.ml
Original file line number Diff line number Diff line change
Expand Up @@ -5,4 +5,23 @@ type t =
; ext_lib : string
; ext_obj : string
; os_type : string
; architecture : string
; system : string
; model : string
}

let var_map =
[ "architecture", (fun t -> t.architecture)
; "system", (fun t -> t.system)
; "model", (fun t -> t.model)
; "os_type", (fun t -> t.os_type)
]

let allowed_in_enabled_if = List.map ~f:fst var_map

let get_for_enabled_if t ~var =
match List.assoc var_map var with
| Some f -> f t
| None ->
Exn.code_error "Lib_config.get_for_enabled_if: var not allowed"
["var", Sexp.Encoder.string var]
13 changes: 13 additions & 0 deletions src/lib_config.mli
Original file line number Diff line number Diff line change
@@ -0,0 +1,13 @@
type t =
{ has_native : bool
; ext_lib : string
; ext_obj : string
; os_type : string
; architecture : string
; system : string
; model : string
}

val allowed_in_enabled_if : string list

val get_for_enabled_if : t -> var:string -> string
7 changes: 5 additions & 2 deletions src/lib_info.ml
Original file line number Diff line number Diff line change
Expand Up @@ -93,7 +93,8 @@ let user_written_deps t =
~f:(fun acc s -> Dune_file.Lib_dep.Direct s :: acc)

let of_library_stanza ~dir
~lib_config:{ Lib_config.has_native; ext_lib; ext_obj; os_type}
~lib_config:({ Lib_config.has_native; ext_lib; ext_obj; _ }
as lib_config)
(conf : Dune_file.Library.t) =
let (_loc, lib_name) = conf.name in
let obj_dir =
Expand Down Expand Up @@ -166,7 +167,9 @@ let of_library_stanza ~dir
Blang.eval conf.enabled_if ~dir ~f:(fun v _ver ->
match String_with_vars.Var.name v,
String_with_vars.Var.payload v with
| "os_type", None -> Some [String os_type]
| var, None ->
let value = Lib_config.get_for_enabled_if lib_config ~var in
Some [String value]
| _ -> None)
in
if not enabled_if_result then
Expand Down
6 changes: 6 additions & 0 deletions src/pform.ml
Original file line number Diff line number Diff line change
Expand Up @@ -210,6 +210,12 @@ module Map = struct
; "ROOT" , renamed_in ~version:(1, 0) ~new_name:"workspace_root"
; "os_type" , since ~version:(1, 10)
(Var.Values [String context.os_type])
; "architecture" , since ~version:(1, 10)
(Var.Values [String context.architecture])
; "system" , since ~version:(1, 10)
(Var.Values [String context.system])
; "model" , since ~version:(1, 10)
(Var.Values [String context.model])
]
in
{ vars =
Expand Down

0 comments on commit 0fd1014

Please sign in to comment.