hasqlator-mysql-0.2.1: composable SQL generation
Safe HaskellSafe-Inferred
LanguageHaskell2010

Database.MySQL.Hasqlator.Typed

Synopsis

Database Types

data Table (table :: Symbol) database Source #

Constructors

Table (Maybe Text) Text 

data Field (table :: Symbol) database (nullable :: Nullable) a Source #

Constructors

AllFields 
Field Text Text 

newtype Alias table database (joinType :: JoinType) Source #

An table alias that can be used inside the Query. The function inside the newtype can also be applied directly to create an expression from a field. For constructing records, applicativeDo is the recommended way. However note that this may fail due to a bug in ghc, that breaks the polymorphism. In that case as a workaround you should use the Alias newtype directly and use the @@ operator to create an expression instead

Constructors

Alias 

Fields

(@@) :: Alias table database (joinType :: JoinType) -> Field table database fieldNull a -> Expression (JoinNullable joinType fieldNull) a infixl 9 Source #

Create an expression from an aliased table and a field.

data Nullable Source #

Constructors

Nullable 
NotNull 

quotedTableName :: Table table database -> Text Source #

quotedFieldName :: Field table database nullable a -> Text Source #

Querying

data QueryClauses database a Source #

Instances

Instances details
Applicative (QueryClauses database) Source # 
Instance details

Defined in Database.MySQL.Hasqlator.Typed

Methods

pure :: a -> QueryClauses database a #

(<*>) :: QueryClauses database (a -> b) -> QueryClauses database a -> QueryClauses database b #

liftA2 :: (a -> b -> c) -> QueryClauses database a -> QueryClauses database b -> QueryClauses database c #

(*>) :: QueryClauses database a -> QueryClauses database b -> QueryClauses database b #

(<*) :: QueryClauses database a -> QueryClauses database b -> QueryClauses database a #

Functor (QueryClauses database) Source # 
Instance details

Defined in Database.MySQL.Hasqlator.Typed

Methods

fmap :: (a -> b) -> QueryClauses database a -> QueryClauses database b #

(<$) :: a -> QueryClauses database b -> QueryClauses database a #

Monad (QueryClauses database) Source # 
Instance details

Defined in Database.MySQL.Hasqlator.Typed

Methods

(>>=) :: QueryClauses database a -> (a -> QueryClauses database b) -> QueryClauses database b #

(>>) :: QueryClauses database a -> QueryClauses database b -> QueryClauses database b #

return :: a -> QueryClauses database a #

data Query database a Source #

mkQuery :: QueryClauses database a -> Query database a Source #

untypeQuery :: Query database (Selector a) -> Query a Source #

executeQuery :: MySQLConn -> Query database (Selector a) -> IO [a] Source #

unionAll :: Query database a -> Query database a -> Query database a Source #

unionDistinct :: Query database a -> Query database a -> Query database a Source #

Selectors

data Selector a Source #

Instances

Instances details
Applicative Selector Source # 
Instance details

Defined in Database.MySQL.Hasqlator.Typed

Methods

pure :: a -> Selector a #

(<*>) :: Selector (a -> b) -> Selector a -> Selector b #

liftA2 :: (a -> b -> c) -> Selector a -> Selector b -> Selector c #

(*>) :: Selector a -> Selector b -> Selector b #

(<*) :: Selector a -> Selector b -> Selector a #

Functor Selector Source # 
Instance details

Defined in Database.MySQL.Hasqlator.Typed

Methods

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

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

Monoid a => Monoid (Selector a) Source # 
Instance details

Defined in Database.MySQL.Hasqlator.Typed

Methods

mempty :: Selector a #

mappend :: Selector a -> Selector a -> Selector a #

mconcat :: [Selector a] -> Selector a #

Semigroup a => Semigroup (Selector a) Source # 
Instance details

Defined in Database.MySQL.Hasqlator.Typed

Methods

(<>) :: Selector a -> Selector a -> Selector a #

sconcat :: NonEmpty (Selector a) -> Selector a #

stimes :: Integral b => b -> Selector a -> Selector a #

sel :: FromSql a => Expression 'NotNull a -> Selector a Source #

