diff options
| author | John MacFarlane <fiddlosopher@gmail.com> | 2013-08-18 14:36:40 -0700 | 
|---|---|---|
| committer | John MacFarlane <fiddlosopher@gmail.com> | 2013-08-18 14:36:40 -0700 | 
| commit | 8d441af3da4709fd48a44e860d5a0cd4d35792af (patch) | |
| tree | 2592fa03c4923df4723ac487c89bbe1cb0558607 /src | |
| parent | 3117c668a7d245689bfc291d5d9a64cb3178b52c (diff) | |
| download | pandoc-8d441af3da4709fd48a44e860d5a0cd4d35792af.tar.gz | |
Adjusted writers and tests for change in parsing of div/span.
Textile, MediaWiki, Markdown, Org, RST will emit raw HTML div tags for divs.
Otherwise Div and Span are "transparent" block containers.
Diffstat (limited to 'src')
| -rw-r--r-- | src/Text/Pandoc/Writers/Docbook.hs | 2 | ||||
| -rw-r--r-- | src/Text/Pandoc/Writers/Markdown.hs | 17 | ||||
| -rw-r--r-- | src/Text/Pandoc/Writers/MediaWiki.hs | 12 | ||||
| -rw-r--r-- | src/Text/Pandoc/Writers/Org.hs | 9 | ||||
| -rw-r--r-- | src/Text/Pandoc/Writers/RST.hs | 6 | ||||
| -rw-r--r-- | src/Text/Pandoc/Writers/Shared.hs | 18 | ||||
| -rw-r--r-- | src/Text/Pandoc/Writers/Textile.hs | 8 | 
7 files changed, 58 insertions, 14 deletions
| diff --git a/src/Text/Pandoc/Writers/Docbook.hs b/src/Text/Pandoc/Writers/Docbook.hs index 3d150d19b..7c03c07dc 100644 --- a/src/Text/Pandoc/Writers/Docbook.hs +++ b/src/Text/Pandoc/Writers/Docbook.hs @@ -149,7 +149,7 @@ listItemToDocbook opts item =  -- | Convert a Pandoc block element to Docbook.  blockToDocbook :: WriterOptions -> Block -> Doc  blockToDocbook _ Null = empty -blockToDocbook opts (Div _ bs) = blocksToDocbook opts bs +blockToDocbook opts (Div _ bs) = blocksToDocbook opts $ map plainToPara bs  blockToDocbook _ (Header _ _ _) = empty -- should not occur after hierarchicalize  blockToDocbook opts (Plain lst) = inlinesToDocbook opts lst  -- title beginning with fig: indicates that the image is a figure diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs index 3d0ed8702..623c445df 100644 --- a/src/Text/Pandoc/Writers/Markdown.hs +++ b/src/Text/Pandoc/Writers/Markdown.hs @@ -1,6 +1,6 @@  {-# LANGUAGE OverloadedStrings, TupleSections, ScopedTypeVariables #-}  {- -Copyright (C) 2006-2010 John MacFarlane <jgm@berkeley.edu> +Copyright (C) 2006-2013 John MacFarlane <jgm@berkeley.edu>  This program is free software; you can redistribute it and/or modify  it under the terms of the GNU General Public License as published by @@ -19,7 +19,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA  {- |     Module      : Text.Pandoc.Writers.Markdown -   Copyright   : Copyright (C) 2006-2010 John MacFarlane +   Copyright   : Copyright (C) 2006-2013 John MacFarlane     License     : GNU GPL, version 2 or above     Maintainer  : John MacFarlane <jgm@berkeley.edu> @@ -301,7 +301,13 @@ blockToMarkdown :: WriterOptions -- ^ Options                  -> Block         -- ^ Block element                  -> State WriterState Doc  blockToMarkdown _ Null = return empty -blockToMarkdown opts (Div _ bs) = blockListToMarkdown opts bs +blockToMarkdown opts (Div attrs ils) = do +  isPlain <- gets stPlain +  contents <- blockListToMarkdown opts ils +  return $ if isPlain +              then contents <> blankline +              else tagWithAttrs "div" attrs <> blankline <> +                     contents <> blankline <> "</div>" <> blankline  blockToMarkdown opts (Plain inlines) = do    contents <- inlineListToMarkdown opts inlines    return $ contents <> cr @@ -629,8 +635,9 @@ escapeSpaces x = x  -- | Convert Pandoc inline element to markdown.  inlineToMarkdown :: WriterOptions -> Inline -> State WriterState Doc -inlineToMarkdown opts (Span _ ils) = -  inlineListToMarkdown opts ils +inlineToMarkdown opts (Span attrs ils) = do +  contents <- inlineListToMarkdown opts ils +  return $ tagWithAttrs "span" attrs <> contents <> text "</span>"  inlineToMarkdown opts (Emph lst) = do    contents <- inlineListToMarkdown opts lst    return $ "*" <> contents <> "*" diff --git a/src/Text/Pandoc/Writers/MediaWiki.hs b/src/Text/Pandoc/Writers/MediaWiki.hs index 4ffba1100..61741a61e 100644 --- a/src/Text/Pandoc/Writers/MediaWiki.hs +++ b/src/Text/Pandoc/Writers/MediaWiki.hs @@ -34,6 +34,7 @@ import Text.Pandoc.Definition  import Text.Pandoc.Options  import Text.Pandoc.Shared  import Text.Pandoc.Writers.Shared +import Text.Pandoc.Pretty (render)  import Text.Pandoc.Templates (renderTemplate')  import Text.Pandoc.XML ( escapeStringForXML )  import Data.List ( intersect, intercalate, intersperse ) @@ -83,8 +84,10 @@ blockToMediaWiki :: WriterOptions -- ^ Options  blockToMediaWiki _ Null = return "" -blockToMediaWiki opts (Div _ bs) = -  blockListToMediaWiki opts bs +blockToMediaWiki opts (Div attrs bs) = do +  contents <- blockListToMediaWiki opts bs +  return $ render Nothing (tagWithAttrs "div" attrs) ++ "\n\n" ++ +                     contents ++ "\n\n" ++ "</div>"  blockToMediaWiki opts (Plain inlines) =    inlineListToMediaWiki opts inlines @@ -332,8 +335,9 @@ inlineListToMediaWiki opts lst =  -- | Convert Pandoc inline element to MediaWiki.  inlineToMediaWiki :: WriterOptions -> Inline -> State WriterState String -inlineToMediaWiki opts (Span _ ils) = -  inlineListToMediaWiki opts ils +inlineToMediaWiki opts (Span attrs ils) = do +  contents <- inlineListToMediaWiki opts ils +  return $ render Nothing (tagWithAttrs "span" attrs) ++ contents ++ "</span>"  inlineToMediaWiki opts (Emph lst) = do    contents <- inlineListToMediaWiki opts lst diff --git a/src/Text/Pandoc/Writers/Org.hs b/src/Text/Pandoc/Writers/Org.hs index 34ae532b0..51083f52b 100644 --- a/src/Text/Pandoc/Writers/Org.hs +++ b/src/Text/Pandoc/Writers/Org.hs @@ -106,7 +106,14 @@ escapeString = escapeStringUsing $  blockToOrg :: Block         -- ^ Block element             -> State WriterState Doc  blockToOrg Null = return empty -blockToOrg (Div _ bs) = blockListToOrg bs +blockToOrg (Div attrs bs) = do +  contents <- blockListToOrg bs +  let startTag = tagWithAttrs "div" attrs +  let endTag = text "</div>" +  return $ blankline $$ "#+BEGIN_HTML" $$ +           nest 2 startTag $$ "#+END_HTML" $$ blankline $$ +           contents $$ blankline $$ "#+BEGIN_HTML" $$ +           nest 2 endTag $$ "#+END_HTML" $$ blankline  blockToOrg (Plain inlines) = inlineListToOrg inlines  -- title beginning with fig: indicates that the image is a figure  blockToOrg (Para [Image txt (src,'f':'i':'g':':':tit)]) = do diff --git a/src/Text/Pandoc/Writers/RST.hs b/src/Text/Pandoc/Writers/RST.hs index 557658bc8..70c6b4421 100644 --- a/src/Text/Pandoc/Writers/RST.hs +++ b/src/Text/Pandoc/Writers/RST.hs @@ -161,7 +161,11 @@ bordered contents c =  blockToRST :: Block         -- ^ Block element             -> State WriterState Doc  blockToRST Null = return empty -blockToRST (Div _ bs) = blockListToRST bs +blockToRST (Div attr bs) = do +  contents <- blockListToRST bs +  let startTag = ".. raw:: html" $+$ nest 3 (tagWithAttrs "div" attr) +  let endTag = ".. raw:: html" $+$ nest 3 "</div>" +  return $ blankline <> startTag $+$ contents $+$ endTag $$ blankline  blockToRST (Plain inlines) = inlineListToRST inlines  -- title beginning with fig: indicates that the image is a figure  blockToRST (Para [Image txt (src,'f':'i':'g':':':tit)]) = do diff --git a/src/Text/Pandoc/Writers/Shared.hs b/src/Text/Pandoc/Writers/Shared.hs index e6ec853f8..89923822c 100644 --- a/src/Text/Pandoc/Writers/Shared.hs +++ b/src/Text/Pandoc/Writers/Shared.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE OverloadedStrings #-}  {-  Copyright (C) 2013 John MacFarlane <jgm@berkeley.edu> @@ -32,9 +33,12 @@ module Text.Pandoc.Writers.Shared (                       , getField                       , setField                       , defField +                     , tagWithAttrs                       )  where  import Text.Pandoc.Definition +import Text.Pandoc.Pretty +import Text.Pandoc.XML (escapeStringForXML)  import Control.Monad (liftM)  import Text.Pandoc.Options (WriterOptions(..))  import qualified Data.HashMap.Strict as H @@ -120,3 +124,17 @@ defField field val (Object hashmap) =      where f _newval oldval = oldval  defField _ _  x = x +-- Produce an HTML tag with the given pandoc attributes. +tagWithAttrs :: String -> Attr -> Doc +tagWithAttrs tag (ident,classes,kvs) = hsep +  ["<" <> text tag +  ,if null ident +      then empty +      else "id=" <> doubleQuotes (text ident) +  ,if null classes +      then empty +      else "class=" <> doubleQuotes (text (unwords classes)) +  ] +  <> hsep (map (\(k,v) -> text k <> "=" <> +                doubleQuotes (text (escapeStringForXML v))) kvs) +  <> ">" diff --git a/src/Text/Pandoc/Writers/Textile.hs b/src/Text/Pandoc/Writers/Textile.hs index 27e8b60ec..7c102cc86 100644 --- a/src/Text/Pandoc/Writers/Textile.hs +++ b/src/Text/Pandoc/Writers/Textile.hs @@ -33,6 +33,7 @@ module Text.Pandoc.Writers.Textile ( writeTextile ) where  import Text.Pandoc.Definition  import Text.Pandoc.Options  import Text.Pandoc.Shared +import Text.Pandoc.Pretty (render)  import Text.Pandoc.Writers.Shared  import Text.Pandoc.Templates (renderTemplate')  import Text.Pandoc.XML ( escapeStringForXML ) @@ -101,8 +102,11 @@ blockToTextile :: WriterOptions -- ^ Options  blockToTextile _ Null = return "" -blockToTextile opts (Div _ bs) = -  blockListToTextile opts bs +blockToTextile opts (Div attr bs) = do +  let startTag = render Nothing $ tagWithAttrs "div" attr +  let endTag = "</div>" +  contents <- blockListToTextile opts bs +  return $ startTag ++ "\n\n" ++ contents ++ "\n\n" ++ endTag ++ "\n"  blockToTextile opts (Plain inlines) =    inlineListToTextile opts inlines | 
