Added page breaks into Pandoc.
This requires an updated version of pandoc-types that introduces PageBreak definition. Not that this initial commit only introduces ODT pagebreaks and distinguishes for it page breaks before, after, or both, the paragraph, as read from the style definition.
This commit is contained in:
parent
5a03ebf05b
commit
30b3412857
3 changed files with 60 additions and 12 deletions
|
@ -381,9 +381,9 @@ getParaModifier :: Style -> ParaModifier
|
||||||
getParaModifier Style{..} | Just props <- paraProperties styleProperties
|
getParaModifier Style{..} | Just props <- paraProperties styleProperties
|
||||||
, isBlockQuote (indentation props)
|
, isBlockQuote (indentation props)
|
||||||
(margin_left props)
|
(margin_left props)
|
||||||
= blockQuote
|
= pageBreakMaybe (paraProperties styleProperties) blockQuote
|
||||||
| otherwise
|
| otherwise
|
||||||
= id
|
= pageBreakMaybe (paraProperties styleProperties) id
|
||||||
where
|
where
|
||||||
isBlockQuote mIndent mMargin
|
isBlockQuote mIndent mMargin
|
||||||
| LengthValueMM indent <- mIndent
|
| LengthValueMM indent <- mIndent
|
||||||
|
@ -408,7 +408,19 @@ getParaModifier Style{..} | Just props <- paraProperties styleProperties
|
||||||
|
|
||||||
| otherwise
|
| otherwise
|
||||||
= False
|
= 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 :: OdtReaderSafe Blocks Blocks -> OdtReaderSafe Blocks Blocks
|
||||||
constructPara reader = proc blocks -> do
|
constructPara reader = proc blocks -> do
|
||||||
|
@ -894,7 +906,6 @@ read_reference_ref = matchingElement NsText "reference-ref"
|
||||||
$ maybeInAnchorRef
|
$ maybeInAnchorRef
|
||||||
<<< matchChildContent [] read_plain_text
|
<<< matchChildContent [] read_plain_text
|
||||||
|
|
||||||
|
|
||||||
----------------------
|
----------------------
|
||||||
-- Entry point
|
-- Entry point
|
||||||
----------------------
|
----------------------
|
||||||
|
|
|
@ -43,6 +43,7 @@ module Text.Pandoc.Readers.Odt.StyleReader
|
||||||
, TextProperties (..)
|
, TextProperties (..)
|
||||||
, ParaProperties (..)
|
, ParaProperties (..)
|
||||||
, VerticalTextPosition (..)
|
, VerticalTextPosition (..)
|
||||||
|
, ParaBreak (..)
|
||||||
, ListItemNumberFormat (..)
|
, ListItemNumberFormat (..)
|
||||||
, ListLevel
|
, ListLevel
|
||||||
, ListStyle (..)
|
, ListStyle (..)
|
||||||
|
@ -273,6 +274,7 @@ instance Default TextProperties where
|
||||||
data ParaProperties = PropP { paraNumbering :: ParaNumbering
|
data ParaProperties = PropP { paraNumbering :: ParaNumbering
|
||||||
, indentation :: LengthOrPercent
|
, indentation :: LengthOrPercent
|
||||||
, margin_left :: LengthOrPercent
|
, margin_left :: LengthOrPercent
|
||||||
|
, page_break :: ParaBreak
|
||||||
}
|
}
|
||||||
deriving ( Eq, Show )
|
deriving ( Eq, Show )
|
||||||
|
|
||||||
|
@ -280,6 +282,7 @@ instance Default ParaProperties where
|
||||||
def = PropP { paraNumbering = NumberingNone
|
def = PropP { paraNumbering = NumberingNone
|
||||||
, indentation = def
|
, indentation = def
|
||||||
, margin_left = def
|
, margin_left = def
|
||||||
|
, page_break = AutoNone
|
||||||
}
|
}
|
||||||
|
|
||||||
----
|
----
|
||||||
|
@ -314,6 +317,9 @@ instance Lookupable UnderlineMode where
|
||||||
data ParaNumbering = NumberingNone | NumberingKeep | NumberingRestart Int
|
data ParaNumbering = NumberingNone | NumberingKeep | NumberingRestart Int
|
||||||
deriving ( Eq, Show )
|
deriving ( Eq, Show )
|
||||||
|
|
||||||
|
data ParaBreak = AutoNone | PageBefore | PageAfter | PageBoth
|
||||||
|
deriving ( Eq, Show )
|
||||||
|
|
||||||
data LengthOrPercent = LengthValueMM Int | PercentValue Int
|
data LengthOrPercent = LengthValueMM Int | PercentValue Int
|
||||||
deriving ( Eq, Show )
|
deriving ( Eq, Show )
|
||||||
|
|
||||||
|
@ -533,16 +539,20 @@ readLineMode modeAttr styleAttr = proc x -> do
|
||||||
readParaProperties :: StyleReader _x ParaProperties
|
readParaProperties :: StyleReader _x ParaProperties
|
||||||
readParaProperties =
|
readParaProperties =
|
||||||
executeIn NsStyle "paragraph-properties" $ liftAsSuccess
|
executeIn NsStyle "paragraph-properties" $ liftAsSuccess
|
||||||
( liftA3 PropP
|
( liftA4 PropP
|
||||||
( liftA2 readNumbering
|
( liftA2 readNumbering
|
||||||
( isSet' NsText "number-lines" )
|
( isSet' NsText "number-lines" )
|
||||||
( readAttr' NsText "line-number" )
|
( readAttr' NsText "line-number" )
|
||||||
)
|
)
|
||||||
( liftA2 readIndentation
|
( liftA2 readIndentation
|
||||||
( isSetWithDefault NsStyle "auto-text-indent" False )
|
( isSetWithDefault NsStyle "auto-text-indent" False )
|
||||||
( getAttr NsXSL_FO "text-indent" )
|
( getAttr NsXSL_FO "text-indent" )
|
||||||
|
)
|
||||||
|
( getAttr NsXSL_FO "margin-left" )
|
||||||
|
( liftA2 readPageBreak
|
||||||
|
( findAttrWithDefault NsXSL_FO "break-before" "auto" )
|
||||||
|
( findAttrWithDefault NsXSL_FO "break-after" "auto" )
|
||||||
)
|
)
|
||||||
( getAttr NsXSL_FO "margin-left" )
|
|
||||||
)
|
)
|
||||||
where readNumbering (Just True) (Just n) = NumberingRestart n
|
where readNumbering (Just True) (Just n) = NumberingRestart n
|
||||||
readNumbering (Just True) _ = NumberingKeep
|
readNumbering (Just True) _ = NumberingKeep
|
||||||
|
@ -551,6 +561,11 @@ readParaProperties =
|
||||||
readIndentation False indent = indent
|
readIndentation False indent = indent
|
||||||
readIndentation True _ = def
|
readIndentation True _ = def
|
||||||
|
|
||||||
|
readPageBreak "page" "page" = PageBoth
|
||||||
|
readPageBreak "page" _ = PageBefore
|
||||||
|
readPageBreak _ "page" = PageAfter
|
||||||
|
readPageBreak _ _ = AutoNone
|
||||||
|
|
||||||
----
|
----
|
||||||
-- List styles
|
-- List styles
|
||||||
----
|
----
|
||||||
|
|
|
@ -36,6 +36,7 @@ import Text.Pandoc.XML
|
||||||
import Text.Pandoc.Shared (linesToPara)
|
import Text.Pandoc.Shared (linesToPara)
|
||||||
import Text.Pandoc.Templates (renderTemplate')
|
import Text.Pandoc.Templates (renderTemplate')
|
||||||
import Text.Pandoc.Readers.TeXMath
|
import Text.Pandoc.Readers.TeXMath
|
||||||
|
import Text.Pandoc.Readers.Odt.StyleReader
|
||||||
import Text.Pandoc.Pretty
|
import Text.Pandoc.Pretty
|
||||||
import Text.Printf ( printf )
|
import Text.Printf ( printf )
|
||||||
import Control.Arrow ( (***), (>>>) )
|
import Control.Arrow ( (***), (>>>) )
|
||||||
|
@ -307,9 +308,7 @@ blockToOpenDocument o bs
|
||||||
else inParagraphTags =<< inlinesToOpenDocument o b
|
else inParagraphTags =<< inlinesToOpenDocument o b
|
||||||
| Para [Image attr c (s,'f':'i':'g':':':t)] <- bs
|
| Para [Image attr c (s,'f':'i':'g':':':t)] <- bs
|
||||||
= figure attr c s t
|
= figure attr c s t
|
||||||
| Para b <- bs = if null b
|
| Para b <- bs = paragraph b
|
||||||
then return empty
|
|
||||||
else inParagraphTags =<< inlinesToOpenDocument o b
|
|
||||||
| LineBlock b <- bs = blockToOpenDocument o $ linesToPara b
|
| LineBlock b <- bs = blockToOpenDocument o $ linesToPara b
|
||||||
| Div _ xs <- bs = blocksToOpenDocument o xs
|
| Div _ xs <- bs = blocksToOpenDocument o xs
|
||||||
| Header i _ b <- bs = setFirstPara >>
|
| Header i _ b <- bs = setFirstPara >>
|
||||||
|
@ -370,6 +369,22 @@ blockToOpenDocument o bs
|
||||||
captionDoc <- withParagraphStyle o "FigureCaption" [Para caption]
|
captionDoc <- withParagraphStyle o "FigureCaption" [Para caption]
|
||||||
return $ imageDoc $$ captionDoc
|
return $ imageDoc $$ captionDoc
|
||||||
|
|
||||||
|
endsWithPageBreak [] = False
|
||||||
|
endsWithPageBreak [PageBreak] = True
|
||||||
|
endsWithPageBreak (_ : xs) = endsWithPageBreak xs
|
||||||
|
|
||||||
|
paragraph :: [Inline] -> State WriterState 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 :: ParaBreak -> [Inline] -> State WriterState Doc
|
||||||
|
paraWithBreak breakKind bs = do
|
||||||
|
pn <- paraBreakStyle breakKind
|
||||||
|
withParagraphStyle o ("P" ++ show pn) [Para bs]
|
||||||
|
|
||||||
colHeadsToOpenDocument :: WriterOptions -> String -> [String] -> [[Block]] -> State WriterState Doc
|
colHeadsToOpenDocument :: WriterOptions -> String -> [String] -> [[Block]] -> State WriterState Doc
|
||||||
colHeadsToOpenDocument o tn ns hs =
|
colHeadsToOpenDocument o tn ns hs =
|
||||||
inTagsIndented "table:table-header-rows" . inTagsIndented "table:table-row" . vcat <$>
|
inTagsIndented "table:table-header-rows" . inTagsIndented "table:table-row" . vcat <$>
|
||||||
|
@ -562,6 +577,13 @@ paraStyle attrs = do
|
||||||
addParaStyle $ inTags True "style:style" (styleAttr ++ attrs) paraProps
|
addParaStyle $ inTags True "style:style" (styleAttr ++ attrs) paraProps
|
||||||
return pn
|
return pn
|
||||||
|
|
||||||
|
paraBreakStyle :: ParaBreak -> State WriterState 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 :: Int -> State WriterState Int
|
paraListStyle :: Int -> State WriterState Int
|
||||||
paraListStyle l = paraStyle
|
paraListStyle l = paraStyle
|
||||||
[("style:parent-style-name","Text_20_body")
|
[("style:parent-style-name","Text_20_body")
|
||||||
|
|
Loading…
Add table
Reference in a new issue