Change Meta.load to return the simplified meta

It's always simplified anyway
This commit is contained in:
Rudi Grinberg 2018-03-22 16:39:43 +08:00
parent ab37e8ec22
commit fae5e78fc2
5 changed files with 40 additions and 35 deletions

View File

@ -99,11 +99,7 @@ module Config = struct
if not (Path.exists conf_file) then if not (Path.exists conf_file) then
die "@{<error>Error@}: ocamlfind toolchain %s isn't defined in %a \ die "@{<error>Error@}: ocamlfind toolchain %s isn't defined in %a \
(context: %s)" toolchain Path.pp path context; (context: %s)" toolchain Path.pp path context;
let vars = let vars = (Meta.load ~name:"" ~fn:(Path.to_string conf_file)).vars in
(Meta.simplify { name = ""
; entries = Meta.load (Path.to_string conf_file)
}).vars
in
{ vars = String_map.map vars ~f:Rules.of_meta_rules { vars = String_map.map vars ~f:Rules.of_meta_rules
; preds = Ps.make [toolchain] ; preds = Ps.make [toolchain]
} }
@ -167,7 +163,7 @@ end
type t = type t =
{ stdlib_dir : Path.t { stdlib_dir : Path.t
; path : Path.t list ; path : Path.t list
; builtins : Meta.t String_map.t ; builtins : Meta.Simplified.t String_map.t
; packages : (string, (Package.t, Unavailable_reason.t) result) Hashtbl.t ; packages : (string, (Package.t, Unavailable_reason.t) result) Hashtbl.t
} }
@ -233,7 +229,7 @@ let parse_package t ~meta_file ~name ~parent_dir ~vars =
(* Parse all the packages defined in a META file and add them to (* Parse all the packages defined in a META file and add them to
[t.packages] *) [t.packages] *)
let parse_and_acknowledge_meta t ~dir ~meta_file (meta : Meta.t) = let parse_and_acknowledge_meta t ~dir ~meta_file (meta : Meta.Simplified.t) =
let rec loop ~dir ~full_name (meta : Meta.Simplified.t) = let rec loop ~dir ~full_name (meta : Meta.Simplified.t) =
let vars = String_map.map meta.vars ~f:Rules.of_meta_rules in let vars = String_map.map meta.vars ~f:Rules.of_meta_rules in
let dir, res = let dir, res =
@ -243,13 +239,13 @@ let parse_and_acknowledge_meta t ~dir ~meta_file (meta : Meta.t) =
List.iter meta.subs ~f:(fun (meta : Meta.Simplified.t) -> List.iter meta.subs ~f:(fun (meta : Meta.Simplified.t) ->
loop ~dir ~full_name:(sprintf "%s.%s" full_name meta.name) meta) loop ~dir ~full_name:(sprintf "%s.%s" full_name meta.name) meta)
in in
loop ~dir ~full_name:meta.name (Meta.simplify meta) loop ~dir ~full_name:meta.name meta
(* Search for a <package>/META file in the findlib search path, parse (* Search for a <package>/META file in the findlib search path, parse
it and add its contents to [t.packages] *) it and add its contents to [t.packages] *)
let find_and_acknowledge_meta t ~fq_name = let find_and_acknowledge_meta t ~fq_name =
let root_name = root_package_name fq_name in let root_name = root_package_name fq_name in
let rec loop dirs : (Path.t * Path.t * Meta.t) option = let rec loop dirs : (Path.t * Path.t * Meta.Simplified.t) option =
match dirs with match dirs with
| dir :: dirs -> | dir :: dirs ->
let sub_dir = Path.relative dir root_name in let sub_dir = Path.relative dir root_name in
@ -257,18 +253,14 @@ let find_and_acknowledge_meta t ~fq_name =
if Path.exists fn then if Path.exists fn then
Some (sub_dir, Some (sub_dir,
fn, fn,
{ name = root_name Meta.load ~name:root_name ~fn:(Path.to_string fn))
; entries = Meta.load (Path.to_string fn)
})
else else
(* Alternative layout *) (* Alternative layout *)
let fn = Path.relative dir ("META." ^ root_name) in let fn = Path.relative dir ("META." ^ root_name) in
if Path.exists fn then if Path.exists fn then
Some (dir, Some (dir,
fn, fn,
{ name = root_name Meta.load ~fn:(Path.to_string fn) ~name:root_name)
; entries = Meta.load (Path.to_string fn)
})
else else
loop dirs loop dirs
| [] -> | [] ->

View File

