aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Readers/Docx
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Readers/Docx')
-rw-r--r--src/Text/Pandoc/Readers/Docx/Fields.hs8
-rw-r--r--src/Text/Pandoc/Readers/Docx/Lists.hs8
-rw-r--r--src/Text/Pandoc/Readers/Docx/Parse.hs11
3 files changed, 12 insertions, 15 deletions
diff --git a/src/Text/Pandoc/Readers/Docx/Fields.hs b/src/Text/Pandoc/Readers/Docx/Fields.hs
index 69758b431..f0821a751 100644
--- a/src/Text/Pandoc/Readers/Docx/Fields.hs
+++ b/src/Text/Pandoc/Readers/Docx/Fields.hs
@@ -46,7 +46,7 @@ parseFieldInfo = parse fieldInfo ""
fieldInfo :: Parser FieldInfo
fieldInfo =
- (try $ HyperlinkField <$> hyperlink)
+ try (HyperlinkField <$> hyperlink)
<|>
return UnknownField
@@ -54,7 +54,7 @@ escapedQuote :: Parser String
escapedQuote = string "\\\""
inQuotes :: Parser String
-inQuotes = do
+inQuotes =
(try escapedQuote) <|> (anyChar >>= (\c -> return [c]))
quotedString :: Parser String
@@ -63,7 +63,7 @@ quotedString = do
concat <$> manyTill inQuotes (try (char '"'))
unquotedString :: Parser String
-unquotedString = manyTill anyChar (try (space))
+unquotedString = manyTill anyChar (try space)
fieldArgument :: Parser String
fieldArgument = quotedString <|> unquotedString
@@ -82,7 +82,7 @@ hyperlink = do
string "HYPERLINK"
spaces
farg <- fieldArgument
- switches <- (spaces *> many hyperlinkSwitch)
+ switches <- spaces *> many hyperlinkSwitch
let url = case switches of
("\\l", s) : _ -> farg ++ ('#': s)
_ -> farg
diff --git a/src/Text/Pandoc/Readers/Docx/Lists.hs b/src/Text/Pandoc/Readers/Docx/Lists.hs
index fa4870fff..c0f05094a 100644
--- a/src/Text/Pandoc/Readers/Docx/Lists.hs
+++ b/src/Text/Pandoc/Readers/Docx/Lists.hs
@@ -44,14 +44,14 @@ isListItem (Div (_, classes, _) _) | "list-item" `elem` classes = True
isListItem _ = False
getLevel :: Block -> Maybe Integer
-getLevel (Div (_, _, kvs) _) = fmap read $ lookup "level" kvs
+getLevel (Div (_, _, kvs) _) = read <$> lookup "level" kvs
getLevel _ = Nothing
getLevelN :: Block -> Integer
getLevelN b = fromMaybe (-1) (getLevel b)
getNumId :: Block -> Maybe Integer
-getNumId (Div (_, _, kvs) _) = fmap read $ lookup "num-id" kvs
+getNumId (Div (_, _, kvs) _) = read <$> lookup "num-id" kvs
getNumId _ = Nothing
getNumIdN :: Block -> Integer
@@ -140,8 +140,8 @@ flatToBullets' num xs@(b : elems)
(children, remaining) =
span
(\b' ->
- (getLevelN b') > bLevel ||
- ((getLevelN b') == bLevel && (getNumIdN b') == bNumId))
+ getLevelN b' > bLevel ||
+ (getLevelN b' == bLevel && getNumIdN b' == bNumId))
xs
in
case getListType b of
diff --git a/src/Text/Pandoc/Readers/Docx/Parse.hs b/src/Text/Pandoc/Readers/Docx/Parse.hs
index 5f648666f..c123a0018 100644
--- a/src/Text/Pandoc/Readers/Docx/Parse.hs
+++ b/src/Text/Pandoc/Readers/Docx/Parse.hs
@@ -358,9 +358,7 @@ archiveToDocument zf = do
docElem <- maybeToD $ (parseXMLDoc . UTF8.toStringLazy . fromEntry) entry
let namespaces = elemToNameSpaces docElem
bodyElem <- maybeToD $ findChildByName namespaces "w" "body" docElem
- let bodyElem' = case walkDocument namespaces bodyElem of
- Just e -> e
- Nothing -> bodyElem
+ let bodyElem' = fromMaybe bodyElem (walkDocument namespaces bodyElem)
body <- elemToBody namespaces bodyElem'
return $ Document namespaces body
@@ -603,7 +601,7 @@ elemToTblLook ns element | isElem ns "w" "tblLook" element =
Just bitMask -> testBitMask bitMask 0x020
Nothing -> False
in
- return $ TblLook{firstRowFormatting = firstRowFmt}
+ return TblLook{firstRowFormatting = firstRowFmt}
elemToTblLook _ _ = throwError WrongElem
elemToRow :: NameSpaces -> Element -> D Row
@@ -623,7 +621,7 @@ elemToCell _ _ = throwError WrongElem
elemToParIndentation :: NameSpaces -> Element -> Maybe ParIndentation
elemToParIndentation ns element | isElem ns "w" "ind" element =
- Just $ ParIndentation {
+ Just ParIndentation {
leftParIndent =
findAttrByName ns "w" "left" element >>=
stringToInteger
@@ -1173,8 +1171,7 @@ elemToRunElems ns element
let font = do
fontElem <- findElement (qualName "rFonts") element
stringToFont =<<
- foldr (<|>) Nothing (
- map (flip findAttr fontElem . qualName) ["ascii", "hAnsi"])
+ foldr ((<|>) . (flip findAttr fontElem . qualName)) Nothing ["ascii", "hAnsi"]
local (setFont font) (mapD (elemToRunElem ns) (elChildren element))
elemToRunElems _ _ = throwError WrongElem