Skip to content

Commit d8e6435

Browse files
authored
Merge pull request #420 from ahstro/fix-compiler-warnings
Fix some compiler warnings
2 parents 3e2f4f2 + e10bd7f commit d8e6435

File tree

8 files changed

+26
-32
lines changed

8 files changed

+26
-32
lines changed

markdown/Cheapskate/Inlines.hs

Lines changed: 12 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -15,15 +15,14 @@ import Prelude hiding (takeWhile)
1515
import Control.Applicative
1616
import Data.Monoid
1717
import Control.Monad
18-
import qualified Data.Map as M
1918
import Data.Text (Text)
2019
import qualified Data.Text as T
2120
import qualified Data.Set as Set
2221

2322
-- Returns tag type and whole tag.
2423
pHtmlTag :: Parser (HtmlTagType, Text)
2524
pHtmlTag = do
26-
char '<'
25+
_ <- char '<'
2726
-- do not end the tag with a > character in a quoted attribute.
2827
closing <- (char '/' >> return True) <|> return False
2928
tagname <- takeWhile1 (\c -> isAsciiAlphaNum c || c == '?' || c == '!')
@@ -37,7 +36,7 @@ pHtmlTag = do
3736
return $ ss <> T.singleton x <> xs <> "=" <> v
3837
attrs <- T.concat <$> many attr
3938
final <- takeWhile (\c -> isSpace c || c == '/')
40-
char '>'
39+
_ <- char '>'
4140
let tagtype = if closing
4241
then Closing tagname'
4342
else case T.stripSuffix "/" final of
@@ -58,7 +57,7 @@ pQuoted c = do
5857
-- do for now.
5958
pHtmlComment :: Parser Text
6059
pHtmlComment = do
61-
string "<!--"
60+
_ <- string "<!--"
6261
rest <- manyTill anyChar (string "-->")
6362
return $ "<!--" <> T.pack rest <> "-->"
6463

@@ -119,7 +118,7 @@ pLinkTitle = do
119118
pReference :: Parser (Text, Text, Text)
120119
pReference = do
121120
lab <- pLinkLabel
122-
char ':'
121+
_ <- char ':'
123122
scanSpnl
124123
url <- pLinkUrl
125124
tit <- option T.empty $ scanSpnl >> pLinkTitle
@@ -240,7 +239,7 @@ schemeSet = Set.fromList $ schemes ++ map T.toUpper schemes
240239
-- Parse a URI, using heuristics to avoid capturing final punctuation.
241240
pUri :: Text -> Parser Inlines
242241
pUri scheme = do
243-
char ':'
242+
_ <- char ':'
244243
x <- scan (OpenParens 0) uriScanner
245244
guard $ not $ T.null x
246245
let (rawuri, endingpunct) =
@@ -345,18 +344,13 @@ pLink refmap = do
345344
-- An inline link: [label](/url "optional title")
346345
pInlineLink :: Inlines -> Parser Inlines
347346
pInlineLink lab = do
348-
char '('
347+
_ <- char '('
349348
scanSpaces
350349
url <- pLinkUrl
351350
tit <- option "" $ scanSpnl *> pLinkTitle <* scanSpaces
352-
char ')'
351+
_ <- char ')'
353352
return $ singleton $ Link lab (Url url) tit
354353

355-
lookupLinkReference :: ReferenceMap
356-
-> Text -- reference label
357-
-> Maybe (Text, Text) -- (url, title)
358-
lookupLinkReference refmap key = M.lookup (normalizeReference key) refmap
359-
360354
-- A reference link: [label], [foo][label], or [label][].
361355
pReferenceLink :: ReferenceMap -> Text -> Inlines -> Parser Inlines
362356
pReferenceLink _ rawlab lab = do
@@ -367,7 +361,7 @@ pReferenceLink _ rawlab lab = do
367361
-- An image: ! followed by a link.
368362
pImage :: ReferenceMap -> Parser Inlines
369363
pImage refmap = do
370-
char '!'
364+
_ <- char '!'
371365
(linkToImage <$> pLink refmap) <|> return (singleton (Str "!"))
372366

373367
linkToImage :: Inlines -> Inlines
@@ -383,23 +377,23 @@ linkToImage ils =
383377
-- convert them to characters and store them as Str inlines.
384378
pEntity :: Parser Inlines
385379
pEntity = do
386-
char '&'
380+
_ <- char '&'
387381
res <- pCharEntity <|> pDecEntity <|> pHexEntity
388-
char ';'
382+
_ <- char ';'
389383
return $ singleton $ Entity $ "&" <> res <> ";"
390384

391385
pCharEntity :: Parser Text
392386
pCharEntity = takeWhile1 (\c -> isAscii c && isLetter c)
393387

394388
pDecEntity :: Parser Text
395389
pDecEntity = do
396-
char '#'
390+
_ <- char '#'
397391
res <- takeWhile1 isDigit
398392
return $ "#" <> res
399393

400394
pHexEntity :: Parser Text
401395
pHexEntity = do
402-
char '#'
396+
_ <- char '#'
403397
x <- char 'X' <|> char 'x'
404398
res <- takeWhile1 isHexDigit
405399
return $ "#" <> T.singleton x <> res

markdown/Cheapskate/Parse.hs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -116,7 +116,7 @@ containerContinue c =
116116
<|>
117117
(do scanSpacesToColumn
118118
(markerColumn li + 1)
119-
upToCountChars (padding li - 1)
119+
_ <- upToCountChars (padding li - 1)
120120
(==' ')
121121
return ())
122122
Reference{} -> nfb scanBlankline >>
@@ -450,7 +450,7 @@ processLine (lineNumber, txt) = do
450450
-- otherwise, close all the unmatched containers, add the new
451451
-- containers, and finally add the new leaf:
452452
(ns, lf) -> do -- close unmatched containers, add new ones
453-
replicateM numUnmatched closeContainer
453+
_ <- replicateM numUnmatched closeContainer
454454
addNew (ns, lf)
455455

