Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data HaskAtomType a where
- Int :: HaskAtomType Int
- Integer :: HaskAtomType Integer
- Double :: HaskAtomType Double
- Text :: HaskAtomType Text
- Bool :: HaskAtomType Bool
- Attr :: Atomable a => HaskAtomType a
- toAtomType'' :: Atomable a => HaskAtomType a -> AtomType
- relation :: [TupleExpr] -> RelationalExpr
- relation' :: [AttributeExprBase ()] -> [TupleExpr] -> RelationalExpr
- tuple :: [(AttributeName, AtomExpr)] -> TupleExprBase ()
- rename :: RelationalExpr -> [(AttributeName, AttributeName)] -> RelationalExpr
- (!!) :: RelationalExpr -> AttributeNames -> RelationalExpr
- (><) :: RelationalExpr -> RelationalExpr -> RelationalExpr
- allBut :: AttributeNames -> AttributeNames
- allFrom :: RelationalExpr -> AttributeNames
- as :: AttributeNames -> AttributeName -> (AttributeNames, AttributeName)
- group :: RelationalExpr -> (AttributeNames, AttributeName) -> RelationalExpr
- ungroup :: RelationalExpr -> AttributeName -> RelationalExpr
- (#:) :: RelationalExpr -> ExtendTupleExpr -> RelationalExpr
- (@@) :: AttributeName -> AtomExpr
- f :: Convertible a AtomExpr => FunctionName -> [a] -> AtomExpr
- (#::) :: RelVarName -> [AttributeExpr] -> DatabaseContextExpr
- (#:=) :: RelVarName -> RelationalExpr -> DatabaseContextExpr
- class Boolean a b where
- (&&&) :: a -> b -> RestrictionPredicateExpr
- (|||) :: a -> b -> RestrictionPredicateExpr
- (@~) :: Convertible a RestrictionPredicateExpr => RelationalExpr -> a -> RelationalExpr
- true :: RelationalExpr
- false :: RelationalExpr
- trueP :: RestrictionPredicateExprBase a
- falseP :: RestrictionPredicateExprBase a
- (?=) :: Convertible a AtomExpr => AttributeName -> a -> RestrictionPredicateExpr
- not' :: Convertible a RestrictionPredicateExpr => a -> RestrictionPredicateExpr
- toAtomExpr :: Atom -> AtomExpr
Main> #a Int :: AttributeExpr
Main> #a (Attr @[Int]) :: AttributeExpr
Main> #a [1] :: AtomExpr
data HaskAtomType a where Source #
Int :: HaskAtomType Int | |
Integer :: HaskAtomType Integer | |
Double :: HaskAtomType Double | |
Text :: HaskAtomType Text | |
Bool :: HaskAtomType Bool | |
Attr :: Atomable a => HaskAtomType a |
Instances
(KnownSymbol x, Atomable a) => IsLabel x (HaskAtomType a -> AttributeExpr) Source # | |
Defined in ProjectM36.Shortcuts fromLabel :: HaskAtomType a -> AttributeExpr Source # |
toAtomType'' :: Atomable a => HaskAtomType a -> AtomType Source #
relation :: [TupleExpr] -> RelationalExpr Source #
relation' :: [AttributeExprBase ()] -> [TupleExpr] -> RelationalExpr Source #
tuple :: [(AttributeName, AtomExpr)] -> TupleExprBase () Source #
rename :: RelationalExpr -> [(AttributeName, AttributeName)] -> RelationalExpr Source #
(!!) :: RelationalExpr -> AttributeNames -> RelationalExpr infix 9 Source #
(><) :: RelationalExpr -> RelationalExpr -> RelationalExpr Source #
as :: AttributeNames -> AttributeName -> (AttributeNames, AttributeName) Source #
group :: RelationalExpr -> (AttributeNames, AttributeName) -> RelationalExpr Source #
ungroup :: RelationalExpr -> AttributeName -> RelationalExpr Source #
Main> #a #:= true #: ( #b (f "count" [1,2]))
(#:) :: RelationalExpr -> ExtendTupleExpr -> RelationalExpr infix 8 Source #
(@@) :: AttributeName -> AtomExpr Source #
f :: Convertible a AtomExpr => FunctionName -> [a] -> AtomExpr Source #
(#::) :: RelVarName -> [AttributeExpr] -> DatabaseContextExpr infix 5 Source #
(#:=) :: RelVarName -> RelationalExpr -> DatabaseContextExpr infix 5 Source #
class Boolean a b where Source #
(&&&) :: a -> b -> RestrictionPredicateExpr infixl 6 Source #
(|||) :: a -> b -> RestrictionPredicateExpr infixl 5 Source #
Instances
(Convertible a RestrictionPredicateExpr, Convertible b RestrictionPredicateExpr) => Boolean a b Source # | |
Defined in ProjectM36.Shortcuts (&&&) :: a -> b -> RestrictionPredicateExpr Source # (|||) :: a -> b -> RestrictionPredicateExpr Source # |
(@~) :: Convertible a RestrictionPredicateExpr => RelationalExpr -> a -> RelationalExpr infix 4 Source #
(?=) :: Convertible a AtomExpr => AttributeName -> a -> RestrictionPredicateExpr infix 9 Source #
not' :: Convertible a RestrictionPredicateExpr => a -> RestrictionPredicateExpr Source #
toAtomExpr :: Atom -> AtomExpr Source #