foundation-0.0.30: Alternative prelude with batteries and no dependencies
LicenseBSD-style
MaintainerHaskell Foundation
Stabilityexperimental
Portabilityportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Foundation.Class.Storable

Description

Synopsis

Documentation

class Storable a where Source #

Storable type of self determined size.

Methods

peek :: Ptr a -> IO a Source #

poke :: Ptr a -> a -> IO () Source #

Instances

Instances details
Storable CChar Source # 
Instance details

Defined in Foundation.Class.Storable

Methods

peek :: Ptr CChar -> IO CChar Source #

poke :: Ptr CChar -> CChar -> IO () Source #

Storable CUChar Source # 
Instance details

Defined in Foundation.Class.Storable

Storable Int16 Source # 
Instance details

Defined in Foundation.Class.Storable

Methods

peek :: Ptr Int16 -> IO Int16 Source #

poke :: Ptr Int16 -> Int16 -> IO () Source #

Storable Int32 Source # 
Instance details

Defined in Foundation.Class.Storable

Methods

peek :: Ptr Int32 -> IO Int32 Source #

poke :: Ptr Int32 -> Int32 -> IO () Source #

Storable Int64 Source # 
Instance details

Defined in Foundation.Class.Storable

Methods

peek :: Ptr Int64 -> IO Int64 Source #

poke :: Ptr Int64 -> Int64 -> IO () Source #

Storable Int8 Source # 
Instance details

Defined in Foundation.Class.Storable

Methods

peek :: Ptr Int8 -> IO Int8 Source #

poke :: Ptr Int8 -> Int8 -> IO () Source #

Storable Word16 Source # 
Instance details

Defined in Foundation.Class.Storable

Storable Word32 Source # 
Instance details

Defined in Foundation.Class.Storable

Storable Word64 Source # 
Instance details

Defined in Foundation.Class.Storable

Storable Word8 Source # 
Instance details

Defined in Foundation.Class.Storable

Methods

peek :: Ptr Word8 -> IO Word8 Source #

poke :: Ptr Word8 -> Word8 -> IO () Source #

Storable Word128 Source # 
Instance details

Defined in Foundation.Class.Storable

Storable Word256 Source # 
Instance details

Defined in Foundation.Class.Storable

Storable IPv4 Source # 
Instance details

Defined in Foundation.Network.IPv4

Methods

peek :: Ptr IPv4 -> IO IPv4 Source #

poke :: Ptr IPv4 -> IPv4 -> IO () Source #

Storable IPv6 Source # 
Instance details

Defined in Foundation.Network.IPv6

Methods

peek :: Ptr IPv6 -> IO IPv6 Source #

poke :: Ptr IPv6 -> IPv6 -> IO () Source #

Storable UUID Source # 
Instance details

Defined in Foundation.UUID

Methods

peek :: Ptr UUID -> IO UUID Source #

poke :: Ptr UUID -> UUID -> IO () Source #

Storable Char Source # 
Instance details

Defined in Foundation.Class.Storable

Methods

peek :: Ptr Char -> IO Char Source #

poke :: Ptr Char -> Char -> IO () Source #

Storable Double Source # 
Instance details

Defined in Foundation.Class.Storable

Storable Float Source # 
Instance details

Defined in Foundation.Class.Storable

Methods

peek :: Ptr Float -> IO Float Source #

poke :: Ptr Float -> Float -> IO () Source #

Storable (Ptr a) Source # 
Instance details

Defined in Foundation.Class.Storable

Methods

peek :: Ptr (Ptr a) -> IO (Ptr a) Source #

poke :: Ptr (Ptr a) -> Ptr a -> IO () Source #

Storable (BE Word16) Source # 
Instance details

Defined in Foundation.Class.Storable

Methods

peek :: Ptr (BE Word16) -> IO (BE Word16) Source #

poke :: Ptr (BE Word16) -> BE Word16 -> IO () Source #

Storable (BE Word32) Source # 
Instance details

Defined in Foundation.Class.Storable

Methods

peek :: Ptr (BE Word32) -> IO (BE Word32) Source #

