Merge branch 'doctest-new-build' of https://github.com/phadej/shellcheck into phadej-doctest-new-build

This commit is contained in:
Vidar Holen 2018-12-16 18:33:21 -08:00
commit 21462b11b3
16 changed files with 1831 additions and 1688 deletions

3
.gitignore vendored
View file

@ -13,6 +13,9 @@ cabal-dev
cabal.sandbox.config cabal.sandbox.config
cabal.config cabal.config
.stack-work .stack-work
dist-newstyle/
.ghc.environment.*
cabal.project.local
### Snap ### ### Snap ###
/snap/.snapcraft/ /snap/.snapcraft/

View file

@ -3,20 +3,53 @@ FROM ubuntu:18.04 AS build
USER root USER root
WORKDIR /opt/shellCheck WORKDIR /opt/shellCheck
# Install OS deps # Install OS deps, including GHC from HVR-PPA
RUN apt-get update && apt-get install -y ghc cabal-install # https://launchpad.net/~hvr/+archive/ubuntu/ghc
RUN apt-get -yq update \
&& apt-get -yq install software-properties-common \
&& apt-add-repository -y "ppa:hvr/ghc" \
&& apt-get -yq update \
&& apt-get -yq install cabal-install-2.4 ghc-8.4.3 pandoc \
&& rm -rf /var/lib/apt/lists/*
ENV PATH="/opt/ghc/bin:${PATH}"
# Use gold linker and check tools versions
RUN ln -s $(which ld.gold) /usr/local/bin/ld && \
cabal --version \
&& ghc --version \
&& ld --version
# Install Haskell deps # Install Haskell deps
# (This is a separate copy/run so that source changes don't require rebuilding) # (This is a separate copy/run so that source changes don't require rebuilding)
#
# We also patch regex-tdfa and aeson removing hard-coded -O2 flag.
# This makes compilation faster and binary smaller.
# Performance loss is unnoticeable for ShellCheck
#
# Remember to update versions, once in a while.
COPY ShellCheck.cabal ./ COPY ShellCheck.cabal ./
RUN cabal update && cabal install --dependencies-only --ghc-options="-optlo-Os -split-sections" RUN cabal update && \
cabal get regex-tdfa-1.2.3.1 && sed -i 's/-O2//' regex-tdfa-1.2.3.1/regex-tdfa.cabal && \
cabal get aeson-1.4.0.0 && sed -i 's/-O2//' aeson-1.4.0.0/aeson.cabal && \
echo 'packages: . regex-tdfa-1.2.3.1 aeson-1.4.0.0 > cabal.project' && \
cabal new-build --dependencies-only \
--disable-executable-dynamic --enable-split-sections --disable-tests
# Copy source and build it # Copy source and build it
COPY LICENSE Setup.hs shellcheck.hs ./ COPY LICENSE Setup.hs shellcheck.hs shellcheck.1.md ./
COPY src src COPY src src
RUN cabal build Paths_ShellCheck && \ COPY test test
ghc -optl-static -optl-pthread -isrc -idist/build/autogen --make shellcheck -split-sections -optc-Wl,--gc-sections -optlo-Os && \ # This SED is the only "nastyness" we have to do
strip --strip-all shellcheck # Hopefully soon we could add per-component ld-options to cabal.project
RUN sed -i 's/-- STATIC/ld-options: -static -pthread -Wl,--gc-sections/' ShellCheck.cabal && \
cat ShellCheck.cabal && \
cabal new-build \
--disable-executable-dynamic --enable-split-sections --disable-tests && \
cp $(find dist-newstyle -type f -name shellcheck) . && \
strip --strip-all shellcheck && \
file shellcheck && \
ls -l shellcheck
RUN mkdir -p /out/bin && \ RUN mkdir -p /out/bin && \
cp shellcheck /out/bin/ cp shellcheck /out/bin/

View file

@ -1,3 +1,8 @@
{-# LANGUAGE CPP #-}
{-# OPTIONS_GHC -Wall #-}
module Main (main) where
import Distribution.PackageDescription ( import Distribution.PackageDescription (
HookedBuildInfo, HookedBuildInfo,
emptyHookedBuildInfo ) emptyHookedBuildInfo )
@ -9,12 +14,42 @@ import Distribution.Simple (
import Distribution.Simple.Setup ( SDistFlags ) import Distribution.Simple.Setup ( SDistFlags )
import System.Process ( system ) import System.Process ( system )
import System.Directory ( doesFileExist, getModificationTime )
#ifndef MIN_VERSION_cabal_doctest
#define MIN_VERSION_cabal_doctest(x,y,z) 0
#endif
#if MIN_VERSION_cabal_doctest(1,0,0)
import Distribution.Extra.Doctest ( addDoctestsUserHook )
main :: IO ()
main = defaultMainWithHooks $ addDoctestsUserHook "doctests" myHooks
where
myHooks = simpleUserHooks { preSDist = myPreSDist }
#else
#ifdef MIN_VERSION_Cabal
-- If the macro is defined, we have new cabal-install,
-- but for some reason we don't have cabal-doctest in package-db
--
-- Probably we are running cabal sdist, when otherwise using new-build
-- workflow
#warning You are configuring this package without cabal-doctest installed. \
The doctests test-suite will not work as a result. \
To fix this, install cabal-doctest before configuring.
#endif
main :: IO ()
main = defaultMainWithHooks myHooks main = defaultMainWithHooks myHooks
where where
myHooks = simpleUserHooks { preSDist = myPreSDist } myHooks = simpleUserHooks { preSDist = myPreSDist }
#endif
-- | This hook will be executed before e.g. @cabal sdist@. It runs -- | This hook will be executed before e.g. @cabal sdist@. It runs
-- pandoc to create the man page from shellcheck.1.md. If the pandoc -- pandoc to create the man page from shellcheck.1.md. If the pandoc
-- command is not found, this will fail with an error message: -- command is not found, this will fail with an error message:
@ -27,10 +62,20 @@ main = defaultMainWithHooks myHooks
-- --
myPreSDist :: Args -> SDistFlags -> IO HookedBuildInfo myPreSDist :: Args -> SDistFlags -> IO HookedBuildInfo
myPreSDist _ _ = do myPreSDist _ _ = do
putStrLn "Building the man page (shellcheck.1) with pandoc..." exists <- doesFileExist "shellcheck.1"
putStrLn pandoc_cmd if exists
result <- system pandoc_cmd then do
putStrLn $ "pandoc exited with " ++ show result source <- getModificationTime "shellcheck.1.md"
target <- getModificationTime "shellcheck.1"
if target < source
then makeManPage
else putStrLn "shellcheck.1 is more recent than shellcheck.1.md"
else makeManPage
return emptyHookedBuildInfo return emptyHookedBuildInfo
where where
pandoc_cmd = "pandoc -s -f markdown-smart -t man shellcheck.1.md -o shellcheck.1" makeManPage = do
putStrLn "Building the man page (shellcheck.1) with pandoc..."
putStrLn pandoc_cmd
result <- system pandoc_cmd
putStrLn $ "pandoc exited with " ++ show result
pandoc_cmd = "pandoc -s -t man shellcheck.1.md -o shellcheck.1"

View file

@ -28,16 +28,14 @@ Extra-Source-Files:
shellcheck.1.md shellcheck.1.md
-- built with a cabal sdist hook -- built with a cabal sdist hook
shellcheck.1 shellcheck.1
-- convenience script for stripping tests
striptests
-- tests
test/shellcheck.hs
custom-setup custom-setup
setup-depends: setup-depends:
base >= 4 && <5, base >= 4 && <5,
process >= 1.0 && <1.7, directory >= 1.2 && <1.4,
Cabal >= 1.10 && <2.5 process >= 1.0 && <1.7,
cabal-doctest >= 1.0.6 && <1.1,
Cabal >= 1.10 && <2.5
source-repository head source-repository head
type: git type: git
@ -60,7 +58,6 @@ library
mtl >= 2.2.1, mtl >= 2.2.1,
parsec, parsec,
regex-tdfa, regex-tdfa,
QuickCheck >= 2.7.4,
-- When cabal supports it, move this to setup-depends: -- When cabal supports it, move this to setup-depends:
process process
exposed-modules: exposed-modules:
@ -98,23 +95,23 @@ executable shellcheck
directory, directory,
mtl >= 2.2.1, mtl >= 2.2.1,
parsec >= 3.0, parsec >= 3.0,
QuickCheck >= 2.7.4,
regex-tdfa regex-tdfa
main-is: shellcheck.hs main-is: shellcheck.hs
test-suite test-shellcheck -- Marker to add flags for static linking
type: exitcode-stdio-1.0 -- STATIC
build-depends:
aeson,
base >= 4 && < 5,
bytestring,
deepseq >= 1.4.0.0,
ShellCheck,
containers,
directory,
mtl >= 2.2.1,
parsec,
QuickCheck >= 2.7.4,
regex-tdfa
main-is: test/shellcheck.hs
test-suite doctests
type: exitcode-stdio-1.0
main-is: doctests.hs
build-depends:
base,
doctest >= 0.16.0 && <0.17,
QuickCheck >=2.11 && <2.13,
ShellCheck,
template-haskell
x-doctest-options: --fast
ghc-options: -Wall -threaded
hs-source-dirs: test

View file

@ -3,3 +3,10 @@
# This allows testing changes without recompiling. # This allows testing changes without recompiling.
runghc -isrc -idist/build/autogen shellcheck.hs "$@" runghc -isrc -idist/build/autogen shellcheck.hs "$@"
# Note: with new-build you can
#
# % cabal new-run --disable-optimization -- shellcheck "$@"
#
# This does build the executable, but as the optimisation is disabled,
# the build is quite fast.

View file

@ -1,22 +1,21 @@
#!/usr/bin/env bash #!/bin/bash
# quicktest runs the ShellCheck unit tests in an interpreted mode. # shellcheck disable=SC2091
# This allows running tests without compiling, which can be faster.
# quicktest runs the ShellCheck unit tests.
# Once `doctests` test executable is build, we can just run it
# This allows running tests without compiling library, which is faster.
# 'cabal test' remains the source of truth. # 'cabal test' remains the source of truth.
( $(find dist -type f -name doctests)
var=$(echo 'liftM and $ sequence [
ShellCheck.Analytics.runTests # Note: if you have build the project with new-build
,ShellCheck.Parser.runTests #
,ShellCheck.Checker.runTests # % cabal new-build -w ghc-8.4.3 --enable-tests
,ShellCheck.Checks.Commands.runTests #
,ShellCheck.Checks.ShellSupport.runTests # and have cabal-plan installed (e.g. with cabal new-install cabal-plan),
,ShellCheck.AnalyzerLib.runTests # then you can quicktest with
]' | tr -d '\n' | cabal repl ShellCheck 2>&1 | tee /dev/stderr) #
if [[ $var == *$'\nTrue'* ]] # % $(cabal-plan list-bin doctests)
then #
exit 0 # Once the test executable exists, we can simply run it to perform doctests
else # which use GHCi under the hood.
grep -C 3 -e "Fail" -e "Tracing" <<< "$var"
exit 1
fi
) 2>&1

File diff suppressed because it is too large Load diff

View file

@ -18,30 +18,29 @@
along with this program. If not, see <https://www.gnu.org/licenses/>. along with this program. If not, see <https://www.gnu.org/licenses/>.
-} -}
{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TemplateHaskell #-}
module ShellCheck.AnalyzerLib where module ShellCheck.AnalyzerLib where
import ShellCheck.AST
import ShellCheck.ASTLib
import ShellCheck.Data
import ShellCheck.Interface
import ShellCheck.Parser
import ShellCheck.Regex
import ShellCheck.AST import Control.Arrow (first)
import ShellCheck.ASTLib import Control.DeepSeq
import ShellCheck.Data import Control.Monad.Identity
import ShellCheck.Interface import Control.Monad.RWS
import ShellCheck.Parser import Control.Monad.State
import ShellCheck.Regex import Control.Monad.Writer
import Data.Char
import Data.List
import qualified Data.Map as Map
import Data.Maybe
import Data.Semigroup
import Control.Arrow (first) prop :: Bool -> IO ()
import Control.DeepSeq prop False = putStrLn "FAIL"
import Control.Monad.Identity prop True = return ()
import Control.Monad.RWS
import Control.Monad.State
import Control.Monad.Writer
import Data.Char
import Data.List
import Data.Maybe
import Data.Semigroup
import qualified Data.Map as Map
import Test.QuickCheck.All (forAllProperties)
import Test.QuickCheck.Test (maxSuccess, quickCheckWithResult, stdArgs)
type Analysis = AnalyzerM () type Analysis = AnalyzerM ()
type AnalyzerM a = RWS Parameters [TokenComment] Cache a type AnalyzerM a = RWS Parameters [TokenComment] Cache a
@ -216,15 +215,15 @@ containsLastpipe root =
_ -> False _ -> False
prop_determineShell0 = determineShellTest "#!/bin/sh" == Sh -- |
prop_determineShell1 = determineShellTest "#!/usr/bin/env ksh" == Ksh -- >>> prop $ determineShellTest "#!/bin/sh" == Sh
prop_determineShell2 = determineShellTest "" == Bash -- >>> prop $ determineShellTest "#!/usr/bin/env ksh" == Ksh
prop_determineShell3 = determineShellTest "#!/bin/sh -e" == Sh -- >>> prop $ determineShellTest "" == Bash
prop_determineShell4 = determineShellTest "#!/bin/ksh\n#shellcheck shell=sh\nfoo" == Sh -- >>> prop $ determineShellTest "#!/bin/sh -e" == Sh
prop_determineShell5 = determineShellTest "#shellcheck shell=sh\nfoo" == Sh -- >>> prop $ determineShellTest "#!/bin/ksh\n#shellcheck shell=sh\nfoo" == Sh
prop_determineShell6 = determineShellTest "#! /bin/sh" == Sh -- >>> prop $ determineShellTest "#shellcheck shell=sh\nfoo" == Sh
prop_determineShell7 = determineShellTest "#! /bin/ash" == Dash -- >>> prop $ determineShellTest "#! /bin/sh" == Sh
-- >>> prop $ determineShellTest "#! /bin/ash" == Dash
determineShellTest = determineShell . fromJust . prRoot . pScript determineShellTest = determineShell . fromJust . prRoot . pScript
determineShell t = fromMaybe Bash $ do determineShell t = fromMaybe Bash $ do
shellString <- foldl mplus Nothing $ getCandidates t shellString <- foldl mplus Nothing $ getCandidates t
@ -667,10 +666,11 @@ getIndexReferences s = fromMaybe [] $ do
where where
re = mkRegex "(\\[.*\\])" re = mkRegex "(\\[.*\\])"
prop_getOffsetReferences1 = getOffsetReferences ":bar" == ["bar"] -- |
prop_getOffsetReferences2 = getOffsetReferences ":bar:baz" == ["bar", "baz"] -- >>> prop $ getOffsetReferences ":bar" == ["bar"]
prop_getOffsetReferences3 = getOffsetReferences "[foo]:bar" == ["bar"] -- >>> prop $ getOffsetReferences ":bar:baz" == ["bar", "baz"]
prop_getOffsetReferences4 = getOffsetReferences "[foo]:bar:baz" == ["bar", "baz"] -- >>> prop $ getOffsetReferences "[foo]:bar" == ["bar"]
-- >>> prop $ getOffsetReferences "[foo]:bar:baz" == ["bar", "baz"]
getOffsetReferences mods = fromMaybe [] $ do getOffsetReferences mods = fromMaybe [] $ do
-- if mods start with [, then drop until ] -- if mods start with [, then drop until ]
match <- matchRegex re mods match <- matchRegex re mods
@ -745,9 +745,15 @@ isUnqualifiedCommand token str = isCommandMatch token (== str)
isCommandMatch token matcher = fromMaybe False $ isCommandMatch token matcher = fromMaybe False $
fmap matcher (getCommandName token) fmap matcher (getCommandName token)
-- |
-- Does this regex look like it was intended as a glob? -- Does this regex look like it was intended as a glob?
-- True: *foo* --
-- False: .*foo.* -- >>> isConfusedGlobRegex "*foo*"
-- True
--
-- >>> isConfusedGlobRegex ".*foo.*"
-- False
--
isConfusedGlobRegex :: String -> Bool isConfusedGlobRegex :: String -> Bool
isConfusedGlobRegex ('*':_) = True isConfusedGlobRegex ('*':_) = True
isConfusedGlobRegex [x,'*'] | x /= '\\' = True isConfusedGlobRegex [x,'*'] | x /= '\\' = True
@ -757,9 +763,10 @@ isVariableStartChar x = x == '_' || isAsciiLower x || isAsciiUpper x
isVariableChar x = isVariableStartChar x || isDigit x isVariableChar x = isVariableStartChar x || isDigit x
variableNameRegex = mkRegex "[_a-zA-Z][_a-zA-Z0-9]*" variableNameRegex = mkRegex "[_a-zA-Z][_a-zA-Z0-9]*"
prop_isVariableName1 = isVariableName "_fo123" -- |
prop_isVariableName2 = not $ isVariableName "4" -- >>> prop $ isVariableName "_fo123"
prop_isVariableName3 = not $ isVariableName "test: " -- >>> prop $ not $ isVariableName "4"
-- >>> prop $ not $ isVariableName "test: "
isVariableName (x:r) = isVariableStartChar x && all isVariableChar r isVariableName (x:r) = isVariableStartChar x && all isVariableChar r
isVariableName _ = False isVariableName _ = False
@ -768,27 +775,28 @@ getVariablesFromLiteralToken token =
-- Try to get referenced variables from a literal string like "$foo" -- Try to get referenced variables from a literal string like "$foo"
-- Ignores tons of cases like arithmetic evaluation and array indices. -- Ignores tons of cases like arithmetic evaluation and array indices.
prop_getVariablesFromLiteral1 = -- >>> prop $ getVariablesFromLiteral "$foo${bar//a/b}$BAZ" == ["foo", "bar", "BAZ"]
getVariablesFromLiteral "$foo${bar//a/b}$BAZ" == ["foo", "bar", "BAZ"]
getVariablesFromLiteral string = getVariablesFromLiteral string =
map (!! 0) $ matchAllSubgroups variableRegex string map (!! 0) $ matchAllSubgroups variableRegex string
where where
variableRegex = mkRegex "\\$\\{?([A-Za-z0-9_]+)" variableRegex = mkRegex "\\$\\{?([A-Za-z0-9_]+)"
-- |
-- Get the variable name from an expansion like ${var:-foo} -- Get the variable name from an expansion like ${var:-foo}
prop_getBracedReference1 = getBracedReference "foo" == "foo" --
prop_getBracedReference2 = getBracedReference "#foo" == "foo" -- >>> prop $ getBracedReference "foo" == "foo"
prop_getBracedReference3 = getBracedReference "#" == "#" -- >>> prop $ getBracedReference "#foo" == "foo"
prop_getBracedReference4 = getBracedReference "##" == "#" -- >>> prop $ getBracedReference "#" == "#"
prop_getBracedReference5 = getBracedReference "#!" == "!" -- >>> prop $ getBracedReference "##" == "#"
prop_getBracedReference6 = getBracedReference "!#" == "#" -- >>> prop $ getBracedReference "#!" == "!"
prop_getBracedReference7 = getBracedReference "!foo#?" == "foo" -- >>> prop $ getBracedReference "!#" == "#"
prop_getBracedReference8 = getBracedReference "foo-bar" == "foo" -- >>> prop $ getBracedReference "!foo#?" == "foo"
prop_getBracedReference9 = getBracedReference "foo:-bar" == "foo" -- >>> prop $ getBracedReference "foo-bar" == "foo"
prop_getBracedReference10= getBracedReference "foo: -1" == "foo" -- >>> prop $ getBracedReference "foo:-bar" == "foo"
prop_getBracedReference11= getBracedReference "!os*" == "" -- >>> prop $ getBracedReference "foo: -1" == "foo"
prop_getBracedReference12= getBracedReference "!os?bar**" == "" -- >>> prop $ getBracedReference "!os*" == ""
prop_getBracedReference13= getBracedReference "foo[bar]" == "foo" -- >>> prop $ getBracedReference "!os?bar**" == ""
-- >>> prop $ getBracedReference "foo[bar]" == "foo"
getBracedReference s = fromMaybe s $ getBracedReference s = fromMaybe s $
nameExpansion s `mplus` takeName noPrefix `mplus` getSpecial noPrefix `mplus` getSpecial s nameExpansion s `mplus` takeName noPrefix `mplus` getSpecial noPrefix `mplus` getSpecial s
where where
@ -811,9 +819,10 @@ getBracedReference s = fromMaybe s $
return "" return ""
nameExpansion _ = Nothing nameExpansion _ = Nothing
prop_getBracedModifier1 = getBracedModifier "foo:bar:baz" == ":bar:baz" -- |
prop_getBracedModifier2 = getBracedModifier "!var:-foo" == ":-foo" -- >>> prop $ getBracedModifier "foo:bar:baz" == ":bar:baz"
prop_getBracedModifier3 = getBracedModifier "foo[bar]" == "[bar]" -- >>> prop $ getBracedModifier "!var:-foo" == ":-foo"
-- >>> prop $ getBracedModifier "foo[bar]" == "[bar]"
getBracedModifier s = fromMaybe "" . listToMaybe $ do getBracedModifier s = fromMaybe "" . listToMaybe $ do
let var = getBracedReference s let var = getBracedReference s
a <- dropModifier s a <- dropModifier s
@ -830,10 +839,13 @@ getBracedModifier s = fromMaybe "" . listToMaybe $ do
-- Run an action in a Maybe (or do nothing). -- Run an action in a Maybe (or do nothing).
-- Example: -- Example:
--
-- @
-- potentially $ do -- potentially $ do
-- s <- getLiteralString cmd -- s <- getLiteralString cmd
-- guard $ s `elem` ["--recursive", "-r"] -- guard $ s `elem` ["--recursive", "-r"]
-- return $ warn .. "Something something recursive" -- return $ warn .. "Something something recursive"
-- @
potentially :: Monad m => Maybe (m ()) -> m () potentially :: Monad m => Maybe (m ()) -> m ()
potentially = fromMaybe (return ()) potentially = fromMaybe (return ())
@ -918,6 +930,3 @@ getOpts flagTokenizer string cmd = process flags
else do else do
more <- process rest2 more <- process rest2
return $ (flag1, token1) : more return $ (flag1, token1) : more
return []
runTests = $( [| $(forAllProperties) (quickCheckWithResult (stdArgs { maxSuccess = 1 }) ) |])

View file

@ -17,8 +17,7 @@
You should have received a copy of the GNU General Public License You should have received a copy of the GNU General Public License
along with this program. If not, see <https://www.gnu.org/licenses/>. along with this program. If not, see <https://www.gnu.org/licenses/>.
-} -}
{-# LANGUAGE TemplateHaskell #-} module ShellCheck.Checker (checkScript) where
module ShellCheck.Checker (checkScript, ShellCheck.Checker.runTests) where
import ShellCheck.Interface import ShellCheck.Interface
import ShellCheck.Parser import ShellCheck.Parser
@ -35,8 +34,6 @@ import qualified System.IO
import Prelude hiding (readFile) import Prelude hiding (readFile)
import Control.Monad import Control.Monad
import Test.QuickCheck.All
tokenToPosition startMap t = fromMaybe fail $ do tokenToPosition startMap t = fromMaybe fail $ do
span <- Map.lookup (tcId t) startMap span <- Map.lookup (tcId t) startMap
return $ newPositionedComment { return $ newPositionedComment {
@ -125,113 +122,132 @@ checkRecursive includes src =
csCheckSourced = True csCheckSourced = True
} }
prop_findsParseIssue = check "echo \"$12\"" == [1037] -- | Dummy binding for doctest to run
--
prop_commentDisablesParseIssue1 = -- >>> check "echo \"$12\""
null $ check "#shellcheck disable=SC1037\necho \"$12\"" -- [1037]
prop_commentDisablesParseIssue2 = --
null $ check "#shellcheck disable=SC1037\n#lol\necho \"$12\"" -- >>> check "#shellcheck disable=SC1037\necho \"$12\""
-- []
prop_findsAnalysisIssue = --
check "echo $1" == [2086] -- >>> check "#shellcheck disable=SC1037\n#lol\necho \"$12\""
prop_commentDisablesAnalysisIssue1 = -- []
null $ check "#shellcheck disable=SC2086\necho $1" --
prop_commentDisablesAnalysisIssue2 = -- >>> check "echo $1"
null $ check "#shellcheck disable=SC2086\n#lol\necho $1" -- [2086]
--
prop_optionDisablesIssue1 = -- >>> check "#shellcheck disable=SC2086\necho $1"
null $ getErrors -- []
(mockedSystemInterface []) --
emptyCheckSpec { -- >>> check "#shellcheck disable=SC2086\n#lol\necho $1"
csScript = "echo $1", -- []
csExcludedWarnings = [2148, 2086] --
} -- >>> :{
-- getErrors
prop_optionDisablesIssue2 = -- (mockedSystemInterface [])
null $ getErrors -- emptyCheckSpec {
(mockedSystemInterface []) -- csScript = "echo $1",
emptyCheckSpec { -- csExcludedWarnings = [2148, 2086]
csScript = "echo \"$10\"", -- }
csExcludedWarnings = [2148, 1037] -- :}
} -- []
--
prop_wontParseBadShell = -- >>> :{
[1071] == check "#!/usr/bin/python\ntrue $1\n" -- getErrors
-- (mockedSystemInterface [])
prop_optionDisablesBadShebang = -- emptyCheckSpec {
null $ getErrors -- csScript = "echo \"$10\"",
(mockedSystemInterface []) -- csExcludedWarnings = [2148, 1037]
emptyCheckSpec { -- }
csScript = "#!/usr/bin/python\ntrue\n", -- :}
csShellTypeOverride = Just Sh -- []
} --
-- >>> check "#!/usr/bin/python\ntrue $1\n"
prop_annotationDisablesBadShebang = -- [1071]
[] == check "#!/usr/bin/python\n# shellcheck shell=sh\ntrue\n" --
-- >>> :{
-- getErrors
prop_canParseDevNull = -- (mockedSystemInterface [])
[] == check "source /dev/null" -- emptyCheckSpec {
-- csScript = "#!/usr/bin/python\ntrue\n",
prop_failsWhenNotSourcing = -- csShellTypeOverride = Just Sh
[1091, 2154] == check "source lol; echo \"$bar\"" -- }
-- :}
prop_worksWhenSourcing = -- []
null $ checkWithIncludes [("lib", "bar=1")] "source lib; echo \"$bar\"" --
-- >>> check "#!/usr/bin/python\n# shellcheck shell=sh\ntrue\n"
prop_worksWhenDotting = -- []
null $ checkWithIncludes [("lib", "bar=1")] ". lib; echo \"$bar\"" --
-- >>> check "source /dev/null"
prop_noInfiniteSourcing = -- []
[] == checkWithIncludes [("lib", "source lib")] "source lib" --
-- >>> check "source lol; echo \"$bar\""
prop_canSourceBadSyntax = -- [1091,2154]
[1094, 2086] == checkWithIncludes [("lib", "for f; do")] "source lib; echo $1" --
-- >>> checkWithIncludes [("lib", "bar=1")] "source lib; echo \"$bar\""
prop_cantSourceDynamic = -- []
[1090] == checkWithIncludes [("lib", "")] ". \"$1\"" --
-- >>> checkWithIncludes [("lib", "bar=1")] ". lib; echo \"$bar\""
prop_cantSourceDynamic2 = -- []
[1090] == checkWithIncludes [("lib", "")] "source ~/foo" --
-- >>> checkWithIncludes [("lib", "source lib")] "source lib"
prop_canSourceDynamicWhenRedirected = -- []
null $ checkWithIncludes [("lib", "")] "#shellcheck source=lib\n. \"$1\"" --
-- >>> checkWithIncludes [("lib", "for f; do")] "source lib; echo $1"
prop_recursiveAnalysis = -- [1094,2086]
[2086] == checkRecursive [("lib", "echo $1")] "source lib" --
-- >>> checkWithIncludes [("lib", "")] ". \"$1\""
prop_recursiveParsing = -- [1090]
[1037] == checkRecursive [("lib", "echo \"$10\"")] "source lib" --
-- >>> checkWithIncludes [("lib", "")] "source ~/foo"
prop_sourceDirectiveDoesntFollowFile = -- [1090]
null $ checkWithIncludes --
[("foo", "source bar"), ("bar", "baz=3")] -- >>> checkWithIncludes [("lib", "")] "#shellcheck source=lib\n. \"$1\""
"#shellcheck source=foo\n. \"$1\"; echo \"$baz\"" -- []
--
prop_filewideAnnotationBase = [2086] == check "#!/bin/sh\necho $1" -- >>> checkRecursive [("lib", "echo $1")] "source lib"
prop_filewideAnnotation1 = null $ -- [2086]
check "#!/bin/sh\n# shellcheck disable=2086\necho $1" --
prop_filewideAnnotation2 = null $ -- >>> checkRecursive [("lib", "echo \"$10\"")] "source lib"
check "#!/bin/sh\n# shellcheck disable=2086\ntrue\necho $1" -- [1037]
prop_filewideAnnotation3 = null $ --
check "#!/bin/sh\n#unrelated\n# shellcheck disable=2086\ntrue\necho $1" -- >>> checkWithIncludes [("foo", "source bar"), ("bar", "baz=3")] "#shellcheck source=foo\n. \"$1\"; echo \"$baz\""
prop_filewideAnnotation4 = null $ -- []
check "#!/bin/sh\n# shellcheck disable=2086\n#unrelated\ntrue\necho $1" --
prop_filewideAnnotation5 = null $ -- >>> check "#!/bin/sh\necho $1"
check "#!/bin/sh\n\n\n\n#shellcheck disable=2086\ntrue\necho $1" -- [2086]
prop_filewideAnnotation6 = null $ --
check "#shellcheck shell=sh\n#unrelated\n#shellcheck disable=2086\ntrue\necho $1" -- >>> check "#!/bin/sh\n# shellcheck disable=2086\necho $1"
prop_filewideAnnotation7 = null $ -- []
check "#!/bin/sh\n# shellcheck disable=2086\n#unrelated\ntrue\necho $1" --
-- >>> check "#!/bin/sh\n# shellcheck disable=2086\ntrue\necho $1"
prop_filewideAnnotationBase2 = [2086, 2181] == check "true\n[ $? == 0 ] && echo $1" -- []
prop_filewideAnnotation8 = null $ --
check "# Disable $? warning\n#shellcheck disable=SC2181\n# Disable quoting warning\n#shellcheck disable=2086\ntrue\n[ $? == 0 ] && echo $1" -- >>> check "#!/bin/sh\n#unrelated\n# shellcheck disable=2086\ntrue\necho $1"
-- []
prop_sourcePartOfOriginalScript = -- #1181: -x disabled posix warning for 'source' --
2039 `elem` checkWithIncludes [("./saywhat.sh", "echo foo")] "#!/bin/sh\nsource ./saywhat.sh" -- >>> check "#!/bin/sh\n# shellcheck disable=2086\n#unrelated\ntrue\necho $1"
-- []
prop_spinBug1413 = null $ check "fun() {\n# shellcheck disable=SC2188\n> /dev/null\n}\n" --
-- >>> check "#!/bin/sh\n\n\n\n#shellcheck disable=2086\ntrue\necho $1"
return [] -- []
runTests = $quickCheckAll --
-- >>> check "#shellcheck shell=sh\n#unrelated\n#shellcheck disable=2086\ntrue\necho $1"
-- []
--
-- >>> check "#!/bin/sh\n# shellcheck disable=2086\n#unrelated\ntrue\necho $1"
-- []
--
-- check "true\n[ $? == 0 ] && echo $1"
-- [2086, 2181]
--
-- check "# Disable $? warning\n#shellcheck disable=SC2181\n# Disable quoting warning\n#shellcheck disable=2086\ntrue\n[ $? == 0 ] && echo $1"
-- []
--
-- >>> 2039 `elem` checkWithIncludes [("./saywhat.sh", "echo foo")] "#!/bin/sh\nsource ./saywhat.sh"
-- True
--
-- >>> check "fun() {\n# shellcheck disable=SC2188\n> /dev/null\n}\n"
-- []
doctests :: ()
doctests = ()

View file

@ -17,11 +17,9 @@
You should have received a copy of the GNU General Public License You should have received a copy of the GNU General Public License
along with this program. If not, see <https://www.gnu.org/licenses/>. along with this program. If not, see <https://www.gnu.org/licenses/>.
-} -}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleContexts #-}
-- This module contains checks that examine specific commands by name. -- This module contains checks that examine specific commands by name.
module ShellCheck.Checks.Commands (checker , ShellCheck.Checks.Commands.runTests) where module ShellCheck.Checks.Commands (checker) where
import ShellCheck.AST import ShellCheck.AST
import ShellCheck.ASTLib import ShellCheck.ASTLib
@ -37,8 +35,6 @@ import Data.Char
import Data.List import Data.List
import Data.Maybe import Data.Maybe
import qualified Data.Map.Strict as Map import qualified Data.Map.Strict as Map
import Test.QuickCheck.All (forAllProperties)
import Test.QuickCheck.Test (quickCheckWithResult, stdArgs, maxSuccess)
data CommandName = Exactly String | Basename String data CommandName = Exactly String | Basename String
deriving (Eq, Ord) deriving (Eq, Ord)
@ -46,7 +42,6 @@ data CommandName = Exactly String | Basename String
data CommandCheck = data CommandCheck =
CommandCheck CommandName (Token -> Analysis) CommandCheck CommandName (Token -> Analysis)
verify :: CommandCheck -> String -> Bool verify :: CommandCheck -> String -> Bool
verify f s = producesComments (getChecker [f]) s == Just True verify f s = producesComments (getChecker [f]) s == Just True
verifyNot f s = producesComments (getChecker [f]) s == Just False verifyNot f s = producesComments (getChecker [f]) s == Just False
@ -130,20 +125,21 @@ getChecker list = Checker {
checker :: Parameters -> Checker checker :: Parameters -> Checker
checker params = getChecker commandChecks checker params = getChecker commandChecks
prop_checkTr1 = verify checkTr "tr [a-f] [A-F]" -- |
prop_checkTr2 = verify checkTr "tr 'a-z' 'A-Z'" -- >>> prop $ verify checkTr "tr [a-f] [A-F]"
prop_checkTr2a= verify checkTr "tr '[a-z]' '[A-Z]'" -- >>> prop $ verify checkTr "tr 'a-z' 'A-Z'"
prop_checkTr3 = verifyNot checkTr "tr -d '[:lower:]'" -- >>> prop $ verify checkTr "tr '[a-z]' '[A-Z]'"
prop_checkTr3a= verifyNot checkTr "tr -d '[:upper:]'" -- >>> prop $ verifyNot checkTr "tr -d '[:lower:]'"
prop_checkTr3b= verifyNot checkTr "tr -d '|/_[:upper:]'" -- >>> prop $ verifyNot checkTr "tr -d '[:upper:]'"
prop_checkTr4 = verifyNot checkTr "ls [a-z]" -- >>> prop $ verifyNot checkTr "tr -d '|/_[:upper:]'"
prop_checkTr5 = verify checkTr "tr foo bar" -- >>> prop $ verifyNot checkTr "ls [a-z]"
prop_checkTr6 = verify checkTr "tr 'hello' 'world'" -- >>> prop $ verify checkTr "tr foo bar"
prop_checkTr8 = verifyNot checkTr "tr aeiou _____" -- >>> prop $ verify checkTr "tr 'hello' 'world'"
prop_checkTr9 = verifyNot checkTr "a-z n-za-m" -- >>> prop $ verifyNot checkTr "tr aeiou _____"
prop_checkTr10= verifyNot checkTr "tr --squeeze-repeats rl lr" -- >>> prop $ verifyNot checkTr "a-z n-za-m"
prop_checkTr11= verifyNot checkTr "tr abc '[d*]'" -- >>> prop $ verifyNot checkTr "tr --squeeze-repeats rl lr"
prop_checkTr12= verifyNot checkTr "tr '[=e=]' 'e'" -- >>> prop $ verifyNot checkTr "tr abc '[d*]'"
-- >>> prop $ verifyNot checkTr "tr '[=e=]' 'e'"
checkTr = CommandCheck (Basename "tr") (mapM_ f . arguments) checkTr = CommandCheck (Basename "tr") (mapM_ f . arguments)
where where
f w | isGlob w = -- The user will go [ab] -> '[ab]' -> 'ab'. Fixme? f w | isGlob w = -- The user will go [ab] -> '[ab]' -> 'ab'. Fixme?
@ -164,9 +160,10 @@ checkTr = CommandCheck (Basename "tr") (mapM_ f . arguments)
let relevant = filter isAlpha s let relevant = filter isAlpha s
in relevant /= nub relevant in relevant /= nub relevant
prop_checkFindNameGlob1 = verify checkFindNameGlob "find / -name *.php" -- |
prop_checkFindNameGlob2 = verify checkFindNameGlob "find / -type f -ipath *(foo)" -- >>> prop $ verify checkFindNameGlob "find / -name *.php"
prop_checkFindNameGlob3 = verifyNot checkFindNameGlob "find * -name '*.php'" -- >>> prop $ verify checkFindNameGlob "find / -type f -ipath *(foo)"
-- >>> prop $ verifyNot checkFindNameGlob "find * -name '*.php'"
checkFindNameGlob = CommandCheck (Basename "find") (f . arguments) where checkFindNameGlob = CommandCheck (Basename "find") (f . arguments) where
acceptsGlob (Just s) = s `elem` [ "-ilname", "-iname", "-ipath", "-iregex", "-iwholename", "-lname", "-name", "-path", "-regex", "-wholename" ] acceptsGlob (Just s) = s `elem` [ "-ilname", "-iname", "-ipath", "-iregex", "-iwholename", "-lname", "-name", "-path", "-regex", "-wholename" ]
acceptsGlob _ = False acceptsGlob _ = False
@ -179,10 +176,11 @@ checkFindNameGlob = CommandCheck (Basename "find") (f . arguments) where
f (b:r) f (b:r)
prop_checkNeedlessExpr = verify checkNeedlessExpr "foo=$(expr 3 + 2)" -- |
prop_checkNeedlessExpr2 = verify checkNeedlessExpr "foo=`echo \\`expr 3 + 2\\``" -- >>> prop $ verify checkNeedlessExpr "foo=$(expr 3 + 2)"
prop_checkNeedlessExpr3 = verifyNot checkNeedlessExpr "foo=$(expr foo : regex)" -- >>> prop $ verify checkNeedlessExpr "foo=`echo \\`expr 3 + 2\\``"
prop_checkNeedlessExpr4 = verifyNot checkNeedlessExpr "foo=$(expr foo \\< regex)" -- >>> prop $ verifyNot checkNeedlessExpr "foo=$(expr foo : regex)"
-- >>> prop $ verifyNot checkNeedlessExpr "foo=$(expr foo \\< regex)"
checkNeedlessExpr = CommandCheck (Basename "expr") f where checkNeedlessExpr = CommandCheck (Basename "expr") f where
f t = f t =
when (all (`notElem` exceptions) (words $ arguments t)) $ when (all (`notElem` exceptions) (words $ arguments t)) $
@ -193,21 +191,22 @@ checkNeedlessExpr = CommandCheck (Basename "expr") f where
words = mapMaybe getLiteralString words = mapMaybe getLiteralString
prop_checkGrepRe1 = verify checkGrepRe "cat foo | grep *.mp3" -- |
prop_checkGrepRe2 = verify checkGrepRe "grep -Ev cow*test *.mp3" -- >>> prop $ verify checkGrepRe "cat foo | grep *.mp3"
prop_checkGrepRe3 = verify checkGrepRe "grep --regex=*.mp3 file" -- >>> prop $ verify checkGrepRe "grep -Ev cow*test *.mp3"
prop_checkGrepRe4 = verifyNot checkGrepRe "grep foo *.mp3" -- >>> prop $ verify checkGrepRe "grep --regex=*.mp3 file"
prop_checkGrepRe5 = verifyNot checkGrepRe "grep-v --regex=moo *" -- >>> prop $ verifyNot checkGrepRe "grep foo *.mp3"
prop_checkGrepRe6 = verifyNot checkGrepRe "grep foo \\*.mp3" -- >>> prop $ verifyNot checkGrepRe "grep-v --regex=moo *"
prop_checkGrepRe7 = verify checkGrepRe "grep *foo* file" -- >>> prop $ verifyNot checkGrepRe "grep foo \\*.mp3"
prop_checkGrepRe8 = verify checkGrepRe "ls | grep foo*.jpg" -- >>> prop $ verify checkGrepRe "grep *foo* file"
prop_checkGrepRe9 = verifyNot checkGrepRe "grep '[0-9]*' file" -- >>> prop $ verify checkGrepRe "ls | grep foo*.jpg"
prop_checkGrepRe10= verifyNot checkGrepRe "grep '^aa*' file" -- >>> prop $ verifyNot checkGrepRe "grep '[0-9]*' file"
prop_checkGrepRe11= verifyNot checkGrepRe "grep --include=*.png foo" -- >>> prop $ verifyNot checkGrepRe "grep '^aa*' file"
prop_checkGrepRe12= verifyNot checkGrepRe "grep -F 'Foo*' file" -- >>> prop $ verifyNot checkGrepRe "grep --include=*.png foo"
prop_checkGrepRe13= verifyNot checkGrepRe "grep -- -foo bar*" -- >>> prop $ verifyNot checkGrepRe "grep -F 'Foo*' file"
prop_checkGrepRe14= verifyNot checkGrepRe "grep -e -foo bar*" -- >>> prop $ verifyNot checkGrepRe "grep -- -foo bar*"
prop_checkGrepRe15= verifyNot checkGrepRe "grep --regex -foo bar*" -- >>> prop $ verifyNot checkGrepRe "grep -e -foo bar*"
-- >>> prop $ verifyNot checkGrepRe "grep --regex -foo bar*"
checkGrepRe = CommandCheck (Basename "grep") check where checkGrepRe = CommandCheck (Basename "grep") check where
check cmd = f cmd (arguments cmd) check cmd = f cmd (arguments cmd)
@ -258,10 +257,11 @@ checkGrepRe = CommandCheck (Basename "grep") check where
contra = mkRegex "[^a-zA-Z1-9]\\*|[][^$+\\\\]" contra = mkRegex "[^a-zA-Z1-9]\\*|[][^$+\\\\]"
prop_checkTrapQuotes1 = verify checkTrapQuotes "trap \"echo $num\" INT" -- |
prop_checkTrapQuotes1a= verify checkTrapQuotes "trap \"echo `ls`\" INT" -- >>> prop $ verify checkTrapQuotes "trap \"echo $num\" INT"
prop_checkTrapQuotes2 = verifyNot checkTrapQuotes "trap 'echo $num' INT" -- >>> prop $ verify checkTrapQuotes "trap \"echo `ls`\" INT"
prop_checkTrapQuotes3 = verify checkTrapQuotes "trap \"echo $((1+num))\" EXIT DEBUG" -- >>> prop $ verifyNot checkTrapQuotes "trap 'echo $num' INT"
-- >>> prop $ verify checkTrapQuotes "trap \"echo $((1+num))\" EXIT DEBUG"
checkTrapQuotes = CommandCheck (Exactly "trap") (f . arguments) where checkTrapQuotes = CommandCheck (Exactly "trap") (f . arguments) where
f (x:_) = checkTrap x f (x:_) = checkTrap x
f _ = return () f _ = return ()
@ -275,24 +275,26 @@ checkTrapQuotes = CommandCheck (Exactly "trap") (f . arguments) where
checkExpansions _ = return () checkExpansions _ = return ()
prop_checkReturn1 = verifyNot checkReturn "return" -- |
prop_checkReturn2 = verifyNot checkReturn "return 1" -- >>> prop $ verifyNot checkReturn "return"
prop_checkReturn3 = verifyNot checkReturn "return $var" -- >>> prop $ verifyNot checkReturn "return 1"
prop_checkReturn4 = verifyNot checkReturn "return $((a|b))" -- >>> prop $ verifyNot checkReturn "return $var"
prop_checkReturn5 = verify checkReturn "return -1" -- >>> prop $ verifyNot checkReturn "return $((a|b))"
prop_checkReturn6 = verify checkReturn "return 1000" -- >>> prop $ verify checkReturn "return -1"
prop_checkReturn7 = verify checkReturn "return 'hello world'" -- >>> prop $ verify checkReturn "return 1000"
-- >>> prop $ verify checkReturn "return 'hello world'"
checkReturn = CommandCheck (Exactly "return") (returnOrExit checkReturn = CommandCheck (Exactly "return") (returnOrExit
(\c -> err c 2151 "Only one integer 0-255 can be returned. Use stdout for other data.") (\c -> err c 2151 "Only one integer 0-255 can be returned. Use stdout for other data.")
(\c -> err c 2152 "Can only return 0-255. Other data should be written to stdout.")) (\c -> err c 2152 "Can only return 0-255. Other data should be written to stdout."))
prop_checkExit1 = verifyNot checkExit "exit" -- |
prop_checkExit2 = verifyNot checkExit "exit 1" -- >>> prop $ verifyNot checkExit "exit"
prop_checkExit3 = verifyNot checkExit "exit $var" -- >>> prop $ verifyNot checkExit "exit 1"
prop_checkExit4 = verifyNot checkExit "exit $((a|b))" -- >>> prop $ verifyNot checkExit "exit $var"
prop_checkExit5 = verify checkExit "exit -1" -- >>> prop $ verifyNot checkExit "exit $((a|b))"
prop_checkExit6 = verify checkExit "exit 1000" -- >>> prop $ verify checkExit "exit -1"
prop_checkExit7 = verify checkExit "exit 'hello world'" -- >>> prop $ verify checkExit "exit 1000"
-- >>> prop $ verify checkExit "exit 'hello world'"
checkExit = CommandCheck (Exactly "exit") (returnOrExit checkExit = CommandCheck (Exactly "exit") (returnOrExit
(\c -> err c 2241 "The exit status can only be one integer 0-255. Use stdout for other data.") (\c -> err c 2241 "The exit status can only be one integer 0-255. Use stdout for other data.")
(\c -> err c 2242 "Can only exit with status 0-255. Other data should be written to stdout/stderr.")) (\c -> err c 2242 "Can only exit with status 0-255. Other data should be written to stdout/stderr."))
@ -317,9 +319,10 @@ returnOrExit multi invalid = (f . arguments)
lit _ = return "WTF" lit _ = return "WTF"
prop_checkFindExecWithSingleArgument1 = verify checkFindExecWithSingleArgument "find . -exec 'cat {} | wc -l' \\;" -- |
prop_checkFindExecWithSingleArgument2 = verify checkFindExecWithSingleArgument "find . -execdir 'cat {} | wc -l' +" -- >>> prop $ verify checkFindExecWithSingleArgument "find . -exec 'cat {} | wc -l' \\;"
prop_checkFindExecWithSingleArgument3 = verifyNot checkFindExecWithSingleArgument "find . -exec wc -l {} \\;" -- >>> prop $ verify checkFindExecWithSingleArgument "find . -execdir 'cat {} | wc -l' +"
-- >>> prop $ verifyNot checkFindExecWithSingleArgument "find . -exec wc -l {} \\;"
checkFindExecWithSingleArgument = CommandCheck (Basename "find") (f . arguments) checkFindExecWithSingleArgument = CommandCheck (Basename "find") (f . arguments)
where where
f = void . sequence . mapMaybe check . tails f = void . sequence . mapMaybe check . tails
@ -335,11 +338,12 @@ checkFindExecWithSingleArgument = CommandCheck (Basename "find") (f . arguments)
commandRegex = mkRegex "[ |;]" commandRegex = mkRegex "[ |;]"
prop_checkUnusedEchoEscapes1 = verify checkUnusedEchoEscapes "echo 'foo\\nbar\\n'" -- |
prop_checkUnusedEchoEscapes2 = verifyNot checkUnusedEchoEscapes "echo -e 'foi\\nbar'" -- >>> prop $ verify checkUnusedEchoEscapes "echo 'foo\\nbar\\n'"
prop_checkUnusedEchoEscapes3 = verify checkUnusedEchoEscapes "echo \"n:\\t42\"" -- >>> prop $ verifyNot checkUnusedEchoEscapes "echo -e 'foi\\nbar'"
prop_checkUnusedEchoEscapes4 = verifyNot checkUnusedEchoEscapes "echo lol" -- >>> prop $ verify checkUnusedEchoEscapes "echo \"n:\\t42\""
prop_checkUnusedEchoEscapes5 = verifyNot checkUnusedEchoEscapes "echo -n -e '\n'" -- >>> prop $ verifyNot checkUnusedEchoEscapes "echo lol"
-- >>> prop $ verifyNot checkUnusedEchoEscapes "echo -n -e '\n'"
checkUnusedEchoEscapes = CommandCheck (Basename "echo") f checkUnusedEchoEscapes = CommandCheck (Basename "echo") f
where where
hasEscapes = mkRegex "\\\\[rnt]" hasEscapes = mkRegex "\\\\[rnt]"
@ -354,9 +358,10 @@ checkUnusedEchoEscapes = CommandCheck (Basename "echo") f
info (getId token) 2028 "echo may not expand escape sequences. Use printf." info (getId token) 2028 "echo may not expand escape sequences. Use printf."
prop_checkInjectableFindSh1 = verify checkInjectableFindSh "find . -exec sh -c 'echo {}' \\;" -- |
prop_checkInjectableFindSh2 = verify checkInjectableFindSh "find . -execdir bash -c 'rm \"{}\"' ';'" -- >>> prop $ verify checkInjectableFindSh "find . -exec sh -c 'echo {}' \\;"
prop_checkInjectableFindSh3 = verifyNot checkInjectableFindSh "find . -exec sh -c 'rm \"$@\"' _ {} \\;" -- >>> prop $ verify checkInjectableFindSh "find . -execdir bash -c 'rm \"{}\"' ';'"
-- >>> prop $ verifyNot checkInjectableFindSh "find . -exec sh -c 'rm \"$@\"' _ {} \\;"
checkInjectableFindSh = CommandCheck (Basename "find") (check . arguments) checkInjectableFindSh = CommandCheck (Basename "find") (check . arguments)
where where
check args = do check args = do
@ -379,9 +384,10 @@ checkInjectableFindSh = CommandCheck (Basename "find") (check . arguments)
warn id 2156 "Injecting filenames is fragile and insecure. Use parameters." warn id 2156 "Injecting filenames is fragile and insecure. Use parameters."
prop_checkFindActionPrecedence1 = verify checkFindActionPrecedence "find . -name '*.wav' -o -name '*.au' -exec rm {} +" -- |
prop_checkFindActionPrecedence2 = verifyNot checkFindActionPrecedence "find . -name '*.wav' -o \\( -name '*.au' -exec rm {} + \\)" -- >>> prop $ verify checkFindActionPrecedence "find . -name '*.wav' -o -name '*.au' -exec rm {} +"
prop_checkFindActionPrecedence3 = verifyNot checkFindActionPrecedence "find . -name '*.wav' -o -name '*.au'" -- >>> prop $ verifyNot checkFindActionPrecedence "find . -name '*.wav' -o \\( -name '*.au' -exec rm {} + \\)"
-- >>> prop $ verifyNot checkFindActionPrecedence "find . -name '*.wav' -o -name '*.au'"
checkFindActionPrecedence = CommandCheck (Basename "find") (f . arguments) checkFindActionPrecedence = CommandCheck (Basename "find") (f . arguments)
where where
pattern = [isMatch, const True, isParam ["-o", "-or"], isMatch, const True, isAction] pattern = [isMatch, const True, isParam ["-o", "-or"], isMatch, const True, isAction]
@ -398,28 +404,29 @@ checkFindActionPrecedence = CommandCheck (Basename "find") (f . arguments)
warnFor t = warn (getId t) 2146 "This action ignores everything before the -o. Use \\( \\) to group." warnFor t = warn (getId t) 2146 "This action ignores everything before the -o. Use \\( \\) to group."
prop_checkMkdirDashPM0 = verify checkMkdirDashPM "mkdir -p -m 0755 a/b" -- |
prop_checkMkdirDashPM1 = verify checkMkdirDashPM "mkdir -pm 0755 $dir" -- >>> prop $ verify checkMkdirDashPM "mkdir -p -m 0755 a/b"
prop_checkMkdirDashPM2 = verify checkMkdirDashPM "mkdir -vpm 0755 a/b" -- >>> prop $ verify checkMkdirDashPM "mkdir -pm 0755 $dir"
prop_checkMkdirDashPM3 = verify checkMkdirDashPM "mkdir -pm 0755 -v a/b" -- >>> prop $ verify checkMkdirDashPM "mkdir -vpm 0755 a/b"
prop_checkMkdirDashPM4 = verify checkMkdirDashPM "mkdir --parents --mode=0755 a/b" -- >>> prop $ verify checkMkdirDashPM "mkdir -pm 0755 -v a/b"
prop_checkMkdirDashPM5 = verify checkMkdirDashPM "mkdir --parents --mode 0755 a/b" -- >>> prop $ verify checkMkdirDashPM "mkdir --parents --mode=0755 a/b"
prop_checkMkdirDashPM6 = verify checkMkdirDashPM "mkdir -p --mode=0755 a/b" -- >>> prop $ verify checkMkdirDashPM "mkdir --parents --mode 0755 a/b"
prop_checkMkdirDashPM7 = verify checkMkdirDashPM "mkdir --parents -m 0755 a/b" -- >>> prop $ verify checkMkdirDashPM "mkdir -p --mode=0755 a/b"
prop_checkMkdirDashPM8 = verifyNot checkMkdirDashPM "mkdir -p a/b" -- >>> prop $ verify checkMkdirDashPM "mkdir --parents -m 0755 a/b"
prop_checkMkdirDashPM9 = verifyNot checkMkdirDashPM "mkdir -m 0755 a/b" -- >>> prop $ verifyNot checkMkdirDashPM "mkdir -p a/b"
prop_checkMkdirDashPM10 = verifyNot checkMkdirDashPM "mkdir a/b" -- >>> prop $ verifyNot checkMkdirDashPM "mkdir -m 0755 a/b"
prop_checkMkdirDashPM11 = verifyNot checkMkdirDashPM "mkdir --parents a/b" -- >>> prop $ verifyNot checkMkdirDashPM "mkdir a/b"
prop_checkMkdirDashPM12 = verifyNot checkMkdirDashPM "mkdir --mode=0755 a/b" -- >>> prop $ verifyNot checkMkdirDashPM "mkdir --parents a/b"
prop_checkMkdirDashPM13 = verifyNot checkMkdirDashPM "mkdir_func -pm 0755 a/b" -- >>> prop $ verifyNot checkMkdirDashPM "mkdir --mode=0755 a/b"
prop_checkMkdirDashPM14 = verifyNot checkMkdirDashPM "mkdir -p -m 0755 singlelevel" -- >>> prop $ verifyNot checkMkdirDashPM "mkdir_func -pm 0755 a/b"
prop_checkMkdirDashPM15 = verifyNot checkMkdirDashPM "mkdir -p -m 0755 ../bin" -- >>> prop $ verifyNot checkMkdirDashPM "mkdir -p -m 0755 singlelevel"
prop_checkMkdirDashPM16 = verify checkMkdirDashPM "mkdir -p -m 0755 ../bin/laden" -- >>> prop $ verifyNot checkMkdirDashPM "mkdir -p -m 0755 ../bin"
prop_checkMkdirDashPM17 = verifyNot checkMkdirDashPM "mkdir -p -m 0755 ./bin" -- >>> prop $ verify checkMkdirDashPM "mkdir -p -m 0755 ../bin/laden"
prop_checkMkdirDashPM18 = verify checkMkdirDashPM "mkdir -p -m 0755 ./bin/laden" -- >>> prop $ verifyNot checkMkdirDashPM "mkdir -p -m 0755 ./bin"
prop_checkMkdirDashPM19 = verifyNot checkMkdirDashPM "mkdir -p -m 0755 ./../bin" -- >>> prop $ verify checkMkdirDashPM "mkdir -p -m 0755 ./bin/laden"
prop_checkMkdirDashPM20 = verifyNot checkMkdirDashPM "mkdir -p -m 0755 .././bin" -- >>> prop $ verifyNot checkMkdirDashPM "mkdir -p -m 0755 ./../bin"
prop_checkMkdirDashPM21 = verifyNot checkMkdirDashPM "mkdir -p -m 0755 ../../bin" -- >>> prop $ verifyNot checkMkdirDashPM "mkdir -p -m 0755 .././bin"
-- >>> prop $ verifyNot checkMkdirDashPM "mkdir -p -m 0755 ../../bin"
checkMkdirDashPM = CommandCheck (Basename "mkdir") check checkMkdirDashPM = CommandCheck (Basename "mkdir") check
where where
check t = potentially $ do check t = potentially $ do
@ -435,13 +442,14 @@ checkMkdirDashPM = CommandCheck (Basename "mkdir") check
re = mkRegex "^(\\.\\.?\\/)+[^/]+$" re = mkRegex "^(\\.\\.?\\/)+[^/]+$"
prop_checkNonportableSignals1 = verify checkNonportableSignals "trap f 8" -- |
prop_checkNonportableSignals2 = verifyNot checkNonportableSignals "trap f 0" -- >>> prop $ verify checkNonportableSignals "trap f 8"
prop_checkNonportableSignals3 = verifyNot checkNonportableSignals "trap f 14" -- >>> prop $ verifyNot checkNonportableSignals "trap f 0"
prop_checkNonportableSignals4 = verify checkNonportableSignals "trap f SIGKILL" -- >>> prop $ verifyNot checkNonportableSignals "trap f 14"
prop_checkNonportableSignals5 = verify checkNonportableSignals "trap f 9" -- >>> prop $ verify checkNonportableSignals "trap f SIGKILL"
prop_checkNonportableSignals6 = verify checkNonportableSignals "trap f stop" -- >>> prop $ verify checkNonportableSignals "trap f 9"
prop_checkNonportableSignals7 = verifyNot checkNonportableSignals "trap 'stop' int" -- >>> prop $ verify checkNonportableSignals "trap f stop"
-- >>> prop $ verifyNot checkNonportableSignals "trap 'stop' int"
checkNonportableSignals = CommandCheck (Exactly "trap") (f . arguments) checkNonportableSignals = CommandCheck (Exactly "trap") (f . arguments)
where where
f args = case args of f args = case args of
@ -470,10 +478,11 @@ checkNonportableSignals = CommandCheck (Exactly "trap") (f . arguments)
"SIGKILL/SIGSTOP can not be trapped." "SIGKILL/SIGSTOP can not be trapped."
prop_checkInteractiveSu1 = verify checkInteractiveSu "su; rm file; su $USER" -- |
prop_checkInteractiveSu2 = verify checkInteractiveSu "su foo; something; exit" -- >>> prop $ verify checkInteractiveSu "su; rm file; su $USER"
prop_checkInteractiveSu3 = verifyNot checkInteractiveSu "echo rm | su foo" -- >>> prop $ verify checkInteractiveSu "su foo; something; exit"
prop_checkInteractiveSu4 = verifyNot checkInteractiveSu "su root < script" -- >>> prop $ verifyNot checkInteractiveSu "echo rm | su foo"
-- >>> prop $ verifyNot checkInteractiveSu "su root < script"
checkInteractiveSu = CommandCheck (Basename "su") f checkInteractiveSu = CommandCheck (Basename "su") f
where where
f cmd = when (length (arguments cmd) <= 1) $ do f cmd = when (length (arguments cmd) <= 1) $ do
@ -488,11 +497,13 @@ checkInteractiveSu = CommandCheck (Basename "su") f
undirected _ = True undirected _ = True
-- |
-- This is hard to get right without properly parsing ssh args -- This is hard to get right without properly parsing ssh args
prop_checkSshCmdStr1 = verify checkSshCommandString "ssh host \"echo $PS1\"" --
prop_checkSshCmdStr2 = verifyNot checkSshCommandString "ssh host \"ls foo\"" -- >>> prop $ verify checkSshCommandString "ssh host \"echo $PS1\""
prop_checkSshCmdStr3 = verifyNot checkSshCommandString "ssh \"$host\"" -- >>> prop $ verifyNot checkSshCommandString "ssh host \"ls foo\""
prop_checkSshCmdStr4 = verifyNot checkSshCommandString "ssh -i key \"$host\"" -- >>> prop $ verifyNot checkSshCommandString "ssh \"$host\""
-- >>> prop $ verifyNot checkSshCommandString "ssh -i key \"$host\""
checkSshCommandString = CommandCheck (Basename "ssh") (f . arguments) checkSshCommandString = CommandCheck (Basename "ssh") (f . arguments)
where where
isOption x = "-" `isPrefixOf` (concat $ oversimplify x) isOption x = "-" `isPrefixOf` (concat $ oversimplify x)
@ -508,24 +519,25 @@ checkSshCommandString = CommandCheck (Basename "ssh") (f . arguments)
checkArg _ = return () checkArg _ = return ()
prop_checkPrintfVar1 = verify checkPrintfVar "printf \"Lol: $s\"" -- |
prop_checkPrintfVar2 = verifyNot checkPrintfVar "printf 'Lol: $s'" -- >>> prop $ verify checkPrintfVar "printf \"Lol: $s\""
prop_checkPrintfVar3 = verify checkPrintfVar "printf -v cow $(cmd)" -- >>> prop $ verifyNot checkPrintfVar "printf 'Lol: $s'"
prop_checkPrintfVar4 = verifyNot checkPrintfVar "printf \"%${count}s\" var" -- >>> prop $ verify checkPrintfVar "printf -v cow $(cmd)"
prop_checkPrintfVar5 = verify checkPrintfVar "printf '%s %s %s' foo bar" -- >>> prop $ verifyNot checkPrintfVar "printf \"%${count}s\" var"
prop_checkPrintfVar6 = verify checkPrintfVar "printf foo bar baz" -- >>> prop $ verify checkPrintfVar "printf '%s %s %s' foo bar"
prop_checkPrintfVar7 = verify checkPrintfVar "printf -- foo bar baz" -- >>> prop $ verify checkPrintfVar "printf foo bar baz"
prop_checkPrintfVar8 = verifyNot checkPrintfVar "printf '%s %s %s' \"${var[@]}\"" -- >>> prop $ verify checkPrintfVar "printf -- foo bar baz"
prop_checkPrintfVar9 = verifyNot checkPrintfVar "printf '%s %s %s\\n' *.png" -- >>> prop $ verifyNot checkPrintfVar "printf '%s %s %s' \"${var[@]}\""
prop_checkPrintfVar10= verifyNot checkPrintfVar "printf '%s %s %s' foo bar baz" -- >>> prop $ verifyNot checkPrintfVar "printf '%s %s %s\\n' *.png"
prop_checkPrintfVar11= verifyNot checkPrintfVar "printf '%(%s%s)T' -1" -- >>> prop $ verifyNot checkPrintfVar "printf '%s %s %s' foo bar baz"
prop_checkPrintfVar12= verify checkPrintfVar "printf '%s %s\\n' 1 2 3" -- >>> prop $ verifyNot checkPrintfVar "printf '%(%s%s)T' -1"
prop_checkPrintfVar13= verifyNot checkPrintfVar "printf '%s %s\\n' 1 2 3 4" -- >>> prop $ verify checkPrintfVar "printf '%s %s\\n' 1 2 3"
prop_checkPrintfVar14= verify checkPrintfVar "printf '%*s\\n' 1" -- >>> prop $ verifyNot checkPrintfVar "printf '%s %s\\n' 1 2 3 4"
prop_checkPrintfVar15= verifyNot checkPrintfVar "printf '%*s\\n' 1 2" -- >>> prop $ verify checkPrintfVar "printf '%*s\\n' 1"
prop_checkPrintfVar16= verifyNot checkPrintfVar "printf $'string'" -- >>> prop $ verifyNot checkPrintfVar "printf '%*s\\n' 1 2"
prop_checkPrintfVar17= verify checkPrintfVar "printf '%-*s\\n' 1" -- >>> prop $ verifyNot checkPrintfVar "printf $'string'"
prop_checkPrintfVar18= verifyNot checkPrintfVar "printf '%-*s\\n' 1 2" -- >>> prop $ verify checkPrintfVar "printf '%-*s\\n' 1"
-- >>> prop $ verifyNot checkPrintfVar "printf '%-*s\\n' 1 2"
checkPrintfVar = CommandCheck (Exactly "printf") (f . arguments) where checkPrintfVar = CommandCheck (Exactly "printf") (f . arguments) where
f (doubledash:rest) | getLiteralString doubledash == Just "--" = f rest f (doubledash:rest) | getLiteralString doubledash == Just "--" = f rest
f (dashv:var:rest) | getLiteralString dashv == Just "-v" = f rest f (dashv:var:rest) | getLiteralString dashv == Just "-v" = f rest
@ -574,24 +586,26 @@ checkPrintfVar = CommandCheck (Exactly "printf") (f . arguments) where
prop_checkUuoeCmd1 = verify checkUuoeCmd "echo $(date)" -- |
prop_checkUuoeCmd2 = verify checkUuoeCmd "echo `date`" -- >>> prop $ verify checkUuoeCmd "echo $(date)"
prop_checkUuoeCmd3 = verify checkUuoeCmd "echo \"$(date)\"" -- >>> prop $ verify checkUuoeCmd "echo `date`"
prop_checkUuoeCmd4 = verify checkUuoeCmd "echo \"`date`\"" -- >>> prop $ verify checkUuoeCmd "echo \"$(date)\""
prop_checkUuoeCmd5 = verifyNot checkUuoeCmd "echo \"The time is $(date)\"" -- >>> prop $ verify checkUuoeCmd "echo \"`date`\""
prop_checkUuoeCmd6 = verifyNot checkUuoeCmd "echo \"$(<file)\"" -- >>> prop $ verifyNot checkUuoeCmd "echo \"The time is $(date)\""
-- >>> prop $ verifyNot checkUuoeCmd "echo \"$(<file)\""
checkUuoeCmd = CommandCheck (Exactly "echo") (f . arguments) where checkUuoeCmd = CommandCheck (Exactly "echo") (f . arguments) where
msg id = style id 2005 "Useless echo? Instead of 'echo $(cmd)', just use 'cmd'." msg id = style id 2005 "Useless echo? Instead of 'echo $(cmd)', just use 'cmd'."
f [token] = when (tokenIsJustCommandOutput token) $ msg (getId token) f [token] = when (tokenIsJustCommandOutput token) $ msg (getId token)
f _ = return () f _ = return ()
prop_checkSetAssignment1 = verify checkSetAssignment "set foo 42" -- |
prop_checkSetAssignment2 = verify checkSetAssignment "set foo = 42" -- >>> prop $ verify checkSetAssignment "set foo 42"
prop_checkSetAssignment3 = verify checkSetAssignment "set foo=42" -- >>> prop $ verify checkSetAssignment "set foo = 42"
prop_checkSetAssignment4 = verifyNot checkSetAssignment "set -- if=/dev/null" -- >>> prop $ verify checkSetAssignment "set foo=42"
prop_checkSetAssignment5 = verifyNot checkSetAssignment "set 'a=5'" -- >>> prop $ verifyNot checkSetAssignment "set -- if=/dev/null"
prop_checkSetAssignment6 = verifyNot checkSetAssignment "set" -- >>> prop $ verifyNot checkSetAssignment "set 'a=5'"
-- >>> prop $ verifyNot checkSetAssignment "set"
checkSetAssignment = CommandCheck (Exactly "set") (f . arguments) checkSetAssignment = CommandCheck (Exactly "set") (f . arguments)
where where
f (var:value:rest) = f (var:value:rest) =
@ -611,10 +625,11 @@ checkSetAssignment = CommandCheck (Exactly "set") (f . arguments)
literal _ = "*" literal _ = "*"
prop_checkExportedExpansions1 = verify checkExportedExpansions "export $foo" -- |
prop_checkExportedExpansions2 = verify checkExportedExpansions "export \"$foo\"" -- >>> prop $ verify checkExportedExpansions "export $foo"
prop_checkExportedExpansions3 = verifyNot checkExportedExpansions "export foo" -- >>> prop $ verify checkExportedExpansions "export \"$foo\""
prop_checkExportedExpansions4 = verifyNot checkExportedExpansions "export ${foo?}" -- >>> prop $ verifyNot checkExportedExpansions "export foo"
-- >>> prop $ verifyNot checkExportedExpansions "export ${foo?}"
checkExportedExpansions = CommandCheck (Exactly "export") (mapM_ check . arguments) checkExportedExpansions = CommandCheck (Exactly "export") (mapM_ check . arguments)
where where
check t = potentially $ do check t = potentially $ do
@ -623,14 +638,15 @@ checkExportedExpansions = CommandCheck (Exactly "export") (mapM_ check . argumen
return . warn (getId t) 2163 $ return . warn (getId t) 2163 $
"This does not export '" ++ name ++ "'. Remove $/${} for that, or use ${var?} to quiet." "This does not export '" ++ name ++ "'. Remove $/${} for that, or use ${var?} to quiet."
prop_checkReadExpansions1 = verify checkReadExpansions "read $var" -- |
prop_checkReadExpansions2 = verify checkReadExpansions "read -r $var" -- >>> prop $ verify checkReadExpansions "read $var"
prop_checkReadExpansions3 = verifyNot checkReadExpansions "read -p $var" -- >>> prop $ verify checkReadExpansions "read -r $var"
prop_checkReadExpansions4 = verifyNot checkReadExpansions "read -rd $delim name" -- >>> prop $ verifyNot checkReadExpansions "read -p $var"
prop_checkReadExpansions5 = verify checkReadExpansions "read \"$var\"" -- >>> prop $ verifyNot checkReadExpansions "read -rd $delim name"
prop_checkReadExpansions6 = verify checkReadExpansions "read -a $var" -- >>> prop $ verify checkReadExpansions "read \"$var\""
prop_checkReadExpansions7 = verifyNot checkReadExpansions "read $1" -- >>> prop $ verify checkReadExpansions "read -a $var"
prop_checkReadExpansions8 = verifyNot checkReadExpansions "read ${var?}" -- >>> prop $ verifyNot checkReadExpansions "read $1"
-- >>> prop $ verifyNot checkReadExpansions "read ${var?}"
checkReadExpansions = CommandCheck (Exactly "read") check checkReadExpansions = CommandCheck (Exactly "read") check
where where
options = getGnuOpts "sreu:n:N:i:p:a:" options = getGnuOpts "sreu:n:N:i:p:a:"
@ -657,9 +673,10 @@ getSingleUnmodifiedVariable word =
in guard (contents == name) >> return t in guard (contents == name) >> return t
_ -> Nothing _ -> Nothing
prop_checkAliasesUsesArgs1 = verify checkAliasesUsesArgs "alias a='cp $1 /a'" -- |
prop_checkAliasesUsesArgs2 = verifyNot checkAliasesUsesArgs "alias $1='foo'" -- >>> prop $ verify checkAliasesUsesArgs "alias a='cp $1 /a'"
prop_checkAliasesUsesArgs3 = verify checkAliasesUsesArgs "alias a=\"echo \\${@}\"" -- >>> prop $ verifyNot checkAliasesUsesArgs "alias $1='foo'"
-- >>> prop $ verify checkAliasesUsesArgs "alias a=\"echo \\${@}\""
checkAliasesUsesArgs = CommandCheck (Exactly "alias") (f . arguments) checkAliasesUsesArgs = CommandCheck (Exactly "alias") (f . arguments)
where where
re = mkRegex "\\$\\{?[0-9*@]" re = mkRegex "\\$\\{?[0-9*@]"
@ -671,9 +688,10 @@ checkAliasesUsesArgs = CommandCheck (Exactly "alias") (f . arguments)
"Aliases can't use positional parameters. Use a function." "Aliases can't use positional parameters. Use a function."
prop_checkAliasesExpandEarly1 = verify checkAliasesExpandEarly "alias foo=\"echo $PWD\"" -- |
prop_checkAliasesExpandEarly2 = verifyNot checkAliasesExpandEarly "alias -p" -- >>> prop $ verify checkAliasesExpandEarly "alias foo=\"echo $PWD\""
prop_checkAliasesExpandEarly3 = verifyNot checkAliasesExpandEarly "alias foo='echo {1..10}'" -- >>> prop $ verifyNot checkAliasesExpandEarly "alias -p"
-- >>> prop $ verifyNot checkAliasesExpandEarly "alias foo='echo {1..10}'"
checkAliasesExpandEarly = CommandCheck (Exactly "alias") (f . arguments) checkAliasesExpandEarly = CommandCheck (Exactly "alias") (f . arguments)
where where
f = mapM_ checkArg f = mapM_ checkArg
@ -683,8 +701,8 @@ checkAliasesExpandEarly = CommandCheck (Exactly "alias") (f . arguments)
checkArg _ = return () checkArg _ = return ()
prop_checkUnsetGlobs1 = verify checkUnsetGlobs "unset foo[1]" -- >>> prop $ verify checkUnsetGlobs "unset foo[1]"
prop_checkUnsetGlobs2 = verifyNot checkUnsetGlobs "unset foo" -- >>> prop $ verifyNot checkUnsetGlobs "unset foo"
checkUnsetGlobs = CommandCheck (Exactly "unset") (mapM_ check . arguments) checkUnsetGlobs = CommandCheck (Exactly "unset") (mapM_ check . arguments)
where where
check arg = check arg =
@ -692,14 +710,15 @@ checkUnsetGlobs = CommandCheck (Exactly "unset") (mapM_ check . arguments)
warn (getId arg) 2184 "Quote arguments to unset so they're not glob expanded." warn (getId arg) 2184 "Quote arguments to unset so they're not glob expanded."
prop_checkFindWithoutPath1 = verify checkFindWithoutPath "find -type f" -- |
prop_checkFindWithoutPath2 = verify checkFindWithoutPath "find" -- >>> prop $ verify checkFindWithoutPath "find -type f"
prop_checkFindWithoutPath3 = verifyNot checkFindWithoutPath "find . -type f" -- >>> prop $ verify checkFindWithoutPath "find"
prop_checkFindWithoutPath4 = verifyNot checkFindWithoutPath "find -H -L \"$path\" -print" -- >>> prop $ verifyNot checkFindWithoutPath "find . -type f"
prop_checkFindWithoutPath5 = verifyNot checkFindWithoutPath "find -O3 ." -- >>> prop $ verifyNot checkFindWithoutPath "find -H -L \"$path\" -print"
prop_checkFindWithoutPath6 = verifyNot checkFindWithoutPath "find -D exec ." -- >>> prop $ verifyNot checkFindWithoutPath "find -O3 ."
prop_checkFindWithoutPath7 = verifyNot checkFindWithoutPath "find --help" -- >>> prop $ verifyNot checkFindWithoutPath "find -D exec ."
prop_checkFindWithoutPath8 = verifyNot checkFindWithoutPath "find -Hx . -print" -- >>> prop $ verifyNot checkFindWithoutPath "find --help"
-- >>> prop $ verifyNot checkFindWithoutPath "find -Hx . -print"
checkFindWithoutPath = CommandCheck (Basename "find") f checkFindWithoutPath = CommandCheck (Basename "find") f
where where
f t@(T_SimpleCommand _ _ (cmd:args)) = f t@(T_SimpleCommand _ _ (cmd:args)) =
@ -718,10 +737,11 @@ checkFindWithoutPath = CommandCheck (Basename "find") f
leadingFlagChars="-EHLPXdfsxO0123456789" leadingFlagChars="-EHLPXdfsxO0123456789"
prop_checkTimeParameters1 = verify checkTimeParameters "time -f lol sleep 10" -- |
prop_checkTimeParameters2 = verifyNot checkTimeParameters "time sleep 10" -- >>> prop $ verify checkTimeParameters "time -f lol sleep 10"
prop_checkTimeParameters3 = verifyNot checkTimeParameters "time -p foo" -- >>> prop $ verifyNot checkTimeParameters "time sleep 10"
prop_checkTimeParameters4 = verifyNot checkTimeParameters "command time -f lol sleep 10" -- >>> prop $ verifyNot checkTimeParameters "time -p foo"
-- >>> prop $ verifyNot checkTimeParameters "command time -f lol sleep 10"
checkTimeParameters = CommandCheck (Exactly "time") f checkTimeParameters = CommandCheck (Exactly "time") f
where where
f (T_SimpleCommand _ _ (cmd:args:_)) = f (T_SimpleCommand _ _ (cmd:args:_)) =
@ -732,9 +752,10 @@ checkTimeParameters = CommandCheck (Exactly "time") f
f _ = return () f _ = return ()
prop_checkTimedCommand1 = verify checkTimedCommand "#!/bin/sh\ntime -p foo | bar" -- |
prop_checkTimedCommand2 = verify checkTimedCommand "#!/bin/dash\ntime ( foo; bar; )" -- >>> prop $ verify checkTimedCommand "#!/bin/sh\ntime -p foo | bar"
prop_checkTimedCommand3 = verifyNot checkTimedCommand "#!/bin/sh\ntime sleep 1" -- >>> prop $ verify checkTimedCommand "#!/bin/dash\ntime ( foo; bar; )"
-- >>> prop $ verifyNot checkTimedCommand "#!/bin/sh\ntime sleep 1"
checkTimedCommand = CommandCheck (Exactly "time") f where checkTimedCommand = CommandCheck (Exactly "time") f where
f (T_SimpleCommand _ _ (c:args@(_:_))) = f (T_SimpleCommand _ _ (c:args@(_:_))) =
whenShell [Sh, Dash] $ do whenShell [Sh, Dash] $ do
@ -758,32 +779,37 @@ checkTimedCommand = CommandCheck (Exactly "time") f where
T_SimpleCommand {} -> return True T_SimpleCommand {} -> return True
_ -> return False _ -> return False
prop_checkLocalScope1 = verify checkLocalScope "local foo=3" -- |
prop_checkLocalScope2 = verifyNot checkLocalScope "f() { local foo=3; }" -- >>> prop $ verify checkLocalScope "local foo=3"
-- >>> prop $ verifyNot checkLocalScope "f() { local foo=3; }"
checkLocalScope = CommandCheck (Exactly "local") $ \t -> checkLocalScope = CommandCheck (Exactly "local") $ \t ->
whenShell [Bash, Dash] $ do -- Ksh allows it, Sh doesn't support local whenShell [Bash, Dash] $ do -- Ksh allows it, Sh doesn't support local
path <- getPathM t path <- getPathM t
unless (any isFunction path) $ unless (any isFunction path) $
err (getId $ getCommandTokenOrThis t) 2168 "'local' is only valid in functions." err (getId $ getCommandTokenOrThis t) 2168 "'local' is only valid in functions."
prop_checkDeprecatedTempfile1 = verify checkDeprecatedTempfile "var=$(tempfile)" -- |
prop_checkDeprecatedTempfile2 = verifyNot checkDeprecatedTempfile "tempfile=$(mktemp)" -- >>> prop $ verify checkDeprecatedTempfile "var=$(tempfile)"
-- >>> prop $ verifyNot checkDeprecatedTempfile "tempfile=$(mktemp)"
checkDeprecatedTempfile = CommandCheck (Basename "tempfile") $ checkDeprecatedTempfile = CommandCheck (Basename "tempfile") $
\t -> warn (getId $ getCommandTokenOrThis t) 2186 "tempfile is deprecated. Use mktemp instead." \t -> warn (getId $ getCommandTokenOrThis t) 2186 "tempfile is deprecated. Use mktemp instead."
prop_checkDeprecatedEgrep = verify checkDeprecatedEgrep "egrep '.+'" -- |
-- >>> prop $ verify checkDeprecatedEgrep "egrep '.+'"
checkDeprecatedEgrep = CommandCheck (Basename "egrep") $ checkDeprecatedEgrep = CommandCheck (Basename "egrep") $
\t -> info (getId $ getCommandTokenOrThis t) 2196 "egrep is non-standard and deprecated. Use grep -E instead." \t -> info (getId $ getCommandTokenOrThis t) 2196 "egrep is non-standard and deprecated. Use grep -E instead."
prop_checkDeprecatedFgrep = verify checkDeprecatedFgrep "fgrep '*' files" -- |
-- >>> prop $ verify checkDeprecatedFgrep "fgrep '*' files"
checkDeprecatedFgrep = CommandCheck (Basename "fgrep") $ checkDeprecatedFgrep = CommandCheck (Basename "fgrep") $
\t -> info (getId $ getCommandTokenOrThis t) 2197 "fgrep is non-standard and deprecated. Use grep -F instead." \t -> info (getId $ getCommandTokenOrThis t) 2197 "fgrep is non-standard and deprecated. Use grep -F instead."
prop_checkWhileGetoptsCase1 = verify checkWhileGetoptsCase "while getopts 'a:b' x; do case $x in a) foo;; esac; done" -- |
prop_checkWhileGetoptsCase2 = verify checkWhileGetoptsCase "while getopts 'a:' x; do case $x in a) foo;; b) bar;; esac; done" -- >>> prop $ verify checkWhileGetoptsCase "while getopts 'a:b' x; do case $x in a) foo;; esac; done"
prop_checkWhileGetoptsCase3 = verifyNot checkWhileGetoptsCase "while getopts 'a:b' x; do case $x in a) foo;; b) bar;; *) :;esac; done" -- >>> prop $ verify checkWhileGetoptsCase "while getopts 'a:' x; do case $x in a) foo;; b) bar;; esac; done"
prop_checkWhileGetoptsCase4 = verifyNot checkWhileGetoptsCase "while getopts 'a:123' x; do case $x in a) foo;; [0-9]) bar;; esac; done" -- >>> prop $ verifyNot checkWhileGetoptsCase "while getopts 'a:b' x; do case $x in a) foo;; b) bar;; *) :;esac; done"
prop_checkWhileGetoptsCase5 = verifyNot checkWhileGetoptsCase "while getopts 'a:' x; do case $x in a) foo;; \\?) bar;; *) baz;; esac; done" -- >>> prop $ verifyNot checkWhileGetoptsCase "while getopts 'a:123' x; do case $x in a) foo;; [0-9]) bar;; esac; done"
-- >>> prop $ verifyNot checkWhileGetoptsCase "while getopts 'a:' x; do case $x in a) foo;; \\?) bar;; *) baz;; esac; done"
checkWhileGetoptsCase = CommandCheck (Exactly "getopts") f checkWhileGetoptsCase = CommandCheck (Exactly "getopts") f
where where
f :: Token -> Analysis f :: Token -> Analysis
@ -848,19 +874,20 @@ checkWhileGetoptsCase = CommandCheck (Exactly "getopts") f
T_Redirecting _ _ x@(T_CaseExpression {}) -> return x T_Redirecting _ _ x@(T_CaseExpression {}) -> return x
_ -> Nothing _ -> Nothing
prop_checkCatastrophicRm1 = verify checkCatastrophicRm "rm -r $1/$2" -- |
prop_checkCatastrophicRm2 = verify checkCatastrophicRm "rm -r /home/$foo" -- >>> prop $ verify checkCatastrophicRm "rm -r $1/$2"
prop_checkCatastrophicRm3 = verifyNot checkCatastrophicRm "rm -r /home/${USER:?}/*" -- >>> prop $ verify checkCatastrophicRm "rm -r /home/$foo"
prop_checkCatastrophicRm4 = verify checkCatastrophicRm "rm -fr /home/$(whoami)/*" -- >>> prop $ verifyNot checkCatastrophicRm "rm -r /home/${USER:?}/*"
prop_checkCatastrophicRm5 = verifyNot checkCatastrophicRm "rm -r /home/${USER:-thing}/*" -- >>> prop $ verify checkCatastrophicRm "rm -fr /home/$(whoami)/*"
prop_checkCatastrophicRm6 = verify checkCatastrophicRm "rm --recursive /etc/*$config*" -- >>> prop $ verifyNot checkCatastrophicRm "rm -r /home/${USER:-thing}/*"
prop_checkCatastrophicRm8 = verify checkCatastrophicRm "rm -rf /home" -- >>> prop $ verify checkCatastrophicRm "rm --recursive /etc/*$config*"
prop_checkCatastrophicRm10= verifyNot checkCatastrophicRm "rm -r \"${DIR}\"/{.gitignore,.gitattributes,ci}" -- >>> prop $ verify checkCatastrophicRm "rm -rf /home"
prop_checkCatastrophicRm11= verify checkCatastrophicRm "rm -r /{bin,sbin}/$exec" -- >>> prop $ verifyNot checkCatastrophicRm "rm -r \"${DIR}\"/{.gitignore,.gitattributes,ci}"
prop_checkCatastrophicRm12= verify checkCatastrophicRm "rm -r /{{usr,},{bin,sbin}}/$exec" -- >>> prop $ verify checkCatastrophicRm "rm -r /{bin,sbin}/$exec"
prop_checkCatastrophicRm13= verifyNot checkCatastrophicRm "rm -r /{{a,b},{c,d}}/$exec" -- >>> prop $ verify checkCatastrophicRm "rm -r /{{usr,},{bin,sbin}}/$exec"
prop_checkCatastrophicRmA = verify checkCatastrophicRm "rm -rf /usr /lib/nvidia-current/xorg/xorg" -- >>> prop $ verifyNot checkCatastrophicRm "rm -r /{{a,b},{c,d}}/$exec"
prop_checkCatastrophicRmB = verify checkCatastrophicRm "rm -rf \"$STEAMROOT/\"*" -- >>> prop $ verify checkCatastrophicRm "rm -rf /usr /lib/nvidia-current/xorg/xorg"
-- >>> prop $ verify checkCatastrophicRm "rm -rf \"$STEAMROOT/\"*"
checkCatastrophicRm = CommandCheck (Basename "rm") $ \t -> checkCatastrophicRm = CommandCheck (Basename "rm") $ \t ->
when (isRecursive t) $ when (isRecursive t) $
mapM_ (mapM_ checkWord . braceExpand) $ arguments t mapM_ (mapM_ checkWord . braceExpand) $ arguments t
@ -909,8 +936,9 @@ checkCatastrophicRm = CommandCheck (Basename "rm") $ \t ->
["", "/", "/*", "/*/*"] >>= (\x -> map (++x) paths) ["", "/", "/*", "/*/*"] >>= (\x -> map (++x) paths)
prop_checkLetUsage1 = verify checkLetUsage "let a=1" -- |
prop_checkLetUsage2 = verifyNot checkLetUsage "(( a=1 ))" -- >>> prop $ verify checkLetUsage "let a=1"
-- >>> prop $ verifyNot checkLetUsage "(( a=1 ))"
checkLetUsage = CommandCheck (Exactly "let") f checkLetUsage = CommandCheck (Exactly "let") f
where where
f t = whenShell [Bash,Ksh] $ do f t = whenShell [Bash,Ksh] $ do
@ -930,15 +958,16 @@ missingDestination handler token = do
any (\x -> x /= "" && x `isPrefixOf` "target-directory") $ any (\x -> x /= "" && x `isPrefixOf` "target-directory") $
map snd args map snd args
prop_checkMvArguments1 = verify checkMvArguments "mv 'foo bar'" -- |
prop_checkMvArguments2 = verifyNot checkMvArguments "mv foo bar" -- >>> prop $ verify checkMvArguments "mv 'foo bar'"
prop_checkMvArguments3 = verifyNot checkMvArguments "mv 'foo bar'{,bak}" -- >>> prop $ verifyNot checkMvArguments "mv foo bar"
prop_checkMvArguments4 = verifyNot checkMvArguments "mv \"$@\"" -- >>> prop $ verifyNot checkMvArguments "mv 'foo bar'{,bak}"
prop_checkMvArguments5 = verifyNot checkMvArguments "mv -t foo bar" -- >>> prop $ verifyNot checkMvArguments "mv \"$@\""
prop_checkMvArguments6 = verifyNot checkMvArguments "mv --target-directory=foo bar" -- >>> prop $ verifyNot checkMvArguments "mv -t foo bar"
prop_checkMvArguments7 = verifyNot checkMvArguments "mv --target-direc=foo bar" -- >>> prop $ verifyNot checkMvArguments "mv --target-directory=foo bar"
prop_checkMvArguments8 = verifyNot checkMvArguments "mv --version" -- >>> prop $ verifyNot checkMvArguments "mv --target-direc=foo bar"
prop_checkMvArguments9 = verifyNot checkMvArguments "mv \"${!var}\"" -- >>> prop $ verifyNot checkMvArguments "mv --version"
-- >>> prop $ verifyNot checkMvArguments "mv \"${!var}\""
checkMvArguments = CommandCheck (Basename "mv") $ missingDestination f checkMvArguments = CommandCheck (Basename "mv") $ missingDestination f
where where
f t = err (getId t) 2224 "This mv has no destination. Check the arguments." f t = err (getId t) 2224 "This mv has no destination. Check the arguments."
@ -952,9 +981,10 @@ checkLnArguments = CommandCheck (Basename "ln") $ missingDestination f
f t = warn (getId t) 2226 "This ln has no destination. Check the arguments, or specify '.' explicitly." f t = warn (getId t) 2226 "This ln has no destination. Check the arguments, or specify '.' explicitly."
prop_checkFindRedirections1 = verify checkFindRedirections "find . -exec echo {} > file \\;" -- |
prop_checkFindRedirections2 = verifyNot checkFindRedirections "find . -exec echo {} \\; > file" -- >>> prop $ verify checkFindRedirections "find . -exec echo {} > file \\;"
prop_checkFindRedirections3 = verifyNot checkFindRedirections "find . -execdir sh -c 'foo > file' \\;" -- >>> prop $ verifyNot checkFindRedirections "find . -exec echo {} \\; > file"
-- >>> prop $ verifyNot checkFindRedirections "find . -execdir sh -c 'foo > file' \\;"
checkFindRedirections = CommandCheck (Basename "find") f checkFindRedirections = CommandCheck (Basename "find") f
where where
f t = do f t = do
@ -969,17 +999,18 @@ checkFindRedirections = CommandCheck (Basename "find") f
"Redirection applies to the find command itself. Rewrite to work per action (or move to end)." "Redirection applies to the find command itself. Rewrite to work per action (or move to end)."
_ -> return () _ -> return ()
prop_checkWhich = verify checkWhich "which '.+'" -- >>> prop $ verify checkWhich "which '.+'"
checkWhich = CommandCheck (Basename "which") $ checkWhich = CommandCheck (Basename "which") $
\t -> info (getId $ getCommandTokenOrThis t) 2230 "which is non-standard. Use builtin 'command -v' instead." \t -> info (getId $ getCommandTokenOrThis t) 2230 "which is non-standard. Use builtin 'command -v' instead."
prop_checkSudoRedirect1 = verify checkSudoRedirect "sudo echo 3 > /proc/file" -- |
prop_checkSudoRedirect2 = verify checkSudoRedirect "sudo cmd < input" -- >>> prop $ verify checkSudoRedirect "sudo echo 3 > /proc/file"
prop_checkSudoRedirect3 = verify checkSudoRedirect "sudo cmd >> file" -- >>> prop $ verify checkSudoRedirect "sudo cmd < input"
prop_checkSudoRedirect4 = verify checkSudoRedirect "sudo cmd &> file" -- >>> prop $ verify checkSudoRedirect "sudo cmd >> file"
prop_checkSudoRedirect5 = verifyNot checkSudoRedirect "sudo cmd 2>&1" -- >>> prop $ verify checkSudoRedirect "sudo cmd &> file"
prop_checkSudoRedirect6 = verifyNot checkSudoRedirect "sudo cmd 2> log" -- >>> prop $ verifyNot checkSudoRedirect "sudo cmd 2>&1"
prop_checkSudoRedirect7 = verifyNot checkSudoRedirect "sudo cmd > /dev/null 2>&1" -- >>> prop $ verifyNot checkSudoRedirect "sudo cmd 2> log"
-- >>> prop $ verifyNot checkSudoRedirect "sudo cmd > /dev/null 2>&1"
checkSudoRedirect = CommandCheck (Basename "sudo") f checkSudoRedirect = CommandCheck (Basename "sudo") f
where where
f t = do f t = do
@ -1003,13 +1034,14 @@ checkSudoRedirect = CommandCheck (Basename "sudo") f
warnAbout _ = return () warnAbout _ = return ()
special file = concat (oversimplify file) == "/dev/null" special file = concat (oversimplify file) == "/dev/null"
prop_checkSudoArgs1 = verify checkSudoArgs "sudo cd /root" -- |
prop_checkSudoArgs2 = verify checkSudoArgs "sudo export x=3" -- >>> prop $ verify checkSudoArgs "sudo cd /root"
prop_checkSudoArgs3 = verifyNot checkSudoArgs "sudo ls /usr/local/protected" -- >>> prop $ verify checkSudoArgs "sudo export x=3"
prop_checkSudoArgs4 = verifyNot checkSudoArgs "sudo ls && export x=3" -- >>> prop $ verifyNot checkSudoArgs "sudo ls /usr/local/protected"
prop_checkSudoArgs5 = verifyNot checkSudoArgs "sudo echo ls" -- >>> prop $ verifyNot checkSudoArgs "sudo ls && export x=3"
prop_checkSudoArgs6 = verifyNot checkSudoArgs "sudo -n -u export ls" -- >>> prop $ verifyNot checkSudoArgs "sudo echo ls"
prop_checkSudoArgs7 = verifyNot checkSudoArgs "sudo docker export foo" -- >>> prop $ verifyNot checkSudoArgs "sudo -n -u export ls"
-- >>> prop $ verifyNot checkSudoArgs "sudo docker export foo"
checkSudoArgs = CommandCheck (Basename "sudo") f checkSudoArgs = CommandCheck (Basename "sudo") f
where where
f t = potentially $ do f t = potentially $ do
@ -1023,9 +1055,10 @@ checkSudoArgs = CommandCheck (Basename "sudo") f
-- This mess is why ShellCheck prefers not to know. -- This mess is why ShellCheck prefers not to know.
parseOpts = getBsdOpts "vAknSbEHPa:g:h:p:u:c:T:r:" parseOpts = getBsdOpts "vAknSbEHPa:g:h:p:u:c:T:r:"
prop_checkSourceArgs1 = verify checkSourceArgs "#!/bin/sh\n. script arg" -- |
prop_checkSourceArgs2 = verifyNot checkSourceArgs "#!/bin/sh\n. script" -- >>> prop $ verify checkSourceArgs "#!/bin/sh\n. script arg"
prop_checkSourceArgs3 = verifyNot checkSourceArgs "#!/bin/bash\n. script arg" -- >>> prop $ verifyNot checkSourceArgs "#!/bin/sh\n. script"
-- >>> prop $ verifyNot checkSourceArgs "#!/bin/bash\n. script arg"
checkSourceArgs = CommandCheck (Exactly ".") f checkSourceArgs = CommandCheck (Exactly ".") f
where where
f t = whenShell [Sh, Dash] $ f t = whenShell [Sh, Dash] $
@ -1033,6 +1066,3 @@ checkSourceArgs = CommandCheck (Exactly ".") f
(file:arg1:_) -> warn (getId arg1) 2240 $ (file:arg1:_) -> warn (getId arg1) 2240 $
"The dot command does not support arguments in sh/dash. Set them as variables." "The dot command does not support arguments in sh/dash. Set them as variables."
_ -> return () _ -> return ()
return []
runTests = $( [| $(forAllProperties) (quickCheckWithResult (stdArgs { maxSuccess = 1 }) ) |])

