tomland-1.3.3.0: Bidirectional TOML serialization
Copyright(c) 2018-2021 Kowainik
LicenseMPL-2.0
MaintainerKowainik <xrom.xkov@gmail.com>
StabilityStable
PortabilityPortable
Safe HaskellNone
LanguageHaskell2010

Toml.Codec.Generic

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 :: TomlCodec User
userCodec = User
    <$> Toml.int "age" .= age
    <*> Toml.table addressCodec "address" .= address
    <*> Toml.list  socialCodec  "socials" .= socials

addressCodec :: TomlCodec Address
addressCodec = Address
    <$> Toml.text "street" .= street
    <*> Toml.int  "house"  .= house

socialCodec :: TomlCodec Social
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 :: TomlCodec User
userCodec = genericCodec

instance HasCodec Address where
    hasCodec = Toml.table genericCodec

instance HasItemCodec Social where
    hasItemCodec = Right genericCodec

Several notes about the interface:

  1. Your top-level data types are always implemented as genericCodec (or other generic codecs).
  2. If you have a custom data type as a field of another type, you need to implement the instance of the HasCodec typeclass.
  3. If the data type appears as an element of a list, you need to implement the instance of the HasItemCodec typeclass.

Since: 1.1.0.0

Synopsis

Documentation

genericCodec :: (Generic a, GenericCodec (Rep a)) => TomlCodec a Source #

Generic codec for arbitrary data types. Uses field names as keys.

Since: 1.1.0.0

genericCodecWithOptions :: forall a. (Generic a, GenericCodec (Rep a), Typeable a) => TomlOptions a -> TomlCodec a Source #

Generic codec with options for arbitrary data types.

Since: 1.1.0.0

stripTypeNameCodec :: forall a. (Generic a, GenericCodec (Rep a), Typeable a) => TomlCodec a Source #

Generic codec that uses stripTypeNameOptions.

Since: 1.1.0.0

Options

data TomlOptions a Source #

Options to configure various parameters of generic encoding. Specifically:

Since: 1.1.0.0

Constructors

TomlOptions 

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.

Since: 1.1.0.0

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"

Since: 1.1.0.0

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.

Since: 1.1.0.0

Methods

hasCodec :: Key -> TomlCodec a Source #

Instances

Instances details
HasCodec Bool Source #

Since: 1.1.0.0

Instance details

Defined in Toml.Codec.Generic

HasCodec Double Source #

Since: 1.1.0.0

Instance details

Defined in Toml.Codec.Generic

HasCodec Float Source #

Since: 1.1.0.0

Instance details

Defined in Toml.Codec.Generic

HasCodec Int Source #

Since: 1.1.0.0

Instance details

Defined in Toml.Codec.Generic

HasCodec Integer Source #

Since: 1.1.0.0

Instance details

Defined in Toml.Codec.Generic

HasCodec Natural Source #

Since: 1.1.0.0

Instance details

Defined in Toml.Codec.Generic

HasCodec Word Source #

Since: 1.1.0.0

Instance details

Defined in Toml.Codec.Generic

HasCodec Word8 Source #

Since: 1.2.0.0

Instance details

Defined in Toml.Codec.Generic

HasCodec All Source #

Since: 1.3.0.0

Instance details

Defined in Toml.Codec.Generic

HasCodec Any Source #

Since: 1.3.0.0

Instance details

Defined in Toml.Codec.Generic

HasCodec IntSet Source #

Since: 1.1.0.0

Instance details

Defined in Toml.Codec.Generic

HasCodec Text Source #

Since: 1.1.0.0

Instance details

Defined in Toml.Codec.Generic

HasCodec Text Source #

Since: 1.1.0.0

Instance details

Defined in Toml.Codec.Generic

HasCodec ZonedTime Source #

Since: 1.1.0.0

Instance details

Defined in Toml.Codec.Generic

HasCodec LocalTime Source #

Since: 1.1.0.0

Instance details

Defined in Toml.Codec.Generic

HasCodec TimeOfDay Source #

Since: 1.1.0.0

