| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Toml.Generic
Contents
Description
This module contains implementation of the Generic TOML codec. If your
data types are big and nested, and you want to have codecs for them without writing a lot of
boilerplate code, you can find this module helpful. Below you can find the detailed
explanation on how the Generic codecs work.
Consider the following Haskell data types:
data User = User
{ age :: Int
, address :: Address
, socials :: [Social]
} deriving (Generic)
data Address = Address
{ street :: Text
, house :: Int
} deriving (Generic)
data Social = Social
{ name :: Text
, link :: Text
} deriving (Generic)
Value of the User type represents the following TOML:
age = 27 [address] street = "Miami Beach" house = 42 [[socials]] name = "Twitter" link = "https://twitter.com/foo" [[socials]] name = "GitHub" link = "https://github.com/bar"
Normally you would write TomlCodec for this data type like this:
userCodec ::TomlCodecUser userCodec = User <$> Toml.int "age" .= age <*> Toml.table addressCodec "address" .= address <*> Toml.list socialCodec "socials" .= socials addressCodec ::TomlCodecAddress addressCodec = Address <$> Toml.text "street" .= street <*> Toml.int "house" .= house socialCodec ::TomlCodecSocial socialCodec = Social <$> Toml.text "name" .= name <*> Toml.text "link" .= link
However, if you derive Generic instance for your data types (as we do in the
example), you can write your codecs in a simpler way.
userCodec ::TomlCodecUser userCodec =genericCodecinstanceHasCodecAddress where hasCodec = Toml.tablegenericCodecinstanceHasItemCodecSocial where hasItemCodec = RightgenericCodec
Several notes about the interface:
- Your top-level data types are always implemented as
genericCodec(or other generic codecs). - If you have a custom data type as a field of another type, you need to implement
the instance of the
HasCodectypeclass. - If the data type appears as an element of a list, you need to implement the instance
of the
HasItemCodectypeclass.
Since: 1.1.1.0
Synopsis
- genericCodec :: (Generic a, GenericCodec (Rep a)) => TomlCodec a
- genericCodecWithOptions :: forall a. (Generic a, GenericCodec (Rep a), Typeable a) => TomlOptions a -> TomlCodec a
- stripTypeNameCodec :: forall a. (Generic a, GenericCodec (Rep a), Typeable a) => TomlCodec a
- data TomlOptions a = TomlOptions {
- tomlOptionsFieldModifier :: Typeable a => Proxy a -> String -> String
- newtype GenericOptions = GenericOptions {}
- stripTypeNameOptions :: Typeable a => TomlOptions a
- stripTypeNamePrefix :: forall a. Typeable a => Proxy a -> String -> String
- class HasCodec a where
- class HasItemCodec a where
- hasItemCodec :: Either (TomlBiMap a AnyValue) (TomlCodec a)
- class GenericCodec (f :: k -> Type) where
- genericTomlCodec :: GenericOptions -> TomlCodec (f p)
Documentation
genericCodec :: (Generic a, GenericCodec (Rep a)) => TomlCodec a Source #
Generic codec for arbitrary data types. Uses field names as keys.
genericCodecWithOptions :: forall a. (Generic a, GenericCodec (Rep a), Typeable a) => TomlOptions a -> TomlCodec a Source #
Generic codec with options for arbitrary data types.
stripTypeNameCodec :: forall a. (Generic a, GenericCodec (Rep a), Typeable a) => TomlCodec a Source #
Generic codec that uses stripTypeNameOptions.
Options
data TomlOptions a Source #
Options to configure various parameters of generic encoding. Specifically:
tomlOptionsFieldModifier: how to translate field names to TOML keys?
Constructors
| TomlOptions | |
Fields
| |
newtype GenericOptions Source #
Same as TomlOptions but with all data type information erased. This data
type is used internally. Define your options using TomlOptions data type.
Constructors
| GenericOptions | |
Fields | |
stripTypeNameOptions :: Typeable a => TomlOptions a Source #
Options that use stripTypeNamePrefix as tomlOptionsFieldModifier.
stripTypeNamePrefix :: forall a. Typeable a => Proxy a -> String -> String Source #
Strips name of the type name from field name prefix.
>>>data UserData = UserData { userDataId :: Int, userDataShortInfo :: Text }>>>stripTypeNamePrefix (Proxy @UserData) "userDataId""id">>>stripTypeNamePrefix (Proxy @UserData) "userDataShortInfo""shortInfo">>>stripTypeNamePrefix (Proxy @UserData) "udStats""stats">>>stripTypeNamePrefix (Proxy @UserData) "fooBar""bar">>>stripTypeNamePrefix (Proxy @UserData) "name""name"
Core generic typeclass
class HasCodec a where Source #
Helper typeclass for generic deriving. This instance tells how the data type should be coded if it's a field of another data type.
NOTE: If you implement TOML codecs for your data types manually, prefer more
explicit Toml.int or Toml.text instead of implicit Toml.hasCodec.
Implement instances of this typeclass only when using genericCodec and when
your custom data types are not covered here.
Instances
| HasCodec Bool Source # | |
| HasCodec Double Source # | |
| HasCodec Float Source # | |
| HasCodec Int Source # | |
| HasCodec Integer Source # | |
| HasCodec Natural Source # | |
| HasCodec Word Source # | |
| HasCodec Word8 Source # | Since: 1.2.0.0 |
| HasCodec IntSet Source # | |
| HasCodec Text Source # | |
| HasCodec Text Source # | |
| HasCodec ZonedTime Source # | |
| HasCodec LocalTime Source # | |
| HasCodec TimeOfDay Source # | |
| HasCodec Day Source # | |
| HasItemCodec a => HasCodec [a] Source # | |
| HasCodec a => HasCodec (Maybe a) Source # | |
| HasItemCodec a => HasCodec (NonEmpty a) Source # | |
| (Ord a, HasItemCodec a) => HasCodec (Set a) Source # | Since: 1.2.0.0 |
| (Hashable a, Eq a, HasItemCodec a) => HasCodec (HashSet a) Source # | Since: 1.2.0.0 |
class HasItemCodec a where Source #
This typeclass tells how the data type should be coded as an item of a list. Lists in TOML can have two types: primitive and table of arrays.
- If
hasItemCodecreturnsLeft: primitive arrays codec is used. - If
hasItemCodecreturns 'Right:' table of arrays codec is used.
Instances
| HasItemCodec Bool Source # | |
Defined in Toml.Generic | |
| HasItemCodec Double Source # | |
Defined in Toml.Generic | |
| HasItemCodec Float Source # | |
Defined in Toml.Generic | |
| HasItemCodec Int Source # | |
Defined in Toml.Generic | |
| HasItemCodec Integer Source # | |
Defined in Toml.Generic | |
| HasItemCodec Natural Source # | |
Defined in Toml.Generic | |
| HasItemCodec Word Source # | |
Defined in Toml.Generic | |
| HasItemCodec Word8 Source # | Since: 1.2.0.0 |
Defined in Toml.Generic | |
| HasItemCodec IntSet Source # | |
Defined in Toml.Generic | |
| HasItemCodec Text Source # | |
Defined in Toml.Generic | |
| HasItemCodec Text Source # | |
Defined in Toml.Generic | |
| HasItemCodec ZonedTime Source # | |
Defined in Toml.Generic | |
| HasItemCodec LocalTime Source # | |
Defined in Toml.Generic | |
| HasItemCodec TimeOfDay Source # | |
Defined in Toml.Generic | |
| HasItemCodec Day Source # | |
Defined in Toml.Generic | |
| (HasItemCodec a, Typeable a) => HasItemCodec [a] Source # | If data type |
Defined in Toml.Generic | |
class GenericCodec (f :: k -> Type) where Source #
Helper class to derive TOML codecs generically.
Methods
genericTomlCodec :: GenericOptions -> TomlCodec (f p) Source #
Instances
| (GenericCodec f, GenericCodec g) => GenericCodec (f :*: g :: k -> Type) Source # | |
Defined in Toml.Generic Methods genericTomlCodec :: forall (p :: k0). GenericOptions -> TomlCodec ((f :*: g) p) Source # | |
| GenericCodec f => GenericCodec (C1 c f :: k -> Type) Source # | |
Defined in Toml.Generic Methods genericTomlCodec :: forall (p :: k0). GenericOptions -> TomlCodec (C1 c f p) Source # | |
| GenericCodec f => GenericCodec (D1 d f :: k -> Type) Source # | |
Defined in Toml.Generic Methods genericTomlCodec :: forall (p :: k0). GenericOptions -> TomlCodec (D1 d f p) Source # | |
| (TypeError GenericSumTomlNotSupported :: Constraint) => GenericCodec (f :+: g :: k -> Type) Source # | |
Defined in Toml.Generic Methods genericTomlCodec :: forall (p :: k0). GenericOptions -> TomlCodec ((f :+: g) p) Source # | |
| (Selector s, HasCodec a) => GenericCodec (S1 s (Rec0 a) :: k -> Type) Source # | |
Defined in Toml.Generic Methods genericTomlCodec :: forall (p :: k0). GenericOptions -> TomlCodec (S1 s (Rec0 a) p) Source # | |