Copyright | (c) 2011 MailRank, Inc. (c) 2011-2012 Leon P Smith (c) 2012-2013 Janne Hellsten |
---|---|
License | BSD3 |
Maintainer | Janne Hellsten <jjhellst@gmail.com> |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
- newtype Query = Query {}
- newtype Connection = Connection {}
- class ToRow a where
- class FromRow a where
- newtype Only a = Only {
- fromOnly :: a
- data h :. t = h :. t
- data SQLData :: *
- = SQLInteger !Int64
- | SQLFloat !Double
- | SQLText !Text
- | SQLBlob !ByteString
- | SQLNull
- data Statement
- newtype ColumnIndex = ColumnIndex ColumnIndex
- open :: String -> IO Connection
- close :: Connection -> IO ()
- withConnection :: String -> (Connection -> IO a) -> IO a
- setTrace :: Connection -> Maybe (Text -> IO ()) -> IO ()
- query :: (ToRow q, FromRow r) => Connection -> Query -> q -> IO [r]
- query_ :: FromRow r => Connection -> Query -> IO [r]
- lastInsertRowId :: Connection -> IO Int64
- fold :: (FromRow row, ToRow params) => Connection -> Query -> params -> a -> (a -> row -> IO a) -> IO a
- fold_ :: FromRow row => Connection -> Query -> a -> (a -> row -> IO a) -> IO a
- execute :: ToRow q => Connection -> Query -> q -> IO ()
- execute_ :: Connection -> Query -> IO ()
- field :: FromField a => RowParser a
- openStatement :: Connection -> Query -> IO Statement
- closeStatement :: Statement -> IO ()
- withStatement :: Connection -> Query -> (Statement -> IO a) -> IO a
- bind :: ToRow params => Statement -> params -> IO ()
- reset :: Statement -> IO ()
- columnName :: Statement -> ColumnIndex -> IO Text
- withBind :: ToRow params => Statement -> params -> IO a -> IO a
- nextRow :: FromRow r => Statement -> IO (Maybe r)
- data FormatError
- data ResultError
Examples of use
Create a test database by copy pasting the below snippet to your shell:
sqlite3 test.db "CREATE TABLE test (id INTEGER PRIMARY KEY, str text); \ INSERT INTO test (str) VALUES ('test string');"
..and access it from Haskell:
{-# LANGUAGE OverloadedStrings #-} import Control.Applicative import Database.SQLite.Simple import Database.SQLite.Simple.FromRow data TestField = TestField Int String deriving (Show) instance FromRow TestField where fromRow = TestField <$> field <*> field main :: IO () main = do conn <- open "test.db" execute conn "INSERT INTO test (str) VALUES (?)" (Only ("test string 2" :: String)) r <- query_ conn "SELECT * from test" :: IO [TestField] mapM_ print r close conn
The Query type
SQL-based applications are somewhat notorious for their susceptibility to attacks through the injection of maliciously crafted data. The primary reason for widespread vulnerability to SQL injections is that many applications are sloppy in handling user data when constructing SQL queries.
This library provides a Query
type and a parameter substitution
facility to address both ease of use and security. A Query
is a
newtype
-wrapped Text
. It intentionally exposes a tiny API that
is not compatible with the Text
API; this makes it difficult to
construct queries from fragments of strings. The query
and
execute
functions require queries to be of type Query
.
To most easily construct a query, enable GHC's OverloadedStrings
language extension and write your query as a normal literal string.
{-# LANGUAGE OverloadedStrings #-} import Database.SQLite.Simple hello = do conn <- open "test.db" query conn "select 2 + 2"
A Query
value does not represent the actual query that will be
executed, but is a template for constructing the final query.
Parameter substitution
Since applications need to be able to construct queries with parameters that change, this library uses SQLite's parameter binding query substitution capability.
The Query
template accepted by query
and execute
can contain
any number of "?
" characters. Both query
and execute
accept a third argument, typically a tuple. When constructing the
real query to execute, these functions replace the first "?
" in
the template with the first element of the tuple, the second
"?
" with the second element, and so on. If necessary, each
tuple element will be quoted and escaped prior to substitution;
this defeats the single most common injection vector for malicious
data.
For example, given the following Query
template:
select * from user where first_name = ? and age > ?
And a tuple of this form:
("Boris" :: String, 37 :: Int)
The query to be executed will look like this after substitution:
select * from user where first_name = 'Boris' and age > 37
If there is a mismatch between the number of "?
" characters in
your template and the number of elements in your tuple, a
FormatError
will be thrown.
Note that the substitution functions do not attempt to parse or
validate your query. It's up to you to write syntactically valid
SQL, and to ensure that each "?
" in your query template is
matched with the right tuple element.
This library restricts parameter substitution to work only with
"?
" characters. SQLite natively supports several other
syntaxes for binding query parameters. Unsupported parameters will
be rejected and a FormatError
will be thrown.
Type inference
Automated type inference means that you will often be able to avoid supplying explicit type signatures for the elements of a tuple. However, sometimes the compiler will not be able to infer your types. Consider a case where you write a numeric literal in a parameter tuple:
query conn "select ? + ?" (40,2)
The above query will be rejected by the compiler, because it does
not know the specific numeric types of the literals 40
and 2
.
This is easily fixed:
query conn "select ? + ?" (40 :: Double, 2 :: Double)
The same kind of problem can arise with string literals if you have
the OverloadedStrings
language extension enabled. Again, just
use an explicit type signature if this happens.
Substituting a single parameter
Haskell lacks a single-element tuple type, so if you have just one value you want substituted into a query, what should you do?
To represent a single value val
as a parameter, write a singleton
list [val]
, use Just
val
, or use Only
val
.
Here's an example using a singleton list:
execute conn "insert into users (first_name) values (?)" ["Nuala"]
Extracting results
The query
and query_
functions return a list of values in the
FromRow
typeclass. This class performs automatic extraction
and type conversion of rows from a query result.
Here is a simple example of how to extract results:
import qualified Data.Text as T xs <- query_ conn "select name,age from users" forM_ xs $ \(name,age) -> putStrLn $ T.unpack name ++ " is " ++ show (age :: Int)
Notice two important details about this code:
- The number of columns we ask for in the query template must
exactly match the number of elements we specify in a row of the
result tuple. If they do not match, a
ResultError
exception will be thrown. - Sometimes, the compiler needs our help in specifying types. It
can infer that
name
must be aText
, due to our use of theunpack
function. However, we have to tell it the type ofage
, as it has no other information to determine the exact type.
Handling null values
The type of a result tuple will look something like this:
(Text, Int, Int)
Although SQL can accommodate NULL
as a value for any of these
types, Haskell cannot. If your result contains columns that may be
NULL
, be sure that you use Maybe
in those positions of of your
tuple.
(Text, Maybe Int, Int)
If query
encounters a NULL
in a row where the corresponding
Haskell type is not Maybe
, it will throw a ResultError
exception.
Type conversions
Conversion of SQL values to Haskell values is somewhat permissive. Here are the rules.
- For numeric types, any Haskell type that can accurately represent an SQLite INTEGER is considered "compatible".
- If a numeric incompatibility is found,
query
will throw aResultError
. - SQLite's TEXT type is always encoded in UTF-8. Thus any text
data coming from an SQLite database should always be compatible
with Haskell
String
andText
types. - SQLite's BLOB type will only be conversible to a Haskell
ByteString
.
You can extend conversion support to your own types be adding your
own FromField
/ ToField
instances.
Conversion to/from UTCTime
SQLite's datetime allows for multiple string representations of UTC time. The following formats are supported for reading SQLite times into Haskell UTCTime values:
- YYYY-MM-DD HH:MM
- YYYY-MM-DD HH:MM:SS
- YYYY-MM-DD HH:MM:SS.SSS
- YYYY-MM-DDTHH:MM
- YYYY-MM-DDTHH:MM:SS
- YYYY-MM-DDTHH:MM:SS.SSS
The above may also be optionally followed by a timezone indicator of the form "[+-]HH:MM" or just "Z".
When Haskell UTCTime values are converted into SQLite values (e.g.,
parameters for a query
), the following format is used:
- YYYY-MM-DD HH:MM:SS.SSS
The last ".SSS" subsecond part is dropped if it's zero. No timezone indicator is used when converting from a UTCTime value into an SQLite string. SQLite assumes all datetimes are in UTC time.
The parser and printers are implemented in Database.SQLite.Simple.Time.
Read more about SQLite's time strings in http://sqlite.org/lang_datefunc.html
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.SQLite.Simple q :: Query q = "select ?"
The underlying type is a Text
, and literal Haskell strings that
contain Unicode characters will be correctly transformed to UTF-8.
newtype Connection Source
Connection to an open database.
You can use connectionHandle
to gain access to the underlying
http://hackage.haskell.org/package/direct-sqlite connection.
This may be useful if you need to access some direct-sqlite
functionality that's not exposed in the sqlite-simple API. This
should be a safe thing to do although mixing both APIs is
discouraged.
A collection type that can be turned into a list of SQLData elements.
ToRow () | |
ToField a => ToRow [a] | |
ToField a => ToRow (Only a) | |
(ToField a, ToField b) => ToRow (a, b) | |
(ToRow a, ToRow b) => ToRow ((:.) a b) | |
(ToField a, ToField b, ToField c) => ToRow (a, b, c) | |
(ToField a, ToField b, ToField c, ToField d) => ToRow (a, b, c, d) | |
(ToField a, ToField b, ToField c, ToField d, ToField e) => ToRow (a, b, c, d, e) | |
(ToField a, ToField b, ToField c, ToField d, ToField e, ToField f) => ToRow (a, b, c, d, e, f) | |
(ToField a, ToField b, ToField c, ToField d, ToField e, ToField f, ToField g) => ToRow (a, b, c, d, e, f, g) | |
(ToField a, ToField b, ToField c, ToField d, ToField e, ToField f, ToField g, ToField h) => ToRow (a, b, c, d, e, f, g, h) | |
(ToField a, ToField b, ToField c, ToField d, ToField e, ToField f, ToField g, ToField h, ToField i) => ToRow (a, b, c, d, e, f, g, h, i) | |
(ToField a, ToField b, ToField c, ToField d, ToField e, ToField f, ToField g, ToField h, ToField i, ToField j) => ToRow (a, b, c, d, e, f, g, h, i, j) |
A collection type that can be converted from a sequence of fields. Instances are provided for tuples up to 10 elements and lists of any length.
Note that instances can defined outside of sqlite-simple, which is often useful. For example, here's an instance for a user-defined pair:
@data User = User { name :: String, fileQuota :: Int }
instance FromRow
User where
fromRow = User <$> field
<*> field
@
The number of calls to field
must match the number of fields returned
in a single row of the query result. Otherwise, a ConversionFailed
exception will be thrown.
Note the caveats associated with user-defined implementations of
fromRow
.
A single-value "collection".
This is useful if you need to supply a single parameter to a SQL query, or extract a single column from a SQL result.
Parameter example:
query c "select x from scores where x > ?" (Only
(42::Int))
Result example:
xs <- query_ c "select id from users"
forM_ xs $ \(Only
id) -> {- ... -}
A composite type to parse your custom data structures without having to define dummy newtype wrappers every time.
instance FromRow MyData where ...
instance FromRow MyData2 where ...
then I can do the following for free:
res <- query' c "..." forM res $ \(MyData{..} :. MyData2{..}) -> do ....
h :. t infixr 3 |
data SQLData :: *
newtype ColumnIndex Source
Index of a column in a result set. Column indices start from 0.
Connections
open :: String -> IO Connection Source
Open a database connection to a given file. Will throw an exception if it cannot connect.
Every open
must be closed with a call to close
.
If you specify ":memory:" or an empty string as the input filename, then a private, temporary in-memory database is created for the connection. This database will vanish when you close the connection.
close :: Connection -> IO () Source
Close a database connection.
withConnection :: String -> (Connection -> IO a) -> IO a Source
Opens a database connection, executes an action using this connection, and closes the connection, even in the presence of exceptions.
setTrace :: Connection -> Maybe (Text -> IO ()) -> IO () Source
http://www.sqlite.org/c3ref/profile.html
Enable/disable tracing of SQL execution. Tracing can be disabled
by setting Nothing
as the logger callback.
Warning: If the logger callback throws an exception, your whole program may crash. Enable only for debugging!
Queries that return results
query :: (ToRow q, FromRow r) => Connection -> Query -> q -> IO [r] Source
Perform a SELECT
or other SQL query that is expected to return
results. All results are retrieved and converted before this
function returns.
When processing large results, this function will consume a lot of
client-side memory. Consider using fold
instead.
Exceptions that may be thrown:
FormatError
: the query string mismatched with given arguments.ResultError
: result conversion failed.
query_ :: FromRow r => Connection -> Query -> IO [r] Source
A version of query
that does not perform query substitution.
lastInsertRowId :: Connection -> IO Int64 Source
Returns the rowid of the most recent successful INSERT on the given database connection.
See also http://www.sqlite.org/c3ref/last_insert_rowid.html.
Queries that stream results
fold :: (FromRow row, ToRow params) => Connection -> Query -> params -> a -> (a -> row -> IO a) -> IO a Source
Perform a SELECT
or other SQL query that is expected to return results.
Results are converted and fed into the action
callback as they are being
retrieved from the database.
This allows gives the possibility of processing results in constant space (for instance writing them to disk).
Exceptions that may be thrown:
FormatError
: the query string mismatched with given arguments.ResultError
: result conversion failed.
fold_ :: FromRow row => Connection -> Query -> a -> (a -> row -> IO a) -> IO a Source
A version of fold
which does not perform parameter substitution.
Statements that do not return results
execute :: ToRow q => Connection -> Query -> q -> IO () Source
Execute an INSERT
, UPDATE
, or other SQL query that is not
expected to return results.
Throws FormatError
if the query could not be formatted correctly.
execute_ :: Connection -> Query -> IO () Source
A version of execute
that does not perform query substitution.
Low-level statement API for stream access and prepared statements
openStatement :: Connection -> Query -> IO Statement Source
Opens a prepared statement. A prepared statement must always be closed with
a corresponding call to closeStatement
before closing the connection. Use
nextRow
to iterate on the values returned. Once nextRow
returns
Nothing
, you need to invoke reset
before reexecuting the statement again
with nextRow
.
closeStatement :: Statement -> IO () Source
Closes a prepared statement.
withStatement :: Connection -> Query -> (Statement -> IO a) -> IO a Source
Opens a prepared statement, executes an action using this statement, and closes the statement, even in the presence of exceptions.
reset :: Statement -> IO () Source
Resets a statement. This does not reset bound parameters, if any, but
allows the statement to be reexecuted again by invoking nextRow
.
columnName :: Statement -> ColumnIndex -> IO Text Source
Return the name of a a particular column in the result set of a
Statement
. Throws an ArrayException
if the colum index is out
of bounds.
withBind :: ToRow params => Statement -> params -> IO a -> IO a Source
Binds parameters to a prepared statement, and reset
s the statement when
the callback completes, even in the presence of exceptions.
Use withBind
to reuse prepared statements. Because it reset
s the
statement after each usage, it avoids a pitfall involving implicit
transactions. SQLite creates an implicit transaction if you don't say
BEGIN
explicitly, and does not commit it until all active statements are
finished with either reset
or closeStatement
.
nextRow :: FromRow r => Statement -> IO (Maybe r) Source
Extracts the next row from the prepared statement.
Exceptions
data FormatError Source
Exception thrown if a Query
was malformed.
This may occur if the number of '?
' characters in the query
string does not match the number of parameters provided.
data ResultError Source
Exception thrown if conversion from a SQL value to a Haskell value fails.