summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorVidar Holen <spam@vidarholen.net>2016-04-16 09:42:07 -0700
committerVidar Holen <spam@vidarholen.net>2016-04-16 09:42:07 -0700
commitf835c2d4c17e826efb1f23a27cf9bcde666e5b73 (patch)
tree883a8c96354966b2ec2a729801245a71b8fcb075
parentdb0c8c2dc9fb3dfc97c807e1bbcd3a3325324978 (diff)
Fix handling of spaces in shebangs.
-rw-r--r--ShellCheck/AnalyzerLib.hs11
-rw-r--r--ShellCheck/Parser.hs13
-rwxr-xr-xquicktest1
-rw-r--r--test/shellcheck.hs1
4 files changed, 21 insertions, 5 deletions
diff --git a/ShellCheck/AnalyzerLib.hs b/ShellCheck/AnalyzerLib.hs
index 4bc95ce..fcf46bb 100644
--- a/ShellCheck/AnalyzerLib.hs
+++ b/ShellCheck/AnalyzerLib.hs
@@ -17,7 +17,7 @@
You should have received a copy of the GNU General Public License
along with this program. If not, see <http://www.gnu.org/licenses/>.
-}
-{-# LANGUAGE TemplateHaskell #-} -- prop_testing
+{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE FlexibleContexts #-}
module ShellCheck.AnalyzerLib where
import ShellCheck.AST
@@ -37,8 +37,10 @@ import Data.List
import Data.Maybe
import qualified Data.Map as Map
-import Test.QuickCheck.All (forAllProperties) -- prop_testing
-import Test.QuickCheck.Test (quickCheckWithResult, stdArgs, maxSuccess) --prop_testing
+import Test.QuickCheck.All (forAllProperties)
+import Test.QuickCheck.Test (quickCheckWithResult, stdArgs, maxSuccess)
+
+import Debug.Trace
type Analysis = ReaderT Parameters (Writer [TokenComment]) ()
@@ -111,6 +113,7 @@ 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
determineShell t = fromMaybe Bash $ do
shellString <- foldl mplus Nothing $ getCandidates t
shellForExecutable shellString
@@ -621,4 +624,4 @@ filterByAnnotation token =
return []
-runTests = $( [| $(forAllProperties) (quickCheckWithResult (stdArgs { maxSuccess = 1 }) ) |]) -- prop_testing
+runTests = $( [| $(forAllProperties) (quickCheckWithResult (stdArgs { maxSuccess = 1 }) ) |])
diff --git a/ShellCheck/Parser.hs b/ShellCheck/Parser.hs
index e0b09da..8a64c7c 100644
--- a/ShellCheck/Parser.hs
+++ b/ShellCheck/Parser.hs
@@ -2345,8 +2345,10 @@ ifParse p t f =
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"
readShebang = do
- try readCorrect <|> try readSwapped
+ try readCorrect <|> try readSwapped <|> try readMissingHash
+ many linewhitespace
str <- many $ noneOf "\r\n"
optional carriageReturn
optional linefeed
@@ -2359,6 +2361,15 @@ readShebang = do
parseProblemAt pos ErrorC 1084
"Use #!, not !#, for the shebang."
+ readMissingHash = do
+ pos <- getPosition
+ char '!'
+ lookAhead $ do
+ many linewhitespace
+ char '/'
+ parseProblemAt pos ErrorC 1104
+ "Use #!, not just !, for the shebang."
+
verifyEof = eof <|> choice [
ifParsable g_Lparen $
parseProblem ErrorC 1088 "Parsing stopped here. Invalid use of parentheses?",
diff --git a/quicktest b/quicktest
index db328cb..60894ab 100755
--- a/quicktest
+++ b/quicktest
@@ -9,6 +9,7 @@
,ShellCheck.Parser.runTests
,ShellCheck.Checker.runTests
,ShellCheck.Checks.Commands.runTests
+ ,ShellCheck.AnalyzerLib.runTests
]' | tr -d '\n' | cabal repl 2>&1 | tee /dev/stderr)
if [[ $var == *$'\nTrue'* ]]
then
diff --git a/test/shellcheck.hs b/test/shellcheck.hs
index e054d7c..6ea3319 100644
--- a/test/shellcheck.hs
+++ b/test/shellcheck.hs
@@ -13,6 +13,7 @@ main = do
ShellCheck.Checker.runTests,
ShellCheck.Checks.Commands.runTests,
ShellCheck.Analytics.runTests,
+ ShellCheck.AnalyzerLib.runTests,
ShellCheck.Parser.runTests
]
if and results