poke :: Ptr (BE Word32) -> BE Word32 -> IO () Source #

Storable (BE Word64) Source # 
Instance details

Defined in Foundation.Class.Storable

Methods

peek :: Ptr (BE Word64) -> IO (BE Word64) Source #

poke :: Ptr (BE Word64) -> BE Word64 -> IO () Source #

Storable (BE Word128) Source # 
Instance details

Defined in Foundation.Class.Storable

Methods

peek :: Ptr (BE Word128) -> IO (BE Word128) Source #

poke :: Ptr (BE Word128) -> BE Word128 -> IO () Source #

Storable (BE Word256) Source # 
Instance details

Defined in Foundation.Class.Storable

Methods

peek :: Ptr (BE Word256) -> IO (BE Word256) Source #

poke :: Ptr (BE Word256) -> BE Word256 -> IO () Source #

Storable (LE Word16) Source # 
Instance details

Defined in Foundation.Class.Storable

Methods

peek :: Ptr (LE Word16) -> IO (LE Word16) Source #

poke :: Ptr (LE Word16) -> LE Word16 -> IO () Source #

Storable (LE Word32) Source # 
Instance details

Defined in Foundation.Class.Storable

Methods

peek :: Ptr (LE Word32) -> IO (LE Word32) Source #

poke :: Ptr (LE Word32) -> LE Word32 -> IO () Source #

Storable (LE Word64) Source # 
Instance details

Defined in Foundation.Class.Storable

Methods

peek :: Ptr (LE Word64) -> IO (LE Word64) Source #

poke :: Ptr (LE Word64) -> LE Word64 -> IO () Source #

Storable (LE Word128) Source # 
Instance details

Defined in Foundation.Class.Storable

Methods

peek :: Ptr (LE Word128) -> IO (LE Word128) Source #

poke :: Ptr (LE Word128) -> LE Word128 -> IO () Source #

Storable (LE Word256) Source # 
Instance details

Defined in Foundation.Class.Storable

Methods

peek :: Ptr (LE Word256) -> IO (LE Word256) Source #

poke :: Ptr (LE Word256) -> LE Word256 -> IO () Source #

class Storable a => StorableFixed a where Source #

Extending the Storable type class to the types that can be sequenced in a structure.

Methods

size :: proxy a -> CountOf Word8 Source #

alignment :: proxy a -> CountOf Word8 Source #

Instances

Instances details
StorableFixed CChar Source # 
Instance details

Defined in Foundation.Class.Storable

Methods

size :: proxy CChar -> CountOf Word8 Source #

alignment :: proxy CChar -> CountOf Word8 Source #

StorableFixed CUChar Source # 
Instance details

Defined in Foundation.Class.Storable

StorableFixed Int16 Source # 
Instance details

Defined in Foundation.Class.Storable

Methods

size :: proxy Int16 -> CountOf Word8 Source #

alignment :: proxy Int16 -> CountOf Word8 Source #

StorableFixed Int32 Source # 
Instance details

Defined in Foundation.Class.Storable

Methods

size :: proxy Int32 -> CountOf Word8 Source #

alignment :: proxy Int32 -> CountOf Word8 Source #

StorableFixed Int64 Source # 
Instance details

Defined in Foundation.Class.Storable

Methods

size :: proxy Int64 -> CountOf Word8 Source #

alignment :: proxy Int64 -> CountOf Word8 Source #

StorableFixed Int8 Source # 
Instance details

Defined in Foundation.Class.Storable

Methods

size :: proxy Int8 -> CountOf Word8 Source #

alignment :: proxy Int8 -> CountOf Word8 Source #

StorableFixed Word16 Source # 
Instance details

Defined in Foundation.Class.Storable

StorableFixed Word32 Source # 
Instance details

Defined in Foundation.Class.Storable

StorableFixed Word64 Source # 
Instance details

Defined in Foundation.Class.Storable

StorableFixed Word8 Source # 
Instance details

Defined in Foundation.Class.Storable

Methods

size :: proxy Word8 -> CountOf Word8 Source #

