{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeSynonymInstances #-}
module TOML.Decode (
decode,
decodeWith,
decodeWithOpts,
decodeFile,
DecodeTOML (..),
Decoder (..),
getField,
getFieldOr,
getFields,
getFieldOpt,
getFieldsOpt,
getFieldWith,
getFieldsWith,
getFieldOptWith,
getFieldsOptWith,
getArrayOf,
DecodeM (..),
makeDecoder,
runDecoder,
addContextItem,
invalidValue,
typeMismatch,
decodeFail,
decodeError,
) where
import Control.Applicative (Alternative (..), Const (..))
import Control.Monad (zipWithM)
#if MIN_VERSION_base(4,9,0) && !MIN_VERSION_base(4,13,0)
import qualified Control.Monad.Fail as MonadFail
#endif
import Data.Bifunctor (first)
import Data.Fixed (Fixed, HasResolution)
import Data.Functor.Identity (Identity (..))
import Data.Int (Int16, Int32, Int64, Int8)
import Data.IntMap (IntMap)
import qualified Data.IntMap as IntMap
import Data.IntSet (IntSet)
import qualified Data.IntSet as IntSet
import Data.List.NonEmpty (NonEmpty)
import qualified Data.List.NonEmpty as NonEmpty
import Data.Map (Map)
import qualified Data.Map.Strict as Map
import Data.Maybe (fromMaybe)
import qualified Data.Monoid as Monoid
import Data.Proxy (Proxy (..))
import Data.Ratio (Ratio)
import qualified Data.Semigroup as Semigroup
import Data.Sequence (Seq)
import qualified Data.Sequence as Seq
import Data.Set (Set)
import qualified Data.Set as Set
import Data.String (IsString, fromString)
import Data.Text (Text)
import qualified Data.Text as Text
import qualified Data.Text.IO as Text
import qualified Data.Text.Lazy as Lazy (Text)
import qualified Data.Text.Lazy as Text.Lazy
import qualified Data.Time as Time
import qualified Data.Time.Clock.System as Time
import Data.Version (Version, parseVersion)
import Data.Void (Void)
import Data.Word (Word16, Word32, Word64, Word8)
import Numeric.Natural (Natural)
import Text.ParserCombinators.ReadP (readP_to_S)
import TOML.Error (
ContextItem (..),
DecodeContext,
DecodeError (..),
TOMLError (..),
)
import TOML.Parser (parseTOML)
import TOML.Value (Value (..))
newtype Decoder a = Decoder {forall a. Decoder a -> Value -> DecodeM a
unDecoder :: Value -> DecodeM a}
instance Functor Decoder where
fmap :: forall a b. (a -> b) -> Decoder a -> Decoder b
fmap a -> b
f = forall a. (Value -> DecodeM a) -> Decoder a
Decoder forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap) a -> b
f forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Decoder a -> Value -> DecodeM a
unDecoder
instance Applicative Decoder where
pure :: forall a. a -> Decoder a
pure a
v = forall a. (Value -> DecodeM a) -> Decoder a
Decoder forall a b. (a -> b) -> a -> b
$ \Value
_ -> forall (f :: * -> *) a. Applicative f => a -> f a
pure a
v
Decoder Value -> DecodeM (a -> b)
decodeF <*> :: forall a b. Decoder (a -> b) -> Decoder a -> Decoder b
<*> Decoder Value -> DecodeM a
decodeV = forall a. (Value -> DecodeM a) -> Decoder a
Decoder forall a b. (a -> b) -> a -> b
$ \Value
v -> Value -> DecodeM (a -> b)
decodeF Value
v forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Value -> DecodeM a
decodeV Value
v
instance Monad Decoder where
Decoder Value -> DecodeM a
decodeA >>= :: forall a b. Decoder a -> (a -> Decoder b) -> Decoder b
>>= a -> Decoder b
f = forall a. (Value -> DecodeM a) -> Decoder a
Decoder forall a b. (a -> b) -> a -> b
$ \Value
v -> do
a
a <- Value -> DecodeM a
decodeA Value
v
let Decoder Value -> DecodeM b
decodeB = a -> Decoder b
f a
a
Value -> DecodeM b
decodeB Value
v
#if !MIN_VERSION_base(4,13,0)
fail msg = Decoder $ \_ -> decodeFail $ Text.pack msg
#endif
instance Alternative Decoder where
empty :: forall a. Decoder a
empty = forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
"Decoder.Alternative: empty"
Decoder Value -> DecodeM a
decode1 <|> :: forall a. Decoder a -> Decoder a -> Decoder a
<|> Decoder Value -> DecodeM a
decode2 = forall a. (Value -> DecodeM a) -> Decoder a
Decoder forall a b. (a -> b) -> a -> b
$ \Value
v -> Value -> DecodeM a
decode1 Value
v forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Value -> DecodeM a
decode2 Value
v
#if MIN_VERSION_base(4,13,0)
instance MonadFail Decoder where
fail :: forall a. String -> Decoder a
fail String
msg = forall a. (Value -> DecodeM a) -> Decoder a
Decoder forall a b. (a -> b) -> a -> b
$ \Value
_ -> forall a. Text -> DecodeM a
decodeFail forall a b. (a -> b) -> a -> b
$ String -> Text
Text.pack String
msg
#elif MIN_VERSION_base(4,9,0)
instance MonadFail.MonadFail Decoder where
fail msg = Decoder $ \_ -> decodeFail $ Text.pack msg
#endif
makeDecoder :: (Value -> DecodeM a) -> Decoder a
makeDecoder :: forall a. (Value -> DecodeM a) -> Decoder a
makeDecoder = forall a. (Value -> DecodeM a) -> Decoder a
Decoder
decoderToEither :: Decoder a -> Value -> DecodeContext -> Either (DecodeContext, DecodeError) a
decoderToEither :: forall a.
Decoder a
-> Value -> DecodeContext -> Either (DecodeContext, DecodeError) a
decoderToEither Decoder a
decoder Value
v DecodeContext
ctx = forall a.
DecodeM a -> DecodeContext -> Either (DecodeContext, DecodeError) a
unDecodeM (forall a. Decoder a -> Value -> DecodeM a
unDecoder Decoder a
decoder Value
v) DecodeContext
ctx
newtype DecodeM a = DecodeM {forall a.
DecodeM a -> DecodeContext -> Either (DecodeContext, DecodeError) a
unDecodeM :: DecodeContext -> Either (DecodeContext, DecodeError) a}
instance Functor DecodeM where
fmap :: forall a b. (a -> b) -> DecodeM a -> DecodeM b
fmap a -> b
f = forall a.
(DecodeContext -> Either (DecodeContext, DecodeError) a)
-> DecodeM a
DecodeM forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap) a -> b
f forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a.
DecodeM a -> DecodeContext -> Either (DecodeContext, DecodeError) a
unDecodeM
instance Applicative DecodeM where
pure :: forall a. a -> DecodeM a
pure a
v = forall a.
(DecodeContext -> Either (DecodeContext, DecodeError) a)
-> DecodeM a
DecodeM forall a b. (a -> b) -> a -> b
$ \DecodeContext
_ -> forall (f :: * -> *) a. Applicative f => a -> f a
pure a
v
DecodeM DecodeContext -> Either (DecodeContext, DecodeError) (a -> b)
decodeF <*> :: forall a b. DecodeM (a -> b) -> DecodeM a -> DecodeM b
<*> DecodeM DecodeContext -> Either (DecodeContext, DecodeError) a
decodeV = forall a.
(DecodeContext -> Either (DecodeContext, DecodeError) a)
-> DecodeM a
DecodeM forall a b. (a -> b) -> a -> b
$ \DecodeContext
ctx -> DecodeContext -> Either (DecodeContext, DecodeError) (a -> b)
decodeF DecodeContext
ctx forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> DecodeContext -> Either (DecodeContext, DecodeError) a
decodeV DecodeContext
ctx
instance Monad DecodeM where
DecodeM DecodeContext -> Either (DecodeContext, DecodeError) a
decodeA >>= :: forall a b. DecodeM a -> (a -> DecodeM b) -> DecodeM b
>>= a -> DecodeM b
f = forall a.
(DecodeContext -> Either (DecodeContext, DecodeError) a)
-> DecodeM a
DecodeM forall a b. (a -> b) -> a -> b
$ \DecodeContext
ctx -> do
a
a <- DecodeContext -> Either (DecodeContext, DecodeError) a
decodeA DecodeContext
ctx
let DecodeM DecodeContext -> Either (DecodeContext, DecodeError) b
decodeB = a -> DecodeM b
f a
a
DecodeContext -> Either (DecodeContext, DecodeError) b
decodeB DecodeContext
ctx
#if !MIN_VERSION_base(4,13,0)
fail = decodeFail . Text.pack
#endif
instance Alternative DecodeM where
empty :: forall a. DecodeM a
empty = forall a. Text -> DecodeM a
decodeFail Text
"DecodeM.Alternative: empty"
DecodeM DecodeContext -> Either (DecodeContext, DecodeError) a
decode1 <|> :: forall a. DecodeM a -> DecodeM a -> DecodeM a
<|> DecodeM DecodeContext -> Either (DecodeContext, DecodeError) a
decode2 = forall a.
(DecodeContext -> Either (DecodeContext, DecodeError) a)
-> DecodeM a
DecodeM forall a b. (a -> b) -> a -> b
$ \DecodeContext
ctx ->
case DecodeContext -> Either (DecodeContext, DecodeError) a
decode1 DecodeContext
ctx of
Left (DecodeContext, DecodeError)
_ -> DecodeContext -> Either (DecodeContext, DecodeError) a
decode2 DecodeContext
ctx
Right a
x -> forall a b. b -> Either a b
Right a
x
#if MIN_VERSION_base(4,13,0)
instance MonadFail DecodeM where
fail :: forall a. String -> DecodeM a
fail = forall a. Text -> DecodeM a
decodeFail forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
Text.pack
#elif MIN_VERSION_base(4,9,0)
instance MonadFail.MonadFail DecodeM where
fail = decodeFail . Text.pack
#endif
runDecoder :: Decoder a -> Value -> DecodeM a
runDecoder :: forall a. Decoder a -> Value -> DecodeM a
runDecoder Decoder a
decoder Value
v = forall a.
(DecodeContext -> Either (DecodeContext, DecodeError) a)
-> DecodeM a
DecodeM (forall a.
Decoder a
-> Value -> DecodeContext -> Either (DecodeContext, DecodeError) a
decoderToEither Decoder a
decoder Value
v)
invalidValue :: Text -> Value -> DecodeM a
invalidValue :: forall a. Text -> Value -> DecodeM a
invalidValue Text
msg Value
v = forall a. DecodeError -> DecodeM a
decodeError forall a b. (a -> b) -> a -> b
$ Text -> Value -> DecodeError
InvalidValue Text
msg Value
v
typeMismatch :: Value -> DecodeM a
typeMismatch :: forall a. Value -> DecodeM a
typeMismatch Value
v = forall a. DecodeError -> DecodeM a
decodeError forall a b. (a -> b) -> a -> b
$ Value -> DecodeError
TypeMismatch Value
v
decodeFail :: Text -> DecodeM a
decodeFail :: forall a. Text -> DecodeM a
decodeFail Text
msg = forall a. DecodeError -> DecodeM a
decodeError forall a b. (a -> b) -> a -> b
$ Text -> DecodeError
OtherDecodeError Text
msg
decodeError :: DecodeError -> DecodeM a
decodeError :: forall a. DecodeError -> DecodeM a
decodeError DecodeError
e = forall a.
(DecodeContext -> Either (DecodeContext, DecodeError) a)
-> DecodeM a
DecodeM forall a b. (a -> b) -> a -> b
$ \DecodeContext
ctx -> forall a b. a -> Either a b
Left (DecodeContext
ctx, DecodeError
e)
addContextItem :: ContextItem -> DecodeM a -> DecodeM a
addContextItem :: forall a. ContextItem -> DecodeM a -> DecodeM a
addContextItem ContextItem
p DecodeM a
m = forall a.
(DecodeContext -> Either (DecodeContext, DecodeError) a)
-> DecodeM a
DecodeM forall a b. (a -> b) -> a -> b
$ \DecodeContext
ctx -> forall a.
DecodeM a -> DecodeContext -> Either (DecodeContext, DecodeError) a
unDecodeM DecodeM a
m (DecodeContext
ctx forall a. Semigroup a => a -> a -> a
<> [ContextItem
p])
decode :: (DecodeTOML a) => Text -> Either TOMLError a
decode :: forall a. DecodeTOML a => Text -> Either TOMLError a
decode = forall a. Decoder a -> Text -> Either TOMLError a
decodeWith forall a. DecodeTOML a => Decoder a
tomlDecoder
decodeWith :: Decoder a -> Text -> Either TOMLError a
decodeWith :: forall a. Decoder a -> Text -> Either TOMLError a
decodeWith Decoder a
decoder = forall a. Decoder a -> String -> Text -> Either TOMLError a
decodeWithOpts Decoder a
decoder String
""
decodeWithOpts :: Decoder a -> String -> Text -> Either TOMLError a
decodeWithOpts :: forall a. Decoder a -> String -> Text -> Either TOMLError a
decodeWithOpts Decoder a
decoder String
filename Text
input = do
Value
v <- String -> Text -> Either TOMLError Value
parseTOML String
filename Text
input
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first (forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry DecodeContext -> DecodeError -> TOMLError
DecodeError) forall a b. (a -> b) -> a -> b
$ forall a.
Decoder a
-> Value -> DecodeContext -> Either (DecodeContext, DecodeError) a
decoderToEither Decoder a
decoder Value
v []
decodeFile :: (DecodeTOML a) => FilePath -> IO (Either TOMLError a)
decodeFile :: forall a. DecodeTOML a => String -> IO (Either TOMLError a)
decodeFile String
fp = forall a. Decoder a -> String -> Text -> Either TOMLError a
decodeWithOpts forall a. DecodeTOML a => Decoder a
tomlDecoder String
fp forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> IO Text
Text.readFile String
fp
getField :: (DecodeTOML a) => Text -> Decoder a
getField :: forall a. DecodeTOML a => Text -> Decoder a
getField = forall a. Decoder a -> Text -> Decoder a
getFieldWith forall a. DecodeTOML a => Decoder a
tomlDecoder
getFieldOr :: (DecodeTOML a) => a -> Text -> Decoder a
getFieldOr :: forall a. DecodeTOML a => a -> Text -> Decoder a
getFieldOr a
def Text
key = forall a. a -> Maybe a -> a
fromMaybe a
def forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. DecodeTOML a => Text -> Decoder (Maybe a)
getFieldOpt Text
key
getFieldWith :: Decoder a -> Text -> Decoder a
getFieldWith :: forall a. Decoder a -> Text -> Decoder a
getFieldWith Decoder a
decoder Text
key = forall a. Decoder a -> [Text] -> Decoder a
getFieldsWith Decoder a
decoder [Text
key]
getFieldOpt :: (DecodeTOML a) => Text -> Decoder (Maybe a)
getFieldOpt :: forall a. DecodeTOML a => Text -> Decoder (Maybe a)
getFieldOpt = forall a. Decoder a -> Text -> Decoder (Maybe a)
getFieldOptWith forall a. DecodeTOML a => Decoder a
tomlDecoder
getFieldOptWith :: Decoder a -> Text -> Decoder (Maybe a)
getFieldOptWith :: forall a. Decoder a -> Text -> Decoder (Maybe a)
getFieldOptWith Decoder a
decoder Text
key = forall a. Decoder a -> [Text] -> Decoder (Maybe a)
getFieldsOptWith Decoder a
decoder [Text
key]
getFields :: (DecodeTOML a) => [Text] -> Decoder a
getFields :: forall a. DecodeTOML a => [Text] -> Decoder a
getFields = forall a. Decoder a -> [Text] -> Decoder a
getFieldsWith forall a. DecodeTOML a => Decoder a
tomlDecoder
getFieldsWith :: Decoder a -> [Text] -> Decoder a
getFieldsWith :: forall a. Decoder a -> [Text] -> Decoder a
getFieldsWith Decoder a
decoder = forall a. (Value -> DecodeM a) -> Decoder a
makeDecoder forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Text] -> Value -> DecodeM a
go
where
go :: [Text] -> Value -> DecodeM a
go [] Value
v = forall a. Decoder a -> Value -> DecodeM a
runDecoder Decoder a
decoder Value
v
go (Text
k : [Text]
ks) Value
v =
case Value
v of
Table Table
o ->
forall a. ContextItem -> DecodeM a -> DecodeM a
addContextItem (Text -> ContextItem
Key Text
k) forall a b. (a -> b) -> a -> b
$
case forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup Text
k Table
o of
Just Value
v' -> [Text] -> Value -> DecodeM a
go [Text]
ks Value
v'
Maybe Value
Nothing -> forall a. DecodeError -> DecodeM a
decodeError DecodeError
MissingField
Value
_ -> forall a. Value -> DecodeM a
typeMismatch Value
v
getFieldsOpt :: (DecodeTOML a) => [Text] -> Decoder (Maybe a)
getFieldsOpt :: forall a. DecodeTOML a => [Text] -> Decoder (Maybe a)
getFieldsOpt = forall a. Decoder a -> [Text] -> Decoder (Maybe a)
getFieldsOptWith forall a. DecodeTOML a => Decoder a
tomlDecoder
getFieldsOptWith :: Decoder a -> [Text] -> Decoder (Maybe a)
getFieldsOptWith :: forall a. Decoder a -> [Text] -> Decoder (Maybe a)
getFieldsOptWith Decoder a
decoder [Text]
keys =
forall a. (Value -> DecodeM a) -> Decoder a
makeDecoder forall a b. (a -> b) -> a -> b
$ \Value
v ->
forall a.
(DecodeContext -> Either (DecodeContext, DecodeError) a)
-> DecodeM a
DecodeM forall a b. (a -> b) -> a -> b
$ \DecodeContext
ctx ->
case (forall a.
DecodeM a -> DecodeContext -> Either (DecodeContext, DecodeError) a
`unDecodeM` DecodeContext
ctx) forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall a. Decoder a -> Value -> DecodeM a
`runDecoder` Value
v) forall a b. (a -> b) -> a -> b
$ forall a. Decoder a -> [Text] -> Decoder a
getFieldsWith Decoder a
decoder [Text]
keys of
Left (DecodeContext
_, DecodeError
MissingField) -> forall a b. b -> Either a b
Right forall a. Maybe a
Nothing
Left (DecodeContext
ctx', DecodeError
e) -> forall a b. a -> Either a b
Left (DecodeContext
ctx', DecodeError
e)
Right a
x -> forall a b. b -> Either a b
Right forall a b. (a -> b) -> a -> b
$ forall a. a -> Maybe a
Just a
x
getArrayOf :: Decoder a -> Decoder [a]
getArrayOf :: forall a. Decoder a -> Decoder [a]
getArrayOf Decoder a
decoder =
forall a. (Value -> DecodeM a) -> Decoder a
makeDecoder forall a b. (a -> b) -> a -> b
$ \case
Array [Value]
vs -> forall (m :: * -> *) a b c.
Applicative m =>
(a -> b -> m c) -> [a] -> [b] -> m [c]
zipWithM (\Int
i -> forall a. ContextItem -> DecodeM a -> DecodeM a
addContextItem (Int -> ContextItem
Index Int
i) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Decoder a -> Value -> DecodeM a
runDecoder Decoder a
decoder) [Int
0 ..] [Value]
vs
Value
v -> forall a. Value -> DecodeM a
typeMismatch Value
v
class DecodeTOML a where
tomlDecoder :: Decoder a
instance DecodeTOML Value where
tomlDecoder :: Decoder Value
tomlDecoder = forall a. (Value -> DecodeM a) -> Decoder a
Decoder forall (f :: * -> *) a. Applicative f => a -> f a
pure
instance DecodeTOML Void where
tomlDecoder :: Decoder Void
tomlDecoder = forall a. (Value -> DecodeM a) -> Decoder a
makeDecoder forall a. Value -> DecodeM a
typeMismatch
instance DecodeTOML Bool where
tomlDecoder :: Decoder Bool
tomlDecoder =
forall a. (Value -> DecodeM a) -> Decoder a
makeDecoder forall a b. (a -> b) -> a -> b
$ \case
Boolean Bool
x -> forall (f :: * -> *) a. Applicative f => a -> f a
pure Bool
x
Value
v -> forall a. Value -> DecodeM a
typeMismatch Value
v
instance DecodeTOML Integer where
tomlDecoder :: Decoder Integer
tomlDecoder =
forall a. (Value -> DecodeM a) -> Decoder a
makeDecoder forall a b. (a -> b) -> a -> b
$ \case
Integer Integer
x -> forall (f :: * -> *) a. Applicative f => a -> f a
pure Integer
x
Value
v -> forall a. Value -> DecodeM a
typeMismatch Value
v
tomlDecoderInt :: forall a. (Num a) => Decoder a
tomlDecoderInt :: forall a. Num a => Decoder a
tomlDecoderInt = forall a. Num a => Integer -> a
fromInteger forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. DecodeTOML a => Decoder a
tomlDecoder
tomlDecoderBoundedInt :: forall a. (Integral a, Bounded a) => Decoder a
tomlDecoderBoundedInt :: forall a. (Integral a, Bounded a) => Decoder a
tomlDecoderBoundedInt =
forall a. DecodeTOML a => Decoder a
tomlDecoder forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Integer
x
| Integer
x forall a. Ord a => a -> a -> Bool
< forall a. Integral a => a -> Integer
toInteger (forall a. Bounded a => a
minBound @a) -> forall a. (Value -> DecodeM a) -> Decoder a
makeDecoder forall a b. (a -> b) -> a -> b
$ forall a. Text -> Value -> DecodeM a
invalidValue Text
"Underflow"
| Integer
x forall a. Ord a => a -> a -> Bool
> forall a. Integral a => a -> Integer
toInteger (forall a. Bounded a => a
maxBound @a) -> forall a. (Value -> DecodeM a) -> Decoder a
makeDecoder forall a b. (a -> b) -> a -> b
$ forall a. Text -> Value -> DecodeM a
invalidValue Text
"Overflow"
| Bool
otherwise -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall a. Num a => Integer -> a
fromInteger Integer
x
instance DecodeTOML Int where
tomlDecoder :: Decoder Int
tomlDecoder = forall a. (Integral a, Bounded a) => Decoder a
tomlDecoderBoundedInt
instance DecodeTOML Int8 where
tomlDecoder :: Decoder Int8
tomlDecoder = forall a. (Integral a, Bounded a) => Decoder a
tomlDecoderBoundedInt
instance DecodeTOML Int16 where
tomlDecoder :: Decoder Int16
tomlDecoder = forall a. (Integral a, Bounded a) => Decoder a
tomlDecoderBoundedInt
instance DecodeTOML Int32 where
tomlDecoder :: Decoder Int32
tomlDecoder = forall a. (Integral a, Bounded a) => Decoder a
tomlDecoderBoundedInt
instance DecodeTOML Int64 where
tomlDecoder :: Decoder Int64
tomlDecoder = forall a. (Integral a, Bounded a) => Decoder a
tomlDecoderBoundedInt
instance DecodeTOML Word where
tomlDecoder :: Decoder Word
tomlDecoder = forall a. (Integral a, Bounded a) => Decoder a
tomlDecoderBoundedInt
instance DecodeTOML Word8 where
tomlDecoder :: Decoder Word8
tomlDecoder = forall a. (Integral a, Bounded a) => Decoder a
tomlDecoderBoundedInt
instance DecodeTOML Word16 where
tomlDecoder :: Decoder Word16
tomlDecoder = forall a. (Integral a, Bounded a) => Decoder a
tomlDecoderBoundedInt
instance DecodeTOML Word32 where
tomlDecoder :: Decoder Word32
tomlDecoder = forall a. (Integral a, Bounded a) => Decoder a
tomlDecoderBoundedInt
instance DecodeTOML Word64 where
tomlDecoder :: Decoder Word64
tomlDecoder = forall a. (Integral a, Bounded a) => Decoder a
tomlDecoderBoundedInt
instance DecodeTOML Natural where
tomlDecoder :: Decoder Natural
tomlDecoder =
forall a. DecodeTOML a => Decoder a
tomlDecoder forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Integer
x
| Integer
x forall a. Ord a => a -> a -> Bool
>= Integer
0 -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall a. Num a => Integer -> a
fromInteger Integer
x
| Bool
otherwise -> forall a. (Value -> DecodeM a) -> Decoder a
makeDecoder forall a b. (a -> b) -> a -> b
$ forall a. Text -> Value -> DecodeM a
invalidValue Text
"Got negative number"
instance DecodeTOML Double where
tomlDecoder :: Decoder Double
tomlDecoder =
forall a. (Value -> DecodeM a) -> Decoder a
makeDecoder forall a b. (a -> b) -> a -> b
$ \case
Float Double
x -> forall (f :: * -> *) a. Applicative f => a -> f a
pure Double
x
Value
v -> forall a. Value -> DecodeM a
typeMismatch Value
v
tomlDecoderFrac :: (Fractional a) => Decoder a
tomlDecoderFrac :: forall a. Fractional a => Decoder a
tomlDecoderFrac = forall a b. (Real a, Fractional b) => a -> b
realToFrac forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. DecodeTOML a => Decoder a
tomlDecoder @Double
instance DecodeTOML Float where
tomlDecoder :: Decoder Float
tomlDecoder = forall a. Fractional a => Decoder a
tomlDecoderFrac
instance (Integral a) => DecodeTOML (Ratio a) where
tomlDecoder :: Decoder (Ratio a)
tomlDecoder = forall a. Fractional a => Decoder a
tomlDecoderFrac
instance (HasResolution a) => DecodeTOML (Fixed a) where
tomlDecoder :: Decoder (Fixed a)
tomlDecoder = forall a. Fractional a => Decoder a
tomlDecoderFrac
instance DecodeTOML Char where
tomlDecoder :: Decoder Char
tomlDecoder =
forall a. DecodeTOML a => Decoder a
tomlDecoder forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Text
s
| Text -> Int
Text.length Text
s forall a. Eq a => a -> a -> Bool
== Int
1 -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ Text -> Char
Text.head Text
s
| Bool
otherwise -> forall a. (Value -> DecodeM a) -> Decoder a
makeDecoder forall a b. (a -> b) -> a -> b
$ forall a. Text -> Value -> DecodeM a
invalidValue Text
"Expected single character string"
instance {-# OVERLAPPING #-} DecodeTOML String where
tomlDecoder :: Decoder String
tomlDecoder = Text -> String
Text.unpack forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. DecodeTOML a => Decoder a
tomlDecoder
instance DecodeTOML Text where
tomlDecoder :: Decoder Text
tomlDecoder =
forall a. (Value -> DecodeM a) -> Decoder a
makeDecoder forall a b. (a -> b) -> a -> b
$ \case
String Text
s -> forall (f :: * -> *) a. Applicative f => a -> f a
pure Text
s
Value
v -> forall a. Value -> DecodeM a
typeMismatch Value
v
instance DecodeTOML Lazy.Text where
tomlDecoder :: Decoder Text
tomlDecoder = Text -> Text
Text.Lazy.fromStrict forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. DecodeTOML a => Decoder a
tomlDecoder
instance DecodeTOML Time.ZonedTime where
tomlDecoder :: Decoder ZonedTime
tomlDecoder =
forall a. (Value -> DecodeM a) -> Decoder a
makeDecoder forall a b. (a -> b) -> a -> b
$ \case
OffsetDateTime (LocalTime
lt, TimeZone
tz) -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ LocalTime -> TimeZone -> ZonedTime
Time.ZonedTime LocalTime
lt TimeZone
tz
Value
v -> forall a. Value -> DecodeM a
typeMismatch Value
v
instance DecodeTOML Time.UTCTime where
tomlDecoder :: Decoder UTCTime
tomlDecoder = ZonedTime -> UTCTime
Time.zonedTimeToUTC forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. DecodeTOML a => Decoder a
tomlDecoder
instance DecodeTOML Time.SystemTime where
tomlDecoder :: Decoder SystemTime
tomlDecoder = UTCTime -> SystemTime
Time.utcToSystemTime forall b c a. (b -> c) -> (a -> b) -> a -> c
. ZonedTime -> UTCTime
Time.zonedTimeToUTC forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. DecodeTOML a => Decoder a
tomlDecoder
instance DecodeTOML Time.LocalTime where
tomlDecoder :: Decoder LocalTime
tomlDecoder =
forall a. (Value -> DecodeM a) -> Decoder a
makeDecoder forall a b. (a -> b) -> a -> b
$ \case
LocalDateTime LocalTime
dt -> forall (f :: * -> *) a. Applicative f => a -> f a
pure LocalTime
dt
Value
v -> forall a. Value -> DecodeM a
typeMismatch Value
v
instance DecodeTOML Time.Day where
tomlDecoder :: Decoder Day
tomlDecoder =
forall a. (Value -> DecodeM a) -> Decoder a
makeDecoder forall a b. (a -> b) -> a -> b
$ \case
LocalDate Day
d -> forall (f :: * -> *) a. Applicative f => a -> f a
pure Day
d
Value
v -> forall a. Value -> DecodeM a
typeMismatch Value
v
instance DecodeTOML Time.TimeOfDay where
tomlDecoder :: Decoder TimeOfDay
tomlDecoder =
forall a. (Value -> DecodeM a) -> Decoder a
makeDecoder forall a b. (a -> b) -> a -> b
$ \case
LocalTime TimeOfDay
t -> forall (f :: * -> *) a. Applicative f => a -> f a
pure TimeOfDay
t
Value
v -> forall a. Value -> DecodeM a
typeMismatch Value
v
#if MIN_VERSION_time(1,9,0)
instance DecodeTOML Time.DayOfWeek where
tomlDecoder :: Decoder DayOfWeek
tomlDecoder = Text -> Decoder DayOfWeek
toDayOfWeek forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Text
Text.toLower forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< forall a. DecodeTOML a => Decoder a
tomlDecoder
where
toDayOfWeek :: Text -> Decoder DayOfWeek
toDayOfWeek = \case
Text
"monday" -> forall (f :: * -> *) a. Applicative f => a -> f a
pure DayOfWeek
Time.Monday
Text
"tuesday" -> forall (f :: * -> *) a. Applicative f => a -> f a
pure DayOfWeek
Time.Tuesday
Text
"wednesday" -> forall (f :: * -> *) a. Applicative f => a -> f a
pure DayOfWeek
Time.Wednesday
Text
"thursday" -> forall (f :: * -> *) a. Applicative f => a -> f a
pure DayOfWeek
Time.Thursday
Text
"friday" -> forall (f :: * -> *) a. Applicative f => a -> f a
pure DayOfWeek
Time.Friday
Text
"saturday" -> forall (f :: * -> *) a. Applicative f => a -> f a
pure DayOfWeek
Time.Saturday
Text
"sunday" -> forall (f :: * -> *) a. Applicative f => a -> f a
pure DayOfWeek
Time.Sunday
Text
_ -> forall a. (Value -> DecodeM a) -> Decoder a
makeDecoder forall a b. (a -> b) -> a -> b
$ forall a. Text -> Value -> DecodeM a
invalidValue Text
"Invalid day of week"
#endif
instance DecodeTOML Time.DiffTime where
tomlDecoder :: Decoder DiffTime
tomlDecoder = forall a. Num a => Decoder a
tomlDecoderInt forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> forall a. Fractional a => Decoder a
tomlDecoderFrac
instance DecodeTOML Time.NominalDiffTime where
tomlDecoder :: Decoder NominalDiffTime
tomlDecoder = forall a. Num a => Decoder a
tomlDecoderInt forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> forall a. Fractional a => Decoder a
tomlDecoderFrac
#if MIN_VERSION_time(1,9,0)
instance DecodeTOML Time.CalendarDiffTime where
tomlDecoder :: Decoder CalendarDiffTime
tomlDecoder =
Integer -> NominalDiffTime -> CalendarDiffTime
Time.CalendarDiffTime
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. DecodeTOML a => Text -> Decoder a
getField Text
"months"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. DecodeTOML a => Text -> Decoder a
getField Text
"time"
instance DecodeTOML Time.CalendarDiffDays where
tomlDecoder :: Decoder CalendarDiffDays
tomlDecoder =
Integer -> Integer -> CalendarDiffDays
Time.CalendarDiffDays
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. DecodeTOML a => Text -> Decoder a
getField Text
"months"
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. DecodeTOML a => Text -> Decoder a
getField Text
"days"
#endif
instance DecodeTOML Version where
tomlDecoder :: Decoder Version
tomlDecoder = forall {a} {a}. [(a, [a])] -> Decoder a
go forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ReadP a -> ReadS a
readP_to_S ReadP Version
parseVersion forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< forall a. DecodeTOML a => Decoder a
tomlDecoder
where
go :: [(a, [a])] -> Decoder a
go ((a
v, []) : [(a, [a])]
_) = forall (f :: * -> *) a. Applicative f => a -> f a
pure a
v
go ((a, [a])
_ : [(a, [a])]
vs) = [(a, [a])] -> Decoder a
go [(a, [a])]
vs
go [] = forall a. (Value -> DecodeM a) -> Decoder a
makeDecoder forall a b. (a -> b) -> a -> b
$ forall a. Text -> Value -> DecodeM a
invalidValue Text
"Invalid Version"
instance DecodeTOML Ordering where
tomlDecoder :: Decoder Ordering
tomlDecoder =
forall a. DecodeTOML a => Decoder a
tomlDecoder @Text forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Text
"LT" -> forall (f :: * -> *) a. Applicative f => a -> f a
pure Ordering
LT
Text
"EQ" -> forall (f :: * -> *) a. Applicative f => a -> f a
pure Ordering
EQ
Text
"GT" -> forall (f :: * -> *) a. Applicative f => a -> f a
pure Ordering
GT
Text
_ -> forall a. (Value -> DecodeM a) -> Decoder a
makeDecoder forall a b. (a -> b) -> a -> b
$ forall a. Text -> Value -> DecodeM a
invalidValue Text
"Invalid Ordering"
instance (DecodeTOML a) => DecodeTOML (Identity a) where
tomlDecoder :: Decoder (Identity a)
tomlDecoder = forall a. a -> Identity a
Identity forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. DecodeTOML a => Decoder a
tomlDecoder
instance DecodeTOML (Proxy a) where
tomlDecoder :: Decoder (Proxy a)
tomlDecoder = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall {k} (t :: k). Proxy t
Proxy
instance (DecodeTOML a) => DecodeTOML (Const a b) where
tomlDecoder :: Decoder (Const a b)
tomlDecoder = forall {k} a (b :: k). a -> Const a b
Const forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. DecodeTOML a => Decoder a
tomlDecoder
instance (DecodeTOML a) => DecodeTOML (Maybe a) where
tomlDecoder :: Decoder (Maybe a)
tomlDecoder = forall a. a -> Maybe a
Just forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. DecodeTOML a => Decoder a
tomlDecoder
instance (DecodeTOML a, DecodeTOML b) => DecodeTOML (Either a b) where
tomlDecoder :: Decoder (Either a b)
tomlDecoder = (forall a b. b -> Either a b
Right forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. DecodeTOML a => Decoder a
tomlDecoder) forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (forall a b. a -> Either a b
Left forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. DecodeTOML a => Decoder a
tomlDecoder)
instance (DecodeTOML a) => DecodeTOML (Monoid.First a) where
tomlDecoder :: Decoder (First a)
tomlDecoder = forall a. Maybe a -> First a
Monoid.First forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. DecodeTOML a => Decoder a
tomlDecoder
instance (DecodeTOML a) => DecodeTOML (Monoid.Last a) where
tomlDecoder :: Decoder (Last a)
tomlDecoder = forall a. Maybe a -> Last a
Monoid.Last forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. DecodeTOML a => Decoder a
tomlDecoder
instance (DecodeTOML a) => DecodeTOML (Semigroup.First a) where
tomlDecoder :: Decoder (First a)
tomlDecoder = forall a. a -> First a
Semigroup.First forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. DecodeTOML a => Decoder a
tomlDecoder
instance (DecodeTOML a) => DecodeTOML (Semigroup.Last a) where
tomlDecoder :: Decoder (Last a)
tomlDecoder = forall a. a -> Last a
Semigroup.Last forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. DecodeTOML a => Decoder a
tomlDecoder
instance (DecodeTOML a) => DecodeTOML (Semigroup.Max a) where
tomlDecoder :: Decoder (Max a)
tomlDecoder = forall a. a -> Max a
Semigroup.Max forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. DecodeTOML a => Decoder a
tomlDecoder
instance (DecodeTOML a) => DecodeTOML (Semigroup.Min a) where
tomlDecoder :: Decoder (Min a)
tomlDecoder = forall a. a -> Min a
Semigroup.Min forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. DecodeTOML a => Decoder a
tomlDecoder
instance (DecodeTOML a) => DecodeTOML (Monoid.Dual a) where
tomlDecoder :: Decoder (Dual a)
tomlDecoder = forall a. a -> Dual a
Monoid.Dual forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. DecodeTOML a => Decoder a
tomlDecoder
instance (DecodeTOML a) => DecodeTOML [a] where
tomlDecoder :: Decoder [a]
tomlDecoder = forall a. Decoder a -> Decoder [a]
getArrayOf forall a. DecodeTOML a => Decoder a
tomlDecoder
instance (IsString k, Ord k, DecodeTOML v) => DecodeTOML (Map k v) where
tomlDecoder :: Decoder (Map k v)
tomlDecoder =
forall a. (Value -> DecodeM a) -> Decoder a
makeDecoder forall a b. (a -> b) -> a -> b
$ \case
Table Table
o -> forall k2 k1 a. Ord k2 => (k1 -> k2) -> Map k1 a -> Map k2 a
Map.mapKeys (forall a. IsString a => String -> a
fromString forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
Text.unpack) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (forall a. Decoder a -> Value -> DecodeM a
runDecoder forall a. DecodeTOML a => Decoder a
tomlDecoder) Table
o
Value
v -> forall a. Value -> DecodeM a
typeMismatch Value
v
instance (DecodeTOML a) => DecodeTOML (NonEmpty a) where
tomlDecoder :: Decoder (NonEmpty a)
tomlDecoder = forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. Decoder a
raiseEmpty forall (f :: * -> *) a. Applicative f => a -> f a
pure forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [a] -> Maybe (NonEmpty a)
NonEmpty.nonEmpty forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< forall a. DecodeTOML a => Decoder a
tomlDecoder
where
raiseEmpty :: Decoder a
raiseEmpty = forall a. (Value -> DecodeM a) -> Decoder a
makeDecoder forall a b. (a -> b) -> a -> b
$ forall a. Text -> Value -> DecodeM a
invalidValue Text
"Got empty list"
instance DecodeTOML IntSet where
tomlDecoder :: Decoder IntSet
tomlDecoder = [Int] -> IntSet
IntSet.fromList forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. DecodeTOML a => Decoder a
tomlDecoder
instance (DecodeTOML a, Ord a) => DecodeTOML (Set a) where
tomlDecoder :: Decoder (Set a)
tomlDecoder = forall a. Ord a => [a] -> Set a
Set.fromList forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. DecodeTOML a => Decoder a
tomlDecoder
instance (DecodeTOML a) => DecodeTOML (IntMap a) where
tomlDecoder :: Decoder (IntMap a)
tomlDecoder = forall a. [(Int, a)] -> IntMap a
IntMap.fromList forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. DecodeTOML a => Decoder a
tomlDecoder
instance (DecodeTOML a) => DecodeTOML (Seq a) where
tomlDecoder :: Decoder (Seq a)
tomlDecoder = forall a. [a] -> Seq a
Seq.fromList forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. DecodeTOML a => Decoder a
tomlDecoder
tomlDecoderTuple :: ([Value] -> Maybe (DecodeM a)) -> Decoder a
tomlDecoderTuple :: forall a. ([Value] -> Maybe (DecodeM a)) -> Decoder a
tomlDecoderTuple [Value] -> Maybe (DecodeM a)
f =
forall a. (Value -> DecodeM a) -> Decoder a
makeDecoder forall a b. (a -> b) -> a -> b
$ \case
Array [Value]
vs | Just DecodeM a
decodeM <- [Value] -> Maybe (DecodeM a)
f [Value]
vs -> DecodeM a
decodeM
Value
v -> forall a. Value -> DecodeM a
typeMismatch Value
v
decodeElem :: (DecodeTOML a) => Int -> Value -> DecodeM a
decodeElem :: forall a. DecodeTOML a => Int -> Value -> DecodeM a
decodeElem Int
i Value
v = forall a. ContextItem -> DecodeM a -> DecodeM a
addContextItem (Int -> ContextItem
Index Int
i) (forall a. Decoder a -> Value -> DecodeM a
runDecoder forall a. DecodeTOML a => Decoder a
tomlDecoder Value
v)
instance DecodeTOML () where
tomlDecoder :: Decoder ()
tomlDecoder = forall a. ([Value] -> Maybe (DecodeM a)) -> Decoder a
tomlDecoderTuple forall a b. (a -> b) -> a -> b
$ \case
[] -> forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
[Value]
_ -> forall a. Maybe a
Nothing
instance (DecodeTOML a, DecodeTOML b) => DecodeTOML (a, b) where
tomlDecoder :: Decoder (a, b)
tomlDecoder = forall a. ([Value] -> Maybe (DecodeM a)) -> Decoder a
tomlDecoderTuple forall a b. (a -> b) -> a -> b
$ \case
[Value
a, Value
b] ->
forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$
(,)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. DecodeTOML a => Int -> Value -> DecodeM a
decodeElem Int
0 Value
a
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. DecodeTOML a => Int -> Value -> DecodeM a
decodeElem Int
1 Value
b
[Value]
_ -> forall a. Maybe a
Nothing
instance (DecodeTOML a, DecodeTOML b, DecodeTOML c) => DecodeTOML (a, b, c) where
tomlDecoder :: Decoder (a, b, c)
tomlDecoder = forall a. ([Value] -> Maybe (DecodeM a)) -> Decoder a
tomlDecoderTuple forall a b. (a -> b) -> a -> b
$ \case
[Value
a, Value
b, Value
c] ->
forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$
(,,)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. DecodeTOML a => Int -> Value -> DecodeM a
decodeElem Int
0 Value
a
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. DecodeTOML a => Int -> Value -> DecodeM a
decodeElem Int
1 Value
b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. DecodeTOML a => Int -> Value -> DecodeM a
decodeElem Int
2 Value
c
[Value]
_ -> forall a. Maybe a
Nothing
instance (DecodeTOML a, DecodeTOML b, DecodeTOML c, DecodeTOML d) => DecodeTOML (a, b, c, d) where
tomlDecoder :: Decoder (a, b, c, d)
tomlDecoder = forall a. ([Value] -> Maybe (DecodeM a)) -> Decoder a
tomlDecoderTuple forall a b. (a -> b) -> a -> b
$ \case
[Value
a, Value
b, Value
c, Value
d] ->
forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$
(,,,)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. DecodeTOML a => Int -> Value -> DecodeM a
decodeElem Int
0 Value
a
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. DecodeTOML a => Int -> Value -> DecodeM a
decodeElem Int
1 Value
b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. DecodeTOML a => Int -> Value -> DecodeM a
decodeElem Int
2 Value
c
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall a. DecodeTOML a => Int -> Value -> DecodeM a
decodeElem Int
3 Value
d
[Value]
_ -> forall a. Maybe a
Nothing