Skip to content

Commit

Permalink
Add opaque property to Lib.t
Browse files Browse the repository at this point in the history
For now this is just set based on the profile

Signed-off-by: Rudi Grinberg <rudi.grinberg@gmail.com>
  • Loading branch information
rgrinberg committed Aug 1, 2018
1 parent 6d782c9 commit c529cf0
Show file tree
Hide file tree
Showing 5 changed files with 20 additions and 6 deletions.
13 changes: 10 additions & 3 deletions src/lib.ml
Original file line number Diff line number Diff line change
Expand Up @@ -63,6 +63,7 @@ module Info = struct
; pps : (Loc.t * Jbuild.Pp.t) list
; optional : bool
; virtual_deps : (Loc.t * string) list
; opaque : bool
; dune_version : Syntax.Version.t option
; sub_systems : Jbuild.Sub_system_info.t Sub_system_name.Map.t
}
Expand All @@ -72,7 +73,7 @@ module Info = struct
~init:(Deps.to_lib_deps t.requires)
~f:(fun acc s -> Jbuild.Lib_dep.Direct s :: acc)

let of_library_stanza ~dir (conf : Jbuild.Library.t) =
let of_library_stanza ~dir ~opaque (conf : Jbuild.Library.t) =
let archive_file ext = Path.relative dir (conf.name ^ ext) in
let archive_files ~f_ext =
Mode.Dict.of_func (fun ~mode -> [archive_file (f_ext mode)])
Expand Down Expand Up @@ -116,6 +117,7 @@ module Info = struct
; pps = Jbuild.Preprocess_map.pps conf.buildable.preprocess
; sub_systems = conf.sub_systems
; dune_version = Some conf.dune_version
; opaque
}

let of_findlib_package pkg =
Expand All @@ -142,6 +144,7 @@ module Info = struct
; virtual_deps = []
; optional = false
; status = Installed
; opaque = false
; (* We don't know how these are named for external libraries *)
foreign_archives = Mode.Dict.make_both []
; sub_systems = sub_systems
Expand Down Expand Up @@ -240,6 +243,7 @@ type t =
; resolved_selects : Resolved_select.t list
; optional : bool
; user_written_deps : Jbuild.Lib_deps.t
; opaque : bool
; dune_version : Syntax.Version.t option
; (* This is mutable to avoid this error:
Expand Down Expand Up @@ -356,6 +360,8 @@ let is_local t = Path.is_managed t.obj_dir

let status t = t.status

let opaque t = t.opaque

let package t =
match t.status with
| Installed ->
Expand Down Expand Up @@ -661,6 +667,7 @@ let rec instantiate db name (info : Info.t) ~stack ~hidden =
; plugins = info.plugins
; foreign_archives = info.foreign_archives
; jsoo_runtime = info.jsoo_runtime
; opaque = info.opaque
; requires = requires
; ppx_runtime_deps = ppx_runtime_deps
; pps = pps
Expand Down Expand Up @@ -980,10 +987,10 @@ module DB = struct
; all = Lazy.from_fun all
}

let create_from_library_stanzas ?parent stanzas =
let create_from_library_stanzas ?parent ~opaque stanzas =
let map =
List.concat_map stanzas ~f:(fun (dir, (conf : Jbuild.Library.t)) ->
let info = Info.of_library_stanza ~dir conf in
let info = Info.of_library_stanza ~dir ~opaque conf in
match conf.public with
| None ->
[(conf.name, Resolve_result.Found info)]
Expand Down
6 changes: 5 additions & 1 deletion src/lib.mli
Original file line number Diff line number Diff line change
Expand Up @@ -26,6 +26,8 @@ val archives : t -> Path.t list Mode.Dict.t
val plugins : t -> Path.t list Mode.Dict.t
val jsoo_runtime : t -> Path.t list

val opaque : t -> bool

val dune_version : t -> Syntax.Version.t option

(** A unique integer identifier. It is only unique for the duration of
Expand Down Expand Up @@ -105,11 +107,12 @@ module Info : sig
; pps : (Loc.t * Jbuild.Pp.t) list
; optional : bool
; virtual_deps : (Loc.t * string) list
; opaque : bool
; dune_version : Syntax.Version.t option
; sub_systems : Jbuild.Sub_system_info.t Sub_system_name.Map.t
}

val of_library_stanza : dir:Path.t -> Jbuild.Library.t -> t
val of_library_stanza : dir:Path.t -> opaque:bool -> Jbuild.Library.t -> t
val of_findlib_package : Findlib.Package.t -> t
end

Expand Down Expand Up @@ -257,6 +260,7 @@ module DB : sig
(** Create a database from a list of library stanzas *)
val create_from_library_stanzas
: ?parent:t
-> opaque:bool
-> (Path.t * Jbuild.Library.t) list
-> t

Expand Down
4 changes: 2 additions & 2 deletions src/scope.ml
Original file line number Diff line number Diff line change
Expand Up @@ -50,7 +50,7 @@ module DB = struct
(Project_name_map.keys t.by_name)
]

let create ~projects ~context ~installed_libs internal_libs =
let create ~projects ~context ~opaque ~installed_libs internal_libs =
let projects_by_name =
List.map projects ~f:(fun (project : Dune_project.t) ->
(project.name, project))
Expand Down Expand Up @@ -119,7 +119,7 @@ module DB = struct
let project = Option.value_exn project in
let libs = Option.value libs ~default:[] in
let db =
Lib.DB.create_from_library_stanzas libs ~parent:public_libs
Lib.DB.create_from_library_stanzas libs ~parent:public_libs ~opaque
in
let root = Path.append_local build_context_dir project.root in
Some { project; db; root })
Expand Down
1 change: 1 addition & 0 deletions src/scope.mli
Original file line number Diff line number Diff line change
Expand Up @@ -24,6 +24,7 @@ module DB : sig
val create
: projects:Dune_project.t list
-> context:string
-> opaque:bool
-> installed_libs:Lib.DB.t
-> (Path.t * Jbuild.Library.t) list
-> t * Lib.DB.t
Expand Down
2 changes: 2 additions & 0 deletions src/super_context.ml
Original file line number Diff line number Diff line change
Expand Up @@ -506,9 +506,11 @@ let create
| Library lib -> Some (ctx_dir, lib)
| _ -> None))
in
let opaque = context.profile = "dev" in
let scopes, public_libs =
Scope.DB.create
~projects
~opaque
~context:context.name
~installed_libs
internal_libs
Expand Down

0 comments on commit c529cf0

Please sign in to comment.