snaplet-hdbc-0.6.2: HDBC snaplet for Snap Framework

Snap.Snaplet.Hdbc

Description

This module provides a very thin wrapper around HDBC. It wraps some of the HDBC functions in more convenient functions and re-exports the rest of the HDBC functions.

Synopsis

Documentation

data HdbcSnaplet c Source

The snaplet state type containing a resource pool, parameterised by a raw HDBC connection.

Constructors

IConnection c => HdbcSnaplet 

Fields

hdbcPool :: Pool c
 

class (IConnection c, MonadControlIO m) => HasHdbc m c | m -> c whereSource

Instantiate this typeclass on 'Handler b YourSnapletState' so this snaplet can find the resource pool. Typically you would instantiate it for Snap's Handler type and use your snaplet's lens to this snaplet to access this snaplet's state, which contains the pool. Suppose your snaplet state type is defined as follows, where Connection is the connection type from the HDBC database adapter of your choosing:

 data App = App
  { _dbLens :: Snaplet (HdbcSnaplet Connection) }

Then a typical instance you will want to define in your own snaplet is the following:

 instance HasHdbc (Handler b App) Connection where
   getPool = with dbLens $ gets hdbcPool

Methods

getPool :: m (Pool c)Source

hdbcInit :: IConnection c => IO c -> SnapletInit b (HdbcSnaplet c)Source

Initialise the snaplet by providing it with a raw HDBC connection. A resource pool is created with some default parameters that should be fine for most common usecases. If a custom resource pool configuration is desired, use the hdbcInit' initialiser instead. When the snaplet is unloaded, the disconnect function is called to close any remaining connections.

querySource

Arguments

:: HasHdbc m c 
=> String

The raw SQL to execute. Use ? to indicate placeholders.

-> [SqlValue]

Values for each placeholder according to its position in the SQL statement.

-> m [Row]

A Map of attribute name to attribute value for each row. Can be the empty list.

Execute a SELECT query on the database by passing the query as String, together with a list of values to bind to it. A list of Rows is returned.

query' :: HasHdbc m conn => String -> [SqlValue] -> m IntegerSource

Similar to query, but instead of returning a list of Rows, it returns an Integer indicating the numbers of affected rows. This is typically used for INSERT, UPDATE and DELETE queries.

clone :: HasHdbc m c => m cSource

commit :: HasHdbc m c => m ()Source

disconnect :: HasHdbc m c => m ()Source

The functions provided below are wrappers around the original HDBC functions. Please refer to the HDBC documentation to see what they do and how they work.

runRaw :: HasHdbc m c => String -> m ()Source

withHdbc :: HasHdbc m c => (c -> IO a) -> m aSource

Get a new connection from the resource pool, apply the provided function to it and return the result in of the IO compution in monad m.

withHdbc' :: HasHdbc m c => (c -> a) -> m aSource

Get a new connection from the resource pool, apply the provided function to it and return the result in of the compution in monad m.

withTransaction :: HasHdbc m c => (c -> IO a) -> m aSource

Run an action inside a transaction. If the action throws an exception, the transaction will be rolled back, and the exception rethrown.

 withTransaction' $ \conn -> do ...

withTransaction' :: HasHdbc m c => m a -> m aSource

Run an action inside a transaction. If the action throws an exception, the transaction will be rolled back, and the exception rethrown.

 withTransaction' $ do
   query "INSERT INTO ..." []
   query "DELETE FROM ..." []

data SqlValue

SqlValue is he main type for expressing Haskell values to SQL databases.

INTRODUCTION TO SQLVALUE

This type is used to marshall Haskell data to and from database APIs. HDBC driver interfaces will do their best to use the most accurate and efficient way to send a particular value to the database server.

Values read back from the server are constructed with the most appropriate SqlValue constructor. fromSql or safeFromSql can then be used to convert them into whatever type is needed locally in Haskell.

Most people will use toSql and fromSql instead of manipulating SqlValues directly.

EASY CONVERSIONS BETWEEN HASKELL TYPES

Conversions are powerful; for instance, you can call fromSql on a SqlInt32 and get a String or a Double out of it. This class attempts to Do The Right Thing whenever possible, and will raise an error when asked to do something incorrect. In particular, when converting to any type except a Maybe, SqlNull as the input will cause an error to be raised.

