Revert "Added page breaks into Pandoc."
This reverts commit f02a12aff638fa2339192231b8f601bffdfe3e14.
This commit is contained in:
parent
73f57daf69
commit
01483f91bd
27 changed files with 16 additions and 95 deletions
|
@ -270,7 +270,7 @@ Library
|
|||
xml >= 1.3.12 && < 1.4,
|
||||
random >= 1 && < 1.2,
|
||||
extensible-exceptions >= 0.1 && < 0.2,
|
||||
pandoc-types >= 1.18 && < 1.19,
|
||||
pandoc-types >= 1.17 && < 1.18,
|
||||
aeson >= 0.7 && < 1.2,
|
||||
tagsoup >= 0.13.7 && < 0.15,
|
||||
base64-bytestring >= 0.1 && < 1.1,
|
||||
|
@ -426,7 +426,7 @@ Library
|
|||
|
||||
Executable pandoc
|
||||
Build-Depends: pandoc,
|
||||
pandoc-types >= 1.18 && < 1.19,
|
||||
pandoc-types >= 1.17 && < 1.18,
|
||||
base >= 4.2 && <5,
|
||||
directory >= 1.2 && < 1.4,
|
||||
filepath >= 1.1 && < 1.5,
|
||||
|
@ -504,7 +504,7 @@ Test-Suite test-pandoc
|
|||
Build-Depends: base >= 4.2 && < 5,
|
||||
syb >= 0.1 && < 0.7,
|
||||
pandoc,
|
||||
pandoc-types >= 1.18 && < 1.19,
|
||||
pandoc-types >= 1.17 && < 1.18,
|
||||
bytestring >= 0.9 && < 0.11,
|
||||
text >= 0.11 && < 1.3,
|
||||
directory >= 1 && < 1.4,
|
||||
|
|
|
@ -381,9 +381,9 @@ getParaModifier :: Style -> ParaModifier
|
|||
getParaModifier Style{..} | Just props <- paraProperties styleProperties
|
||||
, isBlockQuote (indentation props)
|
||||
(margin_left props)
|
||||
= pageBreakMaybe (paraProperties styleProperties) blockQuote
|
||||
= blockQuote
|
||||
| otherwise
|
||||
= pageBreakMaybe (paraProperties styleProperties) id
|
||||
= id
|
||||
where
|
||||
isBlockQuote mIndent mMargin
|
||||
| LengthValueMM indent <- mIndent
|
||||
|
@ -408,19 +408,7 @@ getParaModifier Style{..} | Just props <- paraProperties styleProperties
|
|||
|
||||
| otherwise
|
||||
= False
|
||||
pageBreakMaybe :: Maybe ParaProperties -> ParaModifier -> ParaModifier
|
||||
pageBreakMaybe (Just props) modifier = insertPageBreak (page_break props) modifier
|
||||
pageBreakMaybe Nothing modifier = modifier
|
||||
|
||||
insertPageBreak :: ParaBreak -> ParaModifier -> ParaModifier
|
||||
insertPageBreak PageAfter modifier =
|
||||
\x -> (fromList (toList (modifier x) ++ [Para (toList pageBreak)]))
|
||||
insertPageBreak PageBefore modifier =
|
||||
\x -> (fromList (Para (toList pageBreak) : toList (modifier x)))
|
||||
insertPageBreak PageBoth modifier =
|
||||
\x -> (fromList ((Para (toList pageBreak) : toList (modifier x)) ++ [Para (toList pageBreak)]))
|
||||
insertPageBreak _ modifier =
|
||||
modifier
|
||||
--
|
||||
constructPara :: OdtReaderSafe Blocks Blocks -> OdtReaderSafe Blocks Blocks
|
||||
constructPara reader = proc blocks -> do
|
||||
|
@ -906,6 +894,7 @@ read_reference_ref = matchingElement NsText "reference-ref"
|
|||
$ maybeInAnchorRef
|
||||
<<< matchChildContent [] read_plain_text
|
||||
|
||||
|
||||
----------------------
|
||||
-- Entry point
|
||||
----------------------
|
||||
|
|
|
@ -43,7 +43,6 @@ module Text.Pandoc.Readers.Odt.StyleReader
|
|||
, TextProperties (..)
|
||||
, ParaProperties (..)
|
||||
, VerticalTextPosition (..)
|
||||
, ParaBreak (..)
|
||||
, ListItemNumberFormat (..)
|
||||
, ListLevel
|
||||
, ListStyle (..)
|
||||
|
@ -274,7 +273,6 @@ instance Default TextProperties where
|
|||
data ParaProperties = PropP { paraNumbering :: ParaNumbering
|
||||
, indentation :: LengthOrPercent
|
||||
, margin_left :: LengthOrPercent
|
||||
, page_break :: ParaBreak
|
||||
}
|
||||
deriving ( Eq, Show )
|
||||
|
||||
|
@ -282,7 +280,6 @@ instance Default ParaProperties where
|
|||
def = PropP { paraNumbering = NumberingNone
|
||||
, indentation = def
|
||||
, margin_left = def
|
||||
, page_break = AutoNone
|
||||
}
|
||||
|
||||
----
|
||||
|
@ -317,9 +314,6 @@ instance Lookupable UnderlineMode where
|
|||
data ParaNumbering = NumberingNone | NumberingKeep | NumberingRestart Int
|
||||
deriving ( Eq, Show )
|
||||
|
||||
data ParaBreak = AutoNone | PageBefore | PageAfter | PageBoth
|
||||
deriving ( Eq, Show )
|
||||
|
||||
data LengthOrPercent = LengthValueMM Int | PercentValue Int
|
||||
deriving ( Eq, Show )
|
||||
|
||||
|
@ -539,20 +533,16 @@ readLineMode modeAttr styleAttr = proc x -> do
|
|||
readParaProperties :: StyleReader _x ParaProperties
|
||||
readParaProperties =
|
||||
executeIn NsStyle "paragraph-properties" $ liftAsSuccess
|
||||
( liftA4 PropP
|
||||
( liftA3 PropP
|
||||
( liftA2 readNumbering
|
||||
( isSet' NsText "number-lines" )
|
||||
( readAttr' NsText "line-number" )
|
||||
( isSet' NsText "number-lines" )
|
||||
( readAttr' NsText "line-number" )
|
||||
)
|
||||
( liftA2 readIndentation
|
||||
( isSetWithDefault NsStyle "auto-text-indent" False )
|
||||
( getAttr NsXSL_FO "text-indent" )
|
||||
)
|
||||
( getAttr NsXSL_FO "margin-left" )
|
||||
( liftA2 readPageBreak
|
||||
( findAttrWithDefault NsXSL_FO "break-before" "auto" )
|
||||
( findAttrWithDefault NsXSL_FO "break-after" "auto" )
|
||||
( isSetWithDefault NsStyle "auto-text-indent" False )
|
||||
( getAttr NsXSL_FO "text-indent" )
|
||||
)
|
||||
( getAttr NsXSL_FO "margin-left" )
|
||||
)
|
||||
where readNumbering (Just True) (Just n) = NumberingRestart n
|
||||
readNumbering (Just True) _ = NumberingKeep
|
||||
|
@ -561,11 +551,6 @@ readParaProperties =
|
|||
readIndentation False indent = indent
|
||||
readIndentation True _ = def
|
||||
|
||||
readPageBreak "page" "page" = PageBoth
|
||||
readPageBreak "page" _ = PageBefore
|
||||
readPageBreak _ "page" = PageAfter
|
||||
readPageBreak _ _ = AutoNone
|
||||
|
||||
----
|
||||
-- List styles
|
||||
----
|
||||
|
|
|
@ -413,7 +413,6 @@ inlineToAsciiDoc _ (RawInline f s)
|
|||
| f == "asciidoc" = return $ text s
|
||||
| otherwise = return empty
|
||||
inlineToAsciiDoc _ LineBreak = return $ " +" <> cr
|
||||
inlineToAsciiDoc _ PageBreak = return empty
|
||||
inlineToAsciiDoc _ Space = return space
|
||||
inlineToAsciiDoc opts SoftBreak =
|
||||
case writerWrapText opts of
|
||||
|
|
|
@ -149,7 +149,6 @@ inlineToNodes :: Inline -> [Node] -> [Node]
|
|||
inlineToNodes (Str s) = (node (TEXT (T.pack s)) [] :)
|
||||
inlineToNodes Space = (node (TEXT (T.pack " ")) [] :)
|
||||
inlineToNodes LineBreak = (node LINEBREAK [] :)
|
||||
inlineToNodes PageBreak = id
|
||||
inlineToNodes SoftBreak = (node SOFTBREAK [] :)
|
||||
inlineToNodes (Emph xs) = (node EMPH (inlinesToNodes xs) :)
|
||||
inlineToNodes (Strong xs) = (node STRONG (inlinesToNodes xs) :)
|
||||
|
|
|
@ -347,7 +347,6 @@ inlineToConTeXt SoftBreak = do
|
|||
WrapAuto -> space
|
||||
WrapNone -> space
|
||||
WrapPreserve -> cr
|
||||
inlineToConTeXt PageBreak = return empty
|
||||
inlineToConTeXt Space = return space
|
||||
-- Handle HTML-like internal document references to sections
|
||||
inlineToConTeXt (Link _ txt (('#' : ref), _)) = do
|
||||
|
|
|
@ -310,8 +310,6 @@ inlineToCustom lua (RawInline format str) =
|
|||
|
||||
inlineToCustom lua (LineBreak) = callfunc lua "LineBreak"
|
||||
|
||||
inlineToCustom lua (PageBreak) = callfunc lua "PageBreak"
|
||||
|
||||
inlineToCustom lua (Link attr txt (src,tit)) =
|
||||
callfunc lua "Link" txt src tit (attrToMap attr)
|
||||
|
||||
|
|
|
@ -373,7 +373,6 @@ inlineToDocbook _ (RawInline f x)
|
|||
inlineToDocbook _ LineBreak = return $ text "\n"
|
||||
-- currently ignore, would require the option to add custom
|
||||
-- styles to the document
|
||||
inlineToDocbook _ PageBreak = return empty
|
||||
inlineToDocbook _ Space = return space
|
||||
-- because we use \n for LineBreak, we can't do soft breaks:
|
||||
inlineToDocbook _ SoftBreak = return space
|
||||
|
|
|
@ -1106,7 +1106,6 @@ inlineToOpenXML' opts (Strikeout lst) =
|
|||
withTextProp (mknode "w:strike" [] ())
|
||||
$ inlinesToOpenXML opts lst
|
||||
inlineToOpenXML' _ LineBreak = return [br]
|
||||
inlineToOpenXML' _ PageBreak = return [pageBreak]
|
||||
inlineToOpenXML' _ (RawInline f str)
|
||||
| f == Format "openxml" = return [ x | Elem x <- parseXML str ]
|
||||
| otherwise = return []
|
||||
|
|
|
@ -475,8 +475,6 @@ inlineToDokuWiki _ (RawInline f str)
|
|||
|
||||
inlineToDokuWiki _ LineBreak = return "\\\\\n"
|
||||
|
||||
inlineToDokuWiki _ PageBreak = return mempty
|
||||
|
||||
inlineToDokuWiki opts SoftBreak =
|
||||
case writerWrapText opts of
|
||||
WrapNone -> return " "
|
||||
|
|
|
@ -437,7 +437,6 @@ toXml (Code _ s) = return [el "code" s]
|
|||
toXml Space = return [txt " "]
|
||||
toXml SoftBreak = return [txt " "]
|
||||
toXml LineBreak = return [el "empty-line" ()]
|
||||
toXml PageBreak = return []
|
||||
toXml (Math _ formula) = insertMath InlineImage formula
|
||||
toXml (RawInline _ _) = return [] -- raw TeX and raw HTML are suppressed
|
||||
toXml (Link _ text (url,ttl)) = do
|
||||
|
@ -569,7 +568,6 @@ plain (Code _ s) = s
|
|||
plain Space = " "
|
||||
plain SoftBreak = " "
|
||||
plain LineBreak = "\n"
|
||||
plain PageBreak = "\n"
|
||||
plain (Math _ s) = s
|
||||
plain (RawInline _ s) = s
|
||||
plain (Link _ text (url,_)) = concat (map plain text ++ [" <", url, ">"])
|
||||
|
|
|
@ -713,7 +713,6 @@ inlineToHtml opts inline =
|
|||
WrapPreserve -> preEscapedString "\n"
|
||||
(LineBreak) -> return $ (if writerHtml5 opts then H5.br else H.br)
|
||||
<> strToHtml "\n"
|
||||
(PageBreak) -> return mempty
|
||||
(Span (id',classes,kvs) ils)
|
||||
-> inlineListToHtml opts ils >>=
|
||||
return . addAttrs opts attr' . H.span
|
||||
|
|
|
@ -339,7 +339,6 @@ inlineToHaddock _ (RawInline f str)
|
|||
| otherwise = return empty
|
||||
-- no line break in haddock (see above on CodeBlock)
|
||||
inlineToHaddock _ LineBreak = return cr
|
||||
inlineToHaddock _ PageBreak = return empty
|
||||
inlineToHaddock opts SoftBreak =
|
||||
case writerWrapText opts of
|
||||
WrapAuto -> return space
|
||||
|
|
|
@ -435,7 +435,6 @@ inlineToICML opts style SoftBreak =
|
|||
WrapNone -> charStyle style space
|
||||
WrapPreserve -> charStyle style cr
|
||||
inlineToICML _ style LineBreak = charStyle style $ text lineSeparator
|
||||
inlineToICML _ _ PageBreak = return empty
|
||||
inlineToICML opts style (Math mt str) =
|
||||
lift (texMathToInlines mt str) >>=
|
||||
(fmap cat . mapM (inlineToICML opts style))
|
||||
|
|
|
@ -961,7 +961,6 @@ inlineToLaTeX SoftBreak = do
|
|||
WrapAuto -> return space
|
||||
WrapNone -> return space
|
||||
WrapPreserve -> return cr
|
||||
inlineToLaTeX PageBreak = return $ "\\clearpage{}"
|
||||
inlineToLaTeX Space = return space
|
||||
inlineToLaTeX (Link _ txt ('#':ident, _)) = do
|
||||
contents <- inlineListToLaTeX txt
|
||||
|
|
|
@ -351,7 +351,6 @@ inlineToMan _ (RawInline f str)
|
|||
| otherwise = return empty
|
||||
inlineToMan _ LineBreak = return $
|
||||
cr <> text ".PD 0" $$ text ".P" $$ text ".PD" <> cr
|
||||
inlineToMan _ PageBreak = return empty
|
||||
inlineToMan _ SoftBreak = return space
|
||||
inlineToMan _ Space = return space
|
||||
inlineToMan opts (Link _ txt (src, _)) = do
|
||||
|
|
|
@ -1038,7 +1038,6 @@ inlineToMarkdown opts SoftBreak = do
|
|||
WrapNone -> space'
|
||||
WrapAuto -> space'
|
||||
WrapPreserve -> cr
|
||||
inlineToMarkdown _ PageBreak = return empty
|
||||
inlineToMarkdown opts (Cite [] lst) = inlineListToMarkdown opts lst
|
||||
inlineToMarkdown opts (Cite (c:cs) lst)
|
||||
| not (isEnabled Ext_citations opts) = inlineListToMarkdown opts lst
|
||||
|
|
|
@ -405,8 +405,6 @@ inlineToMediaWiki (RawInline f str)
|
|||
|
||||
inlineToMediaWiki LineBreak = return "<br />\n"
|
||||
|
||||
inlineToMediaWiki PageBreak = return mempty
|
||||
|
||||
inlineToMediaWiki SoftBreak = do
|
||||
wrapText <- gets (writerWrapText . stOptions)
|
||||
case wrapText of
|
||||
|
|
|
@ -35,7 +35,6 @@ import Text.Pandoc.Options
|
|||
import Text.Pandoc.XML
|
||||
import Text.Pandoc.Shared (linesToPara)
|
||||
import Text.Pandoc.Templates (renderTemplate')
|
||||
import Text.Pandoc.Readers.Odt.StyleReader hiding (listStyle)
|
||||
import Text.Pandoc.Writers.Math
|
||||
import Text.Pandoc.Pretty
|
||||
import Text.Printf ( printf )
|
||||
|
@ -319,7 +318,9 @@ blockToOpenDocument o bs
|
|||
else inParagraphTags =<< inlinesToOpenDocument o b
|
||||
| Para [Image attr c (s,'f':'i':'g':':':t)] <- bs
|
||||
= figure attr c s t
|
||||
| Para b <- bs = paragraph b
|
||||
| Para b <- bs = if null b
|
||||
then return empty
|
||||
else inParagraphTags =<< inlinesToOpenDocument o b
|
||||
| LineBlock b <- bs = blockToOpenDocument o $ linesToPara b
|
||||
| Div _ xs <- bs = blocksToOpenDocument o xs
|
||||
| Header i _ b <- bs = setFirstPara >>
|
||||
|
@ -380,22 +381,6 @@ blockToOpenDocument o bs
|
|||
captionDoc <- withParagraphStyle o "FigureCaption" [Para caption]
|
||||
return $ imageDoc $$ captionDoc
|
||||
|
||||
endsWithPageBreak [] = False
|
||||
endsWithPageBreak [PageBreak] = True
|
||||
endsWithPageBreak (_ : xs) = endsWithPageBreak xs
|
||||
|
||||
paragraph :: PandocMonad m => [Inline] -> OD m Doc
|
||||
paragraph [] = return empty
|
||||
paragraph (PageBreak : rest) | endsWithPageBreak rest = paraWithBreak PageBoth rest
|
||||
paragraph (PageBreak : rest) = paraWithBreak PageBefore rest
|
||||
paragraph inlines | endsWithPageBreak inlines = paraWithBreak PageAfter inlines
|
||||
paragraph inlines = inParagraphTags =<< inlinesToOpenDocument o inlines
|
||||
|
||||
paraWithBreak :: PandocMonad m => ParaBreak -> [Inline] -> OD m Doc
|
||||
paraWithBreak breakKind bs' = do
|
||||
pn <- paraBreakStyle breakKind
|
||||
withParagraphStyle o ("P" ++ show pn) [Para bs']
|
||||
|
||||
colHeadsToOpenDocument :: PandocMonad m
|
||||
=> WriterOptions -> String -> [String] -> [[Block]]
|
||||
-> OD m Doc
|
||||
|
@ -595,12 +580,6 @@ paraStyle attrs = do
|
|||
addParaStyle $ inTags True "style:style" (styleAttr ++ attrs) paraProps
|
||||
return pn
|
||||
|
||||
paraBreakStyle :: PandocMonad m => ParaBreak -> OD m Int
|
||||
paraBreakStyle PageBefore = paraStyle "Text_20_body" [("fo:break-before", "page")]
|
||||
paraBreakStyle PageAfter = paraStyle "Text_20_body" [("fo:break-after", "page")]
|
||||
paraBreakStyle PageBoth = paraStyle "Text_20_body" [("fo:break-before", "page"), ("fo:break-after", "page")]
|
||||
paraBreakStyle AutoNone = paraStyle "Text_20_body" []
|
||||
|
||||
paraListStyle :: PandocMonad m => Int -> OD m Int
|
||||
paraListStyle l = paraStyle
|
||||
[("style:parent-style-name","Text_20_body")
|
||||
|
|
|
@ -351,7 +351,6 @@ inlineToOrg (RawInline f@(Format f') str) =
|
|||
then text str
|
||||
else "@@" <> text f' <> ":" <> text str <> "@@"
|
||||
inlineToOrg LineBreak = return (text "\\\\" <> cr)
|
||||
inlineToOrg PageBreak = return empty
|
||||
inlineToOrg Space = return space
|
||||
inlineToOrg SoftBreak = do
|
||||
wrapText <- gets (writerWrapText . stOptions)
|
||||
|
|
|
@ -462,7 +462,6 @@ inlineToRST SoftBreak = do
|
|||
WrapPreserve -> return cr
|
||||
WrapAuto -> return space
|
||||
WrapNone -> return space
|
||||
inlineToRST PageBreak = return $ ".. pagebreak::"
|
||||
-- autolink
|
||||
inlineToRST (Link _ [Str str] (src, _))
|
||||
| isURI src &&
|
||||
|
|
|
@ -396,7 +396,6 @@ inlineToRTF (RawInline f str)
|
|||
| otherwise = return ""
|
||||
inlineToRTF (LineBreak) = return "\\line "
|
||||
inlineToRTF SoftBreak = return " "
|
||||
inlineToRTF PageBreak = return "\\page "
|
||||
inlineToRTF Space = return " "
|
||||
inlineToRTF (Link _ text (src, _)) = do
|
||||
contents <- inlinesToRTF text
|
||||
|
|
|
@ -285,7 +285,6 @@ inlineToTEI _ (Math t str) =
|
|||
inlineToTEI _ (RawInline f x) | f == "tei" = text x
|
||||
| otherwise = empty
|
||||
inlineToTEI _ LineBreak = selfClosingTag "lb" []
|
||||
inlineToTEI _ PageBreak = selfClosingTag "pb" []
|
||||
inlineToTEI _ Space = space
|
||||
-- because we use \n for LineBreak, we can't do soft breaks:
|
||||
inlineToTEI _ SoftBreak = space
|
||||
|
|
|
@ -458,8 +458,6 @@ inlineToTexinfo SoftBreak = do
|
|||
WrapPreserve -> return cr
|
||||
inlineToTexinfo Space = return space
|
||||
|
||||
inlineToTexinfo PageBreak = return $ text "@page"
|
||||
|
||||
inlineToTexinfo (Link _ txt (src@('#':_), _)) = do
|
||||
contents <- escapeCommas $ inlineListToTexinfo txt
|
||||
return $ text "@ref" <>
|
||||
|
|
|
@ -438,8 +438,6 @@ inlineToTextile opts (RawInline f str)
|
|||
|
||||
inlineToTextile _ LineBreak = return "\n"
|
||||
|
||||
inlineToTextile _ PageBreak = return mempty
|
||||
|
||||
inlineToTextile _ SoftBreak = return " "
|
||||
|
||||
inlineToTextile _ Space = return " "
|
||||
|
|
|
@ -320,8 +320,6 @@ inlineToZimWiki opts (RawInline f str)
|
|||
|
||||
inlineToZimWiki _ LineBreak = return "\n" -- was \\\\
|
||||
|
||||
inlineToZimWiki _ PageBreak = return mempty
|
||||
|
||||
inlineToZimWiki opts SoftBreak =
|
||||
case writerWrapText opts of
|
||||
WrapNone -> return " "
|
||||
|
|
|
@ -7,10 +7,6 @@ flags:
|
|||
network-uri: true
|
||||
packages:
|
||||
- '.'
|
||||
- location:
|
||||
git: https://github.com/jgm/pandoc-types.git
|
||||
commit: 973394685aad945ccd92a86bf76e5c644e72e127
|
||||
extra-dep: true
|
||||
- location:
|
||||
git: https://github.com/jgm/texmath.git
|
||||
commit: 31273683a376e97848028e4619f28ab8c03c88af
|
||||
|
@ -19,4 +15,5 @@ extra-deps:
|
|||
- doctemplates-0.1.0.2
|
||||
- pandoc-types-1.17.0.4
|
||||
- skylighting-0.1.1.1
|
||||
- texmath-0.9
|
||||
resolver: lts-7.14
|
||||
|
|
Loading…
Add table
Reference in a new issue