storable-record-0.0.4: Elegant definition of Storable instances for records

Safe HaskellSafe
LanguageHaskell98

Foreign.Storable.Traversable

Description

If you have a Traversable instance of a record, you can load and store all elements, that are accessible by Traversable methods. We treat the record like an array, that is we assume, that all elements have the same size and alignment.

Example:

import Foreign.Storable.Traversable as Store

data Stereo a = Stereo {left, right :: a}

instance Functor Stereo where
   fmap = Trav.fmapDefault

instance Foldable Stereo where
   foldMap = Trav.foldMapDefault

instance Traversable Stereo where
   sequenceA ~(Stereo l r) = liftA2 Stereo l r

instance (Storable a) => Storable (Stereo a) where
   sizeOf = Store.sizeOf
   alignment = Store.alignment
   peek = Store.peek (error "instance Traversable Stereo is lazy, so we do not provide a real value here")
   poke = Store.poke

You would certainly not define the Traversable and according instances just for the implementation of the Storable instance, but there are usually similar applications where the Traversable instance is useful.

Synopsis

Documentation

alignment :: (Foldable f, Storable a) => f a -> Int Source #

sizeOf :: (Foldable f, Storable a) => f a -> Int Source #

peek :: (Traversable f, Storable a) => f () -> Ptr (f a) -> IO (f a) Source #

peek skeleton ptr fills the skeleton with data read from memory beginning at ptr. The skeleton is needed formally for using Traversable. For instance when reading a list, it is not clear, how many elements shall be read. Using the skeleton you can give this information and you also provide information that is not contained in the element type a. For example you can call

peek (replicate 10 ()) ptr

for reading 10 elements from memory starting at ptr.

poke :: (Foldable f, Storable a) => Ptr (f a) -> f a -> IO () Source #

peekApplicative :: (Applicative f, Traversable f, Storable a) => Ptr (f a) -> IO (f a) Source #

Like peek but uses pure for construction of the result. pure would be in class Pointed if that would exist. Thus we use the closest approximate Applicative.