Skip to content

Commit

Permalink
{T,Optt}opdirs: add load_lib function to API.
Browse files Browse the repository at this point in the history
This will be used by {T,Opt}opmain. The signature of this function is
largely suboptimal. But we take care not to introduce any new type
dependency like Lib.Name.t because this module is used and visible by
downstream packages while those may not have have access to
`compiler-libs`'s module because of the expunge process. Maybe once
all this will be improved see ocaml#7589.
  • Loading branch information
dbuenzli committed Sep 29, 2020
1 parent 150e108 commit 94448bb
Show file tree
Hide file tree
Showing 4 changed files with 23 additions and 0 deletions.
7 changes: 7 additions & 0 deletions toplevel/opttopdirs.ml
Original file line number Diff line number Diff line change
Expand Up @@ -136,6 +136,13 @@ let dir_require ppf name = match Lib.Name.of_string name with
let () =
Hashtbl.add directive_table "require" (Directive_string (dir_require std_out))

let load_lib ppf name = match Lib.Name.of_string name with
| Error e -> fprintf ppf "@[%s@]@." e; false
| Ok _n ->
(* We need to implement the Dynlink lib loading API support *)
fprintf ppf "load_lib is not implemented yet (TODO)";
false

(* Load commands from a file *)

let dir_use ppf name = ignore(Opttoploop.use_file ppf name)
Expand Down
5 changes: 5 additions & 0 deletions toplevel/opttopdirs.mli
Original file line number Diff line number Diff line change
Expand Up @@ -44,3 +44,8 @@ val assume_lib_loaded : string -> (unit, string) result
(** [assume_lib_loaded n] assumes library name [n] is loaded. This
will prevent [n] from being looked up. An error is returned if
[n] is not a valid library name. *)

val load_lib : formatter -> string -> bool
(** [load_lib ppf n] loads library named [n] printing errors on [ppf]
and returns [true] if there was no error (including if [n] as
already loaded) and [false] otherwise. *)
6 changes: 6 additions & 0 deletions toplevel/topdirs.ml
Original file line number Diff line number Diff line change
Expand Up @@ -299,6 +299,12 @@ let assume_lib_loaded n = match Lib.Name.of_string n with
| Ok n -> loaded_libs := Lib.Name.Set.add n !loaded_libs; Ok ()

let loaded_libs () = Lib.Name.Set.to_string_set !loaded_libs
let load_lib ppf name = match Lib.Name.of_string name with
| Error e -> fprintf ppf "@[%s@]@." e; false
| Ok n ->
match load_lib ppf ~from_file:None n with
| exception Load_failed -> false
| _ -> true

(* Load commands from a file *)

Expand Down
5 changes: 5 additions & 0 deletions toplevel/topdirs.mli
Original file line number Diff line number Diff line change
Expand Up @@ -48,3 +48,8 @@ val assume_lib_loaded : string -> (unit, string) result
(** [assume_lib_loaded n] assumes library name [n] is loaded. This
will prevent [n] from being looked up. An error is returned if
[n] is not a valid library name. *)

val load_lib : formatter -> string -> bool
(** [load_lib ppf n] loads library named [n] printing errors on [ppf]
and returns [true] if there was no error (including if [n] as
already loaded) and [false] otherwise. *)

0 comments on commit 94448bb

Please sign in to comment.