storable-generic-0.1.0.5: Derive Storable instances with GHC.Generics
Safe HaskellSafe-Inferred
LanguageHaskell2010

Foreign.Storable.Generic

Synopsis

STORABLE CLASS FOR GENERIC

class G a where Source #

Minimal complete definition

Nothing

Methods

gSizeOf :: a -> Int Source #

default gSizeOf :: MapTypeVal2 Sizable (Flatten (Rep a)) => a -> Int Source #

gAlignment :: a -> Int Source #

default gAlignment :: MapTypeVal2 Sizable (Flatten (Rep a)) => a -> Int Source #

gPeek :: Ptr a -> IO a Source #

default gPeek :: (Generic a, Gg (Rep a)) => Ptr a -> IO a Source #

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

default gPoke :: (Generic a, Gg (Rep a)) => Ptr a -> a -> IO () Source #

Instances

Instances details
(Storable a, Storable b) => G (a, b) Source # 
Instance details

Defined in Foreign.Storable.Generic

Methods

gSizeOf :: (a, b) -> Int Source #

gAlignment :: (a, b) -> Int Source #

gPeek :: Ptr (a, b) -> IO (a, b) Source #

gPoke :: Ptr (a, b) -> (a, b) -> IO () Source #

(Storable a, Storable b, Storable c) => G (a, b, c) Source # 
Instance details

Defined in Foreign.Storable.Generic

Methods

gSizeOf :: (a, b, c) -> Int Source #

gAlignment :: (a, b, c) -> Int Source #

gPeek :: Ptr (a, b, c) -> IO (a, b, c) Source #

gPoke :: Ptr (a, b, c) -> (a, b, c) -> IO () Source #

(Storable a, Storable b, Storable c, Storable d) => G (a, b, c, d) Source # 
Instance details

Defined in Foreign.Storable.Generic

Methods

gSizeOf :: (a, b, c, d) -> Int Source #

gAlignment :: (a, b, c, d) -> Int Source #

gPeek :: Ptr (a, b, c, d) -> IO (a, b, c, d) Source #

gPoke :: Ptr (a, b, c, d) -> (a, b, c, d) -> IO () Source #

(Storable a, Storable b, Storable c, Storable d, Storable e) => G (a, b, c, d, e) Source # 
Instance details

Defined in Foreign.Storable.Generic

Methods

gSizeOf :: (a, b, c, d, e) -> Int Source #

gAlignment :: (a, b, c, d, e) -> Int Source #

gPeek :: Ptr (a, b, c, d, e) -> IO (a, b, c, d, e) Source #

gPoke :: Ptr (a, b, c, d, e) -> (a, b, c, d, e) -> IO () Source #

(Storable a, Storable b, Storable c, Storable d, Storable e, Storable f) => G (a, b, c, d, e, f) Source # 
Instance details

Defined in Foreign.Storable.Generic

Methods

gSizeOf :: (a, b, c, d, e, f) -> Int Source #

gAlignment :: (a, b, c, d, e, f) -> Int Source #

gPeek :: Ptr (a, b, c, d, e, f) -> IO (a, b, c, d, e, f) Source #

