summaryrefslogtreecommitdiff
path: root/ghc/lib/exts/ByteArray.lhs
blob: 7f9615b6ded745177df343b8c35e7f73e691ca38 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
%
% (c) The AQUA Project, Glasgow University, 1994-1997
%
\section[ByteArray]{The @ByteArray@ interface}

Immutable, read-only chunks of bytes, the @ByteArray@ collects
together the definitions in @ArrBase@ and exports them as one.

\begin{code}
module ByteArray
       (
        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
        indexWordArray,       -- :: Ix ix => ByteArray ix -> ix -> Word
        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)

        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}

\begin{code}
indexStablePtrArray    :: Ix ix => ByteArray ix -> ix -> (StablePtr a)
indexStablePtrArray (ByteArray ixs barr#) n
  = case (index ixs n)	    	    	of { I# 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}