{-# LINE 1 "src/IGraph/Internal/Attribute.chs" #-}
{-# LANGUAGE ForeignFunctionInterface #-}
module IGraph.Internal.Attribute where
import qualified Foreign.C.String as C2HSImp
import qualified Foreign.C.Types as C2HSImp
import qualified Foreign.Marshal.Utils as C2HSImp
import qualified Foreign.Ptr as C2HSImp
import qualified Foreign.Storable as C2HSImp
import Data.ByteString (packCStringLen)
import Data.ByteString.Unsafe (unsafeUseAsCStringLen)
import Control.Monad
import Control.Applicative
import Data.Serialize (Serialize, decode, encode)
import Foreign
import Foreign.C.Types
import Foreign.C.String
import System.IO.Unsafe (unsafePerformIO)
import IGraph.Internal.Graph
{-# LINE 14 "src/IGraph/Internal/Attribute.chs" #-}
import IGraph.Internal.Data
{-# LINE 15 "src/IGraph/Internal/Attribute.chs" #-}
import IGraph.Internal.Constants
{-# LINE 16 "src/IGraph/Internal/Attribute.chs" #-}
asBS :: Serialize a => a -> (BSLen -> IO b) -> IO b
asBS x fn = unsafeUseAsCStringLen (encode x) (fn . BSLen)
{-# INLINE asBS #-}
asBSVector :: Serialize a => [a] -> (BSVector -> IO b) -> IO b
asBSVector values fn = loop [] values
where
loop acc (x:xs) = unsafeUseAsCStringLen (encode x) $ \ptr ->
loop (BSLen ptr : acc) xs
loop acc _ = toBSVector (reverse acc) >>= fn
{-# INLINE asBSVector #-}
fromBS :: Serialize a => Ptr BSLen -> IO a
fromBS ptr = do
BSLen x <- peek ptr
result <- decode <$> packCStringLen x
case result of
Left msg -> error msg
Right r -> return r
{-# INLINE fromBS #-}
mkStrRec :: CString
-> BSVector
-> AttributeRecord
mkStrRec name xs = AttributeRecord name 2 xs
{-# INLINE mkStrRec #-}
data AttributeRecord = AttributeRecord CString Int BSVector
instance Storable AttributeRecord where
sizeOf _ = 24
{-# LINE 53 "src/IGraph/Internal/Attribute.chs" #-}
alignment _ = 8
{-# LINE 54 "src/IGraph/Internal/Attribute.chs" #-}
peek p = AttributeRecord
<$> ((\ptr -> do {C2HSImp.peekByteOff ptr 0 :: IO (C2HSImp.Ptr C2HSImp.CChar)}) p)
<*> liftM fromIntegral ((\ptr -> do {C2HSImp.peekByteOff ptr 8 :: IO C2HSImp.CInt}) p)
<*> ( do ptr <- (\ptr -> do {C2HSImp.peekByteOff ptr 16 :: IO (C2HSImp.Ptr ())}) p
fptr <- newForeignPtr_ . castPtr $ ptr
return $ BSVector fptr )
poke p (AttributeRecord name t vptr) = do
(\ptr val -> do {C2HSImp.pokeByteOff ptr 0 (val :: (C2HSImp.Ptr C2HSImp.CChar))}) p name
(\ptr val -> do {C2HSImp.pokeByteOff ptr 8 (val :: C2HSImp.CInt)}) p $ fromIntegral t
withBSVector vptr $ \ptr ->
(\ptr val -> do {C2HSImp.pokeByteOff ptr 16 (val :: (C2HSImp.Ptr ()))}) p $ castPtr ptr
igraphHaskellAttributeHasAttr :: (IGraph) -> (AttributeElemtype) -> (String) -> IO ((Bool))
igraphHaskellAttributeHasAttr a1 a2 a3 =
(withIGraph) a1 $ \a1' ->
let {a2' = (fromIntegral . fromEnum) a2} in
C2HSImp.withCString a3 $ \a3' ->
igraphHaskellAttributeHasAttr'_ a1' a2' a3' >>= \res ->
let {res' = C2HSImp.toBool res} in
return (res')
{-# LINE 67 "src/IGraph/Internal/Attribute.chs" #-}
igraphHaskellAttributeGANSet :: (IGraph) -> (String) -> (Double) -> IO ((Int))
igraphHaskellAttributeGANSet a1 a2 a3 =
(withIGraph) a1 $ \a1' ->
C2HSImp.withCString a2 $ \a2' ->
let {a3' = realToFrac a3} in
igraphHaskellAttributeGANSet'_ a1' a2' a3' >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 69 "src/IGraph/Internal/Attribute.chs" #-}
igraphHaskellAttributeGAN :: (IGraph) -> (String) -> IO ((Double))
igraphHaskellAttributeGAN a1 a2 =
(withIGraph) a1 $ \a1' ->
C2HSImp.withCString a2 $ \a2' ->
igraphHaskellAttributeGAN'_ a1' a2' >>= \res ->
let {res' = realToFrac res} in
return (res')
{-# LINE 71 "src/IGraph/Internal/Attribute.chs" #-}
igraphHaskellAttributeVAS :: (IGraph) -> (String) -> (Int) -> IO ((Ptr BSLen))
igraphHaskellAttributeVAS a1 a2 a3 =
(withIGraph) a1 $ \a1' ->
C2HSImp.withCString a2 $ \a2' ->
let {a3' = fromIntegral a3} in
igraphHaskellAttributeVAS'_ a1' a2' a3' >>= \res ->
let {res' = castPtr res} in
return (res')
{-# LINE 73 "src/IGraph/Internal/Attribute.chs" #-}
igraphHaskellAttributeEAN :: (IGraph) -> (String) -> (Int) -> IO ((Double))
igraphHaskellAttributeEAN a1 a2 a3 =
(withIGraph) a1 $ \a1' ->
C2HSImp.withCString a2 $ \a2' ->
let {a3' = fromIntegral a3} in
igraphHaskellAttributeEAN'_ a1' a2' a3' >>= \res ->
let {res' = realToFrac res} in
return (res')
{-# LINE 75 "src/IGraph/Internal/Attribute.chs" #-}
igraphHaskellAttributeEAS :: (IGraph) -> (String) -> (Int) -> IO ((Ptr BSLen))
igraphHaskellAttributeEAS a1 a2 a3 =
(withIGraph) a1 $ \a1' ->
C2HSImp.withCString a2 $ \a2' ->
let {a3' = fromIntegral a3} in
igraphHaskellAttributeEAS'_ a1' a2' a3' >>= \res ->
let {res' = castPtr res} in
return (res')
{-# LINE 77 "src/IGraph/Internal/Attribute.chs" #-}
igraphHaskellAttributeEASSetv :: (IGraph) -> (String) -> (BSVector) -> IO ((Int))
igraphHaskellAttributeEASSetv a1 a2 a3 =
(withIGraph) a1 $ \a1' ->
C2HSImp.withCString a2 $ \a2' ->
(withBSVector) a3 $ \a3' ->
igraphHaskellAttributeEASSetv'_ a1' a2' a3' >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 79 "src/IGraph/Internal/Attribute.chs" #-}
igraphHaskellAttributeVASSet :: (IGraph) -> (String) -> (Int) -> (Ptr BSLen) -> IO ((Int))
igraphHaskellAttributeVASSet a1 a2 a3 a4 =
(withIGraph) a1 $ \a1' ->
C2HSImp.withCString a2 $ \a2' ->
let {a3' = fromIntegral a3} in
let {a4' = castPtr a4} in
igraphHaskellAttributeVASSet'_ a1' a2' a3' a4' >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 81 "src/IGraph/Internal/Attribute.chs" #-}
igraphHaskellAttributeEASSet :: (IGraph) -> (String) -> (Int) -> (Ptr BSLen) -> IO ((Int))
igraphHaskellAttributeEASSet a1 a2 a3 a4 =
(withIGraph) a1 $ \a1' ->
C2HSImp.withCString a2 $ \a2' ->
let {a3' = fromIntegral a3} in
let {a4' = castPtr a4} in
igraphHaskellAttributeEASSet'_ a1' a2' a3' a4' >>= \res ->
let {res' = fromIntegral res} in
return (res')
{-# LINE 83 "src/IGraph/Internal/Attribute.chs" #-}
foreign import ccall safe "IGraph/Internal/Attribute.chs.h igraph_haskell_attribute_has_attr"
igraphHaskellAttributeHasAttr'_ :: ((C2HSImp.Ptr (IGraph)) -> (C2HSImp.CInt -> ((C2HSImp.Ptr C2HSImp.CChar) -> (IO C2HSImp.CInt))))
foreign import ccall safe "IGraph/Internal/Attribute.chs.h igraph_haskell_attribute_GAN_set"
igraphHaskellAttributeGANSet'_ :: ((C2HSImp.Ptr (IGraph)) -> ((C2HSImp.Ptr C2HSImp.CChar) -> (C2HSImp.CDouble -> (IO C2HSImp.CInt))))
foreign import ccall safe "IGraph/Internal/Attribute.chs.h igraph_haskell_attribute_GAN"
igraphHaskellAttributeGAN'_ :: ((C2HSImp.Ptr (IGraph)) -> ((C2HSImp.Ptr C2HSImp.CChar) -> (IO C2HSImp.CDouble)))
foreign import ccall safe "IGraph/Internal/Attribute.chs.h igraph_haskell_attribute_VAS"
igraphHaskellAttributeVAS'_ :: ((C2HSImp.Ptr (IGraph)) -> ((C2HSImp.Ptr C2HSImp.CChar) -> (C2HSImp.CInt -> (IO (C2HSImp.Ptr ())))))
foreign import ccall safe "IGraph/Internal/Attribute.chs.h igraph_haskell_attribute_EAN"
igraphHaskellAttributeEAN'_ :: ((C2HSImp.Ptr (IGraph)) -> ((C2HSImp.Ptr C2HSImp.CChar) -> (C2HSImp.CInt -> (IO C2HSImp.CDouble))))
foreign import ccall safe "IGraph/Internal/Attribute.chs.h igraph_haskell_attribute_EAS"
igraphHaskellAttributeEAS'_ :: ((C2HSImp.Ptr (IGraph)) -> ((C2HSImp.Ptr C2HSImp.CChar) -> (C2HSImp.CInt -> (IO (C2HSImp.Ptr ())))))
foreign import ccall safe "IGraph/Internal/Attribute.chs.h igraph_haskell_attribute_EAS_setv"
igraphHaskellAttributeEASSetv'_ :: ((C2HSImp.Ptr (IGraph)) -> ((C2HSImp.Ptr C2HSImp.CChar) -> ((C2HSImp.Ptr (BSVector)) -> (IO C2HSImp.CInt))))
foreign import ccall safe "IGraph/Internal/Attribute.chs.h igraph_haskell_attribute_VAS_set"
igraphHaskellAttributeVASSet'_ :: ((C2HSImp.Ptr (IGraph)) -> ((C2HSImp.Ptr C2HSImp.CChar) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt)))))
foreign import ccall safe "IGraph/Internal/Attribute.chs.h igraph_haskell_attribute_EAS_set"
igraphHaskellAttributeEASSet'_ :: ((C2HSImp.Ptr (IGraph)) -> ((C2HSImp.Ptr C2HSImp.CChar) -> (C2HSImp.CInt -> ((C2HSImp.Ptr ()) -> (IO C2HSImp.CInt)))))