Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module provides the top level API for Souffle related operations.
It makes use of Haskell's powerful typesystem to make certain invalid states
impossible to represent. It does this with a small type level DSL for
describing properties of the Datalog program (see the Program
and Fact
typeclasses for more information).
The Souffle operations are exposed via 2 mtl-style interfaces
(see MonadSouffle
and MonadSouffleFileIO
) that allows them to be
integrated with existing monad transformer stacks.
This module also contains some helper type families for additional type safety and user-friendly error messages.
Synopsis
- class Program a where
- type ProgramFacts a :: [Type]
- programName :: a -> String
- class Marshal a => Fact a where
- type FactDirection a :: Direction
- factName :: Proxy a -> String
- class Marshal a where
- data Direction
- = Input
- | Output
- | InputOutput
- | Internal
- type family ContainsInputFact prog fact :: Constraint where ...
- type family ContainsOutputFact prog fact :: Constraint where ...
- type family ContainsFact prog fact :: Constraint where ...
- class Monad m => MonadSouffle m where
- type Handler m :: Type -> Type
- type CollectFacts m (c :: Type -> Type) :: Constraint
- run :: Handler m prog -> m ()
- setNumThreads :: Handler m prog -> Word64 -> m ()
- getNumThreads :: Handler m prog -> m Word64
- getFacts :: (Fact a, ContainsOutputFact prog a, CollectFacts m c) => Handler m prog -> m (c a)
- findFact :: (Fact a, ContainsOutputFact prog a, Eq a) => Handler m prog -> a -> m (Maybe a)
- addFact :: (Fact a, ContainsInputFact prog a) => Handler m prog -> a -> m ()
- addFacts :: (Foldable t, Fact a, ContainsInputFact prog a) => Handler m prog -> t a -> m ()
- class MonadSouffle m => MonadSouffleFileIO m where
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.
programName :: a -> String Source #
Function for obtaining the name of a Datalog program. This has to be the same as the name of the .dl file (minus the extension).
class Marshal a => Fact a where Source #
A typeclass for data types representing a fact in datalog.
Example usage:
instance Fact Edge where type FactDirection Edge = 'Input factName = const "edge"
type FactDirection a :: Direction Source #
The direction or "mode" a fact can be used in.
This is used to perform compile-time checks that a fact is only used
in valid situations. For more information, see the Direction
type.
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, GMarshal (Rep a), MonadPush m) => a -> m () Source #
Marshals a value to the datalog side.
pop :: (Generic a, SimpleProduct a, GMarshal (Rep a), MonadPop m) => m a Source #
Unmarshals a value from the datalog side.
A datatype describing which operations a certain fact supports. The direction is from the datalog perspective, so that it aligns with ".decl" statements in Souffle.
Input | Fact can only be stored in Datalog (using |
Output | Fact can only be read from Datalog (using |
InputOutput | Fact supports both reading from / writing to Datalog. |
Internal | Supports neither reading from / writing to Datalog. This is used for facts that are only visible inside Datalog itself. |
type family ContainsInputFact prog fact :: Constraint where ... Source #
A helper type family for checking if a specific Souffle Program
contains
a certain Fact
. Additionally, it also checks if the fact is marked as
either Input
or InputOutput
. This constraint will generate a
user-friendly type error if these conditions are not met.
ContainsInputFact prog fact = (ContainsFact prog fact, IsInput fact (FactDirection fact)) |
type family ContainsOutputFact prog fact :: Constraint where ... Source #
A helper type family for checking if a specific Souffle Program
contains
a certain Fact
. Additionally, it also checks if the fact is marked as
either Output
or InputOutput
. This constraint will generate a
user-friendly type error if these conditions are not met.
ContainsOutputFact prog fact = (ContainsFact prog fact, IsOutput fact (FactDirection fact)) |
type family ContainsFact prog fact :: Constraint where ... Source #
A helper type family for checking if a specific Souffle Program
contains
a certain Fact
. This constraint will generate a user-friendly type error
if this is not the case.
ContainsFact prog fact = CheckContains prog (ProgramFacts prog) fact |
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.
The handle is used in all other functions of this typeclass to perform Souffle-related actions.
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.
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, ContainsOutputFact 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, ContainsOutputFact 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, ContainsInputFact prog a) => Handler m prog -> a -> m () Source #
Adds a fact to the program.
addFacts :: (Foldable t, Fact a, ContainsInputFact 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
class MonadSouffle m => MonadSouffleFileIO m where Source #
A mtl-style typeclass for Souffle-related actions that involve file IO.
loadFiles :: Handler m prog -> FilePath -> m () Source #
Load all facts from files in a certain directory.
writeFiles :: Handler m prog -> FilePath -> m () Source #
Write out all facts of the program to CSV files in a certain directory (as defined in the Souffle program).
Instances
MonadSouffleFileIO SouffleM Source # | |
MonadSouffleFileIO m => MonadSouffleFileIO (ExceptT s m) Source # | |
MonadSouffleFileIO m => MonadSouffleFileIO (StateT s m) Source # | |
(Monoid w, MonadSouffleFileIO m) => MonadSouffleFileIO (WriterT w m) Source # | |
MonadSouffleFileIO m => MonadSouffleFileIO (ReaderT r m) Source # | |
(MonadSouffleFileIO m, Monoid w) => MonadSouffleFileIO (RWST r w s m) Source # | |