Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module provides an implementation for the typeclasses defined in Language.Souffle.Class. It makes use of the low level Souffle C++ API to offer a much more performant alternative implementation to the implementation in Language.Souffle.Interpreted.
This module is mainly intended to be used after the prototyping phase is over since the iteration cycle is slower due to the additional C++ compilation times.
Synopsis
- class Program a where
- type ProgramFacts a :: [Type]
- programName :: Proxy a -> String
- class Marshal a => Fact a where
- class Marshal a where
- data Handle prog
- data SouffleM a
- class Monad m => MonadSouffle m where
- type Handler m :: Type -> Type
- type CollectFacts m (c :: Type -> Type) :: Constraint
- init :: Program prog => prog -> m (Maybe (Handler m prog))
- run :: Handler m prog -> m ()
- setNumThreads :: Handler m prog -> Word64 -> m ()
- getNumThreads :: Handler m prog -> m Word64
- getFacts :: (Fact a, ContainsFact prog a, CollectFacts m c) => Handler m prog -> m (c a)
- findFact :: (Fact a, ContainsFact prog a, Eq a) => Handler m prog -> a -> m (Maybe a)
- addFact :: (Fact a, ContainsFact prog a) => Handler m prog -> a -> m ()
- addFacts :: (Foldable t, Fact a, ContainsFact prog a) => Handler m prog -> t a -> m ()
- runSouffle :: SouffleM a -> IO a
Documentation
class Program a where Source #
A typeclass for describing a datalog program.
Example usage (assuming the program was generated from path.dl and contains 2 facts: Edge and Reachable):
data Path = Path -- Handle for the datalog program instance Program Path where type ProgramFacts Path = '[Edge, Reachable] programName = const "path"
type ProgramFacts a :: [Type] Source #
A type level list of facts that belong to this program. This list is used to check that only known facts are added to a program.
class Marshal a where Source #
A typeclass for providing a uniform API to marshal/unmarshal values between Haskell and Souffle datalog.
The marshalling is done via a stack-based approach, where elements are pushed/popped one by one. You need to make sure that the marshalling of values happens in the correct order or unexpected things might happen (including crashes). Pushing and popping of fields should happen in the same order (from left to right, as defined in Datalog).
Generic implementations for push
and pop
that perform the previously
described behavior are available. This makes it possible to
write very succinct code:
data Edge = Edge String String deriving Generic instance Marshal Edge
Nothing
push :: MonadPush m => a -> m () Source #
Marshals a value to the datalog side.
pop :: MonadPop m => m a Source #
Unmarshals a value from the datalog side.
push :: (Generic a, SimpleProduct a (Rep a), GMarshal (Rep a), MonadPush m) => a -> m () Source #
Marshals a value to the datalog side.
pop :: (Generic a, SimpleProduct a (Rep a), GMarshal (Rep a), MonadPop m) => m a Source #
Unmarshals a value from the datalog side.
A datatype representing a handle to a datalog program. The type parameter is used for keeping track of which program type the handle belongs to for additional type safety.
A monad for executing Souffle-related actions in.
Instances
class Monad m => MonadSouffle m where Source #
A mtl-style typeclass for Souffle-related actions.
type Handler m :: Type -> Type Source #
Represents a handle for interacting with a Souffle program.
See also init
, which returns a handle of this type.
type CollectFacts m (c :: Type -> Type) :: Constraint Source #
Helper associated type constraint that allows collecting facts from Souffle in a list or vector. Only used internally.
init :: Program prog => prog -> m (Maybe (Handler m prog)) Source #
Initializes a Souffle program.
The action will return Nothing
if it failed to load the Souffle C++
program or if it failed to find the Souffle interpreter (depending on
compiled/interpreted variant).
Otherwise it will return a handle that can be used in other functions
in this module.
run :: Handler m prog -> m () Source #
Runs the Souffle program.
setNumThreads :: Handler m prog -> Word64 -> m () Source #
Sets the number of CPU cores this Souffle program should use.
getNumThreads :: Handler m prog -> m Word64 Source #
Gets the number of CPU cores this Souffle program should use.
getFacts :: (Fact a, ContainsFact prog a, CollectFacts m c) => Handler m prog -> m (c a) Source #
Returns all facts of a program. This function makes use of type inference to select the type of fact to return.
findFact :: (Fact a, ContainsFact prog a, Eq a) => Handler m prog -> a -> m (Maybe a) Source #
Searches for a fact in a program.
Returns Nothing
if no matching fact was found; otherwise Just
the fact.
Conceptually equivalent to List.find (== fact) <$> getFacts prog
,
but this operation can be implemented much faster.
addFact :: (Fact a, ContainsFact prog a) => Handler m prog -> a -> m () Source #
Adds a fact to the program.
addFacts :: (Foldable t, Fact a, ContainsFact prog a) => Handler m prog -> t a -> m () Source #
Adds multiple facts to the program. This function could be implemented
in terms of addFact
, but this is done as a minor optimization.
Instances
runSouffle :: SouffleM a -> IO a Source #
Returns the underlying IO action.