souffle-haskell-3.5.0: Souffle Datalog bindings for Haskell
Safe HaskellSafe-Inferred
LanguageHaskell2010

Language.Souffle.Analysis

Description

This module provides an Analysis type for combining multiple Datalog analyses together. Composition of analyses is done via the various type-classes that are implemented for this type. For a longer explanation of how the Analysis type works, see this blogpost.

If you are just starting out using this library, you are probably better of taking a look at the Language.Souffle.Interpreted module instead to start interacting with a single Datalog program.

Synopsis

Documentation

data Analysis m a b Source #

Data type used to compose multiple Datalog programs. Composition is mainly done via the various type-classes implemented for this type. Values of this type can be created using mkAnalysis.

The m type-variable represents the monad the analysis will run in. In most cases, this will be the SouffleM monad from either Language.Souffle.Compiled or Language.Souffle.Interpreted. The a and b type-variables represent respectively the input and output types of the analysis.

Instances

Instances details
(Monad m, Monoid (m ()), Category (Analysis m)) => Arrow (Analysis m) Source # 
Instance details

Defined in Language.Souffle.Analysis

Methods

arr :: (b -> c) -> Analysis m b c #

first :: Analysis m b c -> Analysis m (b, d) (c, d) #

second :: Analysis m b c -> Analysis m (d, b) (d, c) #

(***) :: Analysis m b c -> Analysis m b' c' -> Analysis m (b, b') (c, c') #

(&&&) :: Analysis m b c -> Analysis m b c' -> Analysis m b (c, c') #

(Monad m, Monoid (m ())) => ArrowChoice (Analysis m) Source # 
Instance details

Defined in Language.Souffle.Analysis

Methods

left :: Analysis m b c -> Analysis m (Either b d) (Either c d) #

right :: Analysis m b c -> Analysis m (Either d b) (Either d c) #

(+++) :: Analysis m b c -> Analysis m b' c' -> Analysis m (Either b b') (Either c c') #

(|||) :: Analysis m b d -> Analysis m c d -> Analysis m (Either b c) d #

Applicative m => Choice (Analysis m) Source # 
Instance details

Defined in Language.Souffle.Analysis

Methods

left' :: Analysis m a b -> Analysis m (Either a c) (Either b c)

right' :: Analysis m a b -> Analysis m (Either c a) (Either c b)

Functor m => Strong (Analysis m) Source # 
Instance details

Defined in Language.Souffle.Analysis

Methods

first' :: Analysis m a b -> Analysis m (a, c) (b, c)

second' :: Analysis m a b -> Analysis m (c, a) (c, b)

Functor m => Profunctor (Analysis m) Source # 
Instance details

Defined in Language.Souffle.Analysis

Methods

dimap :: (a -> b) -> (c -> d) -> Analysis m b c -> Analysis m a d

lmap :: (a -> b) -> Analysis m b c -> Analysis m a c

rmap :: (b -> c) -> Analysis m a b -> Analysis m a c

(#.) :: forall a b c q. Coercible c b => q b c -> Analysis m a b -> Analysis m a c

(.#) :: forall a b c q. Coercible b a => Analysis m b c -> q a b -> Analysis m a c

(Monoid (m ()), Monad m) => Category (Analysis m :: Type -> Type -> Type) Source # 
Instance details

Defined in Language.Souffle.Analysis

Methods

id :: forall (a :: k). Analysis m a a #

(.) :: forall (b :: k) (c :: k) (a :: k). Analysis m b c -> Analysis m a b -> Analysis m a c #

(Monoid (m ()), Applicative m) => Applicative (Analysis m a) Source # 
Instance details

Defined in Language.Souffle.Analysis

Methods

pure :: a0 -> Analysis m a a0 #

(<*>) :: Analysis m a (a0 -> b) -> Analysis m a a0 -> Analysis m a b #

liftA2 :: (a0 -> b -> c) -> Analysis m a a0 -> Analysis m a b -> Analysis m a c #

(*>) :: Analysis m a a0 -> Analysis m a b -> Analysis m a b #

(<*) :: Analysis m a a0 -> Analysis m a b -> Analysis m a a0 #

Functor m => Functor (Analysis m a) Source # 
Instance details

Defined in Language.Souffle.Analysis

Methods

fmap :: (a0 -> b) -> Analysis m a a0 -> Analysis m a b #

(<$) :: a0 -> Analysis m a b -> Analysis m a a0 #

(Monoid (m ()), Monoid (m b)) => Monoid (Analysis m a b) Source # 
Instance details

Defined in Language.Souffle.Analysis

Methods

mempty :: Analysis m a b #

mappend :: Analysis m a b -> Analysis m a b -> Analysis m a b #

mconcat :: [Analysis m a b] -> Analysis m a b #

(Semigroup (m ()), Semigroup (m b)) => Semigroup (Analysis m a b) Source # 
Instance details

Defined in Language.Souffle.Analysis

Methods

(<>) :: Analysis m a b -> Analysis m a b -> Analysis m a b #

sconcat :: NonEmpty (Analysis m a b) -> Analysis m a b #

stimes :: Integral b0 => b0 -> Analysis m a b -> Analysis m a b #

mkAnalysis Source #

Arguments

:: (a -> m ())

Function for finding facts used by the Analysis.

-> m ()

Function for actually running the Analysis.

-> m b

Function for retrieving the Analysis results from Souffle.

-> Analysis m a b 

Creates an Analysis value.

execAnalysis :: Applicative m => Analysis m a b -> a -> m b Source #

Converts an Analysis into an effectful function, so it can be executed.