gPoke :: Ptr (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> IO () Source #

(Storable a, Storable b, Storable c, Storable d, Storable e, Storable f, Storable g) => G (a, b, c, d, e, f, g) Source # 
Instance details

Defined in Foreign.Storable.Generic

Methods

gSizeOf :: (a, b, c, d, e, f, g) -> Int Source #

gAlignment :: (a, b, c, d, e, f, g) -> Int Source #

gPeek :: Ptr (a, b, c, d, e, f, g) -> IO (a, b, c, d, e, f, g) Source #

gPoke :: Ptr (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> IO () Source #

(Storable a, Storable b, Storable c, Storable d, Storable e, Storable f, Storable g, Storable h) => G (a, b, c, d, e, f, g, h) Source # 
Instance details

Defined in Foreign.Storable.Generic

Methods

gSizeOf :: (a, b, c, d, e, f, g, h) -> Int Source #

gAlignment :: (a, b, c, d, e, f, g, h) -> Int Source #

gPeek :: Ptr (a, b, c, d, e, f, g, h) -> IO (a, b, c, d, e, f, g, h) Source #

gPoke :: Ptr (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> IO () Source #

(Storable a, Storable b, Storable c, Storable d, Storable e, Storable f, Storable g, Storable h, Storable i) => G (a, b, c, d, e, f, g, h, i) Source # 
Instance details

Defined in Foreign.Storable.Generic

Methods

gSizeOf :: (a, b, c, d, e, f, g, h, i) -> Int Source #

gAlignment :: (a, b, c, d, e, f, g, h, i) -> Int Source #

gPeek :: Ptr (a, b, c, d, e, f, g, h, i) -> IO (a, b, c, d, e, f, g, h, i) Source #

gPoke :: Ptr (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> IO () Source #

(Storable a, Storable b, Storable c, Storable d, Storable e, Storable f, Storable g, Storable h, Storable i, Storable j) => G (a, b, c, d, e, f, g, h, i, j) Source # 
Instance details

Defined in Foreign.Storable.Generic

Methods

gSizeOf :: (a, b, c, d, e, f, g, h, i, j) -> Int Source #

gAlignment :: (a, b, c, d, e, f, g, h, i, j) -> Int Source #

gPeek :: Ptr (a, b, c, d, e, f, g, h, i, j) -> IO (a, b, c, d, e, f, g, h, i, j) Source #

gPoke :: Ptr (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) -> IO () Source #

(Storable a, Storable b, Storable c, Storable d, Storable e, Storable f, Storable g, Storable h, Storable i, Storable j, Storable k) => G (a, b, c, d, e, f, g, h, i, j, k) Source # 
Instance details

Defined in Foreign.Storable.Generic

Methods

gSizeOf :: (a, b, c, d, e, f, g, h, i, j, k) -> Int Source #

gAlignment :: (a, b, c, d, e, f, g, h, i, j, k) -> Int Source #

gPeek :: Ptr (a, b, c, d, e, f, g, h, i, j, k) -> IO (a, b, c, d, e, f, g, h, i, j, k) Source #

gPoke :: Ptr (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) -> IO () Source #

(Storable a, Storable b, Storable c, Storable d, Storable e, Storable f, Storable g, Storable h, Storable i, Storable j, Storable k, Storable l) => G (a, b, c, d, e, f, g, h, i, j, k, l) Source # 
Instance details

Defined in Foreign.Storable.Generic

Methods

gSizeOf :: (a, b, c, d, e, f, g, h, i, j, k, l) -> Int Source #

gAlignment :: (a, b, c, d, e, f, g, h, i, j, k, l) -> Int Source #

gPeek :: Ptr (a, b, c, d, e, f, g, h, i, j, k, l) -> IO (a, b, c, d, e, f, g, h, i, j, k, l) Source #

gPoke :: Ptr (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> IO () Source #

(Storable a, Storable b, Storable c, Storable d, Storable e, Storable f, Storable g, Storable h, Storable i, Storable j, Storable k, Storable l, Storable m) => G (a, b, c, d, e, f, g, h, i, j, k, l, m) Source # 
Instance details

Defined in Foreign.Storable.Generic

Methods

gSizeOf :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Int Source #

gAlignment :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Int Source #

gPeek :: Ptr (a, b, c, d, e, f, g, h, i, j, k, l, m) -> IO (a, b, c, d, e, f, g, h, i, j, k, l, m) Source #

gPoke :: Ptr (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (a, b, c, d, e, f, g, h, i, j, k, l, m) -> IO () Source #

(Storable a, Storable b, Storable c, Storable d, Storable e, Storable f, Storable g, Storable h, Storable i, Storable j, Storable k, Storable l, Storable m, Storable n) => G (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source # 
Instance details

Defined in Foreign.Storable.Generic

Methods

gSizeOf :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Int Source #

gAlignment :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Int Source #

gPeek :: Ptr (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> IO (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source #

gPoke :: Ptr (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> IO () Source #

(Storable a, Storable b, Storable c, Storable d, Storable e, Storable f, Storable g, Storable h, Storable i, Storable j, Storable k, Storable l, Storable m, Storable n, Storable o) => G (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source # 
Instance details

Defined in Foreign.Storable.Generic

Methods

gSizeOf :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Int Source #

gAlignment :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Int Source #

gPeek :: Ptr (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> IO (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source #

gPoke :: Ptr (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> IO () Source #

WRAPPER

newtype W a Source #

Constructors

W 

Fields

Instances

Instances details
G a => Storable (W a) Source # 
Instance details

Defined in Foreign.Storable.Generic.Internal

Methods

sizeOf :: W a -> Int #

alignment :: W a -> Int #

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

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

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

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

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

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

Enum a => Enum (W a) Source # 
Instance details

Defined in Foreign.Storable.Generic.Internal

Methods

succ :: W a -> W a #

pred :: W a -> W a #

toEnum :: Int -> W a #

fromEnum :: W a -> Int #

enumFrom :: W a -> [W a] #

enumFromThen :: W a -> W a -> [W a] #

enumFromTo :: W a -> W a -> [W a] #

enumFromThenTo :: W a -> W a -> W a -> [W a] #

Generic a => Generic (W a) Source # 
Instance details

Defined in Foreign.Storable.Generic.Internal

Associated Types

type Rep (W a) :: Type -> Type #

Methods

from :: W a -> Rep (W a) x #

to :: Rep (W a) x -> W a #

Show a => Show (W a) Source # 
Instance details

Defined in Foreign.Storable.Generic.Internal

Methods

showsPrec :: Int -> W a -> ShowS #

show :: W a -> String #

showList :: [W a] -> ShowS #

Eq a => Eq (W a) Source # 
Instance details

Defined in Foreign.Storable.Generic.Internal

Methods

(==) :: W a -> W a -> Bool #

(/=) :: W a -> W a -> Bool #

Ord a => Ord (W a) Source # 
Instance details

Defined in Foreign.Storable.Generic.Internal

Methods

compare :: W a -> W a -> Ordering #

(<) :: W a -> W a -> Bool #

(<=) :: W a -> W a -> Bool #

(>) :: W a -> W a -> Bool #

(>=) :: W a -> W a -> Bool #

max :: W a -> W a -> W a #

min :: W a -> W a -> W a #

type Rep (W a) Source # 
Instance details

Defined in Foreign.Storable.Generic.Internal

type Rep (W a) = Rep a

Orphan instances

(Storable a, Storable b) => G (a, b) Source # 
Instance details

Methods

gSizeOf :: (a, b) -> Int Source #

gAlignment :: (a, b) -> Int Source #

gPeek :: Ptr (a, b) -> IO (a, b) Source #

gPoke :: Ptr (a, b) -> (a, b) -> IO () Source #

(Storable a, Storable b, Storable c) => G (a, b, c) Source # 
Instance details

Methods

gSizeOf :: (a, b, c) -> Int Source #

gAlignment :: (a, b, c) -> Int Source #

gPeek :: Ptr (a, b, c) -> IO (a, b, c) Source #

gPoke :: Ptr (a, b, c) -> (a, b, c) -> IO () Source #

(Storable a, Storable b, Storable c, Storable d) => G (a, b, c, d) Source # 
Instance details

Methods

gSizeOf :: (a, b, c, d) -> Int Source #

gAlignment :: (a, b, c, d) -> Int Source #

gPeek :: Ptr (a, b, c, d) -> IO (a, b, c, d) Source #

gPoke :: Ptr (a, b, c, d) -> (a, b, c, d) -> IO () Source #

(Storable a, Storable b, Storable c, Storable d, Storable e) => G (a, b, c, d, e) Source # 
Instance details

Methods

gSizeOf :: (a, b, c, d, e) -> Int Source #

gAlignment :: (a, b, c, d, e) -> Int Source #

gPeek :: Ptr (a, b, c, d, e) -> IO (a, b, c, d, e) Source #

gPoke :: Ptr (a, b, c, d, e) -> (a, b, c, d, e) -> IO () Source #

(Storable a, Storable b, Storable c, Storable d, Storable e, Storable f) => G (a, b, c, d, e, f) Source # 
Instance details

Methods

gSizeOf :: (a, b, c, d, e, f) -> Int Source #

gAlignment :: (a, b, c, d, e, f) -> Int Source #

gPeek :: Ptr (a, b, c, d, e, f) -> IO (a, b, c, d, e, f) Source #

gPoke :: Ptr (a, b, c, d, e, f) -> (a, b, c, d, e, f) -> IO () Source #

(Storable a, Storable b, Storable c, Storable d, Storable e, Storable f, Storable g) => G (a, b, c, d, e, f, g) Source # 
Instance details

Methods

gSizeOf :: (a, b, c, d, e, f, g) -> Int Source #

gAlignment :: (a, b, c, d, e, f, g) -> Int Source #

gPeek :: Ptr (a, b, c, d, e, f, g) -> IO (a, b, c, d, e, f, g) Source #

gPoke :: Ptr (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) -> IO () Source #

(Storable a, Storable b, Storable c, Storable d, Storable e, Storable f, Storable g, Storable h) => G (a, b, c, d, e, f, g, h) Source # 
Instance details

Methods

gSizeOf :: (a, b, c, d, e, f, g, h) -> Int Source #

gAlignment :: (a, b, c, d, e, f, g, h) -> Int Source #

gPeek :: Ptr (a, b, c, d, e, f, g, h) -> IO (a, b, c, d, e, f, g, h) Source #

gPoke :: Ptr (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) -> IO () Source #

(Storable a, Storable b, Storable c, Storable d, Storable e, Storable f, Storable g, Storable h, Storable i) => G (a, b, c, d, e, f, g, h, i) Source # 
Instance details

Methods

gSizeOf :: (a, b, c, d, e, f, g, h, i) -> Int Source #

gAlignment :: (a, b, c, d, e, f, g, h, i) -> Int Source #

gPeek :: Ptr (a, b, c, d, e, f, g, h, i) -> IO (a, b, c, d, e, f, g, h, i) Source #

gPoke :: Ptr (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) -> IO () Source #

(Storable a, Storable b, Storable c, Storable d, Storable e, Storable f, Storable g, Storable h, Storable i, Storable j) => G (a, b, c, d, e, f, g, h, i, j) Source # 
Instance details

Methods

gSizeOf :: (a, b, c, d, e, f, g, h, i, j) -> Int Source #

gAlignment :: (a, b, c, d, e, f, g, h, i, j) -> Int Source #

gPeek :: Ptr (a, b, c, d, e, f, g, h, i, j) -> IO (a, b, c, d, e, f, g, h, i, j) Source #

gPoke :: Ptr (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) -> IO () Source #

(Storable a, Storable b, Storable c, Storable d, Storable e, Storable f, Storable g, Storable h, Storable i, Storable j, Storable k) => G (a, b, c, d, e, f, g, h, i, j, k) Source # 
Instance details

Methods

gSizeOf :: (a, b, c, d, e, f, g, h, i, j, k) -> Int Source #

gAlignment :: (a, b, c, d, e, f, g, h, i, j, k) -> Int Source #

gPeek :: Ptr (a, b, c, d, e, f, g, h, i, j, k) -> IO (a, b, c, d, e, f, g, h, i, j, k) Source #

gPoke :: Ptr (a, b, c, d, e, f, g, h, i, j, k) -> (a, b, c, d, e, f, g, h, i, j, k) -> IO () Source #

(Storable a, Storable b, Storable c, Storable d, Storable e, Storable f, Storable g, Storable h, Storable i, Storable j, Storable k, Storable l) => G (a, b, c, d, e, f, g, h, i, j, k, l) Source # 
Instance details

Methods

gSizeOf :: (a, b, c, d, e, f, g, h, i, j, k, l) -> Int Source #

gAlignment :: (a, b, c, d, e, f, g, h, i, j, k, l) -> Int Source #

gPeek :: Ptr (a, b, c, d, e, f, g, h, i, j, k, l) -> IO (a, b, c, d, e, f, g, h, i, j, k, l) Source #

gPoke :: Ptr (a, b, c, d, e, f, g, h, i, j, k, l) -> (a, b, c, d, e, f, g, h, i, j, k, l) -> IO () Source #

(Storable a, Storable b, Storable c, Storable d, Storable e, Storable f, Storable g, Storable h, Storable i, Storable j, Storable k, Storable l, Storable m) => G (a, b, c, d, e, f, g, h, i, j, k, l, m) Source # 
Instance details

Methods

gSizeOf :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Int Source #

gAlignment :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Int Source #

gPeek :: Ptr (a, b, c, d, e, f, g, h, i, j, k, l, m) -> IO (a, b, c, d, e, f, g, h, i, j, k, l, m) Source #

gPoke :: Ptr (a, b, c, d, e, f, g, h, i, j, k, l, m) -> (a, b, c, d, e, f, g, h, i, j, k, l, m) -> IO () Source #

(Storable a, Storable b, Storable c, Storable d, Storable e, Storable f, Storable g, Storable h, Storable i, Storable j, Storable k, Storable l, Storable m, Storable n) => G (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source # 
Instance details

Methods

gSizeOf :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Int Source #

gAlignment :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Int Source #

gPeek :: Ptr (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> IO (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source #

gPoke :: Ptr (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> IO () Source #

(Storable a, Storable b, Storable c, Storable d, Storable e, Storable f, Storable g, Storable h, Storable i, Storable j, Storable k, Storable l, Storable m, Storable n, Storable o) => G (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source # 
Instance details

Methods

gSizeOf :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Int Source #

gAlignment :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Int Source #

gPeek :: Ptr (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> IO (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source #

gPoke :: Ptr (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> IO () Source #