Safe Haskell | None |
---|---|
Language | Haskell2010 |
- genJsonQuery :: TypedQuery Query -> Q Exp
- genTypedQuery :: TypedQuery Query -> Q Exp
- genUncurry :: RunDB q => q -> Int -> Q Exp
- data RunDB q => TypedQuery q :: * -> * = TypedQuery {
- fromTypedQuery :: q
- namesTypedQuery :: [Text]
- typesTypedQuery :: [TypeAction]
- typesTypedInput :: [TypeAction]
- typesTypedInputSource :: [TypeAction]
- data Query :: *
Documentation
genJsonQuery :: TypedQuery Query -> Q Exp Source
genTypedQuery :: TypedQuery Query -> Q Exp Source
genUncurry :: RunDB q => q -> Int -> Q Exp
data RunDB q => TypedQuery q :: * -> *
TypedQuery | |
|
(Eq q, RunDB q) => Eq (TypedQuery q) | |
(Ord q, RunDB q) => Ord (TypedQuery q) | |
(RunDB q, IsString q, Monoid q) => Read (TypedQuery q) | |
(Show q, RunDB q) => Show (TypedQuery q) | |
(RunDB q, IsString q, Monoid q) => IsString (TypedQuery q) | |
(RunDB q, Monoid q) => Monoid (TypedQuery q) | |
(RunDB q, Lift q) => Lift (TypedQuery q) | |
Typeable (* -> *) TypedQuery |
data Query :: *
A query string. This type is intended to make it difficult to construct a SQL query by concatenating string fragments, as that is an extremely common way to accidentally introduce SQL injection vulnerabilities into an application.
This type is an instance of IsString
, so the easiest way to
construct a query is to enable the OverloadedStrings
language
extension and then simply write the query in double quotes.
{-# LANGUAGE OverloadedStrings #-} import Database.MySQL.Simple q :: Query q = "select ?"
The underlying type is a ByteString
, and literal Haskell strings
that contain Unicode characters will be correctly transformed to
UTF-8.