View file

@ -17,9 +17,8 @@
You should have received a copy of the GNU General Public License You should have received a copy of the GNU General Public License
along with this program. If not, see <https://www.gnu.org/licenses/>. along with this program. If not, see <https://www.gnu.org/licenses/>.
-} -}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleContexts #-}
module ShellCheck.Checks.ShellSupport (checker , ShellCheck.Checks.ShellSupport.runTests) where module ShellCheck.Checks.ShellSupport (checker) where
import ShellCheck.AST import ShellCheck.AST
import ShellCheck.ASTLib import ShellCheck.ASTLib
@ -33,8 +32,6 @@ import Data.Char
import Data.List import Data.List
import Data.Maybe import Data.Maybe
import qualified Data.Map as Map import qualified Data.Map as Map
import Test.QuickCheck.All (forAllProperties)
import Test.QuickCheck.Test (quickCheckWithResult, stdArgs, maxSuccess)
data ForShell = ForShell [Shell] (Token -> Analysis) data ForShell = ForShell [Shell] (Token -> Analysis)
@ -67,9 +64,10 @@ testChecker (ForShell _ t) =
verify c s = producesComments (testChecker c) s == Just True verify c s = producesComments (testChecker c) s == Just True
verifyNot c s = producesComments (testChecker c) s == Just False verifyNot c s = producesComments (testChecker c) s == Just False
prop_checkForDecimals1 = verify checkForDecimals "((3.14*c))" -- |
prop_checkForDecimals2 = verify checkForDecimals "foo[1.2]=bar" -- >>> prop $ verify checkForDecimals "((3.14*c))"
prop_checkForDecimals3 = verifyNot checkForDecimals "declare -A foo; foo[1.2]=bar" -- >>> prop $ verify checkForDecimals "foo[1.2]=bar"
-- >>> prop $ verifyNot checkForDecimals "declare -A foo; foo[1.2]=bar"
checkForDecimals = ForShell [Sh, Dash, Bash] f checkForDecimals = ForShell [Sh, Dash, Bash] f
where where
f t@(TA_Expansion id _) = potentially $ do f t@(TA_Expansion id _) = potentially $ do
@ -80,62 +78,63 @@ checkForDecimals = ForShell [Sh, Dash, Bash] f
f _ = return () f _ = return ()
prop_checkBashisms = verify checkBashisms "while read a; do :; done < <(a)" -- |
prop_checkBashisms2 = verify checkBashisms "[ foo -nt bar ]" -- >>> prop $ verify checkBashisms "while read a; do :; done < <(a)"
prop_checkBashisms3 = verify checkBashisms "echo $((i++))" -- >>> prop $ verify checkBashisms "[ foo -nt bar ]"
prop_checkBashisms4 = verify checkBashisms "rm !(*.hs)" -- >>> prop $ verify checkBashisms "echo $((i++))"
prop_checkBashisms5 = verify checkBashisms "source file" -- >>> prop $ verify checkBashisms "rm !(*.hs)"
prop_checkBashisms6 = verify checkBashisms "[ \"$a\" == 42 ]" -- >>> prop $ verify checkBashisms "source file"
prop_checkBashisms7 = verify checkBashisms "echo ${var[1]}" -- >>> prop $ verify checkBashisms "[ \"$a\" == 42 ]"
prop_checkBashisms8 = verify checkBashisms "echo ${!var[@]}" -- >>> prop $ verify checkBashisms "echo ${var[1]}"
prop_checkBashisms9 = verify checkBashisms "echo ${!var*}" -- >>> prop $ verify checkBashisms "echo ${!var[@]}"
prop_checkBashisms10= verify checkBashisms "echo ${var:4:12}" -- >>> prop $ verify checkBashisms "echo ${!var*}"
prop_checkBashisms11= verifyNot checkBashisms "echo ${var:-4}" -- >>> prop $ verify checkBashisms "echo ${var:4:12}"
prop_checkBashisms12= verify checkBashisms "echo ${var//foo/bar}" -- >>> prop $ verifyNot checkBashisms "echo ${var:-4}"
prop_checkBashisms13= verify checkBashisms "exec -c env" -- >>> prop $ verify checkBashisms "echo ${var//foo/bar}"
prop_checkBashisms14= verify checkBashisms "echo -n \"Foo: \"" -- >>> prop $ verify checkBashisms "exec -c env"
prop_checkBashisms15= verify checkBashisms "let n++" -- >>> prop $ verify checkBashisms "echo -n \"Foo: \""
prop_checkBashisms16= verify checkBashisms "echo $RANDOM" -- >>> prop $ verify checkBashisms "let n++"
prop_checkBashisms17= verify checkBashisms "echo $((RANDOM%6+1))" -- >>> prop $ verify checkBashisms "echo $RANDOM"
prop_checkBashisms18= verify checkBashisms "foo &> /dev/null" -- >>> prop $ verify checkBashisms "echo $((RANDOM%6+1))"
prop_checkBashisms19= verify checkBashisms "foo > file*.txt" -- >>> prop $ verify checkBashisms "foo &> /dev/null"
prop_checkBashisms20= verify checkBashisms "read -ra foo" -- >>> prop $ verify checkBashisms "foo > file*.txt"
prop_checkBashisms21= verify checkBashisms "[ -a foo ]" -- >>> prop $ verify checkBashisms "read -ra foo"
prop_checkBashisms22= verifyNot checkBashisms "[ foo -a bar ]" -- >>> prop $ verify checkBashisms "[ -a foo ]"
prop_checkBashisms23= verify checkBashisms "trap mything ERR INT" -- >>> prop $ verifyNot checkBashisms "[ foo -a bar ]"
prop_checkBashisms24= verifyNot checkBashisms "trap mything INT TERM" -- >>> prop $ verify checkBashisms "trap mything ERR INT"
prop_checkBashisms25= verify checkBashisms "cat < /dev/tcp/host/123" -- >>> prop $ verifyNot checkBashisms "trap mything INT TERM"
prop_checkBashisms26= verify checkBashisms "trap mything ERR SIGTERM" -- >>> prop $ verify checkBashisms "cat < /dev/tcp/host/123"
prop_checkBashisms27= verify checkBashisms "echo *[^0-9]*" -- >>> prop $ verify checkBashisms "trap mything ERR SIGTERM"
prop_checkBashisms28= verify checkBashisms "exec {n}>&2" -- >>> prop $ verify checkBashisms "echo *[^0-9]*"
prop_checkBashisms29= verify checkBashisms "echo ${!var}" -- >>> prop $ verify checkBashisms "exec {n}>&2"
prop_checkBashisms30= verify checkBashisms "printf -v '%s' \"$1\"" -- >>> prop $ verify checkBashisms "echo ${!var}"
prop_checkBashisms31= verify checkBashisms "printf '%q' \"$1\"" -- >>> prop $ verify checkBashisms "printf -v '%s' \"$1\""
prop_checkBashisms32= verifyNot checkBashisms "#!/bin/dash\n[ foo -nt bar ]" -- >>> prop $ verify checkBashisms "printf '%q' \"$1\""
prop_checkBashisms33= verify checkBashisms "#!/bin/sh\necho -n foo" -- >>> prop $ verifyNot checkBashisms "#!/bin/dash\n[ foo -nt bar ]"
prop_checkBashisms34= verifyNot checkBashisms "#!/bin/dash\necho -n foo" -- >>> prop $ verify checkBashisms "#!/bin/sh\necho -n foo"
prop_checkBashisms35= verifyNot checkBashisms "#!/bin/dash\nlocal foo" -- >>> prop $ verifyNot checkBashisms "#!/bin/dash\necho -n foo"
prop_checkBashisms36= verifyNot checkBashisms "#!/bin/dash\nread -p foo -r bar" -- >>> prop $ verifyNot checkBashisms "#!/bin/dash\nlocal foo"
prop_checkBashisms37= verifyNot checkBashisms "HOSTNAME=foo; echo $HOSTNAME" -- >>> prop $ verifyNot checkBashisms "#!/bin/dash\nread -p foo -r bar"
prop_checkBashisms38= verify checkBashisms "RANDOM=9; echo $RANDOM" -- >>> prop $ verifyNot checkBashisms "HOSTNAME=foo; echo $HOSTNAME"
prop_checkBashisms39= verify checkBashisms "foo-bar() { true; }" -- >>> prop $ verify checkBashisms "RANDOM=9; echo $RANDOM"
prop_checkBashisms40= verify checkBashisms "echo $(<file)" -- >>> prop $ verify checkBashisms "foo-bar() { true; }"
prop_checkBashisms41= verify checkBashisms "echo `<file`" -- >>> prop $ verify checkBashisms "echo $(<file)"
prop_checkBashisms42= verify checkBashisms "trap foo int" -- >>> prop $ verify checkBashisms "echo `<file`"
prop_checkBashisms43= verify checkBashisms "trap foo sigint" -- >>> prop $ verify checkBashisms "trap foo int"
prop_checkBashisms44= verifyNot checkBashisms "#!/bin/dash\ntrap foo int" -- >>> prop $ verify checkBashisms "trap foo sigint"
prop_checkBashisms45= verifyNot checkBashisms "#!/bin/dash\ntrap foo INT" -- >>> prop $ verifyNot checkBashisms "#!/bin/dash\ntrap foo int"
prop_checkBashisms46= verify checkBashisms "#!/bin/dash\ntrap foo SIGINT" -- >>> prop $ verifyNot checkBashisms "#!/bin/dash\ntrap foo INT"
prop_checkBashisms47= verify checkBashisms "#!/bin/dash\necho foo 42>/dev/null" -- >>> prop $ verify checkBashisms "#!/bin/dash\ntrap foo SIGINT"
prop_checkBashisms48= verifyNot checkBashisms "#!/bin/sh\necho $LINENO" -- >>> prop $ verify checkBashisms "#!/bin/dash\necho foo 42>/dev/null"
prop_checkBashisms49= verify checkBashisms "#!/bin/dash\necho $MACHTYPE" -- >>> prop $ verifyNot checkBashisms "#!/bin/sh\necho $LINENO"
prop_checkBashisms50= verify checkBashisms "#!/bin/sh\ncmd >& file" -- >>> prop $ verify checkBashisms "#!/bin/dash\necho $MACHTYPE"
prop_checkBashisms51= verifyNot checkBashisms "#!/bin/sh\ncmd 2>&1" -- >>> prop $ verify checkBashisms "#!/bin/sh\ncmd >& file"
prop_checkBashisms52= verifyNot checkBashisms "#!/bin/sh\ncmd >&2" -- >>> prop $ verifyNot checkBashisms "#!/bin/sh\ncmd 2>&1"
prop_checkBashisms53= verifyNot checkBashisms "#!/bin/sh\nprintf -- -f\n" -- >>> prop $ verifyNot checkBashisms "#!/bin/sh\ncmd >&2"
prop_checkBashisms54= verify checkBashisms "#!/bin/sh\nfoo+=bar" -- >>> prop $ verifyNot checkBashisms "#!/bin/sh\nprintf -- -f\n"
prop_checkBashisms55= verify checkBashisms "#!/bin/sh\necho ${@%foo}" -- >>> prop $ verify checkBashisms "#!/bin/sh\nfoo+=bar"
prop_checkBashisms56= verifyNot checkBashisms "#!/bin/sh\necho ${##}" -- >>> prop $ verify checkBashisms "#!/bin/sh\necho ${@%foo}"
-- >>> prop $ verifyNot checkBashisms "#!/bin/sh\necho ${##}"
checkBashisms = ForShell [Sh, Dash] $ \t -> do checkBashisms = ForShell [Sh, Dash] $ \t -> do
params <- ask params <- ask
kludge params t kludge params t
@ -317,8 +316,9 @@ checkBashisms = ForShell [Sh, Dash] $ \t -> do
Assignment (_, _, name, _) -> name == var Assignment (_, _, name, _) -> name == var
_ -> False _ -> False
prop_checkEchoSed1 = verify checkEchoSed "FOO=$(echo \"$cow\" | sed 's/foo/bar/g')" -- |
prop_checkEchoSed2 = verify checkEchoSed "rm $(echo $cow | sed -e 's,foo,bar,')" -- >>> prop $ verify checkEchoSed "FOO=$(echo \"$cow\" | sed 's/foo/bar/g')"
-- >>> prop $ verify checkEchoSed "rm $(echo $cow | sed -e 's,foo,bar,')"
checkEchoSed = ForShell [Bash, Ksh] f checkEchoSed = ForShell [Bash, Ksh] f
where where
f (T_Pipeline id _ [a, b]) = f (T_Pipeline id _ [a, b]) =
@ -344,10 +344,11 @@ checkEchoSed = ForShell [Bash, Ksh] f
f _ = return () f _ = return ()
prop_checkBraceExpansionVars1 = verify checkBraceExpansionVars "echo {1..$n}" -- |
prop_checkBraceExpansionVars2 = verifyNot checkBraceExpansionVars "echo {1,3,$n}" -- >>> prop $ verify checkBraceExpansionVars "echo {1..$n}"
prop_checkBraceExpansionVars3 = verify checkBraceExpansionVars "eval echo DSC{0001..$n}.jpg" -- >>> prop $ verifyNot checkBraceExpansionVars "echo {1,3,$n}"
prop_checkBraceExpansionVars4 = verify checkBraceExpansionVars "echo {$i..100}" -- >>> prop $ verify checkBraceExpansionVars "eval echo DSC{0001..$n}.jpg"
-- >>> prop $ verify checkBraceExpansionVars "echo {$i..100}"
checkBraceExpansionVars = ForShell [Bash] f checkBraceExpansionVars = ForShell [Bash] f
where where
f t@(T_BraceExpansion id list) = mapM_ check list f t@(T_BraceExpansion id list) = mapM_ check list
@ -372,12 +373,13 @@ checkBraceExpansionVars = ForShell [Bash] f
return $ isJust cmd && fromJust cmd `isUnqualifiedCommand` "eval" return $ isJust cmd && fromJust cmd `isUnqualifiedCommand` "eval"
prop_checkMultiDimensionalArrays1 = verify checkMultiDimensionalArrays "foo[a][b]=3" -- |
prop_checkMultiDimensionalArrays2 = verifyNot checkMultiDimensionalArrays "foo[a]=3" -- >>> prop $ verify checkMultiDimensionalArrays "foo[a][b]=3"
prop_checkMultiDimensionalArrays3 = verify checkMultiDimensionalArrays "foo=( [a][b]=c )" -- >>> prop $ verifyNot checkMultiDimensionalArrays "foo[a]=3"
prop_checkMultiDimensionalArrays4 = verifyNot checkMultiDimensionalArrays "foo=( [a]=c )" -- >>> prop $ verify checkMultiDimensionalArrays "foo=( [a][b]=c )"
prop_checkMultiDimensionalArrays5 = verify checkMultiDimensionalArrays "echo ${foo[bar][baz]}" -- >>> prop $ verifyNot checkMultiDimensionalArrays "foo=( [a]=c )"
prop_checkMultiDimensionalArrays6 = verifyNot checkMultiDimensionalArrays "echo ${foo[bar]}" -- >>> prop $ verify checkMultiDimensionalArrays "echo ${foo[bar][baz]}"
-- >>> prop $ verifyNot checkMultiDimensionalArrays "echo ${foo[bar]}"
checkMultiDimensionalArrays = ForShell [Bash] f checkMultiDimensionalArrays = ForShell [Bash] f
where where
f token = f token =
@ -392,16 +394,17 @@ checkMultiDimensionalArrays = ForShell [Bash] f
re = mkRegex "^\\[.*\\]\\[.*\\]" -- Fixme, this matches ${foo:- [][]} and such as well re = mkRegex "^\\[.*\\]\\[.*\\]" -- Fixme, this matches ${foo:- [][]} and such as well
isMultiDim t = getBracedModifier (bracedString t) `matches` re isMultiDim t = getBracedModifier (bracedString t) `matches` re
prop_checkPS11 = verify checkPS1Assignments "PS1='\\033[1;35m\\$ '" -- |
prop_checkPS11a= verify checkPS1Assignments "export PS1='\\033[1;35m\\$ '" -- >>> prop $ verify checkPS1Assignments "PS1='\\033[1;35m\\$ '"
prop_checkPSf2 = verify checkPS1Assignments "PS1='\\h \\e[0m\\$ '" -- >>> prop $ verify checkPS1Assignments "export PS1='\\033[1;35m\\$ '"
prop_checkPS13 = verify checkPS1Assignments "PS1=$'\\x1b[c '" -- >>> prop $ verify checkPS1Assignments "PS1='\\h \\e[0m\\$ '"
prop_checkPS14 = verify checkPS1Assignments "PS1=$'\\e[3m; '" -- >>> prop $ verify checkPS1Assignments "PS1=$'\\x1b[c '"
prop_checkPS14a= verify checkPS1Assignments "export PS1=$'\\e[3m; '" -- >>> prop $ verify checkPS1Assignments "PS1=$'\\e[3m; '"
prop_checkPS15 = verifyNot checkPS1Assignments "PS1='\\[\\033[1;35m\\]\\$ '" -- >>> prop $ verify checkPS1Assignments "export PS1=$'\\e[3m; '"
prop_checkPS16 = verifyNot checkPS1Assignments "PS1='\\[\\e1m\\e[1m\\]\\$ '" -- >>> prop $ verifyNot checkPS1Assignments "PS1='\\[\\033[1;35m\\]\\$ '"
prop_checkPS17 = verifyNot checkPS1Assignments "PS1='e033x1B'" -- >>> prop $ verifyNot checkPS1Assignments "PS1='\\[\\e1m\\e[1m\\]\\$ '"
prop_checkPS18 = verifyNot checkPS1Assignments "PS1='\\[\\e\\]'" -- >>> prop $ verifyNot checkPS1Assignments "PS1='e033x1B'"
-- >>> prop $ verifyNot checkPS1Assignments "PS1='\\[\\e\\]'"
checkPS1Assignments = ForShell [Bash] f checkPS1Assignments = ForShell [Bash] f
where where
f token = case token of f token = case token of
@ -417,7 +420,3 @@ checkPS1Assignments = ForShell [Bash] f
isJust $ matchRegex escapeRegex unenclosed isJust $ matchRegex escapeRegex unenclosed
enclosedRegex = mkRegex "\\\\\\[.*\\\\\\]" -- FIXME: shouldn't be eager enclosedRegex = mkRegex "\\\\\\[.*\\\\\\]" -- FIXME: shouldn't be eager
escapeRegex = mkRegex "\\\\x1[Bb]|\\\\e|\x1B|\\\\033" escapeRegex = mkRegex "\\\\x1[Bb]|\\\\e|\x1B|\\\\033"
return []
runTests = $( [| $(forAllProperties) (quickCheckWithResult (stdArgs { maxSuccess = 1 }) ) |])

