Safe Haskell | None |
---|---|
Language | Haskell2010 |
sqlExp :: QuasiQuoter Source #
Maybe the main feature of all library. Quasiquoter which builds
SqlBuilder
from string query. Removes line comments and block
comments (even nested) and sequences of spaces. Correctly works
handles string literals and quoted identifiers. Here is examples of usage
>>>
let name = "name"
>>>
let val = "some 'value'"
>>>
run [sqlExp|SELECT * FROM tbl WHERE ^{Identifier name} = #{val}|]
"SELECT * FROM tbl WHERE \"name\" = 'some ''value'''"
And more comples example:
>>>
let name = Just "name"
>>>
let size = Just 10
>>>
let active = Nothing :: Maybe Bool
>>>
let condlist = catMaybes [ fmap (\a -> [sqlExp|name = #{a}|]) name, fmap (\a -> [sqlExp|size = #{a}|]) size, fmap (\a -> [sqlExp|active = #{a}|]) active]
>>>
let cond = if L.null condlist then mempty else [sqlExp| WHERE ^{mconcat $ L.intersperse " AND " $ condlist} |]
>>>
run [sqlExp|SELECT * FROM tbl ^{cond} -- line comment|]
"SELECT * FROM tbl WHERE name = 'name' AND size = 10 "
Types
Internal type. Result of parsing sql string
RLit Text | Part of raw sql |
RComment Text | Sql comment |
RSpaces Int | Sequence of spaces |
RInt FieldOption Text | String with haskell expression inside #{..} or #?{..} |
RPaste Text | String with haskell expression inside ^{..} |
Parser
ropeParser :: Parser [Rope] Source #
squashRope :: [Rope] -> [Rope] Source #
Removes sequential occurencies of RLit
constructors. Also
removes commentaries and squash sequences of spaces to single space
symbol
Template haskell
:: String | |
-> Q Exp | Expression of type |
Build expression of type SqlBuilder
from SQL query with interpolation
:: String | file path |
-> Q Exp | Expression of type |
Embed sql template and perform interpolation
let name = "name" foo = "bar" query = $(sqlExpEmbed "sqlfoobar.sql") -- usingfoo
andbar
inside
sqlExpFile :: String -> Q Exp Source #
Just like sqlExpEmbed
but uses pattern instead of file
name. So, code
let query = $(sqlExpFile "foo/bar")
is just the same as
let query = $(sqlExpEmbed "sqlfoobar.sql")
This function inspired by Yesod's widgetFile