Use Text.Pandoc.Templates instead of Text.Pandoc.DefaultTemplates.

(in pandoc.hs and Text.Pandoc)

git-svn-id: https://pandoc.googlecode.com/svn/trunk@1689 788f1e2b-df1e-0410-8736-df70ead52e1b
This commit is contained in:
fiddlosopher 2009-12-31 01:10:57 +00:00
parent 2b1c010599
commit ecbf3388d4
3 changed files with 41 additions and 32 deletions

View file

@ -88,8 +88,8 @@ module Text.Pandoc
, WriterOptions (..) , WriterOptions (..)
, HTMLMathMethod (..) , HTMLMathMethod (..)
, defaultWriterOptions , defaultWriterOptions
-- * Default headers for various output formats -- * Rendering templates and default templates
, module Text.Pandoc.DefaultTemplates , module Text.Pandoc.Templates
-- * Version -- * Version
, pandocVersion , pandocVersion
) where ) where
@ -111,7 +111,7 @@ import Text.Pandoc.Writers.OpenDocument
import Text.Pandoc.Writers.Man import Text.Pandoc.Writers.Man
import Text.Pandoc.Writers.RTF import Text.Pandoc.Writers.RTF
import Text.Pandoc.Writers.MediaWiki import Text.Pandoc.Writers.MediaWiki
import Text.Pandoc.DefaultTemplates import Text.Pandoc.Templates
import Text.Pandoc.Shared import Text.Pandoc.Shared
import Data.Version (showVersion) import Data.Version (showVersion)
import Paths_pandoc (version) import Paths_pandoc (version)

View file

@ -57,11 +57,14 @@ 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.
getDefaultTemplate :: String -> IO (Either E.IOException String) getDefaultTemplate :: String -> IO (Either E.IOException String)
getDefaultTemplate "native" = return $ Right ""
getDefaultTemplate "odt" = getDefaultTemplate "opendocument"
getDefaultTemplate format = do getDefaultTemplate format = do
ut <- getTemplateFromUserDataDirectory format let format' = takeWhile (/='+') format -- strip off "+lhs" if present
ut <- getTemplateFromUserDataDirectory format'
case ut of case ut of
Right t -> return $ Right t Right t -> return $ Right t
Left _ -> getTemplateFromCabalDataDirectory format Left _ -> getTemplateFromCabalDataDirectory format'
getTemplateFromUserDataDirectory :: String -> IO (Either E.IOException String) getTemplateFromUserDataDirectory :: String -> IO (Either E.IOException String)
getTemplateFromUserDataDirectory format = E.try $ do getTemplateFromUserDataDirectory format = E.try $ do

View file

@ -32,6 +32,7 @@ writers.
module Main where module Main where
import Text.Pandoc import Text.Pandoc
import Text.Pandoc.ODT import Text.Pandoc.ODT
import Text.Pandoc.Templates (getDefaultTemplate)
import Text.Pandoc.Shared ( HTMLMathMethod (..), tabFilter, ObfuscationMethod (..) ) import Text.Pandoc.Shared ( HTMLMathMethod (..), tabFilter, ObfuscationMethod (..) )
#ifdef _HIGHLIGHTING #ifdef _HIGHLIGHTING
import Text.Pandoc.Highlighting ( languages ) import Text.Pandoc.Highlighting ( languages )
@ -96,26 +97,26 @@ readers = [("native" , readPandoc)
readPandoc :: ParserState -> String -> Pandoc readPandoc :: ParserState -> String -> Pandoc
readPandoc _ = read readPandoc _ = read
-- | Association list of formats and pairs of writers and default headers. -- | Association list of formats and writers.
writers :: [ ( String, ( WriterOptions -> Pandoc -> String, String ) ) ] writers :: [ ( String, WriterOptions -> Pandoc -> String ) ]
writers = [("native" , (writeDoc, "")) writers = [("native" , writeDoc)
,("html" , (writeHtmlString, "")) ,("html" , writeHtmlString)
,("html+lhs" , (writeHtmlString, "")) ,("html+lhs" , writeHtmlString)
,("s5" , (writeS5String, defaultS5Template)) ,("s5" , writeS5String)
,("docbook" , (writeDocbook, defaultDocbookTemplate)) ,("docbook" , writeDocbook)
,("opendocument" , (writeOpenDocument, defaultOpenDocumentTemplate)) ,("opendocument" , writeOpenDocument)
,("odt" , (writeOpenDocument, defaultOpenDocumentTemplate)) ,("odt" , writeOpenDocument)
,("latex" , (writeLaTeX, defaultLaTeXTemplate)) ,("latex" , writeLaTeX)
,("latex+lhs" , (writeLaTeX, defaultLaTeXTemplate)) ,("latex+lhs" , writeLaTeX)
,("context" , (writeConTeXt, defaultConTeXtTemplate)) ,("context" , writeConTeXt)
,("texinfo" , (writeTexinfo, "")) ,("texinfo" , writeTexinfo)
,("man" , (writeMan, "")) ,("man" , writeMan)
,("markdown" , (writeMarkdown, "")) ,("markdown" , writeMarkdown)
,("markdown+lhs" , (writeMarkdown, "")) ,("markdown+lhs" , writeMarkdown)
,("rst" , (writeRST, "")) ,("rst" , writeRST)
,("rst+lhs" , (writeRST, "")) ,("rst+lhs" , writeRST)
,("mediawiki" , (writeMediaWiki, "")) ,("mediawiki" , writeMediaWiki)
,("rtf" , (writeRTF, defaultRTFTemplate)) ,("rtf" , writeRTF)
] ]
isNonTextOutput :: String -> Bool isNonTextOutput :: String -> Bool
@ -427,10 +428,10 @@ options =
, Option "D" ["print-default-template"] , Option "D" ["print-default-template"]
(ReqArg (ReqArg
(\arg _ -> do (\arg _ -> do
let template = case (lookup arg writers) of templ <- getDefaultTemplate arg
Just (_, h) -> h case templ of
Nothing -> error ("Unknown reader: " ++ arg) Right t -> hPutStr stdout t
hPutStr stdout template Left e -> error $ show e
exitWith ExitSuccess) exitWith ExitSuccess)
"FORMAT") "FORMAT")
"" -- "Print default template for FORMAT" "" -- "Print default template for FORMAT"
@ -610,10 +611,15 @@ main = do
Just r -> return r Just r -> return r
Nothing -> error ("Unknown reader: " ++ readerName') Nothing -> error ("Unknown reader: " ++ readerName')
(writer, defaultTemplate) <- case (lookup writerName' writers) of writer <- case (lookup writerName' writers) of
Just (w,h) -> return (w, h) Just r -> return r
Nothing -> error ("Unknown writer: " ++ writerName') Nothing -> error ("Unknown writer: " ++ writerName')
templ <- getDefaultTemplate writerName'
let defaultTemplate = case templ of
Right t -> t
Left e -> error (show e)
environment <- getEnvironment environment <- getEnvironment
let columns = case lookup "COLUMNS" environment of let columns = case lookup "COLUMNS" environment of
Just cols -> read cols Just cols -> read cols