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 | Safe-Inferred |
Language | Haskell2010 |
Top-level module for sqlite-simple.
Documentation
A placeholder for the SQL NULL
value.
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) -> {- ... -}
Instances
Functor Only | |
Data a => Data (Only a) | |
Defined in Data.Tuple.Only 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) | |
Read a => Read (Only a) | |
Show a => Show (Only a) | |
NFData a => NFData (Only a) | |
Defined in Data.Tuple.Only | |
Eq a => Eq (Only a) | |
Ord a => Ord (Only a) | |
FromField a => FromRow (Only a) Source # | |
ToField a => ToRow (Only a) Source # | |
type Rep (Only a) | |
Defined in Data.Tuple.Only |
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.
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 |
Instances
(Read h, Read t) => Read (h :. t) Source # | |
(Show h, Show t) => Show (h :. t) Source # | |
(Eq h, Eq t) => Eq (h :. t) Source # | |
(Ord h, Ord t) => Ord (h :. t) Source # | |
Defined in Database.SQLite.Simple.Types | |
(FromRow a, FromRow b) => FromRow (a :. b) Source # | |
(ToRow a, ToRow b) => ToRow (a :. b) Source # | |