Skip to content
Snippets Groups Projects
Commit 388384b6 authored by Simon Marlow's avatar Simon Marlow
Browse files

FIX #1270: add Eq instances for STUArray and IOUArray

parent 5c1027e3
No related branches found
No related tags found
No related merge requests found
......@@ -1115,6 +1115,10 @@ data STUArray s i a = STUArray !i !i !Int !(MutableByteArray s)
INSTANCE_TYPEABLE3(STUArray,stUArrayTc,"STUArray")
instance Eq (STUArray s i e) where
STUArray _ _ _ arr1# == STUArray _ _ _ arr2# =
sameMutableByteArray# arr1# arr2#
#ifdef __GLASGOW_HASKELL__
{-# INLINE unsafeNewArraySTUArray_ #-}
unsafeNewArraySTUArray_ :: Ix i
......
......@@ -77,6 +77,9 @@ newtype IOUArray i e = IOUArray (STUArray RealWorld i e)
INSTANCE_TYPEABLE2(IOUArray,iOUArrayTc,"IOUArray")
instance Eq (IOUArray i e) where
IOUArray s1 == IOUArray s2 = s1 == s2
instance MArray IOUArray Bool IO where
{-# INLINE getBounds #-}
getBounds (IOUArray arr) = stToIO $ getBounds arr
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment