Skip to content

Commit 13d0ec5

Browse files
authored
Merge pull request #1082 from rgrinberg/info-in-lib
Move info to lib
2 parents 385a3eb + 6eb2086 commit 13d0ec5

File tree

1 file changed

+29
-52
lines changed

1 file changed

+29
-52
lines changed

src/lib.ml

Lines changed: 29 additions & 52 deletions
Original file line numberDiff line numberDiff line change
@@ -221,26 +221,14 @@ module Id = struct
221221
end
222222

223223
type t =
224-
{ loc : Loc.t
224+
{ info : Info.t
225225
; name : string
226226
; unique_id : int
227-
; kind : Jbuild.Library.Kind.t
228-
; status : Status.t
229-
; src_dir : Path.t
230-
; obj_dir : Path.t
231-
; version : string option
232-
; synopsis : string option
233-
; archives : Path.t list Mode.Dict.t
234-
; plugins : Path.t list Mode.Dict.t
235-
; foreign_archives : Path.t list Mode.Dict.t
236-
; jsoo_runtime : Path.t list
237227
; requires : t list Or_exn.t
238228
; ppx_runtime_deps : t list Or_exn.t
239229
; pps : t list Or_exn.t
240230
; resolved_selects : Resolved_select.t list
241-
; optional : bool
242231
; user_written_deps : Jbuild.Lib_deps.t
243-
; dune_version : Syntax.Version.t option
244232
; (* This is mutable to avoid this error:
245233
246234
{[
@@ -340,24 +328,24 @@ let not_available ~loc reason fmt =
340328

341329
let name t = t.name
342330

343-
let kind t = t.kind
344-
let synopsis t = t.synopsis
345-
let archives t = t.archives
346-
let plugins t = t.plugins
347-
let jsoo_runtime t = t.jsoo_runtime
331+
let kind t = t.info.kind
332+
let synopsis t = t.info.synopsis
333+
let archives t = t.info.archives
334+
let plugins t = t.info.plugins
335+
let jsoo_runtime t = t.info.jsoo_runtime
348336
let unique_id t = t.unique_id
349337

350-
let dune_version t = t.dune_version
338+
let dune_version t = t.info.dune_version
351339

352-
let src_dir t = t.src_dir
353-
let obj_dir t = t.obj_dir
340+
let src_dir t = t.info.src_dir
341+
let obj_dir t = t.info.obj_dir
354342

355-
let is_local t = Path.is_managed t.obj_dir
343+
let is_local t = Path.is_managed t.info.obj_dir
356344

357-
let status t = t.status
345+
let status t = t.info.status
358346

359347
let package t =
360-
match t.status with
348+
match t.info.status with
361349
| Installed ->
362350
Some (Findlib.root_package_name t.name
363351
|> Package.Name.of_string)
@@ -367,7 +355,7 @@ let package t =
367355

368356
let to_id t : Id.t =
369357
{ unique_id = t.unique_id
370-
; path = t.src_dir
358+
; path = t.info.src_dir
371359
; name = t.name
372360
}
373361

@@ -405,7 +393,7 @@ module L = struct
405393
let c_include_paths ts ~stdlib_dir =
406394
let dirs =
407395
List.fold_left ts ~init:Path.Set.empty ~f:(fun acc t ->
408-
Path.Set.add acc t.src_dir)
396+
Path.Set.add acc t.info.src_dir)
409397
in
410398
Path.Set.remove dirs stdlib_dir
411399

@@ -415,7 +403,8 @@ module L = struct
415403
let link_flags ts ~mode ~stdlib_dir =
416404
Arg_spec.S
417405
(c_include_flags ts ~stdlib_dir ::
418-
List.map ts ~f:(fun t -> Arg_spec.Deps (Mode.Dict.get t.archives mode)))
406+
List.map ts ~f:(fun t ->
407+
Arg_spec.Deps (Mode.Dict.get t.info.archives mode)))
419408

420409
let compile_and_link_flags ~compile ~link ~mode ~stdlib_dir =
421410
let dirs =
@@ -426,15 +415,15 @@ module L = struct
426415
Arg_spec.S
427416
(to_iflags dirs ::
428417
List.map link ~f:(fun t ->
429-
Arg_spec.Deps (Mode.Dict.get t.archives mode)))
418+
Arg_spec.Deps (Mode.Dict.get t.info.archives mode)))
430419

431420
let jsoo_runtime_files ts =
432-
List.concat_map ts ~f:(fun t -> t.jsoo_runtime)
421+
List.concat_map ts ~f:(fun t -> t.info.jsoo_runtime)
433422

434423
let archive_files ts ~mode ~ext_lib =
435424
List.concat_map ts ~f:(fun t ->
436-
Mode.Dict.get t.archives mode @
437-
List.map (Mode.Dict.get t.foreign_archives mode)
425+
Mode.Dict.get t.info.archives mode @
426+
List.map (Mode.Dict.get t.info.foreign_archives mode)
438427
~f:(Path.extend_basename ~suffix:ext_lib))
439428

440429
let remove_dups l =
@@ -587,7 +576,7 @@ module Dep_stack = struct
587576
end
588577

589578
let check_private_deps ~(lib : lib) ~loc ~allow_private_deps =
590-
if (not allow_private_deps) && Status.is_private lib.status then
579+
if (not allow_private_deps) && Status.is_private lib.info.status then
591580
Result.Error (Error (
592581
Private_deps_not_allowed { private_dep = lib ; pd_loc = loc }))
593582
else
@@ -602,7 +591,7 @@ let already_in_table (info : Info.t) name x =
602591
Path.sexp_of_t x.path]
603592
| St_found t ->
604593
List [Sexp.unsafe_atom_of_string "Found";
605-
Path.sexp_of_t t.src_dir]
594+
Path.sexp_of_t t.info.src_dir]
606595
| St_not_found ->
607596
Sexp.unsafe_atom_of_string "Not_found"
608597
| St_hidden (_, { path; reason; _ }) ->
@@ -648,27 +637,15 @@ let rec instantiate db name (info : Info.t) ~stack ~hidden =
648637
let resolve (loc, name) =
649638
resolve_dep db name ~allow_private_deps ~loc ~stack in
650639
let t =
651-
{ loc = info.loc
640+
{ info = info
652641
; name = name
653642
; unique_id = id.unique_id
654-
; kind = info.kind
655-
; status = info.status
656-
; src_dir = info.src_dir
657-
; obj_dir = info.obj_dir
658-
; version = info.version
659-
; synopsis = info.synopsis
660-
; archives = info.archives
661-
; plugins = info.plugins
662-
; foreign_archives = info.foreign_archives
663-
; jsoo_runtime = info.jsoo_runtime
664643
; requires = requires
665644
; ppx_runtime_deps = ppx_runtime_deps
666645
; pps = pps
667646
; resolved_selects = resolved_selects
668-
; optional = info.optional
669647
; user_written_deps = Info.user_written_deps info
670648
; sub_systems = Sub_system_name.Map.empty
671-
; dune_version = info.dune_version
672649
}
673650
in
674651
t.sub_systems <-
@@ -688,7 +665,7 @@ let rec instantiate db name (info : Info.t) ~stack ~hidden =
688665
match hidden with
689666
| None -> St_found t
690667
| Some reason ->
691-
St_hidden (t, { name; path = t.src_dir; reason })
668+
St_hidden (t, { name; path = t.info.src_dir; reason })
692669
in
693670
Hashtbl.replace db.table ~key:name ~data:res;
694671
res
@@ -941,7 +918,7 @@ module Compile = struct
941918
; requires = t.requires >>= closure_with_overlap_checks db
942919
; resolved_selects = t.resolved_selects
943920
; pps = t.pps
944-
; optional = t.optional
921+
; optional = t.info.optional
945922
; user_written_deps = t.user_written_deps
946923
; sub_systems = t.sub_systems
947924
}
@@ -1161,9 +1138,9 @@ let report_lib_error ppf (e : Error.t) =
11611138
- %S in %s@,\
11621139
\ %a@,\
11631140
This cannot work.@\n"
1164-
lib1.name (Path.to_string_maybe_quoted lib1.src_dir)
1141+
lib1.name (Path.to_string_maybe_quoted lib1.info.src_dir)
11651142
Dep_path.Entries.pp rb1
1166-
lib2.name (Path.to_string_maybe_quoted lib2.src_dir)
1143+
lib2.name (Path.to_string_maybe_quoted lib2.info.src_dir)
11671144
Dep_path.Entries.pp rb2
11681145
| Overlap { in_workspace = lib1; installed = (lib2, rb2) } ->
11691146
Format.fprintf ppf
@@ -1172,8 +1149,8 @@ let report_lib_error ppf (e : Error.t) =
11721149
- %S in %s@,\
11731150
\ %a@,\
11741151
This is not allowed.@\n"
1175-
lib1.name (Path.to_string_maybe_quoted lib1.src_dir)
1176-
lib2.name (Path.to_string_maybe_quoted lib2.src_dir)
1152+
lib1.name (Path.to_string_maybe_quoted lib1.info.src_dir)
1153+
lib2.name (Path.to_string_maybe_quoted lib2.info.src_dir)
11771154
Dep_path.Entries.pp rb2
11781155
| No_solution_found_for_select { loc } ->
11791156
Format.fprintf ppf

0 commit comments

Comments
 (0)