@@ -74,9 +74,6 @@ type TWParser = ParserT [Char] ParserState
7474tryMsg :: String -> TWParser m a -> TWParser m a
7575tryMsg msg p = try p <?> msg
7676
77- skip :: TWParser m a -> TWParser m ()
78- skip parser = parser >> return ()
79-
8077nested :: PandocMonad m => TWParser m a -> TWParser m a
8178nested p = do
8279 nestlevel <- stateMaxNestingLevel <$> getState
@@ -92,7 +89,7 @@ htmlElement tag = tryMsg tag $ do
9289 content <- manyTill anyChar (endtag <|> endofinput)
9390 return (htmlAttrToPandoc attr, trim content)
9491 where
95- endtag = skip $ htmlTag (~== TagClose tag)
92+ endtag = void $ htmlTag (~== TagClose tag)
9693 endofinput = lookAhead $ try $ skipMany blankline >> skipSpaces >> eof
9794 trim = dropWhile (== ' \n ' ) . reverse . dropWhile (== ' \n ' ) . reverse
9895
@@ -114,18 +111,15 @@ parseHtmlContentWithAttrs tag parser = do
114111 endOfContent = try $ skipMany blankline >> skipSpaces >> eof
115112
116113parseHtmlContent :: PandocMonad m => String -> TWParser m a -> TWParser m [a ]
117- parseHtmlContent tag p = parseHtmlContentWithAttrs tag p >>= return . snd
114+ parseHtmlContent tag p = snd <$> parseHtmlContentWithAttrs tag p
118115
119116--
120117-- main parser
121118--
122119
123120parseTWiki :: PandocMonad m => TWParser m Pandoc
124- parseTWiki = do
125- bs <- mconcat <$> many block
126- spaces
127- eof
128- return $ B. doc bs
121+ parseTWiki =
122+ B. doc . mconcat <$> many block <* spaces <* eof
129123
130124
131125--
@@ -158,7 +152,7 @@ separator = tryMsg "separator" $ string "---" >> newline >> return B.horizontalR
158152header :: PandocMonad m => TWParser m B. Blocks
159153header = tryMsg " header" $ do
160154 string " ---"
161- level <- many1 (char ' +' ) >>= return . length
155+ level <- length <$> many1 (char ' +' )
162156 guard $ level <= 6
163157 classes <- option [] $ string " !!" >> return [" unnumbered" ]
164158 skipSpaces
@@ -167,11 +161,10 @@ header = tryMsg "header" $ do
167161 return $ B. headerWith attr level content
168162
169163verbatim :: PandocMonad m => TWParser m B. Blocks
170- verbatim = (htmlElement " verbatim" <|> htmlElement " pre" )
171- >>= return . (uncurry B. codeBlockWith)
164+ verbatim = uncurry B. codeBlockWith <$> (htmlElement " verbatim" <|> htmlElement " pre" )
172165
173166literal :: PandocMonad m => TWParser m B. Blocks
174- literal = htmlElement " literal" >>= return . rawBlock
167+ literal = rawBlock <$> htmlElement " literal"
175168 where
176169 format (_, _, kvs) = fromMaybe " html" $ lookup " format" kvs
177170 rawBlock (attrs, content) = B. rawBlock (format attrs) content
@@ -183,7 +176,7 @@ list prefix = choice [ bulletList prefix
183176
184177definitionList :: PandocMonad m => String -> TWParser m B. Blocks
185178definitionList prefix = tryMsg " definitionList" $ do
186- indent <- lookAhead $ string prefix *> ( many1 $ string " " ) <* string " $ "
179+ indent <- lookAhead $ string prefix *> many1 ( string " " ) <* string " $ "
187180 elements <- many $ parseDefinitionListItem (prefix ++ concat indent)
188181 return $ B. definitionList elements
189182 where
@@ -193,7 +186,7 @@ definitionList prefix = tryMsg "definitionList" $ do
193186 string (indent ++ " $ " ) >> skipSpaces
194187 term <- many1Till inline $ string " : "
195188 line <- listItemLine indent $ string " $ "
196- return $ (mconcat term, [line])
189+ return (mconcat term, [line])
197190
198191bulletList :: PandocMonad m => String -> TWParser m B. Blocks
199192bulletList prefix = tryMsg " bulletList" $
@@ -227,25 +220,24 @@ parseListItem prefix marker = string prefix >> marker >> listItemLine prefix mar
227220
228221listItemLine :: (PandocMonad m , Show a )
229222 => String -> TWParser m a -> TWParser m B. Blocks
230- listItemLine prefix marker = lineContent >>= parseContent >>= return . mconcat
223+ listItemLine prefix marker = mconcat <$> (lineContent >>= parseContent)
231224 where
232225 lineContent = do
233226 content <- anyLine
234227 continuation <- optionMaybe listContinuation
235- return $ filterSpaces content ++ " \n " ++ ( maybe " " (" " ++ ) continuation)
228+ return $ filterSpaces content ++ " \n " ++ maybe " " (" " ++ ) continuation
236229 filterSpaces = reverse . dropWhile (== ' ' ) . reverse
237230 listContinuation = notFollowedBy (string prefix >> marker) >>
238231 string " " >> lineContent
239232 parseContent = parseFromString' $ many1 $ nestedList <|> parseInline
240- parseInline = many1Till inline (lastNewline <|> newlineBeforeNestedList) >>=
241- return . B. plain . mconcat
233+ parseInline = (B. plain . mconcat ) <$> many1Till inline (lastNewline <|> newlineBeforeNestedList)
242234 nestedList = list prefix
243235 lastNewline = try $ char ' \n ' <* eof
244236 newlineBeforeNestedList = try $ char ' \n ' <* lookAhead nestedList
245237
246238table :: PandocMonad m => TWParser m B. Blocks
247239table = try $ do
248- tableHead <- optionMaybe $ many1Till tableParseHeader newline >>= return . unzip
240+ tableHead <- optionMaybe ( unzip <$> many1Till tableParseHeader newline)
249241 rows <- many1 tableParseRow
250242 return $ buildTable mempty rows $ fromMaybe (align rows, columns rows) tableHead
251243 where
@@ -258,11 +250,11 @@ table = try $ do
258250tableParseHeader :: PandocMonad m => TWParser m ((Alignment , Double ), B. Blocks )
259251tableParseHeader = try $ do
260252 char ' |'
261- leftSpaces <- many spaceChar >>= return . length
253+ leftSpaces <- length <$> many spaceChar
262254 char ' *'
263255 content <- tableColumnContent (char ' *' >> skipSpaces >> char ' |' )
264256 char ' *'
265- rightSpaces <- many spaceChar >>= return . length
257+ rightSpaces <- length <$> many spaceChar
266258 optional tableEndOfRow
267259 return (tableAlign leftSpaces rightSpaces, content)
268260 where
@@ -283,13 +275,13 @@ tableEndOfRow :: PandocMonad m => TWParser m Char
283275tableEndOfRow = lookAhead (try $ char ' |' >> char ' \n ' ) >> char ' |'
284276
285277tableColumnContent :: PandocMonad m => TWParser m a -> TWParser m B. Blocks
286- tableColumnContent end = manyTill content (lookAhead $ try end) >>= return . B. plain . mconcat
278+ tableColumnContent end = ( B. plain . mconcat ) <$> manyTill content (lookAhead $ try end)
287279 where
288280 content = continuation <|> inline
289281 continuation = try $ char ' \\ ' >> newline >> return mempty
290282
291283blockQuote :: PandocMonad m => TWParser m B. Blocks
292- blockQuote = parseHtmlContent " blockquote " block >>= return . B. blockQuote . mconcat
284+ blockQuote = ( B. blockQuote . mconcat ) <$> parseHtmlContent " blockquote " block
293285
294286noautolink :: PandocMonad m => TWParser m B. Blocks
295287noautolink = do
@@ -300,15 +292,15 @@ noautolink = do
300292 setState $ st{ stateAllowLinks = True }
301293 return $ mconcat blocks
302294 where
303- parseContent = parseFromString' $ many $ block
295+ parseContent = parseFromString' $ many block
304296
305297para :: PandocMonad m => TWParser m B. Blocks
306- para = many1Till inline endOfParaElement >>= return . result . mconcat
298+ para = (result . mconcat ) <$> many1Till inline endOfParaElement
307299 where
308300 endOfParaElement = lookAhead $ endOfInput <|> endOfPara <|> newBlockElement
309301 endOfInput = try $ skipMany blankline >> skipSpaces >> eof
310302 endOfPara = try $ blankline >> skipMany1 blankline
311- newBlockElement = try $ blankline >> skip blockElements
303+ newBlockElement = try $ blankline >> void blockElements
312304 result content = if F. all (== Space ) content
313305 then mempty
314306 else B. para $ B. trimInlines content
@@ -340,7 +332,7 @@ inline = choice [ whitespace
340332 ] <?> " inline"
341333
342334whitespace :: PandocMonad m => TWParser m B. Inlines
343- whitespace = ( lb <|> regsp) >>= return
335+ whitespace = lb <|> regsp
344336 where lb = try $ skipMany spaceChar >> linebreak >> return B. space
345337 regsp = try $ skipMany1 spaceChar >> return B. space
346338
@@ -362,13 +354,13 @@ enclosed :: (Monoid b, PandocMonad m, Show a)
362354 => TWParser m a -> (TWParser m a -> TWParser m b ) -> TWParser m b
363355enclosed sep p = between sep (try $ sep <* endMarker) p
364356 where
365- endMarker = lookAhead $ skip endSpace <|> skip (oneOf " .,!?:)|" ) <|> eof
357+ endMarker = lookAhead $ void endSpace <|> void (oneOf " .,!?:)|" ) <|> eof
366358 endSpace = (spaceChar <|> newline) >> return B. space
367359
368360macro :: PandocMonad m => TWParser m B. Inlines
369361macro = macroWithParameters <|> withoutParameters
370362 where
371- withoutParameters = enclosed (char ' %' ) (\ _ -> macroName) >>= return . emptySpan
363+ withoutParameters = emptySpan <$> enclosed (char ' %' ) (const macroName)
372364 emptySpan name = buildSpan name [] mempty
373365
374366macroWithParameters :: PandocMonad m => TWParser m B. Inlines
@@ -393,66 +385,64 @@ macroName = do
393385 return (first: rest)
394386
395387attributes :: PandocMonad m => TWParser m (String , [(String , String )])
396- attributes = char ' { ' *> spnl *> many (attribute <* spnl) <* char ' } ' >>=
397- return . foldr ( either mkContent mkKvs) ( [] , [] )
388+ attributes = foldr ( either mkContent mkKvs) ( [] , [] )
389+ <$> (char ' { ' *> spnl *> many (attribute <* spnl) <* char ' } ' )
398390 where
399391 spnl = skipMany (spaceChar <|> newline)
400392 mkContent c ([] , kvs) = (c, kvs)
401393 mkContent c (rest, kvs) = (c ++ " " ++ rest, kvs)
402- mkKvs kv (cont, rest) = (cont, ( kv : rest) )
394+ mkKvs kv (cont, rest) = (cont, kv : rest)
403395
404396attribute :: PandocMonad m => TWParser m (Either String (String , String ))
405397attribute = withKey <|> withoutKey
406398 where
407399 withKey = try $ do
408400 key <- macroName
409401 char ' ='
410- parseValue False >>= return . ( curry Right key)
411- withoutKey = try $ parseValue True >>= return . Left
412- parseValue allowSpaces = (withQuotes <|> withoutQuotes allowSpaces) >>= return . fromEntities
402+ curry Right key <$> parseValue False
403+ withoutKey = try $ Left <$> parseValue True
404+ parseValue allowSpaces = fromEntities <$> (withQuotes <|> withoutQuotes allowSpaces)
413405 withQuotes = between (char ' "' ) (char ' "' ) (\ _ -> count 1 $ noneOf [' "' ])
414406 withoutQuotes allowSpaces
415- | allowSpaces == True = many1 $ noneOf " }"
416- | otherwise = many1 $ noneOf " }"
407+ | allowSpaces = many1 $ noneOf " }"
408+ | otherwise = many1 $ noneOf " }"
417409
418410nestedInlines :: (Show a , PandocMonad m )
419411 => TWParser m a -> TWParser m B. Inlines
420412nestedInlines end = innerSpace <|> nestedInline
421413 where
422- innerSpace = try $ whitespace <* ( notFollowedBy end)
414+ innerSpace = try $ whitespace <* notFollowedBy end
423415 nestedInline = notFollowedBy whitespace >> nested inline
424416
425417strong :: PandocMonad m => TWParser m B. Inlines
426- strong = try $ enclosed (char ' *' ) nestedInlines >>= return . B. strong
418+ strong = try $ B. strong <$> enclosed (char ' *' ) nestedInlines
427419
428420strongHtml :: PandocMonad m => TWParser m B. Inlines
429- strongHtml = (parseHtmlContent " strong" inline <|> parseHtmlContent " b" inline)
430- >>= return . B. strong . mconcat
421+ strongHtml = B. strong . mconcat <$> (parseHtmlContent " strong" inline <|> parseHtmlContent " b" inline)
431422
432423strongAndEmph :: PandocMonad m => TWParser m B. Inlines
433- strongAndEmph = try $ enclosed (string " __" ) nestedInlines >>= return . B. emph . B. strong
424+ strongAndEmph = try $ B. emph . B. strong <$> enclosed (string " __" ) nestedInlines
434425
435426emph :: PandocMonad m => TWParser m B. Inlines
436- emph = try $ enclosed (char ' _' ) nestedInlines >>= return . B. emph
427+ emph = try $ B. emph <$> enclosed (char ' _' ) nestedInlines
437428
438429emphHtml :: PandocMonad m => TWParser m B. Inlines
439- emphHtml = (parseHtmlContent " em" inline <|> parseHtmlContent " i" inline)
440- >>= return . B. emph . mconcat
430+ emphHtml = B. emph . mconcat <$> (parseHtmlContent " em" inline <|> parseHtmlContent " i" inline)
441431
442432nestedString :: (Show a , PandocMonad m )
443433 => TWParser m a -> TWParser m String
444- nestedString end = innerSpace <|> ( count 1 nonspaceChar)
434+ nestedString end = innerSpace <|> count 1 nonspaceChar
445435 where
446436 innerSpace = try $ many1 spaceChar <* notFollowedBy end
447437
448438boldCode :: PandocMonad m => TWParser m B. Inlines
449- boldCode = try $ enclosed (string " == " ) nestedString >>= return . B. strong . B. code . fromEntities
439+ boldCode = try $ ( B. strong . B. code . fromEntities) <$> enclosed (string " == " ) nestedString
450440
451441htmlComment :: PandocMonad m => TWParser m B. Inlines
452442htmlComment = htmlTag isCommentTag >> return mempty
453443
454444code :: PandocMonad m => TWParser m B. Inlines
455- code = try $ enclosed (char ' =' ) nestedString >>= return . B. code . fromEntities
445+ code = try $ ( B. code . fromEntities) <$> enclosed (char ' =' ) nestedString
456446
457447codeHtml :: PandocMonad m => TWParser m B. Inlines
458448codeHtml = do
@@ -464,7 +454,7 @@ autoLink = try $ do
464454 state <- getState
465455 guard $ stateAllowLinks state
466456 (text, url) <- parseLink
467- guard $ checkLink (head $ reverse url)
457+ guard $ checkLink (last url)
468458 return $ makeLink (text, url)
469459 where
470460 parseLink = notFollowedBy nop >> (uri <|> emailAddress)
@@ -474,17 +464,17 @@ autoLink = try $ do
474464 | otherwise = isAlphaNum c
475465
476466str :: PandocMonad m => TWParser m B. Inlines
477- str = (many1 alphaNum <|> count 1 characterReference) >>= return . B. str
467+ str = B. str <$> (many1 alphaNum <|> count 1 characterReference)
478468
479469nop :: PandocMonad m => TWParser m B. Inlines
480- nop = try $ (skip exclamation <|> skip nopTag) >> followContent
470+ nop = try $ (void exclamation <|> void nopTag) >> followContent
481471 where
482472 exclamation = char ' !'
483473 nopTag = stringAnyCase " <nop>"
484- followContent = many1 nonspaceChar >>= return . B. str . fromEntities
474+ followContent = B. str . fromEntities <$> many1 nonspaceChar
485475
486476symbol :: PandocMonad m => TWParser m B. Inlines
487- symbol = count 1 nonspaceChar >>= return . B. str
477+ symbol = B. str <$> count 1 nonspaceChar
488478
489479smart :: PandocMonad m => TWParser m B. Inlines
490480smart = do
@@ -498,17 +488,16 @@ smart = do
498488singleQuoted :: PandocMonad m => TWParser m B. Inlines
499489singleQuoted = try $ do
500490 singleQuoteStart
501- withQuoteContext InSingleQuote $
502- many1Till inline singleQuoteEnd >>=
503- (return . B. singleQuoted . B. trimInlines . mconcat )
491+ withQuoteContext InSingleQuote
492+ (B. singleQuoted . B. trimInlines . mconcat <$> many1Till inline singleQuoteEnd)
504493
505494doubleQuoted :: PandocMonad m => TWParser m B. Inlines
506495doubleQuoted = try $ do
507496 doubleQuoteStart
508497 contents <- mconcat <$> many (try $ notFollowedBy doubleQuoteEnd >> inline)
509- ( withQuoteContext InDoubleQuote $ doubleQuoteEnd >>
498+ withQuoteContext InDoubleQuote ( doubleQuoteEnd >>
510499 return (B. doubleQuoted $ B. trimInlines contents))
511- <|> ( return $ (B. str " \8220" ) B. <> contents)
500+ <|> return (B. str " \8220" B. <> contents)
512501
513502link :: PandocMonad m => TWParser m B. Inlines
514503link = try $ do
@@ -527,5 +516,5 @@ linkText = do
527516 char ' ]'
528517 return (url, " " , content)
529518 where
530- linkContent = ( char ' [' ) >> many1Till anyChar (char ' ]' ) >>= parseLinkContent
519+ linkContent = char ' [' >> many1Till anyChar (char ' ]' ) >>= parseLinkContent
531520 parseLinkContent = parseFromString' $ many1 inline
0 commit comments