Add option for enums and more instances (#9)

Instances for `Either`, `JSDate`.
And some bullshit coverage.
This commit is contained in:
Mark Eibes 2022-07-21 14:45:22 +02:00 committed by GitHub
parent 0e8a34c8d8
commit f9fb9d7b41
No known key found for this signature in database
GPG Key ID: 4AEE18F83AFDEB23
12 changed files with 3526 additions and 43 deletions

View File

@ -34,4 +34,4 @@ jobs:
- run: npm install
- run: spago build
- run: spago -x test.dhall test
- run: npm run coverage

2
.gitignore vendored
View File

@ -6,3 +6,5 @@
/.purs*
/.psa*
/.spago/
/.nyc_output/
/coverage/

8
.nycrc.json Normal file
View File

@ -0,0 +1,8 @@
{
"all": true,
"extension": [".purs"],
"include": [ "src/**/*.purs"],
"exclude": [ "src/Yoga/JSON/Generics.purs"],
"excludeAfterRemap": true,
"sourceMap": true
}

View File

@ -20,24 +20,33 @@ Check out the tests for how to encode/decode increasingly complex types.
## Migrate from `purescript-simple-json`
`purescript-yoga-json` is a drop-in replacement for `purescript-simple-json`. Just change the imports from `Simple.JSON` to `Yoga.JSON`.
`purescript-yoga-json` is almost (read below if you use variants) a drop-in replacement for `purescript-simple-json`. Just change the imports from `Simple.JSON` to `Yoga.JSON`.
## Differences to `simple-json`
## Additions over `simple-json`
### Tuples
There is an inbuilt codec for `Tuple`s thanks to @ursi
`yoga-json` represents tuples as arrays in JSON.
### Tuples
There is an inbuilt codec for `Either`s.
`yoga-json` represents eithers as objects with a `type` and a `value` tag in JSON.
### Generics
It includes @justinwoo's codecs for en- and decoding generics inspired by
[simple-json-generics](https://github.com/justinwoo/purescript-simple-json-generics)
It is possible to customise the representation of enums, tagged sum types, and untagged sum types via options.
### BigInts
It can *read* bigints (if you install `big-integer` as a JS dependency).
### 💣 Cannot write bigints as bigints but only strings
It seems that there is no way to write bigints in JavaScript except for writing your own `JSON.stringify`.
### 💣 The Variant Codec is different
## Differences to `simple-json`
### 💣 Variant codec
If you want to emulate `simple-json`'s format you may use the newtype `TaggedVariant`
```purescript

3380
package-lock.json generated

File diff suppressed because it is too large Load Diff

View File

@ -1,6 +1,15 @@
{
"scripts": {
"test": "spago -x test.dhall test --purs-args '-g sourcemaps'",
"precoverage": "rimraf output && npm run test",
"coverage": "c8 --100 npm run test"
},
"dependencies": {
"big-integer": "^1.6.51"
},
"type": "module"
"type": "module",
"devDependencies": {
"c8": "^7.12.0",
"rimraf": "^3.0.2"
}
}

View File

@ -15,6 +15,7 @@
, "foreign-object"
, "identity"
, "integers"
, "js-date"
, "lists"
, "maybe"
, "newtype"

View File

@ -45,6 +45,8 @@ import Data.Either (Either(..), hush, note)
import Data.FoldableWithIndex (foldrWithIndex)
import Data.Identity (Identity(..))
import Data.Int as Int
import Data.JSDate (JSDate, toISOString)
import Data.JSDate as JSDate
import Data.List.NonEmpty (NonEmptyList, singleton)
import Data.Map (Map)
import Data.Map as Map
@ -229,6 +231,14 @@ instance ReadForeign a ⇒ ReadForeign (Nullable a) where
TypeMismatch inner other → TypeMismatch ("Nullable " <> inner) other
_ → error
instance (ReadForeign a, ReadForeign b) ⇒ ReadForeign (Either a b) where
readImpl f = do
{ type: tpe, value } :: { type :: String, value :: Foreign } <- readImpl f
case tpe of
"left" -> Left <$> readImpl value
"right" -> Right <$> readImpl value
_ -> except $ Left (pure $ ForeignError $ "Invalid Either tag " <> tpe)
instance ReadForeign a ⇒ ReadForeign (Object.Object a) where
readImpl = sequence <<< Object.mapWithKey (const readImpl) <=< readObject'
where
@ -394,6 +404,11 @@ instance WriteForeign a ⇒ WriteForeign (Maybe a) where
instance WriteForeign a ⇒ WriteForeign (Nullable a) where
writeImpl = maybe (unsafeToForeign $ toNullable Nothing) writeImpl <<< toMaybe
instance (WriteForeign a, WriteForeign b) ⇒ WriteForeign (Either a b) where
writeImpl value = case value of
Left l -> writeImpl { type: "left", value: writeImpl l}
Right r -> writeImpl { type: "right", value: writeImpl r}
instance WriteForeign a ⇒ WriteForeign (Object.Object a) where
writeImpl = unsafeToForeign <<< Object.mapWithKey (const writeImpl)
@ -513,6 +528,13 @@ else
instance (Newtype nt key, ReadForeign (Map key value)) => ReadForeign (Map nt value) where
readImpl = (readImpl :: (_ -> _ (Map key value))) >>> map (unsafeCoerce :: (Map key value -> Map nt value))
-- Date instances
instance WriteForeign JSDate where
writeImpl = JSDate.toISOString >>> unsafePerformEffect >>> writeImpl
instance ReadForeign JSDate where
readImpl = readImpl >>> map (JSDate.parse >>> unsafePerformEffect)
unsafeStringToInt :: String → Int
unsafeStringToInt = Int.fromString >>>
(fromMaybe' \_ -> unsafeCrashWith "impossible")

View File

@ -5,4 +5,4 @@ module Yoga.JSON.Generics
import Yoga.JSON.Generics.TaggedSumRep (class ReadGenericTaggedSumRep, class WriteGenericTaggedSumRep, Options, defaultOptions, genericReadForeignTaggedSum, genericReadForeignTaggedSumRep, genericWriteForeignTaggedSum, genericWriteForeignTaggedSumRep) as Exported
import Yoga.JSON.Generics.UntaggedSumRep (class ReadGenericUntaggedSumRep, class WriteGenericUntaggedSumRep, genericReadForeignUntaggedSum, genericReadForeignUntaggedSumRep, genericWriteForeignUntaggedSum, genericWriteForeignUntaggedSumRep) as Exported
import Yoga.JSON.Generics.EnumSumRep (class GenericEnumSumRep, genericEnumReadForeign, genericEnumWriteForeign, genericReadForeignEnum, genericWriteForeignEnum) as Exported
import Yoga.JSON.Generics.UntaggedProductRep (class ReadGenericUntaggedProduct, class WriteGenericUntaggedProduct, Offset, genericReadForeignUntaggedProduct, genericReadForeignUntaggedProductRep, genericWriteForeignUntaggedProduct, genericWriteForeignUntaggedProductRep) as Exported
import Yoga.JSON.Generics.UntaggedProductRep (class ReadGenericUntaggedProduct, class WriteGenericUntaggedProduct, Offset, genericReadForeignUntaggedProduct, genericReadForeignUntaggedProductRep, genericWriteForeignUntaggedProduct, genericWriteForeignUntaggedProductRep) as Exported

View File

@ -9,44 +9,57 @@ import Foreign as Foreign
import Yoga.JSON as JSON
import Type.Prelude (class IsSymbol, Proxy(..), reflectSymbol)
genericReadForeignEnum
:: forall a rep
. GR.Generic a rep
=> GenericEnumSumRep rep
=> Foreign
-> Foreign.F a
genericReadForeignEnum f =
GR.to <$> genericEnumReadForeign f
type Options =
{ toConstructorName ∷ String → String }
genericWriteForeignEnum
:: forall a rep
. GR.Generic a rep
=> GenericEnumSumRep rep
=> a
-> Foreign
genericWriteForeignEnum a = genericEnumWriteForeign (GR.from a)
defaultOptions ∷ Options
defaultOptions = { toConstructorName: identity }
genericReadForeignEnum ∷
∀ a rep.
GR.Generic a rep ⇒
GenericEnumSumRep rep ⇒
Options →
Foreign →
Foreign.F a
genericReadForeignEnum options f =
GR.to <$> genericEnumReadForeign options f
genericWriteForeignEnum ∷
∀ a rep.
GR.Generic a rep ⇒
GenericEnumSumRep rep ⇒
Options →
a →
Foreign
genericWriteForeignEnum options a = genericEnumWriteForeign options (GR.from a)
-- | Generic Enum Sum Representations, with constructor names as strings
class GenericEnumSumRep rep where
genericEnumReadForeign :: Foreign -> Foreign.F rep
genericEnumWriteForeign :: rep -> Foreign
genericEnumReadForeign ∷ Options -> Foreign → Foreign.F rep
genericEnumWriteForeign ∷ Options -> rep → Foreign
instance ( GenericEnumSumRep a , GenericEnumSumRep b) =>
instance
( GenericEnumSumRep a
, GenericEnumSumRep b
) ⇒
GenericEnumSumRep (GR.Sum a b) where
genericEnumReadForeign f = GR.Inl <$> genericEnumReadForeign f
<|> GR.Inr <$> genericEnumReadForeign f
genericEnumWriteForeign = case _ of
(GR.Inl a) -> genericEnumWriteForeign a
(GR.Inr a) -> genericEnumWriteForeign a
genericEnumReadForeign options f = GR.Inl <$> genericEnumReadForeign options f
<|> GR.Inr <$> genericEnumReadForeign options f
genericEnumWriteForeign options = case _ of
(GR.Inl a) → genericEnumWriteForeign options a
(GR.Inr a) → genericEnumWriteForeign options a
instance (IsSymbol name) =>
instance
( IsSymbol name
) ⇒
GenericEnumSumRep (GR.Constructor name GR.NoArguments) where
genericEnumReadForeign f = do
s <- JSON.readImpl f
if s == name then pure $ GR.Constructor GR.NoArguments
genericEnumReadForeign options f = do
s JSON.readImpl f
if s == options.toConstructorName name then pure $ GR.Constructor GR.NoArguments
else fail <<< Foreign.ForeignError $
"Enum string " <> s <> " did not match expected string " <> name
where
name = reflectSymbol (Proxy :: Proxy name)
genericEnumWriteForeign (GR.Constructor GR.NoArguments) =
JSON.writeImpl $ reflectSymbol (Proxy :: Proxy name)
name = reflectSymbol (Proxy Proxy name)
genericEnumWriteForeign options (GR.Constructor GR.NoArguments) =
JSON.writeImpl $ options.toConstructorName (reflectSymbol (Proxy ∷ Proxy name))

View File

@ -6,6 +6,8 @@ import Data.Array.NonEmpty as NEA
import Data.BigInt (BigInt)
import Data.Either (Either(..))
import Data.Foldable (traverse_)
import Data.JSDate as JSDAte
import Data.JSDate as JSDate
import Data.List as List
import Data.List.Lazy as LazyList
import Data.Map as Map
@ -15,6 +17,7 @@ import Data.Nullable as Nullable
import Data.Tuple (Tuple(..))
import Data.Tuple.Nested ((/\))
import Data.Variant (Variant, inj)
import Effect.Class (liftEffect)
import Foreign.Object as Object
import Test.Spec (Spec, describe, it)
import Test.Spec.Assertions (shouldEqual)
@ -38,6 +41,11 @@ spec = describe "En- and decoding" $ do
-- just roundtrips Nothing doesn't work when rendering the JSON
roundtrips { empty: Nothing :: Maybe Int }
it "roundtrips Nullable" $ traverse_ roundtrips [Nullable.notNull 3, Nullable.null]
it "roundtrips Either" do
roundtrips ((Left 3) :: Either Int Int)
roundtrips ((Right 3) :: Either String Int)
writeJSON (Right 3 :: Either Int Int) `shouldEqual` """{"value":3,"type":"right"}"""
writeJSON (Left true :: Either Boolean Int) `shouldEqual` """{"value":true,"type":"left"}"""
it "roundtrips Tuple" $ do
roundtrips (Tuple 3 4)
roundtrips ("4" /\ 8 /\ Just 4)
@ -61,6 +69,7 @@ spec = describe "En- and decoding" $ do
stringified = parsed <#> writeJSON
stringified `shouldEqual` (Right expected)
-- [TODO] Comment in as soon as bug in big-integers is fixed
-- @sigma-andex: What bug? Can we link this???
-- it "roundtrips BigInt (2)" do
-- let
-- smallBig = BigInt.fromInt 10
@ -72,6 +81,16 @@ spec = describe "En- and decoding" $ do
-- parsed ∷ _ ({ big ∷ BigInt, smallBig ∷ BigInt })
-- parsed = readJSON json
-- (spy "parsed" parsed) `shouldEqual` (Right expected)
describe "works with JSDate" do
it "roundtrips" do
now <- JSDate.now # liftEffect
roundtrips now
someDate <- JSDate.parse "2022-01-01:00:00:00Z" # liftEffect
let result = writeJSON someDate
let expected = show "2022-01-01T00:00:00.000Z"
result `shouldEqual` expected
describe "works on record types" do
it "roundtrips" do
roundtrips { a: 12, b: "54" }

View File

@ -9,16 +9,24 @@ import Test.Spec (Spec, describe, it)
import Test.Spec.Assertions (shouldEqual)
import Test.Util (roundtrips)
import Yoga.JSON (class ReadForeign, class WriteForeign, writeJSON)
import Yoga.JSON.Generics (genericReadForeignTaggedSum, genericWriteForeignTaggedSum)
import Yoga.JSON.Generics (defaultOptions, genericReadForeignEnum, genericReadForeignTaggedSum, genericReadForeignUntaggedProduct, genericReadForeignUntaggedSum, genericWriteForeignEnum, genericWriteForeignTaggedSum, genericWriteForeignUntaggedProduct, genericWriteForeignUntaggedSum)
import Yoga.JSON.Generics as GenericTaggedSum
import Yoga.JSON.Generics.EnumSumRep (genericReadForeignEnum, genericWriteForeignEnum)
import Yoga.JSON.Generics.TaggedSumRep (defaultOptions)
import Yoga.JSON.Generics.UntaggedProductRep (genericReadForeignUntaggedProduct, genericWriteForeignUntaggedProduct)
import Yoga.JSON.Generics.UntaggedSumRep (genericReadForeignUntaggedSum, genericWriteForeignUntaggedSum)
import Yoga.JSON.Generics.EnumSumRep as Enum
spec ∷ Spec Unit
spec = describe "Generics" $ do
describe "Enum" do
describe "MyEnum = Enum1 | Enum2 | Enum3" do
it "roundtrips" do
roundtrips (Enum1)
roundtrips (Enum3)
describe "works with custom constructor names" do
it "roundtrips" do
roundtrips (SomeOtherEnum2)
writeJSON (SomeThirdEnum3) `shouldEqual` "\"some_third_enum_3\""
describe "Untagged" do
describe "IntOrString = AnInt Int | AString String" do
@ -70,8 +78,20 @@ data MyEnum = Enum1 | Enum2 | Enum3
derive instance Generic MyEnum _
derive instance Eq MyEnum
instance Show MyEnum where show = genericShow
instance ReadForeign MyEnum where readImpl = genericReadForeignEnum
instance WriteForeign MyEnum where writeImpl = genericWriteForeignEnum
instance ReadForeign MyEnum
where readImpl = genericReadForeignEnum Enum.defaultOptions
instance WriteForeign MyEnum
where writeImpl = genericWriteForeignEnum Enum.defaultOptions
data MyEnum2 = SomeEnum2 | SomeOtherEnum2 | SomeThirdEnum3
derive instance Generic MyEnum2 _
derive instance Eq MyEnum2
instance Show MyEnum2 where show = genericShow
instance ReadForeign MyEnum2
where readImpl = genericReadForeignEnum { toConstructorName: snakeCase}
instance WriteForeign MyEnum2
where writeImpl = genericWriteForeignEnum { toConstructorName: snakeCase}
data IntOrString = AnInt Int | AString String
derive instance Generic IntOrString _