Removed Blank block element as unnecessary.

git-svn-id: https://pandoc.googlecode.com/svn/trunk@578 788f1e2b-df1e-0410-8736-df70ead52e1b
This commit is contained in:
fiddlosopher 2007-03-17 20:23:47 +00:00
parent 9b3d5d88c2
commit 571c3b4173
12 changed files with 6 additions and 20 deletions

View file

@ -48,7 +48,6 @@ data Alignment = AlignLeft
-- | Block element.
data Block
= Plain [Inline] -- ^ Plain text, not a paragraph
| Blank -- ^ A blank line
| Null -- ^ Nothing
| Para [Inline] -- ^ Paragraph
| Key [Inline] Target -- ^ Reference key: name (inlines) and 'Target'

View file

@ -191,7 +191,7 @@ parseBlocks = manyTill block eof
block = choice [ header, table, codeBlock, note, referenceKey, hrule, list,
blockQuote, htmlBlock, rawLaTeXEnvironment', para,
plain, blankBlock, nullBlock ] <?> "block"
plain, nullBlock ] <?> "block"
--
-- header blocks

View file

@ -126,7 +126,7 @@ parseBlocks = manyTill block eof
block = choice [ codeBlock, rawHtmlBlock, rawLaTeXBlock, blockQuote,
referenceKey, imageBlock, unknownDirective, header,
hrule, list, fieldList, lineBlock, para, plain,
blankBlock, nullBlock ] <?> "block"
nullBlock ] <?> "block"
--
-- field list

View file

@ -432,7 +432,6 @@ keyTable [] = ([],[])
keyTable ((Key ref target):lst) = (((ref, target):table), rest)
where (table, rest) = keyTable lst
keyTable (Null:lst) = keyTable lst -- get rid of Nulls
keyTable (Blank:lst) = keyTable lst -- get rid of Blanks
keyTable (other:lst) = (table, (other:rest))
where (table, rest) = keyTable lst

View file

@ -133,7 +133,6 @@ listItemToDocbook opts item =
-- | Convert a Pandoc block element to Docbook.
blockToDocbook :: WriterOptions -> Block -> Doc
blockToDocbook opts Blank = text ""
blockToDocbook opts Null = empty
blockToDocbook opts (Plain lst) = wrap opts lst
blockToDocbook opts (Para lst) =

View file

@ -131,7 +131,6 @@ obfuscateString = concatMap obfuscateChar
-- | Convert Pandoc block element to HTML.
blockToHtml :: WriterOptions -> Block -> Html
blockToHtml opts Blank = noHtml
blockToHtml opts Null = noHtml
blockToHtml opts (Plain lst) = inlineListToHtml opts lst
blockToHtml opts (Para lst) = paragraph $ inlineListToHtml opts lst

View file

@ -102,7 +102,6 @@ deVerb (other:rest) = other:(deVerb rest)
blockToLaTeX :: [Block] -- ^ List of note blocks to use in resolving note refs
-> Block -- ^ Block to convert
-> String
blockToLaTeX notes Blank = "\n"
blockToLaTeX notes Null = ""
blockToLaTeX notes (Plain lst) = inlineListToLaTeX notes lst ++ "\n"
blockToLaTeX notes (Para lst) = (inlineListToLaTeX notes lst) ++ "\n\n"

View file

@ -75,8 +75,8 @@ formatKeys [] = []
formatKeys [x] = [x]
formatKeys ((Key x1 y1):(Key x2 y2):rest) =
(Key x1 y1):(formatKeys ((Key x2 y2):rest))
formatKeys ((Key x1 y1):rest) = (Key x1 y1):Blank:(formatKeys rest)
formatKeys (x:(Key x1 y1):rest) = x:Blank:(formatKeys ((Key x1 y1):rest))
formatKeys ((Key x1 y1):rest) = (Key x1 y1):(Plain [Str ""]):(formatKeys rest)
formatKeys (x:(Key x1 y1):rest) = x:(Plain [Str ""]):(formatKeys ((Key x1 y1):rest))
formatKeys (x:rest) = x:(formatKeys rest)
-- | Convert bibliographic information into Markdown header.
@ -103,7 +103,6 @@ dateToMarkdown str = text "% " <> text (escapeString str)
blockToMarkdown :: Int -- ^ Tab stop
-> Block -- ^ Block element
-> Doc
blockToMarkdown tabStop Blank = text ""
blockToMarkdown tabStop Null = empty
blockToMarkdown tabStop (Plain lst) = wrappedMarkdown lst
blockToMarkdown tabStop (Para lst) = (wrappedMarkdown lst) <> (text "\n")

View file

@ -112,7 +112,6 @@ dateToRST str = text ":Date: " <> text (escapeString str) <> char '\n'
blockToRST :: Int -- ^ tab stop
-> Block -- ^ block element to convert
-> (Doc, Doc) -- ^ first element is text, second is references for end of file
blockToRST tabStop Blank = (text "\n", empty)
blockToRST tabStop Null = (empty, empty)
blockToRST tabStop (Plain lst) = wrappedRST lst
blockToRST tabStop (Para [TeX str]) = -- raw latex block

View file

@ -146,7 +146,6 @@ blockToRTF :: [Block] -- ^ list of note blocks
-> Int -- ^ indent level
-> Block -- ^ block to convert
-> String
blockToRTF notes indent Blank = rtfPar indent 0 ""
blockToRTF notes indent Null = ""
blockToRTF notes indent (Plain lst) =
rtfCompact indent 0 (inlineListToRTF notes lst)

View file

@ -38,7 +38,6 @@ module Text.ParserCombinators.Pandoc (
blanklines,
escaped,
enclosed,
blankBlock,
nullBlock,
stringAnyCase,
parseFromStr
@ -59,12 +58,6 @@ nullBlock = do
anyChar
return Null
-- | Parses one or more blank lines; returns 'Blank'.
blankBlock :: GenParser Char st Block
blankBlock = do
blanklines
return Blank
-- | Parses a space or tab.
spaceChar :: CharParser st Char
spaceChar = oneOf " \t"

View file

@ -172,4 +172,5 @@ Pandoc (Meta [Str "Pandoc",Space,Str "Test",Space,Str "Suite",Str ":",Space,Str
, Plain [Image [Str "image"] (Src "lalune.jpg" "")]
, Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "movie",Space,Image [Str "movie"] (Ref [Str "movie"]),Space,Str "icon."]
, Key [Str "movie"] (Src "movie.jpg" "")
, Blank ]
, Null
, Plain [] ]