Moved shebang verification to parser
This commit is contained in:
parent
a08e60cd07
commit
599beff5b1
|
@ -54,35 +54,22 @@ checksFor Bash = map runBasicAnalysis [
|
||||||
|
|
||||||
runAllAnalytics root m = addToMap notes m
|
runAllAnalytics root m = addToMap notes m
|
||||||
where shell = determineShell root
|
where shell = determineShell root
|
||||||
unsupported = (getId root, Note ErrorC "ShellCheck only handles Bourne based shells, sorry!")
|
notes = checkList ((checksFor shell) ++ genericChecks) root
|
||||||
notes = case shell of
|
|
||||||
Nothing -> [ unsupported ]
|
|
||||||
Just sh -> checkList ((checksFor sh) ++ genericChecks) root
|
|
||||||
|
|
||||||
checkList l t = concatMap (\f -> f t) l
|
checkList l t = concatMap (\f -> f t) l
|
||||||
addToMap list map = foldr (\(id,note) m -> Map.adjust (\(Metadata pos notes) -> Metadata pos (note:notes)) id m) map list
|
addToMap list map = foldr (\(id,note) m -> Map.adjust (\(Metadata pos notes) -> Metadata pos (note:notes)) id m) map list
|
||||||
|
|
||||||
prop_determineShell0 = determineShell (T_Script (Id 0) "#!/bin/sh" []) == Just Sh
|
prop_determineShell0 = determineShell (T_Script (Id 0) "#!/bin/sh" []) == Sh
|
||||||
prop_determineShell1 = determineShell (T_Script (Id 0) "#!/usr/bin/env ksh" []) == Just Ksh
|
prop_determineShell1 = determineShell (T_Script (Id 0) "#!/usr/bin/env ksh" []) == Ksh
|
||||||
prop_determineShell2 = determineShell (T_Script (Id 0) "" []) == Just Bash
|
prop_determineShell2 = determineShell (T_Script (Id 0) "" []) == Bash
|
||||||
determineShell (T_Script _ shebang _) = normalize $ shellFor shebang
|
determineShell (T_Script _ shebang _) = normalize $ shellFor shebang
|
||||||
where shellFor s | "/env " `isInfixOf` s = head ((drop 1 $ words s)++[""])
|
where shellFor s | "/env " `isInfixOf` s = head ((drop 1 $ words s)++[""])
|
||||||
shellFor s = reverse . takeWhile (/= '/') . reverse $ s
|
shellFor s = reverse . takeWhile (/= '/') . reverse $ s
|
||||||
normalize "csh" = Nothing
|
normalize "sh" = Sh
|
||||||
normalize "tcsh" = Nothing
|
normalize "ksh" = Ksh
|
||||||
normalize "sh" = return Sh
|
normalize "zsh" = Zsh
|
||||||
normalize "ksh" = return Ksh
|
normalize "bash" = Bash
|
||||||
normalize "zsh" = return Zsh
|
normalize _ = Bash
|
||||||
normalize "bash" = return Bash
|
|
||||||
normalize x | any (`isPrefixOf` x) [
|
|
||||||
"csh"
|
|
||||||
,"tcsh"
|
|
||||||
,"perl"
|
|
||||||
,"awk"
|
|
||||||
,"python"
|
|
||||||
,"ruby"
|
|
||||||
] = Nothing
|
|
||||||
normalize _ = return Bash
|
|
||||||
|
|
||||||
runBasicAnalysis f t = snd $ runState (doAnalysis f t) []
|
runBasicAnalysis f t = snd $ runState (doAnalysis f t) []
|
||||||
basicChecks = [
|
basicChecks = [
|
||||||
|
|
|
@ -24,7 +24,7 @@ import Text.Parsec
|
||||||
import Debug.Trace
|
import Debug.Trace
|
||||||
import Control.Monad
|
import Control.Monad
|
||||||
import Data.Char
|
import Data.Char
|
||||||
import Data.List (isInfixOf, isSuffixOf, partition, sortBy, intercalate, nub)
|
import Data.List (isPrefixOf, isInfixOf, isSuffixOf, partition, sortBy, intercalate, nub)
|
||||||
import qualified Data.Map as Map
|
import qualified Data.Map as Map
|
||||||
import qualified Control.Monad.State as Ms
|
import qualified Control.Monad.State as Ms
|
||||||
import Data.Maybe
|
import Data.Maybe
|
||||||
|
@ -1558,9 +1558,14 @@ readShebang = do
|
||||||
prop_readScript1 = isOk readScript "#!/bin/bash\necho hello world\n"
|
prop_readScript1 = isOk readScript "#!/bin/bash\necho hello world\n"
|
||||||
prop_readScript2 = isWarning readScript "#!/bin/bash\r\necho hello world\n"
|
prop_readScript2 = isWarning readScript "#!/bin/bash\r\necho hello world\n"
|
||||||
prop_readScript3 = isWarning readScript "#!/bin/bash\necho hello\xA0world"
|
prop_readScript3 = isWarning readScript "#!/bin/bash\necho hello\xA0world"
|
||||||
|
prop_readScript4 = isWarning readScript "#!/usr/bin/perl\nfoo=("
|
||||||
readScript = do
|
readScript = do
|
||||||
id <- getNextId
|
id <- getNextId
|
||||||
|
pos <- getPosition
|
||||||
sb <- option "" readShebang
|
sb <- option "" readShebang
|
||||||
|
verifyShell pos (getShell sb)
|
||||||
|
if (isValidShell $ getShell sb) /= Just False
|
||||||
|
then
|
||||||
do {
|
do {
|
||||||
allspacing;
|
allspacing;
|
||||||
commands <- readTerm;
|
commands <- readTerm;
|
||||||
|
@ -1570,6 +1575,51 @@ readScript = do
|
||||||
parseProblem WarningC "Couldn't read any commands.";
|
parseProblem WarningC "Couldn't read any commands.";
|
||||||
return $ T_Script id sb $ [T_EOF id];
|
return $ T_Script id sb $ [T_EOF id];
|
||||||
}
|
}
|
||||||
|
else do
|
||||||
|
many anyChar
|
||||||
|
return $ T_Script id sb $ [T_EOF id];
|
||||||
|
|
||||||
|
where
|
||||||
|
basename s = reverse . takeWhile (/= '/') . reverse $ s
|
||||||
|
getShell sb =
|
||||||
|
case words sb of
|
||||||
|
[] -> ""
|
||||||
|
[x] -> basename x
|
||||||
|
(first:second:_) ->
|
||||||
|
if basename first == "env"
|
||||||
|
then second
|
||||||
|
else basename first
|
||||||
|
|
||||||
|
verifyShell pos s =
|
||||||
|
case isValidShell s of
|
||||||
|
Just True -> return ()
|
||||||
|
Just False -> parseProblemAt pos ErrorC "ShellCheck only supports Bourne based shell scripts, sorry!"
|
||||||
|
Nothing -> parseProblemAt pos InfoC "This shebang was unrecognized. Note that ShellCheck only handles Bourne based shells."
|
||||||
|
|
||||||
|
isValidShell s =
|
||||||
|
let good = s == "" || any (`isPrefixOf` s) goodShells
|
||||||
|
bad = any (`isPrefixOf` s) badShells
|
||||||
|
in
|
||||||
|
if good
|
||||||
|
then Just True
|
||||||
|
else if bad
|
||||||
|
then Just False
|
||||||
|
else Nothing
|
||||||
|
|
||||||
|
goodShells = [
|
||||||
|
"sh",
|
||||||
|
"bash",
|
||||||
|
"ksh",
|
||||||
|
"zsh"
|
||||||
|
]
|
||||||
|
badShells = [
|
||||||
|
"awk",
|
||||||
|
"csh",
|
||||||
|
"perl",
|
||||||
|
"python",
|
||||||
|
"ruby",
|
||||||
|
"tcsh"
|
||||||
|
]
|
||||||
|
|
||||||
rp p filename contents = Ms.runState (runParserT p initialState filename contents) ([], [])
|
rp p filename contents = Ms.runState (runParserT p initialState filename contents) ([], [])
|
||||||
|
|
||||||
|
|
Loading…
Reference in New Issue