Repository : ssh://darcs.haskell.org//srv/darcs/packages/base

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/0550a28cfc517ac36e6d1ab5594133787b56425d

>---------------------------------------------------------------

commit 0550a28cfc517ac36e6d1ab5594133787b56425d
Author: David Terei <[email protected]>
Date:   Fri Apr 13 04:23:09 2012 -0700

    Revert "Add GHCi monad"
    
    This reverts commit 7e04ab6158957c90e3c68911b6909b6ef69621da.

>---------------------------------------------------------------

 GHC/GHCi.hs |   42 ------------------------------------------
 base.cabal  |    1 -
 2 files changed, 0 insertions(+), 43 deletions(-)

diff --git a/GHC/GHCi.hs b/GHC/GHCi.hs
deleted file mode 100644
index d08aab3..0000000
--- a/GHC/GHCi.hs
+++ /dev/null
@@ -1,42 +0,0 @@
-{-# LANGUAGE NoImplicitPrelude #-}
-{-# OPTIONS_HADDOCK hide #-}
-
------------------------------------------------------------------------------
--- |
--- Module      :  GHC.GHCi
--- Copyright   :  (c) The University of Glasgow 2012
--- License     :  see libraries/base/LICENSE

>---------------------------------------------------------------

--- Maintainer  :  [email protected]
--- Stability   :  internal
--- Portability :  non-portable (GHC Extensions)

>---------------------------------------------------------------

--- The GHCi Monad lifting interface.

>---------------------------------------------------------------

------------------------------------------------------------------------------
-
--- #hide
-module GHC.GHCi (
-        GHCiSandboxIO(..), NoIO()
-    ) where
-
-import GHC.Base (IO(), Monad, (>>=), return, id, (.))
-
--- | A monad that can execute GHCi statements by lifting them out of
--- m into the IO monad. (e.g state monads)
-class (Monad m) => GHCiSandboxIO m where
-    ghciStepIO :: m a -> IO a
-
-instance GHCiSandboxIO IO where
-    ghciStepIO = id
-
--- | A monad that doesn't allow any IO.
-newtype NoIO a = NoIO { noio :: IO a }
-
-instance Monad NoIO where
-    return a  = NoIO (return a)
-    (>>=) k f = NoIO (noio k >>= noio . f)
-
-instance GHCiSandboxIO NoIO where
-    ghciStepIO = noio
-
diff --git a/base.cabal b/base.cabal
index 6e97cc0..2cbfa11 100644
--- a/base.cabal
+++ b/base.cabal
@@ -58,7 +58,6 @@ Library {
             GHC.Float.RealFracMethods,
             GHC.Foreign,
             GHC.ForeignPtr,
-            GHC.GHCi,
             GHC.Handle,
             GHC.IO,
             GHC.IO.Buffer,



_______________________________________________
Cvs-libraries mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-libraries

Reply via email to