Skip to content

Commit

Permalink
Fix GHC 8 warnings from -Wredundant-constraints
Browse files Browse the repository at this point in the history
  • Loading branch information
Blaisorblade committed Aug 4, 2016
1 parent e7c7b0b commit 544d351
Show file tree
Hide file tree
Showing 6 changed files with 9 additions and 9 deletions.
6 changes: 3 additions & 3 deletions src/Stack/Build/Cache.hs
Original file line number Diff line number Diff line change
Expand Up @@ -114,7 +114,7 @@ instance Store BuildCache
instance NFData BuildCache

-- | Try to read the dirtiness cache for the given package directory.
tryGetBuildCache :: (MonadIO m, MonadReader env m, HasConfig env, MonadThrow m, MonadLogger m, HasEnvConfig env, MonadBaseControl IO m)
tryGetBuildCache :: (MonadIO m, MonadReader env m, MonadThrow m, MonadLogger m, HasEnvConfig env, MonadBaseControl IO m)
=> Path Abs Dir -> m (Maybe (Map FilePath FileCacheInfo))
tryGetBuildCache = liftM (fmap buildCacheTimes) . tryGetCache buildCacheFile

Expand Down Expand Up @@ -174,7 +174,7 @@ deleteCaches dir = do
ignoringAbsence (removeFile cfp)

-- | Write to a cache.
writeCache :: (Store a, NFData a, HasTypeHash a, Eq a, MonadIO m, MonadLogger m)
writeCache :: (Store a, HasTypeHash a, Eq a, MonadIO m, MonadLogger m)
=> Path Abs Dir
-> (Path Abs Dir -> m (Path Abs File))
-> a
Expand Down Expand Up @@ -202,7 +202,7 @@ tryGetFlagCache gid = do
fp <- flagCacheFile gid
decodeFileMaybe fp

writeFlagCache :: (MonadIO m, MonadReader env m, HasEnvConfig env, MonadThrow m, MonadLogger m, MonadBaseControl IO m)
writeFlagCache :: (MonadIO m, MonadReader env m, HasEnvConfig env, MonadThrow m, MonadLogger m)
=> Installed
-> ConfigCache
-> m ()
Expand Down
2 changes: 1 addition & 1 deletion src/Stack/Build/ConstructPlan.hs
Original file line number Diff line number Diff line change
Expand Up @@ -124,7 +124,7 @@ instance HasEnvConfig Ctx where
getEnvConfig = ctxEnvConfig

constructPlan :: forall env m.
(MonadCatch m, MonadReader env m, HasEnvConfig env, MonadIO m, MonadLoggerIO m, MonadBaseControl IO m, HasHttpManager env)
(MonadCatch m, MonadReader env m, HasEnvConfig env, MonadLoggerIO m, MonadBaseControl IO m, HasHttpManager env)
=> MiniBuildPlan
-> BaseConfigOpts
-> [LocalPackage]
Expand Down
4 changes: 2 additions & 2 deletions src/Stack/Ghci.hs
Original file line number Diff line number Diff line change
Expand Up @@ -111,7 +111,7 @@ instance Show GhciException where
-- given options and configure it with the load paths and extensions
-- of those targets.
ghci
:: (HasBuildConfig r, HasHttpManager r, MonadMask m, HasLogLevel r, HasTerminal r, HasEnvConfig r, MonadReader r m, MonadIO m, MonadLoggerIO m, MonadBaseUnlift IO m)
:: (HasBuildConfig r, HasHttpManager r, MonadMask m, HasLogLevel r, HasTerminal r, HasEnvConfig r, MonadReader r m, MonadLoggerIO m, MonadBaseUnlift IO m)
=> GhciOpts -> m ()
ghci opts@GhciOpts{..} = do
bopts <- asks (configBuild . getConfig)
Expand Down Expand Up @@ -276,7 +276,7 @@ figureOutMainFile bopts mainIsTargets targets0 packages =
-- | Create a list of infos for each target containing necessary
-- information to load that package/components.
ghciSetup
:: (HasHttpManager r, HasBuildConfig r, MonadMask m, HasTerminal r, HasLogLevel r, HasEnvConfig r, MonadReader r m, MonadIO m, MonadLoggerIO m, MonadBaseUnlift IO m)
:: (HasHttpManager r, HasBuildConfig r, MonadMask m, HasTerminal r, HasLogLevel r, HasEnvConfig r, MonadReader r m, MonadLoggerIO m, MonadBaseUnlift IO m)
=> GhciOpts
-> m (Map PackageName SimpleTarget, Maybe (Map PackageName SimpleTarget), [GhciPkgInfo])
ghciSetup GhciOpts{..} = do
Expand Down
2 changes: 1 addition & 1 deletion src/Stack/New.hs
Original file line number Diff line number Diff line change
Expand Up @@ -129,7 +129,7 @@ data TemplateFrom = LocalTemp | RemoteTemp
-- | Download and read in a template's text content.
loadTemplate
:: forall m r.
(HasConfig r, HasHttpManager r, MonadReader r m, MonadIO m, MonadThrow m, MonadCatch m, MonadLogger m)
(HasConfig r, HasHttpManager r, MonadReader r m, MonadIO m, MonadCatch m, MonadLogger m)
=> TemplateName -> (TemplateFrom -> m ()) -> m Text
loadTemplate name logIt = do
templateDir <- asks (templatesDir . getConfig)
Expand Down
2 changes: 1 addition & 1 deletion src/Stack/Types/StackT.hs
Original file line number Diff line number Diff line change
Expand Up @@ -227,7 +227,7 @@ stickyLoggerFunc loc src level msg = do
liftIO $ func loc src level msg

getStickyLoggerFunc
:: (HasSticky r, HasLogLevel r, HasSupportsUnicode r, ToLogStr msg, MonadReader r m, MonadIO m)
:: (HasSticky r, HasLogLevel r, HasSupportsUnicode r, ToLogStr msg, MonadReader r m)
=> m (Loc -> LogSource -> LogLevel -> msg -> IO ())
getStickyLoggerFunc = do
sticky <- asks getSticky
Expand Down
2 changes: 1 addition & 1 deletion src/test/Stack/StoreSpec.hs
Original file line number Diff line number Diff line change
Expand Up @@ -45,7 +45,7 @@ instance Monad m => Serial m BS.ByteString where
instance (Monad m, Serial m a, Ord a) => Serial m (Set a) where
series = fmap setFromList series

addMinAndMaxBounds :: forall a. (Bounded a, Eq a, Num a) => [a] -> [a]
addMinAndMaxBounds :: forall a. (Bounded a, Eq a) => [a] -> [a]
addMinAndMaxBounds xs =
(if (minBound :: a) `notElem` xs then [minBound] else []) ++
(if (maxBound :: a) `notElem` xs && (maxBound :: a) /= minBound then maxBound : xs else xs)
Expand Down

0 comments on commit 544d351

Please sign in to comment.