Skip to content

Commit

Permalink
Use <$> instead of >>= and return
Browse files Browse the repository at this point in the history
  • Loading branch information
josephcsible committed Dec 30, 2023
1 parent dedf932 commit 980e7d3
Show file tree
Hide file tree
Showing 2 changed files with 4 additions and 4 deletions.
2 changes: 1 addition & 1 deletion src/ShellCheck/CFG.hs
Original file line number Diff line number Diff line change
Expand Up @@ -997,7 +997,7 @@ handleCommand cmd vars args literalCmd = do
(names, flags) = partition (null . fst) pairs
flagNames = map fst flags
literalNames :: [(Token, String)] -- Literal names to unset, e.g. [(myfuncToken, "myfunc")]
literalNames = mapMaybe (\(_, t) -> getLiteralString t >>= (return . (,) t)) names
literalNames = mapMaybe (\(_, t) -> (,) t <$> getLiteralString t) names
-- Apply a constructor like CFUndefineVariable to each literalName, and tag with its id
unsetWith c = newNodeRange $ CFApplyEffects $ map (\(token, name) -> IdTagged (getId token) $ c name) literalNames

Expand Down
6 changes: 3 additions & 3 deletions src/ShellCheck/Parser.hs
Original file line number Diff line number Diff line change
Expand Up @@ -1195,7 +1195,7 @@ readDollarBracedPart = readSingleQuoted <|> readDoubleQuoted <|>

readDollarBracedLiteral = do
start <- startSpan
vars <- (readBraceEscaped <|> (anyChar >>= \x -> return [x])) `reluctantlyTill1` bracedQuotable
vars <- (readBraceEscaped <|> ((\x -> [x]) <$> anyChar)) `reluctantlyTill1` bracedQuotable
id <- endSpan start
return $ T_Literal id $ concat vars

Expand Down Expand Up @@ -1557,7 +1557,7 @@ readGenericLiteral endChars = do
return $ concat strings

readGenericLiteral1 endExp = do
strings <- (readGenericEscaped <|> (anyChar >>= \x -> return [x])) `reluctantlyTill1` endExp
strings <- (readGenericEscaped <|> ((\x -> [x]) <$> anyChar)) `reluctantlyTill1` endExp
return $ concat strings

readGenericEscaped = do
Expand Down Expand Up @@ -2371,7 +2371,7 @@ readPipeSequence = do
return $ T_Pipeline id pipes cmds
where
sepBy1WithSeparators p s = do
let elems = p >>= \x -> return ([x], [])
let elems = (\x -> ([x], [])) <$> p
let seps = do
separator <- s
return $ \(a,b) (c,d) -> (a++c, b ++ d ++ [separator])
Expand Down

0 comments on commit 980e7d3

Please sign in to comment.