@@ -27,41 +27,38 @@ module Data.Codec.Argonaut
27
27
, named
28
28
, coercible
29
29
, prismaticCodec
30
- , module Exports
30
+ , module Codec
31
31
) where
32
32
33
33
import Prelude
34
34
35
- import Control.Monad.Reader (ReaderT (..), runReaderT )
36
- import Control.Monad.Writer (Writer , mapWriter , writer )
37
35
import Data.Argonaut.Core as J
38
36
import Data.Array as A
39
37
import Data.Bifunctor (bimap , lmap )
40
38
import Data.Bifunctor as BF
41
- import Data.Codec (BasicCodec , Codec , GCodec (..), basicCodec , bihoistGCodec , decode , encode )
42
- import Data.Codec (decode , encode , (<~<), (>~>), (~)) as Exports
39
+ import Data.Codec (Codec (..), Codec' )
40
+ import Data.Codec (Codec (..), Codec' , codec , codec' , decode , encode , hoist , identity , (<~<), (>~>), (~)) as Codec
43
41
import Data.Either (Either (..), note )
44
42
import Data.Generic.Rep (class Generic )
45
43
import Data.Int as I
46
44
import Data.List ((:))
47
45
import Data.List as L
48
- import Data.Maybe (Maybe (..), fromJust , maybe )
49
- import Data.Profunctor.Star (Star (..))
46
+ import Data.Maybe (Maybe (..), maybe )
50
47
import Data.String as S
51
48
import Data.String.CodeUnits as SCU
52
49
import Data.Symbol (class IsSymbol , reflectSymbol )
53
- import Data.Traversable ( traverse )
50
+ import Data.TraversableWithIndex ( traverseWithIndex )
54
51
import Data.Tuple (Tuple (..))
55
52
import Foreign.Object as FO
56
- import Partial.Unsafe (unsafePartial )
57
53
import Prim.Coerce (class Coercible )
58
54
import Prim.Row as Row
55
+ import Record.Unsafe as Record
59
56
import Safe.Coerce (coerce )
60
57
import Type.Proxy (Proxy )
61
58
import Unsafe.Coerce (unsafeCoerce )
62
59
63
60
-- | Codec type for `Json` values.
64
- type JsonCodec a = BasicCodec (Either JsonDecodeError ) J.Json a
61
+ type JsonCodec a = Codec' (Either JsonDecodeError ) J.Json a
65
62
66
63
-- | Error type for failures while decoding.
67
64
data JsonDecodeError
@@ -100,7 +97,7 @@ printJsonDecodeError err =
100
97
101
98
-- | The "identity codec" for `Json` values.
102
99
json ∷ JsonCodec J.Json
103
- json = basicCodec pure identity
100
+ json = Codec .codec' pure identity
104
101
105
102
-- | A codec for `null` values in `Json`.
106
103
null ∷ JsonCodec Unit
@@ -154,13 +151,10 @@ jobject = jsonPrimCodec "Object" J.toObject J.fromObject
154
151
-- | codecIntArray = CA.array CA.int
155
152
-- | ```
156
153
array ∷ ∀ a . JsonCodec a → JsonCodec (Array a )
157
- array codec = GCodec dec enc
158
- where
159
- dec = ReaderT \j →
160
- traverse (\(Tuple ix j') → BF .lmap (AtIndex ix) (decode codec j'))
161
- <<< A .mapWithIndex Tuple
162
- =<< decode jarray j
163
- enc = Star \xs → writer $ Tuple xs (J .fromArray (map (encode codec) xs))
154
+ array codec =
155
+ Codec .codec'
156
+ (\j → traverseWithIndex (\ix j' → BF .lmap (AtIndex ix) (Codec .decode codec j')) =<< Codec .decode jarray j)
157
+ (\a → J .fromArray (map (Codec .encode codec) a))
164
158
165
159
-- | Codec type for specifically indexed `JArray` elements.
166
160
type JIndexedCodec a =
@@ -189,20 +183,17 @@ type JIndexedCodec a =
189
183
-- | <*> _.age ~ CA.index 1 CA.int
190
184
-- | ```
191
185
indexedArray ∷ ∀ a . String → JIndexedCodec a → JsonCodec a
192
- indexedArray name =
193
- bihoistGCodec
194
- (\r → ReaderT ( BF . lmap (Named name) <<< runReaderT r <=< decode jarray))
195
- (mapWriter ( BF .rmap ( J .fromArray <<< A .fromFoldable)))
186
+ indexedArray name codec =
187
+ Codec .codec'
188
+ (\j → lmap (Named name) ( Codec .decode codec =<< Codec . decode jarray j ))
189
+ (\a → Codec .encode jarray ( A .fromFoldable ( Codec .encode codec a )))
196
190
197
191
-- | A codec for an item in an `indexedArray`.
198
192
index ∷ ∀ a . Int → JsonCodec a → JIndexedCodec a
199
- index ix codec = GCodec dec enc
200
- where
201
- dec = ReaderT \xs →
202
- BF .lmap (AtIndex ix) case A .index xs ix of
203
- Just val → decode codec val
204
- Nothing → Left MissingValue
205
- enc = Star \val → writer $ Tuple val (pure (encode codec val))
193
+ index ix codec =
194
+ Codec .codec
195
+ (\xs → BF .lmap (AtIndex ix) (maybe (Left MissingValue ) (Codec .decode codec) (A .index xs ix)))
196
+ (pure <<< Codec .encode codec)
206
197
207
198
-- | Codec type for `JObject` prop/value pairs.
208
199
type JPropCodec a =
@@ -218,23 +209,17 @@ type JPropCodec a =
218
209
-- | See also `Data.Codec.Argonaut.Record.object` for a more commonly useful
219
210
-- | version of this function.
220
211
object ∷ ∀ a . String → JPropCodec a → JsonCodec a
221
- object name =
222
- bihoistGCodec
223
- (\r → ReaderT ( BF . lmap (Named name) <<< runReaderT r <=< decode jobject))
224
- (mapWriter ( BF .rmap ( J .fromObject <<< FO .fromFoldable)))
212
+ object name codec =
213
+ Codec .codec'
214
+ (\j → lmap (Named name) ( Codec .decode codec =<< Codec . decode jobject j ))
215
+ (\a → Codec .encode jobject ( FO .fromFoldable ( Codec .encode codec a )))
225
216
226
217
-- | A codec for a property of an object.
227
218
prop ∷ ∀ a . String → JsonCodec a → JPropCodec a
228
- prop key codec = GCodec dec enc
229
- where
230
- dec ∷ ReaderT (FO.Object J.Json ) (Either JsonDecodeError ) a
231
- dec = ReaderT \obj →
232
- BF .lmap (AtKey key) case FO .lookup key obj of
233
- Just val → decode codec val
234
- Nothing → Left MissingValue
235
-
236
- enc ∷ Star (Writer (L.List (Tuple String J.Json ))) a a
237
- enc = Star \val → writer $ Tuple val (pure (Tuple key (encode codec val)))
219
+ prop key codec =
220
+ Codec .codec
221
+ (\obj → BF .lmap (AtKey key) (maybe (Left MissingValue ) (Codec .decode codec) (FO .lookup key obj)))
222
+ (pure <<< Tuple key <<< Codec .encode codec)
238
223
239
224
-- | The starting value for a object-record codec. Used with `recordProp` it
240
225
-- | provides a convenient method for defining codecs for record types that
@@ -258,7 +243,7 @@ prop key codec = GCodec dec enc
258
243
-- | See also `Data.Codec.Argonaut.Record.object` for a more commonly useful
259
244
-- | version of this function.
260
245
record ∷ JPropCodec { }
261
- record = GCodec ( pure {}) ( Star \val → writer ( Tuple val L.Nil ))
246
+ record = Codec (const ( pure {})) pure
262
247
263
248
-- | Used with `record` to define codecs for record types that encode into JSON
264
249
-- | objects of the same shape. See the comment on `record` for an example.
@@ -271,31 +256,24 @@ recordProp
271
256
→ JPropCodec (Record r )
272
257
→ JPropCodec (Record r' )
273
258
recordProp p codecA codecR =
274
- let key = reflectSymbol p in GCodec (dec' key) (enc' key)
259
+ let key = reflectSymbol p in Codec .codec (dec' key) (enc' key)
275
260
where
276
- dec' ∷ String → ReaderT ( FO.Object J.Json ) ( Either JsonDecodeError ) (Record r' )
277
- dec' key = ReaderT \ obj → do
278
- r ← decode codecR obj
261
+ dec' ∷ String → FO.Object J.Json → Either JsonDecodeError (Record r' )
262
+ dec' key obj = do
263
+ r ← Codec . decode codecR obj
279
264
a ← BF .lmap (AtKey key) case FO .lookup key obj of
280
- Just val → decode codecA val
265
+ Just val → Codec . decode codecA val
281
266
Nothing → Left MissingValue
282
- pure $ unsafeSet key a r
267
+ pure $ Record . unsafeSet key a r
283
268
284
- enc' ∷ String → Star (Writer (L.List (Tuple String J.Json ))) (Record r' ) (Record r' )
285
- enc' key = Star \val →
286
- writer $ Tuple val
287
- $ Tuple key (encode codecA (unsafeGet key val))
288
- : encode codecR (unsafeForget val)
269
+ enc' ∷ String → Record r' → L.List (Tuple String J.Json )
270
+ enc' key val =
271
+ Tuple key (Codec .encode codecA (Record .unsafeGet key val))
272
+ : Codec .encode codecR (unsafeForget val)
289
273
290
274
unsafeForget ∷ Record r' → Record r
291
275
unsafeForget = unsafeCoerce
292
276
293
- unsafeSet ∷ String → a → Record r → Record r'
294
- unsafeSet key a = unsafeCoerce <<< FO .insert key a <<< unsafeCoerce
295
-
296
- unsafeGet ∷ String → Record r' → a
297
- unsafeGet s = unsafePartial fromJust <<< FO .lookup s <<< unsafeCoerce
298
-
299
277
-- | Used with `record` to define an optional field.
300
278
-- |
301
279
-- | This will only decode the property as `Nothing` if the field does not exist
@@ -311,41 +289,31 @@ recordPropOptional
311
289
→ JsonCodec a
312
290
→ JPropCodec (Record r )
313
291
→ JPropCodec (Record r' )
314
- recordPropOptional p codecA codecR =
315
- let key = reflectSymbol p in GCodec (dec' key) (enc' key)
292
+ recordPropOptional p codecA codecR = Codec .codec dec' enc'
316
293
where
317
- dec' ∷ String → ReaderT (FO.Object J.Json ) (Either JsonDecodeError ) (Record r' )
318
- dec' key = ReaderT \obj → do
319
- r ← decode codecR obj
294
+ key ∷ String
295
+ key = reflectSymbol p
296
+
297
+ dec' ∷ FO.Object J.Json → Either JsonDecodeError (Record r' )
298
+ dec' obj = do
299
+ r ← Codec .decode codecR obj
320
300
a ← BF .lmap (AtKey key) case FO .lookup key obj of
321
- Just val → Just <$> decode codecA val
301
+ Just val → Just <$> Codec . decode codecA val
322
302
_ → Right Nothing
323
- pure $ unsafeSet key a r
303
+ pure $ Record . unsafeSet key a r
324
304
325
- enc' ∷ String → Star ( Writer ( L.List (Tuple String J.Json ))) ( Record r' ) ( Record r' )
326
- enc' key = Star \ val → do
327
- let w = encode codecR (unsafeForget val)
328
- writer $ Tuple val case unsafeGet key val of
329
- Just a → Tuple key (encode codecA a) : w
305
+ enc' ∷ Record r' → L.List (Tuple String J.Json )
306
+ enc' val = do
307
+ let w = Codec . encode codecR (unsafeForget val)
308
+ case Record . unsafeGet key val of
309
+ Just a → Tuple key (Codec . encode codecA a) : w
330
310
Nothing → w
331
311
332
312
unsafeForget ∷ Record r' → Record r
333
313
unsafeForget = unsafeCoerce
334
314
335
- unsafeSet ∷ String → Maybe a → Record r → Record r'
336
- unsafeSet key a = unsafeCoerce <<< FO .insert key a <<< unsafeCoerce
337
-
338
- unsafeGet ∷ String → Record r' → Maybe a
339
- unsafeGet s = unsafePartial fromJust <<< FO .lookup s <<< unsafeCoerce
340
-
341
- jsonPrimCodec
342
- ∷ ∀ a
343
- . String
344
- → (J.Json → Maybe a )
345
- → (a → J.Json )
346
- → JsonCodec a
347
- jsonPrimCodec ty f =
348
- basicCodec (maybe (Left (TypeMismatch ty)) pure <<< f)
315
+ jsonPrimCodec ∷ ∀ a . String → (J.Json → Maybe a ) → (a → J.Json ) → JsonCodec a
316
+ jsonPrimCodec ty f = Codec .codec' (maybe (Left (TypeMismatch ty)) pure <<< f)
349
317
350
318
-- | Helper function for defining recursive codecs in situations where the codec
351
319
-- | definition causes a _"The value of <codec> is undefined here"_ error.
@@ -370,27 +338,27 @@ jsonPrimCodec ty f =
370
338
-- | ```
371
339
fix ∷ ∀ a . (JsonCodec a → JsonCodec a ) → JsonCodec a
372
340
fix f =
373
- basicCodec
374
- (\x → decode (f (fix f)) x)
375
- (\x → encode (f (fix f)) x)
341
+ Codec .codec'
342
+ (\x → Codec . decode (f (fix f)) x)
343
+ (\x → Codec . encode (f (fix f)) x)
376
344
377
345
-- | A codec for introducing names into error messages - useful when definiting a codec for a type
378
346
-- | synonym for a record, for instance.
379
- named ∷ ∀ a . String → JsonCodec a -> JsonCodec a
347
+ named ∷ ∀ a . String → JsonCodec a → JsonCodec a
380
348
named name codec =
381
- basicCodec
382
- (lmap (Named name) <<< decode codec)
383
- (encode codec)
349
+ Codec .codec'
350
+ (lmap (Named name) <<< Codec . decode codec)
351
+ (Codec . encode codec)
384
352
385
353
-- | A codec for types that can be safely coerced.
386
354
-- |
387
355
-- | Accepts the name of the target type as an argument to improve error messaging when the inner
388
356
-- | codec fails.
389
357
coercible ∷ ∀ a b . Coercible a b ⇒ String → JsonCodec a → JsonCodec b
390
358
coercible name codec =
391
- basicCodec
392
- (bimap (Named name) coerce <<< decode codec)
393
- (coerce (encode codec))
359
+ Codec .codec'
360
+ (bimap (Named name) coerce <<< Codec . decode codec)
361
+ (coerce (Codec . encode codec))
394
362
395
363
-- | Adapts an existing codec with a pair of functions to allow a value to be
396
364
-- | further refined. If the inner decoder fails an `UnexpectedValue` error will
@@ -432,7 +400,7 @@ coercible name codec =
432
400
-- | Although for this latter case there are some other options too, in the form
433
401
-- | of `Data.Codec.Argonaut.Generic.nullarySum` and `Data.Codec.Argonaut.Sum.enumSum`.
434
402
prismaticCodec ∷ ∀ a b . String → (a → Maybe b ) → (b → a ) → JsonCodec a → JsonCodec b
435
- prismaticCodec name f g orig =
436
- basicCodec
437
- (\json' → note (Named name (UnexpectedValue json' )) <<< f =<< decode orig json' )
438
- (encode orig <<< g)
403
+ prismaticCodec name f g codec =
404
+ Codec .codec'
405
+ (\j → note (Named name (UnexpectedValue j )) <<< f =<< Codec . decode codec j )
406
+ (Codec . encode codec <<< g)
0 commit comments