Instance details

Defined in Toml.Codec.Generic

HasCodec Day Source #

Since: 1.1.0.0

Instance details

Defined in Toml.Codec.Generic

HasCodec LByteStringAsBytes Source #

Since: 1.3.0.0

Instance details

Defined in Toml.Codec.Generic

HasCodec LByteStringAsText Source #

Since: 1.3.0.0

Instance details

Defined in Toml.Codec.Generic

HasCodec ByteStringAsBytes Source #

Since: 1.3.0.0

Instance details

Defined in Toml.Codec.Generic

HasCodec ByteStringAsText Source #

Since: 1.3.0.0

Instance details

Defined in Toml.Codec.Generic

HasItemCodec a => HasCodec [a] Source #

Since: 1.1.0.0

Instance details

Defined in Toml.Codec.Generic

Methods

hasCodec :: Key -> TomlCodec [a] Source #

HasCodec a => HasCodec (Maybe a) Source #

Since: 1.1.0.0

Instance details

Defined in Toml.Codec.Generic

Methods

hasCodec :: Key -> TomlCodec (Maybe a) Source #

HasCodec a => HasCodec (First a) Source #

Since: 1.3.0.0

Instance details

Defined in Toml.Codec.Generic

Methods

hasCodec :: Key -> TomlCodec (First a) Source #

HasCodec a => HasCodec (Last a) Source #

Since: 1.3.0.0

Instance details

Defined in Toml.Codec.Generic

Methods

hasCodec :: Key -> TomlCodec (Last a) Source #

(Num a, HasCodec a) => HasCodec (Sum a) Source #

Since: 1.3.0.0

Instance details

Defined in Toml.Codec.Generic

Methods

hasCodec :: Key -> TomlCodec (Sum a) Source #

(Num a, HasCodec a) => HasCodec (Product a) Source #

Since: 1.3.0.0

Instance details

Defined in Toml.Codec.Generic

HasItemCodec a => HasCodec (NonEmpty a) Source #

Since: 1.1.0.0

Instance details

Defined in Toml.Codec.Generic

HasCodec v => HasCodec (IntMap v) Source #

Encodes IntMap as array of tables with the key and val TOML key names for IntMap keys and values. E.g. if you have a type IntMap Text, the HasCodec instance for Generic deriving will work with the following TOML representation:

fieldName =
    [ { key = 10, val = "foo" }
    , { key = 42, val = "bar" }
    ]

Since: 1.3.0.0

Instance details

Defined in Toml.Codec.Generic

Methods

hasCodec :: Key -> TomlCodec (IntMap v) Source #

(Ord a, HasItemCodec a) => HasCodec (Set a) Source #

Since: 1.2.0.0

Instance details

Defined in Toml.Codec.Generic

Methods

hasCodec :: Key -> TomlCodec (Set a) Source #

(Hashable a, Eq a, HasItemCodec a) => HasCodec (HashSet a) Source #

Since: 1.2.0.0

Instance details

Defined in Toml.Codec.Generic

(Generic a, GenericCodec (Rep a), Typeable a) => HasCodec (TomlTableStrip a) Source #

Since: 1.3.2.0

Instance details

Defined in Toml.Codec.Generic

(Generic a, GenericCodec (Rep a)) => HasCodec (TomlTable a) Source #

Since: 1.3.0.0

Instance details

Defined in Toml.Codec.Generic

(Ord k, HasCodec k, HasCodec v) => HasCodec (Map k v) Source #

Encodes Map as array of tables with the key and val TOML key names for Map keys and values. E.g. if you have a type Map Int Text, the HasCodec instance for Generic deriving will work with the following TOML representation:

fieldName =
    [ { key = 10, val = "book" }
    , { key = 42, val = "food" }
    ]

Since: 1.3.0.0

Instance details

Defined in Toml.Codec.Generic

Methods

hasCodec :: Key -> TomlCodec (Map k v) Source #

(Hashable k, Eq k, HasCodec k, HasCodec v) => HasCodec (HashMap k v) Source #

