From: Helmut Grohne <helmut@subdivi.de>
Subject: make TemplateHaskell usage optional
Last-Update: 2014-10-23

The only use of TemplateHaskell in ShellCheck is for collecting QuickCheck
properties. Unfortunately this means that the main ShellCheck modules do not
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
===================================================================
--- 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
@@ -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 CPP #-}
+#ifndef DEBIAN_NO_GHCI
 {-# LANGUAGE TemplateHaskell #-}
-module ShellCheck.Analytics (AnalysisOption(..), filterByAnnotation, runAnalytics, shellForExecutable, runTests) where
+#endif
+module ShellCheck.Analytics (AnalysisOption(..), filterByAnnotation, runAnalytics, shellForExecutable
+#ifndef DEBIAN_NO_GHCI
+	, runTests
+#endif
+	) where
 
 import Control.Arrow (first)
 import Control.Monad
@@ -33,7 +40,9 @@
 import ShellCheck.Parser hiding (runTests)
 import Text.Regex
 import qualified Data.Map as Map
+#ifndef DEBIAN_NO_GHCI
 import Test.QuickCheck.All (quickCheckAll)
+#endif
 
 data Shell = Ksh | Zsh | Sh | Bash
     deriving (Show, Eq)
@@ -2880,6 +2889,8 @@
         return $ param `elem` strs
     warnFor t = warn (getId t) 2146 "This action ignores everything before the -o. Use \\( \\) to group."
 
+#ifndef DEBIAN_NO_GHCI
 return []
 runTests = $quickCheckAll
+#endif
 
Index: ShellCheck-0.3.4/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
@@ -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
+{-# LANGUAGE CPP, NoMonomorphismRestriction #-}
+#ifndef DEBIAN_NO_GHCI
+{-# LANGUAGE TemplateHaskell #-}
+#endif
+module ShellCheck.Parser (Note(..), Severity(..), parseShell, ParseResult(..), ParseNote(..), sortNotes, noteToParseNote
+#ifndef DEBIAN_NO_GHCI
+	, runTests
+#endif
+	) where
 
 import ShellCheck.AST
 import ShellCheck.Data
@@ -33,7 +40,9 @@
 import System.IO
 import Text.Parsec.Error
 import GHC.Exts (sortWith)
+#ifndef DEBIAN_NO_GHCI
 import Test.QuickCheck.All (quickCheckAll)
+#endif
 
 backslash = char '\\'
 linefeed = optional carriageReturn >> char '\n'
@@ -2094,6 +2103,8 @@
 lt x = trace (show x) x
 ltt t = trace (show t)
 
+#ifndef DEBIAN_NO_GHCI
 return []
 runTests = $quickCheckAll
+#endif
 
Index: ShellCheck-0.3.4/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
@@ -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/>.
 -}
+{-# LANGUAGE CPP #-}
+#ifndef DEBIAN_NO_GHCI
 {-# LANGUAGE TemplateHaskell #-}
-module ShellCheck.Simple (shellCheck, ShellCheckComment, scLine, scColumn, scSeverity, scCode, scMessage, runTests) where
+#endif
+module ShellCheck.Simple (shellCheck, ShellCheckComment, scLine, scColumn, scSeverity, scCode, scMessage
+#ifndef DEBIAN_NO_GHCI
+	, runTests
+#endif
+	) where
 
 import ShellCheck.Parser hiding (runTests)
 import ShellCheck.Analytics hiding (runTests)
 import Data.Maybe
 import Text.Parsec.Pos
 import Data.List
+#ifndef DEBIAN_NO_GHCI
 import Test.QuickCheck.All (quickCheckAll)
+#endif
 
 shellCheck :: String -> [AnalysisOption] -> [ShellCheckComment]
 shellCheck script options =
@@ -67,6 +76,7 @@
 prop_commentDisablesAnalysisIssue2 =
     null $ shellCheck "#shellcheck disable=SC2086\n#lol\necho $1" []
 
+#ifndef DEBIAN_NO_GHCI
 return []
 runTests = $quickCheckAll
-
+#endif
