hasqlator-mysql-0.1.0: composable SQL generation
Copyright(c) Kristof Bastiaensen 2020
LicenseBSD-3
Maintainer[email protected]
Stabilityunstable
Portabilityghc
Safe HaskellNone
LanguageHaskell2010

Database.MySQL.Hasqlator

Description

 
Synopsis

Querying

data Query a Source #

Instances

Instances details
ToQueryBuilder (Query a) Source # 
Instance details

Defined in Database.MySQL.Hasqlator

data Command Source #

Instances

Instances details
ToQueryBuilder Command Source # 
Instance details

Defined in Database.MySQL.Hasqlator

mergeSelect :: Query b -> (a -> b -> c) -> Selector a -> Query c Source #

Query Clauses

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 #

as :: QueryBuilder -> QueryBuilder -> QueryBuilder Source #

combinator for aliasing columns.

polymorphic selector

sel :: FromSql a => QueryBuilder -> Selector a Source #

The polymorphic selector. The return type is determined by type inference.

specialised selectors

The following are specialised versions of sel. Using these may make refactoring easier, for example accidently swapping sel "age" and sel "name" would not give a type error, while intSel "age" and textSel "name" most likely would.

intSel :: (Show a, Bounded a, Integral a) => QueryBuilder -> Selector a Source #

an integer field (TINYINT.. BIGINT). Any bounded haskell integer type can be used here , for example Int, Int32, Word32. An Overflow ur Underflow error will be raised if the value doesn't fit the type.

integerSel :: QueryBuilder -> Selector Integer Source #

Un unbounded integer field, either a bounded integer (TINYINT, etc...) or DECIMAL in the database. Will throw a type error if the stored value is actually fractional.

WARNING: this function could potentially create huge integers with DECIMAL, if the exponent is large, even fillup the space and crash your program! Only use this on trusted inputs, or use Scientific instead.

scientificSel :: QueryBuilder -> Selector Scientific Source #

A DECIMAL or NUMERIC field.

localTimeSel :: QueryBuilder -> Selector LocalTime Source #

a DATETIME or a TIMESTAMP field.

timeOfDaySel :: QueryBuilder -> Selector TimeOfDay Source #

A TIME field taken as a specific time.

diffTimeSel :: QueryBuilder -> Selector DiffTime Source #

a TIME field taken as a time duration.

daySel :: QueryBuilder -> Selector Day Source #

A DATE field.

other selectors

rawValues :: [QueryBuilder] -> Selector [MySQLValue] Source #

Read the columns directly as a MySQLValue type without conversion.

rawValues_ :: [QueryBuilder] -> Selector () Source #

Ignore the content of the given columns

Expressions

Insertion

data Insertor a Source #

An Insertor a provides a mapping of parts of values of type a to columns in the database. Insertors can be combined using <>.

Instances

Instances details
Contravariant Insertor Source # 
Instance details

Defined in Database.MySQL.Hasqlator

Methods

contramap :: (a -> b) -> Insertor b -> Insertor a #

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

Semigroup (Insertor a) Source # 
Instance details

Defined in Database.MySQL.Hasqlator

Methods

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

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

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

Monoid (Insertor a) Source # 
Instance details

Defined in Database.MySQL.Hasqlator

Methods

mempty :: Insertor a #

mappend :: Insertor a -> Insertor a -> Insertor a #

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

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

insertData inserts a tuple or other product type into the given fields. It uses generics to match the input to the fields. For example:

insert "Person" (insertData ("name", "age"))
  [Person "Bart Simpson" 10, Person "Lisa Simpson" 8]

skipInsert :: Insertor a Source #

skipInsert is mempty specialized to an Insertor. It can be used to skip fields when using insertData.

into :: ToSql b => (a -> b) -> Text -> Insertor a Source #

into uses the given accessor function to map the part to a field. For example:

insertValues "Person" (fst `into` "name" <> snd `into` "age")
  [("Bart Simpson", 10), ("Lisa Simpson", 8)]

exprInto :: (a -> QueryBuilder) -> Text -> Insertor a Source #

insert an expression

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

A Getter type compatible with the lens library

lensInto :: ToSql b => Getter a b -> Text -> Insertor a Source #

lensInto uses a lens to map the part to a field. For example:

insertValues "Person" (_1 `lensInto` "name" <> _2 `lensInto` "age")
  [("Bart Simpson", 10), ("Lisa Simpson", 8)]

insertOne :: ToSql a => Text -> Insertor a Source #

insert a single value directly

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

Updates

Rendering Queries

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

Executing Queries

executeQuery :: MySQLConn -> Query a -> IO [a] Source #

Execute a Query which returns a resultset. May throw a SQLError exception. See the mysql-haskell package for other exceptions it may throw.

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.