| Maintainer | Toshio Ito <debug.ito@gmail.com> |
|---|---|
| Safe Haskell | None |
| Language | Haskell2010 |
Data.Greskell.AsLabel
Contents
Description
Since: 0.2.2.0
Synopsis
- newtype AsLabel a = AsLabel {}
- type SelectedMap = PMap Single
- unsafeCastAsLabel :: AsLabel a -> AsLabel b
- lookup :: (PMapKey k, NonEmptyLike c) => k -> PMap c v -> Maybe v
- lookupM :: (PMapKey k, NonEmptyLike c, MonadThrow m) => k -> PMap c v -> m v
- lookupAs :: (PMapKey k, NonEmptyLike c, PMapValue k ~ a, FromGraphSON a) => k -> PMap c GValue -> Either PMapLookupException a
- lookupAsM :: (PMapKey k, NonEmptyLike c, PMapValue k ~ a, FromGraphSON a, MonadThrow m) => k -> PMap c GValue -> m a
- data PMapLookupException
- data LabeledP a
AsLabel
AsLabel a represents a label string used in .as step
pointing to the data of type a.
Instances
| Functor AsLabel Source # | Unsafely convert the phantom type. |
| Eq (AsLabel a) Source # | |
| Ord (AsLabel a) Source # | |
| Show (AsLabel a) Source # | |
| IsString (AsLabel a) Source # | Since: 1.0.0.0 |
Defined in Data.Greskell.AsLabel Methods fromString :: String -> AsLabel a # | |
| Hashable (AsLabel a) Source # | |
Defined in Data.Greskell.AsLabel | |
| ToGreskell (AsLabel a) Source # | Returns the |
Defined in Data.Greskell.AsLabel Associated Types type GreskellReturn (AsLabel a) # Methods toGreskell :: AsLabel a -> Greskell (GreskellReturn (AsLabel a)) # | |
| PMapKey (AsLabel a) Source # | Since: 1.0.0.0 |
| type GreskellReturn (AsLabel a) Source # | |
Defined in Data.Greskell.AsLabel | |
| type PMapValue (AsLabel a) Source # | |
Defined in Data.Greskell.AsLabel | |
type SelectedMap = PMap Single Source #
A map keyed with AsLabel. Obtained from .select step, for
example.
unsafeCastAsLabel :: AsLabel a -> AsLabel b Source #
Unsafely cast the phantom type of the AsLabel.
Since: 1.1.0.0
Re-exports
lookup :: (PMapKey k, NonEmptyLike c) => k -> PMap c v -> Maybe v Source #
Lookup the first value for the key from PMap.
lookupM :: (PMapKey k, NonEmptyLike c, MonadThrow m) => k -> PMap c v -> m v Source #
MonadThrow version of lookup. If there is no value for the
key, it throws PMapNoSuchKey.
lookupAs :: (PMapKey k, NonEmptyLike c, PMapValue k ~ a, FromGraphSON a) => k -> PMap c GValue -> Either PMapLookupException a Source #
Lookup the value and parse it into a.
lookupAsM :: (PMapKey k, NonEmptyLike c, PMapValue k ~ a, FromGraphSON a, MonadThrow m) => k -> PMap c GValue -> m a Source #
MonadThrow version of lookupAs.
data PMapLookupException Source #
Constructors
| PMapNoSuchKey Text | The |
| PMapParseError Text String | Failed to parse the value into the type that the |
Instances
LabeledP
LabeledP is just like P, a Haskell representation of
TinkerPop's P class. Unlike P, however, LabeledP keeps a
label (AsLabel) inside. It is used in .where step.
Since: 1.2.0.0
Instances
| PLike (LabeledP a) Source # | You can construct |
Defined in Data.Greskell.AsLabel Associated Types type PParameter (LabeledP a) Source # | |
| type PParameter (LabeledP a) Source # | |
Defined in Data.Greskell.AsLabel | |