diff options
author | fiddlosopher <fiddlosopher@788f1e2b-df1e-0410-8736-df70ead52e1b> | 2008-08-04 03:15:12 +0000 |
---|---|---|
committer | fiddlosopher <fiddlosopher@788f1e2b-df1e-0410-8736-df70ead52e1b> | 2008-08-04 03:15:12 +0000 |
commit | 4719c7841718a131d659cb3037da33bebdf1cf31 (patch) | |
tree | 389d3e230eb9ef3146a065cd2139d7b4742f9731 /Text | |
parent | 6ff1e2a976c61268660da4a7cc392bb0a8cd781f (diff) | |
download | pandoc-4719c7841718a131d659cb3037da33bebdf1cf31.tar.gz |
Added Cite element to definition and writers.
git-svn-id: https://pandoc.googlecode.com/svn/trunk@1375 788f1e2b-df1e-0410-8736-df70ead52e1b
Diffstat (limited to 'Text')
-rw-r--r-- | Text/Pandoc/Definition.hs | 26 | ||||
-rw-r--r-- | Text/Pandoc/Writers/ConTeXt.hs | 1 | ||||
-rw-r--r-- | Text/Pandoc/Writers/Docbook.hs | 2 | ||||
-rw-r--r-- | Text/Pandoc/Writers/HTML.hs | 2 | ||||
-rw-r--r-- | Text/Pandoc/Writers/LaTeX.hs | 2 | ||||
-rw-r--r-- | Text/Pandoc/Writers/Man.hs | 2 | ||||
-rw-r--r-- | Text/Pandoc/Writers/Markdown.hs | 7 | ||||
-rw-r--r-- | Text/Pandoc/Writers/OpenDocument.hs | 1 | ||||
-rw-r--r-- | Text/Pandoc/Writers/RST.hs | 2 | ||||
-rw-r--r-- | Text/Pandoc/Writers/RTF.hs | 1 | ||||
-rw-r--r-- | Text/Pandoc/Writers/Texinfo.hs | 3 |
11 files changed, 41 insertions, 8 deletions
diff --git a/Text/Pandoc/Definition.hs b/Text/Pandoc/Definition.hs index 0a14705f2..f302f0dbd 100644 --- a/Text/Pandoc/Definition.hs +++ b/Text/Pandoc/Definition.hs @@ -1,3 +1,4 @@ +{-# OPTIONS_GHC -fglasgow-exts #-} -- for deriving Typeable {- Copyright (C) 2006-7 John MacFarlane <jgm@berkeley.edu> @@ -30,20 +31,22 @@ of documents. -} module Text.Pandoc.Definition where -data Pandoc = Pandoc Meta [Block] deriving (Eq, Read, Show) +import Data.Generics + +data Pandoc = Pandoc Meta [Block] deriving (Eq, Read, Show, Typeable, Data) -- | Bibliographic information for the document: title (list of 'Inline'), -- authors (list of strings), date (string). data Meta = Meta [Inline] -- title [String] -- authors String -- date - deriving (Eq, Show, Read) + deriving (Eq, Show, Read, Typeable, Data) -- | Alignment of a table column. data Alignment = AlignLeft | AlignRight | AlignCenter - | AlignDefault deriving (Eq, Show, Read) + | AlignDefault deriving (Eq, Show, Read, Typeable, Data) -- | List attributes. type ListAttributes = (Int, ListNumberStyle, ListNumberDelim) @@ -54,13 +57,13 @@ data ListNumberStyle = DefaultStyle | LowerRoman | UpperRoman | LowerAlpha - | UpperAlpha deriving (Eq, Show, Read) + | UpperAlpha deriving (Eq, Show, Read, Typeable, Data) -- | Delimiter of list numbers. data ListNumberDelim = DefaultDelim | Period | OneParen - | TwoParens deriving (Eq, Show, Read) + | TwoParens deriving (Eq, Show, Read, Typeable, Data) -- | Attributes. type Attr = (String, [String], [(String, String)]) -- ^ Identifier, classes, key-value pairs @@ -87,10 +90,10 @@ data Block -- (each a list of blocks), and rows -- (each a list of lists of blocks) | Null -- ^ Nothing - deriving (Eq, Read, Show) + deriving (Eq, Read, Show, Typeable, Data) -- | Type of quotation marks to use in Quoted inline. -data QuoteType = SingleQuote | DoubleQuote deriving (Show, Eq, Read) +data QuoteType = SingleQuote | DoubleQuote deriving (Show, Eq, Read, Typeable, Data) -- | Link target (URL, title). type Target = (String, String) @@ -105,6 +108,7 @@ data Inline | Subscript [Inline] -- ^ Subscripted text (list of inlines) | SmallCaps [Inline] -- ^ Small caps text (list of inlines) | Quoted QuoteType [Inline] -- ^ Quoted text (list of inlines) + | Cite [Target] [Inline] -- ^ Citation (list of inlines) | Code String -- ^ Inline code (literal) | Space -- ^ Inter-word space | EmDash -- ^ Em dash @@ -119,4 +123,10 @@ data Inline | Image [Inline] Target -- ^ Image: alt text (list of inlines), target -- and target | Note [Block] -- ^ Footnote or endnote - deriving (Show, Eq, Read) + deriving (Show, Eq, Read, Typeable, Data) + +processPandoc :: Typeable a => (a -> a) -> Pandoc -> Pandoc +processPandoc f = everywhere (mkT f) + +queryPandoc :: Typeable a => (a -> [b]) -> Pandoc -> [b] +queryPandoc f = everything (++) ([] `mkQ` f) diff --git a/Text/Pandoc/Writers/ConTeXt.hs b/Text/Pandoc/Writers/ConTeXt.hs index 7fe41c792..297322159 100644 --- a/Text/Pandoc/Writers/ConTeXt.hs +++ b/Text/Pandoc/Writers/ConTeXt.hs @@ -266,6 +266,7 @@ inlineToConTeXt (Quoted SingleQuote lst) = do inlineToConTeXt (Quoted DoubleQuote lst) = do contents <- inlineListToConTeXt lst return $ text "\\quotation{" <> contents <> char '}' +inlineToConTeXt (Cite _ lst) = inlineListToConTeXt lst inlineToConTeXt Apostrophe = return $ char '\'' inlineToConTeXt EmDash = return $ text "---" inlineToConTeXt EnDash = return $ text "--" diff --git a/Text/Pandoc/Writers/Docbook.hs b/Text/Pandoc/Writers/Docbook.hs index bd261caf0..5b433c434 100644 --- a/Text/Pandoc/Writers/Docbook.hs +++ b/Text/Pandoc/Writers/Docbook.hs @@ -228,6 +228,8 @@ inlineToDocbook opts (SmallCaps lst) = inlinesToDocbook opts lst inlineToDocbook opts (Quoted _ lst) = inTagsSimple "quote" $ inlinesToDocbook opts lst +inlineToDocbook opts (Cite _ lst) = + inlinesToDocbook opts lst inlineToDocbook _ Apostrophe = char '\'' inlineToDocbook _ Ellipses = text "…" inlineToDocbook _ EmDash = text "—" diff --git a/Text/Pandoc/Writers/HTML.hs b/Text/Pandoc/Writers/HTML.hs index 6c28edb42..e5ed4468e 100644 --- a/Text/Pandoc/Writers/HTML.hs +++ b/Text/Pandoc/Writers/HTML.hs @@ -260,6 +260,7 @@ inlineListToIdentifier' (x:xs) = Subscript lst -> inlineListToIdentifier' lst Strong lst -> inlineListToIdentifier' lst Quoted _ lst -> inlineListToIdentifier' lst + Cite _ lst -> inlineListToIdentifier' lst Code s -> s Space -> "-" EmDash -> "-" @@ -502,6 +503,7 @@ inlineToHtml opts inline = theclass "footnoteRef", identifier ("fnref" ++ ref)] << sup << ref + (Cite _ il) -> inlineListToHtml opts il blockListToNote :: WriterOptions -> String -> [Block] -> State WriterState Html blockListToNote opts ref blocks = diff --git a/Text/Pandoc/Writers/LaTeX.hs b/Text/Pandoc/Writers/LaTeX.hs index b523dea9e..53c6e65e0 100644 --- a/Text/Pandoc/Writers/LaTeX.hs +++ b/Text/Pandoc/Writers/LaTeX.hs @@ -267,6 +267,8 @@ inlineToLaTeX (Subscript lst) = do return $ inCmd "textsubscr" contents inlineToLaTeX (SmallCaps lst) = inlineListToLaTeX (deVerb lst) >>= return . inCmd "textsc" +inlineToLaTeX (Cite _ lst) = + inlineListToLaTeX lst inlineToLaTeX (Code str) = do st <- get if stInNote st diff --git a/Text/Pandoc/Writers/Man.hs b/Text/Pandoc/Writers/Man.hs index 4fd3dc8c2..f83436b31 100644 --- a/Text/Pandoc/Writers/Man.hs +++ b/Text/Pandoc/Writers/Man.hs @@ -263,6 +263,8 @@ inlineToMan opts (Quoted SingleQuote lst) = do inlineToMan opts (Quoted DoubleQuote lst) = do contents <- inlineListToMan opts lst return $ text "\\[lq]" <> contents <> text "\\[rq]" +inlineToMan opts (Cite _ lst) = + inlineListToMan opts lst inlineToMan _ EmDash = return $ text "\\[em]" inlineToMan _ EnDash = return $ text "\\[en]" inlineToMan _ Apostrophe = return $ char '\'' diff --git a/Text/Pandoc/Writers/Markdown.hs b/Text/Pandoc/Writers/Markdown.hs index 2c99109a5..7c360bec2 100644 --- a/Text/Pandoc/Writers/Markdown.hs +++ b/Text/Pandoc/Writers/Markdown.hs @@ -342,6 +342,13 @@ inlineToMarkdown _ (TeX str) = return $ text str inlineToMarkdown _ (HtmlInline str) = return $ text str inlineToMarkdown _ (LineBreak) = return $ text " \n" inlineToMarkdown _ Space = return $ char ' ' +inlineToMarkdown _ (Cite cits _ ) = do + let format (a,b) xs = text a <> + (if b /= [] then char '@' else empty) <> + text b <> + (if isEmpty xs then empty else text "; ") <> + xs + return $ char '[' <> foldr format empty cits <> char ']' inlineToMarkdown opts (Link txt (src, tit)) = do linktext <- inlineListToMarkdown opts txt let linktitle = if null tit then empty else text $ " \"" ++ tit ++ "\"" diff --git a/Text/Pandoc/Writers/OpenDocument.hs b/Text/Pandoc/Writers/OpenDocument.hs index cbf15214f..70aab92f1 100644 --- a/Text/Pandoc/Writers/OpenDocument.hs +++ b/Text/Pandoc/Writers/OpenDocument.hs @@ -380,6 +380,7 @@ inlineToOpenDocument o ils | Quoted t l <- ils = inQuotes t <$> inlinesToOpenDocument o l | Code s <- ils = preformatted s | Math s <- ils = inlinesToOpenDocument o (readTeXMath s) + | Cite _ l <- ils = inlinesToOpenDocument o l | TeX s <- ils = preformatted s | HtmlInline s <- ils = preformatted s | Link l (s,t) <- ils = mkLink s t <$> inlinesToOpenDocument o l diff --git a/Text/Pandoc/Writers/RST.hs b/Text/Pandoc/Writers/RST.hs index 93a592132..9215f051d 100644 --- a/Text/Pandoc/Writers/RST.hs +++ b/Text/Pandoc/Writers/RST.hs @@ -283,6 +283,8 @@ inlineToRST (Quoted SingleQuote lst) = do inlineToRST (Quoted DoubleQuote lst) = do contents <- inlineListToRST lst return $ char '"' <> contents <> char '"' +inlineToRST (Cite _ lst) = + inlineListToRST lst inlineToRST EmDash = return $ text "--" inlineToRST EnDash = return $ char '-' inlineToRST Apostrophe = return $ char '\'' diff --git a/Text/Pandoc/Writers/RTF.hs b/Text/Pandoc/Writers/RTF.hs index db3b9f538..d0fbfb53a 100644 --- a/Text/Pandoc/Writers/RTF.hs +++ b/Text/Pandoc/Writers/RTF.hs @@ -276,6 +276,7 @@ inlineToRTF EnDash = "\\u8211-" inlineToRTF (Code str) = "{\\f1 " ++ (codeStringToRTF str) ++ "}" inlineToRTF (Str str) = stringToRTF str inlineToRTF (Math str) = inlineListToRTF $ readTeXMath str +inlineToRTF (Cite _ lst) = inlineListToRTF lst inlineToRTF (TeX _) = "" inlineToRTF (HtmlInline _) = "" inlineToRTF (LineBreak) = "\\line " diff --git a/Text/Pandoc/Writers/Texinfo.hs b/Text/Pandoc/Writers/Texinfo.hs index 8cc27b585..d0e134346 100644 --- a/Text/Pandoc/Writers/Texinfo.hs +++ b/Text/Pandoc/Writers/Texinfo.hs @@ -356,6 +356,7 @@ inlineForNode (Superscript lst) = inlineListForNode lst inlineForNode (Subscript lst) = inlineListForNode lst inlineForNode (SmallCaps lst) = inlineListForNode lst inlineForNode (Quoted _ lst) = inlineListForNode lst +inlineForNode (Cite _ lst) = inlineListForNode lst inlineForNode (Code str) = inlineForNode (Str str) inlineForNode Space = return $ char ' ' inlineForNode EmDash = return $ text "---" @@ -429,6 +430,8 @@ inlineToTexinfo (Quoted DoubleQuote lst) = do contents <- inlineListToTexinfo lst return $ text "``" <> contents <> text "''" +inlineToTexinfo (Cite _ lst) = + inlineListToTexinfo lst inlineToTexinfo Apostrophe = return $ char '\'' inlineToTexinfo EmDash = return $ text "---" inlineToTexinfo EnDash = return $ text "--" |