Encodes HashMap as array of tables with the key and val TOML key names for HashMap keys and values. E.g. if you have a type HashMap Text Int, the HasCodec instance for Generic deriving will work with the following TOML representation:

fieldName =
    [ { key = "foo", val = 15 }
    , { key = "bar", val = 7  }
    ]

Since: 1.3.0.0

Instance details

Defined in Toml.Codec.Generic

Methods

hasCodec :: Key -> TomlCodec (HashMap k v) Source #

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.

Since: 1.1.0.0

Instances

Instances details
HasItemCodec Bool Source #

Since: 1.1.0.0

Instance details

Defined in Toml.Codec.Generic

HasItemCodec Double Source #

Since: 1.1.0.0

Instance details

Defined in Toml.Codec.Generic

HasItemCodec Float Source #

Since: 1.1.0.0

Instance details

Defined in Toml.Codec.Generic

HasItemCodec Int Source #

Since: 1.1.0.0

Instance details

Defined in Toml.Codec.Generic

HasItemCodec Integer Source #

Since: 1.1.0.0

Instance details

Defined in Toml.Codec.Generic

HasItemCodec Natural Source #

Since: 1.1.0.0

Instance details

Defined in Toml.Codec.Generic

HasItemCodec Word Source #

Since: 1.1.0.0

Instance details

Defined in Toml.Codec.Generic

HasItemCodec Word8 Source #

Since: 1.2.0.0

Instance details

Defined in Toml.Codec.Generic

HasItemCodec IntSet Source #

Since: 1.1.0.0

Instance details

Defined in Toml.Codec.Generic

HasItemCodec Text Source #

Since: 1.1.0.0

Instance details

Defined in Toml.Codec.Generic

HasItemCodec Text Source #

Since: 1.1.0.0

Instance details

Defined in Toml.Codec.Generic

HasItemCodec ZonedTime Source #

Since: 1.1.0.0

Instance details

Defined in Toml.Codec.Generic

HasItemCodec LocalTime Source #

Since: 1.1.0.0

Instance details

Defined in Toml.Codec.Generic

HasItemCodec TimeOfDay Source #

Since: 1.1.0.0

Instance details

Defined in Toml.Codec.Generic

HasItemCodec Day Source #

Since: 1.1.0.0

Instance details

Defined in Toml.Codec.Generic

HasItemCodec LByteStringAsBytes Source #

Since: 1.3.0.0

Instance details

Defined in Toml.Codec.Generic

HasItemCodec LByteStringAsText Source #

Since: 1.3.0.0

Instance details

Defined in Toml.Codec.Generic

HasItemCodec ByteStringAsBytes Source #

Since: 1.3.0.0

Instance details

Defined in Toml.Codec.Generic

HasItemCodec ByteStringAsText Source #

Since: 1.3.0.0

Instance details

Defined in Toml.Codec.Generic

(HasItemCodec a, Typeable a) => HasItemCodec [a] Source #

If data type a is not primitive then this instance returns codec for list under key equal to a type name.

Since: 1.1.0.0

Instance details

Defined in Toml.Codec.Generic

(Generic a, GenericCodec (Rep a), Typeable a) => HasItemCodec (TomlTableStrip a) Source #

Since: 1.3.2.0

Instance details

Defined in Toml.Codec.Generic

(Generic a, GenericCodec (Rep a)) => HasItemCodec (TomlTable a) Source #

Since: 1.3.0.0

Instance details

Defined in Toml.Codec.Generic

class GenericCodec (f :: k -> Type) where Source #

Helper class to derive TOML codecs generically.

Since: 1.1.0.0

Instances

Instances details
(GenericCodec f, GenericCodec g) => GenericCodec (f :*: g :: k -> Type) Source #

Since: 1.1.0.0

Instance details

Defined in Toml.Codec.Generic

Methods

genericTomlCodec :: forall (p :: k0). GenericOptions -> TomlCodec ((f :*: g) p) Source #

GenericCodec f => GenericCodec (C1 c f :: k -> Type) Source #

Since: 1.1.0.0

Instance details