@ -11,7 +11,14 @@ let ksprintf = Printf.ksprintf
let initial_cwd = Sys.getcwd () let initial_cwd = Sys.getcwd ()
module String_set = Set.Make(String) module String_set = Set.Make(String)
module String_map = Map.Make(String) module String_map = struct
include Map.Make(String)
let pp f fmt t =
Format.pp_print_list (fun fmt (k, v) ->
Format.fprintf fmt "@[<hov 2>(%s@ =@ %a)@]" k f v
) fmt (to_list t)
end
module Int_set = Set.Make(Int) module Int_set = Set.Make(Int)
module Int_map = Map.Make(Int) module Int_map = Map.Make(Int)

View File

@ -102,10 +102,6 @@ module Parse = struct
error lb "'package' or variable name expected" error lb "'package' or variable name expected"
end end
let load fn =
Io.with_lexbuf_from_file fn ~f:(fun lb ->
Parse.entries lb 0 [])
module Simplified = struct module Simplified = struct
module Rules = struct module Rules = struct
type t = type t =
@ -145,6 +141,14 @@ let rec simplify t =
in in
{ pkg with vars = String_map.add pkg.vars rule.var rules }) { pkg with vars = String_map.add pkg.vars rule.var rules })
let load ~fn ~name =
{ name
; entries =
Io.with_lexbuf_from_file fn ~f:(fun lb ->
Parse.entries lb 0 [])
}
|> simplify
let rule var predicates action value = let rule var predicates action value =
Rule { var; predicates; action; value } Rule { var; predicates; action; value }
let requires ?(preds=[]) pkgs = let requires ?(preds=[]) pkgs =
@ -225,7 +229,7 @@ let builtins ~stdlib_dir =
else else
[ compiler_libs; str; unix; bigarray; threads ] [ compiler_libs; str; unix; bigarray; threads ]
in in
List.map libs ~f:(fun t -> t.name, t) List.map libs ~f:(fun t -> t.name, simplify t)
|> String_map.of_list_exn |> String_map.of_list_exn
let string_of_action = function let string_of_action = function

View File

@ -25,8 +25,6 @@ and predicate =
| Pos of string | Pos of string
| Neg of string | Neg of string
val load : string -> entry list
module Simplified : sig module Simplified : sig
module Rules : sig module Rules : sig
type t = type t =
@ -42,10 +40,10 @@ module Simplified : sig
} }
end end
val simplify : t -> Simplified.t val load : fn:string -> name:string -> Simplified.t
(** Builtin META files for libraries distributed with the compiler. For when ocamlfind is (** Builtin META files for libraries distributed with the compiler. For when ocamlfind is
not installed. *) not installed. *)
val builtins : stdlib_dir:Path.t -> t String_map.t val builtins : stdlib_dir:Path.t -> Simplified.t String_map.t
val pp : Format.formatter -> entry list -> unit val pp : Format.formatter -> entry list -> unit

View File

@ -10,6 +10,7 @@ let print_pkg ppf pkg =
;; ;;
#install_printer print_pkg;; #install_printer print_pkg;;
#install_printer String_map.pp;;
[%%expect{| [%%expect{|
val print_pkg : Format.formatter -> Jbuilder.Findlib.Package.t -> unit = val print_pkg : Format.formatter -> Jbuilder.Findlib.Package.t -> unit =
@ -50,16 +51,19 @@ Findlib.Package.requires pkg;;
open Meta open Meta
let meta = let meta =
{ name = "foo" Meta.load ~name:"foo" ~fn:"test/unit-tests/findlib-db/foo/META"
; entries = Meta.load "test/unit-tests/findlib-db/foo/META"
}
[%%expect{| [%%expect{|
val meta : Jbuilder.Meta.t = val meta : Jbuilder.Meta.Simplified.t =
{name = "foo"; {Jbuilder.Meta.Simplified.name = "foo";
entries = vars =
[Rule {var = "requires"; predicates = []; action = Set; value = "bar"}; (requires =
Rule {Jbuilder.Meta.Simplified.Rules.set_rules =
{var = "requires"; predicates = [Pos "ppx_driver"]; action = Set; [{Jbuilder__Meta.var = "requires"; predicates = [];
value = "baz"}]} action = Jbuilder__Meta.Set; value = "bar"};
{Jbuilder__Meta.var = "requires";
predicates = [Jbuilder__Meta.Pos "ppx_driver"];
action = Jbuilder__Meta.Set; value = "baz"}];
add_rules = []});
subs = []}
|}] |}]