5 Commits

Author SHA1 Message Date
Vidar Holen
eb597baa7f Improve Fix memory usage 2018-10-22 19:39:24 -07:00
Vidar Holen
fa8c2a0fee Minor renaming and output fixes 2018-10-22 18:41:36 -07:00
Ng Zhi An
279cffd114 Change definition of Replacement, add ToJSON instance for it 2018-10-21 22:25:21 -07:00
Ng Zhi An
01fd944168 Expose token positions in params, use that to construct fixes 2018-10-21 22:25:21 -07:00
Ng Zhi An
2778d658bf Prototype fix 2018-10-21 22:25:21 -07:00
24 changed files with 1703 additions and 1956 deletions

View File

@@ -1,7 +1,7 @@
#### For bugs
- Rule Id (if any, e.g. SC1000):
- My shellcheck version (`shellcheck --version` or "online"):
- [ ] The rule's wiki page does not already cover this (e.g. https://shellcheck.net/wiki/SC2086)
- [ ] I read the issue's wiki page, e.g. https://github.com/koalaman/shellcheck/wiki/SC2086
- [ ] I tried on shellcheck.net and verified that this is still a problem on the latest commit
#### For new checks and feature suggestions

3
.gitignore vendored
View File

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

View File

@@ -1,14 +0,0 @@
# In 2015, cabal-install had a http bug triggered when proxies didn't keep
# the connection open. This version made it into Ubuntu Xenial as used by
# Snapcraft. In June 2018, Snapcraft's proxy started triggering this bug.
#
# https://bugs.launchpad.net/launchpad-buildd/+bug/1797809
#
# Workaround: add more proxy
visible_hostname localhost
http_port 8888
cache_peer 10.10.10.1 parent 8222 0 no-query default
cache_peer_domain localhost !.internal
http_access allow all

View File

@@ -1,30 +1,17 @@
## Since previous release
### Added
- Preliminary support for fix suggestions
## v0.6.0 - 2018-12-02
## ???
### Added
- Command line option --severity/-S for filtering by minimum severity
- Command line option --wiki-link-count/-W for showing wiki links
- SC2152/SC2151: Warn about bad `exit` values like `1234` and `"foo"`
- SC2236/SC2237: Suggest -n/-z instead of ! -z/-n
- SC2238: Warn when redirecting to a known command name, e.g. ls > rm
- SC2239: Warn if the shebang is not an absolute path, e.g. #!bin/sh
- SC2240: Warn when passing additional arguments to dot (.) in sh/dash
- SC1133: Better diagnostics when starting a line with |/||/&&
### Changed
- Most warnings now have useful end positions
- SC1117 about unknown double-quoted escape sequences has been retired
### Fixed
- SC2021 no longer triggers for equivalence classes like `[=e=]`
- SC2021 no longer triggers for equivalence classes like '[=e=]'
- SC2221/SC2222 no longer mistriggers on fall-through case branches
- SC2081 about glob matches in `[ .. ]` now also triggers for `!=`
- SC2086 no longer warns about spaces in `$#`
- SC2164 no longer suggests subshells for `cd ..; cmd; cd ..`
- `read -a` is now correctly considered an array assignment
- SC2039 no longer warns about LINENO now that it's POSIX
## v0.5.0 - 2018-05-31
### Added

View File

@@ -1,55 +1,22 @@
# Build-only image
FROM ubuntu:18.04 AS build
FROM ubuntu:17.10 AS build
USER root
WORKDIR /opt/shellCheck
# Install OS deps, including GHC from HVR-PPA
# 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 OS deps
RUN apt-get update && apt-get install -y ghc cabal-install
# Install Haskell deps
# (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 ./
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
RUN cabal update && cabal install --dependencies-only --ghc-options="-optlo-Os -split-sections"
# Copy source and build it
COPY LICENSE Setup.hs shellcheck.hs shellcheck.1.md ./
COPY LICENSE Setup.hs shellcheck.hs ./
COPY src src
COPY test test
# This SED is the only "nastyness" we have to do
# 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 cabal build Paths_ShellCheck && \
ghc -optl-static -optl-pthread -isrc -idist/build/autogen --make shellcheck -split-sections -optc-Wl,--gc-sections -optlo-Os && \
strip --strip-all shellcheck
RUN mkdir -p /out/bin && \
cp shellcheck /out/bin/

