summaryrefslogtreecommitdiff
path: root/Pancake
diff options
context:
space:
mode:
authordefanor <defanor@uberspace.net>2017-11-06 10:54:15 +0300
committerdefanor <defanor@uberspace.net>2017-11-06 10:54:15 +0300
commite19d502ced73cf9fcbc5c8b7c2983983b48566d7 (patch)
treec2992caf8858595afd18d2b21f0b4fb0317cf702 /Pancake
parent1f23441e61bf9ac4e4e9f5b9a42e77bed7140b4f (diff)
Lint the code
Diffstat (limited to 'Pancake')
-rw-r--r--Pancake/Printing.hs15
-rw-r--r--Pancake/Reading.hs10
-rw-r--r--Pancake/Rendering.hs20
3 files changed, 23 insertions, 22 deletions
diff --git a/Pancake/Printing.hs b/Pancake/Printing.hs
index 2e0aee5..66d2606 100644
--- a/Pancake/Printing.hs
+++ b/Pancake/Printing.hs
@@ -16,7 +16,8 @@ import Control.Monad.State
import System.IO
import System.Console.Terminfo
import Network.URI
-import Data.List
+import Data.Maybe
+
import Pancake.Rendering
@@ -26,24 +27,24 @@ propertize _ (Plain s) = termText s
propertize t (Fg clr s) = maybe id (\f -> f clr)
(getCapability t withForegroundColor) $ propertize t s
propertize t (Bold s) =
- maybe id id (getCapability t withBold) $ propertize t s
+ fromMaybe id (getCapability t withBold) $ propertize t s
propertize t (Emph s) =
- maybe id id (getCapability t withStandout) $ propertize t s
+ fromMaybe id (getCapability t withStandout) $ propertize t s
propertize t (Underline s) =
- maybe id id (getCapability t withUnderline) $ propertize t s
+ fromMaybe id (getCapability t withUnderline) $ propertize t s
propertize t (Denote _ s) = propertize t s
-- | Prints rendered lines.
showLines :: MonadIO m => [StyledLine] -> m ()
showLines ls = liftIO $ do
term <- setupTermFromEnv
- let nl = maybe (termText "\n") id $ getCapability term newline
+ let nl = fromMaybe (termText "\n") $ getCapability term newline
runTermOutput term . mconcat $
map (\l -> mconcat (map (propertize term) l) <#> nl) ls
-- | Shows a list of strings as an s-expression
list :: [String] -> String
-list l = "(" ++ intercalate " " l ++ ")"
+list l = "(" ++ unwords l ++ ")"
-- | Prints a list of strings as an s-expression.
putSexpLn :: MonadIO m => [String] -> m ()
@@ -58,7 +59,7 @@ showSexps uri ro =
-- abandoned, and the task is simple enough to do it here
putSexpLn [ "render"
, list $ "lines" :
- map (list . pure . concat . intersperse " " . map showSexp . mergeStyled)
+ map (list . pure . unwords . map showSexp . mergeStyled)
(rLines ro)
, list $ "identifiers"
: map (\(i, l) -> list [encodeStr i, show l]) (rIdentifiers ro)
diff --git a/Pancake/Reading.hs b/Pancake/Reading.hs
index 2069f35..d54d7b3 100644
--- a/Pancake/Reading.hs
+++ b/Pancake/Reading.hs
@@ -30,6 +30,7 @@ import System.Environment
import GHC.IO.Handle
import Text.Parsec hiding ((<|>))
import Text.Parsec.ByteString
+import Data.Maybe
import Text.Pandoc.Readers.Plain
import Text.Pandoc.Readers.Gopher
@@ -57,8 +58,7 @@ pMeta = do
-- | Document body + metadata parser.
pWithMeta :: Parser (BS.ByteString, (Maybe URI, Maybe String))
-pWithMeta = (,)
- <$> BS.pack <$> manyTill anyToken (try $ lookAhead pMeta)
+pWithMeta = (,) . BS.pack <$> manyTill anyToken (try $ lookAhead pMeta)
<*> pMeta
-- | Retrieves a document. Prints an error message and returns an
@@ -96,9 +96,9 @@ retrieve cmd uri = do
hSetBinaryMode stdout' True
out <- BS.hGetContents stdout'
ec <- waitForProcess ph
- if (ec /= ExitSuccess)
+ if ec /= ExitSuccess
then do
- putErrLn $ concat ["An error occured. Exit code: ", show ec]
+ putErrLn $ "An error occured. Exit code: " ++ show ec
case stderr of
Nothing -> pure ()
Just stderr' -> do
@@ -140,7 +140,7 @@ readDoc out dt uri = do
-- unknown or unrecognized item type
_ -> byExtension ext <|> gopher
(_, ext) -> byExtension ext
- cols = maybe 80 id $ getCapability term termColumns
+ cols = fromMaybe 80 $ getCapability term termColumns
opts = def { P.readerColumns = cols }
case reader of
(P.TextReader f, _) -> case decodeUtf8' out of
diff --git a/Pancake/Rendering.hs b/Pancake/Rendering.hs
index 2af0ec4..7b219b9 100644
--- a/Pancake/Rendering.hs
+++ b/Pancake/Rendering.hs
@@ -72,19 +72,19 @@ data RendererOutput = RLink URI
-- | Extracts links.
rLinks :: [RendererOutput] -> [URI]
rLinks [] = []
-rLinks ((RLink l):xs) = l : rLinks xs
+rLinks (RLink l:xs) = l : rLinks xs
rLinks (_:xs) = rLinks xs
-- | Extracts text lines.
rLines :: [RendererOutput] -> [StyledLine]
rLines [] = []
-rLines ((RLine l):xs) = l : rLines xs
+rLines (RLine l:xs) = l : rLines xs
rLines (_:xs) = rLines xs
-- | Extracts identifiers.
rIdentifiers :: [RendererOutput] -> [(String, Int)]
rIdentifiers [] = []
-rIdentifiers ((RIdentifier s i):xs) = (s, i) : rIdentifiers xs
+rIdentifiers (RIdentifier s i:xs) = (s, i) : rIdentifiers xs
rIdentifiers (_:xs) = rIdentifiers xs
-- | Used to render 'Pandoc' docs by writing text lines and collected
@@ -102,7 +102,7 @@ runRenderer :: Int
-- ^ A renderer.
-> [RendererOutput]
-- ^ Collected links and text lines.
-runRenderer cols ls ln r = snd $ fst $ runState (runWriterT r)
+runRenderer cols ls ln r = snd $ evalState (runWriterT r)
(RS 0 ls ln Nothing cols)
-- | Stores a link, increasing the counter
@@ -159,7 +159,7 @@ indented slines = do
indent = il + prefixLen
fittedLines = fitLines (columns st - indent) slines
pad = (fromString (replicate indent ' ') :)
- padFirst = (\x -> fromString (replicate il ' ') : prefix : x)
+ padFirst x = fromString (replicate il ' ') : prefix : x
-- The following blocks of the same list item should be indented
-- with the same level. This should be reset to the original value
-- where the listing type is getting set.
@@ -217,7 +217,7 @@ fitLines maxLen inlineBits = concatMap (map reverse . fitWords [] 0) inlineBits
in if curLen + wLen <= maxLen
then fitWords (w:curLine) (curLen + wLen) $
-- if there's an unnecessary space ahead, skip it
- if (curLen + wLen + 1 > maxLen && spaceAhead)
+ if curLen + wLen + 1 > maxLen && spaceAhead
then tail ws
else ws
else curLine : fitWords [] 0 (w:ws)
@@ -333,7 +333,7 @@ renderBlock (P.Header level attr i) = do
strings <- readInlines i
storeLines [[""]]
indented $ map (map (Fg Green) . ([fromString (replicate level '#'), " "] ++)
- . (map (Bold . Underline))) strings
+ . map (Bold . Underline)) strings
storeLines [[""]]
renderBlock P.HorizontalRule = do
st <- get
@@ -349,8 +349,8 @@ renderBlock (P.Table caption _ widths headers rows) = do
w -> minimum w /= maximum w
ws <- if widthsAreSet then pure widths else do
lens <- map sum . transpose <$>
- mapM (mapM (\c -> (length . unstyled . concat . rLines)
- <$> renderCell 80 c)) rows
+ mapM (mapM (fmap (length . unstyled . concat . rLines) . renderCell 80))
+ rows
pure $ map (\l -> fromIntegral l / fromIntegral (sum lens)) lens
mapM_ (\r -> renderBlock P.HorizontalRule >> tableRow ws r) (headers : rows)
renderBlock P.HorizontalRule
@@ -364,7 +364,7 @@ renderBlock (P.Table caption _ widths headers rows) = do
tableCell w blocks = do
l <- renderCell w blocks
mapM_ storeLink $ rLinks l
- tell $ map (\(s, i) -> RIdentifier s i) $ rIdentifiers l
+ tell $ map (uncurry RIdentifier) $ rIdentifiers l
pure $ map
(\x -> x ++ [fromString (replicate (w - length (unstyled x)) ' ')])
$ rLines l