Defined in Toml.Codec.Generic

Methods

genericTomlCodec :: forall (p :: k0). GenericOptions -> TomlCodec (C1 c f p) Source #

GenericCodec f => GenericCodec (D1 d f :: k -> Type) Source #

Since: 1.1.0.0

Instance details

Defined in Toml.Codec.Generic

Methods

genericTomlCodec :: forall (p :: k0). GenericOptions -> TomlCodec (D1 d f p) Source #

(TypeError GenericSumTomlNotSupported :: Constraint) => GenericCodec (f :+: g :: k -> Type) Source #

Since: 1.1.0.0

Instance details

Defined in Toml.Codec.Generic

Methods

genericTomlCodec :: forall (p :: k0). GenericOptions -> TomlCodec ((f :+: g) p) Source #

(Selector s, HasCodec a) => GenericCodec (S1 s (Rec0 a) :: k -> Type) Source #

Since: 1.1.0.0

Instance details

Defined in Toml.Codec.Generic

Methods

genericTomlCodec :: forall (p :: k0). GenericOptions -> TomlCodec (S1 s (Rec0 a) p) Source #

ByteString newtypes

There are two ways to encode ByteString in TOML:

  1. Via text.
  2. Via an array of integers (aka array of bytes).

To handle all these cases, tomland provides helpful newtypes, specifically:

As a bonus, on GHC >= 8.6 you can use these newtypes with the DerivingVia extensions for your own ByteString types.

newtype MyByteString = MyByteString
    { unMyByteString :: ByteString
    } deriving HasCodec via ByteStringAsBytes

newtype ByteStringAsText Source #

Newtype wrapper over ByteString to be used for text values.

Since: 1.3.0.0

newtype ByteStringAsBytes Source #

Newtype wrapper over ByteString to be used for array of integers representation.

Since: 1.3.0.0

newtype LByteStringAsText Source #

Newtype wrapper over lazy ByteString to be used for text values.

Since: 1.3.0.0

newtype LByteStringAsBytes Source #

Newtype wrapper over lazy ByteString to be used for array of integers representation.

Since: 1.3.0.0

Deriving Via

newtype TomlTable a Source #

newtype for generic deriving of HasCodec typeclass for custom data types that should we wrapped into separate table. Use it only for data types that are fields of another data types.

data Person = Person
    { personName    :: !Text
    , personAddress :: !Address
    } deriving (Generic)

data Address = Address
    { addressStreet :: !Text
    , addressHouse  :: !Int
    } deriving (Generic)
      deriving HasCodec via TomlTable Address

personCodec :: TomlCodec Person
personCodec = stripTypeNameCodec

personCodec corresponds to the TOML of the following structure:

name = "foo"
[address]
    addressStreet = "Bar"
    addressHouse = 42

Since: 1.3.0.0

Constructors

TomlTable 

Fields

Instances

Instances details
(Generic a, GenericCodec (Rep a)) => HasCodec (TomlTable a) Source #

Since: 1.3.0.0

Instance details

Defined in Toml.Codec.Generic

(Generic a, GenericCodec (Rep a)) => HasItemCodec (TomlTable a) Source #

Since: 1.3.0.0

Instance details

Defined in Toml.Codec.Generic

newtype TomlTableStrip a Source #

newtype for generic deriving of HasCodec typeclass for custom data types that should be wrapped into a separate table.

Similar to TomlTable but also strips the data type name prefix from TOML keys.

personCodec from the TomlTable comment corresponds to the TOML of the following structure:

name = "foo"
[address]
    street = "Bar"
    house = 42

Since: 1.3.2.0

Constructors

TomlTableStrip 

Fields

Instances

Instances details
(Generic a, GenericCodec (Rep a), Typeable a) => HasCodec (TomlTableStrip a) Source #

Since: 1.3.2.0

Instance details

Defined in Toml.Codec.Generic

(Generic a, GenericCodec (Rep a), Typeable a) => HasItemCodec (TomlTableStrip a) Source #

Since: 1.3.2.0

Instance details

Defined in Toml.Codec.Generic