Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Synopsis
- insertStmtFor :: forall a. Entity a => String
- insertReturningStmtFor :: forall a. Entity a => String
- updateStmtFor :: forall a. Entity a => String
- selectFromStmt :: forall a. Entity a => WhereClauseExpr -> String
- deleteStmtFor :: forall a. Entity a => String
- createTableStmtFor :: forall a. Entity a => Database -> String
- dropTableStmtFor :: forall a. Entity a => String
- columnTypeFor :: forall a. Entity a => Database -> String -> String
- data WhereClauseExpr
- data Field
- field :: String -> Field
- whereClauseValues :: WhereClauseExpr -> [SqlValue]
- (&&.) :: WhereClauseExpr -> WhereClauseExpr -> WhereClauseExpr
- (||.) :: WhereClauseExpr -> WhereClauseExpr -> WhereClauseExpr
- (=.) :: Convertible b SqlValue => Field -> b -> WhereClauseExpr
- (>.) :: Convertible b SqlValue => Field -> b -> WhereClauseExpr
- (<.) :: Convertible b SqlValue => Field -> b -> WhereClauseExpr
- (>=.) :: Convertible b SqlValue => Field -> b -> WhereClauseExpr
- (<=.) :: Convertible b SqlValue => Field -> b -> WhereClauseExpr
- (<>.) :: Convertible b SqlValue => Field -> b -> WhereClauseExpr
- like :: Convertible b SqlValue => Field -> b -> WhereClauseExpr
- between :: (Convertible a1 SqlValue, Convertible a2 SqlValue) => Field -> (a1, a2) -> WhereClauseExpr
- in' :: Convertible b SqlValue => Field -> [b] -> WhereClauseExpr
- isNull :: Field -> WhereClauseExpr
- not' :: WhereClauseExpr -> WhereClauseExpr
- sqlFun :: String -> Field -> Field
- allEntries :: WhereClauseExpr
- byId :: Convertible a SqlValue => a -> WhereClauseExpr
- byIdColumn :: WhereClauseExpr
- orderBy :: WhereClauseExpr -> NonEmpty (Field, SortOrder) -> WhereClauseExpr
- data SortOrder
- limit :: WhereClauseExpr -> Int -> WhereClauseExpr
- limitOffset :: WhereClauseExpr -> (Int, Int) -> WhereClauseExpr
- data NonEmpty a = a :| [a]
- data Database
Documentation
insertStmtFor :: forall a. Entity a => String Source #
This module defines some basic SQL statements for Record Data Types that are instances of Entity
.
The SQL statements are generated using Haskell generics to provide compile time reflection capabilities.
A function that returns an SQL insert statement for an entity. Type a
must be an instance of Data.
The function will use the field names of the data type to generate the column names in the insert statement.
The values of the fields will be used as the values in the insert statement.
Output example: INSERT INTO Person (id, name, age, address) VALUES (123456, Alice, 25, "123 Main St");
insertReturningStmtFor :: forall a. Entity a => String Source #
updateStmtFor :: forall a. Entity a => String Source #
A function that returns an SQL update statement for an entity. Type a
must be an instance of Entity.
selectFromStmt :: forall a. Entity a => WhereClauseExpr -> String Source #
A function that returns an SQL select statement for an entity. Type a
must be an instance of Entity.
The function takes a where clause expression as parameter. This expression is used to filter the result set.
deleteStmtFor :: forall a. Entity a => String Source #
dropTableStmtFor :: forall a. Entity a => String Source #
columnTypeFor :: forall a. Entity a => Database -> String -> String Source #
A function that returns the column type for a field of an entity. TODO: Support other databases than just SQLite and Postgres.
data WhereClauseExpr Source #
whereClauseValues :: WhereClauseExpr -> [SqlValue] Source #
(&&.) :: WhereClauseExpr -> WhereClauseExpr -> WhereClauseExpr infixl 3 Source #
(||.) :: WhereClauseExpr -> WhereClauseExpr -> WhereClauseExpr infixl 2 Source #
(=.) :: Convertible b SqlValue => Field -> b -> WhereClauseExpr infixl 4 Source #
(>.) :: Convertible b SqlValue => Field -> b -> WhereClauseExpr infixl 4 Source #
(<.) :: Convertible b SqlValue => Field -> b -> WhereClauseExpr infixl 4 Source #
(>=.) :: Convertible b SqlValue => Field -> b -> WhereClauseExpr infixl 4 Source #
(<=.) :: Convertible b SqlValue => Field -> b -> WhereClauseExpr infixl 4 Source #
(<>.) :: Convertible b SqlValue => Field -> b -> WhereClauseExpr infixl 4 Source #
like :: Convertible b SqlValue => Field -> b -> WhereClauseExpr infixl 4 Source #
between :: (Convertible a1 SqlValue, Convertible a2 SqlValue) => Field -> (a1, a2) -> WhereClauseExpr infixl 4 Source #
in' :: Convertible b SqlValue => Field -> [b] -> WhereClauseExpr infixl 4 Source #
isNull :: Field -> WhereClauseExpr Source #
byId :: Convertible a SqlValue => a -> WhereClauseExpr Source #
orderBy :: WhereClauseExpr -> NonEmpty (Field, SortOrder) -> WhereClauseExpr infixl 1 Source #
limit :: WhereClauseExpr -> Int -> WhereClauseExpr Source #
limitOffset :: WhereClauseExpr -> (Int, Int) -> WhereClauseExpr Source #
Non-empty (and non-strict) list type.
Since: base-4.9.0.0
a :| [a] infixr 5 |
Instances
Foldable NonEmpty | Since: base-4.9.0.0 |
Defined in Data.Foldable fold :: Monoid m => NonEmpty m -> m # foldMap :: Monoid m => (a -> m) -> NonEmpty a -> m # foldMap' :: Monoid m => (a -> m) -> NonEmpty a -> m # foldr :: (a -> b -> b) -> b -> NonEmpty a -> b # foldr' :: (a -> b -> b) -> b -> NonEmpty a -> b # foldl :: (b -> a -> b) -> b -> NonEmpty a -> b # foldl' :: (b -> a -> b) -> b -> NonEmpty a -> b # foldr1 :: (a -> a -> a) -> NonEmpty a -> a # foldl1 :: (a -> a -> a) -> NonEmpty a -> a # elem :: Eq a => a -> NonEmpty a -> Bool # maximum :: Ord a => NonEmpty a -> a # minimum :: Ord a => NonEmpty a -> a # | |
Traversable NonEmpty | Since: base-4.9.0.0 |
Applicative NonEmpty | Since: base-4.9.0.0 |
Functor NonEmpty | Since: base-4.9.0.0 |
Monad NonEmpty | Since: base-4.9.0.0 |
Hashable1 NonEmpty | Since: hashable-1.3.1.0 |
Defined in Data.Hashable.Class | |
Generic1 NonEmpty | |
Semigroup (NonEmpty a) | Since: base-4.9.0.0 |
IsList (NonEmpty a) | Since: base-4.9.0.0 |
Generic (NonEmpty a) | |
Read a => Read (NonEmpty a) | Since: base-4.11.0.0 |
Show a => Show (NonEmpty a) | Since: base-4.11.0.0 |
Eq a => Eq (NonEmpty a) | Since: base-4.9.0.0 |
Ord a => Ord (NonEmpty a) | Since: base-4.9.0.0 |
Hashable a => Hashable (NonEmpty a) | |
Defined in Data.Hashable.Class | |
type Rep1 NonEmpty | Since: base-4.6.0.0 |
Defined in GHC.Generics type Rep1 NonEmpty = D1 ('MetaData "NonEmpty" "GHC.Base" "base" 'False) (C1 ('MetaCons ":|" ('InfixI 'LeftAssociative 9) 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1 :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 []))) | |
type Item (NonEmpty a) | |
type Rep (NonEmpty a) | Since: base-4.6.0.0 |
Defined in GHC.Generics type Rep (NonEmpty a) = D1 ('MetaData "NonEmpty" "GHC.Base" "base" 'False) (C1 ('MetaCons ":|" ('InfixI 'LeftAssociative 9) 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [a]))) |