Added --version flag
This commit is contained in:
parent
c5141b77bf
commit
4e5d32b05a
|
@ -1,5 +1,5 @@
|
||||||
Name: ShellCheck
|
Name: ShellCheck
|
||||||
Version: 0.3.0
|
Version: 0.3.0 -- Must also be updated in ShellCheck/Data.hs
|
||||||
Synopsis: Shell script analysis tool
|
Synopsis: Shell script analysis tool
|
||||||
License: OtherLicense
|
License: OtherLicense
|
||||||
License-file: LICENSE
|
License-file: LICENSE
|
||||||
|
|
|
@ -105,8 +105,11 @@ determineShell (T_Script _ shebang _) = fromMaybe Bash . shellForExecutable $ sh
|
||||||
shellForExecutable "sh" = return Sh
|
shellForExecutable "sh" = return Sh
|
||||||
shellForExecutable "ash" = return Sh
|
shellForExecutable "ash" = return Sh
|
||||||
shellForExecutable "dash" = return Sh
|
shellForExecutable "dash" = return Sh
|
||||||
|
|
||||||
shellForExecutable "ksh" = return Ksh
|
shellForExecutable "ksh" = return Ksh
|
||||||
|
shellForExecutable "ksh88" = return Ksh
|
||||||
shellForExecutable "ksh93" = return Ksh
|
shellForExecutable "ksh93" = return Ksh
|
||||||
|
|
||||||
shellForExecutable "zsh" = return Zsh
|
shellForExecutable "zsh" = return Zsh
|
||||||
shellForExecutable "bash" = return Bash
|
shellForExecutable "bash" = return Bash
|
||||||
shellForExecutable _ = Nothing
|
shellForExecutable _ = Nothing
|
||||||
|
|
|
@ -1,5 +1,7 @@
|
||||||
module ShellCheck.Data where
|
module ShellCheck.Data where
|
||||||
|
|
||||||
|
shellcheckVersion = "0.3.0" -- Must also be updated in ShellCheck.cabal
|
||||||
|
|
||||||
internalVariables = [
|
internalVariables = [
|
||||||
-- Generic
|
-- Generic
|
||||||
"", "_", "rest", "REST",
|
"", "_", "rest", "REST",
|
||||||
|
|
|
@ -22,6 +22,7 @@ import Data.Maybe
|
||||||
import GHC.Exts
|
import GHC.Exts
|
||||||
import GHC.IO.Device
|
import GHC.IO.Device
|
||||||
import Prelude hiding (catch)
|
import Prelude hiding (catch)
|
||||||
|
import ShellCheck.Data
|
||||||
import ShellCheck.Simple
|
import ShellCheck.Simple
|
||||||
import ShellCheck.Analytics
|
import ShellCheck.Analytics
|
||||||
import System.Console.GetOpt
|
import System.Console.GetOpt
|
||||||
|
@ -41,7 +42,9 @@ options = [
|
||||||
Option ['e'] ["exclude"]
|
Option ['e'] ["exclude"]
|
||||||
(ReqArg (Flag "exclude") "CODE1,CODE2..") "exclude types of warnings",
|
(ReqArg (Flag "exclude") "CODE1,CODE2..") "exclude types of warnings",
|
||||||
Option ['s'] ["shell"]
|
Option ['s'] ["shell"]
|
||||||
(ReqArg (Flag "shell") "SHELLNAME") "Specify dialect (bash,sh,ksh,zsh)"
|
(ReqArg (Flag "shell") "SHELLNAME") "Specify dialect (bash,sh,ksh,zsh)",
|
||||||
|
Option ['V'] ["version"]
|
||||||
|
(NoArg $ Flag "version" "true") "Print version information"
|
||||||
]
|
]
|
||||||
|
|
||||||
printErr = hPutStrLn stderr
|
printErr = hPutStrLn stderr
|
||||||
|
@ -61,14 +64,9 @@ instance JSON ShellCheckComment where
|
||||||
|
|
||||||
parseArguments argv =
|
parseArguments argv =
|
||||||
case getOpt Permute options argv of
|
case getOpt Permute options argv of
|
||||||
(opts, files, []) ->
|
(opts, files, []) -> do
|
||||||
if not $ null files
|
verifyOptions opts files
|
||||||
then
|
return $ Just (opts, files)
|
||||||
return $ Just (opts, files)
|
|
||||||
else do
|
|
||||||
printErr "No files specified.\n"
|
|
||||||
printErr $ usageInfo header options
|
|
||||||
exitWith syntaxFailure
|
|
||||||
|
|
||||||
(_, _, errors) -> do
|
(_, _, errors) -> do
|
||||||
printErr $ (concat errors) ++ "\n" ++ usageInfo header options
|
printErr $ (concat errors) ++ "\n" ++ usageInfo header options
|
||||||
|
@ -268,7 +266,6 @@ main = do
|
||||||
|
|
||||||
process Nothing = return False
|
process Nothing = return False
|
||||||
process (Just (options, files)) = do
|
process (Just (options, files)) = do
|
||||||
verifyShellOption options
|
|
||||||
let format = fromMaybe "tty" $ getOption options "format" in
|
let format = fromMaybe "tty" $ getOption options "format" in
|
||||||
case Map.lookup format formats of
|
case Map.lookup format formats of
|
||||||
Nothing -> do
|
Nothing -> do
|
||||||
|
@ -280,10 +277,24 @@ process (Just (options, files)) = do
|
||||||
Just f -> do
|
Just f -> do
|
||||||
f options files
|
f options files
|
||||||
|
|
||||||
verifyShellOption options =
|
verifyOptions opts files = do
|
||||||
let shell = getOption options "shell" in
|
when (isJust $ getOption opts "version") printVersionAndExit
|
||||||
|
|
||||||
|
let shell = getOption opts "shell" in
|
||||||
if isNothing shell
|
if isNothing shell
|
||||||
then return ()
|
then return ()
|
||||||
else when (isNothing $ shell >>= shellForExecutable) $ do
|
else when (isNothing $ shell >>= shellForExecutable) $ do
|
||||||
printErr $ "Unknown shell: " ++ (fromJust shell)
|
printErr $ "Unknown shell: " ++ (fromJust shell)
|
||||||
exitWith supportFailure
|
exitWith supportFailure
|
||||||
|
|
||||||
|
when (null files) $ do
|
||||||
|
printErr "No files specified.\n"
|
||||||
|
printErr $ usageInfo header options
|
||||||
|
exitWith syntaxFailure
|
||||||
|
|
||||||
|
printVersionAndExit = do
|
||||||
|
putStrLn $ "ShellCheck - shell script analysis tool"
|
||||||
|
putStrLn $ "version: " ++ shellcheckVersion
|
||||||
|
putStrLn $ "license: GNU Affero General Public License, version 3"
|
||||||
|
putStrLn $ "website: http://www.shellcheck.net"
|
||||||
|
exitWith ExitSuccess
|
||||||
|
|
Loading…
Reference in New Issue