Skip to content

Commit

Permalink
Get rid of Blang_decode
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 Apr 14, 2019
1 parent 7d87516 commit 1578721
Show file tree
Hide file tree
Showing 5 changed files with 42 additions and 53 deletions.
38 changes: 36 additions & 2 deletions src/blang.ml
Original file line number Diff line number Diff line change
Expand Up @@ -71,5 +71,39 @@ include (
; via_sexp String_with_vars.to_sexp s1
; via_sexp String_with_vars.to_sexp s2
]
end)
)
end))

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
4 changes: 3 additions & 1 deletion src/blang.mli
Original file line number Diff line number Diff line change
Expand Up @@ -22,7 +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

include Dyn.S with type t := t

val decode : t Stanza.Decoder.t
47 changes: 0 additions & 47 deletions src/blang_decode.ml

This file was deleted.

4 changes: 2 additions & 2 deletions src/dune_file.ml
Original file line number Diff line number Diff line change
Expand Up @@ -322,7 +322,7 @@ end

let enabled_if =
field "enabled_if" ~default:Blang.true_
(Syntax.since Stanza.syntax (1, 4) >>> Blang_decode.decode)
(Syntax.since Stanza.syntax (1, 4) >>> Blang.decode)

module Per_module = struct
include Per_item.Make(Module.Name)
Expand Down Expand Up @@ -1895,7 +1895,7 @@ module Alias_conf = struct
and+ action = field_o "action" (located Action_dune_lang.decode)
and+ locks = field "locks" (list String_with_vars.decode) ~default:[]
and+ deps = field "deps" (Bindings.decode Dep_conf.decode) ~default:Bindings.empty
and+ enabled_if = field "enabled_if" Blang_decode.decode ~default:Blang.true_
and+ enabled_if = field "enabled_if" Blang.decode ~default:Blang.true_
in
{ name
; deps
Expand Down
2 changes: 1 addition & 1 deletion src/dune_project.ml
Original file line number Diff line number Diff line change
Expand Up @@ -182,7 +182,7 @@ end

module Opam = struct

let decode_constraint = Blang_decode.decode
let decode_constraint = Blang.decode

module Package = struct
module Name = Package.Name
Expand Down

0 comments on commit 1578721

Please sign in to comment.