{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GADTs #-}
module Toml.Bi.Combinators
(
bool
, int
, integer
, natural
, word
, double
, float
, text
, read
, string
, byteString
, lazyByteString
, zonedTime
, localTime
, day
, timeOfDay
, arrayOf
, arraySetOf
, arrayIntSet
, arrayHashSetOf
, arrayNonEmptyOf
, match
, table
, wrapper
, mdimap
) where
import Control.Monad.Except (MonadError, catchError, throwError)
import Control.Monad.Reader (asks, local)
import Control.Monad.State (execState, gets, modify)
import Control.Monad.Trans.Maybe (MaybeT (..), runMaybeT)
import Data.Coerce (Coercible, coerce)
import Data.Maybe (fromMaybe)
import Data.Proxy (Proxy (..))
import Data.Semigroup ((<>))
import Data.Text (Text)
import Data.Typeable (Typeable, typeRep)
import Data.Time (Day, LocalTime, TimeOfDay, ZonedTime)
import Data.ByteString (ByteString)
import Data.Word (Word)
import Numeric.Natural (Natural)
import Data.Hashable (Hashable)
import Data.Set (Set)
import Data.HashSet (HashSet)
import Data.IntSet (IntSet)
import Data.List.NonEmpty (NonEmpty)
import Toml.Bi.Code (DecodeException (..), Env, St, TomlCodec)
import Toml.Bi.Monad (Codec (..), dimap)
import Toml.BiMap (BiMap (..), _Array, _Bool, _Double,
_Integer, _String, _Text, _ZonedTime, _LocalTime, _Day,
_TimeOfDay, _Int, _Word, _Natural, _Float, _Read,
_ByteString, _LByteString, _Set, _IntSet, _HashSet,
_NonEmpty)
import Toml.Parser (ParseException (..))
import Toml.PrefixTree (Key)
import Toml.Type (AnyValue (..), TOML (..), insertKeyAnyVal, insertTable, valueType)
import Prelude hiding (read)
import qualified Data.HashMap.Strict as HashMap
import qualified Data.Text as Text
import qualified Toml.PrefixTree as Prefix
import qualified Data.ByteString.Lazy as BL
typeName :: forall a . Typeable a => Text
typeName = Text.pack $ show $ typeRep $ Proxy @a
match :: forall a . Typeable a => BiMap 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@(AnyValue val) -> case backward anyVal of
Just v -> pure v
Nothing -> throwError $ TypeMismatch key (typeName @a) (valueType val)
output :: a -> St a
output a = do
anyVal <- MaybeT $ pure $ forward a
a <$ modify (insertKeyAnyVal key anyVal)
mdimap :: (Monad r, Monad w, MonadError DecodeException r)
=> (c -> d)
-> (a -> Maybe b)
-> Codec r w d a
-> Codec r w c b
mdimap toString toMaybe codec = Codec
{ codecRead = (toMaybe <$> codecRead codec) >>= \case
Nothing -> throwError $ ParseError $ ParseException "Can't parse"
Just b -> pure b
, codecWrite = \s -> do
retS <- codecWrite codec $ toString s
case toMaybe retS of
Nothing -> error $ "Given pair of functions for 'mdimap' doesn't satisfy roundtrip property"
Just b -> pure b
}
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
string :: Key -> TomlCodec String
string = match _String
read :: (Show a, Read a, Typeable 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 :: Typeable a => BiMap a AnyValue -> Key -> TomlCodec [a]
arrayOf = match . _Array
arraySetOf :: (Typeable a, Ord a) => BiMap a AnyValue -> Key -> TomlCodec (Set a)
arraySetOf = match . _Set
arrayIntSet :: Key -> TomlCodec IntSet
arrayIntSet = match _IntSet
arrayHashSetOf :: (Typeable a, Hashable a, Eq a) => BiMap a AnyValue -> Key -> TomlCodec (HashSet a)
arrayHashSetOf = match . _HashSet
arrayNonEmptyOf :: Typeable a => BiMap a AnyValue -> Key -> TomlCodec (NonEmpty a)
arrayNonEmptyOf = match . _NonEmpty
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 -> local (const toml) (codecRead codec) `catchError` handleTableName
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)
handleTableName :: DecodeException -> Env a
handleTableName (KeyNotFound name) = throwError $ KeyNotFound (key <> name)
handleTableName (TableNotFound name) = throwError $ TableNotFound (key <> name)
handleTableName (TypeMismatch name t1 t2) = throwError $ TypeMismatch (key <> name) t1 t2
handleTableName e = throwError e
wrapper :: forall b a . Coercible a b => (Key -> TomlCodec a) -> Key -> TomlCodec b
wrapper bi key = dimap coerce coerce (bi key)