alignment :: proxy Word8 -> CountOf Word8 Source #

StorableFixed Word128 Source # 
Instance details

Defined in Foundation.Class.Storable

StorableFixed Word256 Source # 
Instance details

Defined in Foundation.Class.Storable

StorableFixed IPv4 Source # 
Instance details

Defined in Foundation.Network.IPv4

Methods

size :: proxy IPv4 -> CountOf Word8 Source #

alignment :: proxy IPv4 -> CountOf Word8 Source #

StorableFixed IPv6 Source # 
Instance details

Defined in Foundation.Network.IPv6

Methods

size :: proxy IPv6 -> CountOf Word8 Source #

alignment :: proxy IPv6 -> CountOf Word8 Source #

StorableFixed UUID Source # 
Instance details

Defined in Foundation.UUID

Methods

size :: proxy UUID -> CountOf Word8 Source #

alignment :: proxy UUID -> CountOf Word8 Source #

StorableFixed Char Source # 
Instance details

Defined in Foundation.Class.Storable

Methods

size :: proxy Char -> CountOf Word8 Source #

alignment :: proxy Char -> CountOf Word8 Source #

StorableFixed Double Source # 
Instance details

Defined in Foundation.Class.Storable

StorableFixed Float Source # 
Instance details

Defined in Foundation.Class.Storable

Methods

size :: proxy Float -> CountOf Word8 Source #

alignment :: proxy Float -> CountOf Word8 Source #

StorableFixed (Ptr a) Source # 
Instance details

Defined in Foundation.Class.Storable

Methods

size :: proxy (Ptr a) -> CountOf Word8 Source #

alignment :: proxy (Ptr a) -> CountOf Word8 Source #

StorableFixed (BE Word16) Source # 
Instance details

Defined in Foundation.Class.Storable

Methods

size :: proxy (BE Word16) -> CountOf Word8 Source #

alignment :: proxy (BE Word16) -> CountOf Word8 Source #

StorableFixed (BE Word32) Source # 
Instance details

Defined in Foundation.Class.Storable

Methods

size :: proxy (BE Word32) -> CountOf Word8 Source #

alignment :: proxy (BE Word32) -> CountOf Word8 Source #

StorableFixed (BE Word64) Source # 
Instance details

Defined in Foundation.Class.Storable

Methods

size :: proxy (BE Word64) -> CountOf Word8 Source #

alignment :: proxy (BE Word64) -> CountOf Word8 Source #

StorableFixed (BE Word128) Source # 
Instance details

Defined in Foundation.Class.Storable

Methods

size :: proxy (BE Word128) -> CountOf Word8 Source #

alignment :: proxy (BE Word128) -> CountOf Word8 Source #

StorableFixed (BE Word256) Source # 
Instance details

Defined in Foundation.Class.Storable

Methods

size :: proxy (BE Word256) -> CountOf Word8 Source #

alignment :: proxy (BE Word256) -> CountOf Word8 Source #

StorableFixed (LE Word16) Source # 
Instance details

Defined in Foundation.Class.Storable

Methods

size :: proxy (LE Word16) -> CountOf Word8 Source #

alignment :: proxy (LE Word16) -> CountOf Word8 Source #

StorableFixed (LE Word32) Source # 
Instance details

Defined in Foundation.Class.Storable

Methods

size :: proxy (LE Word32) -> CountOf Word8 Source #

alignment :: proxy (LE Word32) -> CountOf Word8 Source #

StorableFixed (LE Word64) Source # 
Instance details

Defined in Foundation.Class.Storable

Methods

size :: proxy (LE Word64) -> CountOf Word8 Source #

alignment :: proxy (LE Word64) -> CountOf Word8 Source #

StorableFixed (LE Word128) Source # 
Instance details

Defined in Foundation.Class.Storable

Methods

size :: proxy (LE Word128) -> CountOf Word8 Source #

alignment :: proxy (LE Word128) -> CountOf Word8 Source #

StorableFixed (LE Word256) Source # 
Instance details

Defined in Foundation.Class.Storable

Methods

size :: proxy (LE Word256) -> CountOf Word8 Source #

