primitive-addr-0.1.0.2: Addresses to unmanaged memory

Safe HaskellNone
LanguageHaskell2010

Data.Primitive.Addr

Contents

Description

Primitive operations on machine addresses.

Synopsis

Types

data Addr Source #

A machine address

Constructors

Addr Addr# 
Instances
Eq Addr Source # 
Instance details

Defined in Data.Primitive.Addr

Methods

(==) :: Addr -> Addr -> Bool #

(/=) :: Addr -> Addr -> Bool #

Ord Addr Source # 
Instance details

Defined in Data.Primitive.Addr

Methods

compare :: Addr -> Addr -> Ordering #

(<) :: Addr -> Addr -> Bool #

(<=) :: Addr -> Addr -> Bool #

(>) :: Addr -> Addr -> Bool #

(>=) :: Addr -> Addr -> Bool #

max :: Addr -> Addr -> Addr #

min :: Addr -> Addr -> Addr #

Show Addr Source # 
Instance details

Defined in Data.Primitive.Addr

Methods

showsPrec :: Int -> Addr -> ShowS #

show :: Addr -> String #

showList :: [Addr] -> ShowS #

Address arithmetic

nullAddr :: Addr Source #

The null address

plusAddr :: Addr -> Int -> Addr infixl 6 Source #

Offset an address by the given number of bytes

minusAddr :: Addr -> Addr -> Int infixl 6 Source #

Distance in bytes between two addresses. The result is only valid if the difference fits in an Int.

remAddr :: Addr -> Int -> Int infixl 7 Source #

The remainder of the address and the integer.

Element access

indexOffAddr :: Prim a => Addr -> Int -> a Source #

Read a value from a memory position given by an address and an offset. The memory block the address refers to must be immutable. The offset is in elements of type a rather than in bytes.

readOffAddr :: (Prim a, PrimMonad m) => Addr -> Int -> m a Source #

Read a value from a memory position given by an address and an offset. The offset is in elements of type a rather than in bytes.

writeOffAddr :: (Prim a, PrimMonad m) => Addr -> Int -> a -> m () Source #

Write a value to a memory position given by an address and an offset. The offset is in elements of type a rather than in bytes.

Block operations

copyAddr Source #

Arguments

:: PrimMonad m 
=> Addr

destination address

-> Addr

source address

-> Int

number of bytes

-> m () 

Copy the given number of bytes from the second Addr to the first. The areas may not overlap.

copyAddrToByteArray Source #

Arguments

:: PrimMonad m 
=> MutableByteArray (PrimState m)

destination

-> Int

offset into the destination array

-> Addr

source

-> Int

number of bytes to copy

-> m () 

Copy the given number of bytes from the Addr to the MutableByteArray. The areas may not overlap. This function is only available when compiling with GHC 7.8 or newer.

moveAddr Source #

Arguments

:: PrimMonad m 
=> Addr

destination address

-> Addr

source address

-> Int

number of bytes

-> m () 

Copy the given number of bytes from the second Addr to the first. The areas may overlap.

setAddr :: (Prim a, PrimMonad m) => Addr -> Int -> a -> m () Source #

Fill a memory block of with the given value. The length is in elements of type a rather than in bytes.

Conversion

addrToInt :: Addr -> Int Source #

Convert an Addr to an Int.