-
Notifications
You must be signed in to change notification settings - Fork 409
Commit
This commit does not belong to any branch on this repository, and may belong to a fork outside of the repository.
[wip] [coq] Allow dependencies and composition with local Coq libraries.
We support simple composition of Coq libraries using the `(theories ...)` field. This is a work-in-progress and I am submitting to gather feedback. - Todo Before Merge: + validation of library names must be adapted to Coq's conventions. + review error handling + add tests - Would be nice to have / next PRs: + Closure of theory dependencies. + Allow to depend on libraries installed globally. Signed-off-by: Emilio Jesus Gallego Arias <[email protected]>
- Loading branch information
Showing
12 changed files
with
207 additions
and
47 deletions.
There are no files selected for viewing
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,49 @@ | ||
(* This file is licensed under The MIT License *) | ||
(* (c) MINES ParisTech 2018-2019 *) | ||
(* Written by: Emilio Jesús Gallego Arias *) | ||
|
||
open! Stdune | ||
|
||
type t = | ||
{ name : Lib_name.t | ||
; src_root : Path.t | ||
; obj_root : Path.t | ||
; package : Package.Name.t option | ||
} | ||
|
||
let name l = l.name | ||
let src_root l = l.src_root | ||
let obj_root l = l.obj_root | ||
let package l = l.package | ||
|
||
module DB = struct | ||
|
||
type nonrec t = t Lib_name.Map.t | ||
|
||
let create_from_stanza (dir, s : Path.t * Dune_file.Coq.t) = | ||
let name = Dune_file.Coq.best_name s in | ||
name, | ||
{ name | ||
; obj_root = dir | ||
; src_root = dir | ||
; package = Option.map s.public ~f:(fun p -> p.package.name) | ||
} | ||
|
||
(* XXX: Error handling: register errors and printers *) | ||
let create_from_coqlib_stanzas sl = | ||
match Lib_name.Map.of_list_map ~f:create_from_stanza sl with | ||
| Ok m -> m | ||
| Error (name, _w1, w2) -> | ||
let loc = (snd w2).loc in | ||
raise (Errors.exnf loc "Duplicate theory name: %a" Lib_name.pp name) | ||
|
||
let resolve db (loc,name) = | ||
match Lib_name.Map.find db name with | ||
| None -> | ||
Error (Errors.exnf loc "Theory %a not found" Lib_name.pp name) | ||
| Some s -> Ok s | ||
|
||
let find_many t ~loc = | ||
Result.List.map ~f:(fun name -> resolve t (loc, name)) | ||
|
||
end |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,33 @@ | ||
(* This file is licensed under The MIT License *) | ||
(* (c) MINES ParisTech 2018-2019 *) | ||
(* Written by: Emilio Jesús Gallego Arias *) | ||
|
||
open! Stdune | ||
|
||
type t | ||
|
||
val name : t -> Lib_name.t | ||
|
||
val src_root : t -> Path.t | ||
val obj_root : t -> Path.t | ||
|
||
val package : t -> Package.Name.t option | ||
|
||
module DB : sig | ||
|
||
type lib | ||
type t | ||
|
||
val create_from_coqlib_stanzas | ||
: (Path.t * Dune_file.Coq.t) list | ||
-> t | ||
|
||
val find_many | ||
: t | ||
-> loc:Loc.t | ||
-> Lib_name.t list | ||
-> lib list Or_exn.t | ||
|
||
val resolve : t -> Loc.t * Lib_name.t -> lib Or_exn.t | ||
|
||
end with type lib := t |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Oops, something went wrong.