greskell-2.0.3.0: Haskell binding for Gremlin graph query language
MaintainerToshio Ito <debug.ito@gmail.com>
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Greskell.AsLabel

Description

Since: 0.2.2.0

Synopsis

AsLabel

newtype AsLabel a Source #

AsLabel a represents a label string used in .as step pointing to the data of type a.

Constructors

AsLabel 

Fields

Instances

Instances details
Functor AsLabel Source #

Unsafely convert the phantom type.

Instance details

Defined in Data.Greskell.AsLabel

Methods

fmap :: (a -> b) -> AsLabel a -> AsLabel b #

(<$) :: a -> AsLabel b -> AsLabel a #

IsString (AsLabel a) Source #

Since: 1.0.0.0

Instance details

Defined in Data.Greskell.AsLabel

Methods

fromString :: String -> AsLabel a #

Show (AsLabel a) Source # 
Instance details

Defined in Data.Greskell.AsLabel

Methods

showsPrec :: Int -> AsLabel a -> ShowS #

show :: AsLabel a -> String #

showList :: [AsLabel a] -> ShowS #

Eq (AsLabel a) Source # 
Instance details

Defined in Data.Greskell.AsLabel

Methods

(==) :: AsLabel a -> AsLabel a -> Bool #

(/=) :: AsLabel a -> AsLabel a -> Bool #

Ord (AsLabel a) Source # 
Instance details

Defined in Data.Greskell.AsLabel

Methods

compare :: AsLabel a -> AsLabel a -> Ordering #

(<) :: AsLabel a -> AsLabel a -> Bool #

(<=) :: AsLabel a -> AsLabel a -> Bool #

(>) :: AsLabel a -> AsLabel a -> Bool #

(>=) :: AsLabel a -> AsLabel a -> Bool #

max :: AsLabel a -> AsLabel a -> AsLabel a #

min :: AsLabel a -> AsLabel a -> AsLabel a #

PMapKey (AsLabel a) Source #

Since: 1.0.0.0

Instance details

Defined in Data.Greskell.AsLabel

Associated Types

type PMapValue (AsLabel a) Source #

Methods

keyText :: AsLabel a -> Text Source #

ToGreskell (AsLabel a) Source #

Returns the Text as a Gremlin string.

Instance details

Defined in Data.Greskell.AsLabel

Associated Types

type GreskellReturn (AsLabel a) #

Hashable (AsLabel a) Source # 
Instance details

Defined in Data.Greskell.AsLabel

Methods

hashWithSalt :: Int -> AsLabel a -> Int #

hash :: AsLabel a -> Int #

type PMapValue (AsLabel a) Source # 
Instance details

Defined in Data.Greskell.AsLabel

type PMapValue (AsLabel a) = a
type GreskellReturn (AsLabel a) Source # 
Instance details

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.

data PMapLookupException Source #

An Exception raised when looking up values from PMap.

Since: 1.0.0.0

Constructors

PMapNoSuchKey Text

The PMap doesn't have the given key.

PMapParseError Text String

Failed to parse the value into the type that the PMapKey indicates. The Text is the key, and the String is the error message.

LabeledP

data LabeledP a Source #

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

Instances details
PLike (LabeledP a) Source #

You can construct Greskell (LabeledP a) from AsLabel a.

Instance details

Defined in Data.Greskell.AsLabel

Associated Types

type PParameter (LabeledP a) Source #

type PParameter (LabeledP a) Source # 
Instance details

Defined in Data.Greskell.AsLabel