make a selector from a column

selMaybe :: FromSql (Maybe a) => Expression 'Nullable a -> Selector (Maybe a) Source #

make a selector from a column that can be null

forUpdate :: [Table table database] -> WaitLock -> QueryClauses database () Source #

forShare :: [Table table database] -> WaitLock -> QueryClauses database () Source #

Expressions

data Expression (nullable :: Nullable) a Source #

Instances

Instances details
IsString (Expression nullable Text) Source # 
Instance details

Defined in Database.MySQL.Hasqlator.Typed

Methods

fromString :: String -> Expression nullable Text #

Monoid (Expression nullable Text) Source # 
Instance details

Defined in Database.MySQL.Hasqlator.Typed

Methods

mempty :: Expression nullable Text #

mappend :: Expression nullable Text -> Expression nullable Text -> Expression nullable Text #

mconcat :: [Expression nullable Text] -> Expression nullable Text #

Semigroup (Expression nullable Text) Source # 
Instance details

Defined in Database.MySQL.Hasqlator.Typed

Methods

(<>) :: Expression nullable Text -> Expression nullable Text -> Expression nullable Text #

sconcat :: NonEmpty (Expression nullable Text) -> Expression nullable Text #

stimes :: Integral b => b -> Expression nullable Text -> Expression nullable Text #

(Num n, ToSql n) => Num (Expression nullable n) Source # 
Instance details

Defined in Database.MySQL.Hasqlator.Typed

Methods

(+) :: Expression nullable n -> Expression nullable n -> Expression nullable n #

(-) :: Expression nullable n -> Expression nullable n -> Expression nullable n #

(*) :: Expression nullable n -> Expression nullable n -> Expression nullable n #

negate :: Expression nullable n -> Expression nullable n #

abs :: Expression nullable n -> Expression nullable n #

signum :: Expression nullable n -> Expression nullable n #

fromInteger :: Integer -> Expression nullable n #

(Fractional n, ToSql n) => Fractional (Expression nullable n) Source # 
Instance details

Defined in Database.MySQL.Hasqlator.Typed

Methods

(/) :: Expression nullable n -> Expression nullable n -> Expression nullable n #

recip :: Expression nullable n -> Expression nullable n #

fromRational :: Rational -> Expression nullable n #

data SomeExpression Source #

An expression of any type

someExpr :: Expression nullable a -> SomeExpression Source #

Remove types of an expression

type Operator a b c = forall nullable. Expression nullable a -> Expression nullable b -> Expression nullable c Source #

arg :: ToSql a => a -> Expression nullable a Source #

pass an argument

argMaybe :: ToSql a => Maybe a -> Expression 'Nullable a Source #

pass an argument which can be null

nullable :: Expression nullable a -> Expression 'Nullable a Source #

make expression nullable

notNull :: Expression 'NotNull a -> Expression 'NotNull a Source #

ensure expression is not null

orNull :: Expression nullable a -> (Expression 'NotNull a -> Expression 'NotNull Bool) -> Expression 'NotNull Bool Source #

