Skip to content

Commit

Permalink
Add re_exports field to library
Browse files Browse the repository at this point in the history
This field allows libraries to re-export the interfaces of other
libraries

Signed-off-by: Rudi Grinberg <rudi.grinberg@gmail.com>
  • Loading branch information
rgrinberg committed Sep 3, 2019
1 parent 09eb562 commit 2b668c5
Show file tree
Hide file tree
Showing 9 changed files with 65 additions and 5 deletions.
8 changes: 7 additions & 1 deletion src/dune/dune_file.ml
Original file line number Diff line number Diff line change
Expand Up @@ -955,6 +955,7 @@ module Library = struct
; stdlib : Stdlib.t option
; special_builtin_support : Special_builtin_support.t option
; enabled_if : Blang.t
; re_exports : Predicate_lang.t
}

let decode =
Expand Down Expand Up @@ -1013,7 +1014,11 @@ module Library = struct
field_o "special_builtin_support"
( Syntax.since Stanza.syntax (1, 10)
>>> Special_builtin_support.decode )
and+ enabled_if = enabled_if ~since:(Some (1, 10)) in
and+ enabled_if = enabled_if ~since:(Some (1, 10))
and+ re_exports =
field "re_exports" ~default:Predicate_lang.false_
(Syntax.since Stanza.syntax (2, 0) >>> Predicate_lang.decode)
in
let wrapped =
Wrapped.make ~wrapped ~implements ~special_builtin_support
in
Expand Down Expand Up @@ -1138,6 +1143,7 @@ module Library = struct
; stdlib
; special_builtin_support
; enabled_if
; re_exports
} ))

let has_stubs t =
Expand Down
1 change: 1 addition & 0 deletions src/dune/dune_file.mli
Original file line number Diff line number Diff line change
Expand Up @@ -266,6 +266,7 @@ module Library : sig
; stdlib : Stdlib.t option
; special_builtin_support : Special_builtin_support.t option
; enabled_if : Blang.t
; re_exports : Predicate_lang.t
}

val has_stubs : t -> bool
Expand Down
12 changes: 11 additions & 1 deletion src/dune/dune_package.ml
Original file line number Diff line number Diff line change
Expand Up @@ -35,13 +35,14 @@ module Lib = struct
; modes : Mode.Dict.Set.t
; special_builtin_support :
Dune_file.Library.Special_builtin_support.t option
; re_exports : Lib_name.t list
}

let make ~loc ~kind ~name ~synopsis ~archives ~plugins ~foreign_objects
~foreign_archives ~jsoo_runtime ~main_module_name ~sub_systems ~requires
~ppx_runtime_deps ~implements ~default_implementation ~virtual_
~known_implementations ~modules ~modes ~version ~orig_src_dir ~obj_dir
~special_builtin_support =
~special_builtin_support ~re_exports =
let dir = Obj_dir.dir obj_dir in
let map_path p =
if Path.is_managed p then
Expand Down Expand Up @@ -74,6 +75,7 @@ module Lib = struct
; modes
; obj_dir
; special_builtin_support
; re_exports
}

let obj_dir t = t.obj_dir
Expand Down Expand Up @@ -112,6 +114,7 @@ module Lib = struct
; modules
; modes
; special_builtin_support
; re_exports
} =
let open Dune_lang.Encoder in
let no_loc f (_loc, x) = f x in
Expand Down Expand Up @@ -148,6 +151,7 @@ module Lib = struct
; field_o "special_builtin_support"
Dune_file.Library.Special_builtin_support.encode
special_builtin_support
; field_l "re_exports" Lib_name.encode re_exports
]
@ ( Sub_system_name.Map.to_list sub_systems
|> List.map ~f:(fun (name, (_ver, sexps)) ->
Expand Down Expand Up @@ -203,6 +207,9 @@ module Lib = struct
field_o "special_builtin_support"
( Syntax.since Stanza.syntax (1, 10)
>>> Dune_file.Library.Special_builtin_support.decode )
and+ re_exports =
field_l "re_exports"
(Syntax.since Stanza.syntax (2, 0) >>> Lib_name.decode)
in
let known_implementations =
Variant.Map.of_list_exn known_implementations
Expand Down Expand Up @@ -231,6 +238,7 @@ module Lib = struct
; modules
; modes
; special_builtin_support
; re_exports
})

