Skip to content

Commit

Permalink
Futher work on docs and error messages
Browse files Browse the repository at this point in the history
Signed-off-by: Andrey Mokhov <amokhov@janestreet.com>
  • Loading branch information
snowleopard committed Oct 16, 2019
1 parent a40146e commit 9ca1576
Show file tree
Hide file tree
Showing 7 changed files with 126 additions and 68 deletions.
7 changes: 7 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
Expand Up @@ -102,6 +102,8 @@

- `c_flags`, `c_names` and `cxx_names` are now supported in `executable`
and `executables` stanzas. (#2562, @nojb)
Note: this feature has been subsequently extended into a separate
`foreign_stubs` field. (#2659, RFC #2650, @snowleopard)

- Remove git integration from `$ dune upgrade` (#2565, @rgrinberg)

Expand Down Expand Up @@ -158,6 +160,11 @@
projects where the language is at least `2.0`, the field is now forbidden.
(#2752, fixes #2747, @rgrinberg)

- Extend support for foreign sources and archives via the `(foreign_library ...)`
stanza as well as the `(foreign_stubs ...)` and `(foreign_archives ...)` fields.
(#2659, RFC #2650, @snowleopard)


1.11.4 (09/10/2019)
-------------------

Expand Down
50 changes: 30 additions & 20 deletions doc/concepts.rst
Original file line number Diff line number Diff line change
Expand Up @@ -1081,14 +1081,15 @@ You can specify foreign sources using the ``foreign_stubs`` field of the
(library
(name lib)
(foreign_stubs (language c) (names src1 src2))
(foreign_stubs (language cxx) (names src3)))
(foreign_stubs (language cxx) (names src3) (flags -O2)))
Here we declare an OCaml library ``lib``, which contains two C sources
``src1`` and ``src2``, and one C++ source ``src3``. These source files will
be compiled and packaged with the library, along with the link-time flags
to be used during linking of the final executable. When matching ``names``
to source files, Dune treats ``*.c`` files as C sources, and ``*.cpp``,
``*.cc`` and ``*.cxx`` files as C++ sources.
``src1`` and ``src2``, and one C++ source ``src3`` that needs to be
compiled with ``-O2``. These source files will be compiled and packaged
with the library, along with the link-time flags to be used when
linking the final executables. When matching ``names`` to source files,
Dune treats ``*.c`` files as C sources, and ``*.cpp``, ``*.cc`` and
``*.cxx`` files as C++ sources.

Here is a complete list of supported subfields:

Expand All @@ -1098,15 +1099,20 @@ Here is a complete list of supported subfields:
file, you should omit the extension and any relative parts of the path;
Dune will scan all library directories, finding all matching files and
raising an error if multiple source files map to the same object name.
If you need to have multiple object files with the same name, use the
``foreign_archives`` field described in the section
:ref:`foreign-sources-archives`.
If you need to have multiple object files with the same name, you can
package them into different :ref:`foreign-archives` via the
``foreign_archives`` field.
- ``flags`` are passed when compiling source files. This field is specified
using the :ref:`ordered-set-language`, where the ``:standard`` value comes
from the environment settings ``c_flags`` and ``cxx_flags``, respectively.
- ``include_dirs`` are tracked as dependencies and passed to the compiler
via the ``-I`` flag. You can use :ref:`variables` in this field.
via the ``-I`` flag. You can use :ref:`variables` in this field. The
contents of included directories is tracked recursively, e.g. if you
use ``(include_dir dir)`` and have headers ``dir/base.h`` and
``dir/lib/lib.h`` then they both will be tracked as dependencies.
- ``extra_deps`` specifies any other dependencies that should be tracked.
This is useful when dealing with ``#include`` statements that escape into
a parent directory like ``#include "../a.h"``.


.. _foreign-archives:
Expand All @@ -1124,32 +1130,36 @@ corresponding ``library`` or ``executable`` stanza. For example:
(library
(name lib)
(foreign_stubs (language c) (names src1 src2))
(foreign_stubs (language cxx) (names src3))
(foreign_stubs (language cxx) (names src3) (flags -O2))
(foreign_archives arch1 some/dir/arch2))
Here, in addition to :ref:`foreign-stubs`, we also specify foreign archives
``arch1`` and ``arch2``, where the latter is stored in a subdirectory
``some/dir``.

You can build a foreign archive manually, e.g. using a custom ``rule``, or
ask Dune to build it via the ``foreign_library`` stanza:
You can build a foreign archive manually, e.g. using a custom ``rule`` as
described in :ref:`foreign-sandboxing`, or ask Dune to build it via the
``foreign_library`` stanza:

.. code:: scheme
(foreign_library
(archive_name arch1)
(language c)
(names src4 src5))
(names src4 src5)
(include_dir headers))
This asks Dune to compile C source files ``src4`` and ``src5``, and put the
resulting object files into an archive ``arch1``, whose full name is
typically ``libarch1.a`` for static linking and ``dllarch1.so`` for dynamic
This asks Dune to compile C source files ``src4`` and ``src5`` with
headers tracked in the ``headers`` directory, and put the resulting
object files into an archive ``arch1``, whose full name is typically
``libarch1.a`` for static linking and ``dllarch1.so`` for dynamic
linking.

The ``foreign_library`` stanza supports all :ref:`foreign-stubs` fields plus
the ``archive_name`` field, which specifies the name of the archive. The same
archive name can appear in multiple OCaml libraries and executables, so a
the ``archive_name`` field, which specifies the archive's name. You can refer
to the same archive name from multiple OCaml libraries and executables, so a
foreign archive is a bit like a foreign library, hence the name of the stanza.

Foreign archives are particularly useful when embedding a library written in
a foreign language and/or built with another build system.
a foreign language and/or built with another build system. See
:ref:`foreign-sandboxing` for more details.
11 changes: 7 additions & 4 deletions editor-integration/emacs/dune.el
Original file line number Diff line number Diff line change
Expand Up @@ -63,7 +63,8 @@
"ocamllex" "ocamlyacc" "menhir" "alias" "install"
"copy_files" "copy_files#" "include" "tests" "test" "dirs"
"env" "ignored_subdirs" "include_subdirs" "data_only_dirs"
"documentation" "cinaps" "coqlib" "coq.theory" "coq.pp")
"documentation" "cinaps" "coqlib" "coq.theory" "coq.pp"
"foreign_library")
) "\\(?:\\_>\\|[[:space:]]\\)"))
"Stanzas in dune files.")

