Skip to content

Commit 9326539

Browse files
authored
Merge pull request #22 from garyb/more-docs
More docs
2 parents 1bece68 + b1acb93 commit 9326539

File tree

6 files changed

+394
-59
lines changed

6 files changed

+394
-59
lines changed

README.md

Lines changed: 183 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -5,7 +5,9 @@
55

66
Bi-directional codecs for [argonaut](https://github.com/purescript-contrib/purescript-argonaut-core).
77

8-
This library is build on `purescript-codec` and offers a different approach to dealing with JSON encoding/decoding than `purescript-argonaut-codecs`. Instead of using type classes, codecs are constructed as values explicitly. As long as the basic codec values provided by this library are used, the codecs are guaranteed to roundtrip succesfully.
8+
This library is build on [`purescript-codec`](https://github.com/garyb/purescript-codec) and offers a different approach to dealing with JSON encoding/decoding than [`purescript-argonaut-codecs`](https://github.com/purescript-contrib/purescript-argonaut-codecs). Instead of using type classes, codecs are constructed as values explicitly. As long as the basic codec values provided by this library are used, the codecs are guaranteed to roundtrip successfully.
9+
10+
The errors reported from this library are a little better than those provided by `purescript-argonaut-codecs` too - they contain the full JSON structure to the point of failure, and the error can be inspected as a value before being printed as a string.
911

1012
For more information on the motivation behind this library, I [wrote a bit about my problems with typeclass codecs](http://code.slipthrough.net/2018/03/13/thoughts-on-typeclass-codecs/) previously.
1113

@@ -15,6 +17,186 @@ For more information on the motivation behind this library, I [wrote a bit about
1517
bower install purescript-codec-argonaut
1618
```
1719

20+
## Usage
21+
22+
As [`JsonCodec`](https://pursuit.purescript.org/packages/purescript-codec-argonaut/docs/Data.Codec.Argonaut#t:JsonCodec)s are values, they need to be fed into the [`encode`](https://pursuit.purescript.org/packages/purescript-codec/docs/Data.Codec/#v:encode) or [`decode`](https://pursuit.purescript.org/packages/purescript-codec/docs/Data.Codec/#v:decode) function provided by [`Data.Codec`](https://pursuit.purescript.org/packages/purescript-codec/docs/Data.Codec) (and re-exported by [`Data.Codec.Argonaut`](https://pursuit.purescript.org/packages/purescript-codec-argonaut/docs/Data.Codec.Argonaut)):
23+
24+
``` purescript
25+
import Data.Argonaut.Core as J
26+
import Data.Codec.Argonaut as CA
27+
import Data.Either (Either)
28+
29+
encodeString ∷ String → J.Json
30+
encodeString = CA.encode CA.string
31+
32+
decodeString ∷ J.Json → Either CA.JsonDecodeError String
33+
decodeString = CA.decode CA.string
34+
```
35+
36+
### Basic codecs
37+
38+
A number of codecs are provided for basic types such as `Boolean`, `Number`, `Int`, `String`, `CodePoint`, `Char`, and are named as such but starting lowercase. So [`CA.boolean`](https://pursuit.purescript.org/packages/purescript-codec-argonaut/docs/Data.Codec.Argonaut#v:boolean), [`CA.number`](https://pursuit.purescript.org/packages/purescript-codec-argonaut/docs/Data.Codec.Argonaut#v:number), and so on.
39+
40+
There is also a `Json` "identity" codec called [`CA.json`](https://pursuit.purescript.org/packages/purescript-codec-argonaut/docs/Data.Codec.Argonaut#v:json) that just passes the value through either way. This is sometimes useful when building up a larger codec. More on that in a moment.
41+
42+
The final two basic codecs are [`CA.null`](https://pursuit.purescript.org/packages/purescript-codec-argonaut/docs/Data.Codec.Argonaut#v:null), which decodes to `Unit` in PureScript and encodes to `null` in JSON, and [`CA.void`](https://pursuit.purescript.org/packages/purescript-codec-argonaut/docs/Data.Codec.Argonaut#v:void), which is an eliminator for `Void` in PureScript and will never actualy encode or decode anything since `Void` is uninhabited. This is another codec that is primarily intended for use in larger codecs.
43+
44+
So far so boring. Things only start getting interesting or useful when we can build up larger codecs for our data model or serialization format, which is where compound codecs come in to play.
45+
46+
### Arrays
47+
48+
The simplest compound codec provided by the library is [`CA.array`](https://pursuit.purescript.org/packages/purescript-codec-argonaut/docs/Data.Codec.Argonaut#v:array), which accepts another codec, and encodes/decodes an arbitrary length array where all the items match the inner codec. For example:
49+
50+
``` purescript
51+
import Data.Codec.Argonaut as CA
52+
53+
codec ∷ CA.JsonCodec (Array String)
54+
codec = CA.array CA.string
55+
```
56+
57+
### Objects
58+
59+
Probably the most useful compound codec is for `Record`, this will generally be the building block of most codecs. There are a few different ways to define these codecs, but the most convenient is the [`record`](https://pursuit.purescript.org/packages/purescript-codec-argonaut/docs/Data.Codec.Argonaut.Record#v:record) function provided by [`Data.Codec.Argonaut.Record`](https://pursuit.purescript.org/packages/purescript-codec-argonaut/docs/Data.Codec.Argonaut.Record):
60+
61+
``` purescript
62+
import Data.Codec.Argonaut as CA
63+
import Data.Codec.Argonaut.Record as CAR
64+
65+
type Person = { name ∷ String, age ∷ Int, active ∷ Boolean }
66+
67+
codec ∷ CA.JsonCodec Person
68+
codec =
69+
CA.object "Person"
70+
(CAR.record
71+
{ name: CA.string
72+
, age: CA.int
73+
, active: CA.boolean
74+
})
75+
```
76+
77+
Note we also used a [`CA.object`](https://pursuit.purescript.org/packages/purescript-codec-argonaut/docs/Data.Codec.Argonaut#v:object) wrapping this [`CAR.record`](https://pursuit.purescript.org/packages/purescript-codec-argonaut/docs/Data.Codec.Argonaut.Record#v:record). This allows us to name the record, for help when debugging decode failures, but is also because [`CAR.record`](https://pursuit.purescript.org/packages/purescript-codec-argonaut/docs/Data.Codec.Argonaut.Record#v:record) produces a [`JPropCodec`](https://pursuit.purescript.org/packages/purescript-codec-argonaut/docs/Data.Codec.Argonaut#t:JPropCodec) rather than a [`JsonCodec`](https://pursuit.purescript.org/packages/purescript-codec-argonaut/docs/Data.Codec.Argonaut#t:JsonCodec) directly. There are some other options for constructing and working with [`JPropCodec`](https://pursuit.purescript.org/packages/purescript-codec-argonaut/docs/Data.Codec.Argonaut#t:JPropCodec) values, but that's out of the scope of this README.
78+
79+
The codec will encode/decode JSON objects of the same shape as the defining record. For example:
80+
81+
``` json
82+
{ "name": "Rashida", "age": 37, "active": true }
83+
```
84+
85+
It's possible to encode/decode records that include properties with spaces and/or symbols in the name, or reserved names, by quoting the fields in the type and definition:
86+
87+
``` purescript
88+
type Person = { "Name" ∷ String, age ∷ Int, "is active" ∷ Boolean }
89+
90+
codec ∷ CA.JsonCodec Person
91+
codec =
92+
CA.object "Person"
93+
(CAR.record
94+
{ "Name": CA.string
95+
, age: CA.int
96+
, "is active": CA.boolean
97+
})
98+
```
99+
100+
### Sum types and variants
101+
102+
This library comes with codec support for [`purescript-variant`](https://github.com/natefaubion/purescript-variant) out of the box and codecs for sums are often based on the variant codec.
103+
104+
First of all, variants. Similar to the object/record case there are a few options for defining variant codecs, but most commonly they will be defined with [`variantMatch`](https://pursuit.purescript.org/packages/purescript-codec-argonaut/docs/Data.Codec.Argonaut.Variant#v:variantMatch) provided by [`Data.Codec.Argonaut.Variant`](https://pursuit.purescript.org/packages/purescript-codec-argonaut/docs/Data.Codec.Argonaut.Variant):
105+
106+
``` purescript
107+
import Prelude
108+
109+
import Data.Codec.Argonaut as CA
110+
import Data.Codec.Argonaut.Variant as CAV
111+
import Data.Either (Either(..))
112+
import Data.Variant as V
113+
114+
type SomeValue = V.Variant
115+
( str ∷ String
116+
, int ∷ Int
117+
, neither ∷ Unit
118+
)
119+
120+
codec ∷ CA.JsonCodec SomeValue
121+
codec = CAV.variantMatch
122+
{ str: Right CA.string
123+
, int: Right CA.int
124+
, neither: Left unit
125+
}
126+
```
127+
128+
The fields in the record passed to [`CAV.variantMatch`](https://pursuit.purescript.org/packages/purescript-codec-argonaut/docs/Data.Codec.Argonaut.Variant#v:variantMatch) correspond with the variant constructors. Each one accepts an `Either` carrying either a codec or a static value - `Right` with a codec for when there's a value that needs encoding for the constructor, `Left` with a static value for nullary constructors.
129+
130+
The variant codec is a little opinionated since there's no exactly corresponding JSON structure for sums. The encoding looks something like:
131+
132+
``` json
133+
{ "tag": <constructorName>, "value": <value> }
134+
```
135+
136+
`value` will be omitted for nullary / `Left`-defined constructors. At the moment it is not possible to customise the encoding for variant types, so they may not be suitable if you are not in control of the serialization format.
137+
138+
Sum type encoding is usually handled by building a variant codec, and then using [`dimap`](https://pursuit.purescript.org/packages/purescript-profunctor/docs/Data.Profunctor#v:dimap) to inject into/project out of a corresponding sum type:
139+
140+
``` purescript
141+
import Prelude
142+
143+
import Data.Codec.Argonaut as CA
144+
import Data.Codec.Argonaut.Variant as CAV
145+
import Data.Either (Either(..))
146+
import Data.Profunctor (dimap)
147+
import Data.Symbol (SProxy(..))
148+
import Data.Variant as V
149+
150+
data SomeValue2 = Str String | Int Int | Neither
151+
152+
codec ∷ CA.JsonCodec SomeValue2
153+
codec =
154+
dimap toVariant fromVariant $ CAV.variantMatch
155+
{ str: Right CA.string
156+
, int: Right CA.int
157+
, neither: Left unit
158+
}
159+
where
160+
toVariant = case _ of
161+
Str s → V.inj (SProxy ∷ _ "str") s
162+
Int i → V.inj (SProxy ∷ _ "int") i
163+
Neither → V.inj (SProxy ∷ _ "neither") unit
164+
fromVariant = V.match
165+
{ str: Str
166+
, int: Int
167+
, neither: \_ → Neither
168+
}
169+
```
170+
171+
This certainly is a little boilerplate-y, but at least when defining codecs this way you do gain the benefits of having a single definition that aligns the encoding and decoding behaviour. This means, assuming there are no mixups in `toVariant`/`fromVariant`, the guaranteed roundtripping is preserved. Often it's not even possible to have mixups during `dimap`, since the sum constructor types will all differ.
172+
173+
If you have a sum type that only consists of nullary constructors and it has a [`Generic`](https://pursuit.purescript.org/packages/purescript-generics-rep/docs/Data.Generic.Rep#t:Generic) instance defined, [`nullarySum`](https://pursuit.purescript.org/packages/purescript-codec-argonaut/docs/Data.Codec.Argonaut.Generic#v:nullarySum) provided by [`Data.Codec.Argonaut.Generic`](https://pursuit.purescript.org/packages/purescript-codec-argonaut/docs/Data.Codec.Argonaut.Generic) can generate a codec that will encode the constructors as string values matching the constructor names in the JSON.
174+
175+
The story for sum type codecs outside of these options isn't great just now. There are some functions provided in [`Data.Codec.Argonaut.Sum`](https://pursuit.purescript.org/packages/purescript-codec-argonaut/docs/Data.Codec.Argonaut.Sum) for defining them, but these are more error prone than the variant method, and use the same encoding methods described above. Often it's just as easy to construct a codec from scratch with [`basicCodec`](https://pursuit.purescript.org/packages/purescript-codec/docs/Data.Codec#v:basicCodec) from [`Data.Codec`](https://pursuit.purescript.org/packages/purescript-codec/docs/Data.Codec), although means it's up to you to ensure the roundtrip succeeds.
176+
177+
### Other common types
178+
179+
The library provides a [`Data.Codec.Argonaut.Common`](https://pursuit.purescript.org/packages/purescript-codec-argonaut/docs/Data.Codec.Argonaut.Common) module with codecs for `Maybe`, `Either`, `Tuple`, and so on. These codecs are somewhat opinionated, so only suitable for cases when you are in control of the serialization format.
180+
181+
There is also a [`Data.Codec.Argonaut.Compat`](https://pursuit.purescript.org/packages/purescript-codec-argonaut/docs/Data.Codec.Argonaut.Compat) module provided for codecs that need to preserve compatibility with the encoding using by [`purescript-argonaut-codecs`](https://github.com/purescript-contrib/purescript-argonaut-codecs). These codecs have some issues, like the inability to accurately encode nested `Maybe`s, so if possible, `Common` should be preferred.
182+
183+
### "Prismatic" codecs
184+
185+
If you have a type with a pair of functions like the `preview` and `view` that make up a prism (`preview :: a -> Maybe b`, `view :: b -> a`), you can use these to adapt an existing codec to further refine it.
186+
187+
For example, to adapt the [`CA.string`](https://pursuit.purescript.org/packages/purescript-codec-argonaut/docs/Data.Codec.Argonaut#v:string) codec to only work for `NonEmptyString`s:
188+
189+
``` purescript
190+
import Data.Codec.Argonaut as CA
191+
import Data.String.NonEmpty (NonEmptyString)
192+
import Data.String.NonEmpty as NES
193+
194+
codec ∷ CA.JsonCodec NonEmptyString
195+
codec = CA.prismaticCodec NES.fromString NES.toString CA.string
196+
```
197+
198+
See the documentation for [another example](https://pursuit.purescript.org/packages/purescript-codec-argonaut/docs/Data.Codec.Argonaut#v:prismaticCodec) of how [`CA.prismaticCodec`](https://pursuit.purescript.org/packages/purescript-codec-argonaut/docs/Data.Codec.Argonaut#v:prismaticCodec) might be used. The main downside to [`CA.prismaticCodec`](https://pursuit.purescript.org/packages/purescript-codec-argonaut/docs/Data.Codec.Argonaut#v:prismaticCodec) is the error reporting for the `Nothing` case might not be good as it otherwise could be, since [`UnexpectedValue`](https://pursuit.purescript.org/packages/purescript-codec-argonaut/docs/Data.Codec.Argonaut#t:JsonDecodeError) is the only information we have at that point.
199+
18200
## Documentation
19201

20202
Module documentation is [published on Pursuit](http://pursuit.purescript.org/packages/purescript-codec-argonaut).

src/Data/Codec/Argonaut.purs

Lines changed: 71 additions & 21 deletions
Original file line numberDiff line numberDiff line change
@@ -8,6 +8,7 @@ module Data.Codec.Argonaut
88
, number
99
, int
1010
, string
11+
, codePoint
1112
, char
1213
, jarray
1314
, jobject
@@ -34,7 +35,7 @@ import Data.Argonaut.Core as J
3435
import Data.Array as A
3536
import Data.Bifunctor as BF
3637
import Data.Codec (BasicCodec, Codec, GCodec(..), basicCodec, bihoistGCodec, decode, encode)
37-
import Data.Codec (decode, encode, (~), (<~<)) as Exports
38+
import Data.Codec (decode, encode, (~), (<~<), (>~>)) as Exports
3839
import Data.Either (Either(..), note)
3940
import Data.Generic.Rep (class Generic)
4041
import Data.Int as I
@@ -136,12 +137,15 @@ jarray = jsonPrimCodec "Array" J.toArray J.fromArray
136137
jobject JsonCodec (FO.Object J.Json)
137138
jobject = jsonPrimCodec "Object" J.toObject J.fromObject
138139

139-
-- | A codec for `Array` values.
140-
-- |```purescript
141-
-- | decodeIntArray ∷ Json → Either JsonDecodeError (Array Int)
142-
-- | decodeIntArray = decode (array int)
143-
-- |```
144-
140+
-- | A codec for arbitrary length `Array`s where every item in the array
141+
-- | shares the same type.
142+
-- |
143+
-- | ``` purescript
144+
-- | import Data.Codec.Argonaut as CA
145+
-- |
146+
-- | codecIntArray ∷ CA.JsonCodec (Array Int)
147+
-- | codecIntArray = CA.array CA.int
148+
-- | ```
145149
array a. JsonCodec a JsonCodec (Array a)
146150
array codec = GCodec dec enc
147151
where
@@ -161,16 +165,20 @@ type JIndexedCodec a =
161165

162166
-- | A codec for types that are encoded as an array with a specific layout.
163167
-- |
164-
-- | For example, given that we'd like to encode a Person as a 2-element array,
165-
-- | like so `[ "Karl", 25 ]`, we could write the following codec:
168+
-- | For example, if we'd like to encode a `Person` as a 2-element array, like
169+
-- | `["Rashida", 37]`, we could write the following codec:
166170
-- |
167171
-- | ```purescript
172+
-- | import Data.Codec ((~))
173+
-- | import Data.Codec.Argonaut as CA
174+
-- |
168175
-- | type Person = { name ∷ String, age ∷ Int }
169176
-- |
170-
-- | JA.indexedArray "Test Object" $
177+
-- | codecPerson ∷ CA.JsonCodec Person
178+
-- | codecPerson = CA.indexedArray "Test Object" $
171179
-- | { name: _, age: _ }
172-
-- | <$> _.name ~ index 0 JA.string
173-
-- | <*> _.age ~ index 1 JA.int
180+
-- | <$> _.name ~ CA.index 0 CA.string
181+
-- | <*> _.age ~ CA.index 1 CA.int
174182
-- | ```
175183
indexedArray a. String JIndexedCodec a JsonCodec a
176184
indexedArray name =
@@ -197,6 +205,9 @@ type JPropCodec a =
197205
a a
198206

199207
-- | A codec for objects that are encoded with specific properties.
208+
-- |
209+
-- | See also `Data.Codec.Argonaut.Record.object` for a more commonly useful
210+
-- | version of this function.
200211
object a. String JPropCodec a JsonCodec a
201212
object name =
202213
bihoistGCodec
@@ -219,13 +230,23 @@ prop key codec = GCodec dec enc
219230
-- | provides a convenient method for defining codecs for record types that
220231
-- | encode into JSON objects of the same shape.
221232
-- |
222-
-- | For example:
233+
-- | For example, to encode a record as the JSON object
234+
-- | `{ "name": "Karl", "age": 25 }` we would define a codec like this:
223235
-- | ```
224-
-- | myRecordCodec =
225-
-- | object "MyRecord" $ record
226-
-- | # recordProp (SProxy :: SProxy "tag") tagCodec
227-
-- | # recordProp (SProxy :: SProxy "value") valueCodec
236+
-- | import Data.Codec.Argonaut as CA
237+
-- | import Data.Symbol (SProxy(..))
238+
-- |
239+
-- | type Person = { name ∷ String, age ∷ Int }
240+
-- |
241+
-- | codecPerson ∷ CA.JsonCodec Person
242+
-- | codecPerson =
243+
-- | CA.object "Person" $ CA.record
244+
-- | # CA.recordProp (SProxy :: _ "name") CA.string
245+
-- | # CA.recordProp (SProxy :: _ "age") CA.int
228246
-- | ```
247+
-- |
248+
-- | See also `Data.Codec.Argonaut.Record.object` for a more commonly useful
249+
-- | version of this function.
229250
record JPropCodec {}
230251
record = GCodec (pure {}) (Star \val → writer (Tuple val L.Nil))
231252

@@ -270,7 +291,27 @@ jsonPrimCodec
270291
jsonPrimCodec ty f =
271292
basicCodec (maybe (Left (TypeMismatch ty)) pure <<< f)
272293

273-
-- | Helper function for defining recursive codecs.
294+
-- | Helper function for defining recursive codecs in situations where the codec
295+
-- | definition causes a _"The value of <codec> is undefined here"_ error.
296+
-- |
297+
-- | ```purescript
298+
-- | import Data.Codec.Argonaut as CA
299+
-- | import Data.Codec.Argonaut.Common as CAC
300+
-- | import Data.Codec.Argonaut.Record as CAR
301+
-- | import Data.Maybe (Maybe)
302+
-- | import Data.Newtype (class Newtype)
303+
-- | import Data.Profunctor (wrapIso)
304+
-- |
305+
-- | newtype IntList = IntList { cell ∷ Int, rest ∷ Maybe IntList }
306+
-- |
307+
-- | derive instance newtypeLoopyList ∷ Newtype IntList _
308+
-- |
309+
-- | codecIntList ∷ CA.JsonCodec IntList
310+
-- | codecIntList =
311+
-- | CA.fix \codec →
312+
-- | wrapIso IntList $
313+
-- | CAR.object "IntList" { cell: CA.int, rest: CAC.maybe codec }
314+
-- | ```
274315
fix a. (JsonCodec a JsonCodec a) JsonCodec a
275316
fix f =
276317
basicCodec
@@ -284,9 +325,15 @@ fix f =
284325
-- | This function is named as such as the pair of functions it accepts
285326
-- | correspond with the `preview` and `view` functions of a `Prism`-style lens.
286327
-- |
287-
-- | For example, in order to parse a mapping from an enum to strings, which
288-
-- | doesn't match up nicely with `Data.Codec.Argonaut.Sum.enumSum` we can use
289-
-- | prismaticCodec:
328+
-- | An example of this would be a codec for `Data.String.NonEmpty.NonEmptyString`:
329+
-- |
330+
-- | ```purescript
331+
-- | nonEmptyString ∷ CA.JsonCodec NES.NonEmptyString
332+
-- | nonEmptyString = CA.prismaticCodec NES.fromString NES.toString CA.string
333+
-- | ```
334+
-- |
335+
-- | Another example might be to handle a mapping from a small sum type to
336+
-- | strings:
290337
-- |
291338
-- | ```purescript
292339
-- | data Direction = North | South | West | East
@@ -307,6 +354,9 @@ fix f =
307354
-- | West -> "W"
308355
-- | East -> "E"
309356
-- | ```
357+
-- |
358+
-- | Although for this latter case there are some other options too, in the form
359+
-- | of `Data.Codec.Argonaut.Generic.nullarySum` and `Data.Codec.Argonaut.Sum.enumSum`.
310360
prismaticCodec a b. (a Maybe b) (b a) JsonCodec a JsonCodec b
311361
prismaticCodec f g orig =
312362
basicCodec

0 commit comments

Comments
 (0)