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

Language.Souffle.Marshal

Description

This module exposes a uniform interface to marshal values to and from Souffle Datalog. This is done via the Marshal typeclass. Also, a mechanism is exposed for generically deriving marshalling and unmarshalling code for simple product types.

Synopsis

Documentation

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 #

class Monad m => MonadPush m where Source #

A typeclass for serializing primitive values from Haskell to Datalog.

This typeclass is only used internally and subject to change.

See also: MonadPop, Marshal.

Methods

pushInt32 :: Int32 -> m () Source #

Marshals a signed 32 bit integer to the datalog side.

pushUInt32 :: Word32 -> m () Source #

Marshals an unsigned 32 bit integer to the datalog side.

pushFloat :: Float -> m () Source #

Marshals a float to the datalog side.

pushString :: String -> m () Source #

Marshals a string to the datalog side.

pushText :: ShortText -> m () Source #

Marshals a UTF8-encoded Text string to the datalog side.

pushTextUtf16 :: Text -> m () Source #

Marshals a UTF16-encoded Text string to the datalog side.

class Monad m => MonadPop m where Source #

A typeclass for serializing primitive values from Datalog to Haskell.

This typeclass is only used internally and subject to change.

See also: MonadPush, Marshal.

Methods

popInt32 :: m Int32 Source #

Unmarshals a signed 32 bit integer from the datalog side.

popUInt32 :: m Word32 Source #

Unmarshals an unsigned 32 bit integer from the datalog side.

popFloat :: m Float Source #

Unmarshals a float from the datalog side.

popString :: m String Source #

Unmarshals a string from the datalog side.

popText :: m ShortText Source #

Unmarshals a Text string from the datalog side.

popTextUtf16 :: m Text Source #

Unmarshals a UTF16-encoded Text string from the datalog side.

type family SimpleProduct (a :: Type) :: Constraint where ... Source #

A helper type family used for generating a more user-friendly type error for incompatible types when generically deriving marshalling code for the Marshal typeclass.

The a type parameter is the original type, used when displaying the type error.

A type error is returned if the passed in type is not a simple product type consisting of only types that implement Marshal.

Equations

SimpleProduct a = (ProductLike a (Rep a), OnlyMarshallableFields (Rep a))