Skip to content

Commit 3cefe37

Browse files
committed
1 parent 2a034e8 commit 3cefe37

File tree

5 files changed

+201
-0
lines changed

5 files changed

+201
-0
lines changed

src/decode.ml

+94
Original file line numberDiff line numberDiff line change
@@ -286,6 +286,100 @@ module Make (Decodeable : Decodeable) :
286286
key_value_pairs_seq' string value_decoder
287287

288288

289+
module Obj = struct
290+
type t =
291+
{ context : value
292+
; map : value U.String_map.t
293+
}
294+
295+
type 'a obj = (t, 'a * t, value Error.t) Decoder.t
296+
297+
let succeed x t = Ok (x, t)
298+
299+
let bind : ('a -> 'b obj) -> 'a obj -> 'b obj =
300+
fun f dec t -> match dec t with Ok (x, t) -> f x t | Error e -> Error e
301+
302+
303+
let map f dec t =
304+
match dec t with Ok (x, t) -> Ok (f x, t) | Error e -> Error e
305+
306+
307+
let apply f dec t =
308+
match f t with
309+
| Ok (f, t) ->
310+
(match dec t with Ok (x, t) -> Ok (f x, t) | Error e -> Error e)
311+
| Error e ->
312+
Error e
313+
314+
315+
module Infix = struct
316+
let ( >>= ) x f = bind f x
317+
318+
let ( >|= ) x f = map f x
319+
320+
let ( <*> ) x f = apply f x
321+
322+
(* let monoid_product a b = map (fun x y -> (x, y)) a <*> b *)
323+
324+
let ( let+ ) = ( >|= )
325+
326+
(* let ( and+ ) = monoid_product *)
327+
328+
let ( let* ) = ( >>= )
329+
330+
(* let ( and* ) = monoid_product *)
331+
end
332+
333+
let field_opt key v_dec : 'a option obj =
334+
fun t ->
335+
match U.String_map.get key t.map with
336+
| None ->
337+
Ok (None, t)
338+
| Some value ->
339+
let m = U.String_map.remove key t.map in
340+
let t = { t with map = m } in
341+
(match v_dec value with Ok x -> Ok (Some x, t) | Error e -> Error e)
342+
343+
344+
let field key v_dec : 'a obj =
345+
fun t ->
346+
match field_opt key v_dec t with
347+
| Ok (Some x, t) ->
348+
Ok (x, t)
349+
| Ok (None, _t) ->
350+
Error
351+
(Error.make
352+
(Printf.sprintf "Expected an object with an attribute %S" key)
353+
~context:t.context )
354+
| Error e ->
355+
Error e
356+
357+
358+
let empty : unit obj =
359+
fun t ->
360+
match U.String_map.choose_opt t.map with
361+
| None ->
362+
Ok ((), t)
363+
| Some (k, _) ->
364+
Error
365+
(Error.make
366+
(Printf.sprintf
367+
"Expected an empty object, but have unconsumed field %S"
368+
k )
369+
~context:t.context )
370+
371+
372+
let run : 'a obj -> 'a decoder =
373+
fun dec context ->
374+
match key_value_pairs value context with
375+
| Ok l ->
376+
let map = U.String_map.of_list l in
377+
let t = { context; map } in
378+
dec t |> U.My_result.map (fun (x, _) -> x)
379+
| Error e ->
380+
Error e
381+
end
382+
289383
let field : string -> 'a decoder -> 'a decoder =
290384
fun key value_decoder t ->
291385
let value =

src/decoders_util.ml

+12
Original file line numberDiff line numberDiff line change
@@ -163,6 +163,18 @@ module My_list = struct
163163
aux f l (fun l -> l)
164164
end
165165

166+
module String_map = struct
167+
include Map.Make (String)
168+
169+
let add_list m l = List.fold_left (fun m (k, v) -> add k v m) m l
170+
171+
let of_list l = add_list empty l
172+
173+
let get = find_opt
174+
175+
let choose_opt m = try Some (choose m) with Not_found -> None
176+
end
177+
166178
let with_file_in file f =
167179
let ic = open_in file in
168180
try

src/decoders_util.mli

