{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE Rank2Types #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Toml.Bi.Combinators
(
BiToml
, Env
, St
, DecodeException
, decode
, encode
, bijectionMaker
, dimapNum
, mdimap
, bool
, int
, integer
, double
, str
, arrayOf
, maybeP
, table
, Valuer (..)
, boolV
, integerV
, doubleV
, strV
, arrV
) where
import Control.Monad.Except (ExceptT, MonadError, catchError, runExceptT, throwError)
import Control.Monad.Reader (Reader, asks, local, runReader)
import Control.Monad.State (State, execState, gets, modify)
import Data.Bifunctor (first)
import Data.Maybe (fromMaybe)
import Data.Text (Text)
import Toml.Bi.Monad (Bi, Bijection (..), dimap)
import Toml.Parser (ParseException (..), parse)
import Toml.PrefixTree (Key)
import Toml.Printer (prettyToml)
import Toml.Type (AnyValue (..), TOML (..), Value (..), ValueType (..), matchArray, matchBool,
matchDouble, matchInteger, matchText)
import qualified Data.HashMap.Strict as HashMap
import qualified Toml.PrefixTree as Prefix
data DecodeException
= KeyNotFound Key
| TableNotFound Key
| TypeMismatch Text
| ParseError ParseException
deriving (Eq, Show)
type Env = ExceptT DecodeException (Reader TOML)
type St = State TOML
type BiToml a = Bi Env St a
decode :: BiToml a -> Text -> Either DecodeException a
decode biToml text = do
toml <- first ParseError (parse text)
runReader (runExceptT $ biRead biToml) toml
encode :: BiToml a -> a -> Text
encode bi obj = prettyToml $ execState (biWrite bi obj) (TOML mempty mempty)
bijectionMaker :: forall a t .
Text
-> (forall f . Value f -> Maybe a)
-> (a -> Value t)
-> Key
-> BiToml a
bijectionMaker typeTag fromVal toVal key = Bijection input output
where
input :: Env a
input = do
mVal <- asks $ HashMap.lookup key . tomlPairs
case mVal of
Nothing -> throwError $ KeyNotFound key
Just (AnyValue val) -> case fromVal val of
Just v -> pure v
Nothing -> throwError $ TypeMismatch typeTag
output :: a -> St a
output a = do
let val = AnyValue (toVal a)
a <$ modify (\(TOML vals nested) -> TOML (HashMap.insert key val vals) nested)
dimapNum :: forall n r w . (Integral n, Functor r, Functor w)
=> Bi r w Integer
-> Bi r w n
dimapNum = dimap toInteger fromIntegral
mdimap :: (Monad r, Monad w, MonadError DecodeException r)
=> (c -> d)
-> (a -> Maybe b)
-> Bijection r w d a
-> Bijection r w c b
mdimap toString toMaybe bi = Bijection
{ biRead = (toMaybe <$> biRead bi) >>= \case
Nothing -> throwError $ ParseError $ ParseException "Can't parse"
Just b -> pure b
, biWrite = \s -> do
retS <- biWrite bi $ toString s
case toMaybe retS of
Nothing -> error $ "Given pair of functions for 'mdimap' doesn't satisfy roundtrip property"
Just b -> pure b
}
data Valuer (tag :: ValueType) a = Valuer
{ valFrom :: forall t . Value t -> Maybe a
, valTo :: a -> Value tag
}
boolV :: Valuer 'TBool Bool
boolV = Valuer matchBool Bool
integerV :: Valuer 'TInt Integer
integerV = Valuer matchInteger Int
doubleV :: Valuer 'TFloat Double
doubleV = Valuer matchDouble Float
strV :: Valuer 'TString Text
strV = Valuer matchText String
arrV :: forall a t . Valuer t a -> Valuer 'TArray [a]
arrV Valuer{..} = Valuer (matchArray valFrom) (Array . map valTo)
bool :: Key -> BiToml Bool
bool = bijectionMaker "Boolean" matchBool Bool
integer :: Key -> BiToml Integer
integer = bijectionMaker "Int" matchInteger Int
int :: Key -> BiToml Int
int = dimapNum . integer
double :: Key -> BiToml Double
double = bijectionMaker "Double" matchDouble Float
str :: Key -> BiToml Text
str = bijectionMaker "String" matchText String
arrayOf :: forall a t . Valuer t a -> Key -> BiToml [a]
arrayOf valuer key = Bijection input output
where
input :: Env [a]
input = do
mVal <- asks $ HashMap.lookup key . tomlPairs
case mVal of
Nothing -> throwError $ KeyNotFound key
Just (AnyValue (Array arr)) -> case arr of
[] -> pure []
xs -> case mapM (valFrom valuer) xs of
Nothing -> throwError $ TypeMismatch "Some type of element"
Just vals -> pure vals
Just _ -> throwError $ TypeMismatch "Array of smth"
output :: [a] -> St [a]
output a = do
let val = AnyValue $ Array $ map (valTo valuer) a
a <$ modify (\(TOML vals tables) -> TOML (HashMap.insert key val vals) tables)
maybeP :: forall a . (Key -> BiToml a) -> Key -> BiToml (Maybe a)
maybeP converter key = let bi = converter key in Bijection
{ biRead = (Just <$> biRead bi) `catchError` handleNotFound
, biWrite = \case
Nothing -> pure Nothing
Just v -> biWrite bi v >> pure (Just v)
}
where
handleNotFound :: DecodeException -> Env (Maybe a)
handleNotFound (KeyNotFound _) = pure Nothing
handleNotFound (TableNotFound _) = pure Nothing
handleNotFound e = throwError e
table :: forall a . BiToml a -> Key -> BiToml a
table bi key = Bijection 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) (biRead bi)
output :: a -> St a
output a = do
mTable <- gets $ Prefix.lookup key . tomlTables
let toml = fromMaybe (TOML mempty mempty) mTable
let newToml = execState (biWrite bi a) toml
a <$ modify (\(TOML vals tables) -> TOML vals (Prefix.insert key newToml tables))