Skip to content

Commit

Permalink
Allow to set per-package information
Browse files Browse the repository at this point in the history
Signed-off-by: Nicolás Ojeda Bär <n.oje.bar@gmail.com>
  • Loading branch information
nojb committed Oct 19, 2019
1 parent 3b88bbb commit 582a2ca
Show file tree
Hide file tree
Showing 5 changed files with 200 additions and 145 deletions.
120 changes: 8 additions & 112 deletions src/dune/dune_project.ml
Original file line number Diff line number Diff line change
Expand Up @@ -139,37 +139,6 @@ module Project_file = struct
]
end

module Source_kind = struct
type t =
| Github of string * string
| Url of string

let to_dyn =
let open Dyn.Encoder in
function
| Github (user, repo) -> constr "Github" [ string user; string repo ]
| Url url -> constr "Url" [ string url ]

let pp fmt = function
| Github (user, repo) ->
Format.fprintf fmt "git+https://github.com/%s/%s.git" user repo
| Url u -> Format.pp_print_string fmt u

let decode =
let open Dune_lang.Decoder in
sum
[ ( "github"
, plain_string (fun ~loc s ->
match String.split ~on:'/' s with
| [ user; repo ] -> Github (user, repo)
| _ ->
User_error.raise ~loc
[ Pp.textf "GitHub repository must be of form user/repo" ])
)
; ("uri", string >>| fun s -> Url s)
]
end

module File_key = struct
type t = string

