From: Helmut Grohne Subject: make TemplateHaskell usage optional Last-Update: 2016-08-13 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). --- a/ShellCheck/Analytics.hs +++ b/ShellCheck/Analytics.hs @@ -17,8 +17,16 @@ You should have received a copy of the GNU General Public License along with this program. If not, see . -} -{-# LANGUAGE TemplateHaskell, FlexibleContexts #-} -module ShellCheck.Analytics (runAnalytics, ShellCheck.Analytics.runTests) where +{-# LANGUAGE CPP #-} +{-# LANGUAGE FlexibleContexts #-} +#ifndef DEBIAN_NO_GHCI +{-# LANGUAGE TemplateHaskell #-} +#endif +module ShellCheck.Analytics (runAnalytics +#ifndef DEBIAN_NO_GHCI + , ShellCheck.Analytics.runTests +#endif + ) where import ShellCheck.AST import ShellCheck.ASTLib @@ -42,7 +50,9 @@ import Data.Ord import Debug.Trace import qualified Data.Map as Map +#ifndef DEBIAN_NO_GHCI import Test.QuickCheck.All (forAllProperties) +#endif import Test.QuickCheck.Test (quickCheckWithResult, stdArgs, maxSuccess) -- Checks that are run on the AST root @@ -2737,5 +2747,7 @@ warn id 2205 "(..) is a subshell. Did you mean [ .. ], a test expression?" +#ifndef DEBIAN_NO_GHCI return [] runTests = $( [| $(forAllProperties) (quickCheckWithResult (stdArgs { maxSuccess = 1 }) ) |]) +#endif --- a/ShellCheck/Parser.hs +++ b/ShellCheck/Parser.hs @@ -17,8 +17,15 @@ yOU should have received a copy of the GNU General Public License along with this program. If not, see . -} -{-# LANGUAGE NoMonomorphismRestriction, TemplateHaskell, FlexibleContexts #-} -module ShellCheck.Parser (parseScript, runTests) where +{-# LANGUAGE CPP, NoMonomorphismRestriction, FlexibleContexts #-} +#ifndef DEBIAN_NO_GHCI +{-# LANGUAGE TemplateHaskell #-} +#endif +module ShellCheck.Parser (parseScript +#ifndef DEBIAN_NO_GHCI + , runTests +#endif + ) where import ShellCheck.AST import ShellCheck.ASTLib @@ -45,7 +52,9 @@ import qualified Control.Monad.State as Ms import qualified Data.Map as Map +#ifndef DEBIAN_NO_GHCI import Test.QuickCheck.All (quickCheckAll) +#endif type SCBase m = Mr.ReaderT (SystemInterface m) (Ms.StateT SystemState m) type SCParser m v = ParsecT String UserState (SCBase m) v @@ -2835,6 +2844,8 @@ lt x = trace (show x) x ltt t = trace (show t) +#ifndef DEBIAN_NO_GHCI return [] runTests = $quickCheckAll +#endif --- a/ShellCheck/AnalyzerLib.hs +++ b/ShellCheck/AnalyzerLib.hs @@ -17,7 +17,10 @@ You should have received a copy of the GNU General Public License along with this program. If not, see . -} +{-# LANGUAGE CPP #-} +#ifndef DEBIAN_NO_GHCI {-# LANGUAGE TemplateHaskell #-} +#endif {-# LANGUAGE FlexibleContexts #-} module ShellCheck.AnalyzerLib where import ShellCheck.AST --- a/ShellCheck/Checker.hs +++ b/ShellCheck/Checker.hs @@ -17,8 +17,15 @@ You should have received a copy of the GNU General Public License along with this program. If not, see . -} +{-# LANGUAGE CPP #-} +#ifndef DEBIAN_NO_GHCI {-# LANGUAGE TemplateHaskell #-} -module ShellCheck.Checker (checkScript, ShellCheck.Checker.runTests) where +#endif +module ShellCheck.Checker (checkScript +#ifndef DEBIAN_NO_GHCI + , ShellCheck.Checker.runTests +#endif + ) where import ShellCheck.Interface import ShellCheck.Parser @@ -35,7 +42,9 @@ import Prelude hiding (readFile) import Control.Monad +#ifndef DEBIAN_NO_GHCI import Test.QuickCheck.All +#endif tokenToPosition map (TokenComment id c) = fromMaybe fail $ do position <- Map.lookup id map @@ -178,5 +187,7 @@ prop_filewideAnnotation8 = null $ check "# Disable $? warning\n#shellcheck disable=SC2181\n# Disable quoting warning\n#shellcheck disable=2086\ntrue\n[ $? == 0 ] && echo $1" +#ifndef DEBIAN_NO_GHCI return [] runTests = $quickCheckAll +#endif --- a/ShellCheck/Checks/Commands.hs +++ b/ShellCheck/Checks/Commands.hs @@ -17,7 +17,10 @@ You should have received a copy of the GNU General Public License along with this program. If not, see . -} +{-# LANGUAGE CPP #-} +#ifndef DEBIAN_NO_GHCI {-# LANGUAGE TemplateHaskell #-} +#endif {-# LANGUAGE FlexibleContexts #-} -- This module contains checks that examine specific commands by name. @@ -681,5 +684,7 @@ checkDeprecatedFgrep = CommandCheck (Basename "fgrep") $ \t -> info (getId t) 2197 "fgrep is non-standard and deprecated. Use grep -F instead." +#ifndef DEBIAN_NO_GHCI return [] runTests = $( [| $(forAllProperties) (quickCheckWithResult (stdArgs { maxSuccess = 1 }) ) |]) +#endif