Conversions are implemented in terms of the Data.Convertible module, part of the convertible package. You can refer to its documentation, and import that module, if you wish to parse the Left result from safeFromSql yourself, or write your own conversion instances.

Here are some notes about conversion:

  • Fractions of a second are not preserved on time values
  • There is no safeToSql because toSql never fails.

See also toSql, safeFromSql, fromSql, nToSql, iToSql, posixToSql.

ERROR CONDITIONS

There may sometimes be an error during conversion. For instance, if you have a SqlString and are attempting to convert it to an Integer, but it doesn't parse as an Integer, you will get an error. This will be indicated as an exception if using fromSql, or a Left result if using safeFromSql.

SPECIAL NOTE ON POSIXTIME

Note that a NominalDiffTime or POSIXTime is converted to SqlDiffTime by toSql. HDBC cannot differentiate between NominalDiffTime and POSIXTime since they are the same underlying type. You must construct SqlPOSIXTime manually or via posixToSql, or use SqlUTCTime.

DETAILS ON SQL TYPES

HDBC database backends are expected to marshal date and time data back and forth using the appropriate representation for the underlying database engine. Databases such as PostgreSQL with builtin date and time types should see automatic conversion between these Haskell types to database types. Other databases will be presented with an integer or a string. Care should be taken to use the same type on the Haskell side as you use on the database side. For instance, if your database type lacks timezone information, you ought not to use ZonedTime, but instead LocalTime or UTCTime. Database type systems are not always as rich as Haskell. For instance, for data stored in a TIMESTAMP WITHOUT TIME ZONE column, HDBC may not be able to tell if it is intended as UTCTime or LocalTime data, and will happily convert it to both, upon your request. It is your responsibility to ensure that you treat timezone issues with due care.

This behavior also exists for other types. For instance, many databases do not have a Rational type, so they will just use the show function and store a Rational as a string.

The conversion between Haskell types and database types is complex, and generic code in HDBC or its backends cannot possibly accomodate every possible situation. In some cases, you may be best served by converting your Haskell type to a String, and passing that to the database.

UNICODE AND BYTESTRINGS

Beginning with HDBC v2.0, interactions with a database are presumed to occur in UTF-8.

To accomplish this, whenever a ByteString must be converted to or from a String, the ByteString is assumed to be in UTF-8 encoding, and will be decoded or encoded as appropriate. Database drivers will generally present text or string data they have received from the database as a SqlValue holding a ByteString, which fromSql will automatically convert to a String, and thus automatically decode UTF-8, when you need it. In the other direction, database drivers will generally convert a SqlString to a ByteString in UTF-8 encoding before passing it to the database engine.

If you are handling some sort of binary data that is not in UTF-8, you can of course work with the ByteString directly, which will bypass any conversion.

Due to lack of support by database engines, lazy ByteStrings are not passed to database drivers. When you use toSql on a lazy ByteString, it will be converted to a strict ByteString for storage. Similarly, fromSql will convert a strict ByteString to a lazy ByteString if you demand it.

EQUALITY OF SQLVALUE

Two SqlValues are considered to be equal if one of these hold. The first comparison that can be made is controlling; if none of these comparisons can be made, then they are not equal:

  • Both are NULL
  • Both represent the same type and the encapsulated values are considered equal by applying (==) to them
  • The values of each, when converted to a string, are equal.

STRING VERSIONS OF TIMES

Default string representations are given as comments below where such are non-obvious. These are used for fromSql when a String is desired. They are also defaults for representing data to SQL backends, though individual backends may override them when a different format is demanded by the underlying database. Date and time formats use ISO8601 date format, with HH:MM:SS added for time, and -HHMM added for timezone offsets.

DEPRECATED CONSTRUCTORS

SqlEpochTime and SqlTimeDiff are no longer created automatically by any toSql or fromSql functions or database backends. They may still be manually constructed, but are expected to be removed in a future version. Although these two constructures will be removed, support for marshalling to and from the old System.Time data will be maintained as long as System.Time is, simply using the newer data types for conversion.

Constructors

SqlString String 
SqlByteString ByteString 
SqlWord32 Word32 
SqlWord64 Word64 
SqlInt32 Int32 
SqlInt64 Int64 
SqlInteger Integer 
SqlChar Char 
SqlBool Bool 
SqlDouble Double 
SqlRational Rational 
SqlLocalDate Day

