diff options
author | John MacFarlane <jgm@berkeley.edu> | 2014-07-12 22:57:22 -0700 |
---|---|---|
committer | John MacFarlane <jgm@berkeley.edu> | 2014-07-12 22:57:22 -0700 |
commit | 4676bfdf825a2b5b205d6057462d317c00c6b354 (patch) | |
tree | 2d5e84a0ddec2b3c2102e6d4cec3cf03e69e1164 /src/Text/Pandoc/Readers/Docx | |
parent | 8bbcff0cfcd9923cdcf5024d13bb411d085715d0 (diff) | |
download | pandoc-4676bfdf825a2b5b205d6057462d317c00c6b354.tar.gz |
Removed space at ends of lines in source.
Diffstat (limited to 'src/Text/Pandoc/Readers/Docx')
-rw-r--r-- | src/Text/Pandoc/Readers/Docx/Lists.hs | 14 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Docx/Parse.hs | 48 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Docx/Reducible.hs | 8 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Docx/TexChar.hs | 2 |
4 files changed, 36 insertions, 36 deletions
diff --git a/src/Text/Pandoc/Readers/Docx/Lists.hs b/src/Text/Pandoc/Readers/Docx/Lists.hs index 1e37d0076..ea195c14a 100644 --- a/src/Text/Pandoc/Readers/Docx/Lists.hs +++ b/src/Text/Pandoc/Readers/Docx/Lists.hs @@ -121,7 +121,7 @@ handleListParagraphs ( in handleListParagraphs ((Div attr1 (blks1 ++ [newDiv2])) : blks) handleListParagraphs (blk:blks) = blk : (handleListParagraphs blks) - + separateBlocks' :: Block -> [[Block]] -> [[Block]] separateBlocks' blk ([] : []) = [[blk]] separateBlocks' b@(BulletList _) acc = (init acc) ++ [(last acc) ++ [b]] @@ -139,7 +139,7 @@ flatToBullets' :: Integer -> [Block] -> [Block] flatToBullets' _ [] = [] flatToBullets' num xs@(b : elems) | getLevelN b == num = b : (flatToBullets' num elems) - | otherwise = + | otherwise = let bNumId = getNumIdN b bLevel = getLevelN b (children, remaining) = @@ -162,7 +162,7 @@ flatToBullets elems = flatToBullets' (-1) elems blocksToBullets :: [Block] -> [Block] blocksToBullets blks = - bottomUp removeListDivs $ + bottomUp removeListDivs $ flatToBullets $ (handleListParagraphs blks) plainParaInlines :: Block -> [Inline] @@ -216,12 +216,12 @@ removeListDivs' blk = [blk] removeListDivs :: [Block] -> [Block] removeListDivs = concatMap removeListDivs' - + blocksToDefinitions :: [Block] -> [Block] blocksToDefinitions = blocksToDefinitions' [] [] - - - + + + diff --git a/src/Text/Pandoc/Readers/Docx/Parse.hs b/src/Text/Pandoc/Readers/Docx/Parse.hs index 4b5a11fa8..8541a1a3a 100644 --- a/src/Text/Pandoc/Readers/Docx/Parse.hs +++ b/src/Text/Pandoc/Readers/Docx/Parse.hs @@ -106,7 +106,7 @@ type NameSpaces = [(String, String)] data Docx = Docx Document deriving Show -data Document = Document NameSpaces Body +data Document = Document NameSpaces Body deriving Show data Body = Body [BodyPart] @@ -276,7 +276,7 @@ defaultRunStyle = RunStyle { isBold = False , isSubScript = False , rUnderline = Nothing , rStyle = Nothing - } + } type Target = String @@ -286,7 +286,7 @@ type BookMarkId = String type RelId = String type ChangeId = String type Author = String -type ChangeDate = String +type ChangeDate = String attrToNSPair :: Attr -> Maybe (String, String) attrToNSPair (Attr (QName s _ (Just "xmlns")) val) = Just (s, val) @@ -301,18 +301,18 @@ archiveToDocx archive = do rEnv = ReaderEnv notes numbering rels media doc <- runD (archiveToDocument archive) rEnv return $ Docx doc - + archiveToDocument :: Archive -> D Document archiveToDocument zf = do entry <- maybeToD $ findEntryByPath "word/document.xml" zf docElem <- maybeToD $ (parseXMLDoc . UTF8.toStringLazy . fromEntry) entry - let namespaces = mapMaybe attrToNSPair (elAttribs docElem) + let namespaces = mapMaybe attrToNSPair (elAttribs docElem) bodyElem <- maybeToD $ findChild (elemName namespaces "w" "body") docElem body <- elemToBody namespaces bodyElem return $ Document namespaces body -elemToBody :: NameSpaces -> Element -> D Body +elemToBody :: NameSpaces -> Element -> D Body elemToBody ns element | isElem ns "w" "body" element = mapD (elemToBodyPart ns) (elChildren element) >>= (\bps -> return $ Body bps) @@ -349,10 +349,10 @@ relElemToRelationship element | qName (elName element) == "Relationship" = target <- findAttr (QName "Target" Nothing Nothing) element return $ Relationship (relId, target) relElemToRelationship _ = Nothing - + archiveToRelationships :: Archive -> [Relationship] -archiveToRelationships archive = +archiveToRelationships archive = let relPaths = filter filePathIsRel (filesInArchive archive) entries = mapMaybe (\f -> findEntryByPath f archive) relPaths relElems = mapMaybe (parseXMLDoc . UTF8.toStringLazy . fromEntry) entries @@ -445,7 +445,7 @@ archiveToNumbering archive = elemToNotes :: NameSpaces -> String -> Element -> Maybe (M.Map String Element) elemToNotes ns notetype element - | isElem ns "w" (notetype ++ "s") element = + | isElem ns "w" (notetype ++ "s") element = let pairs = mapMaybe (\e -> findAttr (elemName ns "w" "id") e >>= (\a -> Just (a, e))) @@ -478,7 +478,7 @@ elemToTblLook :: NameSpaces -> Element -> D TblLook elemToTblLook ns element | isElem ns "w" "tblLook" element = let firstRow = findAttr (elemName ns "w" "firstRow") element val = findAttr (elemName ns "w" "val") element - firstRowFmt = + firstRowFmt = case firstRow of Just "1" -> True Just _ -> False @@ -505,15 +505,15 @@ elemToCell ns element | isElem ns "w" "tc" element = elemToCell _ _ = throwError WrongElem elemToParIndentation :: NameSpaces -> Element -> Maybe ParIndentation -elemToParIndentation ns element | isElem ns "w" "ind" element = +elemToParIndentation ns element | isElem ns "w" "ind" element = Just $ ParIndentation { leftParIndent = findAttr (QName "left" (lookup "w" ns) (Just "w")) element >>= stringToInteger - , rightParIndent = + , rightParIndent = findAttr (QName "right" (lookup "w" ns) (Just "w")) element >>= stringToInteger - , hangingParIndent = + , hangingParIndent = findAttr (QName "hanging" (lookup "w" ns) (Just "w")) element >>= stringToInteger} elemToParIndentation _ _ = Nothing @@ -558,7 +558,7 @@ elemToBodyPart ns element case lookupLevel numId lvl num of Just levelInfo -> return $ ListItem parstyle numId lvl levelInfo parparts Nothing -> throwError WrongElem -elemToBodyPart ns element +elemToBodyPart ns element | isElem ns "w" "p" element = do let parstyle = elemToParagraphStyle ns element parparts <- mapD (elemToParPart ns) (elChildren element) @@ -667,15 +667,15 @@ elemToMathElem ns element | isElem ns "m" "bar" element = do base <-maybeToD (findChild (QName "e" (lookup "m" ns) (Just "m")) element) >>= elemToBase ns return $ Bar barPr base -elemToMathElem ns element | isElem ns "m" "box" element = +elemToMathElem ns element | isElem ns "m" "box" element = maybeToD (findChild (elemName ns "m" "e") element) >>= elemToBase ns >>= (\b -> return $ Box b) -elemToMathElem ns element | isElem ns "m" "borderBox" element = +elemToMathElem ns element | isElem ns "m" "borderBox" element = maybeToD (findChild (elemName ns "m" "e") element) >>= elemToBase ns >>= (\b -> return $ BorderBox b) -elemToMathElem ns element | isElem ns "m" "d" element = +elemToMathElem ns element | isElem ns "m" "d" element = let style = elemToDelimStyle ns element in mapD (elemToBase ns) (elChildren element) >>= @@ -684,8 +684,8 @@ elemToMathElem ns element | isElem ns "m" "eqArr" element = mapD (elemToBase ns) (elChildren element) >>= (\es -> return $ EquationArray es) elemToMathElem ns element | isElem ns "m" "f" element = do - num <- maybeToD $ findChild (elemName ns "m" "num") element - den <- maybeToD $ findChild (elemName ns "m" "den") element + num <- maybeToD $ findChild (elemName ns "m" "num") element + den <- maybeToD $ findChild (elemName ns "m" "den") element numElems <- mapD (elemToMathElem ns) (elChildren num) denElems <- mapD (elemToMathElem ns) (elChildren den) return $ Fraction numElems denElems @@ -695,7 +695,7 @@ elemToMathElem ns element | isElem ns "m" "func" element = do elemToBase ns fnElems <- mapD (elemToMathElem ns) (elChildren fName) return $ Function fnElems base -elemToMathElem ns element | isElem ns "m" "groupChr" element = +elemToMathElem ns element | isElem ns "m" "groupChr" element = let style = elemToGroupStyle ns element in maybeToD (findChild (elemName ns "m" "e") element) >>= @@ -920,11 +920,11 @@ elemToRunElems ns element elemToRunElems _ _ = throwError WrongElem - - - - + + + + diff --git a/src/Text/Pandoc/Readers/Docx/Reducible.hs b/src/Text/Pandoc/Readers/Docx/Reducible.hs index 8c105d1f1..e8e407844 100644 --- a/src/Text/Pandoc/Readers/Docx/Reducible.hs +++ b/src/Text/Pandoc/Readers/Docx/Reducible.hs @@ -90,7 +90,7 @@ combineReducibles r s = True -> case (not . null) rs && isSpace (last rs) of True -> rebuild conts (init rs) ++ [last rs, s] False -> [r,s] - False -> rebuild + False -> rebuild shared $ reduceList $ (rebuild remaining rs) ++ (rebuild remaining' ss) @@ -145,7 +145,7 @@ instance Reducible Inline where isSpace _ = False instance Reducible Block where - (Div (ident, classes, kvs) blks) <++> blk | "list-item" `elem` classes = + (Div (ident, classes, kvs) blks) <++> blk | "list-item" `elem` classes = [Div (ident, classes, kvs) (reduceList blks), blk] blk <++> blk' = combineReducibles blk blk' @@ -177,5 +177,5 @@ rebuild :: [Container a] -> [a] -> [a] rebuild [] xs = xs rebuild ((Container f) : cs) xs = rebuild cs $ [f xs] rebuild (NullContainer : cs) xs = rebuild cs $ xs - - + + diff --git a/src/Text/Pandoc/Readers/Docx/TexChar.hs b/src/Text/Pandoc/Readers/Docx/TexChar.hs index 1bef8d7da..eddcabecc 100644 --- a/src/Text/Pandoc/Readers/Docx/TexChar.hs +++ b/src/Text/Pandoc/Readers/Docx/TexChar.hs @@ -4382,5 +4382,5 @@ uniconvMap = M.fromList [ ('\8193', "\\quad") -- , ('\120829', "\\mttseven") -- , ('\120830', "\\mtteight") -- , ('\120831', "\\mttnine") - + -- ] |