souffle-haskell-0.2.0: Souffle Datalog bindings for Haskell
Safe HaskellNone
LanguageHaskell2010

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

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]
  factName = 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.

Methods

programName :: Proxy 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).

It uses a Proxy to select the correct instance.

class Marshal a => Fact a where Source #

A typeclass for data types representing a fact in datalog.

Methods

factName :: Proxy a -> String Source #

Function for obtaining the name of a fact (has to be the same as described in the Datalog program).

It uses a Proxy to select the correct instance.

Example usage:

instance Fact Edge where
  factName = const "edge"

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

Instances details
MonadSouffle SouffleM Source # 
Instance details

Defined in Language.Souffle.Interpreted

Associated Types

type Handler SouffleM :: Type -> Type Source #

type CollectFacts SouffleM c Source #

MonadSouffle SouffleM Source # 
Instance details

Defined in Language.Souffle.Compiled

Associated Types

type Handler SouffleM :: Type -> Type Source #

type CollectFacts SouffleM c Source #

MonadSouffle m => MonadSouffle (ExceptT e m) Source # 
Instance details

Defined in Language.Souffle.Class

Associated Types

type Handler (ExceptT e m) :: Type -> Type Source #

type CollectFacts (ExceptT e m) c Source #

Methods

init :: Program prog => prog -> ExceptT e m (Maybe (Handler (ExceptT e m) prog)) Source #

run :: Handler (ExceptT e m) prog -> ExceptT e m () Source #

setNumThreads :: Handler (ExceptT e m) prog -> Word64 -> ExceptT e m () Source #

getNumThreads :: Handler (ExceptT e m) prog -> ExceptT e m Word64 Source #

getFacts :: (Fact a, ContainsFact prog a, CollectFacts (ExceptT e m) c) => Handler (ExceptT e m) prog -> ExceptT e m (c a) Source #

findFact :: (Fact a, ContainsFact prog a, Eq a) => Handler (ExceptT e m) prog -> a -> ExceptT e m (Maybe a) Source #

addFact :: (Fact a, ContainsFact prog a) => Handler (ExceptT e m) prog -> a -> ExceptT e m () Source #

addFacts :: (Foldable t, Fact a, ContainsFact prog a) => Handler (ExceptT e m) prog -> t a -> ExceptT e m () Source #

MonadSouffle m => MonadSouffle (ReaderT r m) Source # 
Instance details

Defined in Language.Souffle.Class

Associated Types

type Handler (ReaderT r m) :: Type -> Type Source #

type CollectFacts (ReaderT r m) c Source #

Methods

init :: Program prog => prog -> ReaderT r m (Maybe (Handler (ReaderT r m) prog)) Source #

run :: Handler (ReaderT r m) prog -> ReaderT r m () Source #

setNumThreads :: Handler (ReaderT r m) prog -> Word64 -> ReaderT r m () Source #

getNumThreads :: Handler (ReaderT r m) prog -> ReaderT r m Word64 Source #

getFacts :: (Fact a, ContainsFact prog a, CollectFacts (ReaderT r m) c) => Handler (ReaderT r m) prog -> ReaderT r m (c a) Source #

findFact :: (Fact a, ContainsFact prog a, Eq a) => Handler (ReaderT r m) prog -> a -> ReaderT r m (Maybe a) Source #

addFact :: (Fact a, ContainsFact prog a) => Handler (ReaderT r m) prog -> a -> ReaderT r m () Source #

addFacts :: (Foldable t, Fact a, ContainsFact prog a) => Handler (ReaderT r m) prog -> t a -> ReaderT r m () Source #

MonadSouffle m => MonadSouffle (StateT s m) Source # 
Instance details

Defined in Language.Souffle.Class

Associated Types

type Handler (StateT s m) :: Type -> Type Source #

type CollectFacts (StateT s m) c Source #

Methods

init :: Program prog => prog -> StateT s m (Maybe (Handler (StateT s m) prog)) Source #

run :: Handler (StateT s m) prog -> StateT s m () Source #

setNumThreads :: Handler (StateT s m) prog -> Word64 -> StateT s m () Source #

getNumThreads :: Handler (StateT s m) prog -> StateT s m Word64 Source #

getFacts :: (Fact a, ContainsFact prog a, CollectFacts (StateT s m) c) => Handler (StateT s m) prog -> StateT s m (c a) Source #

findFact :: (Fact a, ContainsFact prog a, Eq a) => Handler (StateT s m) prog -> a -> StateT s m (Maybe a) Source #

addFact :: (Fact a, ContainsFact prog a) => Handler (StateT s m) prog -> a -> StateT s m () Source #

