aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Shared.hs
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2020-02-07 08:32:47 -0800
committerJohn MacFarlane <jgm@berkeley.edu>2020-02-07 09:08:22 -0800
commit4c3db9273fc8e92c2c23d4455a6ab178472be06d (patch)
treecdfc8d65ebd56c0a571f8b46854465dd434489de /src/Text/Pandoc/Shared.hs
parent6cd77d4c638012be63d66882403804aa28feb6ed (diff)
downloadpandoc-4c3db9273fc8e92c2c23d4455a6ab178472be06d.tar.gz
Apply linter suggestions. Add fix_spacing to lint target in Makefile.
Diffstat (limited to 'src/Text/Pandoc/Shared.hs')
-rw-r--r--src/Text/Pandoc/Shared.hs18
1 files changed, 9 insertions, 9 deletions
diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs
index c03a99cdb..a0465211a 100644
--- a/src/Text/Pandoc/Shared.hs
+++ b/src/Text/Pandoc/Shared.hs
@@ -466,7 +466,7 @@ compactify items =
let (others, final) = (init items, last items)
in case reverse (B.toList final) of
(Para a:xs)
- | null [Para x | Para x <- (xs ++ concatMap B.toList others)]
+ | null [Para x | Para x <- xs ++ concatMap B.toList others]
-> others ++ [B.fromList (reverse (Plain a : xs))]
_ | null [Para x | Para x <- concatMap B.toList items]
-> items
@@ -682,9 +682,9 @@ isTightList = all (\item -> firstIsPlain item || null item)
taskListItemFromAscii :: Extensions -> [Block] -> [Block]
taskListItemFromAscii = handleTaskListItem fromMd
where
- fromMd (Str "[" : Space : Str "]" : Space : is) = (Str "☐") : Space : is
- fromMd (Str "[x]" : Space : is) = (Str "☒") : Space : is
- fromMd (Str "[X]" : Space : is) = (Str "☒") : Space : is
+ fromMd (Str "[" : Space : Str "]" : Space : is) = Str "☐" : Space : is
+ fromMd (Str "[x]" : Space : is) = Str "☒" : Space : is
+ fromMd (Str "[X]" : Space : is) = Str "☒" : Space : is
fromMd is = is
-- | Convert a list item containing text starting with @U+2610 BALLOT BOX@
@@ -787,19 +787,19 @@ splitSentences xs =
-- strip out ANSI escape sequences from CodeBlocks (see #5633).
filterIpynbOutput :: Maybe Format -> Pandoc -> Pandoc
filterIpynbOutput mode = walk go
- where go (Div (ident, ("output":os), kvs) bs) =
+ where go (Div (ident, "output":os, kvs) bs) =
case mode of
- Nothing -> Div (ident, ("output":os), kvs) []
+ Nothing -> Div (ident, "output":os, kvs) []
-- "best" for ipynb includes all formats:
Just fmt
| fmt == Format "ipynb"
- -> Div (ident, ("output":os), kvs) bs
- | otherwise -> Div (ident, ("output":os), kvs) $
+ -> Div (ident, "output":os, kvs) bs
+ | otherwise -> Div (ident, "output":os, kvs) $
walk removeANSI $
take 1 $ sortOn rank bs
where
rank (RawBlock (Format "html") _)
- | fmt == Format "html" = (1 :: Int)
+ | fmt == Format "html" = 1 :: Int
| fmt == Format "markdown" = 2
| otherwise = 3
rank (RawBlock (Format "latex") _)