alignment :: proxy (LE Word256) -> CountOf Word8 Source #

Ptr

data Ptr a Source #

A value of type Ptr a represents a pointer to an object, or an array of objects, which may be marshalled to or from Haskell values of type a.

The type a will often be an instance of class Storable which provides the marshalling operations. However this is not essential, and you can provide your own operations to access the pointer. For example you might write small foreign functions to get or set the fields of a C struct.

Instances

Instances details
Generic1 (URec (Ptr ()) :: k -> Type) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 (URec (Ptr ())) :: k -> Type Source #

Methods

from1 :: forall (a :: k0). URec (Ptr ()) a -> Rep1 (URec (Ptr ())) a Source #

to1 :: forall (a :: k0). Rep1 (URec (Ptr ())) a -> URec (Ptr ()) a Source #

Data a => Data (Ptr a)

Since: base-4.8.0.0

Instance details

Defined in Data.Data

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Ptr a -> c (Ptr a) Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Ptr a) Source #

toConstr :: Ptr a -> Constr Source #

dataTypeOf :: Ptr a -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Ptr a)) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Ptr a)) Source #

gmapT :: (forall b. Data b => b -> b) -> Ptr a -> Ptr a Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Ptr a -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Ptr a -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Ptr a -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Ptr a -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Ptr a -> m (Ptr a) Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Ptr a -> m (Ptr a) Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Ptr a -> m (Ptr a) Source #