Expand All @@ -72,9 +73,9 @@
(regexp-opt
'("name" "public_name" "synopsis" "modules" "libraries" "wrapped"
"preprocess" "preprocessor_deps" "optional" "c_names" "cxx_names"
"install_c_headers" "modes" "no_dynlink" "kind"
"ppx_runtime_libraries" "virtual_deps" "js_of_ocaml" "flags"
"ocamlc_flags" "ocamlopt_flags" "library_flags" "c_flags"
"foreign_stubs" "foreign_archives" "install_c_headers" "modes"
"no_dynlink" "kind" "ppx_runtime_libraries" "virtual_deps" "js_of_ocaml"
"flags" "ocamlc_flags" "ocamlopt_flags" "library_flags" "c_flags"
"cxx_flags" "c_library_flags" "self_build_stubs_archive" "inline_tests"
"modules_without_implementation" "private_modules"
;; + special_builtin_support
Expand All @@ -87,6 +88,8 @@
;; + for "executable" and "executables":
"package" "link_flags" "link_deps" "names" "public_names" "variants"
"forbidden_libraries"
;; + for "foreign_library" and "foreign_stubs":
"archive_name" "language" "names" "flags" "include_dirs" "extra_deps"
;; + for "rule":
"targets" "action" "deps" "mode" "fallback" "locks"
;; + for "menhir":
Expand Down
49 changes: 27 additions & 22 deletions src/dune/dune_file.ml
Original file line number Diff line number Diff line change
Expand Up @@ -471,20 +471,24 @@ module Buildable = struct
; allow_overlapping_dependencies : bool
}