456456
where
@@ -531,7 +531,7 @@ scanBlockquoteStart = scanChar '>' >> option () (scanChar ' ')
531531
-- a header.
532532
parseAtxHeaderStart :: Parser Int
533533
parseAtxHeaderStart = do
534-
char '#'
534+
_ <- char '#'
535535
hashes <- upToCountChars 5 (== '#')
536536
-- hashes must be followed by space unless empty header:
537537
notFollowedBy (skip (/= ' '))
@@ -551,7 +551,7 @@ parseSetextHeaderLine = do
551551
scanHRuleLine :: Scanner
552552
scanHRuleLine = do
553553
c <- satisfy (\c -> c == '*' || c == '_' || c == '-')
554-
count 2 $ scanSpaces >> skip (== c)
554+
_ <- count 2 $ scanSpaces >> skip (== c)
555555
skipWhile (\x -> x == ' ' || x == c)
556556
endOfInput
557557

markdown/Cheapskate/Util.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -21,7 +21,7 @@ module Cheapskate.Util (
2121
import Data.Text (Text)
2222
import qualified Data.Text as T
2323
import Data.Char
24-
import Control.Applicative
24+
import Control.Applicative ()
2525
import Cheapskate.ParserCombinators
2626

2727
-- Utility functions.

parser/src/Parse/Helpers.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -465,7 +465,7 @@ accessible :: IParser AST.Expression.Expr -> IParser AST.Expression.Expr
465465
accessible exprParser =
466466
do start <- getMyPosition
467467

468-
annotatedRootExpr@(A.A _ rootExpr) <- exprParser
468+
annotatedRootExpr@(A.A _ _rootExpr) <- exprParser
469469

470470
access <- optionMaybe (try dot <?> "a field access like .name")
471471

@@ -507,7 +507,7 @@ failure :: String -> IParser String
507507
failure msg = do
508508
inp <- getInput
509509
setInput ('x':inp)
510-
anyToken
510+
_ <- anyToken
511511
fail msg
512512

513513

parser/src/Parse/Module.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -234,8 +234,8 @@ mergeListing merge left right =
234234
(Var.OpenListing (Commented pre1 () post1), Var.OpenListing (Commented pre2 () post2)) -> Var.OpenListing (Commented (pre1 ++ pre2) () (post1 ++ post2))
235235
(Var.ClosedListing, Var.ExplicitListing a multiline) -> Var.ExplicitListing a multiline
236236
(Var.ExplicitListing a multiline, Var.ClosedListing) -> Var.ExplicitListing a multiline
237-
(Var.OpenListing comments, Var.ExplicitListing a multiline) -> Var.OpenListing comments
238-
(Var.ExplicitListing a multiline, Var.OpenListing comments) -> Var.OpenListing comments
237+
(Var.OpenListing comments, Var.ExplicitListing _a _multiline) -> Var.OpenListing comments
238+
(Var.ExplicitListing _a _multiline, Var.OpenListing comments) -> Var.OpenListing comments
239239
(Var.ExplicitListing a multiline1, Var.ExplicitListing b multiline2) -> Var.ExplicitListing (merge a b) (multiline1 || multiline2)
240240

241241

parser/src/Reporting/Error/Syntax.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -45,8 +45,8 @@ toReport err =
4545
where
4646
operator =
4747
case op of
48-
Var.VarRef namespace (LowercaseIdentifier name) -> "`" ++ name ++ "`"
49-
Var.TagRef namespace (UppercaseIdentifier name) -> "`" ++ name ++ "`"
48+
Var.VarRef _namespace (LowercaseIdentifier name) -> "`" ++ name ++ "`"
49+
Var.TagRef _namespace (UppercaseIdentifier name) -> "`" ++ name ++ "`"
5050
Var.OpRef (SymbolIdentifier name) -> "(" ++ name ++ ")"
5151

5252
TypeWithoutDefinition valueName ->

src/ElmFormat/Render/Box.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -144,7 +144,7 @@ declarationType decl =
144144
AST.Declaration.PortAnnotation (Commented _ name _) _ _ ->
145145
DDefinition $ Just $ AST.Variable.VarRef [] name
146146

147-
AST.Declaration.Fixity _ _ _ _ name ->
147+
AST.Declaration.Fixity _ _ _ _ _name ->
148148
DFixity
149149

150150
AST.Declaration.DocComment _ ->

src/ElmFormat/Render/Markdown.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -37,7 +37,7 @@ formatMarkdown formatCode blocks =
3737

3838

3939
mapWithPrev :: (Maybe a -> a -> b) -> [a] -> [b]
40-
mapWithPrev f [] = []
40+
mapWithPrev _ [] = []
4141
mapWithPrev f (first:rest) =
4242
f Nothing first : zipWith (\prev next -> f (Just prev) next) (first:rest) rest
4343

@@ -88,7 +88,7 @@ formatMardownBlock formatCode context block =
8888
fold $ (if tight then id else List.intersperse "\n") $
8989
fmap (formatListItem formatCode) $ zip [1..] items
9090

91-
CodeBlock (CodeAttr lang info) code ->
91+
CodeBlock (CodeAttr lang _info) code ->
9292
let
9393
formatted =
9494
fromMaybe (Text.unpack $ ensureNewline code) $ formatCode $ Text.unpack code

0 commit comments

Comments
 (0)