{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilyDependencies #-}
{-# LANGUAGE TypeInType #-}
{-# LANGUAGE TypeOperators #-}
module Database.Bolt.Extras.DSL.Typed.Types where
import Data.Kind (Constraint, Type)
import Data.Text (Text)
import qualified Database.Bolt as B
import GHC.Generics (Rep)
import GHC.TypeLits (KnownSymbol, Symbol)
import qualified Database.Bolt.Extras.DSL as UT
import Database.Bolt.Extras.DSL.Typed.Families
class SelectorLike (a :: k -> Type) where
type CanAddType (types :: k) :: Constraint
type AddType (types :: k) (typ :: Type) = (result :: k) | result -> types typ
type HasField (types :: k) (field :: Symbol) (typ :: Type) :: Constraint
type HasField' (types :: k) (field :: Symbol) :: Constraint
withIdentifier :: Text -> a types -> a types
withLabel
:: CanAddType types
=> KnownSymbol (GetTypeName (Rep typ))
=> a types
-> a (AddType types typ)
withProp
:: HasField types field typ
=> B.IsValue typ
=> (SymbolS field, typ)
-> a types
-> a types
withParam
:: HasField' types field
=> (SymbolS field, Text)
-> a types
-> a types
type LabelConstraint (typ :: Type) = KnownSymbol (GetTypeName (Rep typ))
lbl
:: forall (typ :: Type) k (types :: k) (a :: k -> Type)
. SelectorLike a
=> CanAddType types
=> KnownSymbol (GetTypeName (Rep typ))
=> a types
-> a (AddType types typ)
lbl :: a types -> a (AddType types typ)
lbl = a types -> a (AddType types typ)
forall k (a :: k -> *) (types :: k) typ.
(SelectorLike a, CanAddType types,
KnownSymbol (GetTypeName (Rep typ))) =>
a types -> a (AddType types typ)
withLabel
prop
:: forall (field :: Symbol) k (a :: k -> Type) (types :: k) (typ :: Type)
. SelectorLike a
=> HasField types field typ
=> B.IsValue typ
=> (SymbolS field, typ)
-> a types -> a types
prop :: (SymbolS field, typ) -> a types -> a types
prop = (SymbolS field, typ) -> a types -> a types
forall k (a :: k -> *) (types :: k) (field :: Symbol) typ.
(SelectorLike a, HasField types field typ, IsValue typ) =>
(SymbolS field, typ) -> a types -> a types
withProp
propMaybe
:: forall (field :: Symbol) k (a :: k -> Type) (types :: k) (typ :: Type)
. SelectorLike a
=> HasField types field typ
=> B.IsValue typ
=> (SymbolS field, Maybe typ)
-> a types -> a types
propMaybe :: (SymbolS field, Maybe typ) -> a types -> a types
propMaybe (SymbolS field
name, Just typ
val) = (SymbolS field, typ) -> a types -> a types
forall k (a :: k -> *) (types :: k) (field :: Symbol) typ.
(SelectorLike a, HasField types field typ, IsValue typ) =>
(SymbolS field, typ) -> a types -> a types
withProp (SymbolS field
name, typ
val)
propMaybe (SymbolS field, Maybe typ)
_ = a types -> a types
forall a. a -> a
id
param
:: forall (field :: Symbol) k (a :: k -> Type) (types :: k)
. SelectorLike a
=> HasField' types field
=> (SymbolS field, Text)
-> a types -> a types
param :: (SymbolS field, Text) -> a types -> a types
param = (SymbolS field, Text) -> a types -> a types
forall k (a :: k -> *) (types :: k) (field :: Symbol).
(SelectorLike a, HasField' types field) =>
(SymbolS field, Text) -> a types -> a types
withParam
type (=:) (a :: k) (b :: l) = '(a, b)
(=:) :: forall (field :: Symbol) (typ :: Type). SymbolS field -> typ -> (SymbolS field, typ)
=: :: SymbolS field -> typ -> (SymbolS field, typ)
(=:) = (,)
newtype NodeSelector (typ :: [Type])
= NodeSelector
{ NodeSelector typ -> NodeSelector
nodeSelector :: UT.NodeSelector
}
deriving (Int -> NodeSelector typ -> ShowS
[NodeSelector typ] -> ShowS
NodeSelector typ -> String
(Int -> NodeSelector typ -> ShowS)
-> (NodeSelector typ -> String)
-> ([NodeSelector typ] -> ShowS)
-> Show (NodeSelector typ)
forall (typ :: [*]). Int -> NodeSelector typ -> ShowS
forall (typ :: [*]). [NodeSelector typ] -> ShowS
forall (typ :: [*]). NodeSelector typ -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [NodeSelector typ] -> ShowS
$cshowList :: forall (typ :: [*]). [NodeSelector typ] -> ShowS
show :: NodeSelector typ -> String
$cshow :: forall (typ :: [*]). NodeSelector typ -> String
showsPrec :: Int -> NodeSelector typ -> ShowS
$cshowsPrec :: forall (typ :: [*]). Int -> NodeSelector typ -> ShowS
Show, NodeSelector typ -> NodeSelector typ -> Bool
(NodeSelector typ -> NodeSelector typ -> Bool)
-> (NodeSelector typ -> NodeSelector typ -> Bool)
-> Eq (NodeSelector typ)
forall (typ :: [*]). NodeSelector typ -> NodeSelector typ -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NodeSelector typ -> NodeSelector typ -> Bool
$c/= :: forall (typ :: [*]). NodeSelector typ -> NodeSelector typ -> Bool
== :: NodeSelector typ -> NodeSelector typ -> Bool
$c== :: forall (typ :: [*]). NodeSelector typ -> NodeSelector typ -> Bool
Eq)
newtype RelSelector (typ :: Maybe Type)
= RelSelector
{ RelSelector typ -> RelSelector
relSelector :: UT.RelSelector
}
deriving (Int -> RelSelector typ -> ShowS
[RelSelector typ] -> ShowS
RelSelector typ -> String
(Int -> RelSelector typ -> ShowS)
-> (RelSelector typ -> String)
-> ([RelSelector typ] -> ShowS)
-> Show (RelSelector typ)
forall (typ :: Maybe *). Int -> RelSelector typ -> ShowS
forall (typ :: Maybe *). [RelSelector typ] -> ShowS
forall (typ :: Maybe *). RelSelector typ -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [RelSelector typ] -> ShowS
$cshowList :: forall (typ :: Maybe *). [RelSelector typ] -> ShowS
show :: RelSelector typ -> String
$cshow :: forall (typ :: Maybe *). RelSelector typ -> String
showsPrec :: Int -> RelSelector typ -> ShowS
$cshowsPrec :: forall (typ :: Maybe *). Int -> RelSelector typ -> ShowS
Show, RelSelector typ -> RelSelector typ -> Bool
(RelSelector typ -> RelSelector typ -> Bool)
-> (RelSelector typ -> RelSelector typ -> Bool)
-> Eq (RelSelector typ)
forall (typ :: Maybe *). RelSelector typ -> RelSelector typ -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RelSelector typ -> RelSelector typ -> Bool
$c/= :: forall (typ :: Maybe *). RelSelector typ -> RelSelector typ -> Bool
== :: RelSelector typ -> RelSelector typ -> Bool
$c== :: forall (typ :: Maybe *). RelSelector typ -> RelSelector typ -> Bool
Eq)
newtype SymbolS (s :: Symbol) = SymbolS { SymbolS s -> String
getSymbol :: String }
deriving (Int -> SymbolS s -> ShowS
[SymbolS s] -> ShowS
SymbolS s -> String
(Int -> SymbolS s -> ShowS)
-> (SymbolS s -> String)
-> ([SymbolS s] -> ShowS)
-> Show (SymbolS s)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall (s :: Symbol). Int -> SymbolS s -> ShowS
forall (s :: Symbol). [SymbolS s] -> ShowS
forall (s :: Symbol). SymbolS s -> String
showList :: [SymbolS s] -> ShowS
$cshowList :: forall (s :: Symbol). [SymbolS s] -> ShowS
show :: SymbolS s -> String
$cshow :: forall (s :: Symbol). SymbolS s -> String
showsPrec :: Int -> SymbolS s -> ShowS
$cshowsPrec :: forall (s :: Symbol). Int -> SymbolS s -> ShowS
Show)
defN :: NodeSelector '[]
defN :: NodeSelector '[]
defN = NodeSelector -> NodeSelector '[]
forall (typ :: [*]). NodeSelector -> NodeSelector typ
NodeSelector NodeSelector
UT.defaultNode
defR :: RelSelector 'Nothing
defR :: RelSelector 'Nothing
defR = RelSelector -> RelSelector 'Nothing
forall (typ :: Maybe *). RelSelector -> RelSelector typ
RelSelector RelSelector
UT.defaultRel
infixl 3 .&
(.&) :: a -> (a -> b) -> b
a
a .& :: a -> (a -> b) -> b
.& a -> b
f = a -> b
f a
a
{-# INLINE (.&) #-}
infixl 2 !->:
(!->:) :: RelSelector a -> NodeSelector b -> UT.PathPart
RelSelector RelSelector
r !->: :: RelSelector a -> NodeSelector b -> PathPart
!->: NodeSelector NodeSelector
n = RelSelector
r RelSelector -> NodeSelector -> PathPart
UT.:!->: NodeSelector
n
infixl 2 !-:
(!-:) :: RelSelector a -> NodeSelector b -> UT.PathPart
RelSelector RelSelector
r !-: :: RelSelector a -> NodeSelector b -> PathPart
!-: NodeSelector NodeSelector
n = RelSelector
r RelSelector -> NodeSelector -> PathPart
UT.:!-: NodeSelector
n
infixl 1 -:
(-:) :: NodeSelector a -> UT.PathPart -> UT.PathSelector
NodeSelector NodeSelector
ns -: :: NodeSelector a -> PathPart -> PathSelector
-: PathPart
pp = NodeSelector -> PathSelector
UT.P NodeSelector
ns PathSelector -> PathPart -> PathSelector
UT.:-!: PathPart
pp
infixl 1 <-:
(<-:) :: NodeSelector a -> UT.PathPart -> UT.PathSelector
NodeSelector NodeSelector
ns <-: :: NodeSelector a -> PathPart -> PathSelector
<-: PathPart
pp = NodeSelector -> PathSelector
UT.P NodeSelector
ns PathSelector -> PathPart -> PathSelector
UT.:<-!: PathPart
pp
p :: NodeSelector a -> UT.PathSelector
p :: NodeSelector a -> PathSelector
p (NodeSelector NodeSelector
ns) = NodeSelector -> PathSelector
UT.P NodeSelector
ns