bump to latest ghc

This commit is contained in:
Vanessa McHale 2018-04-02 11:44:18 -05:00
parent da4072a118
commit cf39adff75
3 changed files with 133 additions and 119 deletions

View File

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

View File

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

View File

@ -17,8 +17,8 @@
You should have received a copy of the GNU General Public License
along with this program. If not, see <https://www.gnu.org/licenses/>.
-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE TemplateHaskell #-}
module ShellCheck.AnalyzerLib where
import ShellCheck.AST
import ShellCheck.ASTLib
@ -34,11 +34,13 @@ import Control.Monad.State
import Control.Monad.Writer
import Data.Char
import Data.List
import Data.Maybe
import qualified Data.Map as Map
import Data.Maybe
import Data.Semigroup
import Test.QuickCheck.All (forAllProperties)
import Test.QuickCheck.Test (quickCheckWithResult, stdArgs, maxSuccess)
import Test.QuickCheck.Test (maxSuccess, quickCheckWithResult,
stdArgs)
type Analysis = AnalyzerM ()
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)
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
mempty = Checker {
perScript = nullCheck,
perToken = nullCheck
}
mappend x y = Checker {
perScript = perScript x `composeAnalyzers` perScript y,
perToken = perToken x `composeAnalyzers` perToken y
}
mappend = (Data.Semigroup.<>)
composeAnalyzers :: (a -> Analysis) -> (a -> Analysis) -> a -> Analysis
composeAnalyzers f g x = f x >> g x