diff --git a/CHANGES.md b/CHANGES.md index 3ab7d209c4c..dccd523f0d8 100644 --- a/CHANGES.md +++ b/CHANGES.md @@ -130,6 +130,10 @@ the executable source. Programs that use this feature can be run by a new action (dynamic-run ...). (#2635, @staronj, @aalekseyev) +- Add support for dependencies that are re-exported. Such dependencies + are marked with`re_export` and will automatically be provided to + users of a library (#2605, @rgrinberg) + 1.11.3 (23/08/2019) ------------------- diff --git a/src/dune/cinaps.ml b/src/dune/cinaps.ml index 4a1b460a8ae..2c56acb5dda 100644 --- a/src/dune/cinaps.ml +++ b/src/dune/cinaps.ml @@ -5,7 +5,7 @@ open Build.O type t = { loc : Loc.t ; files : Predicate_lang.t - ; libraries : Dune_file.Lib_dep.t list + ; libraries : Lib_dep.t list ; preprocess : Dune_file.Preprocess_map.t ; preprocessor_deps : Dune_file.Dep_conf.t list ; flags : Ocaml_flags.Spec.t @@ -27,7 +27,10 @@ let decode = ~default:Dune_file.Preprocess_map.default and+ preprocessor_deps = field "preprocessor_deps" (repeat Dune_file.Dep_conf.decode) ~default:[] - and+ libraries = field "libraries" Dune_file.Lib_deps.decode ~default:[] + and+ libraries = + field "libraries" + (Dune_file.Lib_deps.decode ~allow_re_export:false) + ~default:[] and+ flags = Ocaml_flags.Spec.decode in { loc; files; libraries; preprocess; preprocessor_deps; flags }) @@ -87,8 +90,7 @@ let gen_rules sctx t ~dir ~scope = let compile_info = Lib.DB.resolve_user_written_deps_for_exes (Scope.libs scope) [ (t.loc, name) ] - ( Dune_file.Lib_dep.Direct - (loc, Lib_name.of_string_exn "cinaps.runtime" ~loc:None) + ( Lib_dep.Direct (loc, Lib_name.of_string_exn "cinaps.runtime" ~loc:None) :: t.libraries ) ~pps:(Dune_file.Preprocess_map.pps t.preprocess) ~variants:None ~optional:false diff --git a/src/dune/dir_contents.ml b/src/dune/dir_contents.ml index 160369647b1..732abac1070 100644 --- a/src/dune/dir_contents.ml +++ b/src/dune/dir_contents.ml @@ -430,8 +430,10 @@ end = struct |Executables { buildable; _ } -> (* Manually add files generated by the (select ...) dependencies *) List.filter_map buildable.libraries ~f:(fun dep -> - match (dep : Dune_file.Lib_dep.t) with - | Direct _ -> None + match (dep : Lib_dep.t) with + | Re_export _ + |Direct _ -> + None | Select s -> Some s.result_fn) | _ -> []) |> String.Set.of_list @@ -443,9 +445,13 @@ end = struct |Executables { buildable; _ } -> (* add files used by the (select ...) dependencies *) List.concat_map buildable.libraries ~f:(fun dep -> - match (dep : Dune_file.Lib_dep.t) with - | Direct _ -> [] - | Select s -> List.map s.choices ~f:(fun s -> s.Lib_dep.file)) + match (dep : Lib_dep.t) with + | Re_export _ + |Direct _ -> + [] + | Select s -> + List.map s.choices ~f:(fun (s : Lib_dep.Select.choice) -> + s.file)) | _ -> []) |> String.Set.of_list in diff --git a/src/dune/dune_file.ml b/src/dune/dune_file.ml index db22bb4a944..e790c4c8d1c 100644 --- a/src/dune/dune_file.ml +++ b/src/dune/dune_file.ml @@ -37,15 +37,6 @@ let module_name = Module_name.of_string s with Exit -> invalid_module_name ~loc name )) -let file = - plain_string (fun ~loc s -> - match s with - | "." - |".." -> - User_error.raise ~loc - [ Pp.textf "'.' and '..' are not valid filenames" ] - | fn -> fn) - let relative_file = plain_string (fun ~loc fn -> if Filename.is_relative fn then @@ -492,86 +483,6 @@ module Js_of_ocaml = struct { flags = Ordered_set_lang.Unexpanded.standard; javascript_files = [] } end -module Lib_dep = struct - type choice = - { required : Lib_name.Set.t - ; forbidden : Lib_name.Set.t - ; file : string - } - - type select = - { result_fn : string - ; choices : choice list - ; loc : Loc.t (* For error messages *) - } - - type t = - | Direct of (Loc.t * Lib_name.t) - | Select of select - - let choice = - enter - (let+ loc = loc - and+ preds, file = - until_keyword "->" - ~before: - (let+ s = string - and+ loc = loc in - let len = String.length s in - if len > 0 && s.[0] = '!' then - Right - (Lib_name.of_string_exn ~loc:(Some loc) (String.drop s 1)) - else - Left (Lib_name.of_string_exn ~loc:(Some loc) s)) - ~after:file - in - match file with - | None -> - User_error.raise ~loc - [ Pp.textf "(<[!]libraries>... -> ) expected" ] - | Some file -> - let rec loop required forbidden = function - | [] -> - let common = Lib_name.Set.inter required forbidden in - Option.iter (Lib_name.Set.choose common) ~f:(fun name -> - User_error.raise ~loc - [ Pp.textf - "library %S is both required and forbidden in this \ - clause" - (Lib_name.to_string name) - ]); - { required; forbidden; file } - | Left s :: l -> loop (Lib_name.Set.add required s) forbidden l - | Right s :: l -> loop required (Lib_name.Set.add forbidden s) l - in - loop Lib_name.Set.empty Lib_name.Set.empty preds) - - let decode = - if_list - ~then_: - (enter - (let+ loc = loc - and+ () = keyword "select" - and+ result_fn = file - and+ () = keyword "from" - and+ choices = repeat choice in - Select { result_fn; choices; loc })) - ~else_: - (let+ loc, name = located Lib_name.decode in - Direct (loc, name)) - - let to_lib_names = function - | Direct (_, s) -> [ s ] - | Select s -> - List.fold_left s.choices ~init:Lib_name.Set.empty ~f:(fun acc x -> - Lib_name.Set.union acc (Lib_name.Set.union x.required x.forbidden)) - |> Lib_name.Set.to_list - - let direct x = Direct x - - let of_lib_name (loc, pp) = Direct (loc, pp) -end - module Lib_deps = struct type t = Lib_dep.t list @@ -580,9 +491,9 @@ module Lib_deps = struct | Optional | Forbidden - let decode = + let decode ~allow_re_export = let+ loc = loc - and+ t = repeat Lib_dep.decode in + and+ t = repeat (Lib_dep.decode ~allow_re_export) in let add kind name acc = match Lib_name.Map.find acc name with | None -> Lib_name.Map.set acc name kind @@ -612,26 +523,29 @@ module Lib_deps = struct ignore ( List.fold_left t ~init:Lib_name.Map.empty ~f:(fun acc x -> match x with - | Lib_dep.Direct (_, s) -> add Required s acc + | Lib_dep.Re_export (_, s) + |Lib_dep.Direct (_, s) -> + add Required s acc | Select { choices; _ } -> - List.fold_left choices ~init:acc ~f:(fun acc c -> + List.fold_left choices ~init:acc + ~f:(fun acc (c : Lib_dep.Select.choice) -> let acc = - Lib_name.Set.fold c.Lib_dep.required ~init:acc - ~f:(add Optional) + Lib_name.Set.fold c.required ~init:acc ~f:(add Optional) in Lib_name.Set.fold c.forbidden ~init:acc ~f:(add Forbidden))) : kind Lib_name.Map.t ); t - let of_pps pps = - List.map pps ~f:(fun pp -> Lib_dep.of_lib_name (Loc.none, pp)) + let of_pps pps = List.map pps ~f:(fun pp -> Lib_dep.direct (Loc.none, pp)) let info t ~kind = List.concat_map t ~f:(function - | Lib_dep.Direct (_, s) -> [ (s, kind) ] + | Lib_dep.Re_export (_, s) + |Lib_dep.Direct (_, s) -> + [ (s, kind) ] | Select { choices; _ } -> - List.concat_map choices ~f:(fun c -> - Lib_name.Set.to_list c.Lib_dep.required + List.concat_map choices ~f:(fun (c : Lib_dep.Select.choice) -> + Lib_name.Set.to_list c.required |> List.map ~f:(fun d -> (d, Lib_deps_info.Kind.Optional)))) |> Lib_name.Map.of_list_reduce ~f:Lib_deps_info.Kind.merge end @@ -655,7 +569,7 @@ module Buildable = struct ; allow_overlapping_dependencies : bool } - let decode ~since_c = + let decode ~since_c ~allow_re_export = let check_c t = match since_c with | None -> t @@ -673,7 +587,8 @@ module Buildable = struct and+ modules = modules_field "modules" and+ modules_without_implementation = modules_field "modules_without_implementation" - and+ libraries = field "libraries" Lib_deps.decode ~default:[] + and+ libraries = + field "libraries" (Lib_deps.decode ~allow_re_export) ~default:[] and+ flags = Ocaml_flags.Spec.decode and+ js_of_ocaml = field "js_of_ocaml" Js_of_ocaml.decode ~default:Js_of_ocaml.default @@ -1022,7 +937,7 @@ module Library = struct let decode = fields - (let+ buildable = Buildable.decode ~since_c:None + (let+ buildable = Buildable.decode ~since_c:None ~allow_re_export:true and+ loc = loc and+ name = field_o "name" Lib_name.Local.decode_loc and+ public = Public_lib.public_name_field @@ -1610,7 +1525,8 @@ module Executables = struct } let common = - let+ buildable = Buildable.decode ~since_c:(Some (2, 0)) + let+ buildable = + Buildable.decode ~since_c:(Some (2, 0)) ~allow_re_export:false and+ (_ : bool) = field "link_executables" ~default:true (Dune_lang.Syntax.deleted_in Stanza.syntax (1, 0) >>> bool) @@ -2120,7 +2036,8 @@ module Tests = struct let gen_parse names = fields - (let+ buildable = Buildable.decode ~since_c:(Some (2, 0)) + (let+ buildable = + Buildable.decode ~since_c:(Some (2, 0)) ~allow_re_export:false and+ link_flags = field_oslu "link_flags" and+ variants = variants_field and+ names = names diff --git a/src/dune/dune_file.mli b/src/dune/dune_file.mli index 5fb2cc7259e..5449ed7f3a5 100644 --- a/src/dune/dune_file.mli +++ b/src/dune/dune_file.mli @@ -73,38 +73,14 @@ module Js_of_ocaml : sig val default : t end -module Lib_dep : sig - type choice = - { required : Lib_name.Set.t - ; forbidden : Lib_name.Set.t - ; file : string - } - - type select = - { result_fn : string - ; choices : choice list - ; loc : Loc.t - } - - type t = - | Direct of (Loc.t * Lib_name.t) - | Select of select - - val to_lib_names : t -> Lib_name.t list - - val direct : Loc.t * Lib_name.t -> t - - val of_lib_name : Loc.t * Lib_name.t -> t -end - module Lib_deps : sig - type t = Lib_dep.t list + type nonrec t = Lib_dep.t list val of_pps : Lib_name.t list -> t val info : t -> kind:Lib_deps_info.Kind.t -> Lib_deps_info.t - val decode : t Dune_lang.Decoder.t + val decode : allow_re_export:bool -> t Dune_lang.Decoder.t end module Dep_conf : sig diff --git a/src/dune/dune_package.ml b/src/dune/dune_package.ml index 36c3e5c9f73..fa4f1c5120f 100644 --- a/src/dune/dune_package.ml +++ b/src/dune/dune_package.ml @@ -14,10 +14,9 @@ module Lib = struct { info : Path.t Lib_info.t ; modules : Modules.t option ; main_module_name : Module_name.t option - ; requires : (Loc.t * Lib_name.t) list } - let make ~info ~main_module_name ~requires ~modules = + let make ~info ~main_module_name ~modules = let obj_dir = Lib_info.obj_dir info in let dir = Obj_dir.dir obj_dir in let map_path p = @@ -27,13 +26,13 @@ module Lib = struct p in let info = Lib_info.map_path info ~f:map_path in - { info; main_module_name; requires; modules } + { info; main_module_name; modules } let dir_of_name name = let _, components = Lib_name.split name in Path.Local.L.relative Path.Local.root components - let encode ~package_root { info; requires; main_module_name; modules } = + let encode ~package_root { info; main_module_name; modules } = let open Dune_lang.Encoder in let no_loc f (_loc, x) = f x in let path = Dpath.Local.encode ~dir:package_root in @@ -58,6 +57,7 @@ module Lib = struct let archives = Lib_info.archives info in let sub_systems = Lib_info.sub_systems info in let plugins = Lib_info.plugins info in + let requires = Lib_info.requires info in let foreign_archives = Lib_info.foreign_archives info in let foreign_objects = match Lib_info.foreign_objects info with @@ -77,7 +77,7 @@ module Lib = struct ; paths "foreign_objects" foreign_objects ; mode_paths "foreign_archives" foreign_archives ; paths "jsoo_runtime" jsoo_runtime - ; libs "requires" requires + ; Lib_dep.L.field_encode requires ~name:"requires" ; libs "ppx_runtime_deps" ppx_runtime_deps ; field_o "implements" (no_loc Lib_name.encode) implements ; field_l "known_implementations" @@ -134,7 +134,8 @@ module Lib = struct and+ foreign_objects = paths "foreign_objects" and+ foreign_archives = mode_paths "foreign_archives" and+ jsoo_runtime = paths "jsoo_runtime" - and+ requires = libs "requires" + and+ requires = + field_l "requires" (Lib_dep.decode ~allow_re_export:true) and+ ppx_runtime_deps = libs "ppx_runtime_deps" and+ virtual_ = field_b "virtual" and+ known_implementations = @@ -166,7 +167,6 @@ module Lib = struct Dune_file.Library.Inherited.This main_module_name in let foreign_objects = Lib_info.Source.External foreign_objects in - let requires = Lib_info.Deps.Simple requires in let jsoo_archive = None in let pps = [] in let virtual_deps = [] in @@ -191,14 +191,12 @@ module Lib = struct ~known_implementations ~default_implementation ~modes ~wrapped ~special_builtin_support in - { info; requires; main_module_name; modules }) + { info; main_module_name; modules }) let modules t = t.modules let main_module_name t = t.main_module_name - let requires t = t.requires - let compare_name x y = let x = Lib_info.name x.info in let y = Lib_info.name y.info in diff --git a/src/dune/dune_package.mli b/src/dune/dune_package.mli index 6ef8c612f82..b92c20c3ceb 100644 --- a/src/dune/dune_package.mli +++ b/src/dune/dune_package.mli @@ -3,8 +3,6 @@ open! Stdune module Lib : sig type t - val requires : t -> (Loc.t * Lib_name.t) list - val modules : t -> Modules.t option val main_module_name : t -> Module_name.t option @@ -20,7 +18,6 @@ module Lib : sig val make : info:Path.t Lib_info.t -> main_module_name:Module_name.t option - -> requires:(Loc.t * Lib_name.t) list -> modules:Modules.t option -> t end diff --git a/src/dune/findlib/findlib.ml b/src/dune/findlib/findlib.ml index 8bb360e3752..9285a7f0529 100644 --- a/src/dune/findlib/findlib.ml +++ b/src/dune/findlib/findlib.ml @@ -259,7 +259,9 @@ module Package = struct This None in let enabled = Lib_info.Enabled_status.Normal in - let requires = Lib_info.Deps.Simple (List.map ~f:add_loc (requires t)) in + let requires = + requires t |> List.map ~f:(fun name -> Lib_dep.direct (add_loc name)) + in let ppx_runtime_deps = List.map ~f:add_loc (ppx_runtime_deps t) in let special_builtin_support : Dune_file.Library.Special_builtin_support.t option = @@ -287,9 +289,7 @@ module Package = struct ~virtual_ ~implements ~variant ~known_implementations ~default_implementation ~modes ~wrapped ~special_builtin_support in - Dune_package.Lib.make ~info - ~requires:(List.map ~f:add_loc (requires t)) - ~modules:None ~main_module_name:None + Dune_package.Lib.make ~info ~modules:None ~main_module_name:None (* XXX remove *) diff --git a/src/dune/lib.ml b/src/dune/lib.ml index 5bf439dfc9a..8c50b626d0a 100644 --- a/src/dune/lib.ml +++ b/src/dune/lib.ml @@ -283,6 +283,7 @@ module T = struct { info : Lib_info.external_ ; name : Lib_name.t ; unique_id : Id.t + ; re_exports : t list Or_exn.t ; requires : t list Or_exn.t ; ppx_runtime_deps : t list Or_exn.t ; pps : t list Or_exn.t @@ -914,11 +915,14 @@ module rec Resolve : sig val resolve_user_deps : db - -> Lib_info.Deps.t + -> Lib_dep.t list -> allow_private_deps:bool -> pps:(Loc.t * Lib_name.t) list -> stack:Dep_stack.t - -> lib list Or_exn.t * lib list Or_exn.t * Resolved_select.t list + -> lib list Or_exn.t + * lib list Or_exn.t + * Resolved_select.t list + * lib list Or_exn.t val closure_with_overlap_checks : db option @@ -1002,7 +1006,7 @@ end = struct Lib_info.known_implementations info |> Variant.Map.map ~f:resolve_impl )) in - let requires, pps, resolved_selects = + let requires, pps, resolved_selects, re_exports = let pps = Lib_info.pps info in Lib_info.requires info |> resolve_user_deps db ~allow_private_deps ~pps ~stack @@ -1041,6 +1045,7 @@ end = struct ; default_implementation ; resolved_implementations ; stdlib_dir = db.stdlib_dir + ; re_exports } in t.sub_systems <- @@ -1118,80 +1123,84 @@ end = struct Result.List.map names ~f:(fun (loc, name) -> resolve_dep db name ~allow_private_deps ~loc ~stack) + let re_exports_closure ts = + let visited = ref Set.empty in + let res = ref [] in + let rec one (t : lib) = + if Set.mem !visited t then + Ok () + else ( + visited := Set.add !visited t; + let* re_exports = t.re_exports in + let+ () = many re_exports in + res := t :: !res + ) + and many = Result.List.iter ~f:one in + let+ () = many ts in + List.rev !res + let resolve_complex_deps db deps ~allow_private_deps ~stack = - let res, resolved_selects = - List.fold_left deps ~init:(Ok [], []) - ~f:(fun (acc_res, acc_selects) dep -> - let res, acc_selects = - match (dep : Dune_file.Lib_dep.t) with - | Direct (loc, name) -> - let res = - resolve_dep db name ~allow_private_deps ~loc ~stack - >>| List.singleton - in - (res, acc_selects) - | Select { result_fn; choices; loc } -> - let res, src_fn = + let resolve_select { Lib_dep.Select.result_fn; choices; loc } = + let res, src_fn = + match + List.find_map choices ~f:(fun { required; forbidden; file } -> + if + Lib_name.Set.exists forbidden ~f:(available_internal db ~stack) + then + None + else match - List.find_map choices - ~f:(fun { required; forbidden; file } -> - if - Lib_name.Set.exists forbidden - ~f:(available_internal db ~stack) - then - None - else - match - let deps = - Lib_name.Set.fold required ~init:[] - ~f:(fun x acc -> (loc, x) :: acc) - in - resolve_simple_deps ~allow_private_deps db deps - ~stack - with - | Ok ts -> Some (ts, file) - | Error _ -> None) + let deps = + Lib_name.Set.fold required ~init:[] ~f:(fun x acc -> + (loc, x) :: acc) + in + resolve_simple_deps ~allow_private_deps db deps ~stack with - | Some (ts, file) -> (Ok ts, Ok file) - | None -> - let e () = Error.no_solution_found_for_select ~loc in - (e (), e ()) - in - ( res - , { Resolved_select.src_fn; dst_fn = result_fn } :: acc_selects - ) - in - let res = - match (res, acc_res) with - | Ok l, Ok acc -> Ok (List.rev_append l acc) - | (Error _ as res), _ - |_, (Error _ as res) -> - res - in - (res, acc_selects)) - in - let res = - match res with - | Ok l -> Ok (List.rev l) - | Error _ -> res + | Ok ts -> Some (ts, file) + | Error _ -> None) + with + | Some (ts, file) -> (Ok ts, Ok file) + | None -> + let e () = Error.no_solution_found_for_select ~loc in + (e (), e ()) + in + (res, { Resolved_select.src_fn; dst_fn = result_fn }) in - (res, resolved_selects) - - let resolve_deps db deps ~allow_private_deps ~stack = - (* Compute transitive closure *) - let libs, selects = - match (deps : Lib_info.Deps.t) with - | Simple names -> - (resolve_simple_deps db names ~allow_private_deps ~stack, []) - | Complex names -> - resolve_complex_deps db names ~allow_private_deps ~stack + let res, resolved_selects, re_exports = + List.fold_left deps ~init:(Ok [], [], Ok []) + ~f:(fun (acc_res, acc_selects, acc_re_exports) dep -> + match (dep : Lib_dep.t) with + | Re_export (loc, name) -> + let lib = resolve_dep db name ~allow_private_deps ~loc ~stack in + let acc_re_exports = + let+ lib = lib + and+ acc_re_exports = acc_re_exports in + lib :: acc_re_exports + in + let acc_res = + let+ lib = lib + and+ acc_res = acc_res in + lib :: acc_res + in + (acc_res, acc_selects, acc_re_exports) + | Direct (loc, name) -> + let res = + let+ lib = resolve_dep db name ~allow_private_deps ~loc ~stack + and+ acc_res = acc_res in + lib :: acc_res + in + (res, acc_selects, acc_re_exports) + | Select select -> + let res, resolved_select = resolve_select select in + (res, resolved_select :: acc_selects, acc_re_exports)) in - (* Find implementations for virtual libraries. *) - (libs, selects) + let res = Result.map ~f:List.rev res in + let re_exports = Result.map ~f:List.rev re_exports in + (res, resolved_selects, re_exports) let resolve_user_deps db deps ~allow_private_deps ~pps ~stack = - let deps, resolved_selects = - resolve_deps db deps ~allow_private_deps ~stack + let deps, resolved_selects, re_exports = + resolve_complex_deps db deps ~allow_private_deps ~stack in let deps, pps = match pps with @@ -1224,7 +1233,8 @@ end = struct in (deps, pps) in - (deps, pps, resolved_selects) + let deps = deps >>= re_exports_closure in + (deps, pps, resolved_selects, re_exports) (* Compute transitive closure of libraries to figure which ones will trigger their default implementation. @@ -1727,10 +1737,9 @@ module DB = struct else Required ) in - let res, pps, resolved_selects = - Resolve.resolve_user_deps t - (Lib_info.Deps.of_lib_deps deps) - ~pps ~stack:Dep_stack.empty ~allow_private_deps:true + let res, pps, resolved_selects, _re_exports = + Resolve.resolve_user_deps t deps ~pps ~stack:Dep_stack.empty + ~allow_private_deps:true in let requires_link = lazy @@ -1807,42 +1816,17 @@ module Meta = struct end let to_dune_lib ({ info; _ } as lib) ~modules ~foreign_objects ~dir = - let add_loc = - let loc = Lib_info.loc info in - List.map ~f:(fun x -> (loc, x.name)) - in + let loc = Lib_info.loc info in + let add_loc = List.map ~f:(fun x -> (loc, x.name)) in let obj_dir = match Obj_dir.to_local (obj_dir lib) with | None -> assert false | Some obj_dir -> Obj_dir.convert_to_external ~dir obj_dir in - let info = Lib_info.set_obj_dir info obj_dir in let modules = let install_dir = Obj_dir.dir obj_dir in Modules.version_installed modules ~install_dir in - let info = - match !Clflags.store_orig_src_dir with - | false -> info - | true -> - let orig_src_dir = - let orig_src_dir = Lib_info.orig_src_dir info in - match orig_src_dir with - | Some src_dir -> src_dir - | None -> ( - let src_dir = Lib_info.src_dir info in - match Path.drop_build_context src_dir with - | None -> src_dir - | Some src_dir -> - Path.(of_string (to_absolute_filename (Path.source src_dir))) ) - in - Lib_info.set_orig_src_dir info orig_src_dir - in - let info = - match Lib_info.foreign_objects info with - | External _ -> info - | Local -> Lib_info.set_foreign_objects info foreign_objects - in let use_public_name ~lib_field ~info_field = match (info_field, lib_field) with | Some _, None @@ -1855,26 +1839,32 @@ let to_dune_lib ({ info; _ } as lib) ~modules ~foreign_objects ~dir = Some (loc, field.name) in let open Result.O in - let* implements = + let+ implements = use_public_name ~info_field:(Lib_info.implements info) ~lib_field:(implements lib) - in - let* default_implementation = + and+ default_implementation = use_public_name ~info_field:(Lib_info.default_implementation info) ~lib_field:(Option.map ~f:Lazy.force lib.default_implementation) + and+ ppx_runtime_deps = lib.ppx_runtime_deps + and+ main_module_name = main_module_name lib + and+ requires = lib.requires + and+ re_exports = lib.re_exports in - let info = Lib_info.set_implements info implements in - let info = Lib_info.set_default_implementation info default_implementation in - let* ppx_runtime_deps = lib.ppx_runtime_deps in let ppx_runtime_deps = add_loc ppx_runtime_deps in - let info = Lib_info.set_ppx_runtime_deps info ppx_runtime_deps in - let info = Lib_info.set_sub_systems info (Sub_system.public_info lib) in - let* main_module_name = main_module_name lib in - let+ requires = lib.requires in - let requires = add_loc requires in - Dune_package.Lib.make ~info ~requires ~modules:(Some modules) - ~main_module_name + let sub_systems = Sub_system.public_info lib in + let requires = + List.map requires ~f:(fun lib -> + if List.exists re_exports ~f:(fun r -> r = lib) then + Lib_dep.Re_export (loc, lib.name) + else + Direct (loc, lib.name)) + in + let info = + Lib_info.for_dune_package info ~ppx_runtime_deps ~requires ~foreign_objects + ~obj_dir ~implements ~default_implementation ~sub_systems + in + Dune_package.Lib.make ~info ~modules:(Some modules) ~main_module_name module Local : sig type t = private lib diff --git a/src/dune/lib.mli b/src/dune/lib.mli index bcf3f490e6d..7968c692b66 100644 --- a/src/dune/lib.mli +++ b/src/dune/lib.mli @@ -197,7 +197,7 @@ module DB : sig -> (Loc.t * string) list -> ?allow_overlaps:bool -> ?forbidden_libraries:(Loc.t * Lib_name.t) list - -> Dune_file.Lib_dep.t list + -> Lib_dep.t list -> pps:(Loc.t * Lib_name.t) list -> variants:(Loc.t * Variant.Set.t) option -> optional:bool diff --git a/src/dune/lib_dep.ml b/src/dune/lib_dep.ml new file mode 100644 index 00000000000..84eb2011c6f --- /dev/null +++ b/src/dune/lib_dep.ml @@ -0,0 +1,132 @@ +open Stdune + +module Select = struct + type choice = + { required : Lib_name.Set.t + ; forbidden : Lib_name.Set.t + ; file : string + } + + let dyn_of_choice { required; forbidden; file } = + let open Dyn.Encoder in + record + [ ("required", Lib_name.Set.to_dyn required) + ; ("forbidden", Lib_name.Set.to_dyn forbidden) + ; ("file", string file) + ] + + type t = + { result_fn : string + ; choices : choice list + ; loc : Loc.t + } + + let to_dyn { result_fn; choices; loc = _ } = + let open Dyn.Encoder in + record + [ ("result_fn", string result_fn) + ; ("choices", list dyn_of_choice choices) + ] +end + +type t = + | Direct of (Loc.t * Lib_name.t) + | Re_export of (Loc.t * Lib_name.t) + | Select of Select.t + +let to_dyn = + let open Dyn.Encoder in + function + | Direct (_, name) -> Lib_name.to_dyn name + | Re_export (_, name) -> constr "re_export" [ Lib_name.to_dyn name ] + | Select s -> constr "select" [ Select.to_dyn s ] + +let direct x = Direct x + +let re_export x = Re_export x + +let to_lib_names = function + | Direct (_, s) + |Re_export (_, s) -> + [ s ] + | Select s -> + List.fold_left s.choices ~init:Lib_name.Set.empty + ~f:(fun acc (x : Select.choice) -> + Lib_name.Set.union acc (Lib_name.Set.union x.required x.forbidden)) + |> Lib_name.Set.to_list + +let choice = + let open Dune_lang.Decoder in + enter + (let+ loc = loc + and+ preds, file = + until_keyword "->" + ~before: + (let+ s = string + and+ loc = loc in + let len = String.length s in + if len > 0 && s.[0] = '!' then + Right (Lib_name.of_string_exn ~loc:(Some loc) (String.drop s 1)) + else + Left (Lib_name.of_string_exn ~loc:(Some loc) s)) + ~after:filename + in + match file with + | None -> + User_error.raise ~loc + [ Pp.textf "(<[!]libraries>... -> ) expected" ] + | Some file -> + let rec loop required forbidden = function + | [] -> + let common = Lib_name.Set.inter required forbidden in + Option.iter (Lib_name.Set.choose common) ~f:(fun name -> + User_error.raise ~loc + [ Pp.textf + "library %S is both required and forbidden in this clause" + (Lib_name.to_string name) + ]); + { Select.required; forbidden; file } + | Left s :: l -> loop (Lib_name.Set.add required s) forbidden l + | Right s :: l -> loop required (Lib_name.Set.add forbidden s) l + in + loop Lib_name.Set.empty Lib_name.Set.empty preds) + +let decode ~allow_re_export = + let open Dune_lang.Decoder in + if_list + ~then_: + (enter + (let* loc = loc in + let* cloc, constr = located string in + match constr with + | "re_export" -> + if not allow_re_export then + User_error.raise ~loc:cloc + [ Pp.text "re_export is not allowed here" ]; + let+ () = Dune_lang.Syntax.since Stanza.syntax (2, 0) + and+ loc, name = located Lib_name.decode in + Re_export (loc, name) + | "select" -> + let+ result_fn = filename + and+ () = keyword "from" + and+ choices = repeat choice in + Select { result_fn; choices; loc } + | _ -> User_error.raise ~loc:cloc [ Pp.text "invalid constructor" ])) + ~else_: + (let+ loc, name = located Lib_name.decode in + Direct (loc, name)) + +let encode = + let open Dune_lang.Encoder in + function + | Direct (_, name) -> Lib_name.encode name + | Re_export (_, name) -> constr "re_export" Lib_name.encode name + | Select select -> + Code_error.raise "Lib_dep.encode: cannot encode select" + [ ("select", Select.to_dyn select) ] + +module L = struct + let field_encode t ~name = + let open Dune_lang.Encoder in + field_l name encode t +end diff --git a/src/dune/lib_dep.mli b/src/dune/lib_dep.mli new file mode 100644 index 00000000000..5cd1a784468 --- /dev/null +++ b/src/dune/lib_dep.mli @@ -0,0 +1,38 @@ +open Stdune + +module Select : sig + type choice = + { required : Lib_name.Set.t + ; forbidden : Lib_name.Set.t + ; file : string + } + + type t = + { result_fn : string + ; choices : choice list + ; loc : Loc.t + } + + val to_dyn : t -> Dyn.t +end + +type t = + | Direct of (Loc.t * Lib_name.t) + | Re_export of (Loc.t * Lib_name.t) + | Select of Select.t + +val to_dyn : t -> Dyn.t + +val direct : Loc.t * Lib_name.t -> t + +val re_export : Loc.t * Lib_name.t -> t + +val to_lib_names : t -> Lib_name.t list + +val decode : allow_re_export:bool -> t Dune_lang.Decoder.t + +val encode : t Dune_lang.Encoder.t + +module L : sig + val field_encode : t list -> name:string -> Dune_lang.Encoder.field +end diff --git a/src/dune/lib_info.ml b/src/dune/lib_info.ml index 8ba4552e90a..07f5fe63c20 100644 --- a/src/dune/lib_info.ml +++ b/src/dune/lib_info.ml @@ -27,27 +27,6 @@ module Status = struct | Public (name, _) -> Some name end -module Deps = struct - type t = - | Simple of (Loc.t * Lib_name.t) list - | Complex of Dune_file.Lib_dep.t list - - let of_lib_deps deps = - let rec loop acc (deps : Dune_file.Lib_dep.t list) = - match deps with - | [] -> Some (List.rev acc) - | Direct x :: deps -> loop (x :: acc) deps - | Select _ :: _ -> None - in - match loop [] deps with - | Some l -> Simple l - | None -> Complex deps - - let to_lib_deps = function - | Simple l -> List.map l ~f:Dune_file.Lib_dep.direct - | Complex l -> l -end - module Source = struct type 'a t = | Local @@ -82,7 +61,7 @@ type 'path t = ; foreign_archives : 'path list Mode.Dict.t (** [.a/.lib/...] files *) ; jsoo_runtime : 'path list ; jsoo_archive : 'path option - ; requires : Deps.t + ; requires : Lib_dep.t list ; ppx_runtime_deps : (Loc.t * Lib_name.t) list ; pps : (Loc.t * Lib_name.t) list ; enabled : Enabled_status.t @@ -163,25 +142,37 @@ let best_src_dir t = Option.value ~default:t.src_dir t.orig_src_dir let set_version t version = { t with version } -let set_orig_src_dir t orig_src_dir = - { t with orig_src_dir = Some orig_src_dir } - -let set_default_implementation t default_implementation = - { t with default_implementation } - -let set_implements t implements = { t with implements } - -let set_ppx_runtime_deps t ppx_runtime_deps = { t with ppx_runtime_deps } - -let set_sub_systems t sub_systems = { t with sub_systems } - -let set_foreign_objects t foreign_objects = - { t with foreign_objects = External foreign_objects } +let for_dune_package t ~ppx_runtime_deps ~requires ~foreign_objects ~obj_dir + ~implements ~default_implementation ~sub_systems = + let foreign_objects = Source.External foreign_objects in + let orig_src_dir = + match !Clflags.store_orig_src_dir with + | false -> t.orig_src_dir + | true -> + Some + ( match t.orig_src_dir with + | Some src_dir -> src_dir + | None -> ( + match Path.drop_build_context t.src_dir with + | None -> t.src_dir + | Some src_dir -> + Path.source src_dir |> Path.to_absolute_filename |> Path.of_string + ) ) + in + { t with + ppx_runtime_deps + ; requires + ; foreign_objects + ; obj_dir + ; implements + ; default_implementation + ; sub_systems + ; orig_src_dir + } let user_written_deps t = - List.fold_left (t.virtual_deps @ t.ppx_runtime_deps) - ~init:(Deps.to_lib_deps t.requires) ~f:(fun acc s -> - Dune_file.Lib_dep.Direct s :: acc) + List.fold_left (t.virtual_deps @ t.ppx_runtime_deps) ~init:t.requires + ~f:(fun acc s -> Lib_dep.Direct s :: acc) let of_library_stanza ~dir ~lib_config:({ Lib_config.has_native; ext_lib; ext_obj; _ } as lib_config) @@ -272,6 +263,7 @@ let of_library_stanza ~dir |Private _ -> None in + let requires = conf.buildable.libraries in { loc = conf.buildable.loc ; name ; kind = conf.kind @@ -289,7 +281,7 @@ let of_library_stanza ~dir ; jsoo_archive ; status ; virtual_deps = conf.virtual_deps - ; requires = Deps.of_lib_deps conf.buildable.libraries + ; requires ; ppx_runtime_deps = conf.ppx_runtime_libraries ; pps = Dune_file.Preprocess_map.pps conf.buildable.preprocess ; sub_systems = conf.sub_systems @@ -366,8 +358,6 @@ let map t ~f_path ~f_obj_dir = let map_path t ~f = map t ~f_path:f ~f_obj_dir:Fn.id -let set_obj_dir t obj_dir = { t with obj_dir } - let of_local = map ~f_path:Path.build ~f_obj_dir:Obj_dir.of_local let as_local_exn = diff --git a/src/dune/lib_info.mli b/src/dune/lib_info.mli index 1250794dd1b..c579e1add95 100644 --- a/src/dune/lib_info.mli +++ b/src/dune/lib_info.mli @@ -22,14 +22,6 @@ module Status : sig val project_name : t -> Dune_project.Name.t option end -module Deps : sig - type t = - | Simple of (Loc.t * Lib_name.t) list - | Complex of Dune_file.Lib_dep.t list - - val of_lib_deps : Dune_file.Lib_deps.t -> t -end - (** For values like modules that need to be evaluated to be fetched *) module Source : sig type 'a t = @@ -91,7 +83,7 @@ val implements : _ t -> (Loc.t * Lib_name.t) option val known_implementations : _ t -> (Loc.t * Lib_name.t) Variant.Map.t -val requires : _ t -> Deps.t +val requires : _ t -> Lib_dep.t list val ppx_runtime_deps : _ t -> (Loc.t * Lib_name.t) list @@ -120,9 +112,7 @@ val of_library_stanza : -> Dune_file.Library.t -> local -val user_written_deps : _ t -> Dune_file.Lib_deps.t - -val set_obj_dir : 'a t -> 'a Obj_dir.t -> 'a t +val user_written_deps : _ t -> Lib_dep.t list val of_local : local -> external_ @@ -130,17 +120,16 @@ val as_local_exn : external_ -> local val set_version : 'a t -> string option -> 'a t -val set_default_implementation : 'a t -> (Loc.t * Lib_name.t) option -> 'a t - -val set_implements : 'a t -> (Loc.t * Lib_name.t) option -> 'a t - -val set_orig_src_dir : 'a t -> 'a -> 'a t - -val set_ppx_runtime_deps : 'a t -> (Loc.t * Lib_name.t) list -> 'a t - -val set_sub_systems : 'a t -> Sub_system_info.t Sub_system_name.Map.t -> 'a t - -val set_foreign_objects : Path.t t -> Path.t list -> Path.t t +val for_dune_package : + Path.t t + -> ppx_runtime_deps:(Loc.t * Lib_name.t) list + -> requires:Lib_dep.t list + -> foreign_objects:Path.t list + -> obj_dir:Path.t Obj_dir.t + -> implements:(Loc.t * Lib_name.t) option + -> default_implementation:(Loc.t * Lib_name.t) option + -> sub_systems:Sub_system_info.t Sub_system_name.Map.t + -> Path.t t val map_path : 'a t -> f:('a -> 'a) -> 'a t @@ -156,7 +145,7 @@ val create : -> synopsis:string option -> main_module_name:Dune_file.Library.Main_module_name.t -> sub_systems:Sub_system_info.t Sub_system_name.Map.t - -> requires:Deps.t + -> requires:Lib_dep.t list -> foreign_objects:'a list Source.t -> plugins:'a list Mode.Dict.t -> archives:'a list Mode.Dict.t diff --git a/src/dune/toplevel.ml b/src/dune/toplevel.ml index 4f734d022e4..8f8e114656e 100644 --- a/src/dune/toplevel.ml +++ b/src/dune/toplevel.ml @@ -104,9 +104,8 @@ module Stanza = struct in Lib.DB.resolve_user_written_deps_for_exes (Scope.libs scope) [ (source.loc, source.name) ] - ( Dune_file.Lib_dep.Direct (source.loc, compiler_libs) - :: List.map toplevel.libraries ~f:(fun d -> Dune_file.Lib_dep.Direct d) - ) + ( Lib_dep.Direct (source.loc, compiler_libs) + :: List.map toplevel.libraries ~f:(fun d -> Lib_dep.Direct d) ) ~pps:[] ~allow_overlaps:false ~variants:toplevel.variants ~optional:false in diff --git a/src/dune_lang/decoder.ml b/src/dune_lang/decoder.ml index 5060a92dccd..4df4b2cb197 100644 --- a/src/dune_lang/decoder.ml +++ b/src/dune_lang/decoder.ml @@ -262,6 +262,15 @@ let plain_string f = |List (loc, _) -> User_error.raise ~loc [ Pp.text "Atom or quoted string expected" ]) +let filename = + plain_string (fun ~loc s -> + match s with + | "." + |".." -> + User_error.raise ~loc + [ Pp.textf "'.' and '..' are not valid filenames" ] + | fn -> fn) + let enter t = next_with_user_context (fun uc sexp -> match sexp with diff --git a/src/dune_lang/decoder.mli b/src/dune_lang/decoder.mli index 2f1fd9c3471..9b45b986499 100644 --- a/src/dune_lang/decoder.mli +++ b/src/dune_lang/decoder.mli @@ -158,6 +158,9 @@ val junk_everything : (unit, _) parser list. *) val plain_string : (loc:Loc.t -> string -> 'a) -> 'a t +(** A valid filename, i.e. a string other than "." or ".." *) +val filename : string t + val fix : ('a t -> 'a t) -> 'a t val located : ('a, 'k) parser -> (Loc.t * 'a, 'k) parser diff --git a/src/dune_lang/encoder.ml b/src/dune_lang/encoder.ml index dc4b579e8c9..08f0d0798f9 100644 --- a/src/dune_lang/encoder.ml +++ b/src/dune_lang/encoder.ml @@ -25,6 +25,8 @@ let array f a = list f (Array.to_list a) let sexp x = x +let constr s f x = pair string f (s, x) + let option f = function | None -> List [] | Some x -> List [ f x ] diff --git a/src/dune_lang/encoder.mli b/src/dune_lang/encoder.mli index 865ecdd0c1b..72f1375ee78 100644 --- a/src/dune_lang/encoder.mli +++ b/src/dune_lang/encoder.mli @@ -6,6 +6,8 @@ val sexp : T.t t val record : (string * T.t) list -> T.t +val constr : string -> 'a t -> 'a t + type field val field : diff --git a/test/blackbox-tests/dune.inc b/test/blackbox-tests/dune.inc index ce75fc5515a..66d964460c6 100644 --- a/test/blackbox-tests/dune.inc +++ b/test/blackbox-tests/dune.inc @@ -1386,6 +1386,14 @@ test-cases/quoting (progn (run %{exe:cram.exe} -test run.t) (diff? run.t run.t.corrected))))) +(alias + (name re-exported-deps) + (deps (package dune) (source_tree test-cases/re-exported-deps)) + (action + (chdir + test-cases/re-exported-deps + (progn (run %{exe:cram.exe} -test run.t) (diff? run.t run.t.corrected))))) + (alias (name reason) (deps (package dune) (source_tree test-cases/reason)) @@ -1952,6 +1960,7 @@ (alias project-root) (alias promote) (alias quoting) + (alias re-exported-deps) (alias reason) (alias redirections) (alias reporting-of-cycles) @@ -2147,6 +2156,7 @@ (alias project-root) (alias promote) (alias quoting) + (alias re-exported-deps) (alias redirections) (alias reporting-of-cycles) (alias rule-target-external) diff --git a/test/blackbox-tests/test-cases/findlib/run.t b/test/blackbox-tests/test-cases/findlib/run.t index 0f53ef231a4..df7cf0d412f 100644 --- a/test/blackbox-tests/test-cases/findlib/run.t +++ b/test/blackbox-tests/test-cases/findlib/run.t @@ -7,10 +7,10 @@ Reproduction case for #484. The error should point to src/dune $ dune build @install - File "src/dune", line 4, characters 14-15: + File "src/dune", line 4, characters 18-19: 4 | (libraries a b c)) - ^ - Error: Library "a" not found. + ^ + Error: Library "c" not found. Hint: try: dune external-lib-deps --missing @install [1] @@ -21,9 +21,9 @@ the code of dune more complicated to fix the hint. With dune and an explicit profile, it is the same: $ dune build --profile dev @install - File "src/dune", line 4, characters 14-15: + File "src/dune", line 4, characters 18-19: 4 | (libraries a b c)) - ^ - Error: Library "a" not found. + ^ + Error: Library "c" not found. Hint: try: dune external-lib-deps --missing --profile dev @install [1] diff --git a/test/blackbox-tests/test-cases/re-exported-deps/re-export-exe/dune b/test/blackbox-tests/test-cases/re-exported-deps/re-export-exe/dune new file mode 100644 index 00000000000..d3c3dd3266d --- /dev/null +++ b/test/blackbox-tests/test-cases/re-exported-deps/re-export-exe/dune @@ -0,0 +1,7 @@ +(library + (name foo) + (modules ())) + +(executable + (name bar) + (libraries (re_export foo))) diff --git a/test/blackbox-tests/test-cases/re-exported-deps/run.t b/test/blackbox-tests/test-cases/re-exported-deps/run.t new file mode 100644 index 00000000000..8f1c5d147ee --- /dev/null +++ b/test/blackbox-tests/test-cases/re-exported-deps/run.t @@ -0,0 +1,52 @@ +dependencies can be exported transitively: + $ dune exec ./foo.exe --root transitive + Entering directory 'transitive' + Entering directory 'transitive' + +transtive deps expressed in the dune-package + + $ dune build @install --root transitive + Entering directory 'transitive' + $ cat transitive/_build/install/default/lib/pkg/dune-package + (lang dune 2.0) + (name pkg) + (library + (name pkg.aaa) + (kind normal) + (archives (byte aaa/aaa.cma) (native aaa/aaa.cmxa)) + (plugins (byte aaa/aaa.cma) (native aaa/aaa.cmxs)) + (foreign_archives (native aaa/aaa$ext_lib)) + (requires pkg.ccc (re_export pkg.bbb)) + (main_module_name Aaa) + (modes byte native) + (modules (singleton (name Aaa) (obj_name aaa) (visibility public) (impl)))) + (library + (name pkg.bbb) + (kind normal) + (archives (byte bbb/bbb.cma) (native bbb/bbb.cmxa)) + (plugins (byte bbb/bbb.cma) (native bbb/bbb.cmxs)) + (foreign_archives (native bbb/bbb$ext_lib)) + (requires (re_export pkg.ccc)) + (main_module_name Bbb) + (modes byte native) + (modules (singleton (name Bbb) (obj_name bbb) (visibility public) (impl)))) + (library + (name pkg.ccc) + (kind normal) + (archives (byte ccc/ccc.cma) (native ccc/ccc.cmxa)) + (plugins (byte ccc/ccc.cma) (native ccc/ccc.cmxs)) + (foreign_archives (native ccc/ccc$ext_lib)) + (main_module_name Ccc) + (modes byte native) + (modules (singleton (name Ccc) (obj_name ccc) (visibility public) (impl)))) + +Re-exporting deps in executables isn't allowed + $ dune build --root re-export-exe @all + Entering directory 're-export-exe' + Info: Creating file dune-project with this contents: + | (lang dune 2.0) + File "dune", line 7, characters 13-22: + 7 | (libraries (re_export foo))) + ^^^^^^^^^ + Error: re_export is not allowed here + [1] diff --git a/test/blackbox-tests/test-cases/re-exported-deps/transitive/aaa.ml b/test/blackbox-tests/test-cases/re-exported-deps/transitive/aaa.ml new file mode 100644 index 00000000000..e69de29bb2d diff --git a/test/blackbox-tests/test-cases/re-exported-deps/transitive/bbb.ml b/test/blackbox-tests/test-cases/re-exported-deps/transitive/bbb.ml new file mode 100644 index 00000000000..e69de29bb2d diff --git a/test/blackbox-tests/test-cases/re-exported-deps/transitive/ccc.ml b/test/blackbox-tests/test-cases/re-exported-deps/transitive/ccc.ml new file mode 100644 index 00000000000..e69de29bb2d diff --git a/test/blackbox-tests/test-cases/re-exported-deps/transitive/dune b/test/blackbox-tests/test-cases/re-exported-deps/transitive/dune new file mode 100644 index 00000000000..a74bea59925 --- /dev/null +++ b/test/blackbox-tests/test-cases/re-exported-deps/transitive/dune @@ -0,0 +1,21 @@ +(library + (public_name pkg.aaa) + (name aaa) + (libraries (re_export bbb)) + (modules aaa)) + +(library + (public_name pkg.bbb) + (name bbb) + (libraries (re_export ccc)) + (modules bbb)) + +(library + (modules ccc) + (name ccc) + (public_name pkg.ccc)) + +(executable + (name foo) + (modules foo) + (libraries aaa)) diff --git a/test/blackbox-tests/test-cases/re-exported-deps/transitive/dune-project b/test/blackbox-tests/test-cases/re-exported-deps/transitive/dune-project new file mode 100644 index 00000000000..1569c930a16 --- /dev/null +++ b/test/blackbox-tests/test-cases/re-exported-deps/transitive/dune-project @@ -0,0 +1,4 @@ +(lang dune 2.0) + +(package + (name pkg)) diff --git a/test/blackbox-tests/test-cases/re-exported-deps/transitive/foo.ml b/test/blackbox-tests/test-cases/re-exported-deps/transitive/foo.ml new file mode 100644 index 00000000000..134b7c253af --- /dev/null +++ b/test/blackbox-tests/test-cases/re-exported-deps/transitive/foo.ml @@ -0,0 +1,3 @@ +module A = Aaa +module B = Bbb +module C = Ccc diff --git a/test/expect-tests/findlib_tests.ml b/test/expect-tests/findlib_tests.ml index 0b38bb6b0ae..5131086c225 100644 --- a/test/expect-tests/findlib_tests.ml +++ b/test/expect-tests/findlib_tests.ml @@ -24,9 +24,12 @@ let%expect_test _ = | Error _ -> assert false in (* "foo" should depend on "baz" *) - Dune_package.Lib.requires pkg - |> List.iter ~f:(fun (_, name) -> print_endline (Lib_name.to_string name)); - [%expect {|baz|}] + let info = Dune_package.Lib.info pkg in + let requires = Lib_info.requires info in + let dyn = Dyn.Encoder.list Lib_dep.to_dyn requires in + let pp = Dyn.pp dyn in + Format.printf "%a@." Pp.render_ignore_tags pp; + [%expect {|["baz"]|}] (* Meta parsing/simplification *)