aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Filter/Path.hs
blob: ef2e16b635abf0e67d5942da3e490c5bfd81aa0e (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
{-# LANGUAGE NoImplicitPrelude #-}
{- |
   Module      : Text.Pandoc.Filter.Path
   Copyright   : Copyright (C) 2006-2019 John MacFarlane
   License     : GNU GPL, version 2 or above

   Maintainer  : John MacFarlane <jgm@berkeley@edu>
   Stability   : alpha
   Portability : portable

Expand paths of filters, searching the data directory.
-}
module Text.Pandoc.Filter.Path
  ( expandFilterPath
  ) where

import Prelude
import Text.Pandoc.Class (PandocMonad, fileExists, getUserDataDir)
import System.FilePath ((</>), isRelative)

  -- First we check to see if a filter is found.  If not, and if it's
  -- not an absolute path, we check to see whether it's in `userdir/filters`.
  -- If not, we leave it unchanged.
expandFilterPath :: PandocMonad m => FilePath -> m FilePath
expandFilterPath fp = do
  mbDatadir <- getUserDataDir
  fpExists <- fileExists fp
  if fpExists
     then return fp
     else case mbDatadir of
               Just datadir | isRelative fp -> do
                 let filterPath = datadir </> "filters" </> fp
                 filterPathExists <- fileExists filterPath
                 if filterPathExists
                    then return filterPath
                    else return fp
               _ -> return fp