sqlite-simple-0.4.19.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 HaskellSafe-Inferred
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 

Instances

Instances details
Read Null Source # 
Instance details

Defined in Database.SQLite.Simple.Types

Show Null Source # 
Instance details

Defined in Database.SQLite.Simple.Types

Methods

showsPrec :: Int -> Null -> ShowS #

show :: Null -> String #

showList :: [Null] -> ShowS #

Eq Null Source # 
Instance details

Defined in Database.SQLite.Simple.Types

Methods

(==) :: Null -> Null -> Bool #

(/=) :: Null -> Null -> Bool #

FromField Null Source # 
Instance details

Defined in Database.SQLite.Simple.FromField

ToField Null Source # 
Instance details

Defined in Database.SQLite.Simple.ToField

Methods

toField :: Null -> SQLData Source #

newtype Only a #

The 1-tuple type or single-value "collection".

This type is structurally equivalent to the Identity type, but its intent is more about serving as the anonymous 1-tuple type missing from Haskell for attaching typeclass instances.

Parameter usage example:

encodeSomething (Only (42::Int))

Result usage example:

xs <- decodeSomething
forM_ xs $ \(Only id) -> {- ... -}

Constructors

Only 

Fields

Instances

Instances details
Functor Only 
Instance details

Defined in Data.Tuple.Only

Methods

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

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

Data a => Data (Only a) 
Instance details

Defined in Data.Tuple.Only

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Only a -> c (Only a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Only a) #

toConstr :: Only a -> Constr #

dataTypeOf :: Only a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Only a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Only a)) #

gmapT :: (forall b. Data b => b -> b) -> Only a -> Only a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Only a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Only a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Only a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Only a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Only a -> m (Only a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Only a -> m (Only a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Only a -> m (Only a) #

Generic (Only a) 
Instance details

Defined in Data.Tuple.Only

Associated Types

type Rep (Only a) :: Type -> Type #

Methods

from :: Only a -> Rep (Only a) x #

to :: Rep (Only a) x -> Only a #

Read a => Read (Only a) 
Instance details

Defined in Data.Tuple.Only

Show a => Show (Only a) 
Instance details

Defined in Data.Tuple.Only

Methods

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

show :: Only a -> String #

showList :: [Only a] -> ShowS #

NFData a => NFData (Only a) 
Instance details

Defined in Data.Tuple.Only

Methods

rnf :: Only a -> () #

Eq a => Eq (Only a) 
Instance details

Defined in Data.Tuple.Only

Methods

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

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

Ord a => Ord (Only a) 
Instance details

Defined in Data.Tuple.Only

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 #

FromField a => FromRow (Only a) Source # 
Instance details

Defined in Database.SQLite.Simple.FromRow

Methods

fromRow :: RowParser (Only a) Source #

ToField a => ToRow (Only a) Source # 
Instance details

Defined in Database.SQLite.Simple.ToRow

Methods

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

type Rep (Only a) 
Instance details

Defined in Data.Tuple.Only

type Rep (Only a) = D1 ('MetaData "Only" "Data.Tuple.Only" "Only-0.1-IXdIJrspK8g3DM0dTVjCNi" 'True) (C1 ('MetaCons "Only" 'PrefixI 'True) (S1 ('MetaSel ('Just "fromOnly") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

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

Instances

Instances details
IsString Query Source # 
Instance details

Defined in Database.SQLite.Simple.Types

Methods

fromString :: String -> Query #

Monoid Query Source # 
Instance details

Defined in Database.SQLite.Simple.Types

Methods

mempty :: Query #

mappend :: Query -> Query -> Query #

mconcat :: [Query] -> Query #

Semigroup Query Source # 
Instance details

Defined in Database.SQLite.Simple.Types

Methods

(<>) :: Query -> Query -> Query #

sconcat :: NonEmpty Query -> Query #

stimes :: Integral b => b -> Query -> Query #

Read Query Source # 
Instance details

Defined in Database.SQLite.Simple.Types

Show Query Source # 
Instance details

Defined in Database.SQLite.Simple.Types

Methods

showsPrec :: Int -> Query -> ShowS #

show :: Query -> String #

showList :: [Query] -> ShowS #

Eq Query Source # 
Instance details

Defined in Database.SQLite.Simple.Types

Methods

(==) :: Query -> Query -> Bool #

(/=) :: Query -> Query -> Bool #

Ord Query Source # 
Instance details

Defined in Database.SQLite.Simple.Types

Methods

compare :: Query -> Query -> Ordering #

(<) :: Query -> Query -> Bool #

(<=) :: Query -> Query -> Bool #

(>) :: Query -> Query -> Bool #

(>=) :: Query -> Query -> Bool #

max :: Query -> Query -> Query #

min :: Query -> Query -> Query #

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

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

Defined in Database.SQLite.Simple.Types

Methods

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

readList :: ReadS [h :. t] #

readPrec :: ReadPrec (h :. t) #

readListPrec :: ReadPrec [h :. t] #

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

Defined in Database.SQLite.Simple.Types

Methods

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

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

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

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

Defined in Database.SQLite.Simple.Types

Methods

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

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

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

Defined in Database.SQLite.Simple.Types

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 #

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

Defined in Database.SQLite.Simple.FromRow

Methods

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

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

Defined in Database.SQLite.Simple.ToRow

Methods

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