Skip to content

Commit

Permalink
Remove opaque from Lib.t
Browse files Browse the repository at this point in the history
Only use Compilation_context.t for controlling this

Signed-off-by: Rudi Grinberg <rudi.grinberg@gmail.com>
  • Loading branch information
rgrinberg committed Aug 2, 2018
1 parent 718a1bd commit 0638a77
Show file tree
Hide file tree
Showing 7 changed files with 22 additions and 38 deletions.
20 changes: 11 additions & 9 deletions src/compilation_context.ml
Original file line number Diff line number Diff line change
Expand Up @@ -5,7 +5,7 @@ module SC = Super_context
module Includes = struct
type t = string list Arg_spec.t Cm_kind.Dict.t

let make sctx ~requires : _ Cm_kind.Dict.t =
let make sctx ~opaque ~requires : _ Cm_kind.Dict.t =
match requires with
| Error exn -> Cm_kind.Dict.make_all (Arg_spec.Dyn (fun _ -> raise exn))
| Ok libs ->
Expand All @@ -22,13 +22,15 @@ module Includes = struct
Arg_spec.S
[ iflags
; Hidden_deps
( libs
|> List.map ~f:(fun lib ->
(lib, if Lib.opaque lib then
".cmi"
else
".cmi-and-.cmx"))
|> SC.Libs.file_deps_with_exts sctx
( if opaque then
List.map libs ~f:(fun lib ->
(lib, if Lib.is_local lib then
".cmi"
else
".cmi-and-.cmx"))
|> SC.Libs.file_deps_with_exts sctx
else
SC.Libs.file_deps sctx libs ~ext:".cmi-and-.cmx"
)
]
in
Expand Down Expand Up @@ -89,7 +91,7 @@ let create ~super_context ~scope ~dir ?(dir_kind=File_tree.Dune_file.Kind.Dune)
; lib_interface_module
; flags
; requires
; includes = Includes.make super_context ~requires
; includes = Includes.make super_context ~opaque ~requires
; preprocessing
; no_keep_locs
; opaque
Expand Down
7 changes: 4 additions & 3 deletions src/gen_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -17,6 +17,8 @@ module Gen(P : Install_rules.Params) = struct
let sctx = P.sctx
let ctx = SC.context sctx

let opaque = ctx.profile = "dev"

(* +-----------------------------------------------------------------+
| Library stuff |
+-----------------------------------------------------------------+ *)
Expand Down Expand Up @@ -199,7 +201,7 @@ module Gen(P : Install_rules.Params) = struct
~requires
~preprocessing:pp
~no_keep_locs:lib.no_keep_locs
~opaque:(Lib.Compile.opaque compile_info)
~opaque
in

let dep_graphs = Ocamldep.rules cctx in
Expand Down Expand Up @@ -521,7 +523,7 @@ module Gen(P : Install_rules.Params) = struct
~flags
~requires
~preprocessing:pp
~opaque:(Lib.Compile.opaque compile_info)
~opaque
in

Exe.build_and_link_many cctx
Expand All @@ -545,7 +547,6 @@ module Gen(P : Install_rules.Params) = struct
exes.buildable.libraries
~pps:(Jbuild.Preprocess_map.pps exes.buildable.preprocess)
~allow_overlaps:exes.buildable.allow_overlapping_dependencies
~opaque:(ctx.profile = "dev")
in
SC.Libs.gen_select_rules sctx compile_info ~dir;
SC.Libs.with_lib_deps sctx compile_info ~dir
Expand Down
17 changes: 4 additions & 13 deletions src/lib.ml
Original file line number Diff line number Diff line change
Expand Up @@ -63,7 +63,6 @@ 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 @@ -73,7 +72,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 ~opaque (conf : Jbuild.Library.t) =
let of_library_stanza ~dir (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 @@ -117,7 +116,6 @@ 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 @@ -144,7 +142,6 @@ 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 @@ -338,8 +335,6 @@ let plugins t = t.info.plugins
let jsoo_runtime t = t.info.jsoo_runtime
let unique_id t = t.unique_id

let opaque t = t.info.opaque

let dune_version t = t.info.dune_version

let src_dir t = t.info.src_dir
Expand Down Expand Up @@ -914,7 +909,6 @@ module Compile = struct
; pps : t list Or_exn.t
; resolved_selects : Resolved_select.t list
; optional : bool
; opaque : bool
; user_written_deps : Jbuild.Lib_deps.t
; sub_systems : Sub_system0.Instance.t Lazy.t Sub_system_name.Map.t
}
Expand All @@ -927,7 +921,6 @@ module Compile = struct
; optional = t.info.optional
; user_written_deps = t.user_written_deps
; sub_systems = t.sub_systems
; opaque = t.info.opaque
}

