| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Database.Bolt.Extras
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- toCypher :: HasCallStack => a -> Text
 
- class FromValue a where- fromValue :: HasCallStack => Value -> a
 
- type Label = Text
- class Labels a where- getLabels :: HasCallStack => a -> [Label]
 
- class NodeLike a where- toNode :: HasCallStack => a -> Node
- fromNode :: HasCallStack => Node -> a
 
- class Properties a where- getProps :: HasCallStack => a -> Map Text Value
 
- type Property = (Text, Value)
- class ToValue a where- toValue :: HasCallStack => a -> Value
 
- class URelationLike a where- toURelation :: HasCallStack => a -> URelationship
- fromURelation :: HasCallStack => URelationship -> a
 
- newtype ToIsValue a = ToIsValue a
- newtype NodeLikeProps a = NodeLikeProps 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)
Truetautology :: 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.
Constructors
| Persisted | |
| Fields 
 | |
Instances
| Functor Persisted Source # | |
| FromJSON a => FromJSON (Persisted a) Source # | |
| ToJSON a => ToJSON (Persisted a) Source # | |
| Defined in Database.Bolt.Extras.Internal.Persisted | |
| Generic (Persisted a) Source # | |
| Read a => Read (Persisted a) Source # | |
| Show a => Show (Persisted a) Source # | |
| Eq a => Eq (Persisted a) Source # | |
| Ord a => Ord (Persisted a) Source # | |
| Defined in Database.Bolt.Extras.Internal.Persisted | |
| 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.2.0-LlsBPfU8Ggs1Zvm48yF6Qb" '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 Methods getBoltId :: Relationship -> BoltId Source # | |
| GetBoltId URelationship Source # | |
| Defined in Database.Bolt.Extras.Internal.Persisted Methods getBoltId :: URelationship -> BoltId Source # | |
| GetBoltId NodeResult Source # | |
| Defined in Database.Bolt.Extras.Graph.Internal.Get Methods getBoltId :: NodeResult -> BoltId Source # | |
| GetBoltId RelResult Source # | |
| GetBoltId (Persisted a) Source # | |
class ToCypher a where Source #
The class for convertation into Cypher.
Methods
toCypher :: HasCallStack => a -> Text Source #
Instances
| ToCypher Value Source # | Convertation for  | 
| ToCypher Cond Source # | |
| ToCypher Conds Source # | |
| ToCypher NodeSelector Source # | |
| Defined in Database.Bolt.Extras.DSL.Internal.Instances Methods toCypher :: NodeSelector -> Text Source # | |
| ToCypher PathSelector Source # | |
| Defined in Database.Bolt.Extras.DSL.Internal.Instances Methods toCypher :: PathSelector -> Text Source # | |
| ToCypher RelSelector Source # | |
| Defined in Database.Bolt.Extras.DSL.Internal.Instances Methods toCypher :: RelSelector -> Text Source # | |
| ToCypher Selector Source # | |
| ToCypher Selectors Source # | |
| ToCypher Label Source # | Label with  | 
| ToCypher Property Source # | Converts property with  | 
| ToCypher [Label] Source # | Several labels are formatted with concatenation. | 
| ToCypher [Property] Source # | Several properties are formatted with concatenation. | 
| ToCypher [(Text, Text)] Source # | |
| ToCypher (Text, Text) Source # | |
class FromValue a where Source #
Methods
fromValue :: HasCallStack => Value -> a Source #
Instances
| FromValue Structure Source # | |
| FromValue Value Source # | |
| FromValue Text Source # | |
| FromValue () Source # | |
| Defined in Database.Bolt.Extras.Internal.Instances | |
| FromValue Bool Source # | |
| FromValue Double Source # | |
| FromValue Float Source # | |
| FromValue Int Source # | |
| FromValue a => FromValue (NonEmpty a) Source # | |
| FromValue a => FromValue (Maybe a) Source # | |
| FromValue a => FromValue [a] Source # | |
| Defined in Database.Bolt.Extras.Internal.Instances | |
| FromValue (Map Text Value) Source # | |
Labels means that labels can be obtained from entity.
Methods
getLabels :: HasCallStack => a -> [Label] Source #
Instances
| Labels Node Source # | |
| Labels URelationship Source # | |
| Defined in Database.Bolt.Extras.Internal.Types Methods getLabels :: URelationship -> [Label] Source # | |
class NodeLike a where Source #
Instances
class Properties a where Source #
Properties means that properties can be obtained from entity.
Instances
class ToValue a where Source #
Methods
toValue :: HasCallStack => a -> Value Source #
Instances
| ToValue Structure Source # | |
| ToValue Value Source # | |
| ToValue Text Source # | |
| ToValue () Source # | |
| Defined in Database.Bolt.Extras.Internal.Instances | |
| ToValue Bool Source # | |
| ToValue Double Source # | |
| ToValue Float Source # | |
| ToValue Int Source # | |
| ToValue a => ToValue (NonEmpty a) Source # | |
| ToValue a => ToValue (Maybe a) Source # | |
| ToValue a => ToValue [a] Source # | |
| Defined in Database.Bolt.Extras.Internal.Instances | |
| ToValue (Map Text Value) Source # | |
class URelationLike a where Source #
URelationLike class represents convertable into and from URelationship.
Methods
toURelation :: HasCallStack => a -> URelationship Source #
fromURelation :: HasCallStack => URelationship -> a Source #
Instances
| URelationLike RelResult Source # | |
| Defined in Database.Bolt.Extras.Graph.Internal.Get Methods toURelation :: RelResult -> URelationship Source # | |
ToIsValue provides IsValue instance given ToValue
Constructors
| ToIsValue a | 
newtype NodeLikeProps a Source #
NodeLikeProps provides IsValue instance given NodeLike, in form of Map Text Value
Constructors
| NodeLikeProps a | 
Instances
| NodeLike a => IsValue (NodeLikeProps a) Source # | |
| Defined in Database.Bolt.Extras.Internal.Instances | |