6 Commits

Author SHA1 Message Date
Vidar Holen
2f7bd556e8 Stable version 0.3.7
This is purely a bugfix bump that compiles on GHC 7.10
and uses a regex lib that doesn't crash on OS X.
2015-04-16 08:13:49 -07:00
Vidar Holen
081751c1b5 Fixed case sensitivity in 'trap' bashism test 2015-04-05 10:33:54 -07:00
Vidar Holen
cc86aab3f1 Added multiple new checks from checkbashisms 2015-04-05 10:25:00 -07:00
Vidar Holen
9f1f00cdd1 Switch from regex-compat to regex-tdfa 2015-04-04 16:26:28 -07:00
Vidar Holen
93debd3556 Add expect to list of known non-shells 2015-04-02 19:22:47 -07:00
Vidar Holen
47b971c582 Declared FlexibleContexts for GHC 7.10 2015-03-31 21:59:03 -07:00
5 changed files with 188 additions and 71 deletions

View File

@@ -1,5 +1,5 @@
Name: ShellCheck Name: ShellCheck
Version: 0.3.6 Version: 0.3.7
Synopsis: Shell script analysis tool Synopsis: Shell script analysis tool
License: AGPL-3 License: AGPL-3
License-file: LICENSE License-file: LICENSE
@@ -43,7 +43,7 @@ library
json, json,
mtl, mtl,
parsec, parsec,
regex-compat, regex-tdfa,
QuickCheck >= 2.7.4 QuickCheck >= 2.7.4
exposed-modules: exposed-modules:
ShellCheck.Analytics ShellCheck.Analytics
@@ -51,6 +51,7 @@ library
ShellCheck.Data ShellCheck.Data
ShellCheck.Options ShellCheck.Options
ShellCheck.Parser ShellCheck.Parser
ShellCheck.Regex
ShellCheck.Simple ShellCheck.Simple
other-modules: other-modules:
Paths_ShellCheck Paths_ShellCheck
@@ -64,7 +65,7 @@ executable shellcheck
json, json,
mtl, mtl,
parsec, parsec,
regex-compat, regex-tdfa,
transformers, transformers,
QuickCheck >= 2.7.4 QuickCheck >= 2.7.4
main-is: shellcheck.hs main-is: shellcheck.hs
@@ -79,7 +80,7 @@ test-suite test-shellcheck
json, json,
mtl, mtl,
parsec, parsec,
regex-compat, regex-tdfa,
transformers, transformers,
QuickCheck >= 2.7.4 QuickCheck >= 2.7.4
main-is: test/shellcheck.hs main-is: test/shellcheck.hs

View File

@@ -19,7 +19,7 @@ module ShellCheck.AST where
import Control.Monad import Control.Monad
import Control.Monad.Identity import Control.Monad.Identity
import qualified Text.Regex as Re import qualified ShellCheck.Regex as Re
data Id = Id Int deriving (Show, Eq, Ord) data Id = Id Int deriving (Show, Eq, Ord)
@@ -128,11 +128,13 @@ data Token =
data Annotation = DisableComment Integer deriving (Show, Eq) data Annotation = DisableComment Integer deriving (Show, Eq)
data ConditionType = DoubleBracket | SingleBracket deriving (Show, Eq) data ConditionType = DoubleBracket | SingleBracket deriving (Show, Eq)
-- I apologize for nothing! -- This is an abomination.
lolHax s = Re.subRegex (Re.mkRegex "(Id [0-9]+)") (show s) "(Id 0)" tokenEquals :: Token -> Token -> Bool
instance Eq Token where tokenEquals a b = kludge a == kludge b
(==) a b = lolHax a == lolHax b where kludge s = Re.subRegex (Re.mkRegex "\\(Id [0-9]+\\)") (show s) "(Id 0)"
instance Eq Token where
(==) = tokenEquals
analyze :: Monad m => (Token -> m ()) -> (Token -> m ()) -> (Token -> Token) -> Token -> m Token analyze :: Monad m => (Token -> m ()) -> (Token -> m ()) -> (Token -> Token) -> Token -> m Token
analyze f g i = analyze f g i =

View File