let direct_requires t = t.direct_requires
Expand All @@ -936,7 +929,6 @@ module Compile = struct
let pps t = t.pps
let optional t = t.optional
let user_written_deps t = t.user_written_deps
let opaque t = t.opaque
let sub_systems t =
Sub_system_name.Map.values t.sub_systems
|> List.map ~f:(fun (lazy (Sub_system0.Instance.T ((module M), t))) ->
Expand Down Expand Up @@ -965,10 +957,10 @@ module DB = struct
; all = Lazy.from_fun all
}

let create_from_library_stanzas ?parent ~opaque stanzas =
let create_from_library_stanzas ?parent stanzas =
let map =
List.concat_map stanzas ~f:(fun (dir, (conf : Jbuild.Library.t)) ->
let info = Info.of_library_stanza ~dir ~opaque conf in
let info = Info.of_library_stanza ~dir conf in
match conf.public with
| None ->
[(conf.name, Resolve_result.Found info)]
Expand Down Expand Up @@ -1063,7 +1055,7 @@ module DB = struct
let t = Option.some_if (not allow_overlaps) t in
Compile.for_lib t lib

let resolve_user_written_deps t ?(allow_overlaps=false) ~opaque deps ~pps =
let resolve_user_written_deps t ?(allow_overlaps=false) deps ~pps =
let res, pps, resolved_selects =
resolve_user_deps t (Info.Deps.of_lib_deps deps) ~pps
~stack:Dep_stack.empty ~allow_private_deps:true
Expand All @@ -1081,7 +1073,6 @@ module DB = struct
; optional = false
; user_written_deps = deps
; sub_systems = Sub_system_name.Map.empty
; opaque
}

let resolve_pps t pps =
Expand Down
9 changes: 1 addition & 8 deletions src/lib.mli
Original file line number Diff line number Diff line change
Expand Up @@ -26,8 +26,6 @@ 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 @@ -107,12 +105,11 @@ 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 -> opaque:bool -> Jbuild.Library.t -> t
val of_library_stanza : dir:Path.t -> Jbuild.Library.t -> t
val of_findlib_package : Findlib.Package.t -> t
end

Expand Down Expand Up @@ -221,8 +218,6 @@ module Compile : sig
val optional : t -> bool
val user_written_deps : t -> Jbuild.Lib_deps.t

val opaque : t -> bool

(** Sub-systems used in this compilation context *)
val sub_systems : t -> sub_system list
end
Expand Down Expand Up @@ -262,7 +257,6 @@ 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 Expand Up @@ -295,7 +289,6 @@ module DB : sig
val resolve_user_written_deps
: t
-> ?allow_overlaps:bool
-> opaque:bool
-> Jbuild.Lib_dep.t list
-> pps:(Loc.t * Jbuild.Pp.t) list
-> Compile.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 ~opaque ~installed_libs internal_libs =
let create ~projects ~context ~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 ~opaque
Lib.DB.create_from_library_stanzas libs ~parent:public_libs
in
let root = Path.append_local build_context_dir project.root in
Some { project; db; root })
Expand Down
1 change: 0 additions & 1 deletion src/scope.mli
Original file line number Diff line number Diff line change
Expand Up @@ -24,7 +24,6 @@ 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: 0 additions & 2 deletions src/super_context.ml
Original file line number Diff line number Diff line change
Expand Up @@ -506,11 +506,9 @@ 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 0638a77

Please sign in to comment.