Skip to content

Commit

Permalink
Fix configurator on older versions
Browse files Browse the repository at this point in the history
Signed-off-by: Rudi Grinberg <me@rgrinberg.com>
  • Loading branch information
rgrinberg committed Sep 5, 2020
1 parent 722a847 commit 4dec79c
Show file tree
Hide file tree
Showing 3 changed files with 19 additions and 2 deletions.
4 changes: 4 additions & 0 deletions .github/workflows/workflow.yml
Original file line number Diff line number Diff line change
Expand Up @@ -84,3 +84,7 @@ jobs:
- name: test source is well formatted
run: opam exec -- make fmt
if: env.OCAML_VERSION == '4.10.0' && env.OS == 'ubuntu-latest'

- name: build configurator
run: opam install ./dune-configurator.opam
if: env.CONFIGURATOR == 'true'
15 changes: 14 additions & 1 deletion otherlibs/configurator/src/import.ml
Original file line number Diff line number Diff line change
Expand Up @@ -100,7 +100,20 @@ module Bool = struct
end

module Map (S : Map.OrderedType) = struct
include MoreLabels.Map.Make (S)
module M = MoreLabels.Map.Make (S)
include M

let update (type a) (t : a t) (key : M.key) ~(f : a option -> a option) : a t
=
let v =
match find key t with
| exception Not_found -> None
| v -> Some v
in
match (f v, v) with
| None, None -> t
| None, Some _ -> remove key t
| Some data, _ -> add ~key ~data t

let find m k =
match find k m with
Expand Down
2 changes: 1 addition & 1 deletion otherlibs/configurator/src/v1.ml
Original file line number Diff line number Diff line change
Expand Up @@ -529,7 +529,7 @@ const char *s%i = "BEGIN-%i-false-END";
let values =
Io.with_lexbuf_from_file obj_file ~f:(Extract_obj.extract [])
|> List.fold_left ~init:Int.Map.empty ~f:(fun acc (key, v) ->
Int.Map.update acc ~key ~f:(function
Int.Map.update acc key ~f:(function
| None -> Some [ v ]
| Some vs -> Some (v :: vs)))
in
Expand Down

0 comments on commit 4dec79c

Please sign in to comment.