sqlite-simple-0.4.10.0: Mid-Level SQLite client library

Copyright(c) 2011 MailRank Inc.
(c) 2011-2012 Leon P Smith
(c) 2012-2013 Janne Hellsten
LicenseBSD3
MaintainerJanne Hellsten <jjhellst@gmail.com>
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Database.SQLite.Simple.Types

Description

Top-level module for sqlite-simple.

Synopsis

Documentation

data Null Source #

A placeholder for the SQL NULL value.

Constructors

Null 

newtype Only a Source #

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) -> {- ... -}

Constructors

Only 

Fields

Instances

Functor Only Source # 

Methods

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

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

Eq a => Eq (Only a) Source # 

Methods

(==) :: Only a -> Only a -> Bool #

(/=) :: Only a -> Only a -> Bool #

Ord a => Ord (Only a) Source # 

Methods

compare :: Only a -> Only a -> Ordering #

(<) :: Only a -> Only a -> Bool #

(<=) :: Only a -> Only a -> Bool #

(>) :: Only a -> Only a -> Bool #

(>=) :: Only a -> Only a -> Bool #

max :: Only a -> Only a -> Only a #

min :: Only a -> Only a -> Only a #

Read a => Read (Only a) Source # 
Show a => Show (Only a) Source # 

Methods

showsPrec :: Int -> Only a -> ShowS #

show :: Only a -> String #

showList :: [Only a] -> ShowS #

ToField a => ToRow (Only a) Source # 

Methods

toRow :: Only a -> [SQLData] Source #

FromField a => FromRow (Only a) Source # 

Methods

fromRow :: RowParser (Only a) Source #

newtype Query Source #

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.

Constructors

Query 

Fields

data h :. t infixr 3 Source #

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

Constructors

h :. t infixr 3 

Instances

(Eq t, Eq h) => Eq ((:.) h t) Source # 

Methods

(==) :: (h :. t) -> (h :. t) -> Bool #

(/=) :: (h :. t) -> (h :. t) -> Bool #

(Ord t, Ord h) => Ord ((:.) h t) Source # 

Methods

compare :: (h :. t) -> (h :. t) -> Ordering #

(<) :: (h :. t) -> (h :. t) -> Bool #

(<=) :: (h :. t) -> (h :. t) -> Bool #

(>) :: (h :. t) -> (h :. t) -> Bool #

(>=) :: (h :. t) -> (h :. t) -> Bool #

max :: (h :. t) -> (h :. t) -> h :. t #

min :: (h :. t) -> (h :. t) -> h :. t #

(Read t, Read h) => Read ((:.) h t) Source # 

Methods

readsPrec :: Int -> ReadS (h :. t) #

readList :: ReadS [h :. t] #

readPrec :: ReadPrec (h :. t) #

readListPrec :: ReadPrec [h :. t] #

(Show t, Show h) => Show ((:.) h t) Source # 

Methods

showsPrec :: Int -> (h :. t) -> ShowS #

show :: (h :. t) -> String #

showList :: [h :. t] -> ShowS #

(ToRow a, ToRow b) => ToRow ((:.) a b) Source # 

Methods

toRow :: (a :. b) -> [SQLData] Source #

(FromRow a, FromRow b) => FromRow ((:.) a b) Source # 

Methods

fromRow :: RowParser (a :. b) Source #