Skip to content

Commit

Permalink
Added documentation
Browse files Browse the repository at this point in the history
  • Loading branch information
maurer committed Jan 21, 2012
1 parent 992ac7a commit 03165fd
Show file tree
Hide file tree
Showing 3 changed files with 22 additions and 1 deletion.
10 changes: 9 additions & 1 deletion Foreign/CStorable.hs
@@ -1,13 +1,21 @@
-- | This primarily exports the CStorable typeclass, which may have its
-- methods automatically defaulted if it has a Generic instance.
-- Then, this instance can be transfered via the `Storable' constructor.
module Foreign.CStorable module Foreign.CStorable
(CStorable(..) (CStorable(..),
StorableWrap(..)
) where ) where


import Foreign.CStorable.TypeClass import Foreign.CStorable.TypeClass
import Foreign.CStorable.BaseInstances import Foreign.CStorable.BaseInstances
import Foreign.Storable import Foreign.Storable
import Foreign.Ptr import Foreign.Ptr


-- | Applying the `Storable' constructor to something which is Storable
-- gives it a corresponding CStorable instance.
newtype StorableWrap a = Storable a newtype StorableWrap a = Storable a

-- | Translates a Storable instance to a CStorable instance
instance (Storable a) => CStorable (StorableWrap a) where instance (Storable a) => CStorable (StorableWrap a) where
cPeek p = fmap Storable $ peek (castPtr p) cPeek p = fmap Storable $ peek (castPtr p)
cPoke p (Storable x) = poke (castPtr p) x cPoke p (Storable x) = poke (castPtr p) x
Expand Down
1 change: 1 addition & 0 deletions Foreign/CStorable/BaseInstances.hs
@@ -1,3 +1,4 @@
-- | Provides lots of bas instances, pulled over from `Storable'.
module Foreign.CStorable.BaseInstances where module Foreign.CStorable.BaseInstances where


import Data.Word import Data.Word
Expand Down
12 changes: 12 additions & 0 deletions Foreign/CStorable/TypeClass.hs
@@ -1,10 +1,15 @@
{-# LANGUAGE DefaultSignatures #-} {-# LANGUAGE DefaultSignatures #-}
-- | This module provides the mechanical deriving
-- mechanism for `CStorable'.
module Foreign.CStorable.TypeClass where module Foreign.CStorable.TypeClass where


import Foreign.Ptr import Foreign.Ptr
import Foreign.Storable import Foreign.Storable
import GHC.Generics import GHC.Generics


-- | A wrapper class for the raw autoderivation functions,
-- representing twhat is necessary for the defaulted
-- `CStorable' methods.
class GCStorable a where class GCStorable a where
gcPeek :: Ptr (a x)-> IO (a x) gcPeek :: Ptr (a x)-> IO (a x)
gcPoke :: Ptr (a x) -> a x -> IO () gcPoke :: Ptr (a x) -> a x -> IO ()
Expand All @@ -17,15 +22,20 @@ instance GCStorable U1 where
gcAlignment _ = 0 gcAlignment _ = 0
gcSizeOf _ = 0 gcSizeOf _ = 0


-- | Calculates extra space between two items based on alignment
-- and size.
padding :: (GCStorable a, GCStorable b) => a x -> b y -> Int padding :: (GCStorable a, GCStorable b) => a x -> b y -> Int
padding a b = let padding a b = let
sizeA = gcSizeOf a sizeA = gcSizeOf a
alignB = gcAlignment b alignB = gcAlignment b
in ((alignB - sizeA) `mod` alignB) in ((alignB - sizeA) `mod` alignB)


-- | Calculates the total space consumed by a given element, including
-- alignment padding.
offset :: (GCStorable a, GCStorable b) => a x -> b y -> Int offset :: (GCStorable a, GCStorable b) => a x -> b y -> Int
offset a b = padding a b + gcSizeOf a offset a b = padding a b + gcSizeOf a


-- | Test
instance (GCStorable a, GCStorable b) => GCStorable (a :*: b) where instance (GCStorable a, GCStorable b) => GCStorable (a :*: b) where
gcPeek p = do gcPeek p = do
a <- gcPeek $ castPtr p a <- gcPeek $ castPtr p
Expand Down Expand Up @@ -53,6 +63,8 @@ instance (CStorable a) => GCStorable (K1 i a) where
gcAlignment (K1 x) = cAlignment x gcAlignment (K1 x) = cAlignment x
gcSizeOf (K1 x) = cSizeOf x gcSizeOf (K1 x) = cSizeOf x


-- | This typeclass is basically just a duplicate of `Storable'. It exists
-- because I can't easily modify `Storable', as it is part of base.
class CStorable a where class CStorable a where
cPeek :: Ptr a -> IO a cPeek :: Ptr a -> IO a
default cPeek :: (Generic a, GCStorable (Rep a)) => Ptr a -> IO a default cPeek :: (Generic a, GCStorable (Rep a)) => Ptr a -> IO a
Expand Down

0 comments on commit 03165fd

Please sign in to comment.