let name t = t.name
Expand Down Expand Up @@ -278,6 +286,8 @@ module Lib = struct
let compare_name x y = Lib_name.compare x.name y.name

let wrapped t = Option.map t.modules ~f:Modules.wrapped

let re_exports t = t.re_exports
end

type 'sub_system t =
Expand Down
3 changes: 3 additions & 0 deletions src/dune/dune_package.mli
Original file line number Diff line number Diff line change
Expand Up @@ -58,6 +58,8 @@ module Lib : sig

val wrapped : _ t -> Wrapped.t option

val re_exports : _ t -> Lib_name.t list

val make :
loc:Loc.t
-> kind:Lib_kind.t
Expand All @@ -83,6 +85,7 @@ module Lib : sig
-> obj_dir:Path.t Obj_dir.t
-> special_builtin_support:
Dune_file.Library.Special_builtin_support.t option
-> re_exports:Lib_name.t list
-> 'a t

val set_subsystems : 'a t -> 'b Sub_system_name.Map.t -> 'b t
Expand Down
3 changes: 2 additions & 1 deletion src/dune/findlib/findlib.ml
Original file line number Diff line number Diff line change
Expand Up @@ -239,6 +239,7 @@ module Package = struct
else
discovered
in
let re_exports = [] in
Dune_package.Lib.make ~orig_src_dir:None ~loc ~kind:Normal ~name:(name t)
~synopsis:(description t) ~archives ~plugins:(plugins t)
~foreign_objects:[] ~foreign_archives:(Mode.Dict.make_both [])
Expand All @@ -248,7 +249,7 @@ module Package = struct
~virtual_:false ~implements:None ~known_implementations:Variant.Map.empty
~default_implementation:None ~modules:None
~main_module_name:None (* XXX remove *) ~version:(version t) ~modes
~obj_dir
~obj_dir ~re_exports
~special_builtin_support:
( (* findlib has been around for much longer than dune, so it is
acceptable to have a special case in dune for findlib. *)
Expand Down
19 changes: 18 additions & 1 deletion src/dune/lib.ml
Original file line number Diff line number Diff line change
Expand Up @@ -282,6 +282,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
Expand Down Expand Up @@ -1000,6 +1001,19 @@ end = struct
Dep_path.prepend_exn e (Library (src_dir, name)))
in
let requires = map_error requires in
let re_exports : t list Or_exn.t =
let plang =
match Lib_info.re_exports info with
| Local plang -> plang
| External_ l ->
String.Set.of_list_map l ~f:Lib_name.to_string
|> Predicate_lang.of_string_set
in
let+ requires = requires in
List.filter requires ~f:(fun lib ->
Predicate_lang.exec plang ~standard:Predicate_lang.empty
(Lib_name.to_string lib.name))
in
let ppx_runtime_deps = map_error ppx_runtime_deps in
let t =
{ info
Expand All @@ -1015,6 +1029,7 @@ end = struct
; default_implementation
; resolved_implementations
; stdlib_dir = db.stdlib_dir
; re_exports
}
in
t.sub_systems <-
Expand Down Expand Up @@ -1813,6 +1828,8 @@ let to_dune_lib ({ name; info; _ } as lib) ~modules ~foreign_objects ~dir =
use_public_name ~info_field:(Lib_info.implements info)
~lib_field:(implements lib)
in
let* re_exports = lib.re_exports in
let re_exports = List.map ~f:(fun t -> t.name) re_exports in
let+ default_implementation =
use_public_name
~info_field:(Lib_info.default_implementation info)
Expand All @@ -1827,7 +1844,7 @@ let to_dune_lib ({ name; info; _ } as lib) ~modules ~foreign_objects ~dir =
~modules:(Some modules)
~main_module_name:(Result.ok_exn (main_module_name lib))
~sub_systems:(Sub_system.dump_config lib)
~special_builtin_support
~special_builtin_support ~re_exports

