T.P.Filter: centralize filter path expansion
This commit is contained in:
parent
f612421307
commit
8ef995cfc0
3 changed files with 16 additions and 12 deletions
|
@ -42,20 +42,29 @@ import Text.Pandoc.Definition (Pandoc)
|
|||
import Text.Pandoc.Options (ReaderOptions)
|
||||
import qualified Text.Pandoc.Filter.JSON as JSONFilter
|
||||
import qualified Text.Pandoc.Filter.Lua as LuaFilter
|
||||
import qualified Text.Pandoc.Filter.Path as Path
|
||||
|
||||
-- | Type of filter and path to filter file.
|
||||
data Filter = LuaFilter FilePath
|
||||
| JSONFilter FilePath
|
||||
deriving (Show)
|
||||
|
||||
-- | Modify the given document using a filter.
|
||||
applyFilters :: ReaderOptions
|
||||
-> [Filter]
|
||||
-> [String]
|
||||
-> Pandoc
|
||||
-> PandocIO Pandoc
|
||||
applyFilters ropts filters args d =
|
||||
foldrM ($) d $ map applyFilter filters
|
||||
applyFilters ropts filters args d = do
|
||||
expandedFilters <- mapM expandFilterPath filters
|
||||
foldrM ($) d $ map applyFilter expandedFilters
|
||||
where
|
||||
applyFilter (JSONFilter f) = JSONFilter.apply ropts args f
|
||||
applyFilter (LuaFilter f) = LuaFilter.apply ropts args f
|
||||
|
||||
-- | Expand paths of filters, searching the data directory.
|
||||
expandFilterPath :: Filter -> PandocIO Filter
|
||||
expandFilterPath (LuaFilter fp) = LuaFilter <$> Path.expandFilterPath fp
|
||||
expandFilterPath (JSONFilter fp) = JSONFilter <$> Path.expandFilterPath fp
|
||||
|
||||
$(deriveJSON defaultOptions ''Filter)
|
||||
|
|
|
@ -44,7 +44,6 @@ import System.FilePath ((</>), takeExtension)
|
|||
import Text.Pandoc.Class (PandocIO)
|
||||
import Text.Pandoc.Error (PandocError (PandocFilterError))
|
||||
import Text.Pandoc.Definition (Pandoc)
|
||||
import Text.Pandoc.Filter.Path (expandFilterPath)
|
||||
import Text.Pandoc.Options (ReaderOptions)
|
||||
import Text.Pandoc.Process (pipeProcess)
|
||||
import Text.Pandoc.Shared (pandocVersion)
|
||||
|
@ -56,9 +55,7 @@ apply :: ReaderOptions
|
|||
-> FilePath
|
||||
-> Pandoc
|
||||
-> PandocIO Pandoc
|
||||
apply ropts args f d = do
|
||||
f' <- expandFilterPath f
|
||||
liftIO $ externalFilter ropts f' args d
|
||||
apply ropts args f = liftIO . externalFilter ropts f args
|
||||
|
||||
externalFilter :: MonadIO m
|
||||
=> ReaderOptions -> FilePath -> [String] -> Pandoc -> m Pandoc
|
||||
|
|
|
@ -36,7 +36,6 @@ import Control.Monad ((>=>))
|
|||
import Text.Pandoc.Class (PandocIO)
|
||||
import Text.Pandoc.Definition (Pandoc)
|
||||
import Text.Pandoc.Error (PandocError (PandocFilterError))
|
||||
import Text.Pandoc.Filter.Path (expandFilterPath)
|
||||
import Text.Pandoc.Lua (Global (..), LuaException (..),
|
||||
runLua, runFilterFile, setGlobals)
|
||||
import Text.Pandoc.Options (ReaderOptions)
|
||||
|
@ -49,17 +48,16 @@ apply :: ReaderOptions
|
|||
-> FilePath
|
||||
-> Pandoc
|
||||
-> PandocIO Pandoc
|
||||
apply ropts args f doc = do
|
||||
filterPath <- expandFilterPath f
|
||||
apply ropts args fp doc = do
|
||||
let format = case args of
|
||||
(x:_) -> x
|
||||
_ -> error "Format not supplied for Lua filter"
|
||||
runLua >=> forceResult filterPath $ do
|
||||
runLua >=> forceResult fp $ do
|
||||
setGlobals [ FORMAT format
|
||||
, PANDOC_READER_OPTIONS ropts
|
||||
, PANDOC_SCRIPT_FILE filterPath
|
||||
, PANDOC_SCRIPT_FILE fp
|
||||
]
|
||||
runFilterFile filterPath doc
|
||||
runFilterFile fp doc
|
||||
|
||||
forceResult :: FilePath -> Either LuaException Pandoc -> PandocIO Pandoc
|
||||
forceResult fp eitherResult = case eitherResult of
|
||||
|
|
Loading…
Add table
Reference in a new issue