Foldable (UAddr :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Foldable

Methods

fold :: Monoid m => UAddr m -> m Source #

foldMap :: Monoid m => (a -> m) -> UAddr a -> m Source #

foldMap' :: Monoid m => (a -> m) -> UAddr a -> m Source #

foldr :: (a -> b -> b) -> b -> UAddr a -> b Source #

foldr' :: (a -> b -> b) -> b -> UAddr a -> b Source #

foldl :: (b -> a -> b) -> b -> UAddr a -> b Source #

foldl' :: (b -> a -> b) -> b -> UAddr a -> b Source #

foldr1 :: (a -> a -> a) -> UAddr a -> a Source #

foldl1 :: (a -> a -> a) -> UAddr a -> a Source #

toList :: UAddr a -> [a] Source #

null :: UAddr a -> Bool Source #

length :: UAddr a -> Int Source #

elem :: Eq a => a -> UAddr a -> Bool Source #

maximum :: Ord a => UAddr a -> a Source #

minimum :: Ord a => UAddr a -> a Source #

sum :: Num a => UAddr a -> a Source #

product :: Num a => UAddr a -> a Source #

Traversable (UAddr :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> UAddr a -> f (UAddr b) Source #

sequenceA :: Applicative f => UAddr (f a) -> f (UAddr a) Source #

mapM :: Monad m => (a -> m b) -> UAddr a -> m (UAddr b) Source #

sequence :: Monad m => UAddr (m a) -> m (UAddr a) Source #

Storable (Ptr a)

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Ptr a -> Int Source #

alignment :: Ptr a -> Int Source #

peekElemOff :: Ptr (Ptr a) -> Int -> IO (Ptr a) Source #

pokeElemOff :: Ptr (Ptr a) -> Int -> Ptr a -> IO () Source #

peekByteOff :: Ptr b -> Int -> IO (Ptr a) Source #

pokeByteOff :: Ptr b -> Int -> Ptr a -> IO () Source #

peek :: Ptr (Ptr a) -> IO (Ptr a) Source #

poke :: Ptr (Ptr a) -> Ptr a -> IO () Source #

Show (Ptr a)

Since: base-2.1

Instance details

Defined in GHC.Ptr

Methods

showsPrec :: Int -> Ptr a -> ShowS Source #

show :: Ptr a -> String Source #

showList :: [Ptr a] -> ShowS Source #

NormalForm (Ptr a) 
Instance details

Defined in Basement.NormalForm

Methods

toNormalForm :: Ptr a -> () Source #

Storable (Ptr a) Source # 
Instance details

Defined in Foundation.Class.Storable

Methods

peek :: Ptr (Ptr a) -> IO (Ptr a) Source #

poke :: Ptr (Ptr a) -> Ptr a -> IO () Source #

StorableFixed (Ptr a) Source # 
Instance details

Defined in Foundation.Class.Storable

Methods

size :: proxy (Ptr a) -> CountOf Word8 Source #

alignment :: proxy (Ptr a) -> CountOf Word8 Source #

Eq (Ptr a)

Since: base-2.1

Instance details

Defined in GHC.Ptr

Methods

(==) :: Ptr a -> Ptr a -> Bool Source #

(/=) :: Ptr a -> Ptr a -> Bool Source #

Ord (Ptr a)

Since: base-2.1

Instance details

Defined in GHC.Ptr

Methods

compare :: Ptr a -> Ptr a -> Ordering Source #

(<) :: Ptr a -> Ptr a -> Bool Source #

(<=) :: Ptr a -> Ptr a -> Bool Source #

(>) :: Ptr a -> Ptr a -> Bool Source #

(>=) :: Ptr a -> Ptr a -> Bool Source #

max :: Ptr a -> Ptr a -> Ptr a Source #

min :: Ptr a -> Ptr a -> Ptr a Source #

Functor (URec (Ptr ()) :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

fmap :: (a -> b) -> URec (Ptr ()) a -> URec (Ptr ()) b Source #

(<$) :: a -> URec (Ptr ()) b -> URec (Ptr ()) a Source #

Generic (URec (Ptr ()) p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec (Ptr ()) p) :: Type -> Type Source #

Methods

from :: URec (Ptr ()) p -> Rep (URec (Ptr ()) p) x Source #

to :: Rep (URec (Ptr ()) p) x -> URec (Ptr ()) p Source #

Eq (URec (Ptr ()) p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

(==) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool Source #

(/=) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool Source #

Ord (URec (Ptr ()) p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

compare :: URec (Ptr ()) p -> URec (Ptr ()) p -> Ordering Source #

(<) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool Source #

(<=) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool Source #

(>) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool Source #

(>=) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool Source #

max :: URec (Ptr ()) p -> URec (Ptr ()) p -> URec (Ptr ()) p Source #

min :: URec (Ptr ()) p -> URec (Ptr ()) p -> URec (Ptr ()) p Source #

data URec (Ptr ()) (p :: k)

Used for marking occurrences of Addr#

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

data URec (Ptr ()) (p :: k) = UAddr {}
type Rep1 (URec (Ptr ()) :: k -> Type)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

type Rep1 (URec (Ptr ()) :: k -> Type) = D1 ('MetaData "URec" "GHC.Generics" "base" 'False) (C1 ('MetaCons "UAddr" 'PrefixI 'True) (S1 ('MetaSel ('Just "uAddr#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UAddr :: k -> Type)))
type Rep (URec (Ptr ()) p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

type Rep (URec (Ptr ()) p) = D1 ('MetaData "URec" "GHC.Generics" "base" 'False) (C1 ('MetaCons "UAddr" 'PrefixI 'True) (S1 ('MetaSel ('Just "uAddr#") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (UAddr :: Type -> Type)))

castPtr :: Ptr a -> Ptr b Source #

The castPtr function casts a pointer from one type to another.

offset based helper

peekOff :: StorableFixed a => Ptr a -> Offset a -> IO a Source #

like peek but at a given offset.

pokeOff :: StorableFixed a => Ptr a -> Offset a -> a -> IO () Source #

like poke but at a given offset.

Collection

peekArray :: (Buildable col, StorableFixed (Element col)) => CountOf (Element col) -> Ptr (Element col) -> IO col Source #

peekArrayEndedBy :: (Buildable col, StorableFixed (Element col), Eq (Element col), Show (Element col)) => Element col -> Ptr (Element col) -> IO col Source #

pokeArray :: (Sequential col, StorableFixed (Element col)) => Ptr (Element col) -> col -> IO () Source #

pokeArrayEndedBy :: (Sequential col, StorableFixed (Element col)) => Element col -> Ptr (Element col) -> col -> IO () Source #