module Language.Souffle.Internal
( Souffle
, Relation
, RelationIterator
, Tuple
, init
, setNumThreads
, getNumThreads
, run
, loadAll
, printAll
, getRelation
, countFacts
, getRelationIterator
, relationIteratorNext
, allocTuple
, addTuple
, containsTuple
, tuplePushInt32
, tuplePushUInt32
, tuplePushFloat
, tuplePushString
, tuplePopInt32
, tuplePopUInt32
, tuplePopFloat
, tuplePopString
) where
import Prelude hiding ( init )
import Data.Functor ( (<&>) )
import Data.Word
import Data.Int
import Foreign.Marshal.Alloc
import Foreign.Storable
import Foreign.C.String
import Foreign.C.Types
import Foreign.ForeignPtr
import Foreign.Ptr
import qualified Language.Souffle.Internal.Bindings as Bindings
import Language.Souffle.Internal.Bindings
( Souffle, Relation, RelationIterator, Tuple )
init :: String -> IO (Maybe (ForeignPtr Souffle))
init prog = do
ptr <- withCString prog Bindings.init
if ptr == nullPtr
then pure Nothing
else Just <$> newForeignPtr Bindings.free ptr
{-# INLINABLE init #-}
setNumThreads :: ForeignPtr Souffle -> Word64 -> IO ()
setNumThreads prog numThreads = withForeignPtr prog $ \ptr ->
Bindings.setNumThreads ptr $ CSize numThreads
{-# INLINABLE setNumThreads #-}
getNumThreads :: ForeignPtr Souffle -> IO Word64
getNumThreads prog = withForeignPtr prog $ \ptr -> do
(CSize numThreads) <- Bindings.getNumThreads ptr
pure numThreads
{-# INLINABLE getNumThreads #-}
run :: ForeignPtr Souffle -> IO ()
run prog = withForeignPtr prog Bindings.run
{-# INLINABLE run #-}
loadAll :: ForeignPtr Souffle -> FilePath -> IO ()
loadAll prog inputDir = withForeignPtr prog $ withCString inputDir . Bindings.loadAll
{-# INLINABLE loadAll #-}
printAll :: ForeignPtr Souffle -> FilePath -> IO ()
printAll prog outputDir = withForeignPtr prog $ withCString outputDir . Bindings.printAll
{-# INLINABLE printAll #-}
getRelation :: ForeignPtr Souffle -> String -> IO (Ptr Relation)
getRelation prog relation = withForeignPtr prog $ \ptr ->
withCString relation $ Bindings.getRelation ptr
{-# INLINABLE getRelation #-}
countFacts :: Ptr Relation -> IO Int
countFacts relation =
Bindings.getTupleCount relation >>= \(CSize count) ->
pure (fromIntegral count)
getRelationIterator :: Ptr Relation -> IO (ForeignPtr RelationIterator)
getRelationIterator relation =
Bindings.getRelationIterator relation >>= newForeignPtr Bindings.freeRelationIterator
{-# INLINABLE getRelationIterator #-}
relationIteratorNext :: ForeignPtr RelationIterator -> IO (Ptr Tuple)
relationIteratorNext iter = withForeignPtr iter Bindings.relationIteratorNext
{-# INLINABLE relationIteratorNext #-}
allocTuple :: Ptr Relation -> IO (ForeignPtr Tuple)
allocTuple relation =
Bindings.allocTuple relation >>= newForeignPtr Bindings.freeTuple
{-# INLINABLE allocTuple #-}
addTuple :: Ptr Relation -> ForeignPtr Tuple -> IO ()
addTuple relation tuple =
withForeignPtr tuple $ Bindings.addTuple relation
{-# INLINABLE addTuple #-}
containsTuple :: Ptr Relation -> ForeignPtr Tuple -> IO Bool
containsTuple relation tuple = withForeignPtr tuple $ \ptr ->
Bindings.containsTuple relation ptr <&> \case
CBool 0 -> False
CBool _ -> True
{-# INLINABLE containsTuple #-}
tuplePushInt32 :: Ptr Tuple -> Int32 -> IO ()
tuplePushInt32 tuple i = Bindings.tuplePushInt32 tuple (CInt i)
{-# INLINABLE tuplePushInt32 #-}
tuplePushUInt32 :: Ptr Tuple -> Word32 -> IO ()
tuplePushUInt32 tuple i = Bindings.tuplePushUInt32 tuple (CUInt i)
{-# INLINABLE tuplePushUInt32 #-}
tuplePushFloat :: Ptr Tuple -> Float -> IO ()
tuplePushFloat tuple f = Bindings.tuplePushFloat tuple (CFloat f)
{-# INLINABLE tuplePushFloat #-}
tuplePushString :: Ptr Tuple -> String -> IO ()
tuplePushString tuple str =
withCString str $ Bindings.tuplePushString tuple
{-# INLINABLE tuplePushString #-}
tuplePopInt32 :: Ptr Tuple -> IO Int32
tuplePopInt32 tuple = alloca $ \ptr -> do
Bindings.tuplePopInt32 tuple ptr
(CInt res) <- peek ptr
pure res
{-# INLINABLE tuplePopInt32 #-}
tuplePopUInt32 :: Ptr Tuple -> IO Word32
tuplePopUInt32 tuple = alloca $ \ptr -> do
Bindings.tuplePopUInt32 tuple ptr
(CUInt res) <- peek ptr
pure res
{-# INLINABLE tuplePopUInt32 #-}
tuplePopFloat :: Ptr Tuple -> IO Float
tuplePopFloat tuple = alloca $ \ptr -> do
Bindings.tuplePopFloat tuple ptr
(CFloat res) <- peek ptr
pure res
{-# INLINABLE tuplePopFloat #-}
tuplePopString :: Ptr Tuple -> IO String
tuplePopString tuple = alloca $ \ptr -> do
Bindings.tuplePopString tuple ptr
cstr <- peek ptr
str <- peekCString cstr
free cstr
pure str
{-# INLINABLE tuplePopString #-}