Changed readDataFile to look first in user data directory.
This way all of the pandoc data files can be overridden by user files. git-svn-id: https://pandoc.googlecode.com/svn/trunk@1693 788f1e2b-df1e-0410-8736-df70ead52e1b
This commit is contained in:
parent
9eb435d3c1
commit
fad620c004
2 changed files with 7 additions and 21 deletions
|
@ -118,13 +118,13 @@ import Data.Char ( toLower, toUpper, ord, isLower, isUpper, isAlpha,
|
||||||
import Data.List ( find, isPrefixOf, intercalate )
|
import Data.List ( find, isPrefixOf, intercalate )
|
||||||
import Network.URI ( parseURI, URI (..), isAllowedInURI )
|
import Network.URI ( parseURI, URI (..), isAllowedInURI )
|
||||||
import System.Directory
|
import System.Directory
|
||||||
|
import System.FilePath ( FilePath, (</>) )
|
||||||
import Prelude hiding ( putStrLn, writeFile, readFile, getContents )
|
import Prelude hiding ( putStrLn, writeFile, readFile, getContents )
|
||||||
import System.IO.UTF8
|
import System.IO.UTF8
|
||||||
import Data.Generics
|
import Data.Generics
|
||||||
import qualified Control.Monad.State as S
|
import qualified Control.Monad.State as S
|
||||||
import Control.Monad (join)
|
import Control.Monad (join)
|
||||||
import Paths_pandoc (getDataFileName)
|
import Paths_pandoc (getDataFileName)
|
||||||
|
|
||||||
--
|
--
|
||||||
-- List processing
|
-- List processing
|
||||||
--
|
--
|
||||||
|
@ -1033,6 +1033,9 @@ inDirectory path action = do
|
||||||
setCurrentDirectory oldDir
|
setCurrentDirectory oldDir
|
||||||
return result
|
return result
|
||||||
|
|
||||||
-- | Read file from the Cabal data directory.
|
-- | Read file from user data directory or, if not found there, from
|
||||||
|
-- Cabal data directory. On unix the user data directory is @$HOME/.pandoc@.
|
||||||
readDataFile :: FilePath -> IO String
|
readDataFile :: FilePath -> IO String
|
||||||
readDataFile fname = getDataFileName fname >>= readFile
|
readDataFile fname = do
|
||||||
|
userDir <- getAppUserDataDirectory "pandoc"
|
||||||
|
catch (readFile $ userDir </> fname) (\_ -> getDataFileName fname >>= readFile)
|
||||||
|
|
|
@ -49,11 +49,7 @@ import Text.ParserCombinators.Parsec
|
||||||
import Control.Monad (liftM)
|
import Control.Monad (liftM)
|
||||||
import qualified Control.Exception as E (try, IOException)
|
import qualified Control.Exception as E (try, IOException)
|
||||||
import System.FilePath
|
import System.FilePath
|
||||||
import System.Directory
|
|
||||||
import Prelude hiding (readFile)
|
|
||||||
import System.IO.UTF8 (readFile)
|
|
||||||
import Text.Pandoc.Shared (readDataFile)
|
import Text.Pandoc.Shared (readDataFile)
|
||||||
import Paths_pandoc
|
|
||||||
|
|
||||||
-- | Get the default template, either from the application's user data
|
-- | Get the default template, either from the application's user data
|
||||||
-- directory (~/.pandoc on unix) or from the cabal data directory.
|
-- directory (~/.pandoc on unix) or from the cabal data directory.
|
||||||
|
@ -62,20 +58,7 @@ getDefaultTemplate "native" = return $ Right ""
|
||||||
getDefaultTemplate "odt" = getDefaultTemplate "opendocument"
|
getDefaultTemplate "odt" = getDefaultTemplate "opendocument"
|
||||||
getDefaultTemplate format = do
|
getDefaultTemplate format = do
|
||||||
let format' = takeWhile (/='+') format -- strip off "+lhs" if present
|
let format' = takeWhile (/='+') format -- strip off "+lhs" if present
|
||||||
ut <- getTemplateFromUserDataDirectory format'
|
E.try $ readDataFile $ "templates" </> format' <.> "template"
|
||||||
case ut of
|
|
||||||
Right t -> return $ Right t
|
|
||||||
Left _ -> getTemplateFromCabalDataDirectory format'
|
|
||||||
|
|
||||||
getTemplateFromUserDataDirectory :: String -> IO (Either E.IOException String)
|
|
||||||
getTemplateFromUserDataDirectory format = E.try $ do
|
|
||||||
userDir <- getAppUserDataDirectory "pandoc"
|
|
||||||
let templatePath = userDir </> "templates" </> format <.> "template"
|
|
||||||
readFile templatePath
|
|
||||||
|
|
||||||
getTemplateFromCabalDataDirectory :: String -> IO (Either E.IOException String)
|
|
||||||
getTemplateFromCabalDataDirectory format = E.try $
|
|
||||||
readDataFile $ "templates" </> format <.> "template"
|
|
||||||
|
|
||||||
-- | Renders a template
|
-- | Renders a template
|
||||||
renderTemplate :: [(String,String)] -- ^ Assoc. list of values for variables
|
renderTemplate :: [(String,String)] -- ^ Assoc. list of values for variables
|
||||||
|
|
Loading…
Reference in a new issue