addFacts :: (Foldable t, Fact a, ContainsFact prog a) => Handler (StateT s m) prog -> t a -> StateT s m () Source #

(Monoid w, MonadSouffle m) => MonadSouffle (WriterT w m) Source # 
Instance details

Defined in Language.Souffle.Class

Associated Types

type Handler (WriterT w m) :: Type -> Type Source #

type CollectFacts (WriterT w m) c Source #

Methods

init :: Program prog => prog -> WriterT w m (Maybe (Handler (WriterT w m) prog)) Source #

run :: Handler (WriterT w m) prog -> WriterT w m () Source #

setNumThreads :: Handler (WriterT w m) prog -> Word64 -> WriterT w m () Source #

getNumThreads :: Handler (WriterT w m) prog -> WriterT w m Word64 Source #

getFacts :: (Fact a, ContainsFact prog a, CollectFacts (WriterT w m) c) => Handler (WriterT w m) prog -> WriterT w m (c a) Source #

findFact :: (Fact a, ContainsFact prog a, Eq a) => Handler (WriterT w m) prog -> a -> WriterT w m (Maybe a) Source #

addFact :: (Fact a, ContainsFact prog a) => Handler (WriterT w m) prog -> a -> WriterT w m () Source #

addFacts :: (Foldable t, Fact a, ContainsFact prog a) => Handler (WriterT w m) prog -> t a -> WriterT w m () Source #

(MonadSouffle m, Monoid w) => MonadSouffle (RWST r w s m) Source # 
Instance details

Defined in Language.Souffle.Class

Associated Types

type Handler (RWST r w s m) :: Type -> Type Source #

type CollectFacts (RWST r w s m) c Source #

Methods

init :: Program prog => prog -> RWST r w s m (Maybe (Handler (RWST r w s m) prog)) Source #

run :: Handler (RWST r w s m) prog -> RWST r w s m () Source #

setNumThreads :: Handler (RWST r w s m) prog -> Word64 -> RWST r w s m () Source #

getNumThreads :: Handler (RWST r w s m) prog -> RWST r w s m Word64 Source #

getFacts :: (Fact a, ContainsFact prog a, CollectFacts (RWST r w s m) c) => Handler (RWST r w s m) prog -> RWST r w s m (c a) Source #

findFact :: (Fact a, ContainsFact prog a, Eq a) => Handler (RWST r w s m) prog -> a -> RWST r w s m (Maybe a) Source #

addFact :: (Fact a, ContainsFact prog a) => Handler (RWST r w s m) prog -> a -> RWST r w s m () Source #

addFacts :: (Foldable t, Fact a, ContainsFact prog a) => Handler (RWST r w s m) prog -> t a -> RWST r w s m () Source #

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 -> m () Source #

Write out all facts of the program to CSV files (as defined in the Souffle program).

Instances

Instances details
MonadSouffleFileIO SouffleM Source # 
Instance details

Defined in Language.Souffle.Compiled

MonadSouffleFileIO m => MonadSouffleFileIO (ExceptT s m) Source # 
Instance details

Defined in Language.Souffle.Class

Methods

loadFiles :: Handler (ExceptT s m) prog -> FilePath -> ExceptT s m () Source #

writeFiles :: Handler (ExceptT s m) prog -> ExceptT s m () Source #

MonadSouffleFileIO m => MonadSouffleFileIO (ReaderT r m) Source # 
Instance details

Defined in Language.Souffle.Class

Methods

loadFiles :: Handler (ReaderT r m) prog -> FilePath -> ReaderT r m () Source #

writeFiles :: Handler (ReaderT r m) prog -> ReaderT r m () Source #

MonadSouffleFileIO m => MonadSouffleFileIO (StateT s m) Source # 
Instance details

Defined in Language.Souffle.Class

Methods

loadFiles :: Handler (StateT s m) prog -> FilePath -> StateT s m () Source #

writeFiles :: Handler (StateT s m) prog -> StateT s m () Source #

(Monoid w, MonadSouffleFileIO m) => MonadSouffleFileIO (WriterT w m) Source # 
Instance details

Defined in Language.Souffle.Class

Methods

loadFiles :: Handler (WriterT w m) prog -> FilePath -> WriterT w m () Source #

writeFiles :: Handler (WriterT w m) prog -> WriterT w m () Source #

(MonadSouffleFileIO m, Monoid w) => MonadSouffleFileIO (RWST r w s m) Source # 
Instance details

Defined in Language.Souffle.Class

Methods

loadFiles :: Handler (RWST r w s m) prog -> FilePath -> RWST r w s m () Source #

writeFiles :: Handler (RWST r w s m) prog -> RWST r w s m () Source #