blob: f5c1a4f763fa29d674eec2170a1f2b5d198abdb8 (
plain)
| 1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
 | {-# LANGUAGE CPP               #-}
{-# LANGUAGE DeriveGeneric     #-}
{-# LANGUAGE TemplateHaskell   #-}
{-# LANGUAGE OverloadedStrings #-}
{- |
   Module      : Text.Pandoc.Filter
   Copyright   : Copyright (C) 2006-2020 John MacFarlane
   License     : GNU GPL, version 2 or above
   Maintainer  : John MacFarlane <jgm@berkeley@edu>
   Stability   : alpha
   Portability : portable
Programmatically modifications of pandoc documents.
-}
module Text.Pandoc.Filter
  ( Filter (..)
  , applyFilters
  ) where
import System.CPUTime (getCPUTime)
import Data.Aeson.TH (deriveJSON, defaultOptions)
import GHC.Generics (Generic)
import Text.Pandoc.Class.PandocIO (PandocIO)
import Text.Pandoc.Class.PandocMonad (report, getVerbosity)
import Text.Pandoc.Definition (Pandoc)
import Text.Pandoc.Options (ReaderOptions)
import Text.Pandoc.Logging
import Text.Pandoc.Citeproc (processCitations)
import qualified Text.Pandoc.Filter.JSON as JSONFilter
import qualified Text.Pandoc.Filter.Lua as LuaFilter
import qualified Text.Pandoc.Filter.Path as Path
import Data.YAML
import qualified Data.Text as T
import System.FilePath (takeExtension)
import Control.Applicative ((<|>))
import Control.Monad.Trans (MonadIO (liftIO))
import Control.Monad (foldM, when)
-- | Type of filter and path to filter file.
data Filter = LuaFilter FilePath
            | JSONFilter FilePath
            | CiteprocFilter -- built-in citeproc
            deriving (Show, Generic)
instance FromYAML Filter where
 parseYAML node =
  (withMap "Filter" $ \m -> do
    ty <- m .: "type"
    fp <- m .: "path"
    case ty of
      "citeproc" -> return CiteprocFilter
      "lua"  -> return $ LuaFilter $ T.unpack fp
      "json" -> return $ JSONFilter $ T.unpack fp
      _      -> fail $ "Unknown filter type " ++ show (ty :: T.Text)) node
  <|>
  (withStr "Filter" $ \t -> do
    let fp = T.unpack t
    if fp == "citeproc"
       then return CiteprocFilter
       else return $
         case takeExtension fp of
           ".lua"  -> LuaFilter fp
           _       -> JSONFilter fp) node
-- | Modify the given document using a filter.
applyFilters :: ReaderOptions
             -> [Filter]
             -> [String]
             -> Pandoc
             -> PandocIO Pandoc
applyFilters ropts filters args d = do
  expandedFilters <- mapM expandFilterPath filters
  foldM applyFilter d expandedFilters
 where
  applyFilter doc (JSONFilter f) =
    withMessages f $ JSONFilter.apply ropts args f doc
  applyFilter doc (LuaFilter f)  =
    withMessages f $ LuaFilter.apply ropts args f doc
  applyFilter doc CiteprocFilter =
    processCitations doc
  withMessages f action = do
    verbosity <- getVerbosity
    when (verbosity == INFO) $ report $ RunningFilter f
    starttime <- liftIO getCPUTime
    res <- action
    endtime <- liftIO getCPUTime
    when (verbosity == INFO) $ report $ FilterCompleted f $ toMilliseconds $ endtime - starttime
    return res
  toMilliseconds picoseconds = picoseconds `div` 1000000000
-- | 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
expandFilterPath CiteprocFilter = return CiteprocFilter
$(deriveJSON defaultOptions ''Filter)
 |