Merge pull request #1386 from jkr/hanging_indent

Fix hanging indent behavior
This commit is contained in:
John MacFarlane 2014-06-29 21:31:44 -07:00
commit aad618d9db
5 changed files with 58 additions and 15 deletions

View file

@ -94,6 +94,7 @@ import System.FilePath (combine)
import qualified Data.Map as M
import Control.Monad.Reader
import Control.Monad.State
import Control.Applicative (liftA2)
readDocx :: ReaderOptions
-> B.ByteString
@ -153,7 +154,6 @@ runStyleToContainers rPr =
in
classContainers ++ formatters
divAttrToContainers :: [String] -> [(String, String)] -> [Container Block]
divAttrToContainers (c:cs) _ | Just n <- isHeaderClass c =
[Container $ \_ ->
@ -171,22 +171,37 @@ divAttrToContainers (c:cs) kvs | c `elem` listParagraphDivs =
divAttrToContainers (c:cs) kvs | c `elem` blockQuoteDivs =
(Container BlockQuote) : (divAttrToContainers (cs \\ blockQuoteDivs) kvs)
divAttrToContainers (_:cs) kvs = divAttrToContainers cs kvs
divAttrToContainers [] kvs | Just numString <- lookup "indent" kvs =
let kvs' = filter (\(k,_) -> k /= "indent") kvs
divAttrToContainers [] kvs | Just _ <- lookup "indent" kvs
, Just flInd <- lookup "first-line-indent" kvs =
let
kvs' = filter (\(k,_) -> notElem k ["indent", "first-line-indent"]) kvs
in
case numString of
"0" -> divAttrToContainers [] kvs'
('-' : _) -> divAttrToContainers [] kvs'
_ -> (Container BlockQuote) : divAttrToContainers [] kvs'
case flInd of
"0" -> divAttrToContainers [] kvs'
('-':_) -> divAttrToContainers [] kvs'
_ -> (Container BlockQuote) : divAttrToContainers [] kvs'
divAttrToContainers [] kvs | Just ind <- lookup "indent" kvs =
let
kvs' = filter (\(k,_) -> notElem k ["indent"]) kvs
in
case ind of
"0" -> divAttrToContainers [] kvs'
('-':_) -> divAttrToContainers [] kvs'
_ -> (Container BlockQuote) : divAttrToContainers [] kvs'
divAttrToContainers _ _ = []
parStyleToContainers :: ParagraphStyle -> [Container Block]
parStyleToContainers pPr =
let classes = pStyle pPr
kvs = case indent pPr of
Just n -> [("indent", show n)]
Nothing -> []
indent = indentation pPr >>= leftParIndent
hanging = indentation pPr >>= hangingParIndent
firstLineIndent = liftA2 (-) indent hanging
kvs = mapMaybe id
[ indent >>= (\n -> Just ("indent", show n)),
firstLineIndent >>= (\n -> Just ("first-line-indent", show n))
]
in
divAttrToContainers classes kvs

View file

@ -42,6 +42,7 @@ module Text.Pandoc.Readers.Docx.Parse ( Docx(..)
, Relationship
, Media
, RunStyle(..)
, ParIndentation(..)
, ParagraphStyle(..)
, Row(..)
, Cell(..)
@ -341,16 +342,37 @@ testBitMask bitMaskS n =
[] -> False
((n', _) : _) -> ((n' .|. n) /= 0)
data ParIndentation = ParIndentation { leftParIndent :: Maybe Integer
, rightParIndent :: Maybe Integer
, hangingParIndent :: Maybe Integer}
deriving Show
data ParagraphStyle = ParagraphStyle { pStyle :: [String]
, indent :: Maybe Integer
, indentation :: Maybe ParIndentation
}
deriving Show
defaultParagraphStyle :: ParagraphStyle
defaultParagraphStyle = ParagraphStyle { pStyle = []
, indent = Nothing
, indentation = Nothing
}
elemToParIndentation :: NameSpaces -> Element -> Maybe ParIndentation
elemToParIndentation ns element
| qName (elName element) == "ind" &&
qURI (elName element) == (lookup "w" ns) =
Just $ ParIndentation {
leftParIndent =
findAttr (QName "left" (lookup "w" ns) (Just "w")) element >>=
stringToInteger
, rightParIndent =
findAttr (QName "right" (lookup "w" ns) (Just "w")) element >>=
stringToInteger
, hangingParIndent =
findAttr (QName "hanging" (lookup "w" ns) (Just "w")) element >>=
stringToInteger}
elemToParIndentation _ _ = Nothing
elemToParagraphStyle :: NameSpaces -> Element -> ParagraphStyle
elemToParagraphStyle ns element =
case findChild (QName "pPr" (lookup "w" ns) (Just "w")) element of
@ -360,10 +382,9 @@ elemToParagraphStyle ns element =
mapMaybe
(findAttr (QName "val" (lookup "w" ns) (Just "w")))
(findChildren (QName "pStyle" (lookup "w" ns) (Just "w")) pPr)
, indent =
, indentation =
findChild (QName "ind" (lookup "w" ns) (Just "w")) pPr >>=
findAttr (QName "left" (lookup "w" ns) (Just "w")) >>=
stringToInteger
elemToParIndentation ns
}
Nothing -> defaultParagraphStyle

View file

@ -112,6 +112,10 @@ tests = [ testGroup "inlines"
"blockquotes (parsing indent as blockquote)"
"docx.block_quotes.docx"
"docx.block_quotes_parse_indent.native"
, testCompare
"hanging indents"
"docx.hanging_indent.docx"
"docx.hanging_indent.native"
, testCompare
"tables"
"docx.tables.docx"

Binary file not shown.

View file

@ -0,0 +1,3 @@
[Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "hanging",Space,Str "indent,",Space,Str "with",Space,Str "the",Space,Str "left",Space,Str "side",Space,Str "set",Space,Str "to",Space,Str "the",Space,Str "left",Space,Str "margin,",Space,Str "and",Space,Str "it",Space,Str "wraps",Space,Str "around",Space,Str "the",Space,Str "line."]
,BlockQuote
[Para [Str "Five",Space,Str "years",Space,Str "have",Space,Str "passed,",Space,Str "five",Space,Str "summers",Space,Str "with",Space,Str "the",Space,Str "length"]]]