Copyright | (c) 2018-2022 Kowainik |
---|---|
License | MPL-2.0 |
Maintainer | Kowainik <xrom.xkov@gmail.com> |
Stability | Stable |
Portability | Portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
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
instanceHasCodec
Address where hasCodec = Toml.tablegenericCodec
instanceHasItemCodec
Social 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
HasCodec
typeclass. - 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
- 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)
- newtype ByteStringAsText = ByteStringAsText {}
- newtype ByteStringAsBytes = ByteStringAsBytes {}
- newtype LByteStringAsText = LByteStringAsText {}
- newtype LByteStringAsBytes = LByteStringAsBytes {}
- newtype TomlTable a = TomlTable {
- unTomlTable :: a
- newtype TomlTableStrip a = TomlTableStrip {
- unTomlTableStrip :: a
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:
tomlOptionsFieldModifier
: how to translate field names to TOML keys?
Since: 1.1.0.0
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
stripTypeNameOptions :: Typeable a => TomlOptions a Source #
Options that use stripTypeNamePrefix
as tomlOptionsFieldModifier
.
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
Instances
HasCodec All Source # | Since: 1.3.0.0 |
HasCodec Any Source # | Since: 1.3.0.0 |
HasCodec Word8 Source # | Since: 1.2.0.0 |
HasCodec IntSet Source # | Since: 1.1.0.0 |
HasCodec Text Source # | Since: 1.1.0.0 |
HasCodec Text Source # | Since: 1.1.0.0 |
HasCodec Day Source # | Since: 1.1.0.0 |
HasCodec LocalTime Source # | Since: 1.1.0.0 |
HasCodec TimeOfDay Source # | Since: 1.1.0.0 |
HasCodec ZonedTime Source # | Since: 1.1.0.0 |
HasCodec ByteStringAsBytes Source # | Since: 1.3.0.0 |
Defined in Toml.Codec.Generic | |
HasCodec ByteStringAsText Source # | Since: 1.3.0.0 |
Defined in Toml.Codec.Generic | |
HasCodec LByteStringAsBytes Source # | Since: 1.3.0.0 |
Defined in Toml.Codec.Generic | |
HasCodec LByteStringAsText Source # | Since: 1.3.0.0 |
Defined in Toml.Codec.Generic | |
HasCodec Integer Source # | Since: 1.1.0.0 |
HasCodec Natural Source # | Since: 1.1.0.0 |
HasCodec Bool Source # | Since: 1.1.0.0 |
HasCodec Double Source # | Since: 1.1.0.0 |
HasCodec Float Source # | Since: 1.1.0.0 |
HasCodec Int Source # | Since: 1.1.0.0 |
HasCodec Word Source # | Since: 1.1.0.0 |
HasCodec a => HasCodec (First a) Source # | Since: 1.3.0.0 |
HasCodec a => HasCodec (Last a) Source # | Since: 1.3.0.0 |
(Num a, HasCodec a) => HasCodec (Product a) Source # | Since: 1.3.0.0 |
(Num a, HasCodec a) => HasCodec (Sum a) Source # | Since: 1.3.0.0 |
HasItemCodec a => HasCodec (NonEmpty a) Source # | Since: 1.1.0.0 |
HasCodec v => HasCodec (IntMap v) Source # | Encodes fieldName = [ { key = 10, val = "foo" } , { key = 42, val = "bar" } ] Since: 1.3.0.0 |
(Ord a, HasItemCodec a) => HasCodec (Set a) Source # | Since: 1.2.0.0 |
(Generic a, GenericCodec (Rep a)) => HasCodec (TomlTable a) Source # | Since: 1.3.0.0 |
(Generic a, GenericCodec (Rep a), Typeable a) => HasCodec (TomlTableStrip a) Source # | Since: 1.3.2.0 |
Defined in Toml.Codec.Generic | |
(Hashable a, HasItemCodec a) => HasCodec (HashSet a) Source # | Since: 1.2.0.0 |
HasCodec a => HasCodec (Maybe a) Source # | Since: 1.1.0.0 |
HasItemCodec a => HasCodec [a] Source # | Since: 1.1.0.0 |
(Ord k, HasCodec k, HasCodec v) => HasCodec (Map k v) Source # | Encodes fieldName = [ { key = 10, val = "book" } , { key = 42, val = "food" } ] Since: 1.3.0.0 |
(Hashable k, HasCodec k, HasCodec v) => HasCodec (HashMap k v) Source # | Encodes fieldName = [ { key = "foo", val = 15 } , { key = "bar", val = 7 } ] Since: 1.3.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
hasItemCodec
returnsLeft
: primitive arrays codec is used. - If
hasItemCodec
returns 'Right:' table of arrays codec is used.
Since: 1.1.0.0
Instances
class GenericCodec (f :: k -> Type) where Source #
Helper class to derive TOML codecs generically.
Since: 1.1.0.0
genericTomlCodec :: GenericOptions -> TomlCodec (f p) Source #
Instances
ByteString
newtypes
There are two ways to encode ByteString
in TOML:
- Via text.
- 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
} derivingHasCodec
viaByteStringAsBytes
newtype ByteStringAsText Source #
Newtype wrapper over ByteString
to be used for text values.
Since: 1.3.0.0
Instances
Show ByteStringAsText Source # | |
Defined in Toml.Codec.Generic showsPrec :: Int -> ByteStringAsText -> ShowS # show :: ByteStringAsText -> String # showList :: [ByteStringAsText] -> ShowS # | |
Eq ByteStringAsText Source # | |
Defined in Toml.Codec.Generic (==) :: ByteStringAsText -> ByteStringAsText -> Bool # (/=) :: ByteStringAsText -> ByteStringAsText -> Bool # | |
HasCodec ByteStringAsText Source # | Since: 1.3.0.0 |
Defined in Toml.Codec.Generic | |
HasItemCodec ByteStringAsText Source # | Since: 1.3.0.0 |
Defined in Toml.Codec.Generic |
newtype ByteStringAsBytes Source #
Newtype wrapper over ByteString
to be used for array of integers
representation.
Since: 1.3.0.0
Instances
Show ByteStringAsBytes Source # | |
Defined in Toml.Codec.Generic showsPrec :: Int -> ByteStringAsBytes -> ShowS # show :: ByteStringAsBytes -> String # showList :: [ByteStringAsBytes] -> ShowS # | |
Eq ByteStringAsBytes Source # | |
Defined in Toml.Codec.Generic (==) :: ByteStringAsBytes -> ByteStringAsBytes -> Bool # (/=) :: ByteStringAsBytes -> ByteStringAsBytes -> Bool # | |
HasCodec ByteStringAsBytes Source # | Since: 1.3.0.0 |
Defined in Toml.Codec.Generic | |
HasItemCodec ByteStringAsBytes Source # | Since: 1.3.0.0 |
Defined in Toml.Codec.Generic |
newtype LByteStringAsText Source #
Newtype wrapper over lazy ByteString
to be used for text values.
Since: 1.3.0.0
Instances
Show LByteStringAsText Source # | |
Defined in Toml.Codec.Generic showsPrec :: Int -> LByteStringAsText -> ShowS # show :: LByteStringAsText -> String # showList :: [LByteStringAsText] -> ShowS # | |
Eq LByteStringAsText Source # | |
Defined in Toml.Codec.Generic (==) :: LByteStringAsText -> LByteStringAsText -> Bool # (/=) :: LByteStringAsText -> LByteStringAsText -> Bool # | |
HasCodec LByteStringAsText Source # | Since: 1.3.0.0 |
Defined in Toml.Codec.Generic | |
HasItemCodec LByteStringAsText Source # | Since: 1.3.0.0 |
Defined in Toml.Codec.Generic |
newtype LByteStringAsBytes Source #
Newtype wrapper over lazy ByteString
to be used for array of integers
representation.
Since: 1.3.0.0
Instances
Show LByteStringAsBytes Source # | |
Defined in Toml.Codec.Generic showsPrec :: Int -> LByteStringAsBytes -> ShowS # show :: LByteStringAsBytes -> String # showList :: [LByteStringAsBytes] -> ShowS # | |
Eq LByteStringAsBytes Source # | |
Defined in Toml.Codec.Generic (==) :: LByteStringAsBytes -> LByteStringAsBytes -> Bool # (/=) :: LByteStringAsBytes -> LByteStringAsBytes -> Bool # | |
HasCodec LByteStringAsBytes Source # | Since: 1.3.0.0 |
Defined in Toml.Codec.Generic | |
HasItemCodec LByteStringAsBytes Source # | Since: 1.3.0.0 |
Defined in Toml.Codec.Generic |
Deriving Via
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
) derivingHasCodec
viaTomlTable
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
TomlTable | |
|
Instances
(Generic a, GenericCodec (Rep a)) => HasCodec (TomlTable a) Source # | Since: 1.3.0.0 |
(Generic a, GenericCodec (Rep a)) => HasItemCodec (TomlTable a) Source # | Since: 1.3.0.0 |
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
Instances
(Generic a, GenericCodec (Rep a), Typeable a) => HasCodec (TomlTableStrip a) Source # | Since: 1.3.2.0 |
Defined in Toml.Codec.Generic | |
(Generic a, GenericCodec (Rep a), Typeable a) => HasItemCodec (TomlTableStrip a) Source # | Since: 1.3.2.0 |
Defined in Toml.Codec.Generic hasItemCodec :: Either (TomlBiMap (TomlTableStrip a) AnyValue) (TomlCodec (TomlTableStrip a)) Source # |