module Toml.Codec.Combinator.Primitive
(
bool
, integer
, int
, natural
, word
, word8
, double
, float
, string
, text
, lazyText
, byteString
, lazyByteString
, byteStringArray
, lazyByteStringArray
) where
import Data.ByteString (ByteString)
import Data.Text (Text)
import Data.Word (Word8)
import Numeric.Natural (Natural)
import Toml.Codec.BiMap.Conversion (_Bool, _ByteString, _ByteStringArray, _Double, _Float, _Int,
_Integer, _LByteString, _LByteStringArray, _LText, _Natural,
_String, _Text, _Word, _Word8)
import Toml.Codec.Combinator.Common (match)
import Toml.Codec.Types (TomlCodec)
import Toml.Type.Key (Key)
import qualified Data.ByteString.Lazy as BL
import qualified Data.Text.Lazy as L
bool :: Key -> TomlCodec Bool
bool :: Key -> TomlCodec Bool
bool = TomlBiMap Bool AnyValue -> Key -> TomlCodec Bool
forall a. TomlBiMap a AnyValue -> Key -> TomlCodec a
match TomlBiMap Bool AnyValue
_Bool
{-# INLINE bool #-}
integer :: Key -> TomlCodec Integer
integer :: Key -> TomlCodec Integer
integer = TomlBiMap Integer AnyValue -> Key -> TomlCodec Integer
forall a. TomlBiMap a AnyValue -> Key -> TomlCodec a
match TomlBiMap Integer AnyValue
_Integer
{-# INLINE integer #-}
int :: Key -> TomlCodec Int
int :: Key -> TomlCodec Int
int = TomlBiMap Int AnyValue -> Key -> TomlCodec Int
forall a. TomlBiMap a AnyValue -> Key -> TomlCodec a
match TomlBiMap Int AnyValue
_Int
{-# INLINE int #-}
natural :: Key -> TomlCodec Natural
natural :: Key -> TomlCodec Natural
natural = TomlBiMap Natural AnyValue -> Key -> TomlCodec Natural
forall a. TomlBiMap a AnyValue -> Key -> TomlCodec a
match TomlBiMap Natural AnyValue
_Natural
{-# INLINE natural #-}
word :: Key -> TomlCodec Word
word :: Key -> TomlCodec Word
word = TomlBiMap Word AnyValue -> Key -> TomlCodec Word
forall a. TomlBiMap a AnyValue -> Key -> TomlCodec a
match TomlBiMap Word AnyValue
_Word
{-# INLINE word #-}
word8 :: Key -> TomlCodec Word8
word8 :: Key -> TomlCodec Word8
word8 = TomlBiMap Word8 AnyValue -> Key -> TomlCodec Word8
forall a. TomlBiMap a AnyValue -> Key -> TomlCodec a
match TomlBiMap Word8 AnyValue
_Word8
{-# INLINE word8 #-}
double :: Key -> TomlCodec Double
double :: Key -> TomlCodec Double
double = TomlBiMap Double AnyValue -> Key -> TomlCodec Double
forall a. TomlBiMap a AnyValue -> Key -> TomlCodec a
match TomlBiMap Double AnyValue
_Double
{-# INLINE double #-}
float :: Key -> TomlCodec Float
float :: Key -> TomlCodec Float
float = TomlBiMap Float AnyValue -> Key -> TomlCodec Float
forall a. TomlBiMap a AnyValue -> Key -> TomlCodec a
match TomlBiMap Float AnyValue
_Float
{-# INLINE float #-}
string :: Key -> TomlCodec String
string :: Key -> TomlCodec String
string = TomlBiMap String AnyValue -> Key -> TomlCodec String
forall a. TomlBiMap a AnyValue -> Key -> TomlCodec a
match TomlBiMap String AnyValue
_String
{-# INLINE string #-}
text :: Key -> TomlCodec Text
text :: Key -> TomlCodec Text
text = TomlBiMap Text AnyValue -> Key -> TomlCodec Text
forall a. TomlBiMap a AnyValue -> Key -> TomlCodec a
match TomlBiMap Text AnyValue
_Text
{-# INLINE text #-}
lazyText :: Key -> TomlCodec L.Text
lazyText :: Key -> TomlCodec Text
lazyText = TomlBiMap Text AnyValue -> Key -> TomlCodec Text
forall a. TomlBiMap a AnyValue -> Key -> TomlCodec a
match TomlBiMap Text AnyValue
_LText
{-# INLINE lazyText #-}
byteString :: Key -> TomlCodec ByteString
byteString :: Key -> TomlCodec ByteString
byteString = TomlBiMap ByteString AnyValue -> Key -> TomlCodec ByteString
forall a. TomlBiMap a AnyValue -> Key -> TomlCodec a
match TomlBiMap ByteString AnyValue
_ByteString
{-# INLINE byteString #-}
lazyByteString :: Key -> TomlCodec BL.ByteString
lazyByteString :: Key -> TomlCodec ByteString
lazyByteString = TomlBiMap ByteString AnyValue -> Key -> TomlCodec ByteString
forall a. TomlBiMap a AnyValue -> Key -> TomlCodec a
match TomlBiMap ByteString AnyValue
_LByteString
{-# INLINE lazyByteString #-}
byteStringArray :: Key -> TomlCodec ByteString
byteStringArray :: Key -> TomlCodec ByteString
byteStringArray = TomlBiMap ByteString AnyValue -> Key -> TomlCodec ByteString
forall a. TomlBiMap a AnyValue -> Key -> TomlCodec a
match TomlBiMap ByteString AnyValue
_ByteStringArray
{-# INLINE byteStringArray #-}
lazyByteStringArray :: Key -> TomlCodec BL.ByteString
lazyByteStringArray :: Key -> TomlCodec ByteString
lazyByteStringArray = TomlBiMap ByteString AnyValue -> Key -> TomlCodec ByteString
forall a. TomlBiMap a AnyValue -> Key -> TomlCodec a
match TomlBiMap ByteString AnyValue
_LByteStringArray
{-# INLINE lazyByteStringArray #-}