module Language.Souffle.Internal
( Souffle
, Relation
, ByteBuf
, init
, setNumThreads
, getNumThreads
, run
, loadAll
, printAll
, getRelation
, pushFacts
, popFacts
, containsFact
) where
import Prelude hiding ( init )
import Data.Functor ( (<&>) )
import Data.Word
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, ByteBuf )
import Control.Exception (mask_)
init :: String -> IO (Maybe (ForeignPtr Souffle))
init :: String -> IO (Maybe (ForeignPtr Souffle))
init String
prog = forall a. IO a -> IO a
mask_ forall a b. (a -> b) -> a -> b
$ do
Ptr Souffle
ptr <- forall a. String -> (CString -> IO a) -> IO a
withCString String
prog CString -> IO (Ptr Souffle)
Bindings.init
if Ptr Souffle
ptr forall a. Eq a => a -> a -> Bool
== forall a. Ptr a
nullPtr
then forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a. Maybe a
Nothing
else forall a. a -> Maybe a
Just forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. FinalizerPtr a -> Ptr a -> IO (ForeignPtr a)
newForeignPtr FunPtr (Ptr Souffle -> IO ())
Bindings.free Ptr Souffle
ptr
{-# INLINABLE init #-}
setNumThreads :: ForeignPtr Souffle -> Word64 -> IO ()
setNumThreads :: ForeignPtr Souffle -> Word64 -> IO ()
setNumThreads ForeignPtr Souffle
prog Word64
numThreads = forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr Souffle
prog forall a b. (a -> b) -> a -> b
$ \Ptr Souffle
ptr ->
Ptr Souffle -> CSize -> IO ()
Bindings.setNumThreads Ptr Souffle
ptr forall a b. (a -> b) -> a -> b
$ Word64 -> CSize
CSize Word64
numThreads
{-# INLINABLE setNumThreads #-}
getNumThreads :: ForeignPtr Souffle -> IO Word64
getNumThreads :: ForeignPtr Souffle -> IO Word64
getNumThreads ForeignPtr Souffle
prog = forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr Souffle
prog forall a b. (a -> b) -> a -> b
$ \Ptr Souffle
ptr -> do
(CSize Word64
numThreads) <- Ptr Souffle -> IO CSize
Bindings.getNumThreads Ptr Souffle
ptr
forall (f :: * -> *) a. Applicative f => a -> f a
pure Word64
numThreads
{-# INLINABLE getNumThreads #-}
run :: ForeignPtr Souffle -> IO ()
run :: ForeignPtr Souffle -> IO ()
run ForeignPtr Souffle
prog = forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr Souffle
prog Ptr Souffle -> IO ()
Bindings.run
{-# INLINABLE run #-}
loadAll :: ForeignPtr Souffle -> FilePath -> IO ()
loadAll :: ForeignPtr Souffle -> String -> IO ()
loadAll ForeignPtr Souffle
prog String
inputDir = forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr Souffle
prog forall a b. (a -> b) -> a -> b
$ forall a. String -> (CString -> IO a) -> IO a
withCString String
inputDir forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr Souffle -> CString -> IO ()
Bindings.loadAll
{-# INLINABLE loadAll #-}
printAll :: ForeignPtr Souffle -> FilePath -> IO ()
printAll :: ForeignPtr Souffle -> String -> IO ()
printAll ForeignPtr Souffle
prog String
outputDir = forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr Souffle
prog forall a b. (a -> b) -> a -> b
$ forall a. String -> (CString -> IO a) -> IO a
withCString String
outputDir forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr Souffle -> CString -> IO ()
Bindings.printAll
{-# INLINABLE printAll #-}
getRelation :: ForeignPtr Souffle -> String -> IO (Ptr Relation)
getRelation :: ForeignPtr Souffle -> String -> IO (Ptr Relation)
getRelation ForeignPtr Souffle
prog String
relation = forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr Souffle
prog forall a b. (a -> b) -> a -> b
$ \Ptr Souffle
ptr ->
forall a. String -> (CString -> IO a) -> IO a
withCString String
relation forall a b. (a -> b) -> a -> b
$ Ptr Souffle -> CString -> IO (Ptr Relation)
Bindings.getRelation Ptr Souffle
ptr
{-# INLINABLE getRelation #-}
pushFacts :: Ptr Relation -> Ptr ByteBuf -> Word64 -> IO ()
pushFacts :: Ptr Relation -> Ptr ByteBuf -> Word64 -> IO ()
pushFacts Ptr Relation
relation Ptr ByteBuf
buf Word64
x =
Ptr Relation -> Ptr ByteBuf -> CSize -> IO ()
Bindings.pushByteBuf Ptr Relation
relation Ptr ByteBuf
buf (Word64 -> CSize
CSize Word64
x)
{-# INLINABLE pushFacts #-}
popFacts :: Ptr Souffle -> Ptr Relation -> IO (Ptr ByteBuf)
popFacts :: Ptr Souffle -> Ptr Relation -> IO (Ptr ByteBuf)
popFacts = Ptr Souffle -> Ptr Relation -> IO (Ptr ByteBuf)
Bindings.popByteBuf
{-# INLINABLE popFacts #-}
containsFact :: Ptr Relation -> Ptr ByteBuf -> IO Bool
containsFact :: Ptr Relation -> Ptr ByteBuf -> IO Bool
containsFact Ptr Relation
relation Ptr ByteBuf
buf =
Ptr Relation -> Ptr ByteBuf -> IO CBool
Bindings.containsTuple Ptr Relation
relation Ptr ByteBuf
buf forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> \case
CBool Word8
0 -> Bool
False
CBool Word8
_ -> Bool
True
{-# INLINABLE containsFact #-}