{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GADTs #-}
module Toml.Bi.Combinators
(
bool
, integer
, natural
, int
, word
, double
, float
, text
, lazyText
, byteString
, lazyByteString
, string
, zonedTime
, localTime
, day
, timeOfDay
, arrayOf
, arraySetOf
, arrayIntSet
, arrayHashSetOf
, arrayNonEmptyOf
, textBy
, read
, table
, nonEmpty
, list
, match
) where
import Prelude hiding (read)
import Control.Monad (forM)
import Control.Monad.Except (catchError, throwError)
import Control.Monad.Reader (asks, local)
import Control.Monad.State (execState, gets, modify)
import Control.Monad.Trans.Maybe (MaybeT (..), runMaybeT)
import Data.ByteString (ByteString)
import Data.Hashable (Hashable)
import Data.HashSet (HashSet)
import Data.IntSet (IntSet)
import Data.List.NonEmpty (NonEmpty (..), toList)
import Data.Maybe (fromMaybe)
import Data.Semigroup ((<>))
import Data.Set (Set)
import Data.Text (Text)
import Data.Time (Day, LocalTime, TimeOfDay, ZonedTime)
import Data.Word (Word)
import Numeric.Natural (Natural)
import Toml.Bi.Code (DecodeException (..), Env, St, TomlCodec, execTomlCodec)
import Toml.Bi.Map (BiMap (..), TomlBiMap, _Array, _Bool, _ByteString, _Day, _Double, _Float,
_HashSet, _Int, _IntSet, _Integer, _LByteString, _LText, _LocalTime, _Natural,
_NonEmpty, _Read, _Set, _String, _Text, _TextBy, _TimeOfDay, _Word, _ZonedTime)
import Toml.Bi.Monad (Codec (..))
import Toml.PrefixTree (Key)
import Toml.Type (AnyValue (..), TOML (..), insertKeyAnyVal, insertTable, insertTableArrays)
import qualified Data.ByteString.Lazy as BL
import qualified Data.HashMap.Strict as HashMap
import qualified Toml.PrefixTree as Prefix
import qualified Data.Text.Lazy as L
match :: forall a . TomlBiMap a AnyValue -> Key -> TomlCodec a
match BiMap{..} key = Codec input output
where
input :: Env a
input = do
mVal <- asks $ HashMap.lookup key . tomlPairs
case mVal of
Nothing -> throwError $ KeyNotFound key
Just anyVal -> case backward anyVal of
Right v -> pure v
Left err -> throwError $ BiMapError err
output :: a -> St a
output a = do
anyVal <- MaybeT $ pure $ either (const Nothing) Just $ forward a
a <$ modify (insertKeyAnyVal key anyVal)
bool :: Key -> TomlCodec Bool
bool = match _Bool
integer :: Key -> TomlCodec Integer
integer = match _Integer
int :: Key -> TomlCodec Int
int = match _Int
natural :: Key -> TomlCodec Natural
natural = match _Natural
word :: Key -> TomlCodec Word
word = match _Word
double :: Key -> TomlCodec Double
double = match _Double
float :: Key -> TomlCodec Float
float = match _Float
text :: Key -> TomlCodec Text
text = match _Text
lazyText :: Key -> TomlCodec L.Text
lazyText = match _LText
textBy :: (a -> Text) -> (Text -> Either Text a) -> Key -> TomlCodec a
textBy to from = match (_TextBy to from)
string :: Key -> TomlCodec String
string = match _String
read :: (Show a, Read a) => Key -> TomlCodec a
read = match _Read
byteString :: Key -> TomlCodec ByteString
byteString = match _ByteString
lazyByteString :: Key -> TomlCodec BL.ByteString
lazyByteString = match _LByteString
zonedTime :: Key -> TomlCodec ZonedTime
zonedTime = match _ZonedTime
localTime :: Key -> TomlCodec LocalTime
localTime = match _LocalTime
day :: Key -> TomlCodec Day
day = match _Day
timeOfDay :: Key -> TomlCodec TimeOfDay
timeOfDay = match _TimeOfDay
arrayOf :: TomlBiMap a AnyValue -> Key -> TomlCodec [a]
arrayOf = match . _Array
arraySetOf :: Ord a => TomlBiMap a AnyValue -> Key -> TomlCodec (Set a)
arraySetOf = match . _Set
arrayIntSet :: Key -> TomlCodec IntSet
arrayIntSet = match _IntSet
arrayHashSetOf
:: (Hashable a, Eq a)
=> TomlBiMap a AnyValue
-> Key
-> TomlCodec (HashSet a)
arrayHashSetOf = match . _HashSet
arrayNonEmptyOf :: TomlBiMap a AnyValue -> Key -> TomlCodec (NonEmpty a)
arrayNonEmptyOf = match . _NonEmpty
handleErrorInTable :: Key -> DecodeException -> Env a
handleErrorInTable key = \case
KeyNotFound name -> throwError $ KeyNotFound (key <> name)
TableNotFound name -> throwError $ TableNotFound (key <> name)
TypeMismatch name t1 t2 -> throwError $ TypeMismatch (key <> name) t1 t2
e -> throwError e
codecReadTOML :: TOML -> TomlCodec a -> Env a
codecReadTOML toml codec = local (const toml) (codecRead codec)
table :: forall a . TomlCodec a -> Key -> TomlCodec a
table codec key = Codec input output
where
input :: Env a
input = do
mTable <- asks $ Prefix.lookup key . tomlTables
case mTable of
Nothing -> throwError $ TableNotFound key
Just toml -> codecReadTOML toml codec `catchError` handleErrorInTable key
output :: a -> St a
output a = do
mTable <- gets $ Prefix.lookup key . tomlTables
let toml = fromMaybe mempty mTable
let newToml = execState (runMaybeT $ codecWrite codec a) toml
a <$ modify (insertTable key newToml)
nonEmpty :: forall a . TomlCodec a -> Key -> TomlCodec (NonEmpty a)
nonEmpty codec key = Codec input output
where
input :: Env (NonEmpty a)
input = do
mTables <- asks $ HashMap.lookup key . tomlTableArrays
case mTables of
Nothing -> throwError $ TableNotFound key
Just tomls -> forM tomls $ \toml ->
codecReadTOML toml codec `catchError` handleErrorInTable key
output :: NonEmpty a -> St (NonEmpty a)
output as = do
let tomls = fmap (execTomlCodec codec) as
mTables <- gets $ HashMap.lookup key . tomlTableArrays
let newTomls = case mTables of
Nothing -> tomls
Just oldTomls -> oldTomls <> tomls
as <$ modify (insertTableArrays key newTomls)
list :: forall a . TomlCodec a -> Key -> TomlCodec [a]
list codec key = Codec
{ codecRead = (toList <$> codecRead nonEmptyCodec) `catchError` \case
TableNotFound errKey | errKey == key -> pure []
err -> throwError err
, codecWrite = \case
[] -> pure []
l@(x:xs) -> l <$ codecWrite nonEmptyCodec (x :| xs)
}
where
nonEmptyCodec :: TomlCodec (NonEmpty a)
nonEmptyCodec = nonEmpty codec key