hasqlator-mysql-0.0.2: composable SQL generation
Safe HaskellNone
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

Field Text Text 

newtype Tbl 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.

Constructors

Tbl 

Fields

  • getTableAlias :: forall fieldNull exprNull a. CheckExprNullable (JoinNullable joinType fieldNull) exprNull => Field table database fieldNull a -> Expression exprNull a
     

(@@) :: CheckExprNullable (JoinNullable joinType fieldNull) exprNull => Tbl table database (joinType :: JoinType) -> Field table database fieldNull a -> Expression exprNull a infixl 9 Source #

Create an expression from an aliased table and a field.

data Nullable Source #

Constructors

Nullable 
NotNull 

Querying

data Query database a Source #

Instances

Instances details
Monad (Query database) Source # 
Instance details

Defined in Database.MySQL.Hasqlator.Typed

Methods

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

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

return :: a -> Query database a #

Functor (Query database) Source # 
Instance details

Defined in Database.MySQL.Hasqlator.Typed

Methods

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

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

Applicative (Query database) Source # 
Instance details

Defined in Database.MySQL.Hasqlator.Typed

Methods

pure :: a -> Query database a #

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

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

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

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

ToQueryBuilder (Query database (Selector a)) Source # 
Instance details

Defined in Database.MySQL.Hasqlator.Typed

Methods

toQueryBuilder :: Query database (Selector a) -> QueryBuilder Source #

Selectors

data Selector a Source #

Selectors contain the target fields or expressions in a SQL SELECT statement, and perform the conversion to haskell. Selectors are instances of Applicative, so they can return the desired haskell type.

Instances

Instances details
Functor Selector Source # 
Instance details

Defined in Database.MySQL.Hasqlator

Methods

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

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

Applicative Selector Source # 
Instance details

Defined in Database.MySQL.Hasqlator

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 #

FromSql a => IsString (Selector a) Source # 
Instance details

Defined in Database.MySQL.Hasqlator

Methods

fromString :: String -> Selector a #

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

Defined in Database.MySQL.Hasqlator

Methods

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

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

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

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

Defined in Database.MySQL.Hasqlator

Methods

mempty :: Selector a #

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

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

ToQueryBuilder (Query database (Selector a)) Source # 
Instance details

Defined in Database.MySQL.Hasqlator.Typed

Methods

toQueryBuilder :: Query database (Selector a) -> QueryBuilder Source #

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

Expressions

data Expression (nullable :: Nullable) a Source #

Instances

Instances details
(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 #

(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 #

IsString (Expression nullable Text) Source # 
Instance details

Defined in Database.MySQL.Hasqlator.Typed

Methods

fromString :: String -> 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 #

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 #

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

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 #

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

Clauses

from :: Table table database -> Query database (Tbl table database 'InnerJoined) Source #

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

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

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

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

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

where_ :: Expression nullable Bool -> Query database () Source #

groupBy_ :: [SomeExpression] -> Query database () Source #

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

orderBy :: [QueryOrdering] -> Query database () Source #

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

limitOffset :: Int -> Int -> Query 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 -> b) -> Insertor table database b -> Insertor table database a #

(>$) :: b -> Insertor table database b -> 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 #

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 #

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

insertSelect :: Table table database -> Query 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 :: Insertable fieldNull fieldType b => (a -> b) -> Field table database fieldNull fieldType -> Insertor table database a Source #

lensInto :: Insertable fieldNull fieldType b => Getter a b -> Field table database fieldNull fieldType -> Insertor table database a Source #

insertOne :: Insertable fieldNull fieldType a => Field table database fieldNull fieldType -> Insertor table database a Source #

exprInto :: CheckExprNullable exprNullable fieldNullable => Expression exprNullable a -> Field table database fieldNullable a -> Into database table Source #

data Into database (table :: Symbol) 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 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 Int8 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 Integer Source # 
Instance details

Defined in Database.MySQL.Hasqlator

ToSql Word8 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 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 Value Source # 
Instance details

Defined in Database.MySQL.Hasqlator

ToSql TimeOfDay Source # 
Instance details

Defined in Database.MySQL.Hasqlator

ToSql LocalTime Source # 
Instance details

Defined in Database.MySQL.Hasqlator

ToSql DiffTime Source # 
Instance details

Defined in Database.MySQL.Hasqlator

ToSql Day 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 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 Int8 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 Integer Source # 
Instance details

Defined in Database.MySQL.Hasqlator

FromSql Word8 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 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 Value Source # 
Instance details

Defined in Database.MySQL.Hasqlator

FromSql TimeOfDay Source # 
Instance details

Defined in Database.MySQL.Hasqlator

FromSql LocalTime Source # 
Instance details

Defined in Database.MySQL.Hasqlator

FromSql DiffTime Source # 
Instance details

Defined in Database.MySQL.Hasqlator

FromSql Day 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 #