+12
Original file line numberDiff line numberDiff line change
@@ -47,6 +47,18 @@ module My_list : sig
4747
val flat_map : ('a -> 'b list) -> 'a list -> 'b list
4848
end
4949

50+
module String_map : sig
51+
type 'a t
52+
53+
val of_list : (string * 'a) list -> 'a t
54+
55+
val get : string -> 'a t -> 'a option
56+
57+
val remove : string -> 'a t -> 'a t
58+
59+
val choose_opt : 'a t -> (string * 'a) option
60+
end
61+
5062
val with_file_in : string -> (in_channel -> 'a) -> 'a
5163

5264
val read_all : in_channel -> string

src/sig.ml

+30
Original file line numberDiff line numberDiff line change
@@ -119,6 +119,36 @@ module type S = sig
119119

120120
(** {1 Object primitives} *)
121121

122+
module Obj : sig
123+
type 'a obj
124+
125+
val run : 'a obj -> 'a decoder
126+
127+
val succeed : 'a -> 'a obj
128+
129+
val bind : ('a -> 'b obj) -> 'a obj -> 'b obj
130+
131+
val map : ('a -> 'b) -> 'a obj -> 'b obj
132+
133+
val field : string -> 'a decoder -> 'a obj
134+
135+
val field_opt : string -> 'a decoder -> 'a option obj
136+
137+
val empty : unit obj
138+
139+
module Infix : sig
140+
val ( >>= ) : 'a obj -> ('a -> 'b obj) -> 'b obj
141+
142+
val ( >|= ) : 'a obj -> ('a -> 'b) -> 'b obj
143+
144+
val ( <*> ) : 'a obj -> ('a -> 'b) obj -> 'b obj
145+
146+
val ( let* ) : 'a obj -> ('a -> 'b obj) -> 'b obj
147+
148+
val ( let+ ) : 'a obj -> ('a -> 'b) -> 'b obj
149+
end
150+
end
151+
122152
val field : string -> 'a decoder -> 'a decoder
123153
(** Decode an object, requiring a particular field. *)
124154

test-yojson/main.ml

+53
Original file line numberDiff line numberDiff line change
@@ -172,13 +172,66 @@ let yojson_basic_suite =
172172
Format.asprintf "@,@[%a@]" pp_error e)
173173
in
174174

175+
let obj_test =
176+
"objects"
177+
>:: fun _test_ctxt ->
178+
let obj =
179+
Obj.(
180+
let open Infix in
181+
let* name = field "name" string in
182+
let* age = field "age" int in
183+
let* () = empty in
184+
succeed (name, age))
185+
in
186+
let decoder = Obj.run obj in
187+
let input = {| {"name": "Jim", "age": 42} |} in
188+
match decode_string decoder input with
189+
| Ok value ->
190+
assert_equal value ("Jim", 42)
191+
| Error error ->
192+
assert_string (Format.asprintf "%a" pp_error error)
193+
in
194+
195+
let obj_test_2 =
196+
"objects with remaining fields"
197+
>:: fun _test_ctxt ->
198+
let obj =
199+
Obj.(
200+
let open Infix in
201+
let* name = field "name" string in
202+
let* age = field "age" int in
203+
let* () = empty in
204+
succeed (name, age))
205+
in
206+
let decoder = Obj.run obj in
207+
let input = {| {"name": "Jim", "age": 42, "another": "thing"} |} in
208+
match decode_string decoder input with
209+
| Ok _ ->
210+
assert_string "Expected an error"
211+
| Error error ->
212+
let open Decoders in
213+
assert_equal
214+
error
215+
(Error.make
216+
{|Expected an empty object, but have unconsumed field "another"|}
217+
~context:
218+
(`Assoc
219+
[ ("name", `String "Jim")
220+
; ("age", `Int 42)
221+
; ("another", `String "thing")
222+
] ) )
223+
~printer:(fun e -> Format.asprintf "@,@[%a@]" pp_error e)
224+
in
225+
175226
"Yojson.Basic"
176227
>::: [ list_string_test
177228
; array_string_test
178229
; fix_one_of_test
179230
; mut_rec_test
180231
; string_or_floatlit_test
181232
; grouping_errors_test
233+
; obj_test
234+
; obj_test_2
182235
]
183236

184237

0 commit comments

Comments
 (0)