@@ -15,7 +15,7 @@
You should have received a copy of the GNU Affero General Public License You should have received a copy of the GNU Affero General Public License
along with this program. If not, see <http://www.gnu.org/licenses/>. along with this program. If not, see <http://www.gnu.org/licenses/>.
-} -}
{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TemplateHaskell, FlexibleContexts #-}
module ShellCheck.Analytics (AnalysisOptions(..), defaultAnalysisOptions, filterByAnnotation, runAnalytics, shellForExecutable, runTests) where module ShellCheck.Analytics (AnalysisOptions(..), defaultAnalysisOptions, filterByAnnotation, runAnalytics, shellForExecutable, runTests) where
import Control.Arrow (first) import Control.Arrow (first)
@@ -33,7 +33,7 @@ import ShellCheck.AST
import ShellCheck.Options import ShellCheck.Options
import ShellCheck.Data import ShellCheck.Data
import ShellCheck.Parser hiding (runTests) import ShellCheck.Parser hiding (runTests)
import Text.Regex import ShellCheck.Regex
import qualified Data.Map as Map import qualified Data.Map as Map
import Test.QuickCheck.All (forAllProperties) import Test.QuickCheck.All (forAllProperties)
import Test.QuickCheck.Test (quickCheckWithResult, stdArgs, maxSuccess) import Test.QuickCheck.Test (quickCheckWithResult, stdArgs, maxSuccess)
@@ -240,12 +240,6 @@ isVariableName _ = False
potentially = fromMaybe (return ()) potentially = fromMaybe (return ())
matchAll re = unfoldr f
where
f str = do
(_, match, rest, _) <- matchRegexAll re str
return (match, rest)
willSplit x = willSplit x =
case x of case x of
T_DollarBraced {} -> True T_DollarBraced {} -> True
@@ -280,20 +274,9 @@ getSuspiciousRegexWildcard str =
suspicious = mkRegex "([A-Za-z1-9])\\*" suspicious = mkRegex "([A-Za-z1-9])\\*"
contra = mkRegex "[^a-zA-Z1-9]\\*|[][^$+\\\\]" contra = mkRegex "[^a-zA-Z1-9]\\*|[][^$+\\\\]"
matches string regex = isJust $ matchRegex regex string
headOrDefault _ (a:_) = a headOrDefault _ (a:_) = a
headOrDefault def _ = def headOrDefault def _ = def
getAllMatches :: Regex -> String -> [[String]]
getAllMatches regex str = fromJust $ f str
where
f str = do
(_, _, rest, groups) <- matchRegexAll regex str
more <- f rest
return $ groups : more
`mappend` return []
isConstant token = isConstant token =
case token of case token of
T_NormalWord _ l -> all isConstant l T_NormalWord _ l -> all isConstant l
@@ -335,15 +318,18 @@ deadSimple (TA_Sequence _ [TA_Expansion _ v]) = concatMap deadSimple v
deadSimple _ = [] deadSimple _ = []
-- Turn a SimpleCommand foo -avz --bar=baz into args ["a", "v", "z", "bar"] -- Turn a SimpleCommand foo -avz --bar=baz into args ["a", "v", "z", "bar"]
getFlags (T_SimpleCommand _ _ (_:args)) = getFlagsUntil stopCondition (T_SimpleCommand _ _ (_:args)) =
let textArgs = takeWhile (/= "--") $ map (concat . deadSimple) args in let textArgs = takeWhile (not . stopCondition . snd) $ map (\x -> (x, concat $ deadSimple x)) args in
concatMap flag textArgs concatMap flag textArgs
where where
flag ('-':'-':arg) = [ takeWhile (/= '=') arg ] flag (x, ('-':'-':arg)) = [ (x, takeWhile (/= '=') arg) ]
flag ('-':args) = map (:[]) args flag (x, ('-':args)) = map (\v -> (x, [v])) args
flag _ = [] flag _ = []
getFlags _ = error "Internal shellcheck error, please report! (getFlags on non-command)" getFlagsUntil _ _ = error "Internal shellcheck error, please report! (getFlags on non-command)"
getAllFlags = getFlagsUntil (== "--")
getLeadingFlags = getFlagsUntil (not . ("-" `isPrefixOf`))
(!!!) list i = (!!!) list i =
case drop i list of case drop i list of
@@ -413,14 +399,19 @@ checkEchoSed _ (T_Pipeline id _ [a, b]) =
["sed", "-e", v] -> checkIn v ["sed", "-e", v] -> checkIn v
_ -> return () _ -> return ()
where where
sedRe = mkRegex "^s(.)(.*)\\1(.*)\\1g?$" -- This should have used backreferences, but TDFA doesn't support them
sedRe = mkRegex "^s(.)([^\n]*)g?$"
isSimpleSed s = fromMaybe False $ do
[first,rest] <- matchRegex sedRe s
let delimiters = filter (== (first !! 0)) rest
guard $ length delimiters == 2
return True
acmd = deadSimple a acmd = deadSimple a
bcmd = deadSimple b bcmd = deadSimple b
checkIn s = checkIn s =
case matchRegex sedRe s of when (isSimpleSed s) $
Just _ -> style id 2001 style id 2001 "See if you can use ${variable//search/replace} instead."
"See if you can use ${variable//search/replace} instead."
_ -> return ()
checkEchoSed _ _ = return () checkEchoSed _ _ = return ()
prop_checkPipedAssignment1 = verify checkPipedAssignment "A=ls | grep foo" prop_checkPipedAssignment1 = verify checkPipedAssignment "A=ls | grep foo"
@@ -642,6 +633,13 @@ prop_checkBashisms16= verify checkBashisms "echo $RANDOM"
prop_checkBashisms17= verify checkBashisms "echo $((RANDOM%6+1))" prop_checkBashisms17= verify checkBashisms "echo $((RANDOM%6+1))"
prop_checkBashisms18= verify checkBashisms "foo &> /dev/null" prop_checkBashisms18= verify checkBashisms "foo &> /dev/null"
prop_checkBashisms19= verify checkBashisms "foo > file*.txt" prop_checkBashisms19= verify checkBashisms "foo > file*.txt"
prop_checkBashisms20= verify checkBashisms "read -ra foo"
prop_checkBashisms21= verify checkBashisms "[ -a foo ]"
prop_checkBashisms22= verifyNot checkBashisms "[ foo -a bar ]"
prop_checkBashisms23= verify checkBashisms "trap mything err int"
prop_checkBashisms24= verifyNot checkBashisms "trap mything int term"
prop_checkBashisms25= verify checkBashisms "cat < /dev/tcp/host/123"
prop_checkBashisms26= verify checkBashisms "trap mything ERR SIGTERM"
checkBashisms _ = bashism checkBashisms _ = bashism
where where
errMsg id s = err id 2040 $ "In sh, " ++ s ++ " not supported, even when sh is actually bash." errMsg id s = err id 2040 $ "In sh, " ++ s ++ " not supported, even when sh is actually bash."
@@ -660,24 +658,42 @@ checkBashisms _ = bashism
bashism (TC_Binary id SingleBracket op _ _) bashism (TC_Binary id SingleBracket op _ _)
| op `elem` [ "-nt", "-ef", "\\<", "\\>", "==" ] = | op `elem` [ "-nt", "-ef", "\\<", "\\>", "==" ] =
warnMsg id $ op ++ " is" warnMsg id $ op ++ " is"
bashism (TC_Unary id _ "-a" _) =
warnMsg id "unary -a in place of -e is"
bashism (TA_Unary id op _) bashism (TA_Unary id op _)
| op `elem` [ "|++", "|--", "++|", "--|"] = | op `elem` [ "|++", "|--", "++|", "--|"] =
warnMsg id $ filter (/= '|') op ++ " is" warnMsg id $ filter (/= '|') op ++ " is"
bashism t@(T_SimpleCommand id _ _) bashism (TA_Binary id "**" _ _) = warnMsg id "exponentials are"
| t `isCommand` "source" =
warnMsg id "'source' in place of '.' is"
bashism (T_FdRedirect id "&" (T_IoFile _ (T_Greater _) _)) = warnMsg id "&> is" bashism (T_FdRedirect id "&" (T_IoFile _ (T_Greater _) _)) = warnMsg id "&> is"
bashism t@(TA_Expansion id _) | getLiteralString t == Just "RANDOM" = bashism (T_IoFile id _ word) | isNetworked =
warnMsg id "RANDOM is" warnMsg id "/dev/{tcp,udp} is"
bashism t@(T_DollarBraced id _) | getBracedReference (bracedString t) == "RANDOM" = where
warnMsg id "$RANDOM is" file = onlyLiteralString word
bashism (T_DollarBraced id token) = isNetworked = any (`isPrefixOf` file) ["/dev/tcp", "/dev/udp"]
bashism t@(TA_Expansion id _) | isBashism =
warnMsg id $ fromJust str ++ " is"
where
str = getLiteralString t
isBashism = isJust str && fromJust str `elem` bashVars
bashism t@(T_DollarBraced id token) = do
mapM_ check expansion mapM_ check expansion
when (var `elem` bashVars) $ warnMsg id $ var ++ " is"
where where
str = concat $ deadSimple token str = concat $ deadSimple token
var = getBracedReference (bracedString token)
check (regex, feature) = check (regex, feature) =
when (isJust $ matchRegex regex str) $ warnMsg id feature when (isJust $ matchRegex regex str) $ warnMsg id feature
bashism t@(T_Pipe id "|&") =
warnMsg id "|& in place of 2>&1 | is"
bashism (T_Array id _) =
warnMsg id "arrays are"
bashism (T_IoFile id _ t) | isGlob t =
warnMsg id "redirecting to/from globs is"
bashism (T_CoProc id _ _) =
warnMsg id "coproc is"
bashism t@(T_SimpleCommand _ _ (cmd:arg:_)) bashism t@(T_SimpleCommand _ _ (cmd:arg:_))
| t `isCommand` "echo" && "-" `isPrefixOf` argString = | t `isCommand` "echo" && "-" `isPrefixOf` argString =
unless ("--" `isPrefixOf` argString) $ -- echo "-------" unless ("--" `isPrefixOf` argString) $ -- echo "-------"
@@ -688,14 +704,38 @@ checkBashisms _ = bashism
warnMsg (getId arg) "exec flags are" warnMsg (getId arg) "exec flags are"
bashism t@(T_SimpleCommand id _ _) bashism t@(T_SimpleCommand id _ _)
| t `isCommand` "let" = warnMsg id "'let' is" | t `isCommand` "let" = warnMsg id "'let' is"
bashism t@(T_Pipe id "|&") =
warnMsg id "|& in place of 2>&1 | is" bashism t@(T_SimpleCommand id _ (cmd:rest)) =
bashism (T_Array id _) = let name = fromMaybe "" $ getCommandName t
warnMsg id "arrays are" flags = getLeadingFlags t
bashism (T_IoFile id _ t) | isGlob t = in do
warnMsg id "redirecting to/from globs is" when (name `elem` bashCommands) $ warnMsg id $ "'" ++ name ++ "' is"
bashism (T_CoProc id _ _) = potentially $ do
warnMsg id "coproc is" allowed <- Map.lookup name allowedFlags
(word, flag) <- listToMaybe $ filter (\x -> snd x `notElem` allowed) flags
return . warnMsg (getId word) $ name ++ " -" ++ flag ++ " is"
when (name == "source") $ warnMsg id "'source' in place of '.' is"
when (name == "trap") $
let
check token = potentially $ do
word <- liftM (map toLower) $ getLiteralString token
guard $ word `elem` ["err", "debug", "return"]
return $ warnMsg (getId token) $ "trapping " ++ word ++ " is"
in
mapM_ check (reverse rest)
where
bashCommands = [
"let", "caller", "builtin", "complete", "compgen", "declare", "dirs", "disown",
"enable", "mapfile", "readarray", "pushd", "popd", "shopt", "suspend", "type",
"typeset"
]
allowedFlags = Map.fromList [
("read", ["r"]),
("ulimit", ["f"]),
("echo", []),
("exec", [])
]
bashism _ = return () bashism _ = return ()
@@ -705,8 +745,11 @@ checkBashisms _ = bashism
(re $ "^![" ++ varChars ++ "]+\\[[*@]]$", "array key expansion is"), (re $ "^![" ++ varChars ++ "]+\\[[*@]]$", "array key expansion is"),
(re $ "^![" ++ varChars ++ "]+[*@]$", "name matching prefixes are"), (re $ "^![" ++ varChars ++ "]+[*@]$", "name matching prefixes are"),
(re $ "^[" ++ varChars ++ "]+:[^-=?+]", "string indexing is"), (re $ "^[" ++ varChars ++ "]+:[^-=?+]", "string indexing is"),
(re $ "^[" ++ varChars ++ "]+(\\[.*\\])?/", "string replacement is"), (re $ "^[" ++ varChars ++ "]+(\\[.*\\])?/", "string replacement is")
(re "^RANDOM$", "$RANDOM is") ]
bashVars = [
"RANDOM", "LINENO", "OSTYPE", "MACHTYPE", "HOSTTYPE", "HOSTNAME",
"DIRSTACK", "EUID", "UID", "SECONDS", "SHLVL", "PIPESTATUS", "SHELLOPTS"
] ]
prop_checkForInQuoted = verify checkForInQuoted "for f in \"$(ls)\"; do echo foo; done" prop_checkForInQuoted = verify checkForInQuoted "for f in \"$(ls)\"; do echo foo; done"
@@ -2017,15 +2060,15 @@ data StackData =
-- (Base expression, specific position, var name, assigned values) -- (Base expression, specific position, var name, assigned values)
| Assignment (Token, Token, String, DataType) | Assignment (Token, Token, String, DataType)
| Reference (Token, Token, String) | Reference (Token, Token, String)
deriving (Show, Eq) deriving (Show)
data DataType = DataString DataSource | DataArray DataSource data DataType = DataString DataSource | DataArray DataSource
deriving (Show, Eq) deriving (Show)
data DataSource = SourceFrom [Token] | SourceExternal | SourceDeclaration data DataSource = SourceFrom [Token] | SourceExternal | SourceDeclaration
deriving (Show, Eq) deriving (Show)
data VariableState = Dead Token String | Alive deriving (Show, Eq) data VariableState = Dead Token String | Alive deriving (Show)
dataTypeFrom defaultType v = (case v of T_Array {} -> DataArray; _ -> defaultType) $ SourceFrom [v] dataTypeFrom defaultType v = (case v of T_Array {} -> DataArray; _ -> defaultType) $ SourceFrom [v]
@@ -2111,7 +2154,7 @@ getReferencedVariableCommand base@(T_SimpleCommand _ _ (T_NormalWord _ (T_Litera
getReference t@(T_Assignment _ _ name _ value) = [(t, t, name)] getReference t@(T_Assignment _ _ name _ value) = [(t, t, name)]
getReference t@(T_NormalWord _ [T_Literal _ name]) | not ("-" `isPrefixOf` name) = [(t, t, name)] getReference t@(T_NormalWord _ [T_Literal _ name]) | not ("-" `isPrefixOf` name) = [(t, t, name)]
getReference _ = [] getReference _ = []
flags = getFlags base flags = map snd $ getAllFlags base
getReferencedVariableCommand _ = [] getReferencedVariableCommand _ = []
@@ -2144,7 +2187,7 @@ getModifiedVariableCommand base@(T_SimpleCommand _ _ (T_NormalWord _ (T_Literal
_ -> [] _ -> []
where where
flags = getFlags base flags = map snd $ getAllFlags base
stripEquals s = let rest = dropWhile (/= '=') s in stripEquals s = let rest = dropWhile (/= '=') s in
if rest == "" then "" else tail rest if rest == "" then "" else tail rest
stripEqualsFrom (T_NormalWord id1 (T_Literal id2 s:rs)) = stripEqualsFrom (T_NormalWord id1 (T_Literal id2 s:rs)) =
@@ -2220,10 +2263,11 @@ getBracedReference s = fromMaybe s $
getSpecial _ = fail "empty" getSpecial _ = fail "empty"
getIndexReferences s = fromMaybe [] $ do getIndexReferences s = fromMaybe [] $ do
(_, index, _, _) <- matchRegexAll re s match <- matchRegex re s
return $ matchAll variableNameRegex index index <- match !!! 0
return $ matchAllStrings variableNameRegex index
where where
re = mkRegex "\\[.*\\]" re = mkRegex "(\\[.*\\])"
getReferencedVariables t = getReferencedVariables t =
case t of case t of
@@ -2263,7 +2307,7 @@ getReferencedVariables t =
prop_getVariablesFromLiteral1 = prop_getVariablesFromLiteral1 =
getVariablesFromLiteral "$foo${bar//a/b}$BAZ" == ["foo", "bar", "BAZ"] getVariablesFromLiteral "$foo${bar//a/b}$BAZ" == ["foo", "bar", "BAZ"]
getVariablesFromLiteral string = getVariablesFromLiteral string =
map (!! 0) $ getAllMatches variableRegex string map (!! 0) $ matchAllSubgroups variableRegex string
where where
variableRegex = mkRegex "\\$\\{?([A-Za-z0-9_]+)" variableRegex = mkRegex "\\$\\{?([A-Za-z0-9_]+)"
@@ -3107,9 +3151,7 @@ checkMultipleAppends params t =
mapM_ checkList $ getCommandSequences t mapM_ checkList $ getCommandSequences t
where where
checkList list = checkList list =
mapM_ checkGroup groups mapM_ checkGroup (groupWith (liftM fst) $ map getTarget list)
where
groups = groupWith (liftM fst) $ map getTarget list
checkGroup (f:_:_:_) | isJust f = checkGroup (f:_:_:_) | isJust f =
style (snd $ fromJust f) 2129 style (snd $ fromJust f) 2129
"Consider using { cmd1; cmd2; } >> file instead of individual redirects." "Consider using { cmd1; cmd2; } >> file instead of individual redirects."
@@ -3256,7 +3298,7 @@ prop_checkMaskedReturns5 = verifyNot checkMaskedReturns "f() { local -r a=$(fals
checkMaskedReturns _ t@(T_SimpleCommand id _ (cmd:rest)) = potentially $ do checkMaskedReturns _ t@(T_SimpleCommand id _ (cmd:rest)) = potentially $ do
name <- getCommandName t name <- getCommandName t
guard $ name `elem` ["declare", "export"] guard $ name `elem` ["declare", "export"]
|| name == "local" && "r" `notElem` getFlags t || name == "local" && "r" `notElem` (map snd $ getAllFlags t)
return $ mapM_ checkArgs rest return $ mapM_ checkArgs rest
where where
checkArgs (T_Assignment id _ _ _ word) | any hasReturn $ getWordParts word = checkArgs (T_Assignment id _ _ _ word) | any hasReturn $ getWordParts word =

View File

@@ -15,7 +15,7 @@
You should have received a copy of the GNU Affero General Public License You should have received a copy of the GNU Affero General Public License
along with this program. If not, see <http://www.gnu.org/licenses/>. along with this program. If not, see <http://www.gnu.org/licenses/>.
-} -}
{-# LANGUAGE NoMonomorphismRestriction, TemplateHaskell #-} {-# LANGUAGE NoMonomorphismRestriction, TemplateHaskell, FlexibleContexts #-}
module ShellCheck.Parser (Note(..), Severity(..), parseShell, ParseResult(..), ParseNote(..), sortNotes, noteToParseNote, runTests, readScript) where module ShellCheck.Parser (Note(..), Severity(..), parseShell, ParseResult(..), ParseNote(..), sortNotes, noteToParseNote, runTests, readScript) where
import ShellCheck.AST import ShellCheck.AST
@@ -2095,6 +2095,7 @@ readScript = do
badShells = [ badShells = [
"awk", "awk",
"csh", "csh",
"expect",
"perl", "perl",
"python", "python",
"ruby", "ruby",

71
ShellCheck/Regex.hs Normal file
View File

@@ -0,0 +1,71 @@
{-
This file is part of ShellCheck.
http://www.vidarholen.net/contents/shellcheck
ShellCheck is free software: you can redistribute it and/or modify
it under the terms of the GNU Affero General Public License as published by
the Free Software Foundation, either version 3 of the License, or
(at your option) any later version.
ShellCheck is distributed in the hope that it will be useful,
but WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
GNU Affero General Public License for more details.
You should have received a copy of the GNU Affero General Public License
along with this program. If not, see <http://www.gnu.org/licenses/>.
-}
{-# LANGUAGE FlexibleContexts #-}
-- Basically Text.Regex based on regex-tdfa instead of the buggy regex-posix.
module ShellCheck.Regex where
import Data.List
import Data.Maybe
import Control.Monad
import Text.Regex.TDFA
-- Precompile the regex
mkRegex :: String -> Regex
mkRegex str =
let make :: RegexMaker Regex CompOption ExecOption String => String -> Regex
make = makeRegex
in
make str
-- Does the regex match?
matches :: String -> Regex -> Bool
matches = flip match
-- Get all subgroups of the first match
matchRegex :: Regex -> String -> Maybe [String]
matchRegex re str = do
(_, _, _, groups) <- matchM re str :: Maybe (String,String,String,[String])
return groups
-- Get all full matches
matchAllStrings :: Regex -> String -> [String]
matchAllStrings re = unfoldr f
where
f :: String -> Maybe (String, String)
f str = do
(_, match, rest, _) <- matchM re str :: Maybe (String, String, String, [String])
return (match, rest)
-- Get all subgroups from all matches
matchAllSubgroups :: Regex -> String -> [[String]]
matchAllSubgroups re = unfoldr f
where
f :: String -> Maybe ([String], String)
f str = do
(_, _, rest, groups) <- matchM re str :: Maybe (String, String, String, [String])
return (groups, rest)
-- Replace regex in input with string
subRegex :: Regex -> String -> String -> String
subRegex re input replacement = f input
where
f str = fromMaybe str $ do
(before, match, after) <- matchM re str :: Maybe (String, String, String)
when (null match) $ error ("Internal error: substituted empty in " ++ str)
return $ before ++ replacement ++ f after