Skip to content

Commit

Permalink
Added readme and licenses
Browse files Browse the repository at this point in the history
  • Loading branch information
koalaman committed Nov 17, 2012
1 parent a7a19fa commit 258a137
Show file tree
Hide file tree
Showing 9 changed files with 819 additions and 1 deletion.
661 changes: 661 additions & 0 deletions LICENSE

Large diffs are not rendered by default.

27 changes: 27 additions & 0 deletions README
Original file line number Diff line number Diff line change
@@ -0,0 +1,27 @@
ShellCheck - A shell script static analysis tool
http://www.vidarholen.net/contents/shellcheck

Copyright 2012, Vidar 'koala_man' Holen
Licensed under the GNU Affero General Public License, v3

The goals of ShellCheck are:

- To point out and clarify typical beginner's syntax issues,
that causes a shell to give cryptic error messages.

- To point out and clarify typical intermediate level semantic problems,
that causes a shell to behave strangely and counter-intuitively.

- To point out subtle caveats, corner cases and pitfalls, that may cause an
advance user's otherwise working script to fail under future circumstances.


ShellCheck is written in Haskell, and requires GHC and Parsec3. To build the
JSON interface and run the unit tests, it also requires QuickCheck2 and JSON.

On Ubuntu and similar, these are called:
ghc6 libghc6-parsec3-dev libghc6-quickcheck2-dev libghc6-json-dev

Build with 'make'.

Happy ShellChecking!
17 changes: 17 additions & 0 deletions ShellCheck/AST.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,20 @@
{-
This file is part of ShellCheck.
http://www.vidarholen.net/contents/shellcheck
ShellCheck is free software: you can redistribute it and/or modify
it under the terms of the GNU Affero General Public License as published by
the Free Software Foundation, either version 3 of the License, or
(at your option) any later version.
ShellCheck is distributed in the hope that it will be useful,
but WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
GNU Affero General Public License for more details.
You should have received a copy of the GNU Affero General Public License
along with this program. If not, see <http://www.gnu.org/licenses/>.
-}
module ShellCheck.AST where

import Control.Monad
Expand Down
30 changes: 29 additions & 1 deletion ShellCheck/Analytics.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,20 @@
{-
This file is part of ShellCheck.
http://www.vidarholen.net/contents/shellcheck
ShellCheck is free software: you can redistribute it and/or modify
it under the terms of the GNU Affero General Public License as published by
the Free Software Foundation, either version 3 of the License, or
(at your option) any later version.
ShellCheck is distributed in the hope that it will be useful,
but WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
GNU Affero General Public License for more details.
You should have received a copy of the GNU Affero General Public License
along with this program. If not, see <http://www.gnu.org/licenses/>.
-}
module ShellCheck.Analytics where

import ShellCheck.AST
Expand Down Expand Up @@ -42,6 +59,7 @@ basicChecks = [
,checkArithmeticDeref
,checkComparisonAgainstGlob
,checkPrintfVar
,checkCommarrays
]

