Merge pull request #1168 from vmchale/master

Bump to ghc 8.4.1
This commit is contained in:
Vidar Holen 2018-04-22 14:10:25 -07:00 committed by GitHub
commit ce7658ed86
No known key found for this signature in database
GPG Key ID: 4AEE18F83AFDEB23
3 changed files with 136 additions and 123 deletions

View File

@ -43,6 +43,9 @@ source-repository head
library library
hs-source-dirs: src hs-source-dirs: src
if impl(ghc < 8.0)
build-depends:
semigroups
build-depends: build-depends:
-- GHC 7.6.3 (base 4.6.0.1) is buggy (#1131, #1119) in optimized mode. -- GHC 7.6.3 (base 4.6.0.1) is buggy (#1131, #1119) in optimized mode.
-- Just disable that version entirely to fail fast. -- Just disable that version entirely to fail fast.
@ -78,6 +81,9 @@ library
Paths_ShellCheck Paths_ShellCheck
executable shellcheck executable shellcheck
if impl(ghc < 8.0)
build-depends:
semigroups
build-depends: build-depends:
base >= 4 && < 5, base >= 4 && < 5,
ShellCheck, ShellCheck,

View File

@ -17,13 +17,13 @@
You should have received a copy of the GNU General Public License You should have received a copy of the GNU General Public License
along with this program. If not, see <https://www.gnu.org/licenses/>. along with this program. If not, see <https://www.gnu.org/licenses/>.
-} -}
import ShellCheck.Data
import ShellCheck.Checker import ShellCheck.Checker
import ShellCheck.Data
import ShellCheck.Interface import ShellCheck.Interface
import ShellCheck.Regex import ShellCheck.Regex
import ShellCheck.Formatter.Format
import qualified ShellCheck.Formatter.CheckStyle import qualified ShellCheck.Formatter.CheckStyle
import ShellCheck.Formatter.Format
import qualified ShellCheck.Formatter.GCC import qualified ShellCheck.Formatter.GCC
import qualified ShellCheck.Formatter.JSON import qualified ShellCheck.Formatter.JSON
import qualified ShellCheck.Formatter.TTY import qualified ShellCheck.Formatter.TTY
@ -40,6 +40,7 @@ import Data.List
import qualified Data.Map as Map import qualified Data.Map as Map
import Data.Maybe import Data.Maybe
import Data.Monoid import Data.Monoid
import Data.Semigroup (Semigroup (..))
import Prelude hiding (catch) import Prelude hiding (catch)
import System.Console.GetOpt import System.Console.GetOpt
import System.Directory import System.Directory
@ -56,9 +57,12 @@ data Status =
| RuntimeException | RuntimeException
deriving (Ord, Eq, Show) deriving (Ord, Eq, Show)
instance Semigroup Status where
(<>) = max
instance Monoid Status where instance Monoid Status where
mempty = NoProblems mempty = NoProblems
mappend = max mappend = (Data.Semigroup.<>)
data Options = Options { data Options = Options {
checkSpec :: CheckSpec, checkSpec :: CheckSpec,
@ -203,7 +207,7 @@ runFormatter sys format options files = do
process :: FilePath -> IO Status process :: FilePath -> IO Status
process filename = do process filename = do
input <- (siReadFile sys) filename input <- siReadFile sys filename
either (reportFailure filename) check input either (reportFailure filename) check input
where where
check contents = do check contents = do

View File

@ -17,8 +17,8 @@
You should have received a copy of the GNU General Public License You should have received a copy of the GNU General Public License
along with this program. If not, see <https://www.gnu.org/licenses/>. along with this program. If not, see <https://www.gnu.org/licenses/>.
-} -}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TemplateHaskell #-}
module ShellCheck.AnalyzerLib where module ShellCheck.AnalyzerLib where
import ShellCheck.AST import ShellCheck.AST
import ShellCheck.ASTLib import ShellCheck.ASTLib
@ -34,11 +34,13 @@ import Control.Monad.State
import Control.Monad.Writer import Control.Monad.Writer
import Data.Char import Data.Char
import Data.List import Data.List
import Data.Maybe
import qualified Data.Map as Map import qualified Data.Map as Map
import Data.Maybe
import Data.Semigroup
import Test.QuickCheck.All (forAllProperties) import Test.QuickCheck.All (forAllProperties)
import Test.QuickCheck.Test (quickCheckWithResult, stdArgs, maxSuccess) import Test.QuickCheck.Test (maxSuccess, quickCheckWithResult,
stdArgs)
type Analysis = AnalyzerM () type Analysis = AnalyzerM ()
type AnalyzerM a = RWS Parameters [TokenComment] Cache a type AnalyzerM a = RWS Parameters [TokenComment] Cache a
@ -57,16 +59,18 @@ runChecker params checker = notes
check = perScript checker `composeAnalyzers` (\(Root x) -> void $ doAnalysis (perToken checker) x) check = perScript checker `composeAnalyzers` (\(Root x) -> void $ doAnalysis (perToken checker) x)
notes = snd $ evalRWS (check $ Root root) params Cache notes = snd $ evalRWS (check $ Root root) params Cache
instance Semigroup Checker where
(<>) x y = Checker {
perScript = perScript x `composeAnalyzers` perScript y,
perToken = perToken x `composeAnalyzers` perToken y
}
instance Monoid Checker where instance Monoid Checker where
mempty = Checker { mempty = Checker {
perScript = nullCheck, perScript = nullCheck,
perToken = nullCheck perToken = nullCheck
} }
mappend x y = Checker { mappend = (Data.Semigroup.<>)
perScript = perScript x `composeAnalyzers` perScript y,
perToken = perToken x `composeAnalyzers` perToken y
}
composeAnalyzers :: (a -> Analysis) -> (a -> Analysis) -> a -> Analysis composeAnalyzers :: (a -> Analysis) -> (a -> Analysis) -> a -> Analysis
composeAnalyzers f g x = f x >> g x composeAnalyzers f g x = f x >> g x
@ -462,7 +466,7 @@ getModifiedVariables t =
_ -> Nothing _ -> Nothing
guard . not . null $ str guard . not . null $ str
return (t, token, str, DataString $ SourceChecked) return (t, token, str, DataString SourceChecked)
T_DollarBraced _ l -> maybeToList $ do T_DollarBraced _ l -> maybeToList $ do
let string = bracedString t let string = bracedString t
@ -687,9 +691,8 @@ isCommand token str = isCommandMatch token (\cmd -> cmd == str || ('/' : str) `
-- Compare a command to a literal. Like above, but checks full path. -- Compare a command to a literal. Like above, but checks full path.
isUnqualifiedCommand token str = isCommandMatch token (== str) isUnqualifiedCommand token str = isCommandMatch token (== str)
isCommandMatch token matcher = fromMaybe False $ do isCommandMatch token matcher = fromMaybe False $
cmd <- getCommandName token fmap matcher (getCommandName token)
return $ matcher cmd
-- Does this regex look like it was intended as a glob? -- Does this regex look like it was intended as a glob?
-- True: *foo* -- True: *foo*