module Toml.Codec.Code
(
decode
, decodeValidation
, decodeFileEither
, decodeFile
, encode
, encodeToFile
, runTomlCodec
, execTomlCodec
) where
import Control.Exception (throwIO)
import Control.Monad.IO.Class (MonadIO (..))
import Data.Text (Text)
import Validation (Validation (..), validationToEither)
import Toml.Codec.Error (LoadTomlException (..), TomlDecodeError (..), prettyTomlDecodeErrors)
import Toml.Codec.Types (Codec (..), TomlCodec, TomlState (..))
import Toml.Parser (parse)
import Toml.Type (TOML (..))
import Toml.Type.Printer (pretty)
import qualified Data.Text.IO as TIO
decodeValidation :: TomlCodec a -> Text -> Validation [TomlDecodeError] a
decodeValidation :: TomlCodec a -> Text -> Validation [TomlDecodeError] a
decodeValidation codec :: TomlCodec a
codec text :: Text
text = case Text -> Either TomlParseError TOML
parse Text
text of
Left err :: TomlParseError
err -> [TomlDecodeError] -> Validation [TomlDecodeError] a
forall e a. e -> Validation e a
Failure [TomlParseError -> TomlDecodeError
ParseError TomlParseError
err]
Right toml :: TOML
toml -> TomlCodec a -> TOML -> Validation [TomlDecodeError] a
forall a. TomlCodec a -> TOML -> Validation [TomlDecodeError] a
runTomlCodec TomlCodec a
codec TOML
toml
decode :: TomlCodec a -> Text -> Either [TomlDecodeError] a
decode :: TomlCodec a -> Text -> Either [TomlDecodeError] a
decode codec :: TomlCodec a
codec = Validation [TomlDecodeError] a -> Either [TomlDecodeError] a
forall e a. Validation e a -> Either e a
validationToEither (Validation [TomlDecodeError] a -> Either [TomlDecodeError] a)
-> (Text -> Validation [TomlDecodeError] a)
-> Text
-> Either [TomlDecodeError] a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TomlCodec a -> Text -> Validation [TomlDecodeError] a
forall a. TomlCodec a -> Text -> Validation [TomlDecodeError] a
decodeValidation TomlCodec a
codec
decodeFileValidation
:: forall a m . (MonadIO m)
=> TomlCodec a
-> FilePath
-> m (Validation [TomlDecodeError] a)
decodeFileValidation :: TomlCodec a -> FilePath -> m (Validation [TomlDecodeError] a)
decodeFileValidation codec :: TomlCodec a
codec = (Text -> Validation [TomlDecodeError] a)
-> m Text -> m (Validation [TomlDecodeError] a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (TomlCodec a -> Text -> Validation [TomlDecodeError] a
forall a. TomlCodec a -> Text -> Validation [TomlDecodeError] a
decodeValidation TomlCodec a
codec) (m Text -> m (Validation [TomlDecodeError] a))
-> (FilePath -> m Text)
-> FilePath
-> m (Validation [TomlDecodeError] a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IO Text -> m Text
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Text -> m Text) -> (FilePath -> IO Text) -> FilePath -> m Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> IO Text
TIO.readFile
decodeFileEither
:: forall a m . (MonadIO m)
=> TomlCodec a
-> FilePath
-> m (Either [TomlDecodeError] a)
decodeFileEither :: TomlCodec a -> FilePath -> m (Either [TomlDecodeError] a)
decodeFileEither codec :: TomlCodec a
codec = (Validation [TomlDecodeError] a -> Either [TomlDecodeError] a)
-> m (Validation [TomlDecodeError] a)
-> m (Either [TomlDecodeError] a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Validation [TomlDecodeError] a -> Either [TomlDecodeError] a
forall e a. Validation e a -> Either e a
validationToEither (m (Validation [TomlDecodeError] a)
-> m (Either [TomlDecodeError] a))
-> (FilePath -> m (Validation [TomlDecodeError] a))
-> FilePath
-> m (Either [TomlDecodeError] a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TomlCodec a -> FilePath -> m (Validation [TomlDecodeError] a)
forall a (m :: * -> *).
MonadIO m =>
TomlCodec a -> FilePath -> m (Validation [TomlDecodeError] a)
decodeFileValidation TomlCodec a
codec
decodeFile :: forall a m . (MonadIO m) => TomlCodec a -> FilePath -> m a
decodeFile :: TomlCodec a -> FilePath -> m a
decodeFile codec :: TomlCodec a
codec filePath :: FilePath
filePath = TomlCodec a -> FilePath -> m (Either [TomlDecodeError] a)
forall a (m :: * -> *).
MonadIO m =>
TomlCodec a -> FilePath -> m (Either [TomlDecodeError] a)
decodeFileEither TomlCodec a
codec FilePath
filePath m (Either [TomlDecodeError] a)
-> (Either [TomlDecodeError] a -> m a) -> m a
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Either [TomlDecodeError] a -> m a
errorWhenLeft
where
errorWhenLeft :: Either [TomlDecodeError] a -> m a
errorWhenLeft :: Either [TomlDecodeError] a -> m a
errorWhenLeft (Left errs :: [TomlDecodeError]
errs) =
IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO
(IO a -> m a) -> IO a -> m a
forall a b. (a -> b) -> a -> b
$ LoadTomlException -> IO a
forall e a. Exception e => e -> IO a
throwIO
(LoadTomlException -> IO a) -> LoadTomlException -> IO a
forall a b. (a -> b) -> a -> b
$ FilePath -> Text -> LoadTomlException
LoadTomlException FilePath
filePath
(Text -> LoadTomlException) -> Text -> LoadTomlException
forall a b. (a -> b) -> a -> b
$ [TomlDecodeError] -> Text
prettyTomlDecodeErrors [TomlDecodeError]
errs
errorWhenLeft (Right pc :: a
pc) = a -> m a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
pc
encode :: TomlCodec a -> a -> Text
encode :: TomlCodec a -> a -> Text
encode codec :: TomlCodec a
codec obj :: a
obj = TOML -> Text
pretty (TOML -> Text) -> TOML -> Text
forall a b. (a -> b) -> a -> b
$ TomlCodec a -> a -> TOML
forall a. TomlCodec a -> a -> TOML
execTomlCodec TomlCodec a
codec a
obj
encodeToFile :: forall a m . (MonadIO m) => TomlCodec a -> FilePath -> a -> m Text
encodeToFile :: TomlCodec a -> FilePath -> a -> m Text
encodeToFile codec :: TomlCodec a
codec filePath :: FilePath
filePath obj :: a
obj = Text
content Text -> m () -> m Text
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (FilePath -> Text -> IO ()
TIO.writeFile FilePath
filePath Text
content)
where
content :: Text
content :: Text
content = TomlCodec a -> a -> Text
forall a. TomlCodec a -> a -> Text
encode TomlCodec a
codec a
obj
runTomlCodec :: TomlCodec a -> TOML -> Validation [TomlDecodeError] a
runTomlCodec :: TomlCodec a -> TOML -> Validation [TomlDecodeError] a
runTomlCodec = TomlCodec a -> TOML -> Validation [TomlDecodeError] a
forall i o. Codec i o -> TomlEnv o
codecRead
execTomlCodec :: TomlCodec a -> a -> TOML
execTomlCodec :: TomlCodec a -> a -> TOML
execTomlCodec codec :: TomlCodec a
codec obj :: a
obj = (Maybe a, TOML) -> TOML
forall a b. (a, b) -> b
snd ((Maybe a, TOML) -> TOML) -> (Maybe a, TOML) -> TOML
forall a b. (a -> b) -> a -> b
$ TomlState a -> TOML -> (Maybe a, TOML)
forall a. TomlState a -> TOML -> (Maybe a, TOML)
unTomlState (TomlCodec a -> a -> TomlState a
forall i o. Codec i o -> i -> TomlState o
codecWrite TomlCodec a
codec a
obj) TOML
forall a. Monoid a => a
mempty