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

Language.Souffle

Description

This module provides the top level API of this library. 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). This module also provides a MTL-style interface to Souffle related operations so it can be integrated with existing monad transformer stacks.

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]
  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 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. The programmer needs to make sure that the marshalling 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 :: MonadIO m => a -> MarshalT m () Source #

Marshals a value to the datalog side.

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

pop :: MonadIO m => MarshalT m a Source #

Unmarshals a value from the datalog side.

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

Instances

Instances details
Marshal Int32 Source # 
Instance details

Defined in Language.Souffle.Marshal

Methods

push :: forall (m :: Type -> Type). MonadIO m => Int32 -> MarshalT m () Source #

pop :: forall (m :: Type -> Type). MonadIO m => MarshalT m Int32 Source #

Marshal String Source # 
Instance details

Defined in Language.Souffle.Marshal

Methods

push :: forall (m :: Type -> Type). MonadIO m => String -> MarshalT m () Source #

pop :: forall (m :: Type -> Type). MonadIO m => MarshalT m String Source #

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.

class Monad m => MonadSouffle m where Source #

A mtl-style typeclass for Souffle-related actions.

Methods

init :: Program prog => prog -> m (Maybe (Handle prog)) Source #

Initializes a Souffle program.

The action will return Nothing if it failed to load the Souffle program. Otherwise it will return a Handle that can be used in other functions in this module.

run :: Handle prog -> m () Source #

Runs the Souffle program.

setNumThreads :: Handle prog -> Word64 -> m () Source #

Sets the number of CPU cores this Souffle program should use.

getNumThreads :: Handle prog -> m Word64 Source #

Gets the number of CPU cores this Souffle program should use.

loadFiles :: Handle prog -> FilePath -> m () Source #

Load all facts from files in a certain directory.

writeFiles :: Handle prog -> m () Source #

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

getFacts :: (Fact a, ContainsFact prog a) => Handle prog -> m [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) => Handle 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.

addFact :: (Fact a, ContainsFact prog a) => Handle prog -> a -> m () Source #

Adds a fact to the program.

addFacts :: (Foldable t, Fact a, ContainsFact prog a) => Handle 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

Methods

init :: Program prog => prog -> SouffleM (Maybe (Handle prog)) Source #

run :: Handle prog -> SouffleM () Source #

setNumThreads :: Handle prog -> Word64 -> SouffleM () Source #

getNumThreads :: Handle prog -> SouffleM Word64 Source #

loadFiles :: Handle prog -> FilePath -> SouffleM () Source #

writeFiles :: Handle prog -> SouffleM () Source #

getFacts :: (Fact a, ContainsFact prog a) => Handle prog -> SouffleM [a] Source #

findFact :: (Fact a, ContainsFact prog a) => Handle prog -> a -> SouffleM (Maybe a) Source #

addFact :: (Fact a, ContainsFact prog a) => Handle prog -> a -> SouffleM () Source #

addFacts :: (Foldable t, Fact a, ContainsFact prog a) => Handle prog -> t a -> SouffleM () Source #

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

Defined in Language.Souffle

Methods

init :: Program prog => prog -> ExceptT s m (Maybe (Handle prog)) Source #

run :: Handle prog -> ExceptT s m () Source #

setNumThreads :: Handle prog -> Word64 -> ExceptT s m () Source #

getNumThreads :: Handle prog -> ExceptT s m Word64 Source #

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

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

getFacts :: (Fact a, ContainsFact prog a) => Handle prog -> ExceptT s m [a] Source #

findFact :: (Fact a, ContainsFact prog a) => Handle prog -> a -> ExceptT s m (Maybe a) Source #

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

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

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

Defined in Language.Souffle

Methods

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

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

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

getNumThreads :: Handle prog -> ReaderT r m Word64 Source #

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

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

getFacts :: (Fact a, ContainsFact prog a) => Handle prog -> ReaderT r m [a] Source #

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

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

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

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

Defined in Language.Souffle

Methods

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

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

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

getNumThreads :: Handle prog -> StateT s m Word64 Source #

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

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

getFacts :: (Fact a, ContainsFact prog a) => Handle prog -> StateT s m [a] Source #

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

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

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

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

Defined in Language.Souffle

Methods

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

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

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

getNumThreads :: Handle prog -> WriterT w m Word64 Source #

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

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

getFacts :: (Fact a, ContainsFact prog a) => Handle prog -> WriterT w m [a] Source #

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

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

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

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

Defined in Language.Souffle

Methods

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

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

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

getNumThreads :: Handle prog -> RWST r w s m Word64 Source #

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

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

getFacts :: (Fact a, ContainsFact prog a) => Handle prog -> RWST r w s m [a] Source #

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

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

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

data SouffleM a Source #

A monad for executing Souffle-related actions in.

Instances

Instances details
Monad SouffleM Source # 
Instance details

Defined in Language.Souffle

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

Methods

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

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

Applicative SouffleM Source # 
Instance details

Defined in Language.Souffle

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

Methods

liftIO :: IO a -> SouffleM a #

MonadSouffle SouffleM Source # 
Instance details

Defined in Language.Souffle

Methods

init :: Program prog => prog -> SouffleM (Maybe (Handle prog)) Source #

run :: Handle prog -> SouffleM () Source #

setNumThreads :: Handle prog -> Word64 -> SouffleM () Source #

getNumThreads :: Handle prog -> SouffleM Word64 Source #

loadFiles :: Handle prog -> FilePath -> SouffleM () Source #

writeFiles :: Handle prog -> SouffleM () Source #

getFacts :: (Fact a, ContainsFact prog a) => Handle prog -> SouffleM [a] Source #

findFact :: (Fact a, ContainsFact prog a) => Handle prog -> a -> SouffleM (Maybe a) Source #

addFact :: (Fact a, ContainsFact prog a) => Handle prog -> a -> SouffleM () Source #

addFacts :: (Foldable t, Fact a, ContainsFact prog a) => Handle prog -> t a -> SouffleM () Source #

runSouffle :: SouffleM a -> IO a Source #

Returns the underlying IO action.