mirror of
https://github.com/NorfairKing/autodocodec.git
synced 2024-12-03 06:55:43 +03:00
deriving via example
This commit is contained in:
parent
ae46d36ef4
commit
312149899a
@ -24,6 +24,7 @@ library
|
|||||||
exposed-modules:
|
exposed-modules:
|
||||||
Autodocodec.Aeson
|
Autodocodec.Aeson
|
||||||
Autodocodec.Aeson.Decode
|
Autodocodec.Aeson.Decode
|
||||||
|
Autodocodec.Aeson.DerivingVia
|
||||||
Autodocodec.Aeson.Document
|
Autodocodec.Aeson.Document
|
||||||
Autodocodec.Aeson.Encode
|
Autodocodec.Aeson.Encode
|
||||||
other-modules:
|
other-modules:
|
||||||
|
@ -1,11 +1,15 @@
|
|||||||
|
{-# OPTIONS_GHC -fno-warn-dodgy-exports #-}
|
||||||
|
|
||||||
module Autodocodec.Aeson
|
module Autodocodec.Aeson
|
||||||
( -- * To makes sure we definitely export everything.
|
( -- * To makes sure we definitely export everything.
|
||||||
module Autodocodec.Aeson.Decode,
|
module Autodocodec.Aeson.Decode,
|
||||||
|
module Autodocodec.Aeson.DerivingVia,
|
||||||
module Autodocodec.Aeson.Document,
|
module Autodocodec.Aeson.Document,
|
||||||
module Autodocodec.Aeson.Encode,
|
module Autodocodec.Aeson.Encode,
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Autodocodec.Aeson.Decode
|
import Autodocodec.Aeson.Decode
|
||||||
|
import Autodocodec.Aeson.DerivingVia ()
|
||||||
import Autodocodec.Aeson.Document
|
import Autodocodec.Aeson.Document
|
||||||
import Autodocodec.Aeson.Encode
|
import Autodocodec.Aeson.Encode
|
||||||
|
14
autodocodec-aeson/src/Autodocodec/Aeson/DerivingVia.hs
Normal file
14
autodocodec-aeson/src/Autodocodec/Aeson/DerivingVia.hs
Normal file
@ -0,0 +1,14 @@
|
|||||||
|
{-# OPTIONS_GHC -fno-warn-orphans #-}
|
||||||
|
|
||||||
|
module Autodocodec.Aeson.DerivingVia where
|
||||||
|
|
||||||
|
import Autodocodec
|
||||||
|
import Autodocodec.Aeson.Decode
|
||||||
|
import Autodocodec.Aeson.Encode
|
||||||
|
import Data.Aeson
|
||||||
|
|
||||||
|
instance HasCodec a => ToJSON (Autodocodec a) where
|
||||||
|
toJSON = toJSONViaCodec . unAutodocodec
|
||||||
|
|
||||||
|
instance HasCodec a => FromJSON (Autodocodec a) where
|
||||||
|
parseJSON = fmap Autodocodec <$> parseJSONViaCodec
|
@ -1,4 +1,5 @@
|
|||||||
{-# LANGUAGE DeriveGeneric #-}
|
{-# LANGUAGE DeriveGeneric #-}
|
||||||
|
{-# LANGUAGE DerivingVia #-}
|
||||||
{-# LANGUAGE LambdaCase #-}
|
{-# LANGUAGE LambdaCase #-}
|
||||||
{-# LANGUAGE OverloadedStrings #-}
|
{-# LANGUAGE OverloadedStrings #-}
|
||||||
{-# LANGUAGE RecordWildCards #-}
|
{-# LANGUAGE RecordWildCards #-}
|
||||||
@ -10,6 +11,7 @@
|
|||||||
module Autodocodec.Usage where
|
module Autodocodec.Usage where
|
||||||
|
|
||||||
import Autodocodec
|
import Autodocodec
|
||||||
|
import Autodocodec.Aeson ()
|
||||||
import Control.Applicative
|
import Control.Applicative
|
||||||
import Data.Aeson (FromJSON (..), ToJSON (..))
|
import Data.Aeson (FromJSON (..), ToJSON (..))
|
||||||
import qualified Data.Aeson as JSON
|
import qualified Data.Aeson as JSON
|
||||||
@ -32,8 +34,8 @@ data Fruit
|
|||||||
instance Validity Fruit
|
instance Validity Fruit
|
||||||
|
|
||||||
instance GenValid Fruit where
|
instance GenValid Fruit where
|
||||||
genValid = genValidStructurally
|
genValid = genValidStructurallyWithoutExtraChecking
|
||||||
shrinkValid = shrinkValidStructurally
|
shrinkValid = shrinkValidStructurallyWithoutExtraFiltering
|
||||||
|
|
||||||
instance HasCodec Fruit where
|
instance HasCodec Fruit where
|
||||||
codec = shownBoundedEnumCodec
|
codec = shownBoundedEnumCodec
|
||||||
@ -149,3 +151,20 @@ instance HasCodec Recursive where
|
|||||||
eitherCodec
|
eitherCodec
|
||||||
(codec @Int <?> "base case")
|
(codec @Int <?> "base case")
|
||||||
(object "Recurse" $ requiredField "recurse" "recursive case")
|
(object "Recurse" $ requiredField "recurse" "recursive case")
|
||||||
|
|
||||||
|
data Via = Via {viaOne :: !Text, viaTwo :: !Text}
|
||||||
|
deriving stock (Show, Eq, Generic)
|
||||||
|
deriving (FromJSON, ToJSON) via (Autodocodec Via)
|
||||||
|
|
||||||
|
instance Validity Via
|
||||||
|
|
||||||
|
instance GenValid Via where
|
||||||
|
genValid = genValidStructurallyWithoutExtraChecking
|
||||||
|
shrinkValid = shrinkValidStructurallyWithoutExtraFiltering
|
||||||
|
|
||||||
|
instance HasCodec Via where
|
||||||
|
codec =
|
||||||
|
object "Via" $
|
||||||
|
Via
|
||||||
|
<$> requiredField "one" "first field" .= viaOne
|
||||||
|
<*> requiredField "two" "second field" .= viaTwo
|
||||||
|
@ -55,6 +55,7 @@ spec = do
|
|||||||
jsonSchemaSpec @[Text] "list-text"
|
jsonSchemaSpec @[Text] "list-text"
|
||||||
jsonSchemaSpec @Example "example"
|
jsonSchemaSpec @Example "example"
|
||||||
jsonSchemaSpec @Recursive "recursive"
|
jsonSchemaSpec @Recursive "recursive"
|
||||||
|
jsonSchemaSpec @Via "via"
|
||||||
describe "JSONSchema" $ do
|
describe "JSONSchema" $ do
|
||||||
genValidSpec @JSONSchema
|
genValidSpec @JSONSchema
|
||||||
it "roundtrips through json and back" $
|
it "roundtrips through json and back" $
|
||||||
|
@ -53,6 +53,7 @@ spec = do
|
|||||||
aesonCodecSpec @Fruit
|
aesonCodecSpec @Fruit
|
||||||
aesonCodecSpec @Example
|
aesonCodecSpec @Example
|
||||||
aesonCodecSpec @Recursive
|
aesonCodecSpec @Recursive
|
||||||
|
aesonCodecSpec @Via
|
||||||
|
|
||||||
aesonCodecSpec :: forall a. (Show a, Eq a, Typeable a, GenValid a, ToJSON a, FromJSON a, HasCodec a) => Spec
|
aesonCodecSpec :: forall a. (Show a, Eq a, Typeable a, GenValid a, ToJSON a, FromJSON a, HasCodec a) => Spec
|
||||||
aesonCodecSpec =
|
aesonCodecSpec =
|
||||||
|
@ -50,6 +50,7 @@ spec = do
|
|||||||
yamlSchemaSpec @Fruit "fruit"
|
yamlSchemaSpec @Fruit "fruit"
|
||||||
yamlSchemaSpec @Example "example"
|
yamlSchemaSpec @Example "example"
|
||||||
yamlSchemaSpec @Recursive "recursive"
|
yamlSchemaSpec @Recursive "recursive"
|
||||||
|
yamlSchemaSpec @Via "via"
|
||||||
|
|
||||||
yamlSchemaSpec :: forall a. (Show a, Eq a, Typeable a, GenValid a, HasCodec a) => FilePath -> Spec
|
yamlSchemaSpec :: forall a. (Show a, Eq a, Typeable a, GenValid a, HasCodec a) => FilePath -> Spec
|
||||||
yamlSchemaSpec filePath = do
|
yamlSchemaSpec filePath = do
|
||||||
|
16
autodocodec-api-usage/test_resources/schema/via.json
Normal file
16
autodocodec-api-usage/test_resources/schema/via.json
Normal file
@ -0,0 +1,16 @@
|
|||||||
|
{
|
||||||
|
"$comment": "Via",
|
||||||
|
"required": [
|
||||||
|
"one",
|
||||||
|
"two"
|
||||||
|
],
|
||||||
|
"type": "object",
|
||||||
|
"properties": {
|
||||||
|
"two": {
|
||||||
|
"type": "string"
|
||||||
|
},
|
||||||
|
"one": {
|
||||||
|
"type": "string"
|
||||||
|
}
|
||||||
|
}
|
||||||
|
}
|
7
autodocodec-api-usage/test_resources/schema/via.txt
Normal file
7
autodocodec-api-usage/test_resources/schema/via.txt
Normal file
@ -0,0 +1,7 @@
|
|||||||
|
# Via
|
||||||
|
[37mone[m: # [31mrequired[m
|
||||||
|
# first field
|
||||||
|
[33m<string>[m
|
||||||
|
[37mtwo[m: # [31mrequired[m
|
||||||
|
# second field
|
||||||
|
[33m<string>[m
|
@ -25,6 +25,7 @@ library
|
|||||||
Autodocodec
|
Autodocodec
|
||||||
Autodocodec.Class
|
Autodocodec.Class
|
||||||
Autodocodec.Codec
|
Autodocodec.Codec
|
||||||
|
Autodocodec.DerivingVia
|
||||||
other-modules:
|
other-modules:
|
||||||
Paths_autodocodec
|
Paths_autodocodec
|
||||||
hs-source-dirs:
|
hs-source-dirs:
|
||||||
|
@ -68,14 +68,19 @@ module Autodocodec
|
|||||||
pureCodec,
|
pureCodec,
|
||||||
apCodec,
|
apCodec,
|
||||||
|
|
||||||
|
-- * Deriving Via
|
||||||
|
Autodocodec (..),
|
||||||
|
|
||||||
-- ** Internals you most likely don't need
|
-- ** Internals you most likely don't need
|
||||||
showCodecABit,
|
showCodecABit,
|
||||||
|
|
||||||
-- * To make sure we definitely export everything
|
-- * To make sure we definitely export everything
|
||||||
module Autodocodec.Class,
|
module Autodocodec.Class,
|
||||||
|
module Autodocodec.DerivingVia,
|
||||||
module Autodocodec.Codec,
|
module Autodocodec.Codec,
|
||||||
)
|
)
|
||||||
where
|
where
|
||||||
|
|
||||||
import Autodocodec.Class
|
import Autodocodec.Class
|
||||||
import Autodocodec.Codec
|
import Autodocodec.Codec
|
||||||
|
import Autodocodec.DerivingVia
|
||||||
|
17
autodocodec/src/Autodocodec/DerivingVia.hs
Normal file
17
autodocodec/src/Autodocodec/DerivingVia.hs
Normal file
@ -0,0 +1,17 @@
|
|||||||
|
module Autodocodec.DerivingVia where
|
||||||
|
|
||||||
|
-- | 'Autodocodec' is a wrapper to provide codec-based deriving strategies.
|
||||||
|
--
|
||||||
|
-- === Example usage
|
||||||
|
--
|
||||||
|
-- > data Via = Via {viaOne :: !Text, viaTwo :: !Text}
|
||||||
|
-- > deriving stock (Show, Eq, Generic)
|
||||||
|
-- > deriving (FromJSON, ToJSON) via (Autodocodec Via)
|
||||||
|
-- >
|
||||||
|
-- > instance HasCodec Via where
|
||||||
|
-- > codec =
|
||||||
|
-- > object "Via" $
|
||||||
|
-- > Via
|
||||||
|
-- > <$> requiredField "one" "first field" .= viaOne
|
||||||
|
-- > <*> requiredField "two" "second field" .= viaTwo
|
||||||
|
newtype Autodocodec a = Autodocodec {unAutodocodec :: a}
|
Loading…
Reference in New Issue
Block a user