module Local : sig
type t = private lib
Expand Down
3 changes: 2 additions & 1 deletion src/dune/lib.mli
Original file line number Diff line number Diff line change
Expand Up @@ -116,7 +116,8 @@ module Compile : sig
(** Return the list of dependencies needed for linking this library/exe *)
val requires_link : t -> L.t Or_exn.t Lazy.t

(** Dependencies listed by the user + runtime dependencies from ppx *)
(** Dependencies listed by the user + runtime dependencies from ppx +
exported dependencies *)
val direct_requires : t -> L.t Or_exn.t

module Resolved_select : sig
Expand Down
13 changes: 13 additions & 0 deletions src/dune/lib_info.ml
Original file line number Diff line number Diff line change
Expand Up @@ -59,6 +59,12 @@ module Source = struct
| External a -> External (f a)
end

module Re_exports = struct
type t =
| Local of Predicate_lang.t
| External_ of Lib_name.t list
end

module Enabled_status = struct
type t =
| Normal
Expand Down Expand Up @@ -99,6 +105,7 @@ type 'path t =
; modes : Mode.Dict.Set.t
; special_builtin_support :
Dune_file.Library.Special_builtin_support.t option
; re_exports : Re_exports.t
}

let name t = t.name
Expand Down Expand Up @@ -161,6 +168,8 @@ let orig_src_dir t = t.orig_src_dir

let best_src_dir t = Option.value ~default:t.src_dir t.orig_src_dir

let re_exports t = t.re_exports

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 ->
Expand Down Expand Up @@ -255,6 +264,7 @@ let of_library_stanza ~dir
|Private _ ->
None
in
let re_exports = Re_exports.Local conf.re_exports in
{ loc = conf.buildable.loc
; name
; kind = conf.kind
Expand Down Expand Up @@ -286,6 +296,7 @@ let of_library_stanza ~dir
; modes
; wrapped = Some conf.wrapped
; special_builtin_support = conf.special_builtin_support
; re_exports
}

let of_dune_lib dp =
Expand All @@ -303,6 +314,7 @@ let of_dune_lib dp =
|> Option.map ~f:(fun w -> Dune_file.Library.Inherited.This w)
in
let obj_dir = Lib.obj_dir dp in
let re_exports = Re_exports.External_ (Lib.re_exports dp) in
{ loc = Lib.loc dp
; name = Lib.name dp
; kind = Lib.kind dp
Expand Down Expand Up @@ -334,6 +346,7 @@ let of_dune_lib dp =
; modes = Lib.modes dp
; wrapped
; special_builtin_support = Lib.special_builtin_support dp
; re_exports
}

type external_ = Path.t t
Expand Down
8 changes: 8 additions & 0 deletions src/dune/lib_info.mli
Original file line number Diff line number Diff line change
Expand Up @@ -37,6 +37,12 @@ module Source : sig
| External of 'a
end

module Re_exports : sig
type t =
| Local of Predicate_lang.t
| External_ of Lib_name.t list
end

module Enabled_status : sig
type t =
| Normal
Expand Down Expand Up @@ -105,6 +111,8 @@ val orig_src_dir : 'path t -> 'path option

val version : _ t -> string option

val re_exports : _ t -> Re_exports.t

(** Directory where the source files for the library are located. Returns the
original src dir when it exists *)
val best_src_dir : 'path t -> 'path
Expand Down

0 comments on commit 2b668c5

Please sign in to comment.