Fix handling of spaces in shebangs.
This commit is contained in:
parent
db0c8c2dc9
commit
f835c2d4c1
|
@ -17,7 +17,7 @@
|
||||||
You should have received a copy of the GNU General Public License
|
You should have received a copy of the GNU General Public License
|
||||||
along with this program. If not, see <http://www.gnu.org/licenses/>.
|
along with this program. If not, see <http://www.gnu.org/licenses/>.
|
||||||
-}
|
-}
|
||||||
{-# LANGUAGE TemplateHaskell #-} -- prop_testing
|
{-# LANGUAGE TemplateHaskell #-}
|
||||||
{-# LANGUAGE FlexibleContexts #-}
|
{-# LANGUAGE FlexibleContexts #-}
|
||||||
module ShellCheck.AnalyzerLib where
|
module ShellCheck.AnalyzerLib where
|
||||||
import ShellCheck.AST
|
import ShellCheck.AST
|
||||||
|
@ -37,8 +37,10 @@ import Data.List
|
||||||
import Data.Maybe
|
import Data.Maybe
|
||||||
import qualified Data.Map as Map
|
import qualified Data.Map as Map
|
||||||
|
|
||||||
import Test.QuickCheck.All (forAllProperties) -- prop_testing
|
import Test.QuickCheck.All (forAllProperties)
|
||||||
import Test.QuickCheck.Test (quickCheckWithResult, stdArgs, maxSuccess) --prop_testing
|
import Test.QuickCheck.Test (quickCheckWithResult, stdArgs, maxSuccess)
|
||||||
|
|
||||||
|
import Debug.Trace
|
||||||
|
|
||||||
type Analysis = ReaderT Parameters (Writer [TokenComment]) ()
|
type Analysis = ReaderT Parameters (Writer [TokenComment]) ()
|
||||||
|
|
||||||
|
@ -111,6 +113,7 @@ prop_determineShell4 = determineShell (fromJust $ pScript
|
||||||
"#!/bin/ksh\n#shellcheck shell=sh\nfoo") == Sh
|
"#!/bin/ksh\n#shellcheck shell=sh\nfoo") == Sh
|
||||||
prop_determineShell5 = determineShell (fromJust $ pScript
|
prop_determineShell5 = determineShell (fromJust $ pScript
|
||||||
"#shellcheck shell=sh\nfoo") == Sh
|
"#shellcheck shell=sh\nfoo") == Sh
|
||||||
|
prop_determineShell6 = determineShell (fromJust $ pScript "#! /bin/sh") == Sh
|
||||||
determineShell t = fromMaybe Bash $ do
|
determineShell t = fromMaybe Bash $ do
|
||||||
shellString <- foldl mplus Nothing $ getCandidates t
|
shellString <- foldl mplus Nothing $ getCandidates t
|
||||||
shellForExecutable shellString
|
shellForExecutable shellString
|
||||||
|
@ -621,4 +624,4 @@ filterByAnnotation token =
|
||||||
|
|
||||||
|
|
||||||
return []
|
return []
|
||||||
runTests = $( [| $(forAllProperties) (quickCheckWithResult (stdArgs { maxSuccess = 1 }) ) |]) -- prop_testing
|
runTests = $( [| $(forAllProperties) (quickCheckWithResult (stdArgs { maxSuccess = 1 }) ) |])
|
||||||
|
|
|
@ -2345,8 +2345,10 @@ ifParse p t f =
|
||||||
prop_readShebang1 = isOk readShebang "#!/bin/sh\n"
|
prop_readShebang1 = isOk readShebang "#!/bin/sh\n"
|
||||||
prop_readShebang2 = isWarning readShebang "!# /bin/sh\n"
|
prop_readShebang2 = isWarning readShebang "!# /bin/sh\n"
|
||||||
prop_readShebang3 = isNotOk readShebang "#shellcheck shell=/bin/sh\n"
|
prop_readShebang3 = isNotOk readShebang "#shellcheck shell=/bin/sh\n"
|
||||||
|
prop_readShebang4 = isWarning readShebang "! /bin/sh"
|
||||||
readShebang = do
|
readShebang = do
|
||||||
try readCorrect <|> try readSwapped
|
try readCorrect <|> try readSwapped <|> try readMissingHash
|
||||||
|
many linewhitespace
|
||||||
str <- many $ noneOf "\r\n"
|
str <- many $ noneOf "\r\n"
|
||||||
optional carriageReturn
|
optional carriageReturn
|
||||||
optional linefeed
|
optional linefeed
|
||||||
|
@ -2359,6 +2361,15 @@ readShebang = do
|
||||||
parseProblemAt pos ErrorC 1084
|
parseProblemAt pos ErrorC 1084
|
||||||
"Use #!, not !#, for the shebang."
|
"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 [
|
verifyEof = eof <|> choice [
|
||||||
ifParsable g_Lparen $
|
ifParsable g_Lparen $
|
||||||
parseProblem ErrorC 1088 "Parsing stopped here. Invalid use of parentheses?",
|
parseProblem ErrorC 1088 "Parsing stopped here. Invalid use of parentheses?",
|
||||||
|
|
|
@ -9,6 +9,7 @@
|
||||||
,ShellCheck.Parser.runTests
|
,ShellCheck.Parser.runTests
|
||||||
,ShellCheck.Checker.runTests
|
,ShellCheck.Checker.runTests
|
||||||
,ShellCheck.Checks.Commands.runTests
|
,ShellCheck.Checks.Commands.runTests
|
||||||
|
,ShellCheck.AnalyzerLib.runTests
|
||||||
]' | tr -d '\n' | cabal repl 2>&1 | tee /dev/stderr)
|
]' | tr -d '\n' | cabal repl 2>&1 | tee /dev/stderr)
|
||||||
if [[ $var == *$'\nTrue'* ]]
|
if [[ $var == *$'\nTrue'* ]]
|
||||||
then
|
then
|
||||||
|
|
|
@ -13,6 +13,7 @@ main = do
|
||||||
ShellCheck.Checker.runTests,
|
ShellCheck.Checker.runTests,
|
||||||
ShellCheck.Checks.Commands.runTests,
|
ShellCheck.Checks.Commands.runTests,
|
||||||
ShellCheck.Analytics.runTests,
|
ShellCheck.Analytics.runTests,
|
||||||
|
ShellCheck.AnalyzerLib.runTests,
|
||||||
ShellCheck.Parser.runTests
|
ShellCheck.Parser.runTests
|
||||||
]
|
]
|
||||||
if and results
|
if and results
|
||||||
|
|
Loading…
Reference in New Issue