Here are some build errors that I've noticed:
`HsYAML` ([PR](https://github.c…om/haskell-hvr/HsYAML/pull/60)):
```
src/Data/YAML/Loader.hs:60:30: error:
Not in scope: type constructor or class ‘MonadFix’
Perhaps you meant ‘MonadFail’ (imported from Util)
|
60 | decodeLoader :: forall n m . MonadFix m => Loader m n -> BS.L.ByteString -> m (Either (YE.Pos, String) [n])
| ^^^^^^^^
src/Data/YAML/Loader.hs:159:29: error:
Not in scope: type constructor or class ‘MonadFix’
Perhaps you meant ‘MonadFail’ (imported from Util)
|
159 | , MonadFix
| ^^^^^^^^
```
`algebraic-graphs` (note: bounds seem sufficient):
```
src/Algebra/Graph/NonEmpty.hs:690:93: error:
• Variable not in scope:
liftM2
:: (a1 -> b1 -> (a1, b1))
-> NonEmpty (a, a) -> NonEmpty (b, b) -> NonEmpty ((a, a), (b, b))
• Perhaps you meant ‘lift’ (imported from Control.Monad.State)
|
690 | appendNonEmpty (fmap (\((a1,a2),(b1,b2)) -> ((a1, b1), [(a1, b2), (a2, b1)])) $ liftM2 (,) ipxs' ipys') $
| ^^^^^^
src/Algebra/Graph/NonEmpty.hs:713:7: error:
• Variable not in scope:
liftM2
:: (a0 -> b0 -> (a0, b0))
-> NonEmpty (a, a) -> NonEmpty (b, b) -> NonEmpty ((a, a), (b, b))
• Perhaps you meant ‘lift’ (imported from Control.Monad.State)
|
713 | $ liftM2 (,) (pairs1 xs) (pairs1 ys)
| ^^^^^^
```
`happy` ([bounds are fixed](https://github.com/haskell/happy/issues/236), needs patch):
```
src/Grammar.lhs:470:27: error:
Variable not in scope: when :: Bool -> M () -> t
|
470 | > checkArity x = when (x > arity) $ addErr (show x++" out of range")
| ^^^^
```
`lucid` ([bounds are fixed](https://github.com/chrisdone/lucid/issues/131), needs patch):
```
src/Lucid/Base.hs:164:10: error:
Not in scope: type constructor or class ‘MonadFix’
Perhaps you meant ‘MonadFail’ (imported from Prelude)
|
164 | instance MonadFix m => MonadFix (HtmlT m) where
| ^^^^^^^^
src/Lucid/Base.hs:195:23: error:
Not in scope: type constructor or class ‘MonadIO’
Perhaps you meant ‘Monad’ (imported from Prelude)
|
195 | instance MonadIO m => MonadIO (HtmlT m) where
| ^^^^^^^
```
`regex-tdfa` (bounds are sufficient, no compatible version yet):
```
lib/Text/Regex/TDFA/CorePattern.hs:207:34: error:
• Variable not in scope:
liftM2 :: (a1 -> a1 -> a1) -> Maybe Int -> Maybe Int -> Maybe Int
• Perhaps you meant ‘lift’ (imported from Control.Monad.RWS)
|
207 | seqTake (x1,y1) (x2,y2) = (x1+x2,liftM2 (+) y1 y2)
| ^^^^^^
lib/Text/Regex/TDFA/CorePattern.hs:468:39: error:
• Variable not in scope:
replicateM
:: Int
-> PM HandleTag
-> RWST
(Maybe GroupIndex)
[Either Tag GroupInfo]
([OP] -> [OP], Tag)
Data.Functor.Identity.Identity
[HandleTag]
• Perhaps you meant ‘replicate’ (imported from Prelude)
|
468 | bs <- fmap (++[bAdvice]) $ replicateM (pred $ length branches) newUniq -- 2 <= length ps
| ^^^^^^^^^^
lib/Text/Regex/TDFA/CorePattern.hs:470:18: error:
Variable not in scope:
forM
:: [(Pattern, HandleTag)]
-> ((Pattern, HandleTag) -> PM Q)
-> RWST
(Maybe GroupIndex)
[Either Tag GroupInfo]
([OP] -> [OP], Tag)
Data.Functor.Identity.Identity
[Q]
|
470 | qs <- forM (zip branches bs) (\(branch,bTag) -> (go branch aAdvice bTag))
| ^^^^
```
`tasty` ([patch](https://github.com/UnkindPartition/tasty/pull/318)):
```
Test/Tasty/Patterns/Eval.hs:122:29: error:
• Variable not in scope:
(<=<)
:: (Value -> M Int)
-> (Expr -> M Value) -> Expr -> ReaderT Path (Either String) Int
• Perhaps you meant one of these:
‘=<<’ (imported from Prelude), ‘<=’ (imported from Prelude)
|
122 | mb_n <- traverse (asN <=< eval) mb_e3
| ^^^
```
---
**EDIT:** More breakage
`pattern-arrows` ([bounds are fixed](https://github.com/paf31/pattern-arrows/issues/3)):
```
src/Control/PatternArrows.hs:65:16: error:
Variable not in scope:
fix :: (Pattern u a r -> Pattern u a r) -> Pattern u a r
|
65 | chainl g f p = fix $ \c -> g >>> ((c <+> p) *** p) >>> A.arr (uncurry f)
| ^^^
src/Control/PatternArrows.hs:71:16: error:
Variable not in scope:
fix :: (Pattern u a r -> Pattern u a r) -> Pattern u a r
|
71 | chainr g f p = fix $ \c -> g >>> (p *** (c <+> p)) >>> A.arr (uncurry f)
| ^^^
src/Control/PatternArrows.hs:77:14: error:
Variable not in scope:
fix :: (Pattern u a r -> Pattern u a r) -> Pattern u a r
|
77 | wrap g f p = fix $ \c -> g >>> (C.id *** (c <+> p)) >>> A.arr (uncurry f)
| ^^^
```
`aeson-better-errors` ([bounds are fixed](https://github.com/hdgarrood/aeson-better-errors/issues/20), needs patch):
```
src/Data/Aeson/BetterErrors/Internal.hs:431:3: error:
• Variable not in scope:
forM
:: [(a0, A.Value)]
-> ((Int, A.Value) -> ParseT err m a) -> ParseT err m [a]
• Perhaps you meant one of these:
‘V.forM’ (imported from Data.Vector),
‘V.forM_’ (imported from Data.Vector),
‘V.iforM’ (imported from Data.Vector)
Perhaps you want to add ‘forM’ to the import list in the import of
‘Data.Vector’ (src/Data/Aeson/BetterErrors/Internal.hs:32:1-25).
|
431 | forM xs $ \(i, x) ->
| ^^^^
src/Data/Aeson/BetterErrors/Internal.hs:439:3: error:
• Variable not in scope:
forM
:: [(Text, A.Value)]
-> ((Text, A.Value) -> ParseT err m a) -> ParseT err m [a]
• Perhaps you meant one of these:
‘V.forM’ (imported from Data.Vector),
‘V.forM_’ (imported from Data.Vector),
‘V.iforM’ (imported from Data.Vector)
Perhaps you want to add ‘forM’ to the import list in the import of
‘Data.Vector’ (src/Data/Aeson/BetterErrors/Internal.hs:32:1-25).
|
439 | forM xs $ \(k, x) ->
| ^^^^
```
`mfsolve` ([bounds are fixed](https://github.com/kuribas/mfsolve/issues/9), needs patch):
```
Math/MFSolve.hs:265:68: error:
Not in scope: type constructor or class ‘MonadIO’
Perhaps you meant ‘Monad’ (imported from Prelude)
|
265 | deriving (Functor, Applicative, Monad, MonadIO, MonadState (Dependencies v n),
| ^^^^^^^
```
`bytes` (bounds seem sufficient, has compatible release):
```
src/Data/Bytes/Get.hs:232:5: error:
Variable not in scope: unless :: Bool -> m14 a42 -> B.Get a43
|
232 | unless (Strict.length bs >= n) $ Fail.fail "ensure: Required more bytes"
| ^^^^^^
src/Data/Bytes/Get.hs:319:45: error:
• Variable not in scope:
liftM
:: (Either c16 c16 -> c16)
-> m12 (Either a38 b37) -> m (Maybe a, s)
• Perhaps you meant ‘lift’ (imported from Control.Monad.Writer.Strict)
|
319 | lookAheadM (Lazy.StateT m) = Lazy.StateT (liftM factor . lookAheadE . liftM distribute . m)
| ^^^^^
```
`logict` (bounds seem sufficient, no compatible version yet):
```
Control/Monad/Logic/Class.hs:30:8: error:
Not in scope: type constructor or class ‘MonadPlus’
|
30 | class (MonadPlus m) => MonadLogic m where
| ^^^^^^^^^
```
`monad-par` ([bounds are fixed](https://github.com/simonmar/monad-par/issues/74), needs patch):
<details>
```
Control/Monad/Par/Scheds/Direct.hs:210:3: error:
Variable not in scope: when :: Bool -> IO () -> IO a1
|
210 | when dbg $ case mb of
| ^^^^
Control/Monad/Par/Scheds/Direct.hs:220:3: error:
Variable not in scope: when :: Bool -> IO () -> IO a3
|
220 | when dbg $ do sn <- makeStableName task
| ^^^^
Control/Monad/Par/Scheds/Direct.hs:234:3: error:
Variable not in scope: when :: Bool -> IO () -> IO ()
|
234 | when (not (Prelude.null idles)) $ do
| ^^^^
Control/Monad/Par/Scheds/Direct.hs:235:5: error:
Variable not in scope: when :: Bool -> t1 -> IO a2
|
235 | when dbg$ printf "Waking %d idle thread(s).\n" (length idles)
| ^^^^
Control/Monad/Par/Scheds/Direct.hs:272:24: error:
Variable not in scope: when :: Bool -> Par () -> Par a23
|
272 | let userComp' = do when dbg$ io$ do
| ^^^^
Control/Monad/Par/Scheds/Direct.hs:278:31: error:
Variable not in scope: when :: Bool -> IO () -> IO a24
|
278 | io$ do when (dbglvl>=1) $ do
| ^^^^
Control/Monad/Par/Scheds/Direct.hs:287:28: error:
• Variable not in scope:
liftIO :: IO Bool -> RD.ReaderT Sched IO t12
• Perhaps you meant one of these:
‘lift’ (imported from Control.Monad.Cont),
‘liftA’ (imported from Control.Applicative),
‘liftA2’ (imported from Control.Applicative)
|
287 | loop n = do flg <- liftIO$ readIORef newFlag
| ^^^^^^
Control/Monad/Par/Scheds/Direct.hs:288:21: error:
Variable not in scope:
unless :: t12 -> RD.ReaderT Sched IO () -> RD.ReaderT Sched IO ()
|
288 | unless flg $ do
| ^^^^^^
Control/Monad/Par/Scheds/Direct.hs:289:23: error:
Variable not in scope:
when :: Bool -> t13 -> RD.ReaderT Sched IO a22
|
289 | when dbg $ liftIO$ do
| ^^^^
Control/Monad/Par/Scheds/Direct.hs:289:34: error:
• Variable not in scope: liftIO :: IO () -> t13
• Perhaps you meant one of these:
‘lift’ (imported from Control.Monad.Cont),
‘liftA’ (imported from Control.Applicative),
‘liftA2’ (imported from Control.Applicative)
|
289 | when dbg $ liftIO$ do
| ^^^^^^
Control/Monad/Par/Scheds/Direct.hs:301:5: error:
Variable not in scope: when :: Bool -> IO () -> IO a25
|
301 | when (dbglvl>=1)$ do
| ^^^^
Control/Monad/Par/Scheds/Direct.hs:350:8: error:
Variable not in scope: when :: Bool -> t14 -> IO a26
|
350 | when (dbglvl>=1)$ printf " [%d %s] runPar called from existing worker thread, new session (%d)....\n" (no sched) (show tid) (sid0 + 1)
| ^^^^
Control/Monad/Par/Scheds/Direct.hs:361:21: error:
• Variable not in scope:
forM
:: [(a34, Sched)]
-> ((Int, Sched) -> IO (Maybe (MVar Int))) -> IO [Maybe a32]
• Perhaps you meant one of these:
‘PC.fork’ (imported from Control.Monad.Par.Class),
‘fork’ (line 576)
|
361 | doneFlags <- forM (zip [0..] allscheds) $ \(cpu,sched) -> do
| ^^^^
Control/Monad/Par/Scheds/Direct.hs:371:26: error:
Variable not in scope: when :: Bool -> t15 -> IO a27
|
371 | then do when dbg$ printf " [%d %s] Anonymous worker entering scheduling loop.\n" cpu (show tid2)
| ^^^^
Control/Monad/Par/Scheds/Direct.hs:373:26: error:
Variable not in scope: when :: Bool -> t16 -> IO a28
|
373 | when dbg$ printf " [%d] Anonymous worker exited scheduling loop. FINISHED.\n" cpu
| ^^^^
Control/Monad/Par/Scheds/Direct.hs:379:26: error:
Variable not in scope: when :: Bool -> t17 -> IO a29
|
379 | when dbg$ do printf " *** Out of entire runContT user computation on main thread %s.\n" (show tid2)
| ^^^^
Control/Monad/Par/Scheds/Direct.hs:387:8: error:
Variable not in scope: when :: Bool -> m3 b4 -> IO a30
|
387 | when _WAIT_FOR_WORKERS $ do
| ^^^^
Control/Monad/Par/Scheds/Direct.hs:388:12: error:
Variable not in scope: when :: Bool -> t18 -> m3 a31
|
388 | when dbg$ printf " *** [%s] Originator thread: waiting for workers to complete." (show tidorig)
| ^^^^
Control/Monad/Par/Scheds/Direct.hs:389:12: error:
Variable not in scope:
forM_ :: [a32] -> (MVar a35 -> IO b5) -> m3 b4
|
389 | forM_ (catMaybes doneFlags) $ \ mv -> do
| ^^^^^
Control/Monad/Par/Scheds/Direct.hs:392:14: error:
Variable not in scope: when :: Bool -> t19 -> IO b5
|
392 | when dbg$ printf " * [%s] Worker %s completed\n" (show tidorig) (show n)
| ^^^^
Control/Monad/Par/Scheds/Direct.hs:394:8: error:
Variable not in scope: when :: Bool -> t20 -> IO a33
|
394 | when dbg$ do printf " *** [%s] Reading final MVar on originator thread.\n" (show tidorig)
| ^^^^
Control/Monad/Par/Scheds/Direct.hs:411:4: error:
Variable not in scope: when :: Bool -> IO () -> IO a4
|
411 | when dbg$ do tid <- myThreadId
| ^^^^
Control/Monad/Par/Scheds/Direct.hs:413:17: error:
• Variable not in scope:
replicateM
:: Int -> IO (SimpleDeque elt0) -> IO [SimpleDeque (Par ())]
• Perhaps you meant ‘replicate’ (imported from Prelude)
|
413 | workpools <- replicateM numCapabilities $ R.newQ
| ^^^^^^^^^^
Control/Monad/Par/Scheds/Direct.hs:414:17: error:
• Variable not in scope:
replicateM
:: Int
-> IO (HotVar (Random.Gen ghc-prim-0.6.1:GHC.Prim.RealWorld))
-> IO [HotVar (Random.Gen ghc-prim-0.6.1:GHC.Prim.RealWorld)]
• Perhaps you meant ‘replicate’ (imported from Prelude)
|
414 | rngs <- replicateM numCapabilities $ Random.create >>= newHotVar
| ^^^^^^^^^^
Control/Monad/Par/Scheds/Direct.hs:592:7: error:
Variable not in scope: when :: Bool -> Par () -> Par ()
|
592 | when dbg$ do
| ^^^^
Control/Monad/Par/Scheds/Direct.hs:599:7: error:
Variable not in scope: when :: Bool -> Par () -> Par a13
|
599 | when dbg$ io$ printf " [%d] forking task...\n" (no sch)
| ^^^^
Control/Monad/Par/Scheds/Direct.hs:612:3: error:
Variable not in scope:
when :: Bool -> t6 -> RD.ReaderT Sched IO a14
|
612 | when dbg$ liftIO$ do tid <- myThreadId
| ^^^^
Control/Monad/Par/Scheds/Direct.hs:612:13: error:
• Variable not in scope: liftIO :: IO () -> t6
• Perhaps you meant one of these:
‘lift’ (imported from Control.Monad.Cont),
‘liftA’ (imported from Control.Applicative),
‘liftA2’ (imported from Control.Applicative)
|
612 | when dbg$ liftIO$ do tid <- myThreadId
| ^^^^^^
Control/Monad/Par/Scheds/Direct.hs:617:13: error:
• Variable not in scope:
liftIO
:: IO (Maybe (Par ())) -> RD.ReaderT Sched IO (Maybe (Par a19))
• Perhaps you meant one of these:
‘lift’ (imported from Control.Monad.Cont),
‘liftA’ (imported from Control.Applicative),
‘liftA2’ (imported from Control.Applicative)
|
617 | mtask <- liftIO$ popWork mysched
| ^^^^^^
Control/Monad/Par/Scheds/Direct.hs:620:43: error:
• Variable not in scope:
liftIO :: IO [Session] -> RD.ReaderT Sched IO [Session]
• Perhaps you meant one of these:
‘lift’ (imported from Control.Monad.Cont),
‘liftA’ (imported from Control.Applicative),
‘liftA2’ (imported from Control.Applicative)
|
620 | (Session _ finRef):_ <- liftIO$ readIORef $ sessions mysched
| ^^^^^^
Control/Monad/Par/Scheds/Direct.hs:621:26: error:
• Variable not in scope:
liftIO :: IO Bool -> RD.ReaderT Sched IO Bool
• Perhaps you meant one of these:
‘lift’ (imported from Control.Monad.Cont),
‘liftA’ (imported from Control.Applicative),
‘liftA2’ (imported from Control.Applicative)
|
621 | fin <- liftIO$ readIORef finRef
| ^^^^^^
Control/Monad/Par/Scheds/Direct.hs:623:28: error:
Variable not in scope:
when :: Bool -> t7 -> RD.ReaderT Sched IO a15
|
623 | then do when (dbglvl >= 1) $ liftIO $ do
| ^^^^
Control/Monad/Par/Scheds/Direct.hs:623:49: error:
• Variable not in scope: liftIO :: IO b2 -> t7
• Perhaps you meant one of these:
‘lift’ (imported from Control.Monad.Cont),
‘liftA’ (imported from Control.Applicative),
‘liftA2’ (imported from Control.Applicative)
|
623 | then do when (dbglvl >= 1) $ liftIO $ do
| ^^^^^^
Control/Monad/Par/Scheds/Direct.hs:629:30: error:
Variable not in scope: when :: Bool -> t9 -> IO b2
|
629 | when (not empt) $ do
| ^^^^
Control/Monad/Par/Scheds/Direct.hs:640:22: error:
• Variable not in scope: liftIO :: IO () -> RD.ReaderT Sched IO a16
• Perhaps you meant one of these:
‘lift’ (imported from Control.Monad.Cont),
‘liftA’ (imported from Control.Applicative),
‘liftA2’ (imported from Control.Applicative)
|
640 | liftIO$ steal mysched
| ^^^^^^
Control/Monad/Par/Scheds/Direct.hs:644:22: error:
• Variable not in scope: liftIO :: IO () -> RD.ReaderT Sched IO a17
• Perhaps you meant one of these:
‘lift’ (imported from Control.Monad.Cont),
‘liftA’ (imported from Control.Applicative),
‘liftA2’ (imported from Control.Applicative)
|
644 | liftIO yield
| ^^^^^^
Control/Monad/Par/Scheds/Direct.hs:648:8: error:
Variable not in scope:
when :: Bool -> m2 b3 -> RD.ReaderT Sched IO a18
|
648 | when dbg $ do sn <- liftIO$ makeStableName task
| ^^^^
Control/Monad/Par/Scheds/Direct.hs:648:28: error:
• Variable not in scope:
liftIO
:: IO (GHC.StableName.StableName (Par a19))
-> m2 (GHC.StableName.StableName a20)
• Perhaps you meant one of these:
‘lift’ (imported from Control.Monad.Cont),
‘liftA’ (imported from Control.Applicative),
‘liftA2’ (imported from Control.Applicative)
|
648 | when dbg $ do sn <- liftIO$ makeStableName task
| ^^^^^^
Control/Monad/Par/Scheds/Direct.hs:649:22: error:
• Variable not in scope: liftIO :: t10 -> m2 b3
• Perhaps you meant one of these:
‘lift’ (imported from Control.Monad.Cont),
‘liftA’ (imported from Control.Applicative),
‘liftA2’ (imported from Control.Applicative)
|
649 | liftIO$ printf " [%d] popped work %d from own queue\n" (no mysched) (hashStableName sn)
| ^^^^^^
Control/Monad/Par/Scheds/Direct.hs:654:12: error:
Variable not in scope:
when
:: Bool -> t8 -> Control.Monad.Par.Scheds.DirectInternal.ROnly a21
|
654 | when dbg$ liftIO$ printf " + task finished successfully on cpu %d, calling reschedule continuation..\n" (no sch)
| ^^^^
Control/Monad/Par/Scheds/Direct.hs:654:22: error:
• Variable not in scope: liftIO :: t11 -> t8
• Perhaps you meant one of these:
‘lift’ (imported from Control.Monad.Cont),
‘liftA’ (imported from Control.Applicative),
‘liftA2’ (imported from Control.Applicative)
|
654 | when dbg$ liftIO$ printf " + task finished successfully on cpu %d, calling reschedule continuation..\n" (no sch)
| ^^^^^^
Control/Monad/Par/Scheds/Direct.hs:664:3: error:
Variable not in scope: when :: Bool -> IO () -> IO a12
|
664 | when (dbglvl>=2)$ do tid <- myThreadId
| ^^^^
Control/Monad/Par/Scheds/Direct.hs:681:22: error:
Variable not in scope: when :: Bool -> t2 -> IO a5
|
681 | when dbg$ printf " [%d] | waking up all threads\n" my_no
| ^^^^
Control/Monad/Par/Scheds/Direct.hs:690:26: error:
Variable not in scope: when :: Bool -> t3 -> IO a6
|
690 | when dbg$ printf " [%d] | shutting down\n" my_no
| ^^^^
Control/Monad/Par/Scheds/Direct.hs:693:26: error:
Variable not in scope: when :: Bool -> t4 -> IO a7
|
693 | when dbg$ printf " [%d] | woken up\n" my_no
| ^^^^
Control/Monad/Par/Scheds/Direct.hs:708:10: error:
Variable not in scope: when :: Bool -> t5 -> IO a8
|
708 | when (dbglvl>=2)$ printf " [%d] | trying steal from %d\n" my_no (no schd)
| ^^^^
Control/Monad/Par/Scheds/Direct.hs:716:15: error:
Variable not in scope: when :: Bool -> IO () -> IO a9
|
716 | when dbg$ do sn <- makeStableName task
| ^^^^
Control/Monad/Par/Scheds/Direct.hs:721:20: error:
Variable not in scope:
when
:: Bool
-> m0 b1 -> Control.Monad.Par.Scheds.DirectInternal.ROnly a10
|
721 | when dbg$ do sn <- liftIO$ makeStableName task
| ^^^^
Control/Monad/Par/Scheds/Direct.hs:721:39: error:
• Variable not in scope:
liftIO
:: IO (GHC.StableName.StableName (Par ()))
-> m0 (GHC.StableName.StableName a11)
• Perhaps you meant one of these:
‘lift’ (imported from Control.Monad.Cont),
‘liftA’ (imported from Control.Applicative),
‘liftA2’ (imported from Control.Applicative)
|
721 | when dbg$ do sn <- liftIO$ makeStableName task
| ^^^^^^
Control/Monad/Par/Scheds/Direct.hs:722:33: error:
• Variable not in scope: liftIO :: t0 -> m0 b1
• Perhaps you meant one of these:
‘lift’ (imported from Control.Monad.Cont),
‘liftA’ (imported from Control.Applicative),
‘liftA2’ (imported from Control.Applicative)
|
722 | liftIO$ printf " [%d] | DONE running stolen work (unit %d) from %d\n" my_no (hashStableName sn) (no schd)
| ^^^^^^
Control/Monad/Par/Scheds/Direct.hs:863:3: error:
Variable not in scope:
forM_ :: [Sched] -> (Sched -> IO b0) -> IO a0
|
863 | forM_ allscheds $ \ Sched{no, workpool} -> do
| ^^^^^
Control/Monad/Par/Scheds/Direct.hs:865:6: error:
Variable not in scope: when :: Bool -> m1 () -> IO b0
|
865 | when (not b) $ do
| ^^^^
```
</details>
**EDIT 2:** Even more breakage
`repline` (bounds are sufficient, [PR](https://github.com/sdiehl/repline/pull/38)):
<details>
```
src/System/Console/Repline.hs:185:7: error:
Not in scope: type constructor or class ‘MonadIO’
Perhaps you meant ‘Monad’ (imported from Prelude)
|
185 | MonadIO,
| ^^^^^^^
src/System/Console/Repline.hs:186:7: error:
Not in scope: type constructor or class ‘MonadFix’
Perhaps you meant ‘MonadFail’ (imported from Control.Monad.Fail)
|
186 | MonadFix,
| ^^^^^^^^
src/System/Console/Repline.hs:195:32: error:
Not in scope: type constructor or class ‘MonadIO’
Perhaps you meant ‘Monad’ (imported from Prelude)
|
195 | runHaskelineT :: (MonadMask m, MonadIO m) => H.Settings m -> HaskelineT m a -> m a
| ^^^^^^^
src/System/Console/Repline.hs:204:24: error:
Not in scope: type constructor or class ‘MonadIO’
Perhaps you meant ‘Monad’ (imported from Prelude)
|
204 | instance (MonadMask m, MonadIO m) => MonadHaskeline (H.InputT m) where
| ^^^^^^^
src/System/Console/Repline.hs:258:28: error:
Not in scope: type constructor or class ‘MonadIO’
Perhaps you meant ‘Monad’ (imported from Prelude)
|
258 | tryAction :: (MonadMask m, MonadIO m) => HaskelineT m a -> HaskelineT m a
| ^^^^^^^
src/System/Console/Repline.hs:264:15: error:
Not in scope: type constructor or class ‘MonadIO’
Perhaps you meant ‘Monad’ (imported from Prelude)
|
264 | dontCrash :: (MonadIO m, MonadCatch m) => m () -> m ()
| ^^^^^^^
src/System/Console/Repline.hs:273:28: error:
Not in scope: type constructor or class ‘MonadIO’
Perhaps you meant ‘Monad’ (imported from Prelude)
|
273 | (Functor m, MonadMask m, MonadIO m) =>
| ^^^^^^^
src/System/Console/Repline.hs:371:31: error:
Not in scope: type constructor or class ‘MonadIO’
Perhaps you meant ‘Monad’ (imported from Prelude)
|
371 | evalReplOpts :: (MonadMask m, MonadIO m) => ReplOpts m -> m ()
| ^^^^^^^
src/System/Console/Repline.hs:385:17: error:
Not in scope: type constructor or class ‘MonadIO’
Perhaps you meant ‘Monad’ (imported from Prelude)
|
385 | (MonadMask m, MonadIO m) =>
| ^^^^^^^
src/System/Console/Repline.hs:437:16: error:
Not in scope: type constructor or class ‘MonadIO’
Perhaps you meant ‘Monad’ (imported from Prelude)
|
437 | mkCompleter :: MonadIO m => CompleterStyle m -> CompletionFunc m
| ^^^^^^^
src/System/Console/Repline.hs:476:18: error:
Not in scope: type constructor or class ‘MonadIO’
Perhaps you meant ‘Monad’ (imported from Prelude)
|
476 | fileCompleter :: MonadIO m => CompletionFunc m
| ^^^^^^^
```
</details>
---
I wonder whether it might be better to continue to re-export a selected (stable) set of combinators and possibly also classes like `MonadIO` and `MonadFix`.
For combinators like `liftM2`, `when` or `(<=<)`, I don't see how this could do any harm by causing compatibility issues down the road.
In the case of classes like `MonadIO` and `MonadFix` I'm less sure, but even for these it might be no worse to cause the breakage once it's warranted by upstream changes on these classes themselves.
What do you think?