{-# LANGUAGE DeriveAnyClass #-}
module Toml.Bi.Code
(
TomlCodec
, Env
, St
, DecodeException (..)
, LoadTomlException (..)
, prettyException
, decode
, decodeFile
, runTomlCodec
, encode
, execTomlCodec
) where
import Control.DeepSeq (NFData)
import Control.Exception (Exception, throwIO)
import Control.Monad.Except (ExceptT, runExceptT)
import Control.Monad.IO.Class (MonadIO (..))
import Control.Monad.Reader (Reader, runReader)
import Control.Monad.State (State, execState)
import Control.Monad.Trans.Maybe (MaybeT (..))
import Data.Bifunctor (first)
import Data.Foldable (toList)
import Data.Semigroup (Semigroup (..))
import Data.Text (Text)
import GHC.Generics (Generic)
import Toml.Bi.Map (TomlBiMapError, prettyBiMapError)
import Toml.Bi.Monad (BiCodec, Codec (..))
import Toml.Parser (ParseException (..), parse)
import Toml.PrefixTree (Key (..), unPiece)
import Toml.Printer (pretty)
import Toml.Type (TOML (..), TValue, showType)
import qualified Data.Text as Text
import qualified Data.Text.IO as TIO
data DecodeException
= TrivialError
| BiMapError TomlBiMapError
| KeyNotFound Key
| TableNotFound Key
| TypeMismatch Key Text TValue
| ParseError ParseException
deriving (Eq, Generic, NFData)
instance Show DecodeException where
show = Text.unpack . prettyException
instance Semigroup DecodeException where
TrivialError <> e = e
e <> _ = e
instance Monoid DecodeException where
mempty = TrivialError
mappend = (<>)
prettyException :: DecodeException -> Text
prettyException de = "tomland decode error: " <> case de of
TrivialError -> "'empty' parser from 'Alternative' is used"
BiMapError biError -> prettyBiMapError biError
KeyNotFound name -> "Key " <> joinKey name <> " is not found"
TableNotFound name -> "Table [" <> joinKey name <> "] is not found"
TypeMismatch name expected actual -> "Type for key " <> joinKey name <> " doesn't match."
<> "\n Expected: " <> expected
<> "\n Actual: " <> Text.pack (showType actual)
ParseError (ParseException msg) -> "Parse error during conversion from TOML to custom user type: \n " <> msg
where
joinKey :: Key -> Text
joinKey = Text.intercalate "." . map unPiece . toList . unKey
type Env = ExceptT DecodeException (Reader TOML)
type St = MaybeT (State TOML)
type TomlCodec a = BiCodec Env St a
decode :: TomlCodec a -> Text -> Either DecodeException a
decode codec text = do
toml <- first ParseError (parse text)
runTomlCodec codec toml
runTomlCodec :: TomlCodec a -> TOML -> Either DecodeException a
runTomlCodec codec = runReader (runExceptT $ codecRead codec)
encode :: TomlCodec a -> a -> Text
encode codec obj = pretty $ execTomlCodec codec obj
execTomlCodec :: TomlCodec a -> a -> TOML
execTomlCodec codec obj = execState (runMaybeT $ codecWrite codec obj) mempty
data LoadTomlException = LoadTomlException FilePath Text
instance Show LoadTomlException where
show (LoadTomlException filePath msg) = "Couldnt parse file " ++ filePath ++ ": " ++ show msg
instance Exception LoadTomlException
decodeFile :: (MonadIO m) => TomlCodec a -> FilePath -> m a
decodeFile codec filePath = liftIO $
(decode codec <$> TIO.readFile filePath) >>= errorWhenLeft
where
errorWhenLeft :: Either DecodeException a -> IO a
errorWhenLeft (Left e) = throwIO $ LoadTomlException filePath $ prettyException e
errorWhenLeft (Right pc) = pure pc