Skip to content

Commit

Permalink
Improve opam metadata in dune
Browse files Browse the repository at this point in the history
We add metadata that can be used to used to partially specify opam files. Common
fields such as depends, conflicts, authors, are all handled. Dune will now
automatically suggest corrections to the existing opam files based on this
metadata in the dune files

Co-authored-by: Jon Ludlam <jon@recoil.org>
Signed-off-by: Anil Madhavapeddy <anil@recoil.org>
Signed-off-by: Rudi Grinberg <rudi.grinberg@gmail.com>
  • Loading branch information
2 people authored and rgrinberg committed Apr 25, 2019
1 parent 12f7bee commit da5c978
Show file tree
Hide file tree
Showing 40 changed files with 1,235 additions and 181 deletions.
4 changes: 4 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
Expand Up @@ -25,6 +25,10 @@ unreleased
to produce targets that are present in the source tree. This has
been a warning for long enough (#2068, @diml)

- Add more opam metadata and use it to generate corrections to the .opam files
in the source. This allows the user to partially specify opam metadata in the
the dune-project file. (#2017, @avsm, @jonludlam)

1.9.1 (11/04/2019)
------------------

Expand Down
1 change: 1 addition & 0 deletions doc/index.rst
Original file line number Diff line number Diff line change
Expand Up @@ -22,6 +22,7 @@ Welcome to dune's documentation!
configurator
menhir
jsoo
opam
variants
formatting
coq
Expand Down
103 changes: 103 additions & 0 deletions doc/opam.rst
Original file line number Diff line number Diff line change
@@ -0,0 +1,103 @@
****
opam
****

opam_ is the official package manager for OCaml, and dune offers some
integration with it.

Generating opam files
=====================

Dune is able to use metadata specified in the ``dune-project`` file to cross
reference it with the information in the user written ``.opam`` file. To enable
this integration, a user needs to add an ``(opam ..)`` field to the dune-project
file.

The fields that dune uses for this purpose are:

- ``(license <name>)`` - Specified the license of the project

- ``(authors <authors>)`` - A list of authors

- ``(source <source>)`` - where the source is specified two ways:
``(github <user/repo>)`` or ``(uri <uri>)``

To enable dune suggesting corrections to the opam stanza, the user must specify
an ``(opam <fields>)`` with the fields:

- ``(tags <tags>)`` - Specify the list of tags for all packages
- ``(depends <dep-specification>)`` - The list of dependencies shared by all opam packages
in this dune project
- ``(conflicts <dep-specification>)`` - The list of conflicts shared by all opam
packages in this dune project
- ``(package <package>)`` - the list of packages in this project and their
individual metadata.

The list of dependencies ``<dep-specification>`` is modeled after opam's own
language: The syntax is as a list of the following elements:

.. code::
op := '=' | '<' | '>' | '<>' | '>=' | '<='
stage := :with_test | :build | :dev
constr := (<op> <version>)
logop := or | and
dep := (name <stage>)
| (name <constr>)
| (name (<logop> (<stage> | <constr>)*))
dep-specification = dep+
The `(package <package>)` field contains the fields:

- ``(name <string>)`` is the name of the package

- ``(synopsis <string>)`` is a short package description

- ``(description <string>)`` is a longer package description

- ``(depends <dep-specification>)`` are package specific dependencies

- ``(conflicts <dep-specification)`` are package specific conflicts

Here's a complete example of a dune file with opam metadata specification:

.. code:: scheme
(lang dune 1.10)
(name cohttp)
(source (github mirage/ocaml-cohttp))
(license ISC)
(authors "Anil Madhavapeddy" "Rudi Grinberg")
(opam
(tags org:mirage org:dune)
(depends
(ocaml (>= 4.06.0))
(cohttp (>= 1.0.0)))
(package
(name cohttp)
(synopsis "An OCaml library for HTTP clients and servers")
(description "A longer description")
(depends
(alcotest :with-test)
(dune (and :build (> 1.5)))
(foo (and :dev (> 1.5) (< 2.0)))
(uri (>= 1.9.0))
(uri (< 2.0.0))
(fieldslib (> v0.12))
(fieldslib (< v0.13))))
(package
(name cohttp-async)
(synopsis "HTTP client and server for the Async library")
(description "A _really_ long description")
(depends
(cohttp (>= 1.0.2))
(conduit-async (>= 1.0.3))
(async (>= v0.10.0))
(async (< v0.12)))))
.. _opam: https://opam.ocaml.org/
38 changes: 36 additions & 2 deletions dune-project
Original file line number Diff line number Diff line change
@@ -1,4 +1,38 @@
(lang dune 1.8)
(lang dune 1.10)
(name dune)

(implicit_transitive_deps false)
(implicit_transitive_deps false)

(license MIT)
(authors "Jane Street Group, LLC <opensource@janestreet.com>")
(source (github ocaml/dune))

(opam
(package
(name dune)
(depends
(ocaml (>= 4.02))
base-unix
base-threads)
(conflicts
(jbuilder (<> "transition"))
(odoc (< 1.3.0)))
(synopsis "Fast, portable and opinionated build system")
(description "
dune is a build system that was designed to simplify the release of
Jane Street packages. It reads metadata from \"dune\" files following a
very simple s-expression syntax.
dune is fast, it has very low-overhead and support parallel builds on
all platforms. It has no system dependencies, all you need to build
dune and packages using dune is OCaml. You don't need or make or bash
as long as the packages themselves don't use bash explicitly.
dune supports multi-package development by simply dropping multiple
repositories into the same directory.
It also supports multi-context builds, such as building against
several opam roots/switches simultaneously. This helps maintaining
packages across several versions of OCaml and gives cross-compilation
for free.
")))
1 change: 0 additions & 1 deletion dune.opam
Original file line number Diff line number Diff line change
Expand Up @@ -21,7 +21,6 @@ conflicts: [
"jbuilder" {!= "transition"}
"odoc" {< "1.3.0"}
]

synopsis: "Fast, portable and opinionated build system"
description: """
dune is a build system that was designed to simplify the release of
Expand Down
2 changes: 1 addition & 1 deletion example/sample-projects/hello_world/hello_world.opam
Original file line number Diff line number Diff line change
Expand Up @@ -8,4 +8,4 @@ dev-repo: "git+https://github.com/SpongeBob/hello_world.git"
license: "Apache-2.0"
build: [
["dune" "build" "-p" name "-j" jobs]
]
]
2 changes: 1 addition & 1 deletion example/sample-projects/with-configure-step/myproject.opam
Original file line number Diff line number Diff line change
Expand Up @@ -8,4 +8,4 @@ dev-repo: "git+https://github.com/SpongeBob/myproject.git"
license: "Apache-2.0"
build: [
["dune" "build" "-p" name "-j" jobs]
]
]
59 changes: 59 additions & 0 deletions src/blang.ml
Original file line number Diff line number Diff line change
Expand Up @@ -15,6 +15,16 @@ module Op = struct
| (Neq | Lt | Lte) , Lt
| (Neq | Gt | Gte) , Gt -> true
| _, _ -> false

let to_dyn =
let open Dyn.Encoder in
function
| Eq -> string "Eq"
| Gt -> string "Gt"
| Gte -> string "Gte"
| Lte -> string "Lte"
| Lt -> string "Lt"
| Neq -> string "Neq"
end

type t =
Expand Down Expand Up @@ -43,3 +53,52 @@ let rec eval t ~dir ~f =
let x = String_with_vars.expand x ~mode:Many ~dir ~f
and y = String_with_vars.expand y ~mode:Many ~dir ~f in
Op.eval op (Value.L.compare_vals ~dir x y)

let rec to_dyn =
let open Dyn.Encoder in
function
| Const b -> constr "Const" [bool b]
| Expr e -> constr "Expr" [via_sexp String_with_vars.to_sexp e]
| And t -> constr "And" (List.map ~f:to_dyn t)
| Or t -> constr "Or" (List.map ~f:to_dyn t)
| Compare (o, s1, s2) ->
constr "Compare"
[ Op.to_dyn o
; via_sexp String_with_vars.to_sexp s1
; via_sexp String_with_vars.to_sexp s2
]

let ops =
[ "=", Op.Eq
; ">=", Gte
; "<=", Lt
; ">", Gt
; "<", Lt
; "<>", Neq
]

let decode =
let open Stanza.Decoder in
let ops =
List.map ops ~f:(fun (name, op) ->
( name
, (let+ x = String_with_vars.decode
and+ y = String_with_vars.decode
in
Compare (op, x, y))))
in
let decode =
fix begin fun t ->
if_list
~then_:(
[ "or", repeat t >>| (fun x -> Or x)
; "and", repeat t >>| (fun x -> And x)
] @ ops
|> sum)
~else_:(String_with_vars.decode >>| fun v -> Expr v)
end
in
let+ () = Syntax.since Stanza.syntax (1, 1)
and+ decode = decode
in
decode
6 changes: 5 additions & 1 deletion src/blang.mli
Original file line number Diff line number Diff line change
Expand Up @@ -22,5 +22,9 @@ val true_ : t
val eval
: t
-> dir:Path.t
-> f:Value.t list option String_with_vars.expander
-> f:Value.t list option String_with_vars.expander
-> bool

val to_dyn : t -> Dyn.t

val decode : t Stanza.Decoder.t
37 changes: 0 additions & 37 deletions src/dune_file.ml
Original file line number Diff line number Diff line change
Expand Up @@ -319,43 +319,6 @@ module Preprocess = struct
]))
end

module Blang = struct
include Blang

let ops =
[ "=", Op.Eq
; ">=", Gte
; "<=", Lt
; ">", Gt
; "<", Lt
; "<>", Neq
]

let decode =
let ops =
List.map ops ~f:(fun (name, op) ->
( name
, (let+ x = String_with_vars.decode
and+ y = String_with_vars.decode
in
Compare (op, x, y))))
in
let decode =
fix begin fun t ->
if_list
~then_:(
[ "or", repeat t >>| (fun x -> Or x)
; "and", repeat t >>| (fun x -> And x)
] @ ops
|> sum)
~else_:(String_with_vars.decode >>| fun v -> Expr v)
end
in
let+ () = Syntax.since Stanza.syntax (1, 1)
and+ decode = decode
in
decode
end

let enabled_if =
field "enabled_if" ~default:Blang.true_
Expand Down
Loading

0 comments on commit da5c978

Please sign in to comment.