diff options
Diffstat (limited to 'src/Text/Pandoc/Class')
-rw-r--r-- | src/Text/Pandoc/Class/PandocSandboxed.hs | 79 | ||||
-rw-r--r-- | src/Text/Pandoc/Class/Sandbox.hs | 50 |
2 files changed, 50 insertions, 79 deletions
diff --git a/src/Text/Pandoc/Class/PandocSandboxed.hs b/src/Text/Pandoc/Class/PandocSandboxed.hs deleted file mode 100644 index 61ee1f1c6..000000000 --- a/src/Text/Pandoc/Class/PandocSandboxed.hs +++ /dev/null @@ -1,79 +0,0 @@ -{-# LANGUAGE DeriveFunctor #-} -{-# LANGUAGE GeneralizedNewtypeDeriving #-} -{- | -Module : Text.Pandoc.Class.PandocIO -Copyright : Copyright (C) 2016-2020 Jesse Rosenthal, John MacFarlane -License : GNU GPL, version 2 or above - -Maintainer : Jesse Rosenthal <jrosenthal@jhu.edu> -Stability : alpha -Portability : portable - -This module defines @'PandocIO'@, an IO-based instance of the -@'PandocMonad'@ type class. File, data, and network access all are run -using IO operators. --} -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 -import Control.Monad.Catch (MonadCatch, MonadMask, MonadThrow) - --- | Evaluate a 'PandocIO' operation. -runIO :: PandocIO a -> IO (Either PandocError a) -runIO ma = flip evalStateT def $ runExceptT $ unPandocIO ma - --- | Evaluate a 'PandocIO' operation, handling any errors --- by exiting with an appropriate message and error status. -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 - , MonadCatch - , MonadMask - , MonadThrow - , 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 - readStdinStrict = IO.readStdinStrict - - glob = IO.glob - fileExists = IO.fileExists - getDataFileName = IO.getDataFileName - getModificationTime = IO.getModificationTime - - getCommonState = PandocIO $ lift get - putCommonState = PandocIO . lift . put - - logOutput = IO.logOutput - --- | Extract media from the mediabag into a directory. -extractMedia :: (PandocMonad m, MonadIO m) => FilePath -> Pandoc -> m Pandoc -extractMedia = IO.extractMedia diff --git a/src/Text/Pandoc/Class/Sandbox.hs b/src/Text/Pandoc/Class/Sandbox.hs new file mode 100644 index 000000000..8bc0f1e77 --- /dev/null +++ b/src/Text/Pandoc/Class/Sandbox.hs @@ -0,0 +1,50 @@ +{- | +Module : Text.Pandoc.Class.Sandbox +Copyright : Copyright (C) 2021 John MacFarlane +License : GNU GPL, version 2 or above + +Maintainer : John MacFarlane (<jgm@berkeley.edu>) +Stability : alpha +Portability : portable + +This module provides a way to run PandocMonad actions in a sandbox +(pure context, with no IO allowed and access only to designated files). +-} + +module Text.Pandoc.Class.Sandbox + ( sandbox ) +where + +import Control.Monad (foldM) +import Control.Monad.Except (throwError) +import Control.Monad.IO.Class (MonadIO (liftIO)) +import Text.Pandoc.Class.PandocMonad +import Text.Pandoc.Class.PandocPure +import Text.Pandoc.Class.CommonState (CommonState(..)) +import Text.Pandoc.Logging (messageVerbosity) + +-- | Lift a PandocPure action into any instance of PandocMonad. +-- The main computation is done purely, but CommonState is preserved +-- continuously, and warnings are emitted after the action completes. +-- The parameter is a list of FilePaths which will be added to the +-- ersatz file system and be available for reading. +sandbox :: (PandocMonad m, MonadIO m) => [FilePath] -> PandocPure a -> m a +sandbox files action = do + oldState <- getCommonState + tree <- liftIO $ foldM addToFileTree mempty files + case runPure (do putCommonState oldState + modifyPureState $ \ps -> ps{ stFiles = tree } + result <- action + st <- getCommonState + return (st, result)) of + Left e -> throwError e + Right (st, result) -> do + putCommonState st + let verbosity = stVerbosity st + -- emit warnings, since these are not printed in runPure + let newMessages = reverse $ take + (length (stLog st) - length (stLog oldState)) (stLog st) + mapM_ logOutput + (filter ((<= verbosity) . messageVerbosity) newMessages) + return result + |