Remove Control.Parallel*, now in package parallel
[haskell-directory.git] / Data / Array / IO / Internals.hs
index 0f6d94e..fca542e 100644 (file)
@@ -1,4 +1,4 @@
-{-# OPTIONS -#include "HsBase.h" #-}
+{-# OPTIONS_GHC -#include "HsBase.h" #-}
 -----------------------------------------------------------------------------
 -- |
 -- Module      :  Data.Array.IO.Internal
@@ -7,7 +7,7 @@
 -- 
 -- Maintainer  :  libraries@haskell.org
 -- Stability   :  experimental
--- Portability :  non-portable
+-- Portability :  non-portable (uses Data.Array.Base)
 --
 -- Mutable boxed and unboxed arrays in the IO monad.
 --
@@ -41,28 +41,20 @@ import GHC.IOBase
 import GHC.Base
 #endif /* __GLASGOW_HASKELL__ */
 
-iOArrayTc :: TyCon
-iOArrayTc = mkTyCon "IOArray"
+#include "Typeable.h"
 
-instance (Typeable a, Typeable b) => Typeable (IOArray a b) where
-  typeOf a = mkAppTy iOArrayTc [typeOf ((undefined :: IOArray a b -> a) a),
-                               typeOf ((undefined :: IOArray a b -> b) a)]
+INSTANCE_TYPEABLE2(IOArray,iOArrayTc,"IOArray")
 
 -----------------------------------------------------------------------------
 -- | Instance declarations for 'IOArray's
 
-#ifdef __GLASGOW_HASKELL__
-instance HasBounds IOArray where
-    {-# INLINE bounds #-}
-    bounds (IOArray marr) = bounds marr
-#endif
-
-#ifdef __HUGS__
-instance HasBounds IOArray where
-    bounds      = boundsIOArray
-#endif
-
 instance MArray IOArray e IO where
+#if defined(__HUGS__)
+    getBounds   = return . boundsIOArray
+#elif defined(__GLASGOW_HASKELL__)
+    {-# INLINE getBounds #-}
+    getBounds (IOArray marr) = stToIO $ getBounds marr
+#endif
     newArray    = newIOArray
     unsafeRead  = unsafeReadIOArray
     unsafeWrite = unsafeWriteIOArray
@@ -80,18 +72,11 @@ instance MArray IOArray e IO where
 --
 newtype IOUArray i e = IOUArray (STUArray RealWorld i e)
 
-iOUArrayTc :: TyCon
-iOUArrayTc = mkTyCon "IOUArray"
-
-instance (Typeable a, Typeable b) => Typeable (IOUArray a b) where
-  typeOf a = mkAppTy iOUArrayTc [typeOf ((undefined :: IOUArray a b -> a) a),
-                                typeOf ((undefined :: IOUArray a b -> b) a)]
-
-instance HasBounds IOUArray where
-    {-# INLINE bounds #-}
-    bounds (IOUArray marr) = bounds marr
+INSTANCE_TYPEABLE2(IOUArray,iOUArrayTc,"IOUArray")
 
 instance MArray IOUArray Bool IO where
+    {-# INLINE getBounds #-}
+    getBounds (IOUArray arr) = stToIO $ getBounds arr
     {-# INLINE newArray #-}
     newArray lu init = stToIO $ do
         marr <- newArray lu init; return (IOUArray marr)
@@ -104,6 +89,8 @@ instance MArray IOUArray Bool IO where
     unsafeWrite (IOUArray marr) i e = stToIO (unsafeWrite marr i e)
 
 instance MArray IOUArray Char IO where
+    {-# INLINE getBounds #-}
+    getBounds (IOUArray arr) = stToIO $ getBounds arr
     {-# INLINE newArray #-}
     newArray lu init = stToIO $ do
         marr <- newArray lu init; return (IOUArray marr)
@@ -116,6 +103,8 @@ instance MArray IOUArray Char IO where
     unsafeWrite (IOUArray marr) i e = stToIO (unsafeWrite marr i e)
 
 instance MArray IOUArray Int IO where
+    {-# INLINE getBounds #-}
+    getBounds (IOUArray arr) = stToIO $ getBounds arr
     {-# INLINE newArray #-}
     newArray lu init = stToIO $ do
         marr <- newArray lu init; return (IOUArray marr)
@@ -127,8 +116,9 @@ instance MArray IOUArray Int IO where
     {-# INLINE unsafeWrite #-}
     unsafeWrite (IOUArray marr) i e = stToIO (unsafeWrite marr i e)
 
-#ifdef __GLASGOW_HASKELL__
 instance MArray IOUArray Word IO where
+    {-# INLINE getBounds #-}
+    getBounds (IOUArray arr) = stToIO $ getBounds arr
     {-# INLINE newArray #-}
     newArray lu init = stToIO $ do
         marr <- newArray lu init; return (IOUArray marr)
@@ -139,9 +129,10 @@ instance MArray IOUArray Word IO where
     unsafeRead (IOUArray marr) i = stToIO (unsafeRead marr i)
     {-# INLINE unsafeWrite #-}
     unsafeWrite (IOUArray marr) i e = stToIO (unsafeWrite marr i e)
-#endif
 
 instance MArray IOUArray (Ptr a) IO where
+    {-# INLINE getBounds #-}
+    getBounds (IOUArray arr) = stToIO $ getBounds arr
     {-# INLINE newArray #-}
     newArray lu init = stToIO $ do
         marr <- newArray lu init; return (IOUArray marr)
@@ -154,6 +145,8 @@ instance MArray IOUArray (Ptr a) IO where
     unsafeWrite (IOUArray marr) i e = stToIO (unsafeWrite marr i e)
 
 instance MArray IOUArray (FunPtr a) IO where
+    {-# INLINE getBounds #-}
+    getBounds (IOUArray arr) = stToIO $ getBounds arr
     {-# INLINE newArray #-}
     newArray lu init = stToIO $ do
         marr <- newArray lu init; return (IOUArray marr)
@@ -166,6 +159,8 @@ instance MArray IOUArray (FunPtr a) IO where
     unsafeWrite (IOUArray marr) i e = stToIO (unsafeWrite marr i e)
 
 instance MArray IOUArray Float IO where
+    {-# INLINE getBounds #-}
+    getBounds (IOUArray arr) = stToIO $ getBounds arr
     {-# INLINE newArray #-}
     newArray lu init = stToIO $ do
         marr <- newArray lu init; return (IOUArray marr)
@@ -178,6 +173,8 @@ instance MArray IOUArray Float IO where
     unsafeWrite (IOUArray marr) i e = stToIO (unsafeWrite marr i e)
 
 instance MArray IOUArray Double IO where
+    {-# INLINE getBounds #-}
+    getBounds (IOUArray arr) = stToIO $ getBounds arr
     {-# INLINE newArray #-}
     newArray lu init = stToIO $ do
         marr <- newArray lu init; return (IOUArray marr)
@@ -190,6 +187,8 @@ instance MArray IOUArray Double IO where
     unsafeWrite (IOUArray marr) i e = stToIO (unsafeWrite marr i e)
 
 instance MArray IOUArray (StablePtr a) IO where
+    {-# INLINE getBounds #-}
+    getBounds (IOUArray arr) = stToIO $ getBounds arr
     {-# INLINE newArray #-}
     newArray lu init = stToIO $ do
         marr <- newArray lu init; return (IOUArray marr)
@@ -202,6 +201,8 @@ instance MArray IOUArray (StablePtr a) IO where
     unsafeWrite (IOUArray marr) i e = stToIO (unsafeWrite marr i e)
 
 instance MArray IOUArray Int8 IO where
+    {-# INLINE getBounds #-}
+    getBounds (IOUArray arr) = stToIO $ getBounds arr
     {-# INLINE newArray #-}
     newArray lu init = stToIO $ do
         marr <- newArray lu init; return (IOUArray marr)
@@ -214,6 +215,8 @@ instance MArray IOUArray Int8 IO where
     unsafeWrite (IOUArray marr) i e = stToIO (unsafeWrite marr i e)
 
 instance MArray IOUArray Int16 IO where
+    {-# INLINE getBounds #-}
+    getBounds (IOUArray arr) = stToIO $ getBounds arr
     {-# INLINE newArray #-}
     newArray lu init = stToIO $ do
         marr <- newArray lu init; return (IOUArray marr)
@@ -226,6 +229,8 @@ instance MArray IOUArray Int16 IO where
     unsafeWrite (IOUArray marr) i e = stToIO (unsafeWrite marr i e)
 
 instance MArray IOUArray Int32 IO where
+    {-# INLINE getBounds #-}
+    getBounds (IOUArray arr) = stToIO $ getBounds arr
     {-# INLINE newArray #-}
     newArray lu init = stToIO $ do
         marr <- newArray lu init; return (IOUArray marr)
@@ -238,6 +243,8 @@ instance MArray IOUArray Int32 IO where
     unsafeWrite (IOUArray marr) i e = stToIO (unsafeWrite marr i e)
 
 instance MArray IOUArray Int64 IO where
+    {-# INLINE getBounds #-}
+    getBounds (IOUArray arr) = stToIO $ getBounds arr
     {-# INLINE newArray #-}
     newArray lu init = stToIO $ do
         marr <- newArray lu init; return (IOUArray marr)
@@ -250,6 +257,8 @@ instance MArray IOUArray Int64 IO where
     unsafeWrite (IOUArray marr) i e = stToIO (unsafeWrite marr i e)
 
 instance MArray IOUArray Word8 IO where
+    {-# INLINE getBounds #-}
+    getBounds (IOUArray arr) = stToIO $ getBounds arr
     {-# INLINE newArray #-}
     newArray lu init = stToIO $ do
         marr <- newArray lu init; return (IOUArray marr)
@@ -262,6 +271,8 @@ instance MArray IOUArray Word8 IO where
     unsafeWrite (IOUArray marr) i e = stToIO (unsafeWrite marr i e)
 
 instance MArray IOUArray Word16 IO where
+    {-# INLINE getBounds #-}
+    getBounds (IOUArray arr) = stToIO $ getBounds arr
     {-# INLINE newArray #-}
     newArray lu init = stToIO $ do
         marr <- newArray lu init; return (IOUArray marr)
@@ -274,6 +285,8 @@ instance MArray IOUArray Word16 IO where
     unsafeWrite (IOUArray marr) i e = stToIO (unsafeWrite marr i e)
 
 instance MArray IOUArray Word32 IO where
+    {-# INLINE getBounds #-}
+    getBounds (IOUArray arr) = stToIO $ getBounds arr
     {-# INLINE newArray #-}
     newArray lu init = stToIO $ do
         marr <- newArray lu init; return (IOUArray marr)
@@ -286,6 +299,8 @@ instance MArray IOUArray Word32 IO where
     unsafeWrite (IOUArray marr) i e = stToIO (unsafeWrite marr i e)
 
 instance MArray IOUArray Word64 IO where
+    {-# INLINE getBounds #-}
+    getBounds (IOUArray arr) = stToIO $ getBounds arr
     {-# INLINE newArray #-}
     newArray lu init = stToIO $ do
         marr <- newArray lu init; return (IOUArray marr)