let decode ~since_c ~allow_re_export =
let decode ~in_library ~allow_re_export =
let use_foreign =
Dune_lang.Syntax.deleted_in Stanza.syntax (2, 0)
~extra_info:"Use the (foreign_stubs ...) field instead."
in
let check_c t =
match since_c with
| None -> t
| Some v -> Dune_lang.Syntax.since Stanza.syntax v >>> t
let only_in_library decode =
if in_library then
decode
else
return None
in
let add_stubs language ~loc ~names ~flags foreign_stubs =
match names with
| None -> foreign_stubs
| Some names ->
let flags =
Option.value ~default:Ordered_set_lang.Unexpanded.standard flags
in
Foreign.Stubs.make ~loc ~language ~names ~flags :: foreign_stubs
in
let+ loc = loc
Expand All @@ -498,25 +502,28 @@ module Buildable = struct
( Dune_lang.Syntax.since Stanza.syntax (2, 0)
>>> repeat (located string) )
and+ c_flags =
Ordered_set_lang.Unexpanded.field "c_flags"
?check:(Some (use_foreign >>> check_c (return ())))
only_in_library
(field_o "c_flags" (use_foreign >>> Ordered_set_lang.Unexpanded.decode))
and+ cxx_flags =
Ordered_set_lang.Unexpanded.field "cxx_flags"
?check:(Some (use_foreign >>> check_c (return ())))
only_in_library
(field_o "cxx_flags"
(use_foreign >>> Ordered_set_lang.Unexpanded.decode))
and+ c_names_loc, c_names =
located
(field_o "c_names" (use_foreign >>> check_c Ordered_set_lang.decode))
(only_in_library
(field_o "c_names" (use_foreign >>> Ordered_set_lang.decode)))
and+ cxx_names_loc, cxx_names =
located
(field_o "cxx_names" (use_foreign >>> check_c Ordered_set_lang.decode))
(only_in_library
(field_o "cxx_names" (use_foreign >>> Ordered_set_lang.decode)))
and+ modules = modules_field "modules"
and+ self_build_stubs_archive_loc, self_build_stubs_archive =
located
(field "self_build_stubs_archive"
( Dune_lang.Syntax.deleted_in Stanza.syntax (2, 0)
~extra_info:"Use the (foreign_archives ...) field instead."
>>> option string )
~default:None)
(only_in_library
(field ~default:None "self_build_stubs_archive"
( Dune_lang.Syntax.deleted_in Stanza.syntax (2, 0)
~extra_info:"Use the (foreign_archives ...) field instead."
>>> option string )))
and+ modules_without_implementation =
modules_field "modules_without_implementation"
and+ libraries =
Expand Down Expand Up @@ -798,7 +805,7 @@ module Library = struct