Return a true expression if the given expression is NULL (using the IS NULL sql test), or pass the expression (coerced to 'NotNull) to the given test.

unlessNull :: Expression nullable a -> (Expression 'NotNull a -> Expression 'NotNull Bool) -> Expression 'NotNull Bool Source #

Perform test if given expression is not NULL

cast :: Castable a => Expression nullable b -> Expression nullable a Source #

Safe cast. This uses the SQL CAST function to convert safely from one type to another.

unsafeCast :: Expression nullable a -> Expression nullable b Source #

Cast the return type of an expression to any other type, without changing the query. Since this library adds static typing on top of SQL, you may sometimes want to use this to get back the lenient behaviour of SQL. This opens up more possibilies for runtime errors, so it's up to the programmer to ensure type correctness.

op :: (QueryBuilder -> QueryBuilder -> QueryBuilder) -> Operator a b c Source #

create an operator

fun1 :: (QueryBuilder -> QueryBuilder) -> Expression nullable a -> Expression nullable b Source #

fun2 :: (QueryBuilder -> QueryBuilder -> QueryBuilder) -> Expression nullable a -> Expression nullable b -> Expression nullable c Source #

fun3 :: (QueryBuilder -> QueryBuilder -> QueryBuilder -> QueryBuilder) -> Expression nullable a -> Expression nullable b -> Expression nullable c -> Expression nullable d Source #

(=.) :: ToSql a => Operator a a Bool infix 4 Source #

(/=.) :: ToSql a => Operator a a Bool infix 4 Source #

(>.) :: ToSql a => Operator a a Bool infix 4 Source #

(<.) :: ToSql a => Operator a a Bool infix 4 Source #

(>=.) :: ToSql a => Operator a a Bool infix 4 Source #

(<=.) :: ToSql a => Operator a a Bool infix 4 Source #

substr :: Expression nullable Text -> Expression nullable Int -> Expression nullable Int -> Expression nullable Text Source #

in_ :: Expression nullable a -> [Expression nullable a] -> Expression nullable Bool Source #

notIn_ :: Expression nullable a -> [Expression nullable a] -> Expression nullable Bool Source #

and_ :: Foldable f => f (Expression nullable Bool) -> Expression nullable Bool Source #

or_ :: Foldable f => f (Expression nullable Bool) -> Expression nullable Bool Source #

newtype All_ nullable Source #

Constructors

All_ 

Fields

Instances

Instances details
Monoid (All_ nullable) Source # 
Instance details

Defined in Database.MySQL.Hasqlator.Typed

Methods

mempty :: All_ nullable #

mappend :: All_ nullable -> All_ nullable -> All_ nullable #

mconcat :: [All_ nullable] -> All_ nullable #

Semigroup (All_ nullable) Source # 
Instance details

Defined in Database.MySQL.Hasqlator.Typed

Methods

(<>) :: All_ nullable -> All_ nullable -> All_ nullable #

sconcat :: NonEmpty (All_ nullable) -> All_ nullable #

stimes :: Integral b => b -> All_ nullable -> All_ nullable #

newtype Any_ nullable Source #

Constructors

Any_ 

Fields

Instances

Instances details
Monoid (Any_ nullable) Source # 
Instance details

Defined in Database.MySQL.Hasqlator.Typed

Methods

mempty :: Any_ nullable #

mappend :: Any_ nullable -> Any_ nullable -> Any_ nullable #

mconcat :: [Any_ nullable] -> Any_ nullable #

Semigroup (Any_ nullable) Source # 
Instance details

Defined in Database.MySQL.Hasqlator.Typed

Methods

(<>) :: Any_ nullable -> Any_ nullable -> Any_ nullable #

sconcat :: NonEmpty (Any_ nullable) -> Any_ nullable #

stimes :: Integral b => b -> Any_ nullable -> Any_ nullable #

all_ :: Foldable f => (a -> Expression nullable Bool) -> f a -> Expression nullable Bool Source #

any_ :: Foldable f => (a -> Expression nullable Bool) -> f a -> Expression nullable Bool Source #

Clauses

from :: Table table database -> QueryClauses database (Alias table database 'InnerJoined) Source #

fromSubQuery :: (Generic inExprs, Generic outExprs, SubQueryExpr 'LeftJoined (Rep inExprs ()) (Rep outExprs ())) => Query database inExprs -> QueryClauses database outExprs Source #

innerJoin :: Table table database -> (Alias table database 'InnerJoined -> Expression nullable Bool) -> QueryClauses database (Alias table database 'InnerJoined) Source #

leftJoin :: Table table database -> (Alias table database 'LeftJoined -> Expression nullable Bool) -> QueryClauses database (Alias table database 'LeftJoined) Source #

joinSubQuery :: (Generic inExprs, Generic outExprs, SubQueryExpr 'InnerJoined (Rep inExprs ()) (Rep outExprs ())) => Query database inExprs -> (outExprs -> Expression nullable Bool) -> QueryClauses database outExprs Source #

leftJoinSubQuery :: (Generic inExprs, Generic outExprs, SubQueryExpr 'LeftJoined (Rep inExprs ()) (Rep outExprs ())) => Query database inExprs -> (outExprs -> Expression nullable Bool) -> QueryClauses database outExprs Source #

having :: Expression nullable Bool -> QueryClauses database () Source #

limit :: Int -> QueryClauses database () Source #

limitOffset :: Int -> Int -> QueryClauses database () Source #

Insertion

data Insertor (table :: Symbol) database a Source #

Instances

Instances details
Contravariant (Insertor table database) Source # 
Instance details

Defined in Database.MySQL.Hasqlator.Typed

Methods

contramap :: (a' -> a) -> Insertor table database a -> Insertor table database a' #

(>$) :: b -> Insertor table database b -> Insertor table database a #

Monoid (Insertor table database a) Source # 
Instance details

Defined in Database.MySQL.Hasqlator.Typed

Methods

mempty :: Insertor table database a #

mappend :: Insertor table database a -> Insertor table database a -> Insertor table database a #

mconcat :: [Insertor table database a] -> Insertor table database a #

Semigroup (Insertor table database a) Source # 
Instance details

Defined in Database.MySQL.Hasqlator.Typed

Methods

(<>) :: Insertor table database a -> Insertor table database a -> Insertor table database a #

sconcat :: NonEmpty (Insertor table database a) -> Insertor table database a #

stimes :: Integral b => b -> Insertor table database a -> Insertor table database a #

insertValues :: Table table database -> Insertor table database a -> [a] -> Command Source #

insertUpdateValues :: Table table database -> Insertor table database a -> (Alias table database 'InnerJoined -> Alias table database 'InnerJoined -> [Updator table database]) -> [a] -> Command Source #

insertSelect :: Table table database -> QueryClauses database [Into database table] -> Command Source #

insertData :: (Generic a, Generic b, InsertGeneric tbl db (Rep a ()) (Rep b ())) => a -> Insertor tbl db b Source #

into :: (a -> Expression nullable b) -> Field table database nullable b -> Insertor table database a Source #

lensInto :: ToSql b => Getter a b -> Field table database 'NotNull b -> Insertor table database a Source #

maybeLensInto :: ToSql b => Getter a (Maybe b) -> Field table database 'Nullable b -> Insertor table database a Source #

opticInto :: (ToSql b, Is k A_Getter) => Optic' k is a b -> Field table database 'NotNull b -> Insertor table database a Source #

maybeOpticInto :: (ToSql b, Is k A_Getter) => Optic' k is a (Maybe b) -> Field table database 'Nullable b -> Insertor table database a Source #

insertOne :: ToSql a => Field table database 'NotNull fieldType -> Insertor table database a Source #

exprInto :: Expression nullable a -> Field table database nullable a -> Into database table Source #

data Into database (table :: Symbol) Source #

insertWithout :: Field tables database nullable b -> Insertor table database a -> Insertor table database a Source #

updateWithout :: Field table database nullable a -> [Updator table database] -> [Updator table database] Source #

Deletion

delete :: QueryClauses database (Alias table database 'InnerJoined) -> Command Source #

Update

data Updator table database Source #

Constructors

forall nullable a. (Field table database nullable a) := (Expression nullable a) infix 0 

update :: Table table database -> (Alias table database 'InnerJoined -> QueryClauses database [Updator table database]) -> Command Source #

imported from Database.MySQL.Hasqlator

type Getter s a = (a -> Const a a) -> s -> Const a s Source #

A Getter type compatible with the lens library

class ToSql a Source #

Minimal complete definition

toSqlValue

Instances

Instances details
ToSql Value Source # 
Instance details

Defined in Database.MySQL.Hasqlator

ToSql Int16 Source # 
Instance details

Defined in Database.MySQL.Hasqlator

ToSql Int32 Source # 
Instance details

Defined in Database.MySQL.Hasqlator

ToSql Int64 Source # 
Instance details

Defined in Database.MySQL.Hasqlator

ToSql Int8 Source # 
Instance details

Defined in Database.MySQL.Hasqlator

ToSql Word16 Source # 
Instance details

Defined in Database.MySQL.Hasqlator

ToSql Word32 Source # 
Instance details

Defined in Database.MySQL.Hasqlator

ToSql Word64 Source # 
Instance details

Defined in Database.MySQL.Hasqlator

ToSql Word8 Source # 
Instance details

Defined in Database.MySQL.Hasqlator

ToSql ByteString Source # 
Instance details

Defined in Database.MySQL.Hasqlator

ToSql Scientific Source # 
Instance details

Defined in Database.MySQL.Hasqlator

ToSql Text Source # 
Instance details

Defined in Database.MySQL.Hasqlator

ToSql Day Source # 
Instance details

Defined in Database.MySQL.Hasqlator

ToSql DiffTime Source # 
Instance details

Defined in Database.MySQL.Hasqlator

ToSql LocalTime Source # 
Instance details

Defined in Database.MySQL.Hasqlator

ToSql TimeOfDay Source # 
Instance details

Defined in Database.MySQL.Hasqlator

ToSql Integer Source # 
Instance details

Defined in Database.MySQL.Hasqlator

ToSql Bool Source # 
Instance details

Defined in Database.MySQL.Hasqlator

ToSql Double Source # 
Instance details

Defined in Database.MySQL.Hasqlator

ToSql Float Source # 
Instance details

Defined in Database.MySQL.Hasqlator

ToSql Int Source # 
Instance details

Defined in Database.MySQL.Hasqlator

ToSql a => ToSql (Maybe a) Source # 
Instance details

Defined in Database.MySQL.Hasqlator

Methods

toSqlValue :: Maybe a -> MySQLValue

class FromSql a Source #

Minimal complete definition

fromSql

Instances

Instances details
FromSql Value Source # 
Instance details

Defined in Database.MySQL.Hasqlator

FromSql Int16 Source # 
Instance details

Defined in Database.MySQL.Hasqlator

FromSql Int32 Source # 
Instance details

Defined in Database.MySQL.Hasqlator

FromSql Int64 Source # 
Instance details

Defined in Database.MySQL.Hasqlator

FromSql Int8 Source # 
Instance details

Defined in Database.MySQL.Hasqlator

FromSql Word16 Source # 
Instance details

Defined in Database.MySQL.Hasqlator

FromSql Word32 Source # 
Instance details

Defined in Database.MySQL.Hasqlator

FromSql Word64 Source # 
Instance details

Defined in Database.MySQL.Hasqlator

FromSql Word8 Source # 
Instance details

Defined in Database.MySQL.Hasqlator

FromSql ByteString Source # 
Instance details

Defined in Database.MySQL.Hasqlator

FromSql Scientific Source # 
Instance details

Defined in Database.MySQL.Hasqlator

FromSql Text Source # 
Instance details

Defined in Database.MySQL.Hasqlator

FromSql Day Source # 
Instance details

Defined in Database.MySQL.Hasqlator

FromSql DiffTime Source # 
Instance details

Defined in Database.MySQL.Hasqlator

FromSql LocalTime Source # 
Instance details

Defined in Database.MySQL.Hasqlator

FromSql TimeOfDay Source # 
Instance details

Defined in Database.MySQL.Hasqlator

FromSql Integer Source # 
Instance details

Defined in Database.MySQL.Hasqlator

FromSql Bool Source # 
Instance details

Defined in Database.MySQL.Hasqlator

FromSql Double Source # 
Instance details

Defined in Database.MySQL.Hasqlator

FromSql Float Source # 
Instance details

Defined in Database.MySQL.Hasqlator

FromSql Int Source # 
Instance details

Defined in Database.MySQL.Hasqlator

FromSql a => FromSql (Maybe a) Source # 
Instance details

Defined in Database.MySQL.Hasqlator

subQueryExpr :: Query database (Expression nullable a) -> Expression nullable a Source #

executeCommand :: MySQLConn -> Command -> IO OK Source #

Execute a Command which doesn't return a result-set. May throw a SQLError exception. See the mysql-haskell package for other exceptions it may throw.

data Command Source #

A command is a database query that doesn't return a value, but is executed for the side effect (inserting, updating, deleteing).

Instances

Instances details
ToQueryBuilder Command Source # 
Instance details

Defined in Database.MySQL.Hasqlator