{-# LANGUAGE DefaultSignatures #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE InstanceSigs #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE UndecidableInstances #-} module Foreign.Storable.ATS ( ATSStorable (..) , AsCString (..) , Indexed (..) ) where import Control.Composition import qualified Data.ByteString as BS import qualified Data.ByteString.Lazy as BSL import Data.Data import qualified Data.Text as T import qualified Data.Text.Lazy as TL import Data.Word import Foreign.C.String import Foreign.Marshal.Alloc import Foreign.Ptr import qualified Foreign.Storable as C import GHC.Generics class AsCString a where toCString :: a -> IO CString instance AsCString String where toCString = newCString instance AsCString T.Text where toCString = newCString . T.unpack instance AsCString TL.Text where toCString = newCString . TL.unpack instance AsCString BS.ByteString where toCString = flip BS.useAsCString pure instance AsCString BSL.ByteString where toCString = flip BS.useAsCString pure . BSL.toStrict class Storable' f where sizeOf' :: f a -> Int alignment' :: f a -> Int peek' :: Word8 -> Ptr (f a) -> IO (f a) poke' :: Word8 -> Ptr (f a) -> f a -> IO () pokeByteOff' :: Ptr (f a) -> Int -> f a -> IO () pokeByteOff' = poke' 0 .* plusPtr peekByteOff' :: Ptr (f a) -> Int -> IO (f a) peekByteOff' = peek' 0 .* plusPtr instance Storable' V1 where peek' = undefined poke' = undefined alignment' = undefined sizeOf' = undefined instance (Storable' a, Storable' b) => Storable' (a :*: b) where sizeOf' _ = sizeOf' (undefined :: a x) + sizeOf' (undefined :: b x) alignment' _ = gcd (alignment' (undefined :: a x)) (alignment' (undefined :: b x)) peek' n ptr = do a <- peek' n (castPtr ptr) (a :*:) <$> peekByteOff' (castPtr ptr) (sizeOf' a) poke' n ptr (a :*: b) = mconcat [ poke' n (castPtr ptr) a , pokeByteOff' (castPtr ptr) (sizeOf' a) b ] instance C.Storable a => ATSStorable a where sizeOf :: a -> Int sizeOf = C.sizeOf alignment :: a -> Int alignment = C.alignment poke :: Ptr a -> a -> IO () poke = C.poke peek :: Ptr a -> IO a peek = C.peek asIndex :: (Data a) => a -> Int asIndex x = length $ takeWhile (/= ix) cs where ix = toConstr x cs = dataTypeConstrs (dataTypeOf x) instance (Storable' a, Storable' b) => Storable' (a :+: b) where sizeOf' _ = 1 + max (sizeOf' (undefined :: a x)) (sizeOf' (undefined :: b x)) alignment' _ = 1 peek' n ptr = do tag <- peek (castPtr ptr) g (tag :: Word8) where g t | t == n = pure L1 <*> peekByteOff' (castPtr ptr) 1 | otherwise = pure R1 <*> peekByteOff' (castPtr ptr) 1 poke' n ptr (L1 val) = mconcat [ poke (castPtr ptr) (n :: Word8) , pokeByteOff' (castPtr ptr) 1 val ] poke' n ptr (R1 val) = mconcat [ poke (castPtr ptr) (n :: Word8) , pokeByteOff' (castPtr ptr) 1 val ] -- instance (ATSStorable a) => Storable' (K1 i a) where sizeOf' _ = sizeOf (undefined :: a) alignment' _ = alignment (undefined :: a) peek' _ ptr = pure K1 <*> peek (castPtr ptr) poke' _ ptr (K1 val) = poke (castPtr ptr) val instance (Storable' a) => Storable' (M1 i c a) where sizeOf' _ = sizeOf' (undefined :: a x) alignment' _ = alignment' (undefined :: a x) peek' n ptr = pure M1 <*> peek' n (castPtr ptr) poke' n ptr (M1 val) = poke' n (castPtr ptr) val class Indexed a where index :: a -> Word8 default index :: (Data a) => a -> Word8 index = fromIntegral . asIndex class ATSStorable a where sizeOf :: a -> Int default sizeOf :: (Generic a, Storable' (Rep a)) => a -> Int sizeOf _ = (sizeOf' . from) (undefined :: a) alignment :: a -> Int default alignment :: (Generic a, Storable' (Rep a)) => a -> Int alignment _ = (alignment' . from) (undefined :: a) poke :: Ptr a -> a -> IO () default poke :: (Generic a, Indexed a, Storable' (Rep a)) => Ptr a -> a -> IO () poke ptr x = poke' (index x) (castPtr ptr) (from x) peek :: Ptr a -> IO a default peek :: (Generic a, Indexed a, Storable' (Rep a)) => Ptr a -> IO a peek = fmap to . peek' undefined . castPtr writePtr :: a -> IO (Ptr a) writePtr val = do ptr <- mallocBytes (sizeOf val) poke ptr val pure ptr