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

Language.Souffle.Interpreted

Description

This module provides an implementation for the MonadSouffle typeclass defined in Language.Souffle.Class. It makes use of the Souffle interpreter and CSV files to offer an implementation optimized for quick development speed compared to Language.Souffle.Compiled.

It is however much slower so users are advised to switch over to the compiled alternative once the prototyping phase is finished.

Synopsis

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"

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 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

Minimal complete definition

Nothing

Methods

push :: MonadPush m => a -> m () Source #

Marshals a value to the datalog side.

default push :: (Generic a, SimpleProduct a (Rep a), GMarshal (Rep a), MonadPush m) => a -> m () Source #

pop :: MonadPop m => m a Source #

Unmarshals a value from the datalog side.

default pop :: (Generic a, SimpleProduct a (Rep a), GMarshal (Rep a), MonadPop m) => m a Source #

Instances

Instances details
Marshal Int32 Source # 
Instance details

Defined in Language.Souffle.Marshal

Methods

push :: MonadPush m => Int32 -> m () Source #

pop :: MonadPop m => m Int32 Source #

Marshal String Source # 
Instance details

Defined in Language.Souffle.Marshal

Methods

push :: MonadPush m => String -> m () Source #

pop :: MonadPop m => m String Source #

Marshal Text Source # 
Instance details

Defined in Language.Souffle.Marshal

Methods

push :: MonadPush m => Text -> m () Source #

pop :: MonadPop m => m Text Source #

Marshal Text Source # 
Instance details

Defined in Language.Souffle.Marshal

Methods

push :: MonadPush m => Text -> m () Source #

pop :: MonadPop m => m Text Source #

data Config Source #

A helper data type for storing the configurable settings of the interpreter.

  • cfgDatalogDir: The directory where the datalog file(s) are located.
  • cfgSouffleBin: The name of the souffle binary. Has to be available in $PATH or an absolute path needs to be provided. Note: Passing in Nothing will fail to start up the interpreter in the init function.
  • cfgFactDir: The directory where the initial input fact file(s) can be found if present. If Nothing, then a temporary directory will be used, during the souffle session.
  • cfgOutputDir: The directory where the output facts file(s) are created. If Nothing, it will be part of the temporary directory.

Instances

Instances details
Show Config Source # 
Instance details

Defined in Language.Souffle.Interpreted

data Handle prog Source #

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.

data SouffleM a Source #

A monad for executing Souffle-related actions in.

Instances

Instances details
Monad SouffleM Source # 
Instance details

Defined in Language.Souffle.Interpreted

Methods

(>>=) :: SouffleM a -> (a -> SouffleM b) -> SouffleM b #

(>>) :: SouffleM a -> SouffleM b -> SouffleM b #

return :: a -> SouffleM a #

Functor SouffleM Source # 
Instance details

Defined in Language.Souffle.Interpreted

Methods

fmap :: (a -> b) -> SouffleM a -> SouffleM b #

(<$) :: a -> SouffleM b -> SouffleM a #

Applicative SouffleM Source # 
Instance details

Defined in Language.Souffle.Interpreted

Methods

pure :: a -> SouffleM a #

(<*>) :: SouffleM (a -> b) -> SouffleM a -> SouffleM b #

liftA2 :: (a -> b -> c) -> SouffleM a -> SouffleM b -> SouffleM c #

(*>) :: SouffleM a -> SouffleM b -> SouffleM b #

(<*) :: SouffleM a -> SouffleM b -> SouffleM a #

MonadIO SouffleM Source # 
Instance details

Defined in Language.Souffle.Interpreted

Methods

liftIO :: IO a -> SouffleM a #

MonadSouffle SouffleM Source # 
Instance details

Defined in Language.Souffle.Interpreted

Associated Types

type Handler SouffleM :: Type -> Type Source #

type CollectFacts SouffleM c Source #

type Handler SouffleM Source # 
Instance details

Defined in Language.Souffle.Interpreted

type CollectFacts SouffleM c Source # 
Instance details

Defined in Language.Souffle.Interpreted

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 #

runSouffle :: SouffleM a -> IO a Source #

Returns an IO action that will run the Souffle interpreter with default settings (see defaultConfig).

runSouffleWith :: Config -> SouffleM a -> IO a Source #

Returns an IO action that will run the Souffle interpreter with the given interpreter settings.

defaultConfig :: MonadIO m => m Config Source #

Retrieves the default config for the interpreter. These settings can be overridden using record update syntax if needed.

By default, the settings will be configured as follows:

  • cfgDatalogDir: Looks at environment variable $DATALOG_DIR, falls back to the current directory if not set.
  • cfgSouffleBin: Looks at environment variable $SOUFFLE_BIN, or tries to locate the souffle binary using the which shell command if the variable is not set.
  • cfgFactDir: Will make use of a temporary directory.
  • cfgOutputDir: Will make use of a temporary directory.

cleanup :: forall prog. Program prog => Handle prog -> SouffleM () Source #

Cleans up the temporary directory that this library has written files to. This functionality is only provided for the interpreted version since the compiled version directly (de-)serializes data via the C++ API.

souffleStdOut :: forall prog. Program prog => Handle prog -> SouffleM (Maybe Text) Source #

Returns the handle of stdout from the souffle interpreter.

souffleStdErr :: forall prog. Program prog => Handle prog -> SouffleM (Maybe Text) Source #

Returns the content of stderr from the souffle interpreter.