Local YYYY-MM-DD (no timezone)

SqlLocalTimeOfDay TimeOfDay

Local HH:MM:SS (no timezone)

SqlZonedLocalTimeOfDay TimeOfDay TimeZone

Local HH:MM:SS -HHMM. Converts to and from (TimeOfDay, TimeZone).

SqlLocalTime LocalTime

Local YYYY-MM-DD HH:MM:SS (no timezone)

SqlZonedTime ZonedTime

Local YYYY-MM-DD HH:MM:SS -HHMM. Considered equal if both convert to the same UTC time.

SqlUTCTime UTCTime

UTC YYYY-MM-DD HH:MM:SS

SqlDiffTime NominalDiffTime

Calendar diff between seconds. Rendered as Integer when converted to String, but greater precision may be preserved for other types or to underlying database.

SqlPOSIXTime POSIXTime

Time as seconds since midnight Jan 1 1970 UTC. Integer rendering as for SqlDiffTime.

SqlEpochTime Integer

DEPRECATED Representation of ClockTime or CalendarTime. Use SqlPOSIXTime instead.

SqlTimeDiff Integer

DEPRECATED Representation of TimeDiff. Use SqlDiffTime instead.

SqlNull

NULL in SQL or Nothing in Haskell

Instances

Eq SqlValue 
Show SqlValue 
Typeable SqlValue 
Convertible Bool SqlValue 
Convertible Char SqlValue 
Convertible Double SqlValue 
Convertible Int SqlValue 
Convertible Int32 SqlValue 
Convertible Int64 SqlValue 
Convertible Integer SqlValue 
Convertible Rational SqlValue 
Convertible Word32 SqlValue 
Convertible Word64 SqlValue 
Convertible String SqlValue 
Convertible NominalDiffTime SqlValue 
Convertible SqlValue Bool 
Convertible SqlValue Char 
Convertible SqlValue Double 
Convertible SqlValue Int 
Convertible SqlValue Int32 
Convertible SqlValue Int64 
Convertible SqlValue Integer 
Convertible SqlValue Rational 
Convertible SqlValue Word32 
Convertible SqlValue Word64 
Convertible SqlValue String 
Convertible SqlValue NominalDiffTime 
Convertible SqlValue ByteString 
Convertible SqlValue UTCTime 
Convertible SqlValue ByteString 
Convertible SqlValue Text 
Convertible SqlValue Text 
Convertible SqlValue ClockTime 
Convertible SqlValue CalendarTime 
Convertible SqlValue TimeDiff 
Convertible SqlValue LocalTime 
Convertible SqlValue ZonedTime 
Convertible SqlValue TimeOfDay 
Convertible SqlValue Day 
Convertible SqlValue DiffTime 
Convertible ByteString SqlValue 
Convertible UTCTime SqlValue 
Convertible ByteString SqlValue 
Convertible Text SqlValue 
Convertible Text SqlValue 
Convertible ClockTime SqlValue 
Convertible CalendarTime SqlValue 
Convertible TimeDiff SqlValue 
Convertible Password SqlValue 
Convertible UserId SqlValue 
Convertible LocalTime SqlValue 
Convertible ZonedTime SqlValue 
Convertible TimeOfDay SqlValue 
Convertible Day SqlValue 
Convertible DiffTime SqlValue 
Convertible SqlValue a => Convertible SqlValue (Maybe a) 
Convertible SqlValue (TimeOfDay, TimeZone) 
Convertible a SqlValue => Convertible (Maybe a) SqlValue 
Convertible (TimeOfDay, TimeZone) SqlValue 

toSql :: Convertible a SqlValue => a -> SqlValue

Convert a value to an SqlValue. This function is simply a restricted-type wrapper around convert. See extended notes on SqlValue.

fromSql :: Convertible SqlValue a => SqlValue -> a

Convert from an SqlValue to a Haskell value. Any problem is indicated by calling error. This function is simply a restricted-type wrapper around convert. See extended notes on SqlValue.

safeFromSql :: Convertible SqlValue a => SqlValue -> ConvertResult a

Conversions to and from SqlValues and standard Haskell types.

This function converts from an SqlValue to a Haskell value. Many people will use the simpler fromSql instead. This function is simply a restricted-type wrapper around safeConvert.

nToSql :: Integral a => a -> SqlValue

