Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
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.
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
Nothing
push :: MonadPush m => a -> m () Source #
Marshals a value to the datalog side.
pop :: MonadPop m => m a Source #
Unmarshals a value from the datalog side.
Instances
Marshal Int32 Source # | |
Marshal Word32 Source # | |
Marshal Text Source # | |
Marshal Text Source # | |
Marshal String Source # | |
Marshal Float Source # | |
Marshal fact => Marshal (FactOptions fact name dir) Source # | |
Defined in Language.Souffle.Class 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.
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 :: Text -> m () Source #
Marshals a UTF8-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.
Unmarshals a signed 32 bit integer from the datalog side.
popUInt32 :: m Word32 Source #
Unmarshals an unsigned 32 bit integer from the datalog side.
Unmarshals a float from the datalog side.
popString :: m String Source #
Unmarshals a string from the datalog side.
Unmarshals a UTF8-encoded Text string from the datalog side.
type family SimpleProduct a 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
.
SimpleProduct a = (ProductLike a (Rep a), OnlyMarshallableFields (Rep a)) |