modifyMap = modify
Expand Down Expand Up @@ -276,6 +294,16 @@ checkComparisonAgainstGlob (TC_Binary _ DoubleBracket op _ (T_NormalWord id [T_D
warn id $ "Quote the rhs of = in [[ ]] to prevent glob interpretation"
checkComparisonAgainstGlob _ = return ()

prop_checkCommarrays1 = verify checkCommarrays "a=(1, 2)"
prop_checkCommarrays2 = verify checkCommarrays "a+=(1,2,3)"
prop_checkCommarrays3 = verifyNot checkCommarrays "cow=(1 \"foo,bar\" 3)"
checkCommarrays (T_Array id l) =
if any ("," `isSuffixOf`) (concatMap deadSimple l) || (length $ filter (==',') (concat $ concatMap deadSimple l)) > 1
then warn id "Use spaces, not commas, to separate array elements"
else return ()
checkCommarrays _ = return ()


allModifiedVariables t = snd $ runState (doAnalysis (\x -> modify $ (++) (getModifiedVariables x)) t) []

--- Command specific checks
Expand Down Expand Up @@ -311,7 +339,7 @@ checkPrintfVar = checkCommand "printf" f where
f _ = return ()
check format =
if not $ isLiteral format
then warn (getId format) $ "Don't use printf \"$foo\", use printf \"%s\" \"$foo\""
then warn (getId format) $ "Don't use printf \"$foo\", use printf \"%s\" \"$foo\""
else return ()

--- Subshell detection
Expand Down
17 changes: 17 additions & 0 deletions ShellCheck/Parser.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,20 @@
{-
This file is part of ShellCheck.
http://www.vidarholen.net/contents/shellcheck
ShellCheck is free software: you can redistribute it and/or modify
it under the terms of the GNU Affero General Public License as published by
the Free Software Foundation, either version 3 of the License, or
(at your option) any later version.
ShellCheck is distributed in the hope that it will be useful,
but WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
GNU Affero General Public License for more details.
You should have received a copy of the GNU Affero General Public License
along with this program. If not, see <http://www.gnu.org/licenses/>.
-}
{-# LANGUAGE NoMonomorphismRestriction #-}

module ShellCheck.Parser (Note(..), Severity(..), parseShell, ParseResult(..), ParseNote(..), notesFromMap, Metadata(..), sortNotes, getId) where
Expand Down
17 changes: 17 additions & 0 deletions ShellCheck/Simple.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,20 @@
{-
This file is part of ShellCheck.
http://www.vidarholen.net/contents/shellcheck
ShellCheck is free software: you can redistribute it and/or modify
it under the terms of the GNU Affero General Public License as published by
the Free Software Foundation, either version 3 of the License, or
(at your option) any later version.
ShellCheck is distributed in the hope that it will be useful,
but WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
GNU Affero General Public License for more details.
You should have received a copy of the GNU Affero General Public License
along with this program. If not, see <http://www.gnu.org/licenses/>.
-}
module ShellCheck.Simple (shellCheck, ShellCheckComment, scLine, scColumn, scSeverity, scMessage) where

import ShellCheck.Parser
Expand Down
17 changes: 17 additions & 0 deletions jsoncheck.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,20 @@
{-
This file is part of ShellCheck.
http://www.vidarholen.net/contents/shellcheck
ShellCheck is free software: you can redistribute it and/or modify
it under the terms of the GNU Affero General Public License as published by
the Free Software Foundation, either version 3 of the License, or
(at your option) any later version.
ShellCheck is distributed in the hope that it will be useful,
but WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
GNU Affero General Public License for more details.
You should have received a copy of the GNU Affero General Public License
along with this program. If not, see <http://www.gnu.org/licenses/>.
-}
import ShellCheck.Simple
import Text.JSON

Expand Down
17 changes: 17 additions & 0 deletions shellcheck.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,20 @@
{-
This file is part of ShellCheck.
http://www.vidarholen.net/contents/shellcheck
ShellCheck is free software: you can redistribute it and/or modify
it under the terms of the GNU Affero General Public License as published by
the Free Software Foundation, either version 3 of the License, or
(at your option) any later version.
ShellCheck is distributed in the hope that it will be useful,
but WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
GNU Affero General Public License for more details.
You should have received a copy of the GNU Affero General Public License
along with this program. If not, see <http://www.gnu.org/licenses/>.
-}
import Control.Monad
import GHC.Exts
import GHC.IO.Device
Expand Down
17 changes: 17 additions & 0 deletions test/quackCheck.hs
100755 → 100644
Original file line number Diff line number Diff line change
@@ -1,3 +1,20 @@
{-
This file is part of ShellCheck.
http://www.vidarholen.net/contents/shellcheck
ShellCheck is free software: you can redistribute it and/or modify
it under the terms of the GNU Affero General Public License as published by
the Free Software Foundation, either version 3 of the License, or
(at your option) any later version.
ShellCheck is distributed in the hope that it will be useful,
but WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
GNU Affero General Public License for more details.
You should have received a copy of the GNU Affero General Public License
along with this program. If not, see <http://www.gnu.org/licenses/>.
-}
#!/usr/bin/env runhaskell
-- #!/usr/bin/env runhugs
-- $Id: quickcheck,v 1.4 2003/01/08 15:09:22 shae Exp $
Expand Down

0 comments on commit 258a137

Please sign in to comment.