let decode =
fields
(let+ buildable = Buildable.decode ~since_c:None ~allow_re_export:true
(let+ buildable = Buildable.decode ~in_library:true ~allow_re_export:true
and+ loc = loc
and+ name = field_o "name" Lib_name.Local.decode_loc
and+ public = Public_lib.public_name_field
Expand All @@ -823,8 +830,7 @@ module Library = struct
and+ () =
let check =
let+ loc = loc
and+ dune_version = Dune_lang.Syntax.get_exn Stanza.syntax
in
and+ dune_version = Dune_lang.Syntax.get_exn Stanza.syntax in
let is_error = dune_version >= (2, 0) in
User_warning.emit ~loc ~is_error
[ Pp.text "no_keep_locs is a no-op. Please delete it." ]
Expand Down Expand Up @@ -1477,8 +1483,7 @@ module Executables = struct
Dune_project.Extension.register syntax (return ((), [])) Dyn.Encoder.unit

let common =
let+ buildable =
Buildable.decode ~since_c:(Some (2, 0)) ~allow_re_export:false
let+ buildable = Buildable.decode ~in_library:false ~allow_re_export:false
and+ (_ : bool) =
field "link_executables" ~default:true
(Dune_lang.Syntax.deleted_in Stanza.syntax (1, 0) >>> bool)
Expand Down Expand Up @@ -1993,7 +1998,7 @@ module Tests = struct
let gen_parse names =
fields
(let+ buildable =
Buildable.decode ~since_c:(Some (2, 0)) ~allow_re_export:false
Buildable.decode ~in_library:false ~allow_re_export:false
and+ link_flags = Ordered_set_lang.Unexpanded.field "link_flags"
and+ variants = variants_field
and+ names = names
Expand Down
31 changes: 15 additions & 16 deletions src/dune/foreign_sources.ml
Original file line number Diff line number Diff line change
Expand Up @@ -40,9 +40,8 @@ let eval_foreign_sources (d : _ Dir_with_dune.t) foreign_stubs
let osl = stubs.names in
Ordered_set_lang.Unordered_string.eval_loc osl
~key:(fun x -> x)
(* CR-someday aalekseyev:
Might be a good idea to change [standard] to mean
"all files with the relevant extension". *)
(* CR-someday aalekseyev: Might be a good idea to change [standard] to
mean "all files with the relevant extension". *)
~standard:String.Map.empty
~parse:(fun ~loc s ->
let name = valid_name language ~loc s in
Expand All @@ -56,24 +55,21 @@ let eval_foreign_sources (d : _ Dir_with_dune.t) foreign_stubs
];
name)
|> String.Map.map ~f:(fun (loc, name) ->
match String.Map.find sources name with
| Some (_ :: _ :: _ as paths) ->
(* CR aalekseyev:
This looks suspicious to me.
If the user writes foo.c and foo.cpp and only declares a foreign
library that uses foo.cpp, will that be an error?
I think it shouldn't be. *)
match String.Map.find sources name with
| Some (_ :: _ :: _ as paths) ->
(* CR aalekseyev: This looks suspicious to me. If the user writes
foo.c and foo.cpp and only declares a foreign library that uses
foo.cpp, will that be an error? I think it shouldn't be. *)
User_error.raise ~loc
[ Pp.textf "Multiple sources map to the same object name %S:"
name
; Pp.enumerate (
List.map paths ~f:snd
|> List.sort ~compare:(Path.Build.compare))
; Pp.enumerate
( List.map paths ~f:snd
|> List.sort ~compare:Path.Build.compare )
~f:(fun path ->
Pp.text
(Path.to_string_maybe_quoted
(Path.drop_optional_build_context (Path.build path)))
)
(Path.drop_optional_build_context (Path.build path))))
; Pp.text "This is not allowed; please rename them."
]
~hints:
Expand All @@ -85,7 +81,10 @@ let eval_foreign_sources (d : _ Dir_with_dune.t) foreign_stubs
]
| Some [ (l, path) ] when l = language ->
(loc, Foreign.Source.make ~stubs ~path)
| Some [] | None | [ (_wrong_lang, _) ] ->
| None
| Some []
| Some [ (_, _) ]
(* Found a matching source file, but in a wrong language. *) ->
User_error.raise ~loc
[ Pp.textf "Object %S has no source; %s must be present." name
(String.enumerate_one_of
Expand Down
7 changes: 4 additions & 3 deletions test/blackbox-tests/test-cases/foreign-library/run.t
Original file line number Diff line number Diff line change
Expand Up @@ -268,12 +268,13 @@ Testsuite for the (foreign_library ...) stanza.
Error: "/absolute/path" is an external directory; dependencies in external
directories are currently not tracked.
Hint: You can specify "/absolute/path" as an untracked include directory like this:

(flags -I /absolute/path)

[1]



----------------------------------------------------------------------------------
* Error message for multiple declarations with the same "archive_name".

Expand Down Expand Up @@ -603,7 +604,7 @@ Testsuite for the (foreign_library ...) stanza.
> (language c)
> (names day))
> (rule
> (action (write-file day.c "#include <caml/mlvalues.h>\nvalue new_day() { return Val_int(14); }\n")))
> (action (write-file day.c "#include <caml/mlvalues.h>\nvalue new_day(value unit) { return Val_int(14); }\n")))
> EOF

$ cat >dune <<EOF
Expand Down
Loading

0 comments on commit 9ca1576

Please sign in to comment.