View File

@@ -133,10 +133,6 @@ On OS X with homebrew:
brew install shellcheck
On OpenBSD:
pkg_add shellcheck
On openSUSE
zypper in ShellCheck
@@ -172,11 +168,6 @@ Alternatively, you can download pre-compiled binaries for the latest release her
or see the [storage bucket listing](https://shellcheck.storage.googleapis.com/index.html) for checksums, older versions and the latest daily builds.
Distro packages already come with a `man` page. If you are building from source, it can be installed with:
pandoc -s -t man shellcheck.1.md -o shellcheck.1
sudo mv shellcheck.1 /usr/share/man/man1
## Travis CI
Travis CI has now integrated ShellCheck by default, so you don't need to manually install it.

View File

@@ -1,8 +1,3 @@
{-# LANGUAGE CPP #-}
{-# OPTIONS_GHC -Wall #-}
module Main (main) where
import Distribution.PackageDescription (
HookedBuildInfo,
emptyHookedBuildInfo )
@@ -14,42 +9,12 @@ import Distribution.Simple (
import Distribution.Simple.Setup ( SDistFlags )
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
where
myHooks = simpleUserHooks { preSDist = myPreSDist }
#endif
-- | 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
-- command is not found, this will fail with an error message:
@@ -62,20 +27,10 @@ main = defaultMainWithHooks myHooks
--
myPreSDist :: Args -> SDistFlags -> IO HookedBuildInfo
myPreSDist _ _ = do
exists <- doesFileExist "shellcheck.1"
if exists
then do
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
putStrLn "Building the man page (shellcheck.1) with pandoc..."
putStrLn pandoc_cmd
result <- system pandoc_cmd
putStrLn $ "pandoc exited with " ++ show result
return emptyHookedBuildInfo
where
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

@@ -1,5 +1,5 @@
Name: ShellCheck
Version: 0.6.0
Version: 0.5.0
Synopsis: Shell script analysis tool
License: GPL-3
License-file: LICENSE
@@ -28,14 +28,14 @@ Extra-Source-Files:
shellcheck.1.md
-- built with a cabal sdist hook
shellcheck.1
-- tests
test/shellcheck.hs
custom-setup
setup-depends:
base >= 4 && <5,
directory >= 1.2 && <1.4,
process >= 1.0 && <1.7,
cabal-doctest >= 1.0.6 && <1.1,
Cabal >= 1.10 && <2.5
base >= 4 && <5,
process >= 1.0 && <1.7,
Cabal >= 1.10 && <2.5
source-repository head
type: git
@@ -58,6 +58,7 @@ library
mtl >= 2.2.1,
parsec,
regex-tdfa,
QuickCheck >= 2.7.4,
-- When cabal supports it, move this to setup-depends:
process
exposed-modules:
@@ -95,23 +96,23 @@ executable shellcheck
directory,
mtl >= 2.2.1,
parsec >= 3.0,
QuickCheck >= 2.7.4,
regex-tdfa
main-is: shellcheck.hs
-- Marker to add flags for static linking
-- STATIC
test-suite test-shellcheck
type: exitcode-stdio-1.0
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,10 +3,3 @@
# This allows testing changes without recompiling.
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,21 +1,22 @@
#!/bin/bash
# shellcheck disable=SC2091
# 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.
#!/usr/bin/env bash
# quicktest runs the ShellCheck unit tests in an interpreted mode.
# This allows running tests without compiling, which can be faster.
# 'cabal test' remains the source of truth.
$(find dist -type f -name doctests)
# Note: if you have build the project with new-build
#
# % cabal new-build -w ghc-8.4.3 --enable-tests
#
# and have cabal-plan installed (e.g. with cabal new-install cabal-plan),
# then you can quicktest with
#
# % $(cabal-plan list-bin doctests)
#
# Once the test executable exists, we can simply run it to perform doctests
# which use GHCi under the hood.
(
var=$(echo 'liftM and $ sequence [
ShellCheck.Analytics.runTests
,ShellCheck.Parser.runTests
,ShellCheck.Checker.runTests
,ShellCheck.Checks.Commands.runTests
,ShellCheck.Checks.ShellSupport.runTests
,ShellCheck.AnalyzerLib.runTests
]' | tr -d '\n' | cabal repl 2>&1 | tee /dev/stderr)
if [[ $var == *$'\nTrue'* ]]
then
exit 0
else
grep -C 3 -e "Fail" -e "Tracing" <<< "$var"
exit 1
fi
) 2>&1

View File

@@ -37,16 +37,9 @@ parts:
source: ./
build-packages:
- cabal-install
- squid3
build: |
# See comments in .snapsquid.conf
[ "$http_proxy" ] && {
squid3 -f .snapsquid.conf
export http_proxy="http://localhost:8888"
sleep 3
}
cabal sandbox init
cabal update || cat /var/log/squid/*
cabal update
cabal install -j
install: |
install -d $SNAPCRAFT_PART_INSTALL/usr/bin

File diff suppressed because it is too large Load Diff

View File

@@ -18,29 +18,30 @@
along with this program. If not, see <https://www.gnu.org/licenses/>.
-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TemplateHaskell #-}
module ShellCheck.AnalyzerLib where
import ShellCheck.AST
import ShellCheck.ASTLib
import ShellCheck.Data
import ShellCheck.Interface
import ShellCheck.Parser
import ShellCheck.Regex
import Control.Arrow (first)
import Control.DeepSeq
import Control.Monad.Identity
import Control.Monad.RWS
import Control.Monad.State
import Control.Monad.Writer
import Data.Char
import Data.List
import qualified Data.Map as Map
import Data.Maybe
import Data.Semigroup
import ShellCheck.AST
import ShellCheck.ASTLib
import ShellCheck.Data
import ShellCheck.Interface
import ShellCheck.Parser
import ShellCheck.Regex
prop :: Bool -> IO ()
prop False = putStrLn "FAIL"
prop True = return ()
import Control.Arrow (first)
import Control.DeepSeq
import Control.Monad.Identity
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 AnalyzerM a = RWS Parameters [TokenComment] Cache a
@@ -84,7 +85,7 @@ data Parameters = Parameters {
shellTypeSpecified :: Bool, -- True if shell type was forced via flags
rootNode :: Token, -- The root node of the AST
tokenPositions :: Map.Map Id (Position, Position) -- map from token id to start and end position
} deriving (Show)
}
-- TODO: Cache results of common AST ops here
data Cache = Cache {}
@@ -111,12 +112,11 @@ data DataSource =
data VariableState = Dead Token String | Alive deriving (Show)
defaultSpec pr = spec {
defaultSpec root = spec {
asShellType = Nothing,
asCheckSourced = False,
asExecutionMode = Executed,
asTokenPositions = prTokenPositions pr
} where spec = newAnalysisSpec (fromJust $ prRoot pr)
asExecutionMode = Executed
} where spec = newAnalysisSpec root
pScript s =
let
@@ -124,14 +124,13 @@ pScript s =
psFilename = "script",
psScript = s
}
in runIdentity $ parseScript (mockedSystemInterface []) pSpec
in prRoot . runIdentity $ parseScript (mockedSystemInterface []) pSpec
-- For testing. If parsed, returns whether there are any comments
producesComments :: Checker -> String -> Maybe Bool
producesComments c s = do
let pr = pScript s
prRoot pr
let spec = defaultSpec pr
root <- pScript s
let spec = defaultSpec root
let params = makeParameters spec
return . not . null $ runChecker params c
@@ -215,16 +214,16 @@ containsLastpipe root =
_ -> False
-- |
-- >>> prop $ determineShellTest "#!/bin/sh" == Sh
-- >>> prop $ determineShellTest "#!/usr/bin/env ksh" == Ksh
-- >>> prop $ determineShellTest "" == Bash
-- >>> prop $ determineShellTest "#!/bin/sh -e" == Sh
-- >>> prop $ determineShellTest "#!/bin/ksh\n#shellcheck shell=sh\nfoo" == Sh
-- >>> prop $ determineShellTest "#shellcheck shell=sh\nfoo" == Sh
-- >>> prop $ determineShellTest "#! /bin/sh" == Sh
-- >>> prop $ determineShellTest "#! /bin/ash" == Dash
determineShellTest = determineShell . fromJust . prRoot . pScript
prop_determineShell0 = determineShell (fromJust $ pScript "#!/bin/sh") == Sh
prop_determineShell1 = determineShell (fromJust $ pScript "#!/usr/bin/env ksh") == Ksh
prop_determineShell2 = determineShell (fromJust $ pScript "") == Bash
prop_determineShell3 = determineShell (fromJust $ pScript "#!/bin/sh -e") == Sh
prop_determineShell4 = determineShell (fromJust $ pScript
"#!/bin/ksh\n#shellcheck shell=sh\nfoo") == Sh
prop_determineShell5 = determineShell (fromJust $ pScript
"#shellcheck shell=sh\nfoo") == Sh
prop_determineShell6 = determineShell (fromJust $ pScript "#! /bin/sh") == Sh
prop_determineShell7 = determineShell (fromJust $ pScript "#! /bin/ash") == Dash
determineShell t = fromMaybe Bash $ do
shellString <- foldl mplus Nothing $ getCandidates t
shellForExecutable shellString
@@ -666,11 +665,10 @@ getIndexReferences s = fromMaybe [] $ do
where
re = mkRegex "(\\[.*\\])"
-- |
-- >>> prop $ getOffsetReferences ":bar" == ["bar"]
-- >>> prop $ getOffsetReferences ":bar:baz" == ["bar", "baz"]
-- >>> prop $ getOffsetReferences "[foo]:bar" == ["bar"]
-- >>> prop $ getOffsetReferences "[foo]:bar:baz" == ["bar", "baz"]
prop_getOffsetReferences1 = getOffsetReferences ":bar" == ["bar"]
prop_getOffsetReferences2 = getOffsetReferences ":bar:baz" == ["bar", "baz"]
prop_getOffsetReferences3 = getOffsetReferences "[foo]:bar" == ["bar"]
prop_getOffsetReferences4 = getOffsetReferences "[foo]:bar:baz" == ["bar", "baz"]
getOffsetReferences mods = fromMaybe [] $ do
-- if mods start with [, then drop until ]
match <- matchRegex re mods
@@ -745,15 +743,9 @@ isUnqualifiedCommand token str = isCommandMatch token (== str)
isCommandMatch token matcher = fromMaybe False $
fmap matcher (getCommandName token)
-- |
-- Does this regex look like it was intended as a glob?
--
-- >>> isConfusedGlobRegex "*foo*"
-- True
--
-- >>> isConfusedGlobRegex ".*foo.*"
-- False
--
-- True: *foo*
-- False: .*foo.*
isConfusedGlobRegex :: String -> Bool
isConfusedGlobRegex ('*':_) = True
isConfusedGlobRegex [x,'*'] | x /= '\\' = True
@@ -763,10 +755,9 @@ isVariableStartChar x = x == '_' || isAsciiLower x || isAsciiUpper x
isVariableChar x = isVariableStartChar x || isDigit x
variableNameRegex = mkRegex "[_a-zA-Z][_a-zA-Z0-9]*"
-- |
-- >>> prop $ isVariableName "_fo123"
-- >>> prop $ not $ isVariableName "4"
-- >>> prop $ not $ isVariableName "test: "
prop_isVariableName1 = isVariableName "_fo123"
prop_isVariableName2 = not $ isVariableName "4"
prop_isVariableName3 = not $ isVariableName "test: "
isVariableName (x:r) = isVariableStartChar x && all isVariableChar r
isVariableName _ = False
@@ -775,28 +766,27 @@ getVariablesFromLiteralToken token =
-- Try to get referenced variables from a literal string like "$foo"
-- Ignores tons of cases like arithmetic evaluation and array indices.
-- >>> prop $ getVariablesFromLiteral "$foo${bar//a/b}$BAZ" == ["foo", "bar", "BAZ"]
prop_getVariablesFromLiteral1 =
getVariablesFromLiteral "$foo${bar//a/b}$BAZ" == ["foo", "bar", "BAZ"]
getVariablesFromLiteral string =
map (!! 0) $ matchAllSubgroups variableRegex string
where
variableRegex = mkRegex "\\$\\{?([A-Za-z0-9_]+)"
-- |
-- Get the variable name from an expansion like ${var:-foo}
--
-- >>> prop $ getBracedReference "foo" == "foo"
-- >>> prop $ getBracedReference "#foo" == "foo"
-- >>> prop $ getBracedReference "#" == "#"
-- >>> prop $ getBracedReference "##" == "#"
-- >>> prop $ getBracedReference "#!" == "!"
-- >>> prop $ getBracedReference "!#" == "#"
-- >>> prop $ getBracedReference "!foo#?" == "foo"
-- >>> prop $ getBracedReference "foo-bar" == "foo"
-- >>> prop $ getBracedReference "foo:-bar" == "foo"
-- >>> prop $ getBracedReference "foo: -1" == "foo"
-- >>> prop $ getBracedReference "!os*" == ""
-- >>> prop $ getBracedReference "!os?bar**" == ""
-- >>> prop $ getBracedReference "foo[bar]" == "foo"
prop_getBracedReference1 = getBracedReference "foo" == "foo"
prop_getBracedReference2 = getBracedReference "#foo" == "foo"
prop_getBracedReference3 = getBracedReference "#" == "#"
prop_getBracedReference4 = getBracedReference "##" == "#"
prop_getBracedReference5 = getBracedReference "#!" == "!"
prop_getBracedReference6 = getBracedReference "!#" == "#"
prop_getBracedReference7 = getBracedReference "!foo#?" == "foo"
prop_getBracedReference8 = getBracedReference "foo-bar" == "foo"
prop_getBracedReference9 = getBracedReference "foo:-bar" == "foo"
prop_getBracedReference10= getBracedReference "foo: -1" == "foo"
prop_getBracedReference11= getBracedReference "!os*" == ""
prop_getBracedReference12= getBracedReference "!os?bar**" == ""
prop_getBracedReference13= getBracedReference "foo[bar]" == "foo"
getBracedReference s = fromMaybe s $
nameExpansion s `mplus` takeName noPrefix `mplus` getSpecial noPrefix `mplus` getSpecial s
where
@@ -819,10 +809,9 @@ getBracedReference s = fromMaybe s $
return ""
nameExpansion _ = Nothing
-- |
-- >>> prop $ getBracedModifier "foo:bar:baz" == ":bar:baz"
-- >>> prop $ getBracedModifier "!var:-foo" == ":-foo"
-- >>> prop $ getBracedModifier "foo[bar]" == "[bar]"
prop_getBracedModifier1 = getBracedModifier "foo:bar:baz" == ":bar:baz"
prop_getBracedModifier2 = getBracedModifier "!var:-foo" == ":-foo"
prop_getBracedModifier3 = getBracedModifier "foo[bar]" == "[bar]"
getBracedModifier s = fromMaybe "" . listToMaybe $ do
let var = getBracedReference s
a <- dropModifier s
@@ -839,13 +828,10 @@ getBracedModifier s = fromMaybe "" . listToMaybe $ do
-- Run an action in a Maybe (or do nothing).
-- Example:
--
-- @
-- potentially $ do
-- s <- getLiteralString cmd
-- guard $ s `elem` ["--recursive", "-r"]
-- return $ warn .. "Something something recursive"
-- @
potentially :: Monad m => Maybe (m ()) -> m ()
potentially = fromMaybe (return ())
@@ -930,3 +916,6 @@ getOpts flagTokenizer string cmd = process flags
else do
more <- process rest2
return $ (flag1, token1) : more
return []
runTests = $( [| $(forAllProperties) (quickCheckWithResult (stdArgs { maxSuccess = 1 }) ) |])

View File

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

View File

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

View File

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

View File

@@ -95,7 +95,7 @@ outputWiki errRef = do
where
showErr (_, code, msg) =
putStrLn $ " " ++ wikiLink ++ "SC" ++ show code ++ " -- " ++ shorten msg
limit = 36
limit = 40
shorten msg =
if length msg < limit
then msg
@@ -130,7 +130,8 @@ outputForFile color sys comments = do
putStrLn (color "source" line)
mapM_ (\c -> putStrLn (color (severityText c) $ cuteIndent c)) commentsForLine
putStrLn ""
showFixedString color comments lineNum line
-- FIXME: Enable when reasonably stable
-- showFixedString color comments lineNum line
) groups
hasApplicableFix lineNum comment = fromMaybe False $ do

View File

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

View File

@@ -1,3 +1,35 @@
resolver: lts-12.9
# This file was automatically generated by stack init
# 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 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,2 +1,78 @@
#!/usr/bin/env bash
# This file was deprecated by the doctest build.
# This file strips all unit tests from ShellCheck, removing
# 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

View File

@@ -16,14 +16,10 @@ and is still highly experimental.
Make sure you're plugged in and have screen/tmux in place,
then re-run with $0 --run to continue.
Also note that 'dist' will be deleted.
EOF
exit 0
}
echo "Deleting 'dist'..."
rm -rf dist
log=$(mktemp) || die "Can't create temp file"
date >> "$log" || die "Can't write to log"
@@ -67,8 +63,7 @@ opensuse:latest zypper install -y cabal-install ghc
ubuntu:18.04 apt-get update && apt-get install -y cabal-install
ubuntu:17.10 apt-get update && apt-get install -y cabal-install
# Misc Haskell including current and latest Stack build
ubuntu:18.10 set -e; apt-get update && apt-get install -y curl && curl -sSL https://get.haskellstack.org/ | sh -s - -f && cd /mnt && exec test/stacktest
# Misc
haskell:latest true
# Known to currently fail

View File

@@ -1,12 +0,0 @@
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

24
test/shellcheck.hs Normal file
View File

@@ -0,0 +1,24 @@
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

View File

@@ -1,27 +0,0 @@
#!/bin/bash
# This script builds ShellCheck through `stack` using
# various resolvers. It's run via distrotest.
resolvers=(
nightly-"$(date -d "3 days ago" +"%Y-%m-%d")"
)
die() { echo "$*" >&2; exit 1; }
[ -e "ShellCheck.cabal" ] ||
die "ShellCheck.cabal not in current dir"
[ -e "stack.yaml" ] ||
die "stack.yaml not in current dir"
command -v stack ||
die "stack is missing"
stack setup || die "Failed to setup with default resolver"
stack build --test || die "Failed to build/test with default resolver"
for resolver in "${resolvers[@]}"
do
stack --resolver="$resolver" setup || die "Failed to setup $resolver"
stack --resolver="$resolver" build --test || die "Failed build/test with $resolver!"
done
echo "Success"