Skip to content

Commit 510222b

Browse files
committed
Add support for storage transformers.
1 parent aa31327 commit 510222b

File tree

5 files changed

+173
-8
lines changed

5 files changed

+173
-8
lines changed

lib/extensions.ml

Lines changed: 95 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -187,3 +187,98 @@ module Datatype = struct
187187
| `String "nativeint" -> Ok Nativeint
188188
| _ -> Error ("Unsupported metadata data_type")
189189
end
190+
191+
type tf_error =
192+
[ `Store_read of string
193+
| `Store_write of string
194+
| `Node_invariant of string
195+
| `Json_decode of string
196+
| `Bytes_encode_error of string
197+
| `Bytes_decode_error of string
198+
| `Sharding_shape_mismatch of int array * int array * string
199+
| `Invalid_transpose_order of int array * string
200+
| `Gzip of Ezgzip.error
201+
| `Grid of grid_info ]
202+
203+
type range = ByteRange of int * int option
204+
205+
module type STORAGE_TRANSFORMER = sig
206+
type t
207+
val get : t -> string -> (string, [> tf_error]) result
208+
val set : t -> string -> string -> unit
209+
val erase : t -> string -> unit
210+
end
211+
212+
module StorageTransformers = struct
213+
type transformer =
214+
| Identity
215+
type t = transformer list
216+
217+
let default = [Identity]
218+
219+
let deserialize x =
220+
match
221+
Util.get_name x,
222+
Yojson.Safe.Util.(member "configuration" x)
223+
with
224+
| "identity", `Null -> Ok Identity
225+
| _ ->
226+
Error "Unsupported storage transformer name or configuration."
227+
228+
let of_yojson x =
229+
let open Util.Result_syntax in
230+
List.fold_right
231+
(fun x acc ->
232+
acc >>= fun l ->
233+
deserialize x >>| fun s ->
234+
s :: l) (Yojson.Safe.Util.to_list x) (Ok [])
235+
236+
let to_yojson x =
237+
`List
238+
(List.fold_right
239+
(fun x acc ->
240+
match x with
241+
| Identity -> acc) x [])
242+
243+
let get
244+
(type a)
245+
(module M : STORAGE_TRANSFORMER with type t = a)
246+
(store : a)
247+
(transformers : t)
248+
(key : string)
249+
=
250+
let open Util.Result_syntax in
251+
M.get store key >>| fun raw ->
252+
snd @@
253+
List.fold_right
254+
(fun x (k, v) ->
255+
match x with
256+
| Identity -> (k, v)) transformers (key, raw)
257+
258+
let set
259+
(type a)
260+
(module M : STORAGE_TRANSFORMER with type t = a)
261+
(store : a)
262+
(transformers : t)
263+
(key : string)
264+
(value : string)
265+
=
266+
let k', v' =
267+
List.fold_left
268+
(fun (k, v) -> function
269+
| Identity -> (k, v)) (key, value) transformers
270+
in
271+
M.set store k' v'
272+
273+
let erase
274+
(type a)
275+
(module M : STORAGE_TRANSFORMER with type t = a)
276+
(store : a)
277+
(transformers : t)
278+
(key : string)
279+
=
280+
M.erase store @@
281+
List.fold_left
282+
(fun k -> function
283+
| Identity -> k) key transformers
284+
end

lib/extensions.mli

Lines changed: 50 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -46,3 +46,53 @@ module Datatype : sig
4646
val of_yojson : Yojson.Safe.t -> (t, string) result
4747
val to_yojson : t -> Yojson.Safe.t
4848
end
49+
50+
type tf_error =
51+
[ `Store_read of string
52+
| `Store_write of string
53+
| `Node_invariant of string
54+
| `Json_decode of string
55+
| `Bytes_encode_error of string
56+
| `Bytes_decode_error of string
57+
| `Sharding_shape_mismatch of int array * int array * string
58+
| `Invalid_transpose_order of int array * string
59+
| `Gzip of Ezgzip.error
60+
| `Grid of grid_info ]
61+
62+
type range = ByteRange of int * int option
63+
64+
module type STORAGE_TRANSFORMER = sig
65+
type t
66+
val get : t -> string -> (string, [> tf_error]) result
67+
val set : t -> string -> string -> unit
68+
val erase : t -> string -> unit
69+
end
70+
71+
module StorageTransformers : sig
72+
type transformer =
73+
| Identity
74+
type t = transformer list
75+
76+
val default : t
77+
val of_yojson : Yojson.Safe.t -> (t, string) result
78+
val to_yojson : t -> Yojson.Safe.t
79+
val get :
80+
(module STORAGE_TRANSFORMER with type t = 'a) ->
81+
'a ->
82+
t ->
83+
string ->
84+
(string, [> tf_error ]) result
85+
val set :
86+
(module STORAGE_TRANSFORMER with type t = 'a) ->
87+
'a ->
88+
t ->
89+
string ->
90+
string ->
91+
unit
92+
val erase :
93+
(module STORAGE_TRANSFORMER with type t = 'a) ->
94+
'a ->
95+
t ->
96+
string ->
97+
unit
98+
end

lib/metadata.ml

Lines changed: 15 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -112,13 +112,14 @@ module ArrayMetadata = struct
112112
;chunk_key_encoding : ChunkKeyEncoding.t
113113
;attributes : Yojson.Safe.t
114114
;dimension_names : string option list
115-
;storage_transformers : Yojson.Safe.t Util.ExtPoint.t list}
115+
;storage_transformers : StorageTransformers.t}
116116

117117
let create
118118
?(sep=`Slash)
119119
?(codecs=Codecs.Chain.default)
120120
?(dimension_names=[])
121121
?(attributes=`Null)
122+
?(storage_transformers=[StorageTransformers.Identity])
122123
~shape
123124
kind
124125
fv
@@ -134,7 +135,7 @@ module ArrayMetadata = struct
134135
;dimension_names
135136
;zarr_format = 3
136137
;node_type = "array"
137-
;storage_transformers = []
138+
;storage_transformers
138139
;fill_value = FillValue.of_kind kind fv
139140
;data_type = Datatype.of_kind kind
140141
;chunk_key_encoding = ChunkKeyEncoding.create sep}
@@ -168,6 +169,12 @@ module ArrayMetadata = struct
168169
| None -> `Null) xs
169170
in
170171
l @ [("dimension_names", `List xs')]
172+
in
173+
let l =
174+
match t.storage_transformers with
175+
| [StorageTransformers.Identity] -> l
176+
| xs ->
177+
l @ [("storage_transformers", StorageTransformers.to_yojson xs)]
171178
in `Assoc l
172179

173180
let of_yojson x =
@@ -256,8 +263,10 @@ module ArrayMetadata = struct
256263
>>= fun dimension_names ->
257264

258265
(match member "storage_transformers" x with
259-
| `Null -> Ok []
260-
| _ -> Error "storage_transformers field is not yet supported.")
266+
| `Null | `List [] ->
267+
Ok StorageTransformers.default
268+
| _ ->
269+
Error "storage_transformers field is not yet supported.")
261270
>>| fun storage_transformers ->
262271

263272
{zarr_format; shape; node_type; data_type; codecs; fill_value; chunk_grid
@@ -286,6 +295,8 @@ module ArrayMetadata = struct
286295

287296
let attributes t = t.attributes
288297

298+
let storage_transformers t = t.storage_transformers
299+
289300
let chunk_shape t =
290301
RegularGrid.chunk_shape t.chunk_grid
291302

lib/metadata.mli

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -38,6 +38,7 @@ module ArrayMetadata : sig
3838
?codecs:Codecs.Chain.t ->
3939
?dimension_names:string option list ->
4040
?attributes:Yojson.Safe.t ->
41+
?storage_transformers:Extensions.StorageTransformers.t ->
4142
shape:int array ->
4243
('a, 'b) Bigarray.kind ->
4344
'a ->
@@ -76,6 +77,10 @@ module ArrayMetadata : sig
7677
(** [attributes t] Returns a Yojson type containing user attributes assigned
7778
to the zarr array represented by [t]. *)
7879

80+
val storage_transformers : t -> Extensions.StorageTransformers.t
81+
(** [storage_transformers t] Returns the storage transformers to be applied
82+
to the keys and values of this store. *)
83+
7984
val dimension_names : t -> string option list
8085
(** [dimension_name t] returns a list of dimension names. If none are
8186
defined then an empty list is returned. *)

lib/storage/storage.ml

Lines changed: 8 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -8,6 +8,7 @@ module ArraySet = Util.ArraySet
88
module Arraytbl = Util.Arraytbl
99
module AM = Metadata.ArrayMetadata
1010
module GM = Metadata.GroupMetadata
11+
module ST = Extensions.StorageTransformers
1112

1213
module Make (M : STORE) : S with type t = M.t = struct
1314
include M
@@ -154,11 +155,12 @@ module Make (M : STORE) : S with type t = M.t = struct
154155
in
155156
let codecs = AM.codecs meta in
156157
let prefix = ArrayNode.to_key node ^ "/" in
158+
let tf = AM.storage_transformers meta in
157159
let cindices = ArraySet.of_seq @@ Arraytbl.to_seq_keys tbl in
158160
ArraySet.fold (fun idx acc ->
159161
acc >>= fun () ->
160162
let chunkkey = prefix ^ AM.chunk_key meta idx in
161-
(match get t chunkkey with
163+
(match ST.get (module M) t tf chunkkey with
162164
| Ok b ->
163165
Codecs.Chain.decode codecs repr b
164166
| Error _ ->
@@ -173,7 +175,7 @@ module Make (M : STORE) : S with type t = M.t = struct
173175
List.iter
174176
(fun (c, v) -> Ndarray.set arr c v) @@ Arraytbl.find_all tbl idx;
175177
Codecs.Chain.encode codecs arr >>| fun encoded ->
176-
set t chunkkey encoded) cindices (Ok ())
178+
ST.set (module M) t tf chunkkey encoded) cindices (Ok ())
177179

178180
let get_array
179181
: type a b.
@@ -206,6 +208,7 @@ module Make (M : STORE) : S with type t = M.t = struct
206208
let tbl = Arraytbl.create @@ Array.length pair in
207209
let prefix = ArrayNode.to_key node ^ "/" in
208210
let chain = AM.codecs meta in
211+
let tf = AM.storage_transformers meta in
209212
let repr =
210213
{kind
211214
;shape = AM.chunk_shape meta
@@ -217,7 +220,7 @@ module Make (M : STORE) : S with type t = M.t = struct
217220
| Some arr ->
218221
Ok (Ndarray.get arr coord :: l)
219222
| None ->
220-
(match get t @@ prefix ^ AM.chunk_key meta idx with
223+
(match ST.get (module M) t tf @@ prefix ^ AM.chunk_key meta idx with
221224
| Ok b ->
222225
Codecs.Chain.decode chain repr b
223226
| Error _ ->
@@ -243,8 +246,9 @@ module Make (M : STORE) : S with type t = M.t = struct
243246
ArraySet.of_list @@ AM.chunk_indices meta @@ AM.shape meta in
244247
let s' =
245248
ArraySet.of_list @@ AM.chunk_indices meta shape in
249+
let tf = AM.storage_transformers meta in
246250
ArraySet.iter
247-
(fun v -> erase t @@ pre ^ AM.chunk_key meta v)
251+
(fun v -> ST.erase (module M) t tf @@ pre ^ AM.chunk_key meta v)
248252
ArraySet.(diff s s');
249253
Ok (set t mkey @@ AM.encode @@ AM.update_shape meta shape)
250254
end

0 commit comments

Comments
 (0)