Skip to content

Commit

Permalink
Disallow both [self_build_stubs_archive] and [foreign_stubs] until 2.0
Browse files Browse the repository at this point in the history
Signed-off-by: Andrey Mokhov <[email protected]>
  • Loading branch information
snowleopard committed Oct 3, 2019
1 parent f73ad61 commit dcb4a8b
Show file tree
Hide file tree
Showing 3 changed files with 57 additions and 38 deletions.
21 changes: 19 additions & 2 deletions src/dune/dune_file.ml
Original file line number Diff line number Diff line change
Expand Up @@ -637,15 +637,32 @@ module Buildable = struct
field "js_of_ocaml" Js_of_ocaml.decode ~default:Js_of_ocaml.default
and+ allow_overlapping_dependencies =
field_b "allow_overlapping_dependencies"
in
and+ version = Dune_lang.Syntax.get_exn Stanza.syntax in
let foreign_stubs =
foreign_stubs
|> add_stubs C ~loc:c_names_loc ~names:c_names ~flags:c_flags
|> add_stubs Cxx ~loc:cxx_names_loc ~names:cxx_names ~flags:cxx_flags
in
(* TODO_AM: Add [foreign_stubs_archive] stanza. *)
let foreign_archives =
add_archive ~loc:loc_sbsa ~name:self_build_stubs_archive []
if
version < (2, 0)
&& (not (List.is_empty foreign_stubs))
&& Option.is_some self_build_stubs_archive
then
User_error.raise ~loc:loc_sbsa
[ Pp.concat
[ Pp.textf "A library cannot use both "
; Pp.hbox (Pp.textf "(self_build_stubs_archive ...)")
; Pp.textf " and "
; Pp.hbox (Pp.textf "(foreign_stubs ...)")
; Pp.textf
" simultaneously. This feature will only become available in "
; Pp.hbox (Pp.textf "Dune 2.0.")
]
]
else
add_archive ~loc:loc_sbsa ~name:self_build_stubs_archive []
in
{ loc
; preprocess
Expand Down
64 changes: 32 additions & 32 deletions src/dune/foreign_sources.ml
Original file line number Diff line number Diff line change
Expand Up @@ -27,38 +27,38 @@ let valid_name language ~loc s =
let eval_foreign_sources (d : _ Dir_with_dune.t) foreign_stubs
~(object_map : Foreign.Object_map.t) : Foreign.Sources.t =
let eval (library : Foreign.Library.t) =
let language = library.language in
let osl = library.names in
Ordered_set_lang.Unordered_string.eval_loc osl
~key:(fun x -> x)
~parse:(fun ~loc s ->
let s = valid_name language ~loc s in
let s' = Filename.basename s in
if s' <> s then
User_error.raise ~loc
[ Pp.text
"relative part of stub is not necessary and should be \
removed. To include sources in subdirectories, use the \
include_subdirs stanza"
];
s')
~standard:String.Map.empty
|> String.Map.map ~f:(fun (loc, s) ->
match
let open Option.O in
let* map = String.Map.find object_map s in
let+ path = Foreign.Language.Map.find map language in
(loc, Foreign.Source.make ~library ~path)
with
| Some x -> x
| None ->
let dune_version = d.dune_version in
User_error.raise ~loc
[ Pp.textf "Object %S has no source; %s must be present." s
(String.enumerate_one_of
( Foreign.Language.possible_fns language s ~dune_version
|> List.map ~f:(fun s -> "\"" ^ s ^ "\"") ))
])
let language = library.language in
let osl = library.names in
Ordered_set_lang.Unordered_string.eval_loc osl
~key:(fun x -> x)
~parse:(fun ~loc s ->
let s = valid_name language ~loc s in
let s' = Filename.basename s in
if s' <> s then
User_error.raise ~loc
[ Pp.text
"relative part of stub is not necessary and should be \
removed. To include sources in subdirectories, use the \
include_subdirs stanza"
];
s')
~standard:String.Map.empty
|> String.Map.map ~f:(fun (loc, s) ->
match
let open Option.O in
let* map = String.Map.find object_map s in
let+ path = Foreign.Language.Map.find map language in
(loc, Foreign.Source.make ~library ~path)
with
| Some x -> x
| None ->
let dune_version = d.dune_version in
User_error.raise ~loc
[ Pp.textf "Object %S has no source; %s must be present." s
(String.enumerate_one_of
( Foreign.Language.possible_fns language s ~dune_version
|> List.map ~f:(fun s -> "\"" ^ s ^ "\"") ))
])
in
let stub_maps = List.map foreign_stubs ~f:eval in
List.fold_left stub_maps ~init:String.Map.empty ~f:(fun a b ->
Expand Down
10 changes: 6 additions & 4 deletions test/blackbox-tests/test-cases/github1306/run.t
Original file line number Diff line number Diff line change
@@ -1,6 +1,8 @@
$ dune build
File "dune", line 3, characters 10-13:
3 | (c_names foo)
^^^
Error: Object "foo" has no source; "foo.c" must be present.
File "dune", line 4, characters 1-33:
4 | (self_build_stubs_archive (bar)))
^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Error: A library cannot use both (self_build_stubs_archive ...) and
(foreign_stubs ...) simultaneously. This feature will only become available
in Dune 2.0.
[1]

0 comments on commit dcb4a8b

Please sign in to comment.