Skip to content
This repository was archived by the owner on Oct 7, 2020. It is now read-only.

Commit 0fd7e3f

Browse files
Pawel Szulcfendor
Pawel Szulc
authored andcommitted
Remove compiler warnings
There were few functions with some constraints that were redundant. Those constraints got removed.
1 parent 94c4bb8 commit 0fd7e3f

File tree

4 files changed

+9
-12
lines changed

4 files changed

+9
-12
lines changed

hie-plugin-api/Haskell/Ide/Engine/ModuleCache.hs

+4-5
Original file line numberDiff line numberDiff line change
@@ -164,8 +164,7 @@ loadCradle publishDiagnostics iniDynFlags (NewCradle fp) def action = do
164164
where
165165
-- | Initialise the given cradle. This might fail and return an error via `IdeResultFail`.
166166
-- Reports its progress to the client.
167-
initialiseCradle :: (MonadIde m, HasGhcModuleCache m, GHC.GhcMonad m)
168-
=> Bios.Cradle -> (Progress -> IO ()) -> m (IdeResult a)
167+
initialiseCradle :: Bios.Cradle -> (Progress -> IO ()) -> m (IdeResult a)
169168
initialiseCradle cradle f = do
170169
res <- initializeFlagsWithCradleWithMessage (Just (toMessager f)) fp cradle
171170
case res of
@@ -333,7 +332,7 @@ ifCachedModuleM fp k callback = do
333332
-- available.
334333
-- If you are in IdeDeferM and would like to wait until a cached module is available,
335334
-- see also 'withCachedModuleAndData'.
336-
ifCachedModuleAndData :: forall a b m. (ModuleCache a, HasGhcModuleCache m, MonadIO m, MonadMTState IdeState m)
335+
ifCachedModuleAndData :: forall a b m. (ModuleCache a, HasGhcModuleCache m, MonadMTState IdeState m)
337336
=> FilePath -> b -> (GHC.TypecheckedModule -> CachedInfo -> a -> m b) -> m b
338337
ifCachedModuleAndData fp def callback = do
339338
muc <- getUriCache fp
@@ -388,7 +387,7 @@ deferIfNotCached fp cb = do
388387
Just res -> cb res
389388
Nothing -> wrap (Defer fp cb)
390389

391-
lookupCachedData :: forall a m. (HasGhcModuleCache m, MonadMTState IdeState m, MonadIO m, Typeable a, ModuleCache a)
390+
lookupCachedData :: forall a m. (HasGhcModuleCache m, MonadMTState IdeState m, ModuleCache a)
392391
=> FilePath -> GHC.TypecheckedModule -> CachedInfo -> (Map.Map TypeRep Dynamic) -> m a
393392
lookupCachedData fp tm info dat = do
394393
canonical_fp <- liftIO $ canonicalizePath fp
@@ -520,7 +519,7 @@ deleteCachedModule uri = do
520519
-- TODO: this name is confusing, given GhcModuleCache. Change it
521520
class Typeable a => ModuleCache a where
522521
-- | Defines an initial value for the state extension
523-
cacheDataProducer :: (MonadIO m, MonadMTState IdeState m)
522+
cacheDataProducer :: (MonadMTState IdeState m)
524523
=> GHC.TypecheckedModule -> CachedInfo -> m a
525524

526525
instance ModuleCache () where

hie-plugin-api/Haskell/Ide/Engine/PluginUtils.hs

+1-3
Original file line numberDiff line numberDiff line change
@@ -293,10 +293,8 @@ getRangeFromVFS uri rg = do
293293

294294
data ErrorHandler m a = forall e . Exception e => ErrorHandler (e -> m a)
295295

296-
gcatches :: forall m a . (MonadIO m, ExceptionMonad m) => m a -> [ErrorHandler m a] -> m a
296+
gcatches :: forall m a . (ExceptionMonad m) => m a -> [ErrorHandler m a] -> m a
297297
gcatches act handlers = gcatch act h
298298
where
299299
h :: SomeException -> m a
300300
h e = foldr (\(ErrorHandler hand) me -> maybe me hand (fromException e)) (liftIO $ throw e) handlers
301-
302-

hie-plugin-api/Haskell/Ide/Engine/PluginsIdeMonads.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -440,7 +440,7 @@ getPlugins = idePlugins <$> getIdeEnv
440440
-- | 'withProgress' @title cancellable f@ wraps a progress reporting session for long running tasks.
441441
-- f is passed a reporting function that can be used to give updates on the progress
442442
-- of the task.
443-
withProgress :: (MonadIde m , MonadIO m, MonadBaseControl IO m)
443+
withProgress :: (MonadIde m , MonadBaseControl IO m)
444444
=> T.Text -> Core.ProgressCancellable
445445
-> ((Core.Progress -> IO ()) -> m a) -> m a
446446
withProgress t c f = do

hie-plugin-api/Haskell/Ide/Engine/TypeMap.hs

+3-3
Original file line numberDiff line numberDiff line change
@@ -56,21 +56,21 @@ processBind _ = return IM.empty
5656
types :: forall m a . (GhcMonad m, Data a) => a -> m TypeMap
5757
types = everythingButTypeM @GHC.Id (ty `combineM` fun `combineM` funBind)
5858
where
59-
ty :: forall a' . (GhcMonad m, Data a') => a' -> m TypeMap
59+
ty :: forall a' . (Data a') => a' -> m TypeMap
6060
ty term = case cast term of
6161
(Just lhsExprGhc@(GHC.L (GHC.RealSrcSpan spn) _)) ->
6262
getType lhsExprGhc >>= \case
6363
Nothing -> return IM.empty
6464
Just (_, typ) -> return (IM.singleton (rspToInt spn) typ)
6565
_ -> return IM.empty
6666

67-
fun :: forall a' . (GhcMonad m, Data a') => a' -> m TypeMap
67+
fun :: forall a' . (Data a') => a' -> m TypeMap
6868
fun term = case cast term of
6969
(Just (GHC.L (GHC.RealSrcSpan spn) hsPatType)) ->
7070
return (IM.singleton (rspToInt spn) (TcHsSyn.hsPatType hsPatType))
7171
_ -> return IM.empty
7272

73-
funBind :: forall a' . (GhcMonad m, Data a') => a' -> m TypeMap
73+
funBind :: forall a' . (Data a') => a' -> m TypeMap
7474
funBind term = case cast term of
7575
(Just (GHC.L (GHC.RealSrcSpan spn) (Compat.FunBindType t))) ->
7676
return (IM.singleton (rspToInt spn) t)

0 commit comments

Comments
 (0)