Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data Codec context input output where
- NullCodec :: ValueCodec () ()
- BoolCodec :: Maybe Text -> JSONCodec Bool
- StringCodec :: Maybe Text -> JSONCodec Text
- NumberCodec :: Maybe Text -> Maybe NumberBounds -> JSONCodec Scientific
- HashMapCodec :: (Eq k, Hashable k, FromJSONKey k, ToJSONKey k) => JSONCodec v -> JSONCodec (HashMap k v)
- MapCodec :: (Ord k, FromJSONKey k, ToJSONKey k) => JSONCodec v -> JSONCodec (Map k v)
- ValueCodec :: JSONCodec Value
- ArrayOfCodec :: Maybe Text -> ValueCodec input output -> ValueCodec (Vector input) (Vector output)
- ObjectOfCodec :: Maybe Text -> ObjectCodec input output -> ValueCodec input output
- EqCodec :: (Show value, Eq value) => value -> JSONCodec value -> JSONCodec value
- BimapCodec :: (oldOutput -> Either String newOutput) -> (newInput -> oldInput) -> Codec context oldInput oldOutput -> Codec context newInput newOutput
- EitherCodec :: !Union -> Codec context input1 output1 -> Codec context input2 output2 -> Codec context (Either input1 input2) (Either output1 output2)
- DiscriminatedUnionCodec :: Text -> (input -> (Discriminator, ObjectCodec input ())) -> HashMap Discriminator (Text, ObjectCodec Void output) -> ObjectCodec input output
- CommentCodec :: Text -> ValueCodec input output -> ValueCodec input output
- ReferenceCodec :: Text -> ~(ValueCodec input output) -> ValueCodec input output
- RequiredKeyCodec :: Text -> ValueCodec input output -> Maybe Text -> ObjectCodec input output
- OptionalKeyCodec :: Text -> ValueCodec input output -> Maybe Text -> ObjectCodec (Maybe input) (Maybe output)
- OptionalKeyWithDefaultCodec :: Text -> ValueCodec value value -> value -> Maybe Text -> ObjectCodec value value
- OptionalKeyWithOmittedDefaultCodec :: Eq value => Text -> ValueCodec value value -> value -> Maybe Text -> ObjectCodec value value
- PureCodec :: output -> ObjectCodec void output
- ApCodec :: ObjectCodec input (output -> newOutput) -> ObjectCodec input output -> ObjectCodec input newOutput
- data NumberBounds = NumberBounds {}
- checkNumberBounds :: NumberBounds -> Scientific -> Either String Scientific
- data Union
- type ValueCodec = Codec Value
- type ObjectCodec = Codec Object
- type JSONCodec a = ValueCodec a a
- type JSONObjectCodec a = ObjectCodec a a
- showCodecABit :: Codec context input output -> String
- rmapCodec :: (oldOutput -> newOutput) -> Codec context input oldOutput -> Codec context input newOutput
- lmapCodec :: (newInput -> oldInput) -> Codec context oldInput output -> Codec context newInput output
- (.=) :: ObjectCodec oldInput output -> (newInput -> oldInput) -> ObjectCodec newInput output
- dimapCodec :: (oldOutput -> newOutput) -> (newInput -> oldInput) -> Codec context oldInput oldOutput -> Codec context newInput newOutput
- pureCodec :: output -> ObjectCodec input output
- apCodec :: ObjectCodec input (output -> newOutput) -> ObjectCodec input output -> ObjectCodec input newOutput
- maybeCodec :: ValueCodec input output -> ValueCodec (Maybe input) (Maybe output)
- eitherCodec :: Codec context input1 output1 -> Codec context input2 output2 -> Codec context (Either input1 input2) (Either output1 output2)
- disjointEitherCodec :: Codec context input1 output1 -> Codec context input2 output2 -> Codec context (Either input1 input2) (Either output1 output2)
- possiblyJointEitherCodec :: Codec context input1 output1 -> Codec context input2 output2 -> Codec context (Either input1 input2) (Either output1 output2)
- type Discriminator = Text
- mapToEncoder :: b -> Codec context b any -> Codec context a ()
- mapToDecoder :: (b -> a) -> Codec context any b -> Codec context Void a
- discriminatedUnionCodec :: Text -> (input -> (Discriminator, ObjectCodec input ())) -> HashMap Discriminator (Text, ObjectCodec Void output) -> ObjectCodec input output
- bimapCodec :: (oldOutput -> Either String newOutput) -> (newInput -> oldInput) -> Codec context oldInput oldOutput -> Codec context newInput newOutput
- vectorCodec :: ValueCodec input output -> ValueCodec (Vector input) (Vector output)
- listCodec :: ValueCodec input output -> ValueCodec [input] [output]
- nonEmptyCodec :: ValueCodec input output -> ValueCodec (NonEmpty input) (NonEmpty output)
- singleOrListCodec :: ValueCodec input output -> ValueCodec [input] [output]
- singleOrNonEmptyCodec :: ValueCodec input output -> ValueCodec (NonEmpty input) (NonEmpty output)
- requiredFieldWith :: Text -> ValueCodec input output -> Text -> ObjectCodec input output
- requiredFieldWith' :: Text -> ValueCodec input output -> ObjectCodec input output
- optionalFieldWith :: Text -> ValueCodec input output -> Text -> ObjectCodec (Maybe input) (Maybe output)
- optionalFieldWith' :: Text -> ValueCodec input output -> ObjectCodec (Maybe input) (Maybe output)
- optionalFieldWithDefaultWith :: Text -> JSONCodec output -> output -> Text -> ObjectCodec output output
- optionalFieldWithDefaultWith' :: Text -> JSONCodec output -> output -> ObjectCodec output output
- optionalFieldWithOmittedDefaultWith :: Eq output => Text -> JSONCodec output -> output -> Text -> ObjectCodec output output
- optionalFieldWithOmittedDefaultWith' :: Eq output => Text -> JSONCodec output -> output -> ObjectCodec output output
- optionalFieldOrNullWithOmittedDefaultWith :: Eq output => Text -> JSONCodec output -> output -> Text -> ObjectCodec output output
- optionalFieldOrNullWithOmittedDefaultWith' :: Eq output => Text -> JSONCodec output -> output -> ObjectCodec output output
- optionalFieldOrNullWith :: Text -> ValueCodec input output -> Text -> ObjectCodec (Maybe input) (Maybe output)
- optionalFieldOrNullWith' :: Text -> ValueCodec input output -> ObjectCodec (Maybe input) (Maybe output)
- (<?>) :: ValueCodec input output -> Text -> ValueCodec input output
- (<??>) :: ValueCodec input output -> [Text] -> ValueCodec input output
- hashMapCodec :: (Eq k, Hashable k, FromJSONKey k, ToJSONKey k) => JSONCodec v -> JSONCodec (HashMap k v)
- mapCodec :: (Ord k, FromJSONKey k, ToJSONKey k) => JSONCodec v -> JSONCodec (Map k v)
- keyMapCodec :: JSONCodec v -> JSONCodec (KeyMap v)
- valueCodec :: JSONCodec Value
- nullCodec :: JSONCodec ()
- boolCodec :: JSONCodec Bool
- textCodec :: JSONCodec Text
- stringCodec :: JSONCodec String
- scientificCodec :: JSONCodec Scientific
- scientificWithBoundsCodec :: NumberBounds -> JSONCodec Scientific
- object :: Text -> ObjectCodec input output -> ValueCodec input output
- boundedIntegralCodec :: forall i. (Integral i, Bounded i) => JSONCodec i
- boundedIntegralNumberBounds :: forall i. (Integral i, Bounded i) => NumberBounds
- literalTextCodec :: Text -> JSONCodec Text
- literalTextValueCodec :: value -> Text -> JSONCodec value
- matchChoiceCodec :: Codec context input output -> Codec context input' output -> (newInput -> Either input input') -> Codec context newInput output
- disjointMatchChoiceCodec :: Codec context input output -> Codec context input' output -> (newInput -> Either input input') -> Codec context newInput output
- matchChoiceCodecAs :: Union -> Codec context input output -> Codec context input' output -> (newInput -> Either input input') -> Codec context newInput output
- matchChoicesCodec :: [(input -> Maybe input, Codec context input output)] -> Codec context input output -> Codec context input output
- disjointMatchChoicesCodec :: [(input -> Maybe input, Codec context input output)] -> Codec context input output -> Codec context input output
- matchChoicesCodecAs :: Union -> [(input -> Maybe input, Codec context input output)] -> Codec context input output -> Codec context input output
- parseAlternatives :: Codec context input output -> [Codec context input output] -> Codec context input output
- parseAlternative :: Codec context input output -> Codec context input' output -> Codec context input output
- enumCodec :: forall enum context. Eq enum => NonEmpty (enum, Codec context enum enum) -> Codec context enum enum
- stringConstCodec :: forall constant. Eq constant => NonEmpty (constant, Text) -> JSONCodec constant
- shownBoundedEnumCodec :: forall enum. (Show enum, Eq enum, Enum enum, Bounded enum) => JSONCodec enum
- orNullHelper :: ObjectCodec (Maybe (Maybe input)) (Maybe (Maybe output)) -> ObjectCodec (Maybe input) (Maybe output)
- named :: Text -> ValueCodec input output -> ValueCodec input output
- codecViaAeson :: (FromJSON a, ToJSON a) => Text -> JSONCodec a
Documentation
>>>
import Autodocodec.Aeson (toJSONVia, toJSONViaCodec, toJSONObjectVia, toJSONObjectViaCodec, parseJSONVia, parseJSONViaCodec, parseJSONObjectVia, parseJSONObjectViaCodec)
>>>
import qualified Autodocodec.Aeson.Compat as Compat
>>>
import Autodocodec.Class (HasCodec(codec), requiredField)
>>>
import qualified Data.Aeson as JSON
>>>
import qualified Data.HashMap.Strict as HM
>>>
import Data.Aeson (Value(..))
>>>
import qualified Data.Vector as Vector
>>>
import Data.Int
>>>
import Data.Word
>>>
:set -XOverloadedStrings
>>>
:set -XOverloadedLists
>>>
:set -XLambdaCase
data Codec context input output where Source #
A Self-documenting encoder and decoder,
also called an Autodocodec.
In an ideal situation, this type would have only one type parameter: 'Codec value'.
This does not work very well because we want to be able to implement Functor
and Applicative
, which each require a kind '* -> *'.
So instead we use two type parameters.
The two type parameters correspond to the phase in which they are used:
- The
input
parameter is used for the type that is used during encoding of a value, so it's theinput
to the codec. - The
output
parameter is used for the type that is used during decoding of a value, so it's theoutput
of the codec. - Both parameters are unused during documentation.
NullCodec :: ValueCodec () () | Encode |
BoolCodec | Encode a |
StringCodec | Encode This is named after the primitive type String in json, not after the haskell type string. |
NumberCodec | Encode The number has optional NOTE: We use |
| |
HashMapCodec :: (Eq k, Hashable k, FromJSONKey k, ToJSONKey k) => JSONCodec v -> JSONCodec (HashMap k v) | |
MapCodec :: (Ord k, FromJSONKey k, ToJSONKey k) => JSONCodec v -> JSONCodec (Map k v) | |
ValueCodec :: JSONCodec Value | |
ArrayOfCodec | Encode a |
| |
ObjectOfCodec | Encode a value as a an |
| |
EqCodec | Match a given value using its |
BimapCodec :: (oldOutput -> Either String newOutput) -> (newInput -> oldInput) -> Codec context oldInput oldOutput -> Codec context newInput newOutput | Map a codec in both directions. This is not strictly dimap, because the decoding function is allowed to fail, but we can implement dimap using this function by using a decoding function that does not fail. Otherwise we would have to have another constructor here. |
EitherCodec | Encode/Decode an During encoding, encode either value of an This codec is used to implement choice. Note that this codec works for both values and objects. However: due to the complex nature of documentation, the documentation may not be as good as you would hope when you use this codec. In particular, you should prefer using it for values rather than objects, because those docs are easier to generate. |
DiscriminatedUnionCodec | Encode/decode a discriminated union of objects The type of object being encoded/decoded is discriminated by a designated "discriminator" property on the object which takes a string value. When encoding, the provided function is applied to the input to obtain a new encoder
for the input. The function When decoding, the value of the discriminator property is looked up in the The |
| |
CommentCodec | A comment codec This is used to add implementation-irrelevant but human-relevant information. |
| |
ReferenceCodec | A reference codec This is used for naming a codec, so that recursive codecs can have a finite schema. It doesn't _need_ to be recursive, and you may just have wanted to name the codec, but it _may_ be recursive from here downward. This value MUST be lazy, otherwise we can never define recursive codecs. |
| |
RequiredKeyCodec | |
| |
OptionalKeyCodec | |
| |
OptionalKeyWithDefaultCodec | |
| |
OptionalKeyWithOmittedDefaultCodec | |
| |
PureCodec | To implement Pure is not available for non-object codecs because there is no |
| |
ApCodec :: ObjectCodec input (output -> newOutput) -> ObjectCodec input output -> ObjectCodec input newOutput | To implement Ap is not available for non-object codecs because we cannot combine ( |
Instances
Applicative (ObjectCodec input) Source # | |
Defined in Autodocodec.Codec pure :: a -> ObjectCodec input a # (<*>) :: ObjectCodec input (a -> b) -> ObjectCodec input a -> ObjectCodec input b # liftA2 :: (a -> b -> c) -> ObjectCodec input a -> ObjectCodec input b -> ObjectCodec input c # (*>) :: ObjectCodec input a -> ObjectCodec input b -> ObjectCodec input b # (<*) :: ObjectCodec input a -> ObjectCodec input b -> ObjectCodec input a # | |
Functor (Codec context input) Source # | |
data NumberBounds Source #
Instances
checkNumberBounds :: NumberBounds -> Scientific -> Either String Scientific Source #
Check if a number falls within given NumberBounds
.
What type of union the encoding uses
PossiblyJointUnion | Not disjoint, see |
DisjointUnion | Disjoint, see |
type ValueCodec = Codec Value Source #
A codec within the Value
context.
An Codec
can be used to turn a Haskell value into a Value
or to parse a Value
into a haskell value.
This cannot be used in certain places where ObjectCodec
could be used, and vice versa.
type ObjectCodec = Codec Object Source #
type JSONCodec a = ValueCodec a a Source #
A completed autodocodec for parsing and rendering a Value
.
You can use a value of this type to get everything else for free:
- Encode values to JSON using
toJSONViaCodec
ortoJSONVia
- Decode values from JSON using
parseJSONViaCodec
orparseJSONVia
- Produce a JSON Schema using
jsonSchemaViaCodec
orjsonSchemaVia
fromautodocodec-schema
- Encode to and decode from Yaml using
autodocodec-yaml
- Produce a human-readible YAML schema using
renderColouredSchemaViaCodec
fromautodocodec-yaml
- Produce a Swagger2 schema using
autodocodec-swagger2
- Produce a OpenAPI3 schema using
autodocodec-openapi3
type JSONObjectCodec a = ObjectCodec a a Source #
A completed autodocodec for parsing and rendering a Value
.
showCodecABit :: Codec context input output -> String Source #
Show a codec to a human.
This function exists for codec debugging. It omits any unshowable information from the output.
rmapCodec :: (oldOutput -> newOutput) -> Codec context input oldOutput -> Codec context input newOutput Source #
Map the output part of a codec
You can use this function if you only need to map the parsing-side of a codec. This function is probably only useful if the function you map does not change the codec type.
WARNING: This can be used to produce a codec that does not roundtrip.
>>>
JSON.parseMaybe (parseJSONVia (rmapCodec (*2) codec)) (Number 5) :: Maybe Int
Just 10
lmapCodec :: (newInput -> oldInput) -> Codec context oldInput output -> Codec context newInput output Source #
Map the input part of a codec
You can use this function if you only need to map the rendering-side of a codec. This function is probably only useful if the function you map does not change the codec type.
WARNING: This can be used to produce a codec that does not roundtrip.
>>>
toJSONVia (lmapCodec (*2) (codec :: JSONCodec Int)) 5
Number 10.0
(.=) :: ObjectCodec oldInput output -> (newInput -> oldInput) -> ObjectCodec newInput output Source #
Infix version of lmapCodec
Use this function to supply the rendering side of a codec.
(.=) = flip lmapCodec
Example usage
data Example = Example { exampleText :: !Text, exampleBool :: !Bool } instance HasCodec Example where codec = object "Example" $ Example <$> requiredField "text" .= exampleText <*> requiredField "bool" .= exampleBool
:: (oldOutput -> newOutput) | Function to make to the new type |
-> (newInput -> oldInput) | Function to make from the new type |
-> Codec context oldInput oldOutput | Codec for the old type |
-> Codec context newInput newOutput |
Map both directions of a codec
You can use this function to change the type of a codec as long as the two functions are inverses.
HasCodec
instance for newtypes
A good use-case is implementing HasCodec
for newtypes:
newtype MyInt = MyInt { unMyInt :: Int } instance HasCodec MyInt where codec = dimapCodec MyInt unMyInt codec
pureCodec :: output -> ObjectCodec input output Source #
Produce a value without parsing any part of an Object
.
This function exists to implement Applicative (ObjectCodec input)
.
API Note
This is a forward-compatible version of PureCodec
.
pureCodec = PureCodec
apCodec :: ObjectCodec input (output -> newOutput) -> ObjectCodec input output -> ObjectCodec input newOutput Source #
Sequentially apply two codecs that parse part of an Object
.
This function exists to implement Applicative (ObjectCodec input)
.
API Note
This is a forward-compatible version of ApCodec
.
apCodec = ApCodec
maybeCodec :: ValueCodec input output -> ValueCodec (Maybe input) (Maybe output) Source #
eitherCodec :: Codec context input1 output1 -> Codec context input2 output2 -> Codec context (Either input1 input2) (Either output1 output2) Source #
Either codec
During encoding, parse a value according to either codec. During encoding, use the corresponding codec to encode either value.
HasCodec
instance for sum types
To write a HasCodec
instance for sum types, you will need to decide whether encoding is disjoint or not.
The default, so also the implementation of this function, is possiblyJointEitherCodec
, but you may want to use disjointEitherCodec
instead.
Ask yourself: Can the encoding of a Left
value be decoded as Right
value (or vice versa)?
Yes ->
use possiblyJointEitherCodec
.
No ->
use disjointEitherCodec
.
Example usage
>>>
let c = eitherCodec codec codec :: JSONCodec (Either Int String)
>>>
toJSONVia c (Left 5)
Number 5.0>>>
toJSONVia c (Right "hello")
String "hello">>>
JSON.parseMaybe (parseJSONVia c) (String "world") :: Maybe (Either Int String)
Just (Right "world")
API Note
This is a forward-compatible version of possiblyJointEitherCodec
.
eitherCodec = possiblyJointEitherCodec
disjointEitherCodec :: Codec context input1 output1 -> Codec context input2 output2 -> Codec context (Either input1 input2) (Either output1 output2) Source #
Possibly joint either codec
During encoding, parse a value according to either codec. During encoding, use the corresponding codec to encode either value.
This codec is for the case in which parsing must be disjoint.
HasCodec
instance for sum types with an encoding that is definitely disjoint.
The eitherCodec
can be used to implement HasCodec
instances for sum types
for which the encoding is definitely disjoint.
>>>
data War = WorldWar Word8 | OtherWar Text deriving (Show, Eq)
>>>
:{
instance HasCodec War where codec = dimapCodec f g $ disjointEitherCodec (codec :: JSONCodec Word8) (codec :: JSONCodec Text) where f = \case Left w -> WorldWar w Right t -> OtherWar t g = \case WorldWar w -> Left w OtherWar t -> Right t :}
Note that this incoding is indeed disjoint because an encoded String
can
never be parsed as an Word8
and vice versa.
>>>
toJSONViaCodec (WorldWar 2)
Number 2.0>>>
toJSONViaCodec (OtherWar "OnDrugs")
String "OnDrugs">>>
JSON.parseMaybe parseJSONViaCodec (String "of the roses") :: Maybe War
Just (OtherWar "of the roses")
WARNING
If it turns out that the encoding of a value is not disjoint, decoding may fail and documentation may be wrong.
>>>
let c = disjointEitherCodec (codec :: JSONCodec Int) (codec :: JSONCodec Int)
>>>
JSON.parseMaybe (parseJSONVia c) (Number 5) :: Maybe (Either Int Int)
Nothing
Encoding still works as expected, however:
>>>
toJSONVia c (Left 5)
Number 5.0>>>
toJSONVia c (Right 6)
Number 6.0
Example usage
>>>
toJSONVia (disjointEitherCodec (codec :: JSONCodec Int) (codec :: JSONCodec String)) (Left 5)
Number 5.0>>>
toJSONVia (disjointEitherCodec (codec :: JSONCodec Int) (codec :: JSONCodec String)) (Right "hello")
String "hello"
API Note
This is a forward-compatible version of 'EitherCodec DisjointUnion'.
disjointEitherCodec = EitherCodec DisjointUnion
possiblyJointEitherCodec :: Codec context input1 output1 -> Codec context input2 output2 -> Codec context (Either input1 input2) (Either output1 output2) Source #
Possibly joint either codec
During encoding, parse a value according to either codec. During encoding, use the corresponding codec to encode either value.
This codec is for the case in which parsing may not be disjoint.
HasCodec
instance for sum types with an encoding that is not disjoint.
The eitherCodec
can be used to implement HasCodec
instances for sum types.
If you just have two codecs that you want to try in order, while parsing, you can do this:
>>>
:{
data Ainur = Valar Text Text | Maiar Text deriving (Show, Eq) :}
>>>
:{
instance HasCodec Ainur where codec = dimapCodec f g $ possiblyJointEitherCodec (object "Valar" $ (,) <$> requiredField "domain" "Domain which the Valar rules over" .= fst <*> requiredField "name" "Name of the Valar" .= snd) (object "Maiar" $ requiredField "name" "Name of the Maiar") where f = \case Left (domain, name) -> Valar domain name Right name -> Maiar name g = \case Valar domain name -> Left (domain, name) Maiar name -> Right name :}
Note that this encoding is indeed not disjoint, because a Valar
object can
parse as a Maiar
value.
>>>
toJSONViaCodec (Valar "Stars" "Varda")
Object (fromList [("domain",String "Stars"),("name",String "Varda")])>>>
toJSONViaCodec (Maiar "Sauron")
Object (fromList [("name",String "Sauron")])>>>
JSON.parseMaybe parseJSONViaCodec (Object (Compat.fromList [("name",String "Olorin")])) :: Maybe Ainur
Just (Maiar "Olorin")
WARNING
The order of the codecs in a possiblyJointEitherCodec
matters.
In the above example, decoding works as expected because the Valar
case is parsed first.
If the Maiar
case were first in the possiblyJointEitherCodec
, then
Valar
could never be parsed.
API Note
This is a forward-compatible version of 'EitherCodec PossiblyJointUnion'.
possiblyJointEitherCodec = EitherCodec PossiblyJointUnion
type Discriminator = Text Source #
Discriminator value used in DiscriminatedUnionCodec
mapToEncoder :: b -> Codec context b any -> Codec context a () Source #
Wrap up a value of type b
with its codec to produce
and encoder for a
s that ignores its input and instead encodes
the value b
.
This is useful for building discriminatedUnionCodec
s.
mapToDecoder :: (b -> a) -> Codec context any b -> Codec context Void a Source #
Map a codec for decoding b
s into a decoder for a
s.
This is useful for building discriminatedUnionCodec
s.
discriminatedUnionCodec Source #
:: Text | propertyName |
-> (input -> (Discriminator, ObjectCodec input ())) | how to encode the input Use |
-> HashMap Discriminator (Text, ObjectCodec Void output) | how to decode the output The Use |
-> ObjectCodec input output |
Encode/decode a discriminated union of objects
The type of object being encoded/decoded is discriminated by a designated "discriminator" property on the object which takes a string value.
When encoding, the provided function is applied to the input to obtain a new encoder
for the input. The function mapToEncoder
is provided to assist with building these
encoders. See examples in hs
.
When decoding, the value of the discriminator property is looked up in the HashMap
to obtain a decoder for the output. The function mapToDecoder
is provided
to assist with building these decoders. See examples in hs
.
The HashMap
is also used to generate schemas for the type.
In particular, for OpenAPI 3, it will generate a schema with a discriminator
, as defined
by https://swagger.io/docs/specification/data-models/inheritance-and-polymorphism/
API Note
This is a forward-compatible version of DiscriminatedUnionCodec
.
discriminatedUnionCodec = 'DiscriminatedUnionCodec'
bimapCodec :: (oldOutput -> Either String newOutput) -> (newInput -> oldInput) -> Codec context oldInput oldOutput -> Codec context newInput newOutput Source #
Map a codec's input and output types.
This function allows you to have the parsing fail in a new way.
If you use this function, then you will most likely want to add documentation about how not every value that the schema specifies will be accepted.
This function is like BimapCodec
except it also combines one level of a nested BimapCodec
s.
Example usage
logLevelCodec :: JSONCodec LogLevel logLevelCodec = bimapCodec parseLogLevel renderLogLevel codec ? "Valid values include DEBUG, INFO, WARNING, ERROR."
vectorCodec :: ValueCodec input output -> ValueCodec (Vector input) (Vector output) Source #
Vector codec
Build a codec for vectors of values from a codec for a single value.
Example usage
>>>
toJSONVia (vectorCodec codec) (Vector.fromList ['a','b'])
Array [String "a",String "b"]
API Note
This is a forward-compatible version of ArrayOfCodec
without a name.
vectorCodec = ArrayOfCodec Nothing
listCodec :: ValueCodec input output -> ValueCodec [input] [output] Source #
List codec
Build a codec for lists of values from a codec for a single value.
Example usage
>>>
toJSONVia (listCodec codec) ['a','b']
Array [String "a",String "b"]
API Note
This is the list version of vectorCodec
.
nonEmptyCodec :: ValueCodec input output -> ValueCodec (NonEmpty input) (NonEmpty output) Source #
Build a codec for nonempty lists of values from a codec for a single value.
Example usage
>>>
toJSONVia (nonEmptyCodec codec) ('a' :| ['b'])
Array [String "a",String "b"]
API Note
This is the non-empty list version of vectorCodec
.
singleOrListCodec :: ValueCodec input output -> ValueCodec [input] [output] Source #
Single or list codec
This codec behaves like listCodec
, except the values may also be
simplified as a single value.
During parsing, a single element may be parsed as the list of just that element. During rendering, a list with only one element will be rendered as just that element.
Example usage
>>>
let c = singleOrListCodec codec :: JSONCodec [Int]
>>>
toJSONVia c [5]
Number 5.0>>>
toJSONVia c [5,6]
Array [Number 5.0,Number 6.0]>>>
JSON.parseMaybe (parseJSONVia c) (Number 5) :: Maybe [Int]
Just [5]>>>
JSON.parseMaybe (parseJSONVia c) (Array [Number 5, Number 6]) :: Maybe [Int]
Just [5,6]
WARNING
If you use nested lists, for example when the given value codec is also a
listCodec
, you may get in trouble with ambiguities during parsing.
singleOrNonEmptyCodec :: ValueCodec input output -> ValueCodec (NonEmpty input) (NonEmpty output) Source #
Single or nonempty list codec
This codec behaves like nonEmptyCodec
, except the values may also be
simplified as a single value.
During parsing, a single element may be parsed as the list of just that element. During rendering, a list with only one element will be rendered as just that element.
Example usage
>>>
let c = singleOrNonEmptyCodec codec :: JSONCodec (NonEmpty Int)
>>>
toJSONVia c (5 :| [])
Number 5.0>>>
toJSONVia c (5 :| [6])
Array [Number 5.0,Number 6.0]>>>
JSON.parseMaybe (parseJSONVia c) (Number 5) :: Maybe (NonEmpty Int)
Just (5 :| [])>>>
JSON.parseMaybe (parseJSONVia c) (Array [Number 5, Number 6]) :: Maybe (NonEmpty Int)
Just (5 :| [6])
WARNING
If you use nested lists, for example when the given value codec is also a
nonEmptyCodec
, you may get in trouble with ambiguities during parsing.
API Note
This is a nonempty version of singleOrListCodec
.
:: Text | Key |
-> ValueCodec input output | Codec for the value |
-> Text | Documentation |
-> ObjectCodec input output |
A required field
During decoding, the field must be in the object.
During encoding, the field will always be in the object.
:: Text | Key |
-> ValueCodec input output | Codec for the value |
-> ObjectCodec input output |
Like requiredFieldWith
, but without documentation.
:: Text | Key |
-> ValueCodec input output | Codec for the value |
-> Text | Documentation |
-> ObjectCodec (Maybe input) (Maybe output) |
:: Text | Key |
-> ValueCodec input output | Codec for the value |
-> ObjectCodec (Maybe input) (Maybe output) |
Like optionalFieldWith
, but without documentation.
optionalFieldWithDefaultWith Source #
:: Text | Key |
-> JSONCodec output | Codec for the value |
-> output | Default value |
-> Text | Documentation |
-> ObjectCodec output output |
An optional field with default value
During decoding, the field may be in the object. The default value will be parsed otherwise.
During encoding, the field will always be in the object. The default value is ignored.
The shown version of the default value will appear in the documentation.
optionalFieldWithDefaultWith' Source #
:: Text | Key |
-> JSONCodec output | Codec for the value |
-> output | Default value |
-> ObjectCodec output output |
Like optionalFieldWithDefaultWith
, but without documentation.
optionalFieldWithOmittedDefaultWith Source #
:: Eq output | |
=> Text | Key |
-> JSONCodec output | Codec for the value |
-> output | Default value |
-> Text | Documentation |
-> ObjectCodec output output |
An optional field with default value that can be omitted when encoding
During decoding, the field may be in the object. The default value will be parsed otherwise.
During encoding, the field will be omitted from the object if it is equal to the default value.
The shown version of the default value will appear in the documentation.
optionalFieldWithOmittedDefaultWith' Source #
:: Eq output | |
=> Text | Key |
-> JSONCodec output | Codec for the value |
-> output | Default value |
-> ObjectCodec output output |
Like optionalFieldWithOmittedDefaultWith
, but without documentation.
optionalFieldOrNullWithOmittedDefaultWith Source #
:: Eq output | |
=> Text | Key |
-> JSONCodec output | Codec for the value |
-> output | Default value |
-> Text | Documentation |
-> ObjectCodec output output |
Like optionalFieldWithOmittedDefaultWith
, but the value may also be
null
and that will be interpreted as the default value.
optionalFieldOrNullWithOmittedDefaultWith' Source #
:: Eq output | |
=> Text | Key |
-> JSONCodec output | Codec for the value |
-> output | Default value |
-> ObjectCodec output output |
Like optionalFieldWithOmittedDefaultWith'
, but the value may also be
null
and that will be interpreted as the default value.
optionalFieldOrNullWith Source #
:: Text | Key |
-> ValueCodec input output | Codec for the value |
-> Text | Documentation |
-> ObjectCodec (Maybe input) (Maybe output) |
optionalFieldOrNullWith' Source #
:: Text | Key |
-> ValueCodec input output | Codec for the value |
-> ObjectCodec (Maybe input) (Maybe output) |
Like optionalFieldOrNullWith
, but without documentation
:: ValueCodec input output | |
-> Text | Comment |
-> ValueCodec input output |
Add a comment to a codec
This is an infix version of CommentCodec
> (?) = flip CommentCodec
:: ValueCodec input output | |
-> [Text] | Lines of comments |
-> ValueCodec input output |
A version of <?>
that lets you supply a list of lines of text instead of a single text.
This helps when you use an automated formatter that deals with lists more nicely than with multi-line strings.
hashMapCodec :: (Eq k, Hashable k, FromJSONKey k, ToJSONKey k) => JSONCodec v -> JSONCodec (HashMap k v) Source #
Encode a HashMap
, and decode any HashMap
.
API Note
This is a forward-compatible version of HashMapCodec
.
hashMapCodec = HashMapCodec
keyMapCodec :: JSONCodec v -> JSONCodec (KeyMap v) Source #
Encode a KeyMap
, and decode any KeyMap
.
This chooses hashMapCodec
or mapCodec
based on ordered-keymap
flag in aeson.
valueCodec :: JSONCodec Value Source #
Codec for a Value
This is essentially your escape-hatch for when you would normally need a monad instance for Codec
.
You can build monad parsing by using valueCodec
together with bimapCodec
and supplying your own parsing function.
Note that this _does_ mean that the documentation will just say that you are parsing and rendering a value, so you may want to document the extra parsing further using <?>
.
API Note
This is a forward-compatible version of Codec
.
valueCodec = ValueCodec
nullCodec :: JSONCodec () Source #
Codec for null
Example usage
>>>
toJSONVia nullCodec ()
Null>>>
JSON.parseMaybe (parseJSONVia nullCodec) Null
Just ()>>>
JSON.parseMaybe (parseJSONVia nullCodec) (Number 5)
Nothing
API Note
This is a forward-compatible version of NullCodec
.
nullCodec = NullCodec
boolCodec :: JSONCodec Bool Source #
Codec for boolean values
Example usage
>>>
toJSONVia boolCodec True
Bool True
API Note
This is a forward-compatible version of BoolCodec
without a name.
boolCodec = BoolCodec Nothing
textCodec :: JSONCodec Text Source #
Codec for text values
Example usage
>>>
toJSONVia textCodec "hello"
String "hello"
API Note
This is a forward-compatible version of StringCodec
without a name.
textCodec = StringCodec Nothing
scientificCodec :: JSONCodec Scientific Source #
Codec for Scientific
values
Example usage
>>>
toJSONVia scientificCodec 5
Number 5.0>>>
JSON.parseMaybe (parseJSONVia scientificCodec) (Number 3)
Just 3.0
WARNING
Scientific
is a type that is only for JSON parsing and rendering.
Do not use it for any calculations.
Instead, convert to another number type before doing any calculations.
λ> (1 / 3) :: Scientific *** Exception: fromRational has been applied to a repeating decimal which can't be represented as a Scientific! It's better to avoid performing fractional operations on Scientifics and convert them to other fractional types like Double as early as possible.
API Note
This is a forward-compatible version of NumberCodec
without a name.
scientificCodec = NumberCodec Nothing Nothing
scientificWithBoundsCodec :: NumberBounds -> JSONCodec Scientific Source #
Codec for Scientific
values with bounds
Example usage
>>>
let c = scientificWithBoundsCodec NumberBounds {numberBoundsLower = 2, numberBoundsUpper = 4}
>>>
toJSONVia c 3
Number 3.0>>>
toJSONVia c 5
Number 5.0>>>
JSON.parseMaybe (parseJSONVia c) (Number 3)
Just 3.0>>>
JSON.parseMaybe (parseJSONVia c) (Number 5)
Nothing
WARNING
Scientific
is a type that is only for JSON parsing and rendering.
Do not use it for any calculations.
Instead, convert to another number type before doing any calculations.
λ> (1 / 3) :: Scientific *** Exception: fromRational has been applied to a repeating decimal which can't be represented as a Scientific! It's better to avoid performing fractional operations on Scientifics and convert them to other fractional types like Double as early as possible.
API Note
This is a forward-compatible version of NumberCodec
without a name.
scientificWithBoundsCodec bounds = NumberCodec Nothing (Just bounds)
object :: Text -> ObjectCodec input output -> ValueCodec input output Source #
An object codec with a given name
Example usage
data Example = Example { exampleText :: !Text, exampleBool :: !Bool } instance HasCodec Example where codec = object "Example" $ Example <$> requiredField "text" "a text" .= exampleText <*> requiredField "bool" "a bool" .= exampleBool
API Note
This is a forward-compatible version ObjectOfCodec
with a name.
object name = ObjectOfCodec (Just name)
boundedIntegralCodec :: forall i. (Integral i, Bounded i) => JSONCodec i Source #
A codec for bounded integers like Int
, Int8
, and Word
.
This codec will not have a name, and it will use the boundedNumberBounds
to add number bounds.
>>>
let c = boundedIntegralCodec :: JSONCodec Int8
>>>
toJSONVia c 5
Number 5.0>>>
JSON.parseMaybe (parseJSONVia c) (Number 100)
Just 100>>>
JSON.parseMaybe (parseJSONVia c) (Number 200)
Nothing
boundedIntegralNumberBounds :: forall i. (Integral i, Bounded i) => NumberBounds Source #
NumberBounds
for a bounded integral type.
You can call this using TypeApplications
: boundedIntegralNumberBounds
Word@
literalTextCodec :: Text -> JSONCodec Text Source #
A codec for a literal piece of Text
.
During parsing, only the given Text
is accepted.
During rendering, the given Text
is always output.
Example usage
>>>
let c = literalTextCodec "hello"
>>>
toJSONVia c "hello"
String "hello">>>
toJSONVia c "world"
String "hello">>>
JSON.parseMaybe (parseJSONVia c) (String "hello")
Just "hello">>>
JSON.parseMaybe (parseJSONVia c) (String "world")
Nothing
literalTextValueCodec :: value -> Text -> JSONCodec value Source #
A codec for a literal value corresponding to a literal piece of Text
.
During parsing, only the given Text
is accepted.
During rendering, the given value
is always output.
Example usage
>>>
let c = literalTextValueCodec True "yes"
>>>
toJSONVia c True
String "yes">>>
toJSONVia c False
String "yes">>>
JSON.parseMaybe (parseJSONVia c) (String "yes") :: Maybe Bool
Just True>>>
JSON.parseMaybe (parseJSONVia c) (String "no") :: Maybe Bool
Nothing
:: Codec context input output | First codec |
-> Codec context input' output | Second codec |
-> (newInput -> Either input input') | Rendering chooser |
-> Codec context newInput output |
A choice codec, but unlike eitherCodec
, it's for the same output type instead of different ones.
While parsing, this codec will first try the left codec, then the right if that fails.
While rendering, the provided function is used to decide which codec to use for rendering.
Note: The reason this is less primitive than the eitherCodec
is that Either
makes it clear which codec you want to use for rendering.
In this case, we need to provide our own function for choosing which codec we want to use for rendering.
Example usage
>>>
:{
let c = matchChoiceCodec (literalTextCodec "even") (literalTextCodec "odd") (\s -> if s == "even" then Left s else Right s) :}
>>>
toJSONVia c "even"
String "even">>>
toJSONVia c "odd"
String "odd">>>
JSON.parseMaybe (parseJSONVia c) (String "even") :: Maybe Text
Just "even">>>
JSON.parseMaybe (parseJSONVia c) (String "odd") :: Maybe Text
Just "odd"
API Note
This is a forward-compatible version of 'matchChoiceCodecAs PossiblyJointUnion':
disjointMatchChoiceCodec = matchChoiceCodecAs PossiblyJointUnion
disjointMatchChoiceCodec Source #
:: Codec context input output | First codec |
-> Codec context input' output | Second codec |
-> (newInput -> Either input input') | Rendering chooser |
-> Codec context newInput output |
Disjoint version of matchChoiceCodec
API Note
This is a forward-compatible version of 'matchChoiceCodecAs DisjointUnion':
disjointMatchChoiceCodec = matchChoiceCodecAs DisjointUnion
:: Union | Is the union DisjointUnion or PossiblyJointUnion |
-> Codec context input output | First codec |
-> Codec context input' output | Second codec |
-> (newInput -> Either input input') | Rendering chooser |
-> Codec context newInput output |
An even more general version of matchChoiceCodec
and disjointMatchChoiceCodec
.
:: [(input -> Maybe input, Codec context input output)] | Codecs, each with their own rendering matcher |
-> Codec context input output | Fallback codec, in case none of the matchers in the list match |
-> Codec context input output |
A choice codec for a list of options, each with their own rendering matcher.
During parsing, each of the codecs are tried from first to last until one succeeds.
During rendering, each matching function is tried until either one succeeds and the corresponding codec is used, or none succeed and the fallback codec is used.
Example usage
>>>
:{
let c = matchChoicesCodec [ (\s -> if s == "even" then Just s else Nothing, literalTextCodec "even") , (\s -> if s == "odd" then Just s else Nothing, literalTextCodec "odd") ] (literalTextCodec "fallback") :}
>>>
toJSONVia c "even"
String "even">>>
toJSONVia c "odd"
String "odd">>>
toJSONVia c "foobar"
String "fallback">>>
JSON.parseMaybe (parseJSONVia c) (String "even") :: Maybe Text
Just "even">>>
JSON.parseMaybe (parseJSONVia c) (String "odd") :: Maybe Text
Just "odd">>>
JSON.parseMaybe (parseJSONVia c) (String "foobar") :: Maybe Text
Nothing>>>
JSON.parseMaybe (parseJSONVia c) (String "fallback") :: Maybe Text
Just "fallback"
API Note
This is a forward-compatible version of 'matchChoicesCodecAs DisjointUnion'.
disjointMatchChoiceCodec = matchChoicesCodecAs DisjointUnion
disjointMatchChoicesCodec Source #
:: [(input -> Maybe input, Codec context input output)] | Codecs, each with their own rendering matcher |
-> Codec context input output | Fallback codec, in case none of the matchers in the list match |
-> Codec context input output |
Disjoint version of matchChoicesCodec
API Note
This is a forward-compatible version of 'matchChoicesCodecAs DisjointUnion'.
disjointMatchChoiceCodec = matchChoicesCodecAs DisjointUnion
:: Union | |
-> [(input -> Maybe input, Codec context input output)] | Codecs, each with their own rendering matcher |
-> Codec context input output | Fallback codec, in case none of the matchers in the list match |
-> Codec context input output |
An even more general version of matchChoicesCodec
and disjointMatchChoicesCodec
:: Codec context input output | Main codec, for parsing and rendering |
-> [Codec context input output] | Alternative codecs just for parsing |
-> Codec context input output |
Use one codec for the default way of parsing and rendering, but then also use a list of other codecs for potentially different parsing.
You can use this for keeping old ways of parsing intact while already rendering in the new way.
Example usage
>>>
data Fruit = Apple | Orange deriving (Show, Eq, Bounded, Enum)
>>>
let c = parseAlternatives shownBoundedEnumCodec [stringConstCodec [(Apple, "foo"), (Orange, "bar")]]
>>>
toJSONVia c Apple
String "Apple">>>
JSON.parseMaybe (parseJSONVia c) (String "foo") :: Maybe Fruit
Just Apple>>>
JSON.parseMaybe (parseJSONVia c) (String "Apple") :: Maybe Fruit
Just Apple>>>
JSON.parseMaybe (parseJSONVia c) (String "Tomato") :: Maybe Fruit
Nothing
:: Codec context input output | Main codec, for parsing and rendering |
-> Codec context input' output | Alternative codecs just for parsing |
-> Codec context input output |
Like parseAlternatives
, but with only one alternative codec
Example usage
Values
>>>
data Fruit = Apple | Orange deriving (Show, Eq, Bounded, Enum)
>>>
let c = parseAlternative shownBoundedEnumCodec (stringConstCodec [(Apple, "foo"), (Orange, "bar")])
>>>
toJSONVia c Apple
String "Apple">>>
JSON.parseMaybe (parseJSONVia c) (String "foo") :: Maybe Fruit
Just Apple>>>
JSON.parseMaybe (parseJSONVia c) (String "Apple") :: Maybe Fruit
Just Apple
Required object fields
>>>
data Fruit = Apple | Orange deriving (Show, Eq, Bounded, Enum)
>>>
let c = shownBoundedEnumCodec
>>>
let o = parseAlternative (requiredFieldWith "current" c "current key for this field") (requiredFieldWith "legacy" c "legacy key for this field")
>>>
toJSONObjectVia o Apple
fromList [("current",String "Apple")]>>>
JSON.parseMaybe (parseJSONObjectVia o) (KM.fromList [("current",String "Apple")]) :: Maybe Fruit
Just Apple>>>
JSON.parseMaybe (parseJSONObjectVia o) (KM.fromList [("legacy",String "Apple")]) :: Maybe Fruit
Just Apple>>>
JSON.parseMaybe (parseJSONObjectVia o) (KM.fromList [("current",String "Tomato")]) :: Maybe Fruit
Nothing
Required object fields
While parseAlternative
works exactly like you would expect it would with requiredField
, using parseAlterternative
with optional fields has some pitfalls.
>>>
data Fruit = Apple | Orange deriving (Show, Eq, Bounded, Enum)
>>>
let c = shownBoundedEnumCodec
>>>
let o = parseAlternative (optionalFieldWith "current" c "current key for this field") (optionalFieldWith "legacy" c "legacy key for this field")
>>>
toJSONObjectVia o (Just Apple)
fromList [("current",String "Apple")]>>>
toJSONObjectVia o Nothing
fromList []>>>
JSON.parseMaybe (parseJSONObjectVia o) (KM.fromList [("current",String "Apple")]) :: Maybe (Maybe Fruit)
Just (Just Apple)
! This is the important result !
The second optionalFieldWith
is not tried because the first one _succeeds_ in parsing Nothing
>>>
JSON.parseMaybe (parseJSONObjectVia o) (KM.fromList [("legacy",String "Apple")]) :: Maybe (Maybe Fruit)
Just Nothing
Here the parser succeeds as well, because it fails to parse the current
field, so it tries to parse the legacy
field, which is missing.
>>>
JSON.parseMaybe (parseJSONObjectVia o) (KM.fromList [("current",String "Tomato")]) :: Maybe (Maybe Fruit)
Just Nothing
enumCodec :: forall enum context. Eq enum => NonEmpty (enum, Codec context enum enum) -> Codec context enum enum Source #
A codec for an enum that can be written each with their own codec.
WARNING
If you don't provide a string for one of the type's constructors, the last codec in the list will be used instead.
stringConstCodec :: forall constant. Eq constant => NonEmpty (constant, Text) -> JSONCodec constant Source #
A codec for an enum that can be written as constant string values
Example usage
>>>
data Fruit = Apple | Orange deriving (Show, Eq)
>>>
let c = stringConstCodec [(Apple, "foo"), (Orange, "bar")]
>>>
toJSONVia c Orange
String "bar">>>
JSON.parseMaybe (parseJSONVia c) (String "foo") :: Maybe Fruit
Just Apple
WARNING
If you don't provide a string for one of the type's constructors, the last string in the list will be used instead:
>>>
let c = stringConstCodec [(Apple, "foo")]
>>>
toJSONVia c Orange
String "foo"
shownBoundedEnumCodec :: forall enum. (Show enum, Eq enum, Enum enum, Bounded enum) => JSONCodec enum Source #
A codec for a Bounded
Enum
that uses its Show
instance to have the values correspond to literal Text
values.
Example usage
>>>
data Fruit = Apple | Orange deriving (Show, Eq, Enum, Bounded)
>>>
let c = shownBoundedEnumCodec
>>>
toJSONVia c Apple
String "Apple">>>
JSON.parseMaybe (parseJSONVia c) (String "Orange") :: Maybe Fruit
Just Orange
orNullHelper :: ObjectCodec (Maybe (Maybe input)) (Maybe (Maybe output)) -> ObjectCodec (Maybe input) (Maybe output) Source #
Helper function for optionalFieldOrNullWith
and optionalFieldOrNull
.
You probably don't need this.
named :: Text -> ValueCodec input output -> ValueCodec input output Source #
Name a codec.
This is used to allow for references to the codec, and that's necessary to produce finite documentation for recursive codecs.
API Note
This is a forward-compatible version of ReferenceCodec
.
named = ReferenceCodec
Produce a codec using a type's FromJSON
and ToJSON
instances.
You will only want to use this if you cannot figure out how to produce a
JSONCodec
for your type.
Note that this will not have good documentation because, at a codec level,
it's just parsing and rendering a Value
.
Example usage
>>>
toJSONVia (codecViaAeson "Int") (5 :: Int)
Number 5.0>>>
JSON.parseMaybe (parseJSONVia (codecViaAeson "Int")) (Number 5) :: Maybe Int
Just 5