{-# LANGUAGE NoImplicitPrelude #-}
{-# OPTIONS_HADDOCK not-home #-}
module GHC.GHCi {-# WARNING "This is an unstable interface." #-} (
        GHCiSandboxIO(..), NoIO()
    ) where
import GHC.Base (IO(), Monad, Functor(fmap), Applicative(..), (>>=), id, (.), ap)
class (Monad m) => GHCiSandboxIO m where
    ghciStepIO :: m a -> IO a
instance GHCiSandboxIO IO where
    ghciStepIO :: forall a. IO a -> IO a
ghciStepIO = IO a -> IO a
forall a. a -> a
id
newtype NoIO a = NoIO { forall a. NoIO a -> IO a
noio :: IO a }
instance Functor NoIO where
  fmap :: forall a b. (a -> b) -> NoIO a -> NoIO b
fmap a -> b
f (NoIO IO a
a) = IO b -> NoIO b
forall a. IO a -> NoIO a
NoIO ((a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f IO a
a)
instance Applicative NoIO where
  pure :: forall a. a -> NoIO a
pure a
a = IO a -> NoIO a
forall a. IO a -> NoIO a
NoIO (a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
a)
  <*> :: forall a b. NoIO (a -> b) -> NoIO a -> NoIO b
(<*>) = NoIO (a -> b) -> NoIO a -> NoIO b
forall (m :: * -> *) a b. Monad m => m (a -> b) -> m a -> m b
ap
instance Monad NoIO where
    >>= :: forall a b. NoIO a -> (a -> NoIO b) -> NoIO b
(>>=) NoIO a
k a -> NoIO b
f = IO b -> NoIO b
forall a. IO a -> NoIO a
NoIO (NoIO a -> IO a
forall a. NoIO a -> IO a
noio NoIO a
k IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= NoIO b -> IO b
forall a. NoIO a -> IO a
noio (NoIO b -> IO b) -> (a -> NoIO b) -> a -> IO b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> NoIO b
f)
instance GHCiSandboxIO NoIO where
    ghciStepIO :: forall a. NoIO a -> IO a
ghciStepIO = NoIO a -> IO a
forall a. NoIO a -> IO a
noio