Skip to content

Commit

Permalink
Merge pull request #420 from ahstro/fix-compiler-warnings
Browse files Browse the repository at this point in the history
Fix some compiler warnings
  • Loading branch information
avh4 authored Oct 25, 2017
2 parents 3e2f4f2 + e10bd7f commit d8e6435
Show file tree
Hide file tree
Showing 8 changed files with 26 additions and 32 deletions.
30 changes: 12 additions & 18 deletions markdown/Cheapskate/Inlines.hs
Original file line number Diff line number Diff line change
Expand Up @@ -15,15 +15,14 @@ import Prelude hiding (takeWhile)
import Control.Applicative
import Data.Monoid
import Control.Monad
import qualified Data.Map as M
import Data.Text (Text)
import qualified Data.Text as T
import qualified Data.Set as Set

-- Returns tag type and whole tag.
pHtmlTag :: Parser (HtmlTagType, Text)
pHtmlTag = do
char '<'
_ <- char '<'
-- do not end the tag with a > character in a quoted attribute.
closing <- (char '/' >> return True) <|> return False
tagname <- takeWhile1 (\c -> isAsciiAlphaNum c || c == '?' || c == '!')
Expand All @@ -37,7 +36,7 @@ pHtmlTag = do
return $ ss <> T.singleton x <> xs <> "=" <> v
attrs <- T.concat <$> many attr
final <- takeWhile (\c -> isSpace c || c == '/')
char '>'
_ <- char '>'
let tagtype = if closing
then Closing tagname'
else case T.stripSuffix "/" final of
Expand All @@ -58,7 +57,7 @@ pQuoted c = do
-- do for now.
pHtmlComment :: Parser Text
pHtmlComment = do
string "<!--"
_ <- string "<!--"
rest <- manyTill anyChar (string "-->")
return $ "<!--" <> T.pack rest <> "-->"

Expand Down Expand Up @@ -119,7 +118,7 @@ pLinkTitle = do
pReference :: Parser (Text, Text, Text)
pReference = do
lab <- pLinkLabel
char ':'
_ <- char ':'
scanSpnl
url <- pLinkUrl
tit <- option T.empty $ scanSpnl >> pLinkTitle
Expand Down Expand Up @@ -240,7 +239,7 @@ schemeSet = Set.fromList $ schemes ++ map T.toUpper schemes
-- Parse a URI, using heuristics to avoid capturing final punctuation.
pUri :: Text -> Parser Inlines
pUri scheme = do
char ':'
_ <- char ':'
x <- scan (OpenParens 0) uriScanner
guard $ not $ T.null x
let (rawuri, endingpunct) =
Expand Down Expand Up @@ -345,18 +344,13 @@ pLink refmap = do
-- An inline link: [label](/url "optional title")
pInlineLink :: Inlines -> Parser Inlines
pInlineLink lab = do
char '('
_ <- char '('
scanSpaces
url <- pLinkUrl
tit <- option "" $ scanSpnl *> pLinkTitle <* scanSpaces
char ')'
_ <- char ')'
return $ singleton $ Link lab (Url url) tit

lookupLinkReference :: ReferenceMap
-> Text -- reference label
-> Maybe (Text, Text) -- (url, title)
lookupLinkReference refmap key = M.lookup (normalizeReference key) refmap

-- A reference link: [label], [foo][label], or [label][].
pReferenceLink :: ReferenceMap -> Text -> Inlines -> Parser Inlines
pReferenceLink _ rawlab lab = do
Expand All @@ -367,7 +361,7 @@ pReferenceLink _ rawlab lab = do
-- An image: ! followed by a link.
pImage :: ReferenceMap -> Parser Inlines
pImage refmap = do
char '!'
_ <- char '!'
(linkToImage <$> pLink refmap) <|> return (singleton (Str "!"))

linkToImage :: Inlines -> Inlines
Expand All @@ -383,23 +377,23 @@ linkToImage ils =
-- convert them to characters and store them as Str inlines.
pEntity :: Parser Inlines
pEntity = do
char '&'
_ <- char '&'
res <- pCharEntity <|> pDecEntity <|> pHexEntity
char ';'
_ <- char ';'
return $ singleton $ Entity $ "&" <> res <> ";"

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

pDecEntity :: Parser Text
pDecEntity = do
char '#'
_ <- char '#'
res <- takeWhile1 isDigit
return $ "#" <> res

pHexEntity :: Parser Text
pHexEntity = do
char '#'
_ <- char '#'
x <- char 'X' <|> char 'x'
res <- takeWhile1 isHexDigit
return $ "#" <> T.singleton x <> res
Expand Down
8 changes: 4 additions & 4 deletions markdown/Cheapskate/Parse.hs
Original file line number Diff line number Diff line change
Expand Up @@ -116,7 +116,7 @@ containerContinue c =
<|>
(do scanSpacesToColumn
(markerColumn li + 1)
upToCountChars (padding li - 1)
_ <- upToCountChars (padding li - 1)
(==' ')
return ())
Reference{} -> nfb scanBlankline >>
Expand Down Expand Up @@ -450,7 +450,7 @@ processLine (lineNumber, txt) = do
-- otherwise, close all the unmatched containers, add the new
-- containers, and finally add the new leaf:
(ns, lf) -> do -- close unmatched containers, add new ones
replicateM numUnmatched closeContainer
_ <- replicateM numUnmatched closeContainer
addNew (ns, lf)

