Skip to content

Commit

Permalink
configurator: add write_lines function
Browse files Browse the repository at this point in the history
The `write_flags` only works with `(:include` directives, and it
is also useful to be able to write a list of lines so that the
discovered information can be used in variable expansion actions.

For example, ocaml-yaml discovers CFLAGS and then directly has
`(run ${CC} ${read-lines:cflags})` actions that use this new
write_lines function to list cflags instead of s-expressions.
They must be line-by-line or else variable expansion doesnt work
since CFLAGS contain spaces.

Signed-off-by: Anil Madhavapeddy <anil@recoil.org>
  • Loading branch information
avsm authored and rgrinberg committed Jul 8, 2018
1 parent e7bc884 commit 23576a4
Show file tree
Hide file tree
Showing 2 changed files with 46 additions and 11 deletions.
27 changes: 20 additions & 7 deletions src/configurator/v1.ml
Original file line number Diff line number Diff line change
Expand Up @@ -61,6 +61,24 @@ module Temp = struct
dir
end

module Flags = struct
let extract_words = String.extract_words

let extract_comma_space_separated_words =
String.extract_comma_space_separated_words

let extract_blank_separated_words = String.extract_blank_separated_words

let write_lines fname s =
let path = Path.of_string fname in
Io.write_lines path s

let write_sexp fname s =
let path = Path.in_source fname in
let sexp = Usexp.List (List.map s ~f:(fun s -> Usexp.Quoted_string s)) in
Io.write_file path (Usexp.to_string sexp ~syntax:Dune)
end

module Find_in_path = struct
let path_sep =
if Sys.win32 then
Expand Down Expand Up @@ -485,18 +503,13 @@ module Pkg_config = struct
None
end

let write_flags fname s =
let path = Path.in_source fname in
let sexp = Usexp.List (List.map s ~f:(fun s -> Usexp.Quoted_string s)) in
Io.write_file path (Usexp.to_string sexp ~syntax:Dune)

let main ?(args=[]) ~name f =
let ocamlc = ref (
match Sys.getenv "DUNE_CONFIGURATOR" with
| s -> Some s
| exception Not_found ->
die "Configurator scripts must be ran with jbuilder. \
To manually run a script, use $ jbuilder exec."
die "Configurator scripts must be run with Dune. \
To manually run a script, use $ dune exec."
) in
let verbose = ref false in
let dest_dir = ref None in
Expand Down
30 changes: 26 additions & 4 deletions src/configurator/v1.mli
Original file line number Diff line number Diff line change
Expand Up @@ -87,10 +87,32 @@ module Pkg_config : sig
val query : t -> package:string -> package_conf option
end with type configurator := t

val write_flags : string -> string list -> unit
(** [write_flags fname s] write the list of strings [s] to the file
[fname] in an appropriate format so that it can used in jbuild
files with "(:include [fname])". *)
module Flags : sig

val write_sexp : string -> string list -> unit
(** [write_sexp fname s] writes the list of strings [s] to the file [fname] in
an appropriate format so that it can used in jbuild files with [(:include
[fname])]. *)

val write_lines : string -> string list -> unit
(** [write_lines fname s] writes the list of string [s] to the file [fname]
with one line per string so that it can be used in Dune action rules with
[%{read-lines:<path>}]. *)

val extract_comma_space_separated_words : string -> string list
(** [extract_comma_space_separated_words s] returns a list of words in
[s] that are separated by a newline, tab, space or comma character. *)

val extract_blank_separated_words : string -> string list
(** [extract_blank_separated_words s] returns a list of words in [s]
that are separated by a tab or space character. *)

val extract_words : string -> is_word_char:(char -> bool) -> string list
(** [extract_words s ~is_word_char] will split the string [s] into
a list of words. A valid word character is defined by the [is_word_char]
predicate returning true and anything else is considered a separator.
Any blank words are filtered out of the results. *)
end

(** Typical entry point for configurator programs *)
val main
Expand Down

0 comments on commit 23576a4

Please sign in to comment.