Expand All @@ -188,13 +157,7 @@ type t =
{ name : Name.t
; root : Path.Source.t
; version : string option
; source : Source_kind.t option
; license : string option
; authors : string list
; homepage : string option
; bug_reports : string option
; documentation : string option
; maintainers : string list
; info : Package.Info.t
; packages : Package.t Package.Name.Map.t
; stanza_parser : Stanza.t list Dune_lang.Decoder.t
; project_file : Project_file.t
Expand All @@ -219,19 +182,7 @@ let packages t = t.packages

let version t = t.version

let source t = t.source

let license t = t.license

let homepage t = t.homepage

let documentation t = t.documentation

let bug_reports t = t.bug_reports

let maintainers t = t.maintainers

let authors t = t.authors
let info t = t.info

let name t = t.name

Expand All @@ -257,15 +208,9 @@ let to_dyn
{ name
; root
; version
; source
; license
; authors
; homepage
; documentation
; info
; project_file
; parsing_context = _
; bug_reports
; maintainers
; extension_args = _
; stanza_parser = _
; packages
Expand All @@ -284,13 +229,7 @@ let to_dyn
[ ("name", Name.to_dyn name)
; ("root", Path.Source.to_dyn root)
; ("version", (option string) version)
; ("source", (option Source_kind.to_dyn) source)
; ("license", (option string) license)
; ("homepage", (option string) homepage)
; ("documentation", (option string) documentation)
; ("bug_reports", (option string) bug_reports)
; ("maintainers", (list string) maintainers)
; ("authors", (list string) authors)
; ("info", Package.Info.to_dyn info)
; ("project_file", Project_file.to_dyn project_file)
; ( "packages"
, (list (pair Package.Name.to_dyn Package.to_dyn))
Expand Down Expand Up @@ -618,13 +557,7 @@ let infer ~dir packages =
{ name
; packages
; root
; source = None
; license = None
; homepage = None
; bug_reports = None
; documentation = None
; maintainers = []
; authors = []
; info = Package.Info.empty
; version = None
; implicit_transitive_deps
; wrapped_executables
Expand All @@ -647,28 +580,8 @@ let parse ~dir ~lang ~opam_packages ~file =
fields
(let+ name = field_o "name" Name.decode
and+ version = field_o "version" string
and+ source =
field_o "source"
(Dune_lang.Syntax.since Stanza.syntax (1, 7) >>> Source_kind.decode)
and+ info = Package.Info.decode ()
and+ packages = multi_field "package" (Package.decode ~dir)
and+ authors =
field ~default:[] "authors"
(Dune_lang.Syntax.since Stanza.syntax (1, 9) >>> repeat string)
and+ license =
field_o "license"
(Dune_lang.Syntax.since Stanza.syntax (1, 9) >>> string)
and+ homepage =
field_o "homepage"
(Dune_lang.Syntax.since Stanza.syntax (1, 10) >>> string)
and+ documentation =
field_o "documentation"
(Dune_lang.Syntax.since Stanza.syntax (1, 10) >>> string)
and+ bug_reports =
field_o "bug_reports"
(Dune_lang.Syntax.since Stanza.syntax (1, 10) >>> string)
and+ maintainers =
field "maintainers" ~default:[]
(Dune_lang.Syntax.since Stanza.syntax (1, 10) >>> repeat string)
and+ explicit_extensions =
multi_field "using"
(let+ loc = loc
Expand Down Expand Up @@ -699,18 +612,6 @@ let parse ~dir ~lang ~opam_packages ~file =
field_o_b "explicit_js_mode"
~check:(Dune_lang.Syntax.since Stanza.syntax (1, 11))
and+ format_config = Format_config.field in
let homepage =
match (homepage, source) with
| None, Some (Github (user, repo)) ->
Some (sprintf "https://github.com/%s/%s" user repo)
| s, _ -> s
in
let bug_reports =
match (bug_reports, source) with
| None, Some (Github (user, repo)) ->
Some (sprintf "https://github.com/%s/%s/issues" user repo)
| s, _ -> s
in
let packages =
if List.is_empty packages then
Package.Name.Map.map opam_packages ~f:(fun (_loc, p) -> Lazy.force p)
Expand Down Expand Up @@ -820,13 +721,7 @@ let parse ~dir ~lang ~opam_packages ~file =
; file_key
; root
; version
; source
; license
; authors
; homepage
; documentation
; bug_reports
; maintainers
; info
; packages
; stanza_parser
; project_file
Expand Down Expand Up @@ -886,6 +781,7 @@ let load ~dir ~files ~infer_from_opam_files =
; conflicts = []
; depends = []
; depopts = []
; info = Package.Info.empty
; synopsis = None
; description = None
; kind = Opam
Expand Down
24 changes: 1 addition & 23 deletions src/dune/dune_project.mli
Original file line number Diff line number Diff line change
Expand Up @@ -41,16 +41,6 @@ module Project_file : sig
val to_dyn : t -> Dyn.t
end

module Source_kind : sig
type t =
| Github of string * string
| Url of string

val pp : t Fmt.t

val to_dyn : t -> Dyn.t
end

type t

module File_key : sig
Expand All @@ -77,19 +67,7 @@ val name : t -> Name.t

val root : t -> Path.Source.t

val source : t -> Source_kind.t option

val license : t -> string option

val maintainers : t -> string list

val bug_reports : t -> string option

val documentation : t -> string option

val homepage : t -> string option

val authors : t -> string list
val info : t -> Package.Info.t

val stanza_parser : t -> Stanza.t list Dune_lang.Decoder.t

Expand Down
26 changes: 16 additions & 10 deletions src/dune/opam_create.ml
Original file line number Diff line number Diff line change
Expand Up @@ -41,6 +41,7 @@ let package_fields
; depends
; conflicts
; depopts
; info = _
; name = _
; path = _
; version = _
Expand Down Expand Up @@ -104,28 +105,33 @@ let opam_fields project (package : Package.t) =
in
let package_fields = package_fields package ~project in
let open Opam_file.Create in
let info =
Package.Info.superpose (Dune_project.info project) package.Package.info
in
let optional_fields =
[ ("bug-reports", Dune_project.bug_reports project)
; ("homepage", Dune_project.homepage project)
; ("doc", Dune_project.documentation project)
; ("license", Dune_project.license project)
[ ("bug-reports", info.Package.Info.bug_reports)
; ("homepage", info.Package.Info.homepage)
; ("doc", info.Package.Info.documentation)
; ("license", info.Package.Info.license)
; ("version", Dune_project.version project)
; ( "dev-repo"
, Option.map
~f:(Format.asprintf "%a" Dune_project.Source_kind.pp)
(Dune_project.source project) )
~f:(Format.asprintf "%a" Package.Source_kind.pp)
info.Package.Info.source )
]
|> List.filter_map ~f:(fun (k, v) ->
Option.map v ~f:(fun v -> (k, string v)))
in
let list_fields =
[ ("maintainer", Dune_project.maintainers project)
; ("authors", Dune_project.authors project)
[ ("maintainer", info.Package.Info.maintainers)
; ("authors", info.Package.Info.authors)
]
|> List.filter_map ~f:(fun (k, v) ->
match v with
| [] -> None
| _ :: _ -> Some (k, string_list v))
| None
| Some [] ->
None
| Some (_ :: _ as v) -> Some (k, string_list v))
in
let fields =
[ ("opam-version", string "2.0"); ("build", default_build_command project) ]
Expand Down
Loading

0 comments on commit 582a2ca

Please sign in to comment.