Changeset View
Changeset View
Standalone View
Standalone View
libraries/base/System/Mem/Address.hs
- This file was added.
1 | {-# LANGUAGE MagicHash #-} | ||||
---|---|---|---|---|---|
2 | | ||||
3 | Module System.Mem.Address ( | ||||
4 | -- * Types | ||||
5 | Addr(..), | ||||
6 | | ||||
7 | -- * Address arithmetic | ||||
8 | nullAddr, plusAddr, minusAddr, remAddr, | ||||
9 | | ||||
10 | -- * Conversion | ||||
11 | addrToInt, addrToPtr, ptrToAddr | ||||
12 | | ||||
13 | | ||||
14 | | ||||
15 | ) where | ||||
16 | | ||||
17 | | ||||
18 | | ||||
19 | import GHC.Base ( Int(..) ) | ||||
20 | import GHC.Prim | ||||
21 | | ||||
22 | import GHC.Exts (isTrue#) | ||||
23 | import GHC.Ptr | ||||
24 | import Foreign.Marshal.Utils | ||||
25 | | ||||
26 | import Data.Typeable ( Typeable ) | ||||
27 | import Data.Data ( Data(..), mkNoRepType ) | ||||
28 | | ||||
29 | | ||||
30 | -- | A machine address | ||||
31 | data Addr = Addr Addr# deriving ( Typeable ) | ||||
32 | | ||||
33 | instance Show Addr where | ||||
34 | showsPrec _ (Addr a) = | ||||
35 | showString "0x" . showHex (fromIntegral (I# (addr2Int# a)) :: Word) | ||||
36 | | ||||
37 | instance Eq Addr where | ||||
38 | Addr a# == Addr b# = isTrue# (eqAddr# a# b#) | ||||
39 | Addr a# /= Addr b# = isTrue# (neAddr# a# b#) | ||||
40 | | ||||
41 | instance Ord Addr where | ||||
42 | Addr a# > Addr b# = isTrue# (gtAddr# a# b#) | ||||
43 | Addr a# >= Addr b# = isTrue# (geAddr# a# b#) | ||||
44 | Addr a# < Addr b# = isTrue# (ltAddr# a# b#) | ||||
45 | Addr a# <= Addr b# = isTrue# (leAddr# a# b#) | ||||
46 | | ||||
47 | instance Data Addr where | ||||
48 | toConstr _ = error "toConstr" | ||||
49 | gunfold _ _ = error "gunfold" | ||||
50 | dataTypeOf _ = mkNoRepType "Data.Primitive.Types.Addr" | ||||
51 | | ||||
52 | -- | The null address | ||||
53 | nullAddr :: Addr | ||||
54 | nullAddr = Addr nullAddr# | ||||
55 | | ||||
56 | infixl 6 `plusAddr`, `minusAddr` | ||||
57 | infixl 7 `remAddr` | ||||
58 | | ||||
59 | -- | Offset an address by the given number of bytes | ||||
60 | plusAddr :: Addr -> Int -> Addr | ||||
61 | plusAddr (Addr a#) (I# i#) = Addr (plusAddr# a# i#) | ||||
62 | | ||||
63 | -- | Distance in bytes between two addresses. The result is only valid if the | ||||
64 | -- difference fits in an 'Int'. | ||||
65 | minusAddr :: Addr -> Addr -> Int | ||||
66 | minusAddr (Addr a#) (Addr b#) = I# (minusAddr# a# b#) | ||||
67 | | ||||
68 | -- | The remainder of the address and the integer, in bytes. | ||||
69 | remAddr :: Addr -> Int -> Int | ||||
70 | remAddr (Addr a#) (I# i#) = I# (remAddr# a# i#) | ||||
71 | | ||||
72 | -- | Convert an 'Addr' to an 'Int'. | ||||
73 | addrToInt :: Addr -> Int | ||||
74 | {-# INLINE addrToInt #-} | ||||
75 | addrToInt (Addr addr#) = I# (addr2Int# addr#) | ||||
76 | | ||||
77 | -- | convert `Addr` to `Ptr a` | ||||
78 | addrToPtr :: Addr -> Ptr a | ||||
79 | addrToPtr (Addr addr#) = Ptr addr# | ||||
80 | | ||||
81 | -- | convert `Ptr a` to `Addr` | ||||
82 | ptrToAddr :: Ptr a -> Addr | ||||
83 | ptrToAddr (Ptr p) = Addr p |