| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Waargonaut.Generic
Description
This module contains the types and functions that power the Generic functions for Waargonaut. Code
 that writes the code so you don't have to.
Synopsis
- class JsonEncode t a where
- mkEncoder :: Applicative f => Tagged t (Encoder f a)
 
 - class JsonDecode t a where
 - data GWaarg
 - data NewtypeName
 - data Options = Options {}
 - defaultOpts :: Options
 - trimPrefixLowerFirst :: Text -> String -> String
 - gEncoder :: forall t a f. (Generic a, Applicative f, HasDatatypeInfo a, All2 (JsonEncode t) (Code a)) => Options -> Tagged t (Encoder f a)
 - gDecoder :: forall f a t. (Generic a, HasDatatypeInfo a, All2 (JsonDecode t) (Code a), Monad f) => Options -> Tagged t (Decoder f a)
 - module Data.Tagged
 - module Data.Tagged
 - class All (SListI :: [Type] -> Constraint) (Code a) => Generic a where
 - class Generic a => HasDatatypeInfo a where
- type DatatypeInfoOf a :: DatatypeInfo
 - datatypeInfo :: proxy a -> DatatypeInfo (Code a)
 
 
Rationale
Although creating your Decoders and Encoders explicitly is the preferred way of utilising
 Waargonaut. The Generic mechanism within Haskell provides immense opportunity to reduce or
 eliminate the need to write code. Given the mechanical nature of JSON this a benefit that cannot
 be ignored. 
There are two typeclasses provided, JsonEncode and JsonDecode. Each with a single function
 that will generate a Encoder or Decoder for that type. Normally, typeclasses such as these
 are only parameterised over the type that is to be encoded/decoded. Which is acceptable if there
 is only ever a single possible way to encode or decode a value of that type. However this is
 rarely the case, even with respect to strings or numbers.
To account for this, the JsonEncode and JsonDecode typeclasses require an additional type
 parameter  t . This parameter allows you to differentiate between the alternative ways of
 encoding or decoding a single type  a . This parameter is attached to the Encoder or
 Decoder using the Tagged newtype. Allowing the type system to help you keep track of them.
Quick Start
A quick example on how to use the Waargonaut Generic functionality. We will use the following
 type and let GHC and Generic write our Encoder and Decoder for us.
data Image = Image
  { _imageWidth    :: Int
  , _imageHeight   :: Int
  , _imageTitle    :: Text
  , _imageAnimated :: Bool
  , _imageIDs      :: [Int]
  }
  deriving (Eq, Show)
