Skip to content

Commit

Permalink
Test Suite in Cabal (cabal test)
Browse files Browse the repository at this point in the history
Please run using "cabal test --show-details=streaming", there's a known
issue about this that was fixed in the latest version of cabal:
haskell/cabal#1810
  • Loading branch information
rodrigosetti committed May 31, 2014
1 parent 3fcc6c4 commit 0a9ed91
Show file tree
Hide file tree
Showing 8 changed files with 141 additions and 192 deletions.
6 changes: 1 addition & 5 deletions Makefile
Original file line number Diff line number Diff line change
Expand Up @@ -3,17 +3,13 @@
GHCFLAGS=-O9
GHCFLAGS_STATIC=$(GHCFLAGS) -optl-static -optl-pthread

all: shellcheck .tests shellcheck.1
all: shellcheck shellcheck.1
: Done

shellcheck: regardless
: Conditionally compiling shellcheck
ghc $(GHCFLAGS) --make shellcheck

.tests: *.hs */*.hs
: Running unit tests
./test/runQuack && touch .tests

shellcheck.1: shellcheck.1.md
: Formatting man page
pandoc -s -t man $< -o $@
Expand Down
20 changes: 18 additions & 2 deletions ShellCheck.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -35,7 +35,8 @@ library
json,
mtl,
parsec,
regex-compat
regex-compat,
QuickCheck >= 2.2
exposed-modules:
ShellCheck.Analytics
ShellCheck.AST
Expand All @@ -54,6 +55,21 @@ executable shellcheck
json,
mtl,
parsec,
regex-compat
regex-compat,
QuickCheck >= 2.2
main-is: shellcheck.hs

test-suite test-shellcheck
type: exitcode-stdio-1.0
build-depends:
ShellCheck,
base >= 4 && < 5,
containers,
directory,
json,
mtl,
parsec,
regex-compat,
QuickCheck >= 2.2
main-is: test/shellcheck.hs

147 changes: 73 additions & 74 deletions ShellCheck/Analytics.hs

Large diffs are not rendered by default.

12 changes: 8 additions & 4 deletions ShellCheck/Parser.hs
Original file line number Diff line number Diff line change
Expand Up @@ -15,9 +15,8 @@
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(..), sortNotes, noteToParseNote) where
{-# LANGUAGE NoMonomorphismRestriction, TemplateHaskell #-}
module ShellCheck.Parser (Note(..), Severity(..), parseShell, ParseResult(..), ParseNote(..), sortNotes, noteToParseNote, runTests) where

import ShellCheck.AST
import ShellCheck.Data
Expand All @@ -33,6 +32,7 @@ import Prelude hiding (readList)
import System.IO
import Text.Parsec.Error
import GHC.Exts (sortWith)
import Test.QuickCheck.All (quickCheckAll)

backslash = char '\\'
linefeed = (optional carriageReturn) >> char '\n'
Expand Down Expand Up @@ -2071,4 +2071,8 @@ parseShell filename contents = do
"The mentioned parser error was in this " ++ str ++ "."

lt x = trace (show x) x
ltt t x = trace (show t) x
ltt t = trace (show t)

return []
runTests = $quickCheckAll

45 changes: 25 additions & 20 deletions ShellCheck/Simple.hs
Original file line number Diff line number Diff line change
Expand Up @@ -15,30 +15,15 @@
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, scCode, scMessage) where
{-# LANGUAGE TemplateHaskell #-}
module ShellCheck.Simple (shellCheck, ShellCheckComment, scLine, scColumn, scSeverity, scCode, scMessage, runTests) where

import ShellCheck.Parser
import ShellCheck.Analytics
import ShellCheck.Parser hiding (runTests)
import ShellCheck.Analytics hiding (runTests)
import Data.Maybe
import Text.Parsec.Pos
import Data.List


prop_findsParseIssue =
let comments = shellCheck "echo \"$12\"" [] in
(length comments) == 1 && (scCode $ head comments) == 1037
prop_commentDisablesParseIssue1 =
null $ shellCheck "#shellcheck disable=SC1037\necho \"$12\"" []
prop_commentDisablesParseIssue2 =
null $ shellCheck "#shellcheck disable=SC1037\n#lol\necho \"$12\"" []

prop_findsAnalysisIssue =
let comments = shellCheck "echo $1" [] in
(length comments) == 1 && (scCode $ head comments) == 2086
prop_commentDisablesAnalysisIssue1 =
null $ shellCheck "#shellcheck disable=SC2086\necho $1" []
prop_commentDisablesAnalysisIssue2 =
null $ shellCheck "#shellcheck disable=SC2086\n#lol\necho $1" []
import Test.QuickCheck.All (quickCheckAll)

shellCheck :: String -> [AnalysisOption] -> [ShellCheckComment]
shellCheck script options =
Expand All @@ -65,3 +50,23 @@ severityToString s =

formatNote (ParseNote pos severity code text) =
ShellCheckComment (sourceLine pos) (sourceColumn pos) (severityToString severity) (fromIntegral code) text

prop_findsParseIssue =
let comments = shellCheck "echo \"$12\"" [] in
length comments == 1 && scCode (head comments) == 1037
prop_commentDisablesParseIssue1 =
null $ shellCheck "#shellcheck disable=SC1037\necho \"$12\"" []
prop_commentDisablesParseIssue2 =
null $ shellCheck "#shellcheck disable=SC1037\n#lol\necho \"$12\"" []

prop_findsAnalysisIssue =
let comments = shellCheck "echo $1" [] in
length comments == 1 && scCode (head comments) == 2086
prop_commentDisablesAnalysisIssue1 =
null $ shellCheck "#shellcheck disable=SC2086\necho $1" []
prop_commentDisablesAnalysisIssue2 =
null $ shellCheck "#shellcheck disable=SC2086\n#lol\necho $1" []

return []
runTests = $quickCheckAll

65 changes: 0 additions & 65 deletions test/quackCheck.hs

This file was deleted.

22 changes: 0 additions & 22 deletions test/runQuack

This file was deleted.

16 changes: 16 additions & 0 deletions test/shellcheck.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,16 @@
module Main where

import Control.Monad
import System.Exit
import qualified ShellCheck.Simple
import qualified ShellCheck.Analytics
import qualified ShellCheck.Parser

main = do
putStrLn "Running ShellCheck tests..."
results <- sequence [ShellCheck.Simple.runTests,
ShellCheck.Analytics.runTests,
ShellCheck.Parser.runTests]
if and results then exitSuccess
else exitFailure

0 comments on commit 0a9ed91

Please sign in to comment.