{- |
   Module      : Text.Pandoc.Filter.Path
   Copyright   : Copyright (C) 2006-2020 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 Text.Pandoc.Class.PandocMonad (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 :: FilePath -> m FilePath
expandFilterPath FilePath
fp = do
  Maybe FilePath
mbDatadir <- m (Maybe FilePath)
forall (m :: * -> *). PandocMonad m => m (Maybe FilePath)
getUserDataDir
  Bool
fpExists <- FilePath -> m Bool
forall (m :: * -> *). PandocMonad m => FilePath -> m Bool
fileExists FilePath
fp
  if Bool
fpExists
     then FilePath -> m FilePath
forall (m :: * -> *) a. Monad m => a -> m a
return FilePath
fp
     else case Maybe FilePath
mbDatadir of
               Just FilePath
datadir | FilePath -> Bool
isRelative FilePath
fp -> do
                 let filterPath :: FilePath
filterPath = FilePath
datadir FilePath -> FilePath -> FilePath
</> FilePath
"filters" FilePath -> FilePath -> FilePath
</> FilePath
fp
                 Bool
filterPathExists <- FilePath -> m Bool
forall (m :: * -> *). PandocMonad m => FilePath -> m Bool
fileExists FilePath
filterPath
                 if Bool
filterPathExists
                    then FilePath -> m FilePath
forall (m :: * -> *) a. Monad m => a -> m a
return FilePath
filterPath
                    else FilePath -> m FilePath
forall (m :: * -> *) a. Monad m => a -> m a
return FilePath
fp
               Maybe FilePath
_ -> FilePath -> m FilePath
forall (m :: * -> *) a. Monad m => a -> m a
return FilePath
fp