summaryrefslogtreecommitdiff
path: root/p/shellcheck/debian
diff options
context:
space:
mode:
authorHelmut Grohne <helmut@subdivi.de>2014-12-31 00:06:03 +0300
committerHelmut Grohne <helmut@subdivi.de>2014-12-31 00:06:03 +0300
commit11830c42c8c6ee02350719ea7a0ba707922ef69a (patch)
tree5b5a1ddf07cb7f46eb90e1a4ab0ecb4ae6e9287b /p/shellcheck/debian
parent2ded465de1bd7ef5819f48502294a850f95f031f (diff)
downloadDHG_packages-11830c42c8c6ee02350719ea7a0ba707922ef69a.tar.gz
shellcheck: refresh make_testsuite_optional.patch
Diffstat (limited to 'p/shellcheck/debian')
-rw-r--r--p/shellcheck/debian/changelog1
-rw-r--r--p/shellcheck/debian/patches/make_testsuite_optional.patch54
2 files changed, 28 insertions, 27 deletions
diff --git a/p/shellcheck/debian/changelog b/p/shellcheck/debian/changelog
index 1d24fb2bc..19a7685bd 100644
--- a/p/shellcheck/debian/changelog
+++ b/p/shellcheck/debian/changelog
@@ -1,6 +1,7 @@
shellcheck (0.3.5-1) UNRELEASED; urgency=medium
* New Upstream release.
+ * Refresh make_testsuite_optional.patch.
-- Helmut Grohne <helmut@subdivi.de> Tue, 30 Dec 2014 21:43:21 +0100
diff --git a/p/shellcheck/debian/patches/make_testsuite_optional.patch b/p/shellcheck/debian/patches/make_testsuite_optional.patch
index 645759773..618ce3037 100644
--- a/p/shellcheck/debian/patches/make_testsuite_optional.patch
+++ b/p/shellcheck/debian/patches/make_testsuite_optional.patch
@@ -8,10 +8,10 @@ build on non-TH architectures. This patch removes the runTests symbol defined
using TemplateHaskell on non-TH architectures by branching on the
Debian-specific DEBIAN_NO_GHCI CPP macro (Thanks to Joachim Breitner).
-Index: ShellCheck-0.3.4/ShellCheck/Analytics.hs
+Index: ShellCheck-0.3.5/ShellCheck/Analytics.hs
===================================================================
---- ShellCheck-0.3.4.orig/ShellCheck/Analytics.hs 2014-10-23 21:56:44.000000000 +0200
-+++ ShellCheck-0.3.4/ShellCheck/Analytics.hs 2014-10-23 22:11:08.000000000 +0200
+--- ShellCheck-0.3.5.orig/ShellCheck/Analytics.hs 2014-12-30 21:44:59.000000000 +0100
++++ ShellCheck-0.3.5/ShellCheck/Analytics.hs 2014-12-30 21:46:39.000000000 +0100
@@ -15,8 +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/>.
@@ -19,9 +19,9 @@ Index: ShellCheck-0.3.4/ShellCheck/Analytics.hs
+{-# LANGUAGE CPP #-}
+#ifndef DEBIAN_NO_GHCI
{-# LANGUAGE TemplateHaskell #-}
--module ShellCheck.Analytics (AnalysisOption(..), filterByAnnotation, runAnalytics, shellForExecutable, runTests) where
+-module ShellCheck.Analytics (AnalysisOptions(..), defaultAnalysisOptions, filterByAnnotation, runAnalytics, shellForExecutable, runTests) where
+#endif
-+module ShellCheck.Analytics (AnalysisOption(..), filterByAnnotation, runAnalytics, shellForExecutable
++module ShellCheck.Analytics (AnalysisOptions(..), defaultAnalysisOptions, filterByAnnotation, runAnalytics, shellForExecutable
+#ifndef DEBIAN_NO_GHCI
+ , runTests
+#endif
@@ -29,7 +29,7 @@ Index: ShellCheck-0.3.4/ShellCheck/Analytics.hs
import Control.Arrow (first)
import Control.Monad
-@@ -33,7 +40,9 @@
+@@ -34,7 +41,9 @@
import ShellCheck.Parser hiding (runTests)
import Text.Regex
import qualified Data.Map as Map
@@ -37,9 +37,9 @@ Index: ShellCheck-0.3.4/ShellCheck/Analytics.hs
import Test.QuickCheck.All (quickCheckAll)
+#endif
- data Shell = Ksh | Zsh | Sh | Bash
- deriving (Show, Eq)
-@@ -2880,6 +2889,8 @@
+ data Parameters = Parameters {
+ variableFlow :: [StackData],
+@@ -3012,6 +3021,8 @@
return $ param `elem` strs
warnFor t = warn (getId t) 2146 "This action ignores everything before the -o. Use \\( \\) to group."
@@ -48,16 +48,16 @@ Index: ShellCheck-0.3.4/ShellCheck/Analytics.hs
runTests = $quickCheckAll
+#endif
-Index: ShellCheck-0.3.4/ShellCheck/Parser.hs
+Index: ShellCheck-0.3.5/ShellCheck/Parser.hs
===================================================================
---- ShellCheck-0.3.4.orig/ShellCheck/Parser.hs 2014-10-23 21:56:44.000000000 +0200
-+++ ShellCheck-0.3.4/ShellCheck/Parser.hs 2014-10-23 22:09:34.000000000 +0200
+--- ShellCheck-0.3.5.orig/ShellCheck/Parser.hs 2014-12-30 21:44:59.000000000 +0100
++++ ShellCheck-0.3.5/ShellCheck/Parser.hs 2014-12-30 21:48:13.000000000 +0100
@@ -15,8 +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/>.
-}
-{-# LANGUAGE NoMonomorphismRestriction, TemplateHaskell #-}
--module ShellCheck.Parser (Note(..), Severity(..), parseShell, ParseResult(..), ParseNote(..), sortNotes, noteToParseNote, runTests) where
+-module ShellCheck.Parser (Note(..), Severity(..), parseShell, ParseResult(..), ParseNote(..), sortNotes, noteToParseNote, runTests, readScript) where
+{-# LANGUAGE CPP, NoMonomorphismRestriction #-}
+#ifndef DEBIAN_NO_GHCI
+{-# LANGUAGE TemplateHaskell #-}
@@ -66,7 +66,7 @@ Index: ShellCheck-0.3.4/ShellCheck/Parser.hs
+#ifndef DEBIAN_NO_GHCI
+ , runTests
+#endif
-+ ) where
++ , readScript) where
import ShellCheck.AST
import ShellCheck.Data
@@ -80,7 +80,7 @@ Index: ShellCheck-0.3.4/ShellCheck/Parser.hs
backslash = char '\\'
linefeed = optional carriageReturn >> char '\n'
-@@ -2094,6 +2103,8 @@
+@@ -2138,6 +2147,8 @@
lt x = trace (show x) x
ltt t = trace (show t)
@@ -89,10 +89,10 @@ Index: ShellCheck-0.3.4/ShellCheck/Parser.hs
runTests = $quickCheckAll
+#endif
-Index: ShellCheck-0.3.4/ShellCheck/Simple.hs
+Index: ShellCheck-0.3.5/ShellCheck/Simple.hs
===================================================================
---- ShellCheck-0.3.4.orig/ShellCheck/Simple.hs 2014-10-23 21:56:44.000000000 +0200
-+++ ShellCheck-0.3.4/ShellCheck/Simple.hs 2014-10-23 22:11:37.000000000 +0200
+--- ShellCheck-0.3.5.orig/ShellCheck/Simple.hs 2014-12-30 21:44:59.000000000 +0100
++++ ShellCheck-0.3.5/ShellCheck/Simple.hs 2014-12-30 21:52:22.000000000 +0100
@@ -15,15 +15,24 @@
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/>.
@@ -108,20 +108,20 @@ Index: ShellCheck-0.3.4/ShellCheck/Simple.hs
+#endif
+ ) where
- import ShellCheck.Parser hiding (runTests)
- import ShellCheck.Analytics hiding (runTests)
- import Data.Maybe
- import Text.Parsec.Pos
import Data.List
+ import Data.Maybe
+ import ShellCheck.Analytics hiding (runTests)
+ import ShellCheck.Options
+ import ShellCheck.Parser hiding (runTests)
+#ifndef DEBIAN_NO_GHCI
import Test.QuickCheck.All (quickCheckAll)
+#endif
+ import Text.Parsec.Pos
- shellCheck :: String -> [AnalysisOption] -> [ShellCheckComment]
- shellCheck script options =
-@@ -67,6 +76,7 @@
- prop_commentDisablesAnalysisIssue2 =
- null $ shellCheck "#shellcheck disable=SC2086\n#lol\necho $1" []
+ shellCheck :: AnalysisOptions -> String -> [ShellCheckComment]
+@@ -72,6 +81,7 @@
+ prop_optionDisablesIssue1 =
+ null $ shellCheck (defaultAnalysisOptions { optionExcludes = [2086, 2148] }) "echo $1"
+#ifndef DEBIAN_NO_GHCI
return []