Converts any Integral type to a SqlValue by using toInteger.

iToSql :: Int -> SqlValue

Convenience function for using numeric literals in your program.

posixToSql :: POSIXTime -> SqlValue

Convenience function for converting POSIXTime to a SqlValue, because toSql cannot do the correct thing in this instance.

withWConn :: ConnWrapper -> (forall conn. IConnection conn => conn -> b) -> b

Unwrap a ConnWrapper and pass the embedded IConnection to a function. Example:

withWConn wrapped run $ "SELECT * from foo where bar = 1" []

data Statement

sExecute :: Statement -> [Maybe String] -> IO Integer

Like execute, but take a list of Maybe Strings instead of SqlValues.

sExecuteMany :: Statement -> [[Maybe String]] -> IO ()

Like executeMany, but take a list of Maybe Strings instead of SqlValues.

fetchRowAL :: Statement -> IO (Maybe [(String, SqlValue)])

Like fetchRow, but instead of returning a list, return an association list from column name to value.

The keys of the column names are lowercase versions of the data returned by getColumnNames. Please heed the warnings there. Additionally, results are undefined if multiple columns are returned with identical names.

fetchRowMap :: Statement -> IO (Maybe (Map String SqlValue))

Similar to fetchRowAL, but return a Map instead of an association list.

sFetchRow :: Statement -> IO (Maybe [Maybe String])

Like fetchRow, but return a list of Maybe Strings instead of SqlValues.

fetchAllRows :: Statement -> IO [[SqlValue]]

Lazily fetch all rows from an executed Statement.

You can think of this as hGetContents applied to a database result set.

The result of this is a lazy list, and each new row will be read, lazily, from the database as the list is processed.

When you have exhausted the list, the Statement will be finished.

Please note that the careless use of this function can lead to some unpleasant behavior. In particular, if you have not consumed the entire list, then attempt to finish or re-execute the statement, and then attempt to consume more elements from the list, the result will almost certainly not be what you want.

But then, similar caveats apply with hGetContents.

Bottom line: this is a very convenient abstraction; use it wisely.

Use fetchAllRows' if you need something that is strict, without all these caveats.

fetchAllRows' :: Statement -> IO [[SqlValue]]

Strict version of fetchAllRows. Does not have the side-effects of fetchAllRows, but forces the entire result set to be buffered in memory.

fetchAllRowsAL :: Statement -> IO [[(String, SqlValue)]]

Like fetchAllRows, but instead of returning a list for each row, return an association list for each row, from column name to value.

See fetchRowAL for more details.

fetchAllRowsAL' :: Statement -> IO [[(String, SqlValue)]]

Strict version of fetchAllRowsAL

fetchAllRowsMap :: Statement -> IO [Map String SqlValue]

Like fetchAllRowsAL, but return a list of Maps instead of a list of association lists.

sFetchAllRows :: Statement -> IO [[Maybe String]]

Like fetchAllRows, but return Maybe Strings instead of SqlValues.

sFetchAllRows' :: Statement -> IO [[Maybe String]]

Strict version of sFetchAllRows.

data SqlError

The main HDBC exception object. As much information as possible is passed from the database through to the application through this object.

Errors generated in the Haskell layer will have seNativeError set to -1.

Constructors

SqlError 

throwSqlError :: SqlError -> IO a

A utility function to throw a SqlError. The mechanics of throwing such a thing differ between GHC 6.8.x, Hugs, and GHC 6.10. This function takes care of the special cases to make it simpler.

With GHC 6.10, it is a type-restricted alias for throw. On all other systems, it is a type-restricted alias for throwDyn.

catchSql :: IO a -> (SqlError -> IO a) -> IO a

Execute the given IO action.

If it raises a SqlError, then execute the supplied handler and return its return value. Otherwise, proceed as normal.

handleSql :: (SqlError -> IO a) -> IO a -> IO a

Like catchSql, with the order of arguments reversed.

sqlExceptions :: SqlError -> Maybe SqlError

Given an Exception, return Just SqlError if it was an SqlError, or Nothing otherwise. Useful with functions like catchJust.

handleSqlError :: IO a -> IO a

Catches SqlErrors, and re-raises them as IO errors with fail. Useful if you don't care to catch SQL errors, but want to see a sane error message if one happens. One would often use this as a high-level wrapper around SQL calls.