snaplet-sqlite-simple-0.4.8.3: sqlite-simple snaplet for the Snap Framework

Safe HaskellNone
LanguageHaskell2010

Snap.Snaplet.SqliteSimple

Contents

Description

This snaplet makes it simple to use a SQLite database from your Snap application and is based on the sqlite-simple library (http://hackage.haskell.org/package/sqlite-simple). Now, adding a database to your web app takes just two simple steps.

First, include this snaplet in your application's state.

data App = App
    { ... -- Other state needed in your app
    , _db :: Snaplet Sqlite
    }

Next, call the sqliteInit from your application's initializer.

appInit = makeSnaplet ... $ do
    ...
    d <- nestSnaplet "db" db sqliteInit
    return $ App ... d

Now you can use any of the sqlite-simple wrapper functions defined in this module anywhere in your application handlers. For instance:

postHandler :: Handler App App ()
postHandler = do
    posts <- with db $ query_ "select * from blog_post"
    ...

Optionally, if you find yourself doing many database queries, you can eliminate some of the boilerplate by defining a HasSqlite instance for your application.

instance HasSqlite (Handler b App) where
  getSqliteState = with db get

With this code, our postHandler example no longer requires the with function:

postHandler :: Handler App App ()
postHandler = do
    posts <- query_ "select * from blog_post"
    ...

The first time you run an application with the sqlite-simple snaplet, a configuration file devel.cfg is created in the snaplets/sqlite-simple directory underneath your project root. It specifies how to connect to your Sqlite database. Edit this file and modify the values appropriately and you'll be off and running.

If you want to have out-of-the-box authentication, look at the documentation for the Snap.Snaplet.Auth.Backends.Sqlite module.

Synopsis

The Snaplet

data Sqlite Source

The state for the sqlite-simple snaplet. To use it in your app include this in your application state and use sqliteInit to initialize it.

Constructors

Sqlite 

Fields

sqliteConn :: MVar Connection

Function for retrieving the database connection

Instances

MonadCatchIO m => HasSqlite (ReaderT (Snaplet Sqlite) m)

A convenience instance to make it easier to use this snaplet in the Initializer monad like this:

d <- nestSnaplet "db" db sqliteInit
count <- liftIO $ runReaderT (execute "INSERT ..." params) d
MonadCatchIO m => HasSqlite (ReaderT Sqlite m)

A convenience instance to make it easier to use functions written for this snaplet in non-snaplet contexts.

HasSqlite (Handler b Sqlite)

Default instance

class MonadCatchIO m => HasSqlite m where Source

Instantiate this typeclass on 'Handler b YourAppState' so this snaplet can find the connection source. If you need to have multiple instances of the sqlite snaplet in your application, then don't provide this instance and leverage the default instance by using "with dbLens" in front of calls to snaplet-sqlite-simple functions.

Instances

MonadCatchIO m => HasSqlite (ReaderT (Snaplet Sqlite) m)

A convenience instance to make it easier to use this snaplet in the Initializer monad like this:

d <- nestSnaplet "db" db sqliteInit
count <- liftIO $ runReaderT (execute "INSERT ..." params) d
MonadCatchIO m => HasSqlite (ReaderT Sqlite m)

A convenience instance to make it easier to use functions written for this snaplet in non-snaplet contexts.

HasSqlite (Handler b Sqlite)

Default instance

sqliteInit :: SnapletInit b Sqlite Source

Initialize the snaplet

withSqlite :: HasSqlite m => (Connection -> IO b) -> m b Source

Convenience function for executing a function that needs a database connection.

Multi-threading considerations: The database connection is mutexed such that only a single thread can read or write at any given time. This means we lose database access parallelism. Please see https://github.com/nurpax/snaplet-sqlite-simple/issues/5 for more information.

Wrappers and re-exports

query :: (HasSqlite m, ToRow q, FromRow r) => Query -> q -> m [r] Source

See query

See also withSqlite for notes on concurrent access.

query_ :: (HasSqlite m, FromRow r) => Query -> m [r] Source

See query_

See also withSqlite for notes on concurrent access.

execute :: (HasSqlite m, ToRow q, MonadCatchIO m) => Query -> q -> m () Source

See also withSqlite for notes on concurrent access.

execute_ :: (HasSqlite m, MonadCatchIO m) => Query -> m () Source

See also withSqlite for notes on concurrent access.

data Connection :: *

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.

data Query :: *

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 Only a :: * -> *

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

fromOnly :: a
 

Instances

Functor Only 
Eq a => Eq (Only a) 
Ord a => Ord (Only a) 
Read a => Read (Only a) 
Show a => Show (Only a) 
FromField a => FromRow (Only a) 
ToField a => ToRow (Only a) 
Typeable (* -> *) Only 

data FormatError :: *

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 :: *

Exception thrown if conversion from a SQL value to a Haskell value fails.

data h :. t :: * -> * -> * infixr 3

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 h, Eq t) => Eq ((:.) h t) 
(Ord h, Ord t) => Ord ((:.) h t) 
(Read h, Read t) => Read ((:.) h t) 
(Show h, Show t) => Show ((:.) h t) 
(FromRow a, FromRow b) => FromRow ((:.) a b) 
(ToRow a, ToRow b) => ToRow ((:.) a b) 
Typeable (* -> * -> *) (:.) 

class ToRow a where

A collection type that can be turned into a list of SQLData elements.

Methods

toRow :: a -> [SQLData]

ToField a collection of values.

Instances

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) 

class FromRow a where

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.

Methods

fromRow :: RowParser a

Instances

FromRow AuthUser 
FromField a => FromRow [a] 
FromField a => FromRow (Only a) 
(FromField a, FromField b) => FromRow (a, b) 
(FromRow a, FromRow b) => FromRow ((:.) a b) 
(FromField a, FromField b, FromField c) => FromRow (a, b, c) 
(FromField a, FromField b, FromField c, FromField d) => FromRow (a, b, c, d) 
(FromField a, FromField b, FromField c, FromField d, FromField e) => FromRow (a, b, c, d, e) 
(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f) => FromRow (a, b, c, d, e, f) 
(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g) => FromRow (a, b, c, d, e, f, g) 
(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g, FromField h) => FromRow (a, b, c, d, e, f, g, h) 
(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g, FromField h, FromField i) => FromRow (a, b, c, d, e, f, g, h, i) 
(FromField a, FromField b, FromField c, FromField d, FromField e, FromField f, FromField g, FromField h, FromField i, FromField j) => FromRow (a, b, c, d, e, f, g, h, i, j)