where
Expand Down Expand Up @@ -531,7 +531,7 @@ scanBlockquoteStart = scanChar '>' >> option () (scanChar ' ')
-- a header.
parseAtxHeaderStart :: Parser Int
parseAtxHeaderStart = do
char '#'
_ <- char '#'
hashes <- upToCountChars 5 (== '#')
-- hashes must be followed by space unless empty header:
notFollowedBy (skip (/= ' '))
Expand All @@ -551,7 +551,7 @@ parseSetextHeaderLine = do
scanHRuleLine :: Scanner
scanHRuleLine = do
c <- satisfy (\c -> c == '*' || c == '_' || c == '-')
count 2 $ scanSpaces >> skip (== c)
_ <- count 2 $ scanSpaces >> skip (== c)
skipWhile (\x -> x == ' ' || x == c)
endOfInput

Expand Down
2 changes: 1 addition & 1 deletion markdown/Cheapskate/Util.hs
Original file line number Diff line number Diff line change
Expand Up @@ -21,7 +21,7 @@ module Cheapskate.Util (
import Data.Text (Text)
import qualified Data.Text as T
import Data.Char
import Control.Applicative
import Control.Applicative ()
import Cheapskate.ParserCombinators

-- Utility functions.
Expand Down
4 changes: 2 additions & 2 deletions parser/src/Parse/Helpers.hs
Original file line number Diff line number Diff line change
Expand Up @@ -465,7 +465,7 @@ accessible :: IParser AST.Expression.Expr -> IParser AST.Expression.Expr
accessible exprParser =
do start <- getMyPosition

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

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

Expand Down Expand Up @@ -507,7 +507,7 @@ failure :: String -> IParser String
failure msg = do
inp <- getInput
setInput ('x':inp)
anyToken
_ <- anyToken
fail msg


Expand Down
4 changes: 2 additions & 2 deletions parser/src/Parse/Module.hs
Original file line number Diff line number Diff line change
Expand Up @@ -234,8 +234,8 @@ mergeListing merge left right =
(Var.OpenListing (Commented pre1 () post1), Var.OpenListing (Commented pre2 () post2)) -> Var.OpenListing (Commented (pre1 ++ pre2) () (post1 ++ post2))
(Var.ClosedListing, Var.ExplicitListing a multiline) -> Var.ExplicitListing a multiline
(Var.ExplicitListing a multiline, Var.ClosedListing) -> Var.ExplicitListing a multiline
(Var.OpenListing comments, Var.ExplicitListing a multiline) -> Var.OpenListing comments
(Var.ExplicitListing a multiline, Var.OpenListing comments) -> Var.OpenListing comments
(Var.OpenListing comments, Var.ExplicitListing _a _multiline) -> Var.OpenListing comments
(Var.ExplicitListing _a _multiline, Var.OpenListing comments) -> Var.OpenListing comments
(Var.ExplicitListing a multiline1, Var.ExplicitListing b multiline2) -> Var.ExplicitListing (merge a b) (multiline1 || multiline2)


Expand Down
4 changes: 2 additions & 2 deletions parser/src/Reporting/Error/Syntax.hs
Original file line number Diff line number Diff line change
Expand Up @@ -45,8 +45,8 @@ toReport err =
where
operator =
case op of
Var.VarRef namespace (LowercaseIdentifier name) -> "`" ++ name ++ "`"
Var.TagRef namespace (UppercaseIdentifier name) -> "`" ++ name ++ "`"
Var.VarRef _namespace (LowercaseIdentifier name) -> "`" ++ name ++ "`"
Var.TagRef _namespace (UppercaseIdentifier name) -> "`" ++ name ++ "`"
Var.OpRef (SymbolIdentifier name) -> "(" ++ name ++ ")"

TypeWithoutDefinition valueName ->
Expand Down
2 changes: 1 addition & 1 deletion src/ElmFormat/Render/Box.hs
Original file line number Diff line number Diff line change
Expand Up @@ -144,7 +144,7 @@ declarationType decl =
AST.Declaration.PortAnnotation (Commented _ name _) _ _ ->
DDefinition $ Just $ AST.Variable.VarRef [] name

AST.Declaration.Fixity _ _ _ _ name ->
AST.Declaration.Fixity _ _ _ _ _name ->
DFixity

AST.Declaration.DocComment _ ->
Expand Down
4 changes: 2 additions & 2 deletions src/ElmFormat/Render/Markdown.hs
Original file line number Diff line number Diff line change
Expand Up @@ -37,7 +37,7 @@ formatMarkdown formatCode blocks =


mapWithPrev :: (Maybe a -> a -> b) -> [a] -> [b]
mapWithPrev f [] = []
mapWithPrev _ [] = []
mapWithPrev f (first:rest) =
f Nothing first : zipWith (\prev next -> f (Just prev) next) (first:rest) rest

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

CodeBlock (CodeAttr lang info) code ->
CodeBlock (CodeAttr lang _info) code ->
let
formatted =
fromMaybe (Text.unpack $ ensureNewline code) $ formatCode $ Text.unpack code
Expand Down

0 comments on commit d8e6435

Please sign in to comment.