Skip to content

Commit 769917f

Browse files
panglesdjonludlam
authored andcommitted
Driver: add interface to the Library_names module (+ improvements)
Removed unused parts: - The unused list of module field - The code to compute it - The unused type `t` Signed-off-by: Paul-Elliot <[email protected]>
1 parent 1a91c64 commit 769917f

File tree

3 files changed

+12
-94
lines changed

3 files changed

+12
-94
lines changed

src/driver/library_names.ml

Lines changed: 5 additions & 92 deletions
Original file line numberDiff line numberDiff line change
@@ -3,20 +3,14 @@
33
1. parse the META file of the package with ocamlfind to see which libraries
44
exist and what their archive name (.cma filename) is.
55
6-
2. use ocamlobjinfo to get a list of all modules within the archives.
6+
2. use ocamlobjinfo to get a list of all modules within the archives. EDIT:
7+
it seems this step is now skipped.
78
89
This code assumes that the META file lists for every library an archive
910
[archive_name], and that for this cma archive exists a corresponsing
1011
[archive_name].ocamlobjinfo file. *)
1112

12-
type library = {
13-
name : string;
14-
archive_name : string;
15-
mutable modules : string list;
16-
dir : string option;
17-
}
18-
19-
type t = { libraries : library list }
13+
type library = { name : string; archive_name : string; dir : string option }
2014

2115
let read_libraries_from_pkg_defs ~library_name pkg_defs =
2216
try
@@ -31,12 +25,12 @@ let read_libraries_from_pkg_defs ~library_name pkg_defs =
3125
else cma_filename
3226
in
3327
if String.length archive_name > 0 then
34-
[ { name = library_name; archive_name; modules = []; dir } ]
28+
[ { name = library_name; archive_name; dir } ]
3529
else []
3630
with Not_found -> []
3731

3832
let process_meta_file file =
39-
let _ = Format.eprintf "process_meta_file: %s\n%!" (Fpath.to_string file) in
33+
let () = Format.eprintf "process_meta_file: %s\n%!" (Fpath.to_string file) in
4034
let ic = open_in (Fpath.to_string file) in
4135
let meta = Fl_metascanner.parse ic in
4236
let base_library_name =
@@ -72,84 +66,3 @@ let process_meta_file file =
7266
|> List.filter is_not_private
7367
in
7468
libraries
75-
76-
let process_ocamlobjinfo_file ~(libraries : library list) file =
77-
let _ =
78-
Format.eprintf "process_ocamlobjinfo_file: %s\n%!" (Fpath.to_string file)
79-
in
80-
let ic = open_in (Fpath.to_string file) in
81-
let lines = Util.lines_of_channel ic in
82-
let affix = "Unit name: " in
83-
let len = String.length affix in
84-
close_in ic;
85-
let units =
86-
List.concat_map
87-
(fun line ->
88-
if Astring.String.is_prefix ~affix line then
89-
[ String.sub line len (String.length line - len) ]
90-
else [])
91-
lines
92-
in
93-
let _, archive_name = Fpath.split_base file in
94-
let archive_name = archive_name |> Fpath.rem_ext |> Fpath.to_string in
95-
let _ =
96-
Format.eprintf "trying to look up archive_name: %s\nunits: %s\n%!"
97-
archive_name (String.concat "," units)
98-
in
99-
try
100-
let library =
101-
List.find (fun l -> l.archive_name = archive_name) libraries
102-
in
103-
library.modules <- library.modules @ units
104-
with Not_found ->
105-
Format.eprintf "failed to find archive_name: %s\n%!" archive_name;
106-
()
107-
108-
(* let get_libraries package =
109-
let path = package in
110-
let maybe_meta_files =
111-
Bos.OS.Dir.fold_contents ~dotfiles:true
112-
(fun p acc ->
113-
let is_meta = p |> Fpath.basename = "META" in
114-
if is_meta then p :: acc else acc)
115-
[] path
116-
in
117-
118-
match maybe_meta_files with
119-
| Error (`Msg msg) ->
120-
failwith
121-
("FIXME: error traversing directories to find the META files: " ^ msg)
122-
| Ok meta_files -> (
123-
let libraries =
124-
meta_files |> List.map process_meta_file |> List.flatten
125-
in
126-
127-
let _ =
128-
Format.eprintf "found archive_names: [%s]\n%!"
129-
(String.concat ", "
130-
(List.map (fun (l : library) -> l.archive_name) libraries))
131-
in
132-
133-
let maybe_ocamlobjinfo_files =
134-
Bos.OS.Dir.fold_contents ~dotfiles:true
135-
(fun p acc ->
136-
let is_ocamlobjinfo = Fpath.get_ext p = ".ocamlobjinfo" in
137-
if is_ocamlobjinfo then p :: acc else acc)
138-
[] path
139-
in
140-
match maybe_ocamlobjinfo_files with
141-
| Error (`Msg msg) ->
142-
failwith
143-
("FIXME: error traversing directories to find the ocamlobjinfo \
144-
files: " ^ msg)
145-
| Ok ocamlobjinfo_files ->
146-
List.iter (process_ocamlobjinfo_file ~libraries) ocamlobjinfo_files;
147-
let _ =
148-
Format.eprintf "found archive_names: [%s]\n%!"
149-
(String.concat ", "
150-
(List.map
151-
(fun (l : library) ->
152-
l.archive_name ^ "/" ^ String.concat "," l.modules)
153-
libraries))
154-
in
155-
{ libraries }) *)

src/driver/library_names.mli

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,5 @@
1+
type library = { name : string; archive_name : string; dir : string option }
2+
3+
val process_meta_file : Fpath.t -> library list
4+
(** From a path to a [Meta] file, returns the list of libraries defined in this
5+
file. *)

src/driver/voodoo.ml

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -134,7 +134,7 @@ let process_package pkg =
134134
(fun k v -> Logs.debug (fun m -> m "%s,%s\n%!" k v))
135135
libname_of_archive;
136136
Some
137-
(List.map
137+
(List.concat_map
138138
(fun directory ->
139139
Format.eprintf "Processing directory: %a\n%!" Fpath.pp directory;
140140
Packages.Lib.v (top_dir pkg) libname_of_archive pkg.name
@@ -168,7 +168,7 @@ let process_package pkg =
168168
in
169169
Printf.eprintf "Found %d metas" (List.length metas);
170170
let mld_odoc_dir = Packages.parent_of_pkg (top_dir pkg) in
171-
let libraries = List.flatten (List.flatten libraries) in
171+
let libraries = List.flatten libraries in
172172
let libraries = List.flatten extra_libraries @ libraries in
173173
{
174174
Packages.name = pkg.name;

0 commit comments

Comments
 (0)