Skip to content

Commit

Permalink
Add singular form
Browse files Browse the repository at this point in the history
Signed-off-by: Rudi Grinberg <rudi.grinberg@gmail.com>
  • Loading branch information
rgrinberg committed Jul 5, 2018
1 parent dd9915c commit ebe5b81
Show file tree
Hide file tree
Showing 6 changed files with 28 additions and 5 deletions.
15 changes: 11 additions & 4 deletions src/jbuild.ml
Original file line number Diff line number Diff line change
Expand Up @@ -1360,11 +1360,11 @@ module Tests = struct
; deps : Dep_conf.t list
}

let t =
let gen_parse names =
record
(Buildable.t >>= fun buildable ->
(Buildable.t >>= fun buildable ->
field_oslu "link_flags" >>= fun link_flags ->
field "names" (list (located string)) >>= fun names ->
names >>= fun names ->
field "deps" (list Dep_conf.t) ~default:[] >>= fun deps ->
field_o "package" Pkg.t >>= fun package ->
field "locks" (list String_with_vars.t) ~default:[] >>= fun locks ->
Expand All @@ -1383,6 +1383,10 @@ module Tests = struct
; package
; deps
})

let multi = gen_parse (field "names" (list (located string)))

let single = gen_parse (field "name" (located string) >>| List.singleton)
end

module Copy_files = struct
Expand Down Expand Up @@ -1519,7 +1523,10 @@ module Stanzas = struct
Jbuild_version.t >>| fun _ -> [])
; "tests",
(Syntax.since Stanza.syntax (1, 0) >>= fun () ->
(Tests.t >>| fun t -> [Tests t]))
(Tests.multi >>| fun t -> [Tests t]))
; "test",
(Syntax.since Stanza.syntax (1, 0) >>= fun () ->
(Tests.single >>| fun t -> [Tests t]))
; "env",
(Syntax.since Stanza.syntax (1, 0) >>= fun () ->
loc >>= fun loc ->
Expand Down
2 changes: 2 additions & 0 deletions src/stdune/list.ml
Original file line number Diff line number Diff line change
Expand Up @@ -102,3 +102,5 @@ let rec assoc t x =
match t with
| [] -> None
| (k, v) :: t -> if x = k then Some v else assoc t x

let singleton x = [x]
2 changes: 2 additions & 0 deletions src/stdune/list.mli
Original file line number Diff line number Diff line change
Expand Up @@ -38,3 +38,5 @@ val stable_sort : 'a t -> compare:('a -> 'a -> Ordering.t) -> 'a t
val compare : 'a t -> 'a t -> compare:('a -> 'a -> Ordering.t) -> Ordering.t

val assoc : ('a * 'b) t -> 'a -> 'b option

val singleton : 'a -> 'a t
7 changes: 6 additions & 1 deletion test/blackbox-tests/test-cases/tests-stanza/dune
Original file line number Diff line number Diff line change
@@ -1,2 +1,7 @@
(tests
(names expect_test regular_test))
(names expect_test regular_test)
(modules :standard \ singular))

(test
(name singular)
(modules singular))
6 changes: 6 additions & 0 deletions test/blackbox-tests/test-cases/tests-stanza/run.t
Original file line number Diff line number Diff line change
@@ -1,4 +1,10 @@
$ dune runtest --display short
ocamldep .singular.eobjs/singular.ml.d
ocamlc .singular.eobjs/singular.{cmi,cmo,cmt}
ocamlopt .singular.eobjs/singular.{cmx,o}
ocamlopt singular.exe
singular alias runtest
singular test
ocamldep .expect_test.eobjs/expect_test.ml.d
ocamldep .expect_test.eobjs/regular_test.ml.d
ocamlc .expect_test.eobjs/regular_test.{cmi,cmo,cmt}
Expand Down
1 change: 1 addition & 0 deletions test/blackbox-tests/test-cases/tests-stanza/singular.ml
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
print_endline "singular test"

0 comments on commit ebe5b81

Please sign in to comment.