Skip to content

Commit

Permalink
Variants: wrap to 80 characters
Browse files Browse the repository at this point in the history
Signed-off-by: Lucas Pluvinage <lucas.pluvinage@gmail.com>
  • Loading branch information
TheLortex committed Mar 4, 2019
1 parent 8c78099 commit e7f52ed
Show file tree
Hide file tree
Showing 3 changed files with 171 additions and 101 deletions.
11 changes: 8 additions & 3 deletions src/dune_file.ml
Expand Up @@ -637,7 +637,8 @@ module Buildable = struct
and preprocess =
field "preprocess" Preprocess_map.decode ~default:Preprocess_map.default
and variants =
field "variants" ((list Variant.decode) >>| Variant.Set.of_list) ~default:Variant.Set.empty
field "variants" ((list Variant.decode) >>| Variant.Set.of_list)
~default:Variant.Set.empty
and preprocessor_deps =
field "preprocessor_deps" (list Dep_conf.decode) ~default:[]
and lint = field "lint" Lint.decode ~default:Lint.default
Expand Down Expand Up @@ -935,10 +936,14 @@ module Library = struct
"A library cannot be both virtual and implement %s"
(Lib_name.to_string impl));
match virtual_modules, default_implementation with
| None, Some (loc, _) -> of_sexp_error loc "Only virtual libraries can specify a default implementation."
| None, Some (loc, _) ->
of_sexp_error loc
"Only virtual libraries can specify a default implementation."
| _ -> ();
match implements, variant with
| None, Some (loc, _) -> of_sexp_error loc "Only implementations can specify a variant."
| None, Some (loc, _) ->
of_sexp_error loc
"Only implementations can specify a variant."
| _ -> ();
let variant = Option.map variant ~f:(fun (_, v) -> v) in
let self_build_stubs_archive =
Expand Down
9 changes: 6 additions & 3 deletions src/dune_package.ml
Expand Up @@ -31,7 +31,8 @@ module Lib = struct

let make ~loc ~kind ~name ~synopsis ~archives ~plugins ~foreign_objects
~foreign_archives ~jsoo_runtime ~main_module_name ~sub_systems
~requires ~ppx_runtime_deps ~implements ~variant ~default_implementation ~virtual_ ~modules ~modes
~requires ~ppx_runtime_deps ~implements ~variant
~default_implementation ~virtual_ ~modules ~modes
~version ~orig_src_dir ~dir =
let map_path p = Path.relative dir (Path.basename p) in
let map_list = List.map ~f:map_path in
Expand Down Expand Up @@ -74,7 +75,8 @@ module Lib = struct
{ loc = _ ; kind ; synopsis ; name ; archives ; plugins
; foreign_objects ; foreign_archives ; jsoo_runtime ; requires
; ppx_runtime_deps ; sub_systems ; virtual_
; implements ; variant ; default_implementation ; main_module_name ; version = _; dir = _; orig_src_dir
; implements ; variant ; default_implementation
; main_module_name ; version = _; dir = _; orig_src_dir
; modules ; modes
} =
let open Dune_lang.Encoder in
Expand Down Expand Up @@ -123,7 +125,8 @@ module Lib = struct
field_o "main_module_name" Module.Name.decode >>= fun main_module_name ->
field_o "implements" (located Lib_name.decode) >>= fun implements ->
field_o "variant" Variant.decode >>= fun variant ->
field_o "default_implementation" (located Lib_name.decode) >>= fun default_implementation ->
field_o "default_implementation" (located Lib_name.decode)
>>= fun default_implementation ->
field "name" Lib_name.decode >>= fun name ->
let dir = Path.append_local base (dir_of_name name) in
let%map synopsis = field_o "synopsis" string
Expand Down

0 comments on commit e7f52ed

Please sign in to comment.