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

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/7e04ab6158957c90e3c68911b6909b6ef69621da

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

commit 7e04ab6158957c90e3c68911b6909b6ef69621da
Author: David Terei <[email protected]>
Date:   Wed Feb 8 15:08:07 2012 -0800

    Add GHCi monad

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

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

diff --git a/GHC/GHCi.hs b/GHC/GHCi.hs
new file mode 100644
index 0000000..d08aab3
--- /dev/null
+++ b/GHC/GHCi.hs
@@ -0,0 +1,42 @@
+{-# 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 2cbfa11..6e97cc0 100644
--- a/base.cabal
+++ b/base.cabal
@@ -58,6 +58,7 @@ 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