Ensure we have the required imports and language options:
{-# LANGUAGE DeriveGeneric #-}
import qualified GHC.Generic as GHC
import Waargonaut.Generic (Generic, HasDatatypeInfo, JsonEncode, JsonDecode, GWaarg)
Update our data type 'deriving' to have GHC to do the heavy lifting:
data Image = Image ... deriving (..., GHC.Generic)
Because Waargonaut uses the 'generics-sop'
 package to make the Generic functions easier to write and maintain. We need two more instances,
 note that we don't have to write these either. We can leave these empty and the default
 implementations, courtesy of Generic, will handle it for us.
instance HasDatatypeInfo Image instance Generic Image
Now we can define our JsonEncode and JsonDecode instances. We need to provide the  t 
 parameter. Assume we have no special requirements, so we can use the GWaarg tag.
instance JsonEncode GWaarg Image instance JsonDecode GWaarg Image
That's it! We can now use mkEncoder and mkDecoder to write the code for our Image type.
 These will be tagged with our GWaarg phantom type parameter:
mkEncoder :: Applicative f => Tagged GWaarg (Encoder f Image) mkDecoder :: Monad f => Tagged GWaarg (Decoder f Image)
The encoding and decoding "runner" functions will require that you remove the tag. You can use
 the untag function for this. The next section will discuss the Tagged type.
There is Template Haskell available that can write all of the Generic deriving for you, see the
 'Generics.SOP.TH'
 module in the 'generics-sop' package for more. Given how little boilerplate code is required and
 that the Template Haskell extension enforces a strict ordering of code within the file. It is not
 the recommended solution. But I'm not your supervisor, I'm just a library.
Tagged
 The Tagged type comes from the 'tagged' package.
 It is a 'newtype' that provides a phantom type parameter. As well as having a several useful
 typeclass instances and helpful functions already written for us.
When dealing with the Tagged Encoders and Decoders there are two functions that are
 particularly useful; untag, and proxy.
The untag function removes the tag from the inner type:
untag :: -- forall k (s :: k) b. Tagged s b -> b
When used with one of the Tagged Generic functions:
let e = mkEncoder :: Applicative f => Tagged GWaarg (Encoder f Image) untag e :: Applicative f => Encoder f Image
The other function proxy, allows you to use mkEncoder or mkDecoder with the desired  t 
 parameter and then immediately remove the tag. This function requires the use of some proxy
 that carries the same  t  of your instance:
proxy :: Tagged s a -> proxy s -> a
One way to utilise this function is in combination with Proxy from base:
(proxy mkDecoder (Proxy :: Proxy GWaarg)) :: Monad f => Decoder f Image
This lets you skip the untag step but without losing the safety of the Tagged phantom type.
GHC >= 8 Convenience
All of the techniques described above are explicit and will work in all versions of GHC that Waargonaut supports. Should you be running a GHC that is version 8.0.1 or later, then you have access to a language extension called TypeApplications.
This extension allows you to avoid much of the explicit type annotations described in Tagged
 section of Waargonaut.Generic. For example the proxy function may be utilised like so:
(proxy mkDecoder (Proxy :: Proxy GWaarg)) :: Monad f => Decoder f Image
Becomes:
(proxy mkDecoder @GWaarg) :: Monad f => Decoder f Image
You can also use the TypeApplications directly on the mkEncoder or mkDecoder function:
mkEncoder GWaarg :: Applicative f => Tagged GWaarg (Encoder f Image)
mkDecoder GWaarg :: Monad f       => Tagged GWaarg (Decoder f Image)
TypeClasses
class JsonEncode t a where Source #
Encoding Typeclass for Waargonaut.
This type class is responsible for creating an Encoder for the type of  a , differentiated
 from the other possible instances of this typeclass for type  a  by the tag type  t .
To create a Tagged Encoder for the purposes of writing an instance your self, you need only
 data constructor Tagged from Tagged. It has been re-exported from this module.
instance JsonEncode GWaarg Foo where mkEncoder = Tagged fooEncoderIWroteEarlier
Minimal complete definition
Nothing
Methods
mkEncoder :: Applicative f => Tagged t (Encoder f a) Source #
mkEncoder :: (Applicative f, Generic a, HasDatatypeInfo a, All2 (JsonEncode t) (Code a)) => Tagged t (Encoder f a) Source #
Instances
| JsonEncode (t :: k) Bool Source # | |
Defined in Waargonaut.Generic  | |
| JsonEncode (t :: k) Scientific Source # | |
Defined in Waargonaut.Generic Methods mkEncoder :: Applicative f => Tagged t (Encoder f Scientific) Source #  | |
| JsonEncode (t :: k) Int Source # | |
Defined in Waargonaut.Generic  | |
| JsonEncode (t :: k) Text Source # | |
Defined in Waargonaut.Generic  | |
| JsonEncode t a => JsonEncode (t :: k) (NonEmpty a) Source # | |
Defined in Waargonaut.Generic  | |
| JsonEncode t a => JsonEncode (t :: k) [a] Source # | |
Defined in Waargonaut.Generic  | |
| JsonEncode t a => JsonEncode (t :: k) (Maybe a) Source # | |
Defined in Waargonaut.Generic  | |
| (JsonEncode t a, JsonEncode t b) => JsonEncode (t :: k) (Either a b) Source # | |
Defined in Waargonaut.Generic  | |
class JsonDecode t a where Source #
Decoding Typeclass for Waargonaut
Responsible for creating a Decoder for the type  a , differentiated from the other possible
 instances of this typeclass for type  a  by the tag type  t .
To create a Tagged Decoder for the purposes of writing an instance your self, you need only
 data constructor Tagged from Tagged. It has been re-exported from this module.
instance JsonDecode GWaarg Foo where mkDecoder = Tagged fooDecoderIWroteEarlier
Minimal complete definition
Nothing
Methods
mkDecoder :: Monad f => Tagged t (Decoder f a) Source #
mkDecoder :: (Monad f, Generic a, HasDatatypeInfo a, All2 (JsonDecode t) (Code a)) => Tagged t (Decoder f a) Source #
Instances
| JsonDecode (t :: k) Bool Source # | |
| JsonDecode (t :: k) Scientific Source # | |
Defined in Waargonaut.Generic  | |
| JsonDecode (t :: k) Int Source # | |
| JsonDecode (t :: k) Text Source # | |
| JsonDecode t a => JsonDecode (t :: k) (NonEmpty a) Source # | |
| JsonDecode t a => JsonDecode (t :: k) [a] Source # | |
| JsonDecode t a => JsonDecode (t :: k) (Maybe a) Source # | |
| (JsonDecode t a, JsonDecode t b) => JsonDecode (t :: k) (Either a b) Source # | |
Tag
This is a provided tag that may be used for tagging the JsonEncode and JsonDecode
 instances. You are encouraged to make your own tags for full control of your own instances.
Options
data NewtypeName Source #
The options we currently have for using the Generic mechanism to handle 'newtype' values:
Constructors
| Unwrap | Discard the newtype wrapper and encode the inner value. newtype Foo = Foo Text let x = Foo Fred Will be encoded as:   | 
| ConstructorNameAsKey | Encode the newtype value as an object using the constructor as the "key". newtype Foo = Foo Text let x = Foo Fred  | 
Instances
| Eq NewtypeName Source # | |
Defined in Waargonaut.Generic  | |
| Show NewtypeName Source # | |
Defined in Waargonaut.Generic Methods showsPrec :: Int -> NewtypeName -> ShowS # show :: NewtypeName -> String # showList :: [NewtypeName] -> ShowS #  | |
The configuration options for creating Generic encoder or decoder values.
Constructors
| Options | |
Fields 
  | |
trimPrefixLowerFirst :: Text -> String -> String Source #
Helper function to alter record field names for encoding and decoding. Intended use is to be
 given the prefix you would like to have removed and then included in the Options for the
 typeclass you are implementing.
A common use case when encoding Haskell record types is to remove a prefix and then lower-case the first letter:
>>>trimPrefixLowerFirst "_image" "_imageHeight""height"
>>>trimPrefixLowerFirst "_image" "Height""Height"
>>>trimPrefixLowerFirst "_image" """"
>>>trimPrefixLowerFirst "" "_imageHeight""_imageHeight"
Creation
gEncoder :: forall t a f. (Generic a, Applicative f, HasDatatypeInfo a, All2 (JsonEncode t) (Code a)) => Options -> Tagged t (Encoder f a) Source #
Create a Tagged Encoder for type  a , tagged by  t , using the given Options.
Combined with the defaultOpts this is the default implementation of JsonEncode.
Some examples:
instance JsonEncode GWaarg Image where mkEncoder = gEncoder defaultOpts
instance JsonEncode GWaarg Image where
  mkEncoder = gEncoder (defaultOpts { _optionsFieldName = trimPrefixLowerFirst "_image" })
gDecoder :: forall f a t. (Generic a, HasDatatypeInfo a, All2 (JsonDecode t) (Code a), Monad f) => Options -> Tagged t (Decoder f a) Source #
Create a Tagged Decoder for type  a , tagged by  t , using the given Options.
Combined with the defaultOpts this is the default implementation of JsonEncode.
Some examples:
instance JsonEncode GWaarg Image where mkDecoder = gDecoder defaultOpts
instance JsonEncode GWaarg Image where
  mkDecoder = gDecoder (defaultOpts { _optionsFieldName = trimPrefixLowerFirst "_image" })
Reexports
module Data.Tagged
module Data.Tagged
class All (SListI :: [Type] -> Constraint) (Code a) => Generic a where #
The class of representable datatypes.
The SOP approach to generic programming is based on viewing
 datatypes as a representation (Rep) built from the sum of
 products of its components. The components of are datatype
 are specified using the Code type family.
The isomorphism between the original Haskell datatype and its
 representation is witnessed by the methods of this class,
 from and to. So for instances of this class, the following
 laws should (in general) hold:
to.from===id:: a -> afrom.to===id::Repa ->Repa
You typically don't define instances of this class by hand, but rather derive the class instance automatically.
Option 1: Derive via the built-in GHC-generics. For this, you
 need to use the DeriveGeneric extension to first derive an
 instance of the Generic class from module GHC.Generics.
 With this, you can then give an empty instance for Generic, and
 the default definitions will just work. The pattern looks as
 follows:
import qualified GHC.Generics as GHC import Generics.SOP ... data T = ... deriving (GHC.Generic, ...) instanceGenericT -- empty instanceHasDatatypeInfoT -- empty, if you want/need metadata
Option 2: Derive via Template Haskell. For this, you need to
 enable the TemplateHaskell extension. You can then use
 deriveGeneric from module Generics.SOP.TH
 to have the instance generated for you. The pattern looks as
 follows:
import Generics.SOP import Generics.SOP.TH ... data T = ...deriveGeneric''T -- derivesHasDatatypeInfoas well
Tradeoffs: Whether to use Option 1 or 2 is mainly a matter of personal taste. The version based on Template Haskell probably has less run-time overhead.
Non-standard instances:
 It is possible to give Generic instances manually that deviate
 from the standard scheme, as long as at least
to.from===id:: a -> a
still holds.
Minimal complete definition
Nothing
Associated Types
The code of a datatype.
This is a list of lists of its components. The outer list contains one element per constructor. The inner list contains one element per constructor argument (field).
Example: The datatype
data Tree = Leaf Int | Node Tree Tree
is supposed to have the following code:
type instance Code (Tree a) = '[ '[ Int ] , '[ Tree, Tree ] ]
class Generic a => HasDatatypeInfo a where #
A class of datatypes that have associated metadata.
It is possible to use the sum-of-products approach to generic programming without metadata. If you need metadata in a function, an additional constraint on this class is in order.
You typically don't define instances of this class by hand, but
 rather derive the class instance automatically. See the documentation
 of Generic for the options.
Minimal complete definition
Nothing
Methods
datatypeInfo :: proxy a -> DatatypeInfo (Code a) #
Term-level datatype info; by default, the term-level datatype info is produced from the type-level info.