souffle-haskell-3.4.0: Souffle Datalog bindings for Haskell
Safe HaskellSafe-Inferred
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

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

Instances

Instances details
KnownSymbol progName => Program (ProgramOptions prog progName facts) Source # 
Instance details

Defined in Language.Souffle.Class

Associated Types

type ProgramFacts (ProgramOptions prog progName facts) :: [Type] Source #

Methods

programName :: ProgramOptions prog progName facts -> String Source #

newtype ProgramOptions (prog :: Type) (progName :: Symbol) (facts :: [Type]) Source #

A helper data type, used in combination with the DerivingVia extension to automatically generate code to bind Haskell to a Souffle Datalog program.

The following is an example how to bind to a Datalog program "path" (saved as path.dl / path.cpp), that uses two facts called "edge" and "reachable" (represented with the Edge and Reachable types):

data Path = Path
  deriving Souffle.Program
  via Souffle.ProgramOptions Path "path" '[Edge, Reachable]

See also: FactOptions.

Constructors

ProgramOptions prog 

Instances

Instances details
KnownSymbol progName => Program (ProgramOptions prog progName facts) Source # 
Instance details

Defined in Language.Souffle.Class

Associated Types

type ProgramFacts (ProgramOptions prog progName facts) :: [Type] Source #

Methods

programName :: ProgramOptions prog progName facts -> String Source #

type ProgramFacts (ProgramOptions prog progName facts) Source # 
Instance details

Defined in Language.Souffle.Class

type ProgramFacts (ProgramOptions prog progName facts) = facts

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"

Associated Types

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.

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.

Instances

Instances details
(Marshal fact, KnownSymbol factName) => Fact (FactOptions fact factName dir) Source # 
Instance details

Defined in Language.Souffle.Class

Associated Types

type FactDirection (FactOptions fact factName dir) :: Direction Source #

Methods

factName :: Proxy (FactOptions fact factName dir) -> String Source #

newtype FactOptions (fact :: Type) (factName :: Symbol) (dir :: Direction) Source #

A helper data type, used in combination with the DerivingVia extension to automatically generate code to bind a Haskell datatype to a Souffle Datalog fact.

The following is an example how to bind to a Datalog fact "edge" that contains two symbols (strings in Haskell) that is an input (from the Datalog point of view):

data Edge = Edge String String
  deriving (Eq, Show, Generic)
  deriving anyclass Souffle.Marshal
  deriving Souffle.Fact
  via Souffle.FactOptions Edge "edge" 'Souffle.Input

See also: ProgramOptions.

Constructors

FactOptions fact 

Instances

Instances details
(Marshal fact, KnownSymbol factName) => Fact (FactOptions fact factName dir) Source # 
Instance details

Defined in Language.Souffle.Class

Associated Types

type FactDirection (FactOptions fact factName dir) :: Direction Source #

Methods

factName :: Proxy (FactOptions fact factName dir) -> String Source #

Marshal fact => Marshal (FactOptions fact name dir) Source # 
Instance details

Defined in Language.Souffle.Class

Methods

push :: MonadPush m => FactOptions fact name dir -> m () Source #

pop :: MonadPop m => m (FactOptions fact name dir) Source #

type FactDirection (FactOptions fact factName dir) Source # 
Instance details

Defined in Language.Souffle.Class

type FactDirection (FactOptions fact factName dir) = dir

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). The ordering of how nested products are serialized is the same as when the fields of the nested product types are inlined into the parent type.

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, 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, 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 Word32 Source # 
Instance details

Defined in Language.Souffle.Marshal

Methods

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

pop :: MonadPop m => m Word32 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 #

Marshal ShortText Source # 
Instance details

Defined in Language.Souffle.Marshal

Methods

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

pop :: MonadPop m => m ShortText 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 Float Source # 
Instance details

Defined in Language.Souffle.Marshal

Methods

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

pop :: MonadPop m => m Float Source #

Marshal fact => Marshal (FactOptions fact name dir) Source # 
Instance details

Defined in Language.Souffle.Class

Methods

push :: MonadPush m => FactOptions fact name dir -> m () Source #

pop :: MonadPop m => m (FactOptions fact name dir) Source #

data Direction Source #

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.

Constructors

Input

Fact can only be stored in Datalog (using addFact/addFacts).

Output

Fact can only be read from Datalog (using getFacts/findFact).

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.

Equations

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.

Equations

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.

Equations

ContainsFact prog fact = CheckContains prog (ProgramFacts prog) fact 

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.

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.

type SubmitFacts m (a :: Type) :: Constraint Source #

Helper associated type constraint that allows submitting facts to Souffle. Only used internally.

Methods

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, SubmitFacts m 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, SubmitFacts m a) => Handler m prog -> a -> m () Source #

Adds a fact to the program.

addFacts :: (Foldable t, Fact a, ContainsInputFact prog a, SubmitFacts m 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.Compiled

MonadSouffle SouffleM Source # 
Instance details

Defined in Language.Souffle.Interpreted

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 #

type SubmitFacts (ExceptT e m) a Source #

Methods

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, ContainsOutputFact prog a, CollectFacts (ExceptT e m) c) => Handler (ExceptT e m) prog -> ExceptT e m (c a) Source #

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

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

addFacts :: (Foldable t, Fact a, ContainsInputFact prog a, SubmitFacts (ExceptT e m) 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 #

type SubmitFacts (ReaderT r m) a Source #

Methods

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, ContainsOutputFact prog a, CollectFacts (ReaderT r m) c) => Handler (ReaderT r m) prog -> ReaderT r m (c a) Source #

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

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

addFacts :: (Foldable t, Fact a, ContainsInputFact prog a, SubmitFacts (ReaderT r m) 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 #

type SubmitFacts (StateT s m) a Source #

Methods

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, ContainsOutputFact prog a, CollectFacts (StateT s m) c) => Handler (StateT s m) prog -> StateT s m (c a) Source #

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

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

addFacts :: (Foldable t, Fact a, ContainsInputFact prog a, SubmitFacts (StateT s m) 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 #

type SubmitFacts (WriterT w m) a Source #

Methods

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, ContainsOutputFact prog a, CollectFacts (WriterT w m) c) => Handler (WriterT w m) prog -> WriterT w m (c a) Source #

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

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

addFacts :: (Foldable t, Fact a, ContainsInputFact prog a, SubmitFacts (WriterT w m) 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 #

type SubmitFacts (RWST r w s m) a Source #

Methods

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, ContainsOutputFact 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, ContainsOutputFact prog a, Eq a, SubmitFacts (RWST r w s m) a) => Handler (RWST r w s m) prog -> a -> RWST r w s m (Maybe a) Source #

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

addFacts :: (Foldable t, Fact a, ContainsInputFact prog a, SubmitFacts (RWST r w s m) 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 -> FilePath -> m () Source #

Write out all facts of the program to CSV files in a certain directory (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 -> FilePath -> 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 -> FilePath -> 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 -> FilePath -> 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 -> FilePath -> 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 -> FilePath -> RWST r w s m () Source #