diff options
author | Christian Despres <50160106+despresc@users.noreply.github.com> | 2020-09-13 10:48:14 -0400 |
---|---|---|
committer | GitHub <noreply@github.com> | 2020-09-13 07:48:14 -0700 |
commit | cae155b095e5182cc1b342b21f7430e40afe7ba8 (patch) | |
tree | 82b6342b0a8dc6f98ce73188bb89ae5ad0267060 /src/Text/Pandoc/Readers/Org | |
parent | 2109ded7101dba0ac48c9b60cdf454ad39a7e272 (diff) | |
download | pandoc-cae155b095e5182cc1b342b21f7430e40afe7ba8.tar.gz |
Fix hlint suggestions, update hlint.yaml (#6680)
* Fix hlint suggestions, update hlint.yaml
Most suggestions were redundant brackets. Some required
LambdaCase.
The .hlint.yaml file had a small typo, and didn't ignore camelCase
suggestions in certain modules.
Diffstat (limited to 'src/Text/Pandoc/Readers/Org')
-rw-r--r-- | src/Text/Pandoc/Readers/Org/Blocks.hs | 23 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Org/ParserState.hs | 2 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Org/Shared.hs | 4 |
3 files changed, 13 insertions, 16 deletions
diff --git a/src/Text/Pandoc/Readers/Org/Blocks.hs b/src/Text/Pandoc/Readers/Org/Blocks.hs index c60817d1b..d71cd7faf 100644 --- a/src/Text/Pandoc/Readers/Org/Blocks.hs +++ b/src/Text/Pandoc/Readers/Org/Blocks.hs @@ -34,6 +34,7 @@ import Text.Pandoc.Shared (compactify, compactifyDL, safeRead) import Control.Monad (foldM, guard, mplus, mzero, void) import Data.Char (isSpace) import Data.Default (Default) +import Data.Functor (($>)) import Data.List (foldl', intersperse) import Data.Maybe (fromMaybe, isJust, isNothing) import Data.Text (Text) @@ -103,9 +104,7 @@ attrFromBlockAttributes :: BlockAttributes -> Attr attrFromBlockAttributes BlockAttributes{..} = let ident = fromMaybe mempty $ lookup "id" blockAttrKeyValues - classes = case lookup "class" blockAttrKeyValues of - Nothing -> [] - Just clsStr -> T.words clsStr + classes = maybe [] T.words $ lookup "class" blockAttrKeyValues kv = filter ((`notElem` ["id", "class"]) . fst) blockAttrKeyValues in (ident, classes, kv) @@ -576,10 +575,10 @@ rawExportLine = try $ do rawOrgLine :: PandocMonad m => OrgParser m (F Blocks) rawOrgLine = do line <- metaLineStart *> anyLine - returnF $ B.rawBlock "org" $ ("#+" <> line) + returnF $ B.rawBlock "org" $ "#+" <> line commentLine :: Monad m => OrgParser m Blocks -commentLine = commentLineStart *> anyLine *> pure mempty +commentLine = commentLineStart *> anyLine $> mempty -- @@ -648,12 +647,12 @@ orgToPandocTable (OrgTable colProps heads lns) caption = (TableFoot nullAttr []) where toRow = Row nullAttr . map B.simpleCell - toHeaderRow l = if null l then [] else [toRow l] + toHeaderRow l = [toRow l | not (null l)] convertColProp :: Maybe Int -> ColumnProperty -> (Alignment, ColWidth) convertColProp totalWidth colProp = let align' = fromMaybe AlignDefault $ columnAlignment colProp - width' = (\w t -> (fromIntegral w / fromIntegral t)) + width' = (\w t -> fromIntegral w / fromIntegral t) <$> columnRelWidth colProp <*> totalWidth in (align', maybe ColWidthDefault ColWidth width') @@ -691,9 +690,9 @@ columnPropertyCell = emptyOrgCell <|> propCell <?> "alignment info" tableAlignFromChar :: Monad m => OrgParser m Alignment tableAlignFromChar = try $ - choice [ char 'l' *> return AlignLeft - , char 'c' *> return AlignCenter - , char 'r' *> return AlignRight + choice [ char 'l' $> AlignLeft + , char 'c' $> AlignCenter + , char 'r' $> AlignRight ] tableHline :: Monad m => OrgParser m OrgTableRow @@ -796,13 +795,13 @@ paraOrPlain = try $ do -- Make sure we are not looking at a headline notFollowedBy' headerStart ils <- inlines - nl <- option False (newline *> return True) + nl <- option False (newline $> True) -- Read block as paragraph, except if we are in a list context and the block -- is directly followed by a list item, in which case the block is read as -- plain text. try (guard nl *> notFollowedBy (inList *> (orderedListStart <|> bulletListStart)) - *> return (B.para <$> ils)) + $> (B.para <$> ils)) <|> return (B.plain <$> ils) diff --git a/src/Text/Pandoc/Readers/Org/ParserState.hs b/src/Text/Pandoc/Readers/Org/ParserState.hs index 6e2e86373..1e4799e7b 100644 --- a/src/Text/Pandoc/Readers/Org/ParserState.hs +++ b/src/Text/Pandoc/Readers/Org/ParserState.hs @@ -122,7 +122,7 @@ data OrgParserState = OrgParserState , orgMacros :: M.Map Text Macro } -data OrgParserLocal = OrgParserLocal +newtype OrgParserLocal = OrgParserLocal { orgLocalQuoteContext :: QuoteContext } diff --git a/src/Text/Pandoc/Readers/Org/Shared.hs b/src/Text/Pandoc/Readers/Org/Shared.hs index 3934be6e1..7f72077a4 100644 --- a/src/Text/Pandoc/Readers/Org/Shared.hs +++ b/src/Text/Pandoc/Readers/Org/Shared.hs @@ -58,9 +58,7 @@ cleanLinkText s originalLang :: Text -> [(Text, Text)] originalLang lang = let transLang = translateLang lang - in if transLang == lang - then [] - else [("org-language", lang)] + in [("org-language", lang) | transLang /= lang] -- | Translate from Org-mode's programming language identifiers to those used -- by Pandoc. This is useful to allow for proper syntax highlighting in |