View file

@ -17,11 +17,10 @@
You should have received a copy of the GNU General Public License You should have received a copy of the GNU General Public License
along with this program. If not, see <https://www.gnu.org/licenses/>. along with this program. If not, see <https://www.gnu.org/licenses/>.
-} -}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE NoMonomorphismRestriction #-} {-# LANGUAGE NoMonomorphismRestriction #-}
{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE MultiWayIf #-} {-# LANGUAGE MultiWayIf #-}
module ShellCheck.Parser (parseScript, runTests) where module ShellCheck.Parser (parseScript) where
import ShellCheck.AST import ShellCheck.AST
import ShellCheck.ASTLib import ShellCheck.ASTLib
@ -48,7 +47,9 @@ import qualified Control.Monad.Reader as Mr
import qualified Control.Monad.State as Ms import qualified Control.Monad.State as Ms
import qualified Data.Map as Map import qualified Data.Map as Map
import Test.QuickCheck.All (quickCheckAll) prop :: Bool -> IO ()
prop False = putStrLn "FAIL"
prop True = return ()
type SCBase m = Mr.ReaderT (Environment m) (Ms.StateT SystemState m) type SCBase m = Mr.ReaderT (Environment m) (Ms.StateT SystemState m)
type SCParser m v = ParsecT String UserState (SCBase m) v type SCParser m v = ParsecT String UserState (SCBase m) v
@ -87,7 +88,8 @@ extglobStart = oneOf extglobStartChars
unicodeDoubleQuotes = "\x201C\x201D\x2033\x2036" unicodeDoubleQuotes = "\x201C\x201D\x2033\x2036"
unicodeSingleQuotes = "\x2018\x2019" unicodeSingleQuotes = "\x2018\x2019"
prop_spacing = isOk spacing " \\\n # Comment" -- |
-- >>> prop $ isOk spacing " \\\n # Comment"
spacing = do spacing = do
x <- many (many1 linewhitespace <|> try (string "\\\n" >> return "")) x <- many (many1 linewhitespace <|> try (string "\\\n" >> return ""))
optional readComment optional readComment
@ -98,9 +100,10 @@ spacing1 = do
when (null spacing) $ fail "Expected whitespace" when (null spacing) $ fail "Expected whitespace"
return spacing return spacing
prop_allspacing = isOk allspacing "#foo" -- |
prop_allspacing2 = isOk allspacing " #foo\n # bar\n#baz\n" -- >>> prop $ isOk allspacing "#foo"
prop_allspacing3 = isOk allspacing "#foo\n#bar\n#baz\n" -- >>> prop $ isOk allspacing " #foo\n # bar\n#baz\n"
-- >>> prop $ isOk allspacing "#foo\n#bar\n#baz\n"
allspacing = do allspacing = do
s <- spacing s <- spacing
more <- option False (linefeed >> return True) more <- option False (linefeed >> return True)
@ -673,29 +676,30 @@ readConditionContents single =
readCondContents = readCondOr readCondContents = readCondOr
prop_a1 = isOk readArithmeticContents " n++ + ++c" -- |
prop_a2 = isOk readArithmeticContents "$N*4-(3,2)" -- >>> prop $ isOk readArithmeticContents " n++ + ++c"
prop_a3 = isOk readArithmeticContents "n|=2<<1" -- >>> prop $ isOk readArithmeticContents "$N*4-(3,2)"
prop_a4 = isOk readArithmeticContents "n &= 2 **3" -- >>> prop $ isOk readArithmeticContents "n|=2<<1"
prop_a5 = isOk readArithmeticContents "1 |= 4 && n >>= 4" -- >>> prop $ isOk readArithmeticContents "n &= 2 **3"
prop_a6 = isOk readArithmeticContents " 1 | 2 ||3|4" -- >>> prop $ isOk readArithmeticContents "1 |= 4 && n >>= 4"
prop_a7 = isOk readArithmeticContents "3*2**10" -- >>> prop $ isOk readArithmeticContents " 1 | 2 ||3|4"
prop_a8 = isOk readArithmeticContents "3" -- >>> prop $ isOk readArithmeticContents "3*2**10"
prop_a9 = isOk readArithmeticContents "a^!-b" -- >>> prop $ isOk readArithmeticContents "3"
prop_a10= isOk readArithmeticContents "! $?" -- >>> prop $ isOk readArithmeticContents "a^!-b"
prop_a11= isOk readArithmeticContents "10#08 * 16#f" -- >>> prop $ isOk readArithmeticContents "! $?"
prop_a12= isOk readArithmeticContents "\"$((3+2))\" + '37'" -- >>> prop $ isOk readArithmeticContents "10#08 * 16#f"
prop_a13= isOk readArithmeticContents "foo[9*y+x]++" -- >>> prop $ isOk readArithmeticContents "\"$((3+2))\" + '37'"
prop_a14= isOk readArithmeticContents "1+`echo 2`" -- >>> prop $ isOk readArithmeticContents "foo[9*y+x]++"
prop_a15= isOk readArithmeticContents "foo[`echo foo | sed s/foo/4/g` * 3] + 4" -- >>> prop $ isOk readArithmeticContents "1+`echo 2`"
prop_a16= isOk readArithmeticContents "$foo$bar" -- >>> prop $ isOk readArithmeticContents "foo[`echo foo | sed s/foo/4/g` * 3] + 4"
prop_a17= isOk readArithmeticContents "i<(0+(1+1))" -- >>> prop $ isOk readArithmeticContents "$foo$bar"
prop_a18= isOk readArithmeticContents "a?b:c" -- >>> prop $ isOk readArithmeticContents "i<(0+(1+1))"
prop_a19= isOk readArithmeticContents "\\\n3 +\\\n 2" -- >>> prop $ isOk readArithmeticContents "a?b:c"
prop_a20= isOk readArithmeticContents "a ? b ? c : d : e" -- >>> prop $ isOk readArithmeticContents "\\\n3 +\\\n 2"
prop_a21= isOk readArithmeticContents "a ? b : c ? d : e" -- >>> prop $ isOk readArithmeticContents "a ? b ? c : d : e"
prop_a22= isOk readArithmeticContents "!!a" -- >>> prop $ isOk readArithmeticContents "a ? b : c ? d : e"
prop_a23= isOk readArithmeticContents "~0" -- >>> prop $ isOk readArithmeticContents "!!a"
-- >>> prop $ isOk readArithmeticContents "~0"
readArithmeticContents :: Monad m => SCParser m Token readArithmeticContents :: Monad m => SCParser m Token
readArithmeticContents = readArithmeticContents =
readSequence readSequence
@ -876,33 +880,34 @@ readArithmeticContents =
prop_readCondition = isOk readCondition "[ \\( a = b \\) -a \\( c = d \\) ]" -- |
prop_readCondition2 = isOk readCondition "[[ (a = b) || (c = d) ]]" -- >>> prop $ isOk readCondition "[ \\( a = b \\) -a \\( c = d \\) ]"
prop_readCondition3 = isOk readCondition "[[ $c = [[:alpha:].~-] ]]" -- >>> prop $ isOk readCondition "[[ (a = b) || (c = d) ]]"
prop_readCondition4 = isOk readCondition "[[ $c =~ *foo* ]]" -- >>> prop $ isOk readCondition "[[ $c = [[:alpha:].~-] ]]"
prop_readCondition5 = isOk readCondition "[[ $c =~ f( ]] )* ]]" -- >>> prop $ isOk readCondition "[[ $c =~ *foo* ]]"
prop_readCondition5a = isOk readCondition "[[ $c =~ a(b) ]]" -- >>> prop $ isOk readCondition "[[ $c =~ f( ]] )* ]]"
prop_readCondition5b = isOk readCondition "[[ $c =~ f( ($var ]]) )* ]]" -- >>> prop $ isOk readCondition "[[ $c =~ a(b) ]]"
prop_readCondition6 = isOk readCondition "[[ $c =~ ^[yY]$ ]]" -- >>> prop $ isOk readCondition "[[ $c =~ f( ($var ]]) )* ]]"
prop_readCondition7 = isOk readCondition "[[ ${line} =~ ^[[:space:]]*# ]]" -- >>> prop $ isOk readCondition "[[ $c =~ ^[yY]$ ]]"
prop_readCondition8 = isOk readCondition "[[ $l =~ ogg|flac ]]" -- >>> prop $ isOk readCondition "[[ ${line} =~ ^[[:space:]]*# ]]"
prop_readCondition9 = isOk readCondition "[ foo -a -f bar ]" -- >>> prop $ isOk readCondition "[[ $l =~ ogg|flac ]]"
prop_readCondition10 = isOk readCondition "[[\na == b\n||\nc == d ]]" -- >>> prop $ isOk readCondition "[ foo -a -f bar ]"
prop_readCondition10a= isOk readCondition "[[\na == b ||\nc == d ]]" -- >>> prop $ isOk readCondition "[[\na == b\n||\nc == d ]]"
prop_readCondition10b= isOk readCondition "[[ a == b\n||\nc == d ]]" -- >>> prop $ isOk readCondition "[[\na == b ||\nc == d ]]"
prop_readCondition11 = isOk readCondition "[[ a == b ||\n c == d ]]" -- >>> prop $ isOk readCondition "[[ a == b\n||\nc == d ]]"
prop_readCondition12 = isWarning readCondition "[ a == b \n -o c == d ]" -- >>> prop $ isOk readCondition "[[ a == b ||\n c == d ]]"
prop_readCondition13 = isOk readCondition "[[ foo =~ ^fo{1,3}$ ]]" -- >>> prop $ isWarning readCondition "[ a == b \n -o c == d ]"
prop_readCondition14 = isOk readCondition "[ foo '>' bar ]" -- >>> prop $ isOk readCondition "[[ foo =~ ^fo{1,3}$ ]]"
prop_readCondition15 = isOk readCondition "[ foo \">=\" bar ]" -- >>> prop $ isOk readCondition "[ foo '>' bar ]"
prop_readCondition16 = isOk readCondition "[ foo \\< bar ]" -- >>> prop $ isOk readCondition "[ foo \">=\" bar ]"
prop_readCondition17 = isOk readCondition "[[ ${file::1} = [-.\\|/\\\\] ]]" -- >>> prop $ isOk readCondition "[ foo \\< bar ]"
prop_readCondition18 = isOk readCondition "[ ]" -- >>> prop $ isOk readCondition "[[ ${file::1} = [-.\\|/\\\\] ]]"
prop_readCondition19 = isOk readCondition "[ '(' x \")\" ]" -- >>> prop $ isOk readCondition "[ ]"
prop_readCondition20 = isOk readCondition "[[ echo_rc -eq 0 ]]" -- >>> prop $ isOk readCondition "[ '(' x \")\" ]"
prop_readCondition21 = isOk readCondition "[[ $1 =~ ^(a\\ b)$ ]]" -- >>> prop $ isOk readCondition "[[ echo_rc -eq 0 ]]"
prop_readCondition22 = isOk readCondition "[[ $1 =~ \\.a\\.(\\.b\\.)\\.c\\. ]]" -- >>> prop $ isOk readCondition "[[ $1 =~ ^(a\\ b)$ ]]"
prop_readCondition23 = isOk readCondition "[[ -v arr[$var] ]]" -- >>> prop $ isOk readCondition "[[ $1 =~ \\.a\\.(\\.b\\.)\\.c\\. ]]"
-- >>> prop $ isOk readCondition "[[ -v arr[$var] ]]"
readCondition = called "test expression" $ do readCondition = called "test expression" $ do
opos <- getPosition opos <- getPosition
start <- startSpan start <- startSpan
@ -940,12 +945,13 @@ readAnnotationPrefix = do
many linewhitespace many linewhitespace
string "shellcheck" string "shellcheck"
prop_readAnnotation1 = isOk readAnnotation "# shellcheck disable=1234,5678\n" -- |
prop_readAnnotation2 = isOk readAnnotation "# shellcheck disable=SC1234 disable=SC5678\n" -- >>> prop $ isOk readAnnotation "# shellcheck disable=1234,5678\n"
prop_readAnnotation3 = isOk readAnnotation "# shellcheck disable=SC1234 source=/dev/null disable=SC5678\n" -- >>> prop $ isOk readAnnotation "# shellcheck disable=SC1234 disable=SC5678\n"
prop_readAnnotation4 = isWarning readAnnotation "# shellcheck cats=dogs disable=SC1234\n" -- >>> prop $ isOk readAnnotation "# shellcheck disable=SC1234 source=/dev/null disable=SC5678\n"
prop_readAnnotation5 = isOk readAnnotation "# shellcheck disable=SC2002 # All cats are precious\n" -- >>> prop $ isWarning readAnnotation "# shellcheck cats=dogs disable=SC1234\n"
prop_readAnnotation6 = isOk readAnnotation "# shellcheck disable=SC1234 # shellcheck foo=bar\n" -- >>> prop $ isOk readAnnotation "# shellcheck disable=SC2002 # All cats are precious\n"
-- >>> prop $ isOk readAnnotation "# shellcheck disable=SC1234 # shellcheck foo=bar\n"
readAnnotation = called "shellcheck directive" $ do readAnnotation = called "shellcheck directive" $ do
try readAnnotationPrefix try readAnnotationPrefix
many1 linewhitespace many1 linewhitespace
@ -1002,18 +1008,19 @@ readAnyComment = do
char '#' char '#'
many $ noneOf "\r\n" many $ noneOf "\r\n"
prop_readNormalWord = isOk readNormalWord "'foo'\"bar\"{1..3}baz$(lol)" -- |
prop_readNormalWord2 = isOk readNormalWord "foo**(foo)!!!(@@(bar))" -- >>> prop $ isOk readNormalWord "'foo'\"bar\"{1..3}baz$(lol)"
prop_readNormalWord3 = isOk readNormalWord "foo#" -- >>> prop $ isOk readNormalWord "foo**(foo)!!!(@@(bar))"
prop_readNormalWord4 = isOk readNormalWord "$\"foo\"$'foo\nbar'" -- >>> prop $ isOk readNormalWord "foo#"
prop_readNormalWord5 = isWarning readNormalWord "${foo}}" -- >>> prop $ isOk readNormalWord "$\"foo\"$'foo\nbar'"
prop_readNormalWord6 = isOk readNormalWord "foo/{}" -- >>> prop $ isWarning readNormalWord "${foo}}"
prop_readNormalWord7 = isOk readNormalWord "foo\\\nbar" -- >>> prop $ isOk readNormalWord "foo/{}"
prop_readNormalWord8 = isWarning readSubshell "(foo\\ \nbar)" -- >>> prop $ isOk readNormalWord "foo\\\nbar"
prop_readNormalWord9 = isOk readSubshell "(foo\\ ;\nbar)" -- >>> prop $ isWarning readSubshell "(foo\\ \nbar)"
prop_readNormalWord10 = isWarning readNormalWord "\x201Chello\x201D" -- >>> prop $ isOk readSubshell "(foo\\ ;\nbar)"
prop_readNormalWord11 = isWarning readNormalWord "\x2018hello\x2019" -- >>> prop $ isWarning readNormalWord "\x201Chello\x201D"
prop_readNormalWord12 = isWarning readNormalWord "hello\x2018" -- >>> prop $ isWarning readNormalWord "\x2018hello\x2019"
-- >>> prop $ isWarning readNormalWord "hello\x2018"
readNormalWord = readNormalishWord "" readNormalWord = readNormalishWord ""
readNormalishWord end = do readNormalishWord end = do
@ -1111,9 +1118,10 @@ readParamSubSpecialChar = do
id <- endSpan start id <- endSpan start
return $ T_ParamSubSpecialChar id x return $ T_ParamSubSpecialChar id x
prop_readProcSub1 = isOk readProcSub "<(echo test | wc -l)" -- |
prop_readProcSub2 = isOk readProcSub "<( if true; then true; fi )" -- >>> prop $ isOk readProcSub "<(echo test | wc -l)"
prop_readProcSub3 = isOk readProcSub "<( # nothing here \n)" -- >>> prop $ isOk readProcSub "<( if true; then true; fi )"
-- >>> prop $ isOk readProcSub "<( # nothing here \n)"
readProcSub = called "process substitution" $ do readProcSub = called "process substitution" $ do
start <- startSpan start <- startSpan
dir <- try $ do dir <- try $ do
@ -1126,13 +1134,14 @@ readProcSub = called "process substitution" $ do
id <- endSpan start id <- endSpan start
return $ T_ProcSub id dir list return $ T_ProcSub id dir list
prop_readSingleQuoted = isOk readSingleQuoted "'foo bar'" -- |
prop_readSingleQuoted2 = isWarning readSingleQuoted "'foo bar\\'" -- >>> prop $ isOk readSingleQuoted "'foo bar'"
prop_readSingleQuoted4 = isWarning readNormalWord "'it's" -- >>> prop $ isWarning readSingleQuoted "'foo bar\\'"
prop_readSingleQuoted5 = isWarning readSimpleCommand "foo='bar\ncow 'arg" -- >>> prop $ isWarning readNormalWord "'it's"
prop_readSingleQuoted6 = isOk readSimpleCommand "foo='bar cow 'arg" -- >>> prop $ isWarning readSimpleCommand "foo='bar\ncow 'arg"
prop_readSingleQuoted7 = isOk readSingleQuoted "'foo\x201C\&bar'" -- >>> prop $ isOk readSimpleCommand "foo='bar cow 'arg"
prop_readSingleQuoted8 = isWarning readSingleQuoted "'foo\x2018\&bar'" -- >>> prop $ isOk readSingleQuoted "'foo\x201C\&bar'"
-- >>> prop $ isWarning readSingleQuoted "'foo\x2018\&bar'"
readSingleQuoted = called "single quoted string" $ do readSingleQuoted = called "single quoted string" $ do
start <- startSpan start <- startSpan
startPos <- getPosition startPos <- getPosition
@ -1174,14 +1183,15 @@ readSingleQuotedPart =
return [x] return [x]
prop_readBackTicked = isOk (readBackTicked False) "`ls *.mp3`" -- |
prop_readBackTicked2 = isOk (readBackTicked False) "`grep \"\\\"\"`" -- >>> prop $ isOk (readBackTicked False) "`ls *.mp3`"
prop_readBackTicked3 = isWarning (readBackTicked False) "´grep \"\\\"\"´" -- >>> prop $ isOk (readBackTicked False) "`grep \"\\\"\"`"
prop_readBackTicked4 = isOk readSimpleCommand "`echo foo\necho bar`" -- >>> prop $ isWarning (readBackTicked False) "´grep \"\\\"\"´"
prop_readBackTicked5 = isOk readSimpleCommand "echo `foo`bar" -- >>> prop $ isOk readSimpleCommand "`echo foo\necho bar`"
prop_readBackTicked6 = isWarning readSimpleCommand "echo `foo\necho `bar" -- >>> prop $ isOk readSimpleCommand "echo `foo`bar"
prop_readBackTicked7 = isOk readSimpleCommand "`#inline comment`" -- >>> prop $ isWarning readSimpleCommand "echo `foo\necho `bar"
prop_readBackTicked8 = isOk readSimpleCommand "echo `#comment` \\\nbar baz" -- >>> prop $ isOk readSimpleCommand "`#inline comment`"
-- >>> prop $ isOk readSimpleCommand "echo `#comment` \\\nbar baz"
readQuotedBackTicked = readBackTicked True readQuotedBackTicked = readBackTicked True
readUnquotedBackTicked = readBackTicked False readUnquotedBackTicked = readBackTicked False
readBackTicked quoted = called "backtick expansion" $ do readBackTicked quoted = called "backtick expansion" $ do
@ -1247,15 +1257,16 @@ parseForgettingContext alsoOnSuccess parser = do
Ms.put c Ms.put c
fail "" fail ""
prop_readDoubleQuoted = isOk readDoubleQuoted "\"Hello $FOO\"" -- |
prop_readDoubleQuoted2 = isOk readDoubleQuoted "\"$'\"" -- >>> prop $ isOk readDoubleQuoted "\"Hello $FOO\""
prop_readDoubleQuoted3 = isOk readDoubleQuoted "\"\x2018hello\x2019\"" -- >>> prop $ isOk readDoubleQuoted "\"$'\""
prop_readDoubleQuoted4 = isWarning readSimpleCommand "\"foo\nbar\"foo" -- >>> prop $ isOk readDoubleQuoted "\"\x2018hello\x2019\""
prop_readDoubleQuoted5 = isOk readSimpleCommand "lol \"foo\nbar\" etc" -- >>> prop $ isWarning readSimpleCommand "\"foo\nbar\"foo"
prop_readDoubleQuoted6 = isOk readSimpleCommand "echo \"${ ls; }\"" -- >>> prop $ isOk readSimpleCommand "lol \"foo\nbar\" etc"
prop_readDoubleQuoted7 = isOk readSimpleCommand "echo \"${ ls;}bar\"" -- >>> prop $ isOk readSimpleCommand "echo \"${ ls; }\""
prop_readDoubleQuoted8 = isWarning readDoubleQuoted "\"\x201Chello\x201D\"" -- >>> prop $ isOk readSimpleCommand "echo \"${ ls;}bar\""
prop_readDoubleQuoted10 = isOk readDoubleQuoted "\"foo\\\\n\"" -- >>> prop $ isWarning readDoubleQuoted "\"\x201Chello\x201D\""
-- >>> prop $ isOk readDoubleQuoted "\"foo\\\\n\""
readDoubleQuoted = called "double quoted string" $ do readDoubleQuoted = called "double quoted string" $ do
start <- startSpan start <- startSpan
startPos <- getPosition startPos <- getPosition
@ -1308,14 +1319,15 @@ readNormalLiteral end = do
id <- endSpan start id <- endSpan start
return $ T_Literal id (concat s) return $ T_Literal id (concat s)
prop_readGlob1 = isOk readGlob "*" -- |
prop_readGlob2 = isOk readGlob "[^0-9]" -- >>> prop $ isOk readGlob "*"
prop_readGlob3 = isOk readGlob "[a[:alpha:]]" -- >>> prop $ isOk readGlob "[^0-9]"
prop_readGlob4 = isOk readGlob "[[:alnum:]]" -- >>> prop $ isOk readGlob "[a[:alpha:]]"
prop_readGlob5 = isOk readGlob "[^[:alpha:]1-9]" -- >>> prop $ isOk readGlob "[[:alnum:]]"
prop_readGlob6 = isOk readGlob "[\\|]" -- >>> prop $ isOk readGlob "[^[:alpha:]1-9]"
prop_readGlob7 = isOk readGlob "[^[]" -- >>> prop $ isOk readGlob "[\\|]"
prop_readGlob8 = isOk readGlob "[*?]" -- >>> prop $ isOk readGlob "[^[]"
-- >>> prop $ isOk readGlob "[*?]"
readGlob = readExtglob <|> readSimple <|> readClass <|> readGlobbyLiteral readGlob = readExtglob <|> readSimple <|> readClass <|> readGlobbyLiteral
where where
readSimple = do readSimple = do
@ -1383,13 +1395,14 @@ readNormalEscaped = called "escaped char" $ do
parseProblemAt pos ErrorC 1101 "Delete trailing spaces after \\ to break line (or use quotes for literal space)." parseProblemAt pos ErrorC 1101 "Delete trailing spaces after \\ to break line (or use quotes for literal space)."
prop_readExtglob1 = isOk readExtglob "!(*.mp3)" -- |
prop_readExtglob2 = isOk readExtglob "!(*.mp3|*.wmv)" -- >>> prop $ isOk readExtglob "!(*.mp3)"
prop_readExtglob4 = isOk readExtglob "+(foo \\) bar)" -- >>> prop $ isOk readExtglob "!(*.mp3|*.wmv)"
prop_readExtglob5 = isOk readExtglob "+(!(foo *(bar)))" -- >>> prop $ isOk readExtglob "+(foo \\) bar)"
prop_readExtglob6 = isOk readExtglob "*(((||))|())" -- >>> prop $ isOk readExtglob "+(!(foo *(bar)))"
prop_readExtglob7 = isOk readExtglob "*(<>)" -- >>> prop $ isOk readExtglob "*(((||))|())"
prop_readExtglob8 = isOk readExtglob "@(|*())" -- >>> prop $ isOk readExtglob "*(<>)"
-- >>> prop $ isOk readExtglob "@(|*())"
readExtglob = called "extglob" $ do readExtglob = called "extglob" $ do
start <- startSpan start <- startSpan
c <- try $ do c <- try $ do
@ -1465,14 +1478,15 @@ readGenericEscaped = do
x <- anyChar x <- anyChar
return $ if x == '\n' then [] else ['\\', x] return $ if x == '\n' then [] else ['\\', x]
prop_readBraced = isOk readBraced "{1..4}" -- |
prop_readBraced2 = isOk readBraced "{foo,bar,\"baz lol\"}" -- >>> prop $ isOk readBraced "{1..4}"
prop_readBraced3 = isOk readBraced "{1,\\},2}" -- >>> prop $ isOk readBraced "{foo,bar,\"baz lol\"}"
prop_readBraced4 = isOk readBraced "{1,{2,3}}" -- >>> prop $ isOk readBraced "{1,\\},2}"
prop_readBraced5 = isOk readBraced "{JP{,E}G,jp{,e}g}" -- >>> prop $ isOk readBraced "{1,{2,3}}"
prop_readBraced6 = isOk readBraced "{foo,bar,$((${var}))}" -- >>> prop $ isOk readBraced "{JP{,E}G,jp{,e}g}"
prop_readBraced7 = isNotOk readBraced "{}" -- >>> prop $ isOk readBraced "{foo,bar,$((${var}))}"
prop_readBraced8 = isNotOk readBraced "{foo}" -- >>> prop $ isNotOk readBraced "{}"
-- >>> prop $ isNotOk readBraced "{foo}"
readBraced = try braceExpansion readBraced = try braceExpansion
where where
braceExpansion = braceExpansion =
@ -1512,9 +1526,10 @@ readDoubleQuotedDollar = do
readDollarExp <|> readDollarLonely readDollarExp <|> readDollarLonely
prop_readDollarExpression1 = isOk readDollarExpression "$(((1) && 3))" -- |
prop_readDollarExpression2 = isWarning readDollarExpression "$(((1)) && 3)" -- >>> prop $ isOk readDollarExpression "$(((1) && 3))"
prop_readDollarExpression3 = isWarning readDollarExpression "$((\"$@\" &); foo;)" -- >>> prop $ isWarning readDollarExpression "$(((1)) && 3)"
-- >>> prop $ isWarning readDollarExpression "$((\"$@\" &); foo;)"
readDollarExpression :: Monad m => SCParser m Token readDollarExpression :: Monad m => SCParser m Token
readDollarExpression = do readDollarExpression = do
ensureDollar ensureDollar
@ -1525,7 +1540,8 @@ readDollarExp = arithmetic <|> readDollarExpansion <|> readDollarBracket <|> rea
arithmetic = readAmbiguous "$((" readDollarArithmetic readDollarExpansion (\pos -> arithmetic = readAmbiguous "$((" readDollarArithmetic readDollarExpansion (\pos ->
parseNoteAt pos WarningC 1102 "Shells disambiguate $(( differently or not at all. For $(command substition), add space after $( . For $((arithmetics)), fix parsing errors.") parseNoteAt pos WarningC 1102 "Shells disambiguate $(( differently or not at all. For $(command substition), add space after $( . For $((arithmetics)), fix parsing errors.")
prop_readDollarSingleQuote = isOk readDollarSingleQuote "$'foo\\\'lol'" -- |
-- >>> prop $ isOk readDollarSingleQuote "$'foo\\\'lol'"
readDollarSingleQuote = called "$'..' expression" $ do readDollarSingleQuote = called "$'..' expression" $ do
start <- startSpan start <- startSpan
try $ string "$'" try $ string "$'"
@ -1534,7 +1550,8 @@ readDollarSingleQuote = called "$'..' expression" $ do
id <- endSpan start id <- endSpan start
return $ T_DollarSingleQuoted id str return $ T_DollarSingleQuoted id str
prop_readDollarDoubleQuote = isOk readDollarDoubleQuote "$\"hello\"" -- |
-- >>> prop $ isOk readDollarDoubleQuote "$\"hello\""
readDollarDoubleQuote = do readDollarDoubleQuote = do
lookAhead . try $ string "$\"" lookAhead . try $ string "$\""
start <- startSpan start <- startSpan
@ -1545,8 +1562,9 @@ readDollarDoubleQuote = do
id <- endSpan start id <- endSpan start
return $ T_DollarDoubleQuoted id x return $ T_DollarDoubleQuoted id x
prop_readDollarArithmetic = isOk readDollarArithmetic "$(( 3 * 4 +5))" -- |
prop_readDollarArithmetic2 = isOk readDollarArithmetic "$(((3*4)+(1*2+(3-1))))" -- >>> prop $ isOk readDollarArithmetic "$(( 3 * 4 +5))"
-- >>> prop $ isOk readDollarArithmetic "$(((3*4)+(1*2+(3-1))))"
readDollarArithmetic = called "$((..)) expression" $ do readDollarArithmetic = called "$((..)) expression" $ do
start <- startSpan start <- startSpan
try (string "$((") try (string "$((")
@ -1565,7 +1583,8 @@ readDollarBracket = called "$[..] expression" $ do
id <- endSpan start id <- endSpan start
return (T_DollarBracket id c) return (T_DollarBracket id c)
prop_readArithmeticExpression = isOk readArithmeticExpression "((a?b:c))" -- |
-- >>> prop $ isOk readArithmeticExpression "((a?b:c))"
readArithmeticExpression = called "((..)) command" $ do readArithmeticExpression = called "((..)) command" $ do
start <- startSpan start <- startSpan
try (string "((") try (string "((")
@ -1588,8 +1607,9 @@ readAmbiguous prefix expected alternative warner = do
warner pos warner pos
return t return t
prop_readDollarBraceCommandExpansion1 = isOk readDollarBraceCommandExpansion "${ ls; }" -- |
prop_readDollarBraceCommandExpansion2 = isOk readDollarBraceCommandExpansion "${\nls\n}" -- >>> prop $ isOk readDollarBraceCommandExpansion "${ ls; }"
-- >>> prop $ isOk readDollarBraceCommandExpansion "${\nls\n}"
readDollarBraceCommandExpansion = called "ksh ${ ..; } command expansion" $ do readDollarBraceCommandExpansion = called "ksh ${ ..; } command expansion" $ do
start <- startSpan start <- startSpan
try $ do try $ do
@ -1601,10 +1621,11 @@ readDollarBraceCommandExpansion = called "ksh ${ ..; } command expansion" $ do
id <- endSpan start id <- endSpan start
return $ T_DollarBraceCommandExpansion id term return $ T_DollarBraceCommandExpansion id term
prop_readDollarBraced1 = isOk readDollarBraced "${foo//bar/baz}" -- |
prop_readDollarBraced2 = isOk readDollarBraced "${foo/'{cow}'}" -- >>> prop $ isOk readDollarBraced "${foo//bar/baz}"
prop_readDollarBraced3 = isOk readDollarBraced "${foo%%$(echo cow\\})}" -- >>> prop $ isOk readDollarBraced "${foo/'{cow}'}"
prop_readDollarBraced4 = isOk readDollarBraced "${foo#\\}}" -- >>> prop $ isOk readDollarBraced "${foo%%$(echo cow\\})}"
-- >>> prop $ isOk readDollarBraced "${foo#\\}}"
readDollarBraced = called "parameter expansion" $ do readDollarBraced = called "parameter expansion" $ do
start <- startSpan start <- startSpan
try (string "${") try (string "${")
@ -1613,9 +1634,10 @@ readDollarBraced = called "parameter expansion" $ do
id <- endSpan start id <- endSpan start
return $ T_DollarBraced id word return $ T_DollarBraced id word
prop_readDollarExpansion1= isOk readDollarExpansion "$(echo foo; ls\n)" -- |
prop_readDollarExpansion2= isOk readDollarExpansion "$( )" -- >>> prop $ isOk readDollarExpansion "$(echo foo; ls\n)"
prop_readDollarExpansion3= isOk readDollarExpansion "$( command \n#comment \n)" -- >>> prop $ isOk readDollarExpansion "$( )"
-- >>> prop $ isOk readDollarExpansion "$( command \n#comment \n)"
readDollarExpansion = called "command expansion" $ do readDollarExpansion = called "command expansion" $ do
start <- startSpan start <- startSpan
try (string "$(") try (string "$(")
@ -1624,12 +1646,12 @@ readDollarExpansion = called "command expansion" $ do
id <- endSpan start id <- endSpan start
return $ T_DollarExpansion id cmds return $ T_DollarExpansion id cmds
prop_readDollarVariable = isOk readDollarVariable "$@" -- |
prop_readDollarVariable2 = isOk (readDollarVariable >> anyChar) "$?!" -- >>> prop $ isOk readDollarVariable "$@"
prop_readDollarVariable3 = isWarning (readDollarVariable >> anyChar) "$10" -- >>> prop $ isOk (readDollarVariable >> anyChar) "$?!"
prop_readDollarVariable4 = isWarning (readDollarVariable >> string "[@]") "$arr[@]" -- >>> prop $ isWarning (readDollarVariable >> anyChar) "$10"
prop_readDollarVariable5 = isWarning (readDollarVariable >> string "[f") "$arr[f" -- >>> prop $ isWarning (readDollarVariable >> string "[@]") "$arr[@]"
-- >>> prop $ isWarning (readDollarVariable >> string "[f") "$arr[f"
readDollarVariable :: Monad m => SCParser m Token readDollarVariable :: Monad m => SCParser m Token
readDollarVariable = do readDollarVariable = do
start <- startSpan start <- startSpan
@ -1678,25 +1700,26 @@ readDollarLonely = do
n <- lookAhead (anyChar <|> (eof >> return '_')) n <- lookAhead (anyChar <|> (eof >> return '_'))
return $ T_Literal id "$" return $ T_Literal id "$"
prop_readHereDoc = isOk readScript "cat << foo\nlol\ncow\nfoo" -- |
prop_readHereDoc2 = isNotOk readScript "cat <<- EOF\n cow\n EOF" -- >>> prop $ isOk readScript "cat << foo\nlol\ncow\nfoo"
prop_readHereDoc3 = isOk readScript "cat << foo\n$\"\nfoo" -- >>> prop $ isNotOk readScript "cat <<- EOF\n cow\n EOF"
prop_readHereDoc4 = isNotOk readScript "cat << foo\n`\nfoo" -- >>> prop $ isOk readScript "cat << foo\n$\"\nfoo"
prop_readHereDoc5 = isOk readScript "cat <<- !foo\nbar\n!foo" -- >>> prop $ isNotOk readScript "cat << foo\n`\nfoo"
prop_readHereDoc6 = isOk readScript "cat << foo\\ bar\ncow\nfoo bar" -- >>> prop $ isOk readScript "cat <<- !foo\nbar\n!foo"
prop_readHereDoc7 = isOk readScript "cat << foo\n\\$(f ())\nfoo" -- >>> prop $ isOk readScript "cat << foo\\ bar\ncow\nfoo bar"
prop_readHereDoc8 = isOk readScript "cat <<foo>>bar\netc\nfoo" -- >>> prop $ isOk readScript "cat << foo\n\\$(f ())\nfoo"
prop_readHereDoc9 = isOk readScript "if true; then cat << foo; fi\nbar\nfoo\n" -- >>> prop $ isOk readScript "cat <<foo>>bar\netc\nfoo"
prop_readHereDoc10= isOk readScript "if true; then cat << foo << bar; fi\nfoo\nbar\n" -- >>> prop $ isOk readScript "if true; then cat << foo; fi\nbar\nfoo\n"
prop_readHereDoc11= isOk readScript "cat << foo $(\nfoo\n)lol\nfoo\n" -- >>> prop $ isOk readScript "if true; then cat << foo << bar; fi\nfoo\nbar\n"
prop_readHereDoc12= isOk readScript "cat << foo|cat\nbar\nfoo" -- >>> prop $ isOk readScript "cat << foo $(\nfoo\n)lol\nfoo\n"
prop_readHereDoc13= isOk readScript "cat <<'#!'\nHello World\n#!\necho Done" -- >>> prop $ isOk readScript "cat << foo|cat\nbar\nfoo"
prop_readHereDoc14= isWarning readScript "cat << foo\nbar\nfoo \n" -- >>> prop $ isOk readScript "cat <<'#!'\nHello World\n#!\necho Done"
prop_readHereDoc15= isWarning readScript "cat <<foo\nbar\nfoo bar\nfoo" -- >>> prop $ isWarning readScript "cat << foo\nbar\nfoo \n"
prop_readHereDoc16= isOk readScript "cat <<- ' foo'\nbar\n foo\n" -- >>> prop $ isWarning readScript "cat <<foo\nbar\nfoo bar\nfoo"
prop_readHereDoc17= isWarning readScript "cat <<- ' foo'\nbar\n foo\n foo\n" -- >>> prop $ isOk readScript "cat <<- ' foo'\nbar\n foo\n"
prop_readHereDoc20= isWarning readScript "cat << foo\n foo\n()\nfoo\n" -- >>> prop $ isWarning readScript "cat <<- ' foo'\nbar\n foo\n foo\n"
prop_readHereDoc21= isOk readScript "# shellcheck disable=SC1039\ncat << foo\n foo\n()\nfoo\n" -- >>> prop $ isWarning readScript "cat << foo\n foo\n()\nfoo\n"
-- >>> prop $ isOk readScript "# shellcheck disable=SC1039\ncat << foo\n foo\n()\nfoo\n"
readHereDoc = called "here document" $ do readHereDoc = called "here document" $ do
pos <- getPosition pos <- getPosition
try $ string "<<" try $ string "<<"
@ -1864,7 +1887,8 @@ readIoDuplicate = try $ do
return $ str ++ dash return $ str ++ dash
prop_readIoFile = isOk readIoFile ">> \"$(date +%YYmmDD)\"" -- |
-- >>> prop $ isOk readIoFile ">> \"$(date +%YYmmDD)\""
readIoFile = called "redirection" $ do readIoFile = called "redirection" $ do
start <- startSpan start <- startSpan
op <- readIoFileOp op <- readIoFileOp
@ -1884,13 +1908,14 @@ readIoSource = try $ do
lookAhead $ void readIoFileOp <|> void (string "<<") lookAhead $ void readIoFileOp <|> void (string "<<")
return x return x
prop_readIoRedirect = isOk readIoRedirect "3>&2" -- |
prop_readIoRedirect2 = isOk readIoRedirect "2> lol" -- >>> prop $ isOk readIoRedirect "3>&2"
prop_readIoRedirect3 = isOk readIoRedirect "4>&-" -- >>> prop $ isOk readIoRedirect "2> lol"
prop_readIoRedirect4 = isOk readIoRedirect "&> lol" -- >>> prop $ isOk readIoRedirect "4>&-"
prop_readIoRedirect5 = isOk readIoRedirect "{foo}>&2" -- >>> prop $ isOk readIoRedirect "&> lol"
prop_readIoRedirect6 = isOk readIoRedirect "{foo}<&-" -- >>> prop $ isOk readIoRedirect "{foo}>&2"
prop_readIoRedirect7 = isOk readIoRedirect "{foo}>&1-" -- >>> prop $ isOk readIoRedirect "{foo}<&-"
-- >>> prop $ isOk readIoRedirect "{foo}>&1-"
readIoRedirect = do readIoRedirect = do
start <- startSpan start <- startSpan
n <- readIoSource n <- readIoSource
@ -1902,7 +1927,8 @@ readIoRedirect = do
readRedirectList = many1 readIoRedirect readRedirectList = many1 readIoRedirect
prop_readHereString = isOk readHereString "<<< \"Hello $world\"" -- |
-- >>> prop $ isOk readHereString "<<< \"Hello $world\""
readHereString = called "here string" $ do readHereString = called "here string" $ do
start <- startSpan start <- startSpan
try $ string "<<<" try $ string "<<<"
@ -1921,11 +1947,12 @@ readNewlineList =
"Unexpected start of line. If breaking lines, |/||/&& should be at the end of the previous one." "Unexpected start of line. If breaking lines, |/||/&& should be at the end of the previous one."
readLineBreak = optional readNewlineList readLineBreak = optional readNewlineList
prop_readSeparator1 = isWarning readScript "a &; b" -- |
prop_readSeparator2 = isOk readScript "a & b" -- >>> prop $ isWarning readScript "a &; b"
prop_readSeparator3 = isWarning readScript "a &amp; b" -- >>> prop $ isOk readScript "a & b"
prop_readSeparator4 = isWarning readScript "a &gt; file; b" -- >>> prop $ isWarning readScript "a &amp; b"
prop_readSeparator5 = isWarning readScript "curl https://example.com/?foo=moo&bar=cow" -- >>> prop $ isWarning readScript "a &gt; file; b"
-- >>> prop $ isWarning readScript "curl https://example.com/?foo=moo&bar=cow"
readSeparatorOp = do readSeparatorOp = do
notFollowedBy2 (void g_AND_IF <|> void readCaseSeparator) notFollowedBy2 (void g_AND_IF <|> void readCaseSeparator)
notFollowedBy2 (string "&>") notFollowedBy2 (string "&>")
@ -1969,20 +1996,21 @@ readSeparator =
end <- getPosition end <- getPosition
return ('\n', (start, end)) return ('\n', (start, end))
prop_readSimpleCommand = isOk readSimpleCommand "echo test > file" -- |
prop_readSimpleCommand2 = isOk readSimpleCommand "cmd &> file" -- >>> prop $ isOk readSimpleCommand "echo test > file"
prop_readSimpleCommand3 = isOk readSimpleCommand "export foo=(bar baz)" -- >>> prop $ isOk readSimpleCommand "cmd &> file"
prop_readSimpleCommand4 = isOk readSimpleCommand "typeset -a foo=(lol)" -- >>> prop $ isOk readSimpleCommand "export foo=(bar baz)"
prop_readSimpleCommand5 = isOk readSimpleCommand "time if true; then echo foo; fi" -- >>> prop $ isOk readSimpleCommand "typeset -a foo=(lol)"
prop_readSimpleCommand6 = isOk readSimpleCommand "time -p ( ls -l; )" -- >>> prop $ isOk readSimpleCommand "time if true; then echo foo; fi"
prop_readSimpleCommand7 = isOk readSimpleCommand "\\ls" -- >>> prop $ isOk readSimpleCommand "time -p ( ls -l; )"
prop_readSimpleCommand8 = isWarning readSimpleCommand "// Lol" -- >>> prop $ isOk readSimpleCommand "\\ls"
prop_readSimpleCommand9 = isWarning readSimpleCommand "/* Lolbert */" -- >>> prop $ isWarning readSimpleCommand "// Lol"
prop_readSimpleCommand10 = isWarning readSimpleCommand "/**** Lolbert */" -- >>> prop $ isWarning readSimpleCommand "/* Lolbert */"
prop_readSimpleCommand11 = isOk readSimpleCommand "/\\* foo" -- >>> prop $ isWarning readSimpleCommand "/**** Lolbert */"
prop_readSimpleCommand12 = isWarning readSimpleCommand "elsif foo" -- >>> prop $ isOk readSimpleCommand "/\\* foo"
prop_readSimpleCommand13 = isWarning readSimpleCommand "ElseIf foo" -- >>> prop $ isWarning readSimpleCommand "elsif foo"
prop_readSimpleCommand14 = isWarning readSimpleCommand "elseif[$i==2]" -- >>> prop $ isWarning readSimpleCommand "ElseIf foo"
-- >>> prop $ isWarning readSimpleCommand "elseif[$i==2]"
readSimpleCommand = called "simple command" $ do readSimpleCommand = called "simple command" $ do
prefix <- option [] readCmdPrefix prefix <- option [] readCmdPrefix
skipAnnotationAndWarn skipAnnotationAndWarn
@ -2108,9 +2136,10 @@ readSource t@(T_Redirecting _ _ (T_SimpleCommand cmdId _ (cmd:file:_))) = do
readSource t = return t readSource t = return t
prop_readPipeline = isOk readPipeline "! cat /etc/issue | grep -i ubuntu" -- |
prop_readPipeline2 = isWarning readPipeline "!cat /etc/issue | grep -i ubuntu" -- >>> prop $ isOk readPipeline "! cat /etc/issue | grep -i ubuntu"
prop_readPipeline3 = isOk readPipeline "for f; do :; done|cat" -- >>> prop $ isWarning readPipeline "!cat /etc/issue | grep -i ubuntu"
-- >>> prop $ isOk readPipeline "for f; do :; done|cat"
readPipeline = do readPipeline = do
unexpecting "keyword/token" readKeyword unexpecting "keyword/token" readKeyword
do do
@ -2120,9 +2149,10 @@ readPipeline = do
<|> <|>
readPipeSequence readPipeSequence
prop_readAndOr = isOk readAndOr "grep -i lol foo || exit 1" -- |
prop_readAndOr1 = isOk readAndOr "# shellcheck disable=1\nfoo" -- >>> prop $ isOk readAndOr "grep -i lol foo || exit 1"
prop_readAndOr2 = isOk readAndOr "# shellcheck disable=1\n# lol\n# shellcheck disable=3\nfoo" -- >>> prop $ isOk readAndOr "# shellcheck disable=1\nfoo"
-- >>> prop $ isOk readAndOr "# shellcheck disable=1\n# lol\n# shellcheck disable=3\nfoo"
readAndOr = do readAndOr = do
start <- startSpan start <- startSpan
apos <- getPosition apos <- getPosition
@ -2150,7 +2180,8 @@ readTermOrNone = do
eof eof
return [] return []
prop_readTerm = isOk readTerm "time ( foo; bar; )" -- |
-- >>> prop $ isOk readTerm "time ( foo; bar; )"
readTerm = do readTerm = do
allspacing allspacing
m <- readAndOr m <- readAndOr
@ -2221,11 +2252,12 @@ skipAnnotationAndWarn = optional $ do
parseProblem ErrorC 1126 "Place shellcheck directives before commands, not after." parseProblem ErrorC 1126 "Place shellcheck directives before commands, not after."
readAnyComment readAnyComment
prop_readIfClause = isOk readIfClause "if false; then foo; elif true; then stuff; more stuff; else cows; fi" -- |
prop_readIfClause2 = isWarning readIfClause "if false; then; echo oo; fi" -- >>> prop $ isOk readIfClause "if false; then foo; elif true; then stuff; more stuff; else cows; fi"
prop_readIfClause3 = isWarning readIfClause "if false; then true; else; echo lol; fi" -- >>> prop $ isWarning readIfClause "if false; then; echo oo; fi"
prop_readIfClause4 = isWarning readIfClause "if false; then true; else if true; then echo lol; fi; fi" -- >>> prop $ isWarning readIfClause "if false; then true; else; echo lol; fi"
prop_readIfClause5 = isOk readIfClause "if false; then true; else\nif true; then echo lol; fi; fi" -- >>> prop $ isWarning readIfClause "if false; then true; else if true; then echo lol; fi; fi"
-- >>> prop $ isOk readIfClause "if false; then true; else\nif true; then echo lol; fi; fi"
readIfClause = called "if expression" $ do readIfClause = called "if expression" $ do
start <- startSpan start <- startSpan
pos <- getPosition pos <- getPosition
@ -2300,7 +2332,8 @@ ifNextToken parser action =
try . lookAhead $ parser try . lookAhead $ parser
action action
prop_readSubshell = isOk readSubshell "( cd /foo; tar cf stuff.tar * )" -- |
-- >>> prop $ isOk readSubshell "( cd /foo; tar cf stuff.tar * )"
readSubshell = called "explicit subshell" $ do readSubshell = called "explicit subshell" $ do
start <- startSpan start <- startSpan
char '(' char '('
@ -2311,9 +2344,10 @@ readSubshell = called "explicit subshell" $ do
id <- endSpan start id <- endSpan start
return $ T_Subshell id list return $ T_Subshell id list
prop_readBraceGroup = isOk readBraceGroup "{ a; b | c | d; e; }" -- |
prop_readBraceGroup2 = isWarning readBraceGroup "{foo;}" -- >>> prop $ isOk readBraceGroup "{ a; b | c | d; e; }"
prop_readBraceGroup3 = isOk readBraceGroup "{(foo)}" -- >>> prop $ isWarning readBraceGroup "{foo;}"
-- >>> prop $ isOk readBraceGroup "{(foo)}"
readBraceGroup = called "brace group" $ do readBraceGroup = called "brace group" $ do
start <- startSpan start <- startSpan
char '{' char '{'
@ -2331,7 +2365,8 @@ readBraceGroup = called "brace group" $ do
id <- endSpan start id <- endSpan start
return $ T_BraceGroup id list return $ T_BraceGroup id list
prop_readWhileClause = isOk readWhileClause "while [[ -e foo ]]; do sleep 1; done" -- |
-- >>> prop $ isOk readWhileClause "while [[ -e foo ]]; do sleep 1; done"
readWhileClause = called "while loop" $ do readWhileClause = called "while loop" $ do
start <- startSpan start <- startSpan
kwId <- getId <$> g_While kwId <- getId <$> g_While
@ -2340,7 +2375,8 @@ readWhileClause = called "while loop" $ do
id <- endSpan start id <- endSpan start
return $ T_WhileExpression id condition statements return $ T_WhileExpression id condition statements
prop_readUntilClause = isOk readUntilClause "until kill -0 $PID; do sleep 1; done" -- |
-- >>> prop $ isOk readUntilClause "until kill -0 $PID; do sleep 1; done"
readUntilClause = called "until loop" $ do readUntilClause = called "until loop" $ do
start <- startSpan start <- startSpan
kwId <- getId <$> g_Until kwId <- getId <$> g_Until
@ -2373,17 +2409,18 @@ readDoGroup kwId = do
return commands return commands
prop_readForClause = isOk readForClause "for f in *; do rm \"$f\"; done" -- |
prop_readForClause3 = isOk readForClause "for f; do foo; done" -- >>> prop $ isOk readForClause "for f in *; do rm \"$f\"; done"
prop_readForClause4 = isOk readForClause "for((i=0; i<10; i++)); do echo $i; done" -- >>> prop $ isOk readForClause "for f; do foo; done"
prop_readForClause5 = isOk readForClause "for ((i=0;i<10 && n>x;i++,--n))\ndo \necho $i\ndone" -- >>> prop $ isOk readForClause "for((i=0; i<10; i++)); do echo $i; done"
prop_readForClause6 = isOk readForClause "for ((;;))\ndo echo $i\ndone" -- >>> prop $ isOk readForClause "for ((i=0;i<10 && n>x;i++,--n))\ndo \necho $i\ndone"
prop_readForClause7 = isOk readForClause "for ((;;)) do echo $i\ndone" -- >>> prop $ isOk readForClause "for ((;;))\ndo echo $i\ndone"
prop_readForClause8 = isOk readForClause "for ((;;)) ; do echo $i\ndone" -- >>> prop $ isOk readForClause "for ((;;)) do echo $i\ndone"
prop_readForClause9 = isOk readForClause "for i do true; done" -- >>> prop $ isOk readForClause "for ((;;)) ; do echo $i\ndone"
prop_readForClause10= isOk readForClause "for ((;;)) { true; }" -- >>> prop $ isOk readForClause "for i do true; done"
prop_readForClause12= isWarning readForClause "for $a in *; do echo \"$a\"; done" -- >>> prop $ isOk readForClause "for ((;;)) { true; }"
prop_readForClause13= isOk readForClause "for foo\nin\\\n bar\\\n baz\ndo true; done" -- >>> prop $ isWarning readForClause "for $a in *; do echo \"$a\"; done"
-- >>> prop $ isOk readForClause "for foo\nin\\\n bar\\\n baz\ndo true; done"
readForClause = called "for loop" $ do readForClause = called "for loop" $ do
pos <- getPosition pos <- getPosition
(T_For id) <- g_For (T_For id) <- g_For
@ -2416,8 +2453,9 @@ readForClause = called "for loop" $ do
group <- readDoGroup id group <- readDoGroup id
return $ T_ForIn id name values group return $ T_ForIn id name values group
prop_readSelectClause1 = isOk readSelectClause "select foo in *; do echo $foo; done" -- |
prop_readSelectClause2 = isOk readSelectClause "select foo; do echo $foo; done" -- >>> prop $ isOk readSelectClause "select foo in *; do echo $foo; done"
-- >>> prop $ isOk readSelectClause "select foo; do echo $foo; done"
readSelectClause = called "select loop" $ do readSelectClause = called "select loop" $ do
(T_Select id) <- g_Select (T_Select id) <- g_Select
spacing spacing
@ -2446,11 +2484,12 @@ readInClause = do
return things return things
prop_readCaseClause = isOk readCaseClause "case foo in a ) lol; cow;; b|d) fooo; esac" -- |
prop_readCaseClause2 = isOk readCaseClause "case foo\n in * ) echo bar;; esac" -- >>> prop $ isOk readCaseClause "case foo in a ) lol; cow;; b|d) fooo; esac"
prop_readCaseClause3 = isOk readCaseClause "case foo\n in * ) echo bar & ;; esac" -- >>> prop $ isOk readCaseClause "case foo\n in * ) echo bar;; esac"
prop_readCaseClause4 = isOk readCaseClause "case foo\n in *) echo bar ;& bar) foo; esac" -- >>> prop $ isOk readCaseClause "case foo\n in * ) echo bar & ;; esac"
prop_readCaseClause5 = isOk readCaseClause "case foo\n in *) echo bar;;& foo) baz;; esac" -- >>> prop $ isOk readCaseClause "case foo\n in *) echo bar ;& bar) foo; esac"
-- >>> prop $ isOk readCaseClause "case foo\n in *) echo bar;;& foo) baz;; esac"
readCaseClause = called "case expression" $ do readCaseClause = called "case expression" $ do
start <- startSpan start <- startSpan
g_Case g_Case
@ -2494,18 +2533,19 @@ readCaseSeparator = choice [
lookAhead (readLineBreak >> g_Esac) >> return CaseBreak lookAhead (readLineBreak >> g_Esac) >> return CaseBreak
] ]
prop_readFunctionDefinition = isOk readFunctionDefinition "foo() { command foo --lol \"$@\"; }" -- |
prop_readFunctionDefinition1 = isOk readFunctionDefinition "foo (){ command foo --lol \"$@\"; }" -- >>> prop $ isOk readFunctionDefinition "foo() { command foo --lol \"$@\"; }"
prop_readFunctionDefinition4 = isWarning readFunctionDefinition "foo(a, b) { true; }" -- >>> prop $ isOk readFunctionDefinition "foo (){ command foo --lol \"$@\"; }"
prop_readFunctionDefinition5 = isOk readFunctionDefinition ":(){ :|:;}" -- >>> prop $ isWarning readFunctionDefinition "foo(a, b) { true; }"
prop_readFunctionDefinition6 = isOk readFunctionDefinition "?(){ foo; }" -- >>> prop $ isOk readFunctionDefinition ":(){ :|:;}"
prop_readFunctionDefinition7 = isOk readFunctionDefinition "..(){ cd ..; }" -- >>> prop $ isOk readFunctionDefinition "?(){ foo; }"
prop_readFunctionDefinition8 = isOk readFunctionDefinition "foo() (ls)" -- >>> prop $ isOk readFunctionDefinition "..(){ cd ..; }"
prop_readFunctionDefinition9 = isOk readFunctionDefinition "function foo { true; }" -- >>> prop $ isOk readFunctionDefinition "foo() (ls)"
prop_readFunctionDefinition10= isOk readFunctionDefinition "function foo () { true; }" -- >>> prop $ isOk readFunctionDefinition "function foo { true; }"
prop_readFunctionDefinition11= isWarning readFunctionDefinition "function foo{\ntrue\n}" -- >>> prop $ isOk readFunctionDefinition "function foo () { true; }"
prop_readFunctionDefinition12= isOk readFunctionDefinition "function []!() { true; }" -- >>> prop $ isWarning readFunctionDefinition "function foo{\ntrue\n}"
prop_readFunctionDefinition13= isOk readFunctionDefinition "@require(){ true; }" -- >>> prop $ isOk readFunctionDefinition "function []!() { true; }"
-- >>> prop $ isOk readFunctionDefinition "@require(){ true; }"
readFunctionDefinition = called "function" $ do readFunctionDefinition = called "function" $ do
start <- startSpan start <- startSpan
functionSignature <- try readFunctionSignature functionSignature <- try readFunctionSignature
@ -2547,9 +2587,10 @@ readFunctionDefinition = called "function" $ do
g_Rparen g_Rparen
return () return ()
prop_readCoProc1 = isOk readCoProc "coproc foo { echo bar; }" -- |
prop_readCoProc2 = isOk readCoProc "coproc { echo bar; }" -- >>> prop $ isOk readCoProc "coproc foo { echo bar; }"
prop_readCoProc3 = isOk readCoProc "coproc echo bar" -- >>> prop $ isOk readCoProc "coproc { echo bar; }"
-- >>> prop $ isOk readCoProc "coproc echo bar"
readCoProc = called "coproc" $ do readCoProc = called "coproc" $ do
start <- startSpan start <- startSpan
try $ do try $ do
@ -2576,7 +2617,8 @@ readCoProc = called "coproc" $ do
readPattern = (readNormalWord `thenSkip` spacing) `sepBy1` (char '|' `thenSkip` spacing) readPattern = (readNormalWord `thenSkip` spacing) `sepBy1` (char '|' `thenSkip` spacing)
prop_readCompoundCommand = isOk readCompoundCommand "{ echo foo; }>/dev/null" -- |
-- >>> prop $ isOk readCompoundCommand "{ echo foo; }>/dev/null"
readCompoundCommand = do readCompoundCommand = do
cmd <- choice [ cmd <- choice [
readBraceGroup, readBraceGroup,
@ -2668,24 +2710,26 @@ readLiteralForParser parser = do
id <- endSpan start id <- endSpan start
return $ T_Literal id str return $ T_Literal id str
prop_readAssignmentWord = isOk readAssignmentWord "a=42" -- |
prop_readAssignmentWord2 = isOk readAssignmentWord "b=(1 2 3)" -- >>> prop $ isOk readAssignmentWord "a=42"
prop_readAssignmentWord3 = isWarning readAssignmentWord "$b = 13" -- >>> prop $ isOk readAssignmentWord "b=(1 2 3)"
prop_readAssignmentWord4 = isWarning readAssignmentWord "b = $(lol)" -- >>> prop $ isWarning readAssignmentWord "$b = 13"
prop_readAssignmentWord5 = isOk readAssignmentWord "b+=lol" -- >>> prop $ isWarning readAssignmentWord "b = $(lol)"
prop_readAssignmentWord6 = isWarning readAssignmentWord "b += (1 2 3)" -- >>> prop $ isOk readAssignmentWord "b+=lol"
prop_readAssignmentWord7 = isOk readAssignmentWord "a[3$n'']=42" -- >>> prop $ isWarning readAssignmentWord "b += (1 2 3)"
prop_readAssignmentWord8 = isOk readAssignmentWord "a[4''$(cat foo)]=42" -- >>> prop $ isOk readAssignmentWord "a[3$n'']=42"
prop_readAssignmentWord9 = isOk readAssignmentWord "IFS= " -- >>> prop $ isOk readAssignmentWord "a[4''$(cat foo)]=42"
prop_readAssignmentWord9a= isOk readAssignmentWord "foo=" -- >>> prop $ isOk readAssignmentWord "IFS= "
prop_readAssignmentWord9b= isOk readAssignmentWord "foo= " -- >>> prop $ isOk readAssignmentWord "foo="
prop_readAssignmentWord9c= isOk readAssignmentWord "foo= #bar" -- >>> prop $ isOk readAssignmentWord "foo= "
prop_readAssignmentWord10= isWarning readAssignmentWord "foo$n=42" -- >>> prop $ isOk readAssignmentWord "foo= #bar"
prop_readAssignmentWord11= isOk readAssignmentWord "foo=([a]=b [c] [d]= [e f )" -- >>> prop $ isWarning readAssignmentWord "foo$n=42"
prop_readAssignmentWord12= isOk readAssignmentWord "a[b <<= 3 + c]='thing'" -- >>> prop $ isOk readAssignmentWord "foo=([a]=b [c] [d]= [e f )"
prop_readAssignmentWord13= isOk readAssignmentWord "var=( (1 2) (3 4) )" -- >>> prop $ isOk readAssignmentWord "a[b <<= 3 + c]='thing'"
prop_readAssignmentWord14= isOk readAssignmentWord "var=( 1 [2]=(3 4) )" -- >>> prop $ isOk readAssignmentWord "var=( (1 2) (3 4) )"
prop_readAssignmentWord15= isOk readAssignmentWord "var=(1 [2]=(3 4))" -- >>> prop $ isOk readAssignmentWord "var=( 1 [2]=(3 4) )"
-- >>> prop $ isOk readAssignmentWord "var=(1 [2]=(3 4))"
readAssignmentWord = readAssignmentWordExt True readAssignmentWord = readAssignmentWordExt True
readWellFormedAssignment = readAssignmentWordExt False readWellFormedAssignment = readAssignmentWordExt False
readAssignmentWordExt lenient = try $ do readAssignmentWordExt lenient = try $ do
@ -2879,13 +2923,14 @@ readKeyword = choice [ g_Then, g_Else, g_Elif, g_Fi, g_Do, g_Done, g_Esac, g_Rbr
ifParse p t f = ifParse p t f =
(lookAhead (try p) >> t) <|> f (lookAhead (try p) >> t) <|> f
prop_readShebang1 = isOk readShebang "#!/bin/sh\n" -- |
prop_readShebang2 = isWarning readShebang "!# /bin/sh\n" -- >>> prop $ isOk readShebang "#!/bin/sh\n"
prop_readShebang3 = isNotOk readShebang "#shellcheck shell=/bin/sh\n" -- >>> prop $ isWarning readShebang "!# /bin/sh\n"
prop_readShebang4 = isWarning readShebang "! /bin/sh" -- >>> prop $ isNotOk readShebang "#shellcheck shell=/bin/sh\n"
prop_readShebang5 = isWarning readShebang "\n#!/bin/sh" -- >>> prop $ isWarning readShebang "! /bin/sh"
prop_readShebang6 = isWarning readShebang " # Copyright \n!#/bin/bash" -- >>> prop $ isWarning readShebang "\n#!/bin/sh"
prop_readShebang7 = isNotOk readShebang "# Copyright \nfoo\n#!/bin/bash" -- >>> prop $ isWarning readShebang " # Copyright \n!#/bin/bash"
-- >>> prop $ isNotOk readShebang "# Copyright \nfoo\n#!/bin/bash"
readShebang = do readShebang = do
anyShebang <|> try readMissingBang <|> withHeader anyShebang <|> try readMissingBang <|> withHeader
many linewhitespace many linewhitespace
@ -2968,11 +3013,12 @@ verifyEof = eof <|> choice [
try (lookAhead p) try (lookAhead p)
action action
prop_readScript1 = isOk readScriptFile "#!/bin/bash\necho hello world\n" -- |
prop_readScript2 = isWarning readScriptFile "#!/bin/bash\r\necho hello world\n" -- >>> prop $ isOk readScriptFile "#!/bin/bash\necho hello world\n"
prop_readScript3 = isWarning readScriptFile "#!/bin/bash\necho hello\xA0world" -- >>> prop $ isWarning readScriptFile "#!/bin/bash\r\necho hello world\n"
prop_readScript4 = isWarning readScriptFile "#!/usr/bin/perl\nfoo=(" -- >>> prop $ isWarning readScriptFile "#!/bin/bash\necho hello\xA0world"
prop_readScript5 = isOk readScriptFile "#!/bin/bash\n#This is an empty script\n\n" -- >>> prop $ isWarning readScriptFile "#!/usr/bin/perl\nfoo=("
-- >>> prop $ isOk readScriptFile "#!/bin/bash\n#This is an empty script\n\n"
readScriptFile = do readScriptFile = do
start <- startSpan start <- startSpan
pos <- getPosition pos <- getPosition
@ -3295,7 +3341,3 @@ tryWithErrors parser = do
endInput <- getInput endInput <- getInput
endState <- getState endState <- getState
return (result, endPos, endInput, endState) return (result, endPos, endInput, endState)
return []
runTests = $quickCheckAll

View file

@ -1,35 +1,3 @@
# This file was automatically generated by stack init resolver: lts-12.9
# For more information, see: https://docs.haskellstack.org/en/stable/yaml_configuration/
# Specifies the GHC version and set of packages available (e.g., lts-3.5, nightly-2015-09-21, ghc-7.10.2)
resolver: lts-8.5
# Local packages, usually specified by relative directory name
packages: packages:
- '.' - '.'
# Packages to be pulled from upstream that are not in the resolver (e.g., acme-missiles-0.3)
extra-deps: []
# Override default flag values for local packages and extra-deps
flags: {}
# Extra package databases containing global packages
extra-package-dbs: []
# Control whether we use the GHC we find on the path
# system-ghc: true
# Require a specific version of stack, using version ranges
# require-stack-version: -any # Default
# require-stack-version: >= 1.0.0
# Override the architecture used by stack, especially useful on Windows
# arch: i386
# arch: x86_64
# Extra directories used by stack for building
# extra-include-dirs: [/path/to/dir]
# extra-lib-dirs: [/path/to/dir]
# Allow a newer minor version of GHC than the snapshot specifies
# compiler-check: newer-minor

View file

@ -1,78 +1,2 @@
#!/usr/bin/env bash #!/usr/bin/env bash
# This file strips all unit tests from ShellCheck, removing # This file was deprecated by the doctest build.
# the dependency on QuickCheck and Template Haskell and
# reduces the binary size considerably.
set -o pipefail
sponge() {
local data
data="$(cat)"
printf '%s\n' "$data" > "$1"
}
modify() {
if ! "${@:2}" < "$1" | sponge "$1"
then
{
printf 'Failed to modify %s: ' "$1"
printf '%q ' "${@:2}"
printf '\n'
} >&2
exit 1
fi
}
detestify() {
printf '%s\n' '-- AUTOGENERATED from ShellCheck by striptests. Do not modify.'
awk '
BEGIN {
state = 0;
}
/LANGUAGE TemplateHaskell/ { next; }
/^import.*Test\./ { next; }
/^module/ {
sub(/,[^,)]*runTests/, "");
}
# Delete tests
/^prop_/ { state = 1; next; }
# ..and any blank lines following them.
state == 1 && /^ / { next; }
# Template Haskell marker
/^return / {
exit;
}
{ state = 0; print; }
'
}
if [[ ! -e 'ShellCheck.cabal' ]]
then
echo "Run me from the ShellCheck directory." >&2
exit 1
fi
if [[ -d '.git' ]] && ! git diff --exit-code > /dev/null 2>&1
then
echo "You have local changes! These may be overwritten." >&2
exit 2
fi
modify 'ShellCheck.cabal' sed -e '
/QuickCheck/d
/^test-suite/{ s/.*//; q; }
'
find . -name '.git' -prune -o -type f -name '*.hs' -print |
while IFS= read -r file
do
modify "$file" detestify
done

12
test/doctests.hs Normal file
View file

@ -0,0 +1,12 @@
module Main where
import Build_doctests (flags, pkgs, module_sources)
import Data.Foldable (traverse_)
import Test.DocTest (doctest)
main :: IO ()
main = do
traverse_ putStrLn args
doctest args
where
args = flags ++ pkgs ++ module_sources

View file

@ -1,24 +0,0 @@
module Main where
import Control.Monad
import System.Exit
import qualified ShellCheck.Checker
import qualified ShellCheck.Analytics
import qualified ShellCheck.AnalyzerLib
import qualified ShellCheck.Parser
import qualified ShellCheck.Checks.Commands
import qualified ShellCheck.Checks.ShellSupport
main = do
putStrLn "Running ShellCheck tests..."
results <- sequence [
ShellCheck.Checker.runTests,
ShellCheck.Checks.Commands.runTests,
ShellCheck.Checks.ShellSupport.runTests,
ShellCheck.Analytics.runTests,
ShellCheck.AnalyzerLib.runTests,
ShellCheck.Parser.runTests
]
if and results
then exitSuccess
else exitFailure