Use let !y = x in .. x .. instead of seq in $! and evaluate (#2273)
[ghc-base.git] / GHC / IO.hs
index fef57da..9615953 100644 (file)
--- a/GHC/IO.hs
+++ b/GHC/IO.hs
@@ -1,4 +1,5 @@
-{-# OPTIONS_GHC -fno-implicit-prelude -funbox-strict-fields #-}
+{-# OPTIONS_GHC -fno-warn-orphans #-}
+{-# OPTIONS_GHC -XNoImplicitPrelude -funbox-strict-fields -XBangPatterns #-}
 {-# OPTIONS_HADDOCK hide #-}
 -----------------------------------------------------------------------------
 -- |
@@ -16,7 +17,7 @@
 
 -- #hide
 module GHC.IO (
-    IO(..), unIO, failIO, liftIO, bindIO, thenIO, returnIO, 
+    IO(..), unIO, failIO, liftIO,
     unsafePerformIO, unsafeInterleaveIO,
     unsafeDupablePerformIO, unsafeDupableInterleaveIO,
     noDuplicate,
@@ -64,55 +65,9 @@ Libraries - parts of hslibs/lang.
 --SDM
 -}
 
-{-|
-A value of type @'IO' a@ is a computation which, when performed,
-does some I\/O before returning a value of type @a@.  
-
-There is really only one way to \"perform\" an I\/O action: bind it to
-@Main.main@ in your program.  When your program is run, the I\/O will
-be performed.  It isn't possible to perform I\/O from an arbitrary
-function, unless that function is itself in the 'IO' monad and called
-at some point, directly or indirectly, from @Main.main@.
-
-'IO' is a monad, so 'IO' actions can be combined using either the do-notation
-or the '>>' and '>>=' operations from the 'Monad' class.
--}
-newtype IO a = IO (State# RealWorld -> (# State# RealWorld, a #))
-
-unIO :: IO a -> (State# RealWorld -> (# State# RealWorld, a #))
-unIO (IO a) = a
-
-instance  Functor IO where
-   fmap f x = x >>= (return . f)
-
-instance  Monad IO  where
-    {-# INLINE return #-}
-    {-# INLINE (>>)   #-}
-    {-# INLINE (>>=)  #-}
-    m >> k      =  m >>= \ _ -> k
-    return x    = returnIO x
-
-    m >>= k     = bindIO m k
-    fail s      = failIO s
-
 liftIO :: IO a -> State# RealWorld -> STret RealWorld a
 liftIO (IO m) = \s -> case m s of (# s', r #) -> STret s' r
 
-bindIO :: IO a -> (a -> IO b) -> IO b
-bindIO (IO m) k = IO ( \ s ->
-  case m s of 
-    (# new_s, a #) -> unIO (k a) new_s
-  )
-
-thenIO :: IO a -> IO b -> IO b
-thenIO (IO m) k = IO ( \ s ->
-  case m s of 
-    (# new_s, _ #) -> unIO k new_s
-  )
-
-returnIO :: a -> IO a
-returnIO x = IO (\ s -> (# s, x #))
-
 failIO :: String -> IO a
 failIO s = IO (raiseIO# (toException (userError s)))
 
@@ -352,7 +307,7 @@ blocked = IO $ \s -> case asyncExceptionsBlocked# s of
                         (# s', i #) -> (# s', i /=# 0# #)
 
 onException :: IO a -> IO b -> IO a
-onException io what = io `catchException` \e -> do what
+onException io what = io `catchException` \e -> do _ <- what
                                                    throw (e :: SomeException)
 
 finally :: IO a         -- ^ computation to run first
@@ -362,7 +317,7 @@ finally :: IO a         -- ^ computation to run first
 a `finally` sequel =
   block (do
     r <- unblock a `onException` sequel
-    sequel
+    _ <- sequel
     return r
   )
 
@@ -381,7 +336,4 @@ a `finally` sequel =
 -- >   evaluate x = (return $! x) >>= return
 --
 evaluate :: a -> IO a
-evaluate a = IO $ \s -> case a `seq` () of () -> (# s, a #)
-        -- NB. can't write
-        --      a `seq` (# s, a #)
-        -- because we can't have an unboxed tuple as a function argument
+evaluate a = IO $ \s -> let !va = a in (# s, va #) -- NB. see #2273