From ec6d0638bef218bb3eddd0c77bc4b90586825f7e Mon Sep 17 00:00:00 2001
From: Jesse Rosenthal <jrosenthal@jhu.edu>
Date: Tue, 27 Sep 2016 10:00:04 -0400
Subject: [PATCH] Check `$DATADIR/filters` for filters

If the `$DATADIR/filters` is present, pandoc will look in it for filters
specified without a path, before looking in the $PATH. Note that unlike
executables in $PATH, the `filters` dir may contain scripts that are not
executable (pandoc will try to execute them using an associated
interpreter, if possible).

Note: the `filters` dir has priority over the user path. In order of
preference, pandoc will look in:

  1. a specified full or relative path (executable or non-executable)
  2. `$DATADIR/filters` (executable or non-executable)
  3. `$PATH` (executable only)

This closes #3127.
---
 pandoc.hs | 25 ++++++++++++++++++++-----
 1 file changed, 20 insertions(+), 5 deletions(-)

diff --git a/pandoc.hs b/pandoc.hs
index 97ab4680b..e89e6ef0e 100644
--- a/pandoc.hs
+++ b/pandoc.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE CPP, TupleSections, ScopedTypeVariables #-}
+{-# LANGUAGE CPP, TupleSections, ScopedTypeVariables, PatternGuards #-}
 {-
 Copyright (C) 2006-2016 John MacFarlane <jgm@berkeley.edu>
 
@@ -1042,9 +1042,24 @@ adjustMetadata metadata d = return $ M.foldWithKey setMeta d metadata
 applyTransforms :: [Transform] -> Pandoc -> IO Pandoc
 applyTransforms transforms d = return $ foldr ($) d transforms
 
-applyFilters :: [FilePath] -> [String] -> Pandoc -> IO Pandoc
-applyFilters filters args d =
-  foldrM ($) d $ map (flip externalFilter args) filters
+  -- First we check to see if a filter is a path. If it isn't, we
+  -- check to see whether it's in `userdir/filters`. If not, we leave
+  -- it unchanged.
+expandFilterPath :: Maybe FilePath -> FilePath -> IO FilePath
+expandFilterPath mbDatadir fp
+  | '/' `elem` fp = return fp
+  | Just datadir <- mbDatadir = do
+      let filterPath = (datadir </> "filters" </> fp)
+      filterPathExists <- doesFileExist filterPath
+      if filterPathExists
+        then return filterPath
+        else return fp
+  | otherwise = return fp
+
+applyFilters :: Maybe FilePath -> [FilePath] -> [String] -> Pandoc -> IO Pandoc
+applyFilters mbDatadir filters args d = do
+  expandedFilters <- mapM (expandFilterPath mbDatadir) filters
+  foldrM ($) d $ map (flip externalFilter args) expandedFilters
 
 uppercaseFirstLetter :: String -> String
 uppercaseFirstLetter (c:cs) = toUpper c : cs
@@ -1377,7 +1392,7 @@ convertWithOpts opts args = do
   doc' <- (maybe return (extractMedia media) mbExtractMedia >=>
            adjustMetadata metadata >=>
            applyTransforms transforms >=>
-           applyFilters filters' [format]) doc
+           applyFilters datadir filters' [format]) doc
 
   let writeBinary :: B.ByteString -> IO ()
       writeBinary = B.writeFile (UTF8.encodePath outputFile)