Skip to content

Commit

Permalink
Add Unit instances (#43)
Browse files Browse the repository at this point in the history
* Add Unit instances

* Void instances, docs

* Add Maybe instances
  • Loading branch information
paf31 authored Apr 24, 2018
1 parent e35698c commit 5152882
Show file tree
Hide file tree
Showing 11 changed files with 163 additions and 49 deletions.
8 changes: 8 additions & 0 deletions generated-docs/Data/Foreign/Class.md
Original file line number Diff line number Diff line change
Expand Up @@ -25,13 +25,17 @@ to decode your foreign/JSON-encoded data.

##### Instances
``` purescript
Decode Void
Decode Unit
Decode Foreign
Decode String
Decode Char
Decode Boolean
Decode Number
Decode Int
(Decode a) => Decode (Array a)
(Decode v) => Decode (StrMap v)
(Decode a) => Decode (NullOrUndefined a)
```

#### `Encode`
Expand Down Expand Up @@ -59,13 +63,17 @@ to encode your data as JSON.

##### Instances
``` purescript
Encode Void
Encode Unit
Encode Foreign
Encode String
Encode Char
Encode Boolean
Encode Number
Encode Int
(Encode a) => Encode (Array a)
(Encode a) => Encode (NullOrUndefined a)
(Encode v) => Encode (StrMap v)
```


4 changes: 3 additions & 1 deletion generated-docs/Data/Foreign/Generic.md
Original file line number Diff line number Diff line change
Expand Up @@ -11,6 +11,8 @@ Default decoding/encoding options:
- Represent sum types as records with `tag` and `contents` fields
- Unwrap single arguments
- Don't unwrap single constructors
- Use the constructor names as-is
- Use the field names as-is

#### `genericDecode`

Expand Down Expand Up @@ -42,7 +44,7 @@ Decode a JSON string using a `Decode` instance.
encodeJSON :: forall a. Encode a => a -> String
```

Encode value that has an `Encode` instance into a JSON string.
Encode a JSON string using an `Encode` instance.

#### `genericDecodeJSON`

Expand Down
8 changes: 4 additions & 4 deletions generated-docs/Data/Foreign/Generic/Class.md
Original file line number Diff line number Diff line change
Expand Up @@ -32,7 +32,7 @@ GenericEncode NoConstructors

``` purescript
class GenericDecodeArgs a where
decodeArgs :: Int -> List Foreign -> F { result :: a, rest :: List Foreign, next :: Int }
decodeArgs :: Options -> Int -> List Foreign -> F { result :: a, rest :: List Foreign, next :: Int }
```

##### Instances
Expand All @@ -47,7 +47,7 @@ GenericDecodeArgs NoArguments

``` purescript
class GenericEncodeArgs a where
encodeArgs :: a -> List Foreign
encodeArgs :: Options -> a -> List Foreign
```

##### Instances
Expand All @@ -62,7 +62,7 @@ GenericEncodeArgs NoArguments

``` purescript
class GenericDecodeFields a where
decodeFields :: Foreign -> F a
decodeFields :: Options -> Foreign -> F a
```

##### Instances
Expand All @@ -75,7 +75,7 @@ class GenericDecodeFields a where

``` purescript
class GenericEncodeFields a where
encodeFields :: a -> StrMap Foreign
encodeFields :: Options -> a -> StrMap Foreign
```

##### Instances
Expand Down
84 changes: 84 additions & 0 deletions generated-docs/Data/Foreign/Generic/EnumEncoding.md
Original file line number Diff line number Diff line change
@@ -0,0 +1,84 @@
## Module Data.Foreign.Generic.EnumEncoding

#### `GenericEnumOptions`

``` purescript
type GenericEnumOptions = { constructorTagTransform :: String -> String }
```

#### `defaultGenericEnumOptions`

``` purescript
defaultGenericEnumOptions :: GenericEnumOptions
```

#### `genericDecodeEnum`

``` purescript
genericDecodeEnum :: forall a rep. Generic a rep => GenericDecodeEnum rep => GenericEnumOptions -> Foreign -> F a
```

A generic function to be used with "Enums", or sum types with only no-argument constructors. This is used for decoding from strings to one of the constructors, combined with the `constructorTagTransform` property of `SumEncoding`.

#### `genericEncodeEnum`

``` purescript
genericEncodeEnum :: forall a rep. Generic a rep => GenericEncodeEnum rep => GenericEnumOptions -> a -> Foreign
```

A generic function to be used with "Enums", or sum types with only no-argument constructors. This is used for encoding to strings from one of the constructors, combined with the `constructorTagTransform` property of `SumEncoding`.

For example:

```purescript
data Fruit = Apple | Banana | Frikandel
derive instance geFruit :: Generic Fruit _
instance eFruit :: Encode Fruit where
encode = genericEncodeEnum defaultGenericEnumOptions
#### `GenericDecodeEnum`
``` purescript
class GenericDecodeEnum a where
decodeEnum :: GenericEnumOptions -> Foreign -> F a
```

A type class for type representations that can be used for decoding to an Enum. Only the sum and no-argument constructor instances are valid, while others provide a `Fail` constraint to fail in compilation.

For example:

```purescript
data Fruit = Apple | Banana | Frikandel
derive instance geFruit :: Generic Fruit _
instance dFruit :: Decode Fruit where
decode = genericDecodeEnum defaultGenericEnumOptions
```

##### Instances
``` purescript
(GenericDecodeEnum a, GenericDecodeEnum b) => GenericDecodeEnum (Sum a b)
(IsSymbol name) => GenericDecodeEnum (Constructor name NoArguments)
(Fail "genericEncode/DecodeEnum cannot be used on types that are not sums of constructors with no arguments.") => GenericDecodeEnum (Constructor name (Argument a))
(Fail "genericEncode/DecodeEnum cannot be used on types that are not sums of constructors with no arguments.") => GenericDecodeEnum (Constructor name (Product a b))
(Fail "genericEncode/DecodeEnum cannot be used on types that are not sums of constructors with no arguments.") => GenericDecodeEnum (Constructor name (Rec a))
```

#### `GenericEncodeEnum`

``` purescript
class GenericEncodeEnum a where
encodeEnum :: GenericEnumOptions -> a -> Foreign
```

A type class for type representations that can be used for encoding from an Enum. Only the sum and no-argument constructor instances are valid, while others provide a `Fail` constraint to fail in compilation.

##### Instances
``` purescript
(GenericEncodeEnum a, GenericEncodeEnum b) => GenericEncodeEnum (Sum a b)
(IsSymbol name) => GenericEncodeEnum (Constructor name NoArguments)
(Fail "genericEncode/DecodeEnum cannot be used on types that are not sums of constructors with no arguments.") => GenericEncodeEnum (Constructor name (Argument a))
(Fail "genericEncode/DecodeEnum cannot be used on types that are not sums of constructors with no arguments.") => GenericEncodeEnum (Constructor name (Product a b))
(Fail "genericEncode/DecodeEnum cannot be used on types that are not sums of constructors with no arguments.") => GenericEncodeEnum (Constructor name (Rec a))
```


8 changes: 6 additions & 2 deletions generated-docs/Data/Foreign/Generic/Types.md
Original file line number Diff line number Diff line change
Expand Up @@ -3,14 +3,18 @@
#### `Options`

``` purescript
type Options = { sumEncoding :: SumEncoding, unwrapSingleConstructors :: Boolean, unwrapSingleArguments :: Boolean }
type Options = { sumEncoding :: SumEncoding, unwrapSingleConstructors :: Boolean, unwrapSingleArguments :: Boolean, fieldTransform :: String -> String }
```

#### `SumEncoding`

``` purescript
data SumEncoding
= TaggedObject { tagFieldName :: String, contentsFieldName :: String }
= TaggedObject { tagFieldName :: String, contentsFieldName :: String, constructorTagTransform :: String -> String }
```

The encoding of sum types for your type.
`TaggedObject`s will be encoded in the form `{ [tagFieldName]: "ConstructorTag", [contentsFieldName]: "Contents"}`.
`constructorTagTransform` can be provided to transform the constructor tag to a form you use, e.g. `toLower`/`toUpper`.


19 changes: 19 additions & 0 deletions generated-docs/Data/Foreign/Internal.md
Original file line number Diff line number Diff line change
@@ -0,0 +1,19 @@
## Module Data.Foreign.Internal

#### `isStrMap`

``` purescript
isStrMap :: Foreign -> Boolean
```

Test whether a foreign value is a dictionary

#### `readStrMap`

``` purescript
readStrMap :: Foreign -> F (StrMap Foreign)
```

Attempt to coerce a foreign value to a StrMap


6 changes: 6 additions & 0 deletions generated-docs/Data/Foreign/NullOrUndefined.md
Original file line number Diff line number Diff line change
Expand Up @@ -37,4 +37,10 @@ readNullOrUndefined :: forall a. (Foreign -> F a) -> Foreign -> F (NullOrUndefin

Read a `NullOrUndefined` value

#### `undefined`

``` purescript
undefined :: Foreign
```


33 changes: 23 additions & 10 deletions src/Data/Foreign/Class.purs
Original file line number Diff line number Diff line change
@@ -1,12 +1,13 @@
module Data.Foreign.Class where

import Prelude
import Control.Monad.Except (mapExcept)
import Control.Monad.Except (except, mapExcept)
import Data.Array ((..), zipWith, length)
import Data.Bifunctor (lmap)
import Data.Foreign (F, Foreign, ForeignError(ErrorAtIndex), readArray, readBoolean, readChar, readInt, readNumber, readString, toForeign)
import Data.Foreign.NullOrUndefined (NullOrUndefined(..), readNullOrUndefined, undefined)
import Data.Maybe (maybe)
import Data.Either (Either(..))
import Data.Foreign (F, Foreign, ForeignError(..), readArray, readBoolean, readChar, readInt, readNumber, readString, toForeign)
import Data.Foreign.NullOrUndefined (readNullOrUndefined, undefined)
import Data.Maybe (Maybe, maybe)
import Data.StrMap as StrMap
import Data.Traversable (sequence)
import Data.Foreign.Internal (readStrMap)
Expand All @@ -29,6 +30,12 @@ import Data.Foreign.Internal (readStrMap)
class Decode a where
decode :: Foreign -> F a

instance voidDecode :: Decode Void where
decode _ = except (Left (pure (ForeignError "Decode: void")))

instance unitDecode :: Decode Unit where
decode _ = pure unit

instance foreignDecode :: Decode Foreign where
decode = pure

Expand All @@ -55,6 +62,9 @@ instance arrayDecode :: Decode a => Decode (Array a) where
readElement :: Int -> Foreign -> F a
readElement i value = mapExcept (lmap (map (ErrorAtIndex i))) (decode value)

instance maybeDecode :: Decode a => Decode (Maybe a) where
decode = readNullOrUndefined decode

instance strMapDecode :: (Decode v) => Decode (StrMap.StrMap v) where
decode = sequence <<< StrMap.mapWithKey (\_ -> decode) <=< readStrMap

Expand All @@ -76,6 +86,12 @@ instance strMapDecode :: (Decode v) => Decode (StrMap.StrMap v) where
class Encode a where
encode :: a -> Foreign

instance voidEncode :: Encode Void where
encode = absurd

instance unitEncode :: Encode Unit where
encode _ = toForeign {}

instance foreignEncode :: Encode Foreign where
encode = id

Expand All @@ -97,11 +113,8 @@ instance intEncode :: Encode Int where
instance arrayEncode :: Encode a => Encode (Array a) where
encode = toForeign <<< map encode

instance decodeNullOrUndefined :: Decode a => Decode (NullOrUndefined a) where
decode = readNullOrUndefined decode

instance encodeNullOrUndefined :: Encode a => Encode (NullOrUndefined a) where
encode (NullOrUndefined a) = maybe undefined encode a
instance maybeEncode :: Encode a => Encode (Maybe a) where
encode = maybe undefined encode

instance strMapEncode :: Encode v => Encode (StrMap.StrMap v) where
instance strMapEncode :: Encode v => Encode (StrMap.StrMap v) where
encode = toForeign <<< StrMap.mapWithKey (\_ -> encode)
27 changes: 4 additions & 23 deletions src/Data/Foreign/NullOrUndefined.purs
Original file line number Diff line number Diff line change
Expand Up @@ -2,31 +2,12 @@ module Data.Foreign.NullOrUndefined where

import Prelude

import Data.Newtype (class Newtype, unwrap)
import Data.Maybe (Maybe(..))
import Data.Foreign (F, Foreign, isUndefined, isNull)

-- | A `newtype` wrapper whose `IsForeign` instance correctly handles
-- | null and undefined values.
-- |
-- | Conceptually, this type represents values which may be `null`
-- | or `undefined`.
newtype NullOrUndefined a = NullOrUndefined (Maybe a)

derive instance newtypeNullOrUndefined :: Newtype (NullOrUndefined a) _
derive instance eqNullOrUndefined :: Eq a => Eq (NullOrUndefined a)
derive instance ordNullOrUndefined :: Ord a => Ord (NullOrUndefined a)

instance showNullOrUndefined :: (Show a) => Show (NullOrUndefined a) where
show x = "(NullOrUndefined " <> show (unwrap x) <> ")"

-- | Unwrap a `NullOrUndefined` value
unNullOrUndefined :: forall a. NullOrUndefined a -> Maybe a
unNullOrUndefined (NullOrUndefined m) = m

-- | Read a `NullOrUndefined` value
readNullOrUndefined :: forall a. (Foreign -> F a) -> Foreign -> F (NullOrUndefined a)
readNullOrUndefined _ value | isNull value || isUndefined value = pure (NullOrUndefined Nothing)
readNullOrUndefined f value = NullOrUndefined <<< Just <$> f value
-- | Read a value which may be null or undeifned.
readNullOrUndefined :: forall a. (Foreign -> F a) -> Foreign -> F (Maybe a)
readNullOrUndefined _ value | isNull value || isUndefined value = pure Nothing
readNullOrUndefined f value = Just <$> f value

foreign import undefined :: Foreign
11 changes: 4 additions & 7 deletions test/Main.purs
Original file line number Diff line number Diff line change
Expand Up @@ -13,7 +13,6 @@ import Data.Foreign.Generic.Class (class GenericDecode, class GenericEncode, enc
import Data.Foreign.Generic.EnumEncoding (class GenericDecodeEnum, class GenericEncodeEnum, GenericEnumOptions, genericDecodeEnum, genericEncodeEnum)
import Data.Foreign.Generic.Types (Options, SumEncoding(..))
import Data.Foreign.JSON (parseJSON)
import Data.Foreign.NullOrUndefined (NullOrUndefined(..))
import Data.Generic.Rep (class Generic)
import Data.Maybe (Maybe(..))
import Data.StrMap as StrMap
Expand Down Expand Up @@ -111,16 +110,14 @@ main :: forall eff. Eff (console :: CONSOLE, assert :: ASSERT | eff) Unit
main = do
testRoundTrip (RecordTest { foo: 1, bar: "test", baz: 'a' })
testRoundTrip (Cons 1 (Cons 2 (Cons 3 Nil)))
testRoundTrip (UndefinedTest {a: NullOrUndefined (Just "test")})
testRoundTrip (UndefinedTest {a: NullOrUndefined Nothing})
testRoundTrip [NullOrUndefined (Just "test")]
testRoundTrip [NullOrUndefined (Nothing :: Maybe String)]
testRoundTrip (UndefinedTest {a: Just "test"})
testRoundTrip (UndefinedTest {a: Nothing})
testRoundTrip [Just "test"]
testRoundTrip [Nothing :: Maybe String]
testRoundTrip (Apple)
testRoundTrip (makeTree 0)
testRoundTrip (makeTree 5)
testRoundTrip (StrMap.fromFoldable [Tuple "one" 1, Tuple "two" 2])
testUnaryConstructorLiteral
let opts = defaultOptions { fieldTransform = toUpper }
testGenericRoundTrip opts (RecordTest { foo: 1, bar: "test", baz: 'a' })


4 changes: 2 additions & 2 deletions test/Types.purs
Original file line number Diff line number Diff line change
Expand Up @@ -8,10 +8,10 @@ import Data.Foreign.Class (class Encode, class Decode, encode, decode)
import Data.Foreign.Generic (defaultOptions, genericDecode, genericEncode)
import Data.Foreign.Generic.EnumEncoding (defaultGenericEnumOptions, genericDecodeEnum, genericEncodeEnum)
import Data.Foreign.Generic.Types (Options, SumEncoding(..))
import Data.Foreign.NullOrUndefined (NullOrUndefined)
import Data.Generic.Rep (class Generic)
import Data.Generic.Rep.Eq (genericEq)
import Data.Generic.Rep.Show (genericShow)
import Data.Maybe (Maybe(..))
import Data.Tuple (Tuple(..))

newtype TupleArray a b = TupleArray (Tuple a b)
Expand Down Expand Up @@ -103,7 +103,7 @@ instance encodeTree :: Encode a => Encode (Tree a) where
encode x = genericEncode defaultOptions x

newtype UndefinedTest = UndefinedTest
{ a :: NullOrUndefined String
{ a :: Maybe String
}

derive instance eqUT :: Eq UndefinedTest
Expand Down

0 comments on commit 5152882

Please sign in to comment.