diff -up ShellCheck-0.3.4/ShellCheck.cabal.orig ShellCheck-0.3.4/ShellCheck.cabal --- ShellCheck-0.3.4/ShellCheck.cabal.orig 2014-07-09 10:52:01.000000000 +0900 +++ ShellCheck-0.3.4/ShellCheck.cabal 2014-11-06 19:44:37.829332580 +0900 @@ -41,8 +41,7 @@ library json, mtl, parsec, - regex-compat, - QuickCheck >= 2.2 + regex-compat exposed-modules: ShellCheck.Analytics ShellCheck.AST @@ -61,8 +60,7 @@ executable shellcheck json, mtl, parsec, - regex-compat, - QuickCheck >= 2.2 + regex-compat main-is: shellcheck.hs test-suite test-shellcheck diff -up ShellCheck-0.3.4/ShellCheck/Analytics.hs.orig ShellCheck-0.3.4/ShellCheck/Analytics.hs --- ShellCheck-0.3.4/ShellCheck/Analytics.hs.orig 2014-07-09 10:52:01.000000000 +0900 +++ ShellCheck-0.3.4/ShellCheck/Analytics.hs 2014-11-07 13:56:50.249086778 +0900 @@ -15,8 +15,7 @@ You should have received a copy of the GNU Affero General Public License along with this program. If not, see . -} -{-# LANGUAGE TemplateHaskell #-} -module ShellCheck.Analytics (AnalysisOption(..), filterByAnnotation, runAnalytics, shellForExecutable, runTests) where +module ShellCheck.Analytics (AnalysisOption(..), filterByAnnotation, runAnalytics, shellForExecutable) where import Control.Arrow (first) import Control.Monad @@ -30,10 +29,9 @@ import Data.Maybe import Debug.Trace import ShellCheck.AST import ShellCheck.Data -import ShellCheck.Parser hiding (runTests) +import ShellCheck.Parser import Text.Regex import qualified Data.Map as Map -import Test.QuickCheck.All (quickCheckAll) data Shell = Ksh | Zsh | Sh | Bash deriving (Show, Eq) @@ -2879,7 +2877,3 @@ checkFindActionPrecedence params = check param <- getLiteralString t return $ param `elem` strs warnFor t = warn (getId t) 2146 "This action ignores everything before the -o. Use \\( \\) to group." - -return [] -runTests = $quickCheckAll - diff -up ShellCheck-0.3.4/ShellCheck/Parser.hs.orig ShellCheck-0.3.4/ShellCheck/Parser.hs --- ShellCheck-0.3.4/ShellCheck/Parser.hs.orig 2014-07-09 10:52:01.000000000 +0900 +++ ShellCheck-0.3.4/ShellCheck/Parser.hs 2014-11-06 19:44:37.830332583 +0900 @@ -15,8 +15,8 @@ You should have received a copy of the GNU Affero General Public License along with this program. If not, see . -} -{-# LANGUAGE NoMonomorphismRestriction, TemplateHaskell #-} -module ShellCheck.Parser (Note(..), Severity(..), parseShell, ParseResult(..), ParseNote(..), sortNotes, noteToParseNote, runTests) where +{-# LANGUAGE NoMonomorphismRestriction #-} +module ShellCheck.Parser (Note(..), Severity(..), parseShell, ParseResult(..), ParseNote(..), sortNotes, noteToParseNote) where import ShellCheck.AST import ShellCheck.Data @@ -33,7 +33,6 @@ 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' @@ -2093,7 +2092,3 @@ parseShell filename contents = lt x = trace (show x) x ltt t = trace (show t) - -return [] -runTests = $quickCheckAll - diff -up ShellCheck-0.3.4/ShellCheck/Simple.hs.orig ShellCheck-0.3.4/ShellCheck/Simple.hs --- ShellCheck-0.3.4/ShellCheck/Simple.hs.orig 2014-07-09 10:52:01.000000000 +0900 +++ ShellCheck-0.3.4/ShellCheck/Simple.hs 2014-11-07 13:57:03.711115912 +0900 @@ -15,15 +15,13 @@ You should have received a copy of the GNU Affero General Public License along with this program. If not, see . -} -{-# LANGUAGE TemplateHaskell #-} -module ShellCheck.Simple (shellCheck, ShellCheckComment, scLine, scColumn, scSeverity, scCode, scMessage, runTests) where +module ShellCheck.Simple (shellCheck, ShellCheckComment, scLine, scColumn, scSeverity, scCode, scMessage) where -import ShellCheck.Parser hiding (runTests) -import ShellCheck.Analytics hiding (runTests) +import ShellCheck.Parser +import ShellCheck.Analytics import Data.Maybe import Text.Parsec.Pos import Data.List -import Test.QuickCheck.All (quickCheckAll) shellCheck :: String -> [AnalysisOption] -> [ShellCheckComment] shellCheck script options = @@ -66,7 +64,3 @@ prop_commentDisablesAnalysisIssue1 = null $ shellCheck "#shellcheck disable=SC2086\necho $1" [] prop_commentDisablesAnalysisIssue2 = null $ shellCheck "#shellcheck disable=SC2086\n#lol\necho $1" [] - -return [] -runTests = $quickCheckAll -