Skip to content
Snippets Groups Projects
Commit d1d2c1d2 authored by sof's avatar sof
Browse files

[project @ 1999-02-02 13:21:59 by sof]

- Added:

     newByteArray      :: Ix ix => (ix,ix) -> ST s (ByteArray ix)
     boundsOfByteArray :: Ix ix => ByteArray ix -> (ix,ix)
     sizeofByteArray   :: Ix ix => ByteArray ix -> Int

  plus defined Eq over ByteArrays.
parent 189e0677
No related merge requests found
......@@ -9,9 +9,11 @@ together the definitions in @ArrBase@ and exports them as one.
\begin{code}
module ByteArray
(
ByteArray(..), -- not abstract, for now.
ByteArray(..), -- not abstract, for now. Instance of : CCallable, Eq.
Ix,
newByteArray, -- :: Ix ix => (ix,ix) -> ST s (ByteArray ix)
--Indexing of ordinary @Arrays@ is standard Haskell and isn't defined here.
indexCharArray, -- :: Ix ix => ByteArray ix -> ix -> Char
indexIntArray, -- :: Ix ix => ByteArray ix -> ix -> Int
......@@ -19,13 +21,17 @@ module ByteArray
indexAddrArray, -- :: Ix ix => ByteArray ix -> ix -> Addr
indexFloatArray, -- :: Ix ix => ByteArray ix -> ix -> Float
indexDoubleArray, -- :: Ix ix => ByteArray ix -> ix -> Double
indexStablePtrArray -- :: Ix ix => ByteArray ix -> ix -> (StablePtr a)
indexStablePtrArray, -- :: Ix ix => ByteArray ix -> ix -> (StablePtr a)
sizeofByteArray, -- :: Ix ix => ByteArray ix -> Int
boundsOfByteArray -- :: Ix ix => ByteArray ix -> (ix, ix)
) where
import PrelArr
import PrelBase
import PrelStable( StablePtr(..) )
import PrelST
import Ix
\end{code}
......@@ -36,3 +42,35 @@ indexStablePtrArray (ByteArray ixs barr#) n
case indexStablePtrArray# barr# n# of { r# ->
(StablePtr r#)}}
\end{code}
The size returned is in bytes.
\begin{code}
sizeofByteArray :: Ix ix => ByteArray ix -> Int
sizeofByteArray (ByteArray _ arr#) =
case (sizeofByteArray# arr#) of
i# -> (I# i#)
boundsOfByteArray :: Ix ix => ByteArray ix -> (ix, ix)
boundsOfByteArray (ByteArray ixs _) = ixs
\end{code}
\begin{code}
newByteArray :: Ix ix => (ix,ix) -> ST s (ByteArray ix)
newByteArray ixs = do
m_arr <- newCharArray ixs
unsafeFreezeByteArray m_arr
\end{code}
If it should turn out to be an issue, could probably be speeded
up quite a bit.
\begin{code}
instance Ix ix => Eq (ByteArray ix) where
b1 == b2 = eqByteArray b1 b2
eqByteArray :: Ix ix => ByteArray ix -> ByteArray ix -> Bool
eqByteArray b1 b2 =
sizeofByteArray b1 == sizeofByteArray b2 &&
all (\ x -> indexCharArray b1 x == indexCharArray b2 x) (range (boundsOfByteArray b1))
\end{code}
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