{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Text.Pandoc.Class.PandocIO
( PandocIO(..)
, runIO
, runIOorExplode
, extractMedia
) where
import Control.Monad.Except (ExceptT, MonadError, runExceptT)
import Control.Monad.IO.Class (MonadIO)
import Control.Monad.State (StateT, evalStateT, lift, get, put)
import Data.Default (Default (def))
import Text.Pandoc.Class.CommonState (CommonState (..))
import Text.Pandoc.Class.PandocMonad
import Text.Pandoc.Definition
import Text.Pandoc.Error
import qualified Text.Pandoc.Class.IO as IO
runIO :: PandocIO a -> IO (Either PandocError a)
runIO ma = flip evalStateT def $ runExceptT $ unPandocIO ma
runIOorExplode :: PandocIO a -> IO a
runIOorExplode ma = runIO ma >>= handleError
newtype PandocIO a = PandocIO {
unPandocIO :: ExceptT PandocError (StateT CommonState IO) a
} deriving ( MonadIO
, Functor
, Applicative
, Monad
, MonadError PandocError
)
instance PandocMonad PandocIO where
lookupEnv = IO.lookupEnv
getCurrentTime = IO.getCurrentTime
getCurrentTimeZone = IO.getCurrentTimeZone
newStdGen = IO.newStdGen
newUniqueHash = IO.newUniqueHash
openURL = IO.openURL
readFileLazy = IO.readFileLazy
readFileStrict = IO.readFileStrict
glob = IO.glob
fileExists = IO.fileExists
getDataFileName = IO.getDataFileName
getModificationTime = IO.getModificationTime
getCommonState = PandocIO $ lift get
putCommonState = PandocIO . lift . put
logOutput = IO.logOutput
extractMedia :: FilePath -> Pandoc -> PandocIO Pandoc
extractMedia = IO.extractMedia