Updated texinfo writer to use new templates.
git-svn-id: https://pandoc.googlecode.com/svn/trunk@1735 788f1e2b-df1e-0410-8736-df70ead52e1b
This commit is contained in:
parent
cc6294c4f2
commit
3f53d6f270
3 changed files with 85 additions and 124 deletions
|
@ -30,17 +30,19 @@ Conversion of 'Pandoc' format into Texinfo.
|
||||||
module Text.Pandoc.Writers.Texinfo ( writeTexinfo ) where
|
module Text.Pandoc.Writers.Texinfo ( writeTexinfo ) where
|
||||||
import Text.Pandoc.Definition
|
import Text.Pandoc.Definition
|
||||||
import Text.Pandoc.Shared
|
import Text.Pandoc.Shared
|
||||||
|
import Text.Pandoc.Templates (renderTemplate)
|
||||||
import Text.Pandoc.Readers.TeXMath
|
import Text.Pandoc.Readers.TeXMath
|
||||||
import Text.Printf ( printf )
|
import Text.Printf ( printf )
|
||||||
import Data.List ( isSuffixOf, transpose, maximumBy )
|
import Data.List ( isSuffixOf, transpose, maximumBy )
|
||||||
import Data.Ord ( comparing )
|
import Data.Ord ( comparing )
|
||||||
import Data.Char ( chr, ord )
|
import Data.Char ( chr, ord )
|
||||||
import qualified Data.Set as S
|
|
||||||
import Control.Monad.State
|
import Control.Monad.State
|
||||||
import Text.PrettyPrint.HughesPJ hiding ( Str )
|
import Text.PrettyPrint.HughesPJ hiding ( Str )
|
||||||
|
|
||||||
data WriterState =
|
data WriterState =
|
||||||
WriterState { stIncludes :: S.Set String -- strings to include in header
|
WriterState { stStrikeout :: Bool -- document contains strikeout
|
||||||
|
, stSuperscript :: Bool -- document contains superscript
|
||||||
|
, stSubscript :: Bool -- document contains subscript
|
||||||
}
|
}
|
||||||
|
|
||||||
{- TODO:
|
{- TODO:
|
||||||
|
@ -48,81 +50,45 @@ data WriterState =
|
||||||
- generated .texi files don't work when run through texi2dvi
|
- generated .texi files don't work when run through texi2dvi
|
||||||
-}
|
-}
|
||||||
|
|
||||||
-- | Add line to header.
|
|
||||||
addToHeader :: String -> State WriterState ()
|
|
||||||
addToHeader str = do
|
|
||||||
st <- get
|
|
||||||
let includes = stIncludes st
|
|
||||||
put st {stIncludes = S.insert str includes}
|
|
||||||
|
|
||||||
-- | Convert Pandoc to Texinfo.
|
-- | Convert Pandoc to Texinfo.
|
||||||
writeTexinfo :: WriterOptions -> Pandoc -> String
|
writeTexinfo :: WriterOptions -> Pandoc -> String
|
||||||
writeTexinfo options document =
|
writeTexinfo options document =
|
||||||
render $ evalState (pandocToTexinfo options $ wrapTop document) $
|
evalState (pandocToTexinfo options $ wrapTop document) $
|
||||||
WriterState { stIncludes = S.empty }
|
WriterState { stStrikeout = False, stSuperscript = False, stSubscript = False }
|
||||||
|
|
||||||
-- | Add a "Top" node around the document, needed by Texinfo.
|
-- | Add a "Top" node around the document, needed by Texinfo.
|
||||||
wrapTop :: Pandoc -> Pandoc
|
wrapTop :: Pandoc -> Pandoc
|
||||||
wrapTop (Pandoc (Meta title authors date) blocks) =
|
wrapTop (Pandoc (Meta title authors date) blocks) =
|
||||||
Pandoc (Meta title authors date) (Header 0 title : blocks)
|
Pandoc (Meta title authors date) (Header 0 title : blocks)
|
||||||
|
|
||||||
pandocToTexinfo :: WriterOptions -> Pandoc -> State WriterState Doc
|
pandocToTexinfo :: WriterOptions -> Pandoc -> State WriterState String
|
||||||
pandocToTexinfo options (Pandoc meta blocks) = do
|
pandocToTexinfo options (Pandoc (Meta title authors date) blocks) = do
|
||||||
return empty -- TODO
|
titleText <- inlineListToTexinfo title
|
||||||
-- main <- blockListToTexinfo blocks
|
authorsText <- mapM inlineListToTexinfo authors
|
||||||
-- head' <- if writerStandalone options
|
dateText <- inlineListToTexinfo date
|
||||||
-- then texinfoHeader options meta
|
let titlePage = not $ all null $ title : date : authors
|
||||||
-- else return empty
|
main <- blockListToTexinfo blocks
|
||||||
-- let before = if null (writerIncludeBefore options)
|
st <- get
|
||||||
-- then empty
|
let before = if null (writerIncludeBefore options)
|
||||||
-- else text (writerIncludeBefore options)
|
then empty
|
||||||
-- let after = if null (writerIncludeAfter options)
|
else text (writerIncludeBefore options)
|
||||||
-- then empty
|
let after = if null (writerIncludeAfter options)
|
||||||
-- else text (writerIncludeAfter options)
|
then empty
|
||||||
-- let body = before $$ main $$ after
|
else text (writerIncludeAfter options)
|
||||||
-- -- XXX toc untested
|
let body = render $ before $$ main $$ after
|
||||||
-- let toc = if writerTableOfContents options
|
let context = writerVariables options ++
|
||||||
-- then text "@contents"
|
[ ("body", body)
|
||||||
-- else empty
|
, ("title", render titleText)
|
||||||
-- let foot = if writerStandalone options
|
, ("date", render dateText) ] ++
|
||||||
-- then text "@bye"
|
[ ("toc", "yes") | writerTableOfContents options ] ++
|
||||||
-- else empty
|
[ ("titlepage", "yes") | titlePage ] ++
|
||||||
-- return $ head' $$ toc $$ body $$ foot
|
[ ("subscript", "yes") | stSubscript st ] ++
|
||||||
|
[ ("superscript", "yes") | stSuperscript st ] ++
|
||||||
-- | Insert bibliographic information into Texinfo header.
|
[ ("strikeout", "yes") | stStrikeout st ] ++
|
||||||
texinfoHeader :: WriterOptions -- ^ Options, including Texinfo header
|
[ ("author", render a) | a <- authorsText ]
|
||||||
-> Meta -- ^ Meta with bibliographic information
|
if writerStandalone options
|
||||||
-> State WriterState Doc
|
then return $ renderTemplate context $ writerTemplate options
|
||||||
texinfoHeader options (Meta title authors date) = do
|
else return body
|
||||||
return empty -- TODO
|
|
||||||
-- titletext <- if null title
|
|
||||||
-- then return empty
|
|
||||||
-- else do
|
|
||||||
-- t <- inlineListToTexinfo title
|
|
||||||
-- return $ text "@title " <> t
|
|
||||||
-- headerIncludes <- get >>= return . S.toList . stIncludes
|
|
||||||
-- let extras = text $ unlines headerIncludes
|
|
||||||
-- let authorstext = map makeAuthor authors
|
|
||||||
-- let datetext = if date == ""
|
|
||||||
-- then empty
|
|
||||||
-- else text $ stringToTexinfo date
|
|
||||||
--
|
|
||||||
-- let baseHeader = case writerHeader options of
|
|
||||||
-- "" -> empty
|
|
||||||
-- x -> text x
|
|
||||||
-- let header = text "@documentencoding utf-8" $$ baseHeader $$ extras
|
|
||||||
-- return $ text "\\input texinfo" $$
|
|
||||||
-- header $$
|
|
||||||
-- text "@ifnottex" $$
|
|
||||||
-- text "@paragraphindent 0" $$
|
|
||||||
-- text "@end ifnottex" $$
|
|
||||||
-- text "@titlepage" $$
|
|
||||||
-- titletext $$ vcat authorstext $$
|
|
||||||
-- datetext $$
|
|
||||||
-- text "@end titlepage"
|
|
||||||
|
|
||||||
makeAuthor :: String -> Doc
|
|
||||||
makeAuthor author = text $ "@author " ++ (stringToTexinfo author)
|
|
||||||
|
|
||||||
-- | Escape things as needed for Texinfo.
|
-- | Escape things as needed for Texinfo.
|
||||||
stringToTexinfo :: String -> String
|
stringToTexinfo :: String -> String
|
||||||
|
@ -397,33 +363,17 @@ inlineToTexinfo (Strong lst) =
|
||||||
inlineListToTexinfo lst >>= return . inCmd "strong"
|
inlineListToTexinfo lst >>= return . inCmd "strong"
|
||||||
|
|
||||||
inlineToTexinfo (Strikeout lst) = do
|
inlineToTexinfo (Strikeout lst) = do
|
||||||
addToHeader $ "@macro textstrikeout{text}\n" ++
|
modify $ \st -> st{ stStrikeout = True }
|
||||||
"~~\\text\\~~\n" ++
|
|
||||||
"@end macro\n"
|
|
||||||
contents <- inlineListToTexinfo lst
|
contents <- inlineListToTexinfo lst
|
||||||
return $ text "@textstrikeout{" <> contents <> text "}"
|
return $ text "@textstrikeout{" <> contents <> text "}"
|
||||||
|
|
||||||
inlineToTexinfo (Superscript lst) = do
|
inlineToTexinfo (Superscript lst) = do
|
||||||
addToHeader $ "@macro textsuperscript{text}\n" ++
|
modify $ \st -> st{ stSuperscript = True }
|
||||||
"@iftex\n" ++
|
|
||||||
"@textsuperscript{\\text\\}\n" ++
|
|
||||||
"@end iftex\n" ++
|
|
||||||
"@ifnottex\n" ++
|
|
||||||
"^@{\\text\\@}\n" ++
|
|
||||||
"@end ifnottex\n" ++
|
|
||||||
"@end macro\n"
|
|
||||||
contents <- inlineListToTexinfo lst
|
contents <- inlineListToTexinfo lst
|
||||||
return $ text "@textsuperscript{" <> contents <> char '}'
|
return $ text "@textsuperscript{" <> contents <> char '}'
|
||||||
|
|
||||||
inlineToTexinfo (Subscript lst) = do
|
inlineToTexinfo (Subscript lst) = do
|
||||||
addToHeader $ "@macro textsubscript{text}\n" ++
|
modify $ \st -> st{ stSubscript = True }
|
||||||
"@iftex\n" ++
|
|
||||||
"@textsubscript{\\text\\}\n" ++
|
|
||||||
"@end iftex\n" ++
|
|
||||||
"@ifnottex\n" ++
|
|
||||||
"_@{\\text\\@}\n" ++
|
|
||||||
"@end ifnottex\n" ++
|
|
||||||
"@end macro\n"
|
|
||||||
contents <- inlineListToTexinfo lst
|
contents <- inlineListToTexinfo lst
|
||||||
return $ text "@textsubscript{" <> contents <> char '}'
|
return $ text "@textsubscript{" <> contents <> char '}'
|
||||||
|
|
||||||
|
|
|
@ -1,51 +1,60 @@
|
||||||
|
$if(legacy-header)$
|
||||||
|
$legacy-header$
|
||||||
|
$else$
|
||||||
\input texinfo
|
\input texinfo
|
||||||
@documentencoding utf-8
|
@documentencoding utf-8
|
||||||
|
$endif$
|
||||||
|
$for(header-includes)$
|
||||||
$header-includes$
|
$header-includes$
|
||||||
|
$endfor$
|
||||||
|
|
||||||
|
$if(strikeout)$
|
||||||
|
@macro textstrikeout{text}
|
||||||
|
~~\text\~~
|
||||||
|
@end macro
|
||||||
|
|
||||||
|
$endif$
|
||||||
|
$if(subscript)$
|
||||||
|
@macro textsubscript{text}
|
||||||
|
@iftex
|
||||||
|
@textsubscript{\text\}
|
||||||
|
@end iftex
|
||||||
|
@ifnottex
|
||||||
|
_@{\text\@}
|
||||||
|
@end ifnottex
|
||||||
|
@end macro
|
||||||
|
|
||||||
|
$endif$
|
||||||
|
$if(superscript)$
|
||||||
|
@macro textsuperscript{text}
|
||||||
|
@iftex
|
||||||
|
@textsuperscript{\text\}
|
||||||
|
@end iftex
|
||||||
|
@ifnottex
|
||||||
|
^@{\text\@}
|
||||||
|
@end ifnottex
|
||||||
|
@end macro
|
||||||
|
|
||||||
|
$endif$
|
||||||
@ifnottex
|
@ifnottex
|
||||||
@paragraphindent 0
|
@paragraphindent 0
|
||||||
@end ifnottex
|
@end ifnottex
|
||||||
|
$if(titlepage)$
|
||||||
@titlepage
|
@titlepage
|
||||||
@title @math{title}
|
@title $title$
|
||||||
@author $authors$
|
$for(author)$
|
||||||
|
@author $author$
|
||||||
|
$endfor$
|
||||||
|
$if(date)$
|
||||||
$date$
|
$date$
|
||||||
|
$endif$
|
||||||
@end titlepage
|
@end titlepage
|
||||||
|
|
||||||
|
$endif$
|
||||||
|
$if(toc)$
|
||||||
@contents
|
@contents
|
||||||
|
|
||||||
@node Top
|
$endif$
|
||||||
@top @math{title}
|
$body$
|
||||||
|
|
||||||
@menu
|
|
||||||
* section oen::
|
|
||||||
@end menu
|
|
||||||
|
|
||||||
@node section oen
|
|
||||||
@chapter section oen
|
|
||||||
@enumerate
|
|
||||||
@item
|
|
||||||
one
|
|
||||||
@enumerate a
|
|
||||||
@item
|
|
||||||
two
|
|
||||||
@enumerate 3
|
|
||||||
@item
|
|
||||||
three
|
|
||||||
@end enumerate
|
|
||||||
|
|
||||||
@end enumerate
|
|
||||||
|
|
||||||
@end enumerate
|
|
||||||
|
|
||||||
@verbatim
|
|
||||||
hi
|
|
||||||
@end verbatim
|
|
||||||
|
|
||||||
footnote@footnote{with code
|
|
||||||
@verbatim
|
|
||||||
code
|
|
||||||
@end verbatim
|
|
||||||
}
|
|
||||||
|
|
||||||
|
|
||||||
@bye
|
@bye
|
||||||
|
|
|
@ -1,5 +1,6 @@
|
||||||
\input texinfo
|
\input texinfo
|
||||||
@documentencoding utf-8
|
@documentencoding utf-8
|
||||||
|
|
||||||
@macro textstrikeout{text}
|
@macro textstrikeout{text}
|
||||||
~~\text\~~
|
~~\text\~~
|
||||||
@end macro
|
@end macro
|
||||||
|
@ -22,7 +23,6 @@ _@{\text\@}
|
||||||
@end ifnottex
|
@end ifnottex
|
||||||
@end macro
|
@end macro
|
||||||
|
|
||||||
|
|
||||||
@ifnottex
|
@ifnottex
|
||||||
@paragraphindent 0
|
@paragraphindent 0
|
||||||
@end ifnottex
|
@end ifnottex
|
||||||
|
@ -32,6 +32,7 @@ _@{\text\@}
|
||||||
@author Anonymous
|
@author Anonymous
|
||||||
July 17@comma{} 2006
|
July 17@comma{} 2006
|
||||||
@end titlepage
|
@end titlepage
|
||||||
|
|
||||||
@node Top
|
@node Top
|
||||||
@top Pandoc Test Suite
|
@top Pandoc Test Suite
|
||||||
|
|
||||||
|
@ -1010,3 +1011,4 @@ And in list items.@footnote{In list.}
|
||||||
This paragraph should not be part of the note@comma{} as it is not indented.
|
This paragraph should not be part of the note@comma{} as it is not indented.
|
||||||
|
|
||||||
@bye
|
@bye
|
||||||
|
|
||||||
|
|
Loading…
Add table
Reference in a new issue