[GHC] #15812: add System.Mem.Address to base

GHC ghc-devs at haskell.org
Fri Oct 26 18:31:32 UTC 2018


#15812: add System.Mem.Address to base
-------------------------------------+-------------------------------------
           Reporter:  carter         |             Owner:  (none)
               Type:  bug            |            Status:  new
           Priority:  normal         |         Milestone:  8.8.1
          Component:                 |           Version:  8.7
  libraries/base                     |
           Keywords:                 |  Operating System:  Unknown/Multiple
       Architecture:                 |   Type of failure:  None/Unknown
  Unknown/Multiple                   |
          Test Case:                 |        Blocked By:
           Blocking:                 |   Related Tickets:
Differential Rev(s):  D5268          |         Wiki Page:
-------------------------------------+-------------------------------------
 per libraries in progress discussion  and
 https://phabricator.haskell.org/D5268

 current state is this

 {{{

 {-# LANGUAGE MagicHash #-}

 Module System.Mem.Address (
  -- * Types
   Addr(..),

   -- * Address arithmetic
   nullAddr, plusAddr, minusAddr, remAddr,

   -- * Conversion
   addrToInt, addrToPtr, ptrToAddr



   ) where



 import GHC.Base ( Int(..) )
 import GHC.Prim

 import GHC.Exts (isTrue#)
 import GHC.Ptr
 import Foreign.Marshal.Utils

 import Data.Typeable ( Typeable )
 import Data.Data ( Data(..), mkNoRepType )


 -- | A machine address
 data Addr = Addr Addr# deriving ( Typeable )

 instance Show Addr where
   showsPrec _ (Addr a) =
     showString "0x" . showHex (fromIntegral (I# (addr2Int# a)) :: Word)

 instance Eq Addr where
   Addr a# == Addr b# = isTrue# (eqAddr# a# b#)
   Addr a# /= Addr b# = isTrue# (neAddr# a# b#)

 instance Ord Addr where
   Addr a# > Addr b# = isTrue# (gtAddr# a# b#)
   Addr a# >= Addr b# = isTrue# (geAddr# a# b#)
   Addr a# < Addr b# = isTrue# (ltAddr# a# b#)
   Addr a# <= Addr b# = isTrue# (leAddr# a# b#)

 instance Data Addr where
   toConstr _ = error "toConstr"
   gunfold _ _ = error "gunfold"
   dataTypeOf _ = mkNoRepType "Data.Primitive.Types.Addr"

 -- | The null address
 nullAddr :: Addr
 nullAddr = Addr nullAddr#

 infixl 6 `plusAddr`, `minusAddr`
 infixl 7 `remAddr`

 -- | Offset an address by the given number of bytes
 plusAddr :: Addr -> Int -> Addr
 plusAddr (Addr a#) (I# i#) = Addr (plusAddr# a# i#)

 -- | Distance in bytes between two addresses. The result is only valid if
 the
 -- difference fits in an 'Int'.
 minusAddr :: Addr -> Addr -> Int
 minusAddr (Addr a#) (Addr b#) = I# (minusAddr# a# b#)

 -- | The remainder of the address and the integer.
 remAddr :: Addr -> Int -> Int
 remAddr (Addr a#) (I# i#) = I# (remAddr# a# i#)

 -- | Convert an 'Addr' to an 'Int'.
 addrToInt :: Addr -> Int
 {-# INLINE addrToInt #-}
 addrToInt (Addr addr#) = I# (addr2Int# addr#)

 -- | convert `Addr` to `Ptr a`
 addrToPtr :: Addr -> Ptr a
 addrToPtr (Addr addr#) = Ptr addr#

 -- | convert `Ptr a` to `Addr`
 ptrToAddr :: Ptr a -> Addr
 ptrToAddr (Ptr p) = Addr p

 }}}

-- 
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/15812>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler


More information about the ghc-tickets mailing list