sqlite-simple-0.4.18.2: Mid-Level SQLite client library
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

Database.SQLite.Simple.Types

Description

Top-level module for sqlite-simple.

Synopsis

Documentation

newtype Only a Source #

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

Eq a => Eq ( Only a)
Instance details

Defined in Data.Tuple.Only

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) Source #

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

toConstr :: Only a -> Constr Source #

dataTypeOf :: Only a -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord a => Ord ( Only a)
Instance details

Defined in Data.Tuple.Only

Read a => Read ( Only a)
Instance details

Defined in Data.Tuple.Only

Show a => Show ( Only a)
Instance details

Defined in Data.Tuple.Only

Generic ( Only a)
Instance details

Defined in Data.Tuple.Only

Associated Types

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

NFData a => NFData ( Only a)
Instance details

Defined in Data.Tuple.Only

Methods

rnf :: Only a -> () Source #

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

Defined in Database.SQLite.Simple.ToRow

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

Defined in Database.SQLite.Simple.FromRow

type Rep ( Only a)
Instance details

Defined in Data.Tuple.Only

type Rep ( Only a) = D1 (' MetaData "Only" "Data.Tuple.Only" "Only-0.1-5HMnGEdyovGeWGWSTFEMo" ' 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

Instances

Instances details
Eq Query Source #
Instance details

Defined in Database.SQLite.Simple.Types

Ord Query Source #
Instance details

Defined in Database.SQLite.Simple.Types

Read Query Source #
Instance details

Defined in Database.SQLite.Simple.Types

Show Query Source #
Instance details

Defined in Database.SQLite.Simple.Types

IsString Query Source #
Instance details

Defined in Database.SQLite.Simple.Types

Semigroup Query Source #
Instance details

Defined in Database.SQLite.Simple.Types

Monoid Query Source #
Instance details

Defined in Database.SQLite.Simple.Types

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