Safe Haskell | None |
---|---|
Language | Haskell2010 |
Language.Souffle.Class
Description
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
- type family ContainsFact prog fact :: Constraint where ...
- class Program a where
- type ProgramFacts a :: [Type]
- programName :: Proxy a -> String
- class Marshal a => Fact a where
- 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 ()
- class MonadSouffle m => MonadSouffleFileIO m where
Documentation
type family ContainsFact prog fact :: Constraint where ... Source #
A helper type family for checking if a specific Souffle Program
contains a certain Fact
.
This will generate a user-friendly type error if this is not the case.
Equations
ContainsFact prog fact = CheckContains prog (ProgramFacts prog) fact |
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"
Associated Types
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 Monad m => MonadSouffle m where Source #
A mtl-style typeclass for Souffle-related actions.
Associated Types
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.
Methods
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
class MonadSouffle m => MonadSouffleFileIO m where Source #
A mtl-style typeclass for Souffle-related actions that involve file IO.
Methods
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 # | |