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:
parent
2b1c010599
commit
ecbf3388d4
3 changed files with 41 additions and 32 deletions
|
@ -88,8 +88,8 @@ module Text.Pandoc
|
|||
, WriterOptions (..)
|
||||
, HTMLMathMethod (..)
|
||||
, defaultWriterOptions
|
||||
-- * Default headers for various output formats
|
||||
, module Text.Pandoc.DefaultTemplates
|
||||
-- * Rendering templates and default templates
|
||||
, module Text.Pandoc.Templates
|
||||
-- * Version
|
||||
, pandocVersion
|
||||
) where
|
||||
|
@ -111,7 +111,7 @@ import Text.Pandoc.Writers.OpenDocument
|
|||
import Text.Pandoc.Writers.Man
|
||||
import Text.Pandoc.Writers.RTF
|
||||
import Text.Pandoc.Writers.MediaWiki
|
||||
import Text.Pandoc.DefaultTemplates
|
||||
import Text.Pandoc.Templates
|
||||
import Text.Pandoc.Shared
|
||||
import Data.Version (showVersion)
|
||||
import Paths_pandoc (version)
|
||||
|
|
|
@ -57,11 +57,14 @@ import Paths_pandoc
|
|||
-- | Get the default template, either from the application's user data
|
||||
-- directory (~/.pandoc on unix) or from the cabal data directory.
|
||||
getDefaultTemplate :: String -> IO (Either E.IOException String)
|
||||
getDefaultTemplate "native" = return $ Right ""
|
||||
getDefaultTemplate "odt" = getDefaultTemplate "opendocument"
|
||||
getDefaultTemplate format = do
|
||||
ut <- getTemplateFromUserDataDirectory format
|
||||
let format' = takeWhile (/='+') format -- strip off "+lhs" if present
|
||||
ut <- getTemplateFromUserDataDirectory format'
|
||||
case ut of
|
||||
Right t -> return $ Right t
|
||||
Left _ -> getTemplateFromCabalDataDirectory format
|
||||
Left _ -> getTemplateFromCabalDataDirectory format'
|
||||
|
||||
getTemplateFromUserDataDirectory :: String -> IO (Either E.IOException String)
|
||||
getTemplateFromUserDataDirectory format = E.try $ do
|
||||
|
|
|
@ -32,6 +32,7 @@ writers.
|
|||
module Main where
|
||||
import Text.Pandoc
|
||||
import Text.Pandoc.ODT
|
||||
import Text.Pandoc.Templates (getDefaultTemplate)
|
||||
import Text.Pandoc.Shared ( HTMLMathMethod (..), tabFilter, ObfuscationMethod (..) )
|
||||
#ifdef _HIGHLIGHTING
|
||||
import Text.Pandoc.Highlighting ( languages )
|
||||
|
@ -96,26 +97,26 @@ readers = [("native" , readPandoc)
|
|||
readPandoc :: ParserState -> String -> Pandoc
|
||||
readPandoc _ = read
|
||||
|
||||
-- | Association list of formats and pairs of writers and default headers.
|
||||
writers :: [ ( String, ( WriterOptions -> Pandoc -> String, String ) ) ]
|
||||
writers = [("native" , (writeDoc, ""))
|
||||
,("html" , (writeHtmlString, ""))
|
||||
,("html+lhs" , (writeHtmlString, ""))
|
||||
,("s5" , (writeS5String, defaultS5Template))
|
||||
,("docbook" , (writeDocbook, defaultDocbookTemplate))
|
||||
,("opendocument" , (writeOpenDocument, defaultOpenDocumentTemplate))
|
||||
,("odt" , (writeOpenDocument, defaultOpenDocumentTemplate))
|
||||
,("latex" , (writeLaTeX, defaultLaTeXTemplate))
|
||||
,("latex+lhs" , (writeLaTeX, defaultLaTeXTemplate))
|
||||
,("context" , (writeConTeXt, defaultConTeXtTemplate))
|
||||
,("texinfo" , (writeTexinfo, ""))
|
||||
,("man" , (writeMan, ""))
|
||||
,("markdown" , (writeMarkdown, ""))
|
||||
,("markdown+lhs" , (writeMarkdown, ""))
|
||||
,("rst" , (writeRST, ""))
|
||||
,("rst+lhs" , (writeRST, ""))
|
||||
,("mediawiki" , (writeMediaWiki, ""))
|
||||
,("rtf" , (writeRTF, defaultRTFTemplate))
|
||||
-- | Association list of formats and writers.
|
||||
writers :: [ ( String, WriterOptions -> Pandoc -> String ) ]
|
||||
writers = [("native" , writeDoc)
|
||||
,("html" , writeHtmlString)
|
||||
,("html+lhs" , writeHtmlString)
|
||||
,("s5" , writeS5String)
|
||||
,("docbook" , writeDocbook)
|
||||
,("opendocument" , writeOpenDocument)
|
||||
,("odt" , writeOpenDocument)
|
||||
,("latex" , writeLaTeX)
|
||||
,("latex+lhs" , writeLaTeX)
|
||||
,("context" , writeConTeXt)
|
||||
,("texinfo" , writeTexinfo)
|
||||
,("man" , writeMan)
|
||||
,("markdown" , writeMarkdown)
|
||||
,("markdown+lhs" , writeMarkdown)
|
||||
,("rst" , writeRST)
|
||||
,("rst+lhs" , writeRST)
|
||||
,("mediawiki" , writeMediaWiki)
|
||||
,("rtf" , writeRTF)
|
||||
]
|
||||
|
||||
isNonTextOutput :: String -> Bool
|
||||
|
@ -427,10 +428,10 @@ options =
|
|||
, Option "D" ["print-default-template"]
|
||||
(ReqArg
|
||||
(\arg _ -> do
|
||||
let template = case (lookup arg writers) of
|
||||
Just (_, h) -> h
|
||||
Nothing -> error ("Unknown reader: " ++ arg)
|
||||
hPutStr stdout template
|
||||
templ <- getDefaultTemplate arg
|
||||
case templ of
|
||||
Right t -> hPutStr stdout t
|
||||
Left e -> error $ show e
|
||||
exitWith ExitSuccess)
|
||||
"FORMAT")
|
||||
"" -- "Print default template for FORMAT"
|
||||
|
@ -610,9 +611,14 @@ main = do
|
|||
Just r -> return r
|
||||
Nothing -> error ("Unknown reader: " ++ readerName')
|
||||
|
||||
(writer, defaultTemplate) <- case (lookup writerName' writers) of
|
||||
Just (w,h) -> return (w, h)
|
||||
Nothing -> error ("Unknown writer: " ++ writerName')
|
||||
writer <- case (lookup writerName' writers) of
|
||||
Just r -> return r
|
||||
Nothing -> error ("Unknown writer: " ++ writerName')
|
||||
|
||||
templ <- getDefaultTemplate writerName'
|
||||
let defaultTemplate = case templ of
|
||||
Right t -> t
|
||||
Left e -> error (show e)
|
||||
|
||||
environment <- getEnvironment
|
||||
let columns = case lookup "COLUMNS" environment of
|
||||
|
|
Loading…
Reference in a new issue