Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data Condition a
- tautology :: Condition a
- matches :: a -> Condition a -> Bool
- itself :: a -> a
- type BoltId = Int
- data Persisted a = Persisted {
- objectId :: BoltId
- objectValue :: a
- class GetBoltId a where
- fromInt :: Int -> BoltId
- class ToCypher a where
- class FromValue a where
- type Label = Text
- class Labels a where
- class NodeLike a where
- class Properties a where
- type Property = (Text, Value)
- class ToValue a where
- class URelationLike a where
- toURelation :: a -> URelationship
- fromURelation :: URelationship -> a
Documentation
Conditional expressions over type a
and its mappings.
Supported operations:
Typical usage:
Say we have variable var :: a
, a function f :: a -> b
and a value val :: b
.
Expression f :== val
acts as f var == val
.
Examples:
data D = D { fld1 :: Int , fld2 :: String , fld3 :: Double } d = D 42 "noononno" 1.618 d `matches` (fld1 :== 12 :&& fld2 :== "abc") False d `matches` (fld1 :== 42 :|| fld3 == 1.0) True
tautology :: Condition a Source #
Matching tautology
will always succeed.
whatever `matches` tautology == True
Match is lazy:
undefined `matches` tautology == True
Object itself instead of its mappings is matched with help of this alias.
42 `matches` (itself :== 42) == True 42 `matches` (itself :== 41) == False
BoltId
is alias for Bolt Node
, Relationship
and URelationship
identities.
Persisted | |
|
Instances
Functor Persisted Source # | |
Eq a => Eq (Persisted a) Source # | |
Ord a => Ord (Persisted a) Source # | |
Defined in Database.Bolt.Extras.Internal.Persisted | |
Read a => Read (Persisted a) Source # | |
Show a => Show (Persisted a) Source # | |
Generic (Persisted a) Source # | |
ToJSON a => ToJSON (Persisted a) Source # | |
Defined in Database.Bolt.Extras.Internal.Persisted | |
FromJSON a => FromJSON (Persisted a) Source # | |
GetBoltId (Persisted a) Source # | |
type Rep (Persisted a) Source # | |
Defined in Database.Bolt.Extras.Internal.Persisted type Rep (Persisted a) = D1 ('MetaData "Persisted" "Database.Bolt.Extras.Internal.Persisted" "hasbolt-extras-0.0.1.7-3FlaUg4g8ip6QmPMDATn4z" 'False) (C1 ('MetaCons "Persisted" 'PrefixI 'True) (S1 ('MetaSel ('Just "objectId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BoltId) :*: S1 ('MetaSel ('Just "objectValue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a))) |
class GetBoltId a where Source #
Common class to get BoltId
from the object.
Instances
GetBoltId Node Source # | |
GetBoltId Relationship Source # | |
Defined in Database.Bolt.Extras.Internal.Persisted getBoltId :: Relationship -> BoltId Source # | |
GetBoltId URelationship Source # | |
Defined in Database.Bolt.Extras.Internal.Persisted getBoltId :: URelationship -> BoltId Source # | |
GetBoltId RelResult Source # | |
GetBoltId NodeResult Source # | |
Defined in Database.Bolt.Extras.Graph.Internal.Get getBoltId :: NodeResult -> BoltId Source # | |
GetBoltId (Persisted a) Source # | |
class ToCypher a where Source #
The class for convertation into Cypher.
Instances
ToCypher Value Source # | Convertation for |
ToCypher Property Source # | Converts property with |
ToCypher Label Source # | Label with |
ToCypher Conds Source # | |
ToCypher Cond Source # | |
ToCypher Selectors Source # | |
ToCypher Selector Source # | |
ToCypher PathSelector Source # | |
Defined in Database.Bolt.Extras.DSL.Internal.Instances toCypher :: PathSelector -> Text Source # | |
ToCypher RelSelector Source # | |
Defined in Database.Bolt.Extras.DSL.Internal.Instances toCypher :: RelSelector -> Text Source # | |
ToCypher NodeSelector Source # | |
Defined in Database.Bolt.Extras.DSL.Internal.Instances toCypher :: NodeSelector -> Text Source # | |
ToCypher [(Text, Text)] Source # | |
ToCypher [Property] Source # | Several properties are formatted with concatenation. |
ToCypher [Label] Source # | Several labels are formatted with concatenation. |
ToCypher (Text, Text) Source # | |
class FromValue a where Source #
Instances
FromValue Bool Source # | |
FromValue Double Source # | |
FromValue Float Source # | |
FromValue Int Source # | |
FromValue () Source # | |
Defined in Database.Bolt.Extras.Internal.Instances | |
FromValue Text Source # | |
FromValue Structure Source # | |
FromValue Value Source # | |
FromValue a => FromValue [a] Source # | |
Defined in Database.Bolt.Extras.Internal.Instances | |
FromValue a => FromValue (Maybe a) Source # | |
FromValue (Map Text Value) Source # | |
Labels
means that labels can be obtained from entity.
Instances
Labels Node Source # | |
Labels URelationship Source # | |
Defined in Database.Bolt.Extras.Internal.Types getLabels :: URelationship -> [Label] Source # |
class Properties a where Source #
Properties
means that properties can be obtained from entity.
Instances
class ToValue a where Source #
Instances
ToValue Bool Source # | |
ToValue Double Source # | |
ToValue Float Source # | |
ToValue Int Source # | |
ToValue () Source # | |
Defined in Database.Bolt.Extras.Internal.Instances | |
ToValue Text Source # | |
ToValue Structure Source # | |
ToValue Value Source # | |
ToValue a => ToValue [a] Source # | |
Defined in Database.Bolt.Extras.Internal.Instances | |
ToValue a => ToValue (Maybe a) Source # | |
ToValue (Map Text Value) Source # | |
class URelationLike a where Source #
URelationLike
class represents convertable into and from URelationship
.
toURelation :: a -> URelationship Source #
fromURelation :: URelationship -> a Source #