generic-persistence-0.5.0: Database persistence using generics
Safe HaskellSafe-Inferred
LanguageGHC2021

Database.GP

Synopsis

Documentation

selectById :: forall a id. (Entity a, Convertible id SqlValue) => Conn -> id -> IO (Maybe a) Source #

This module defines RDBMS Persistence operations for Record Data Types that are instances of Data. I call instances of such a data type Entities.

The Persistence operations are using Haskell generics to provide compile time reflection capabilities. HDBC is used to access the RDBMS.

A function that retrieves an entity from a database. The function takes entity id as parameter. If an entity with the given id exists in the database, it is returned as a Just value. If no such entity exists, Nothing is returned. An error is thrown if there are more than one entity with the given id.

select :: forall a. Entity a => Conn -> WhereClauseExpr -> IO [a] Source #

This function retrieves all entities of type a from a database. The function takes an HDBC connection as parameter. The type a is determined by the context of the function call. retrieveAll :: forall a. (Entity a) => Conn -> IO [a] retrieveAll conn = do eitherExRow <- GpSafe.retrieveAll @a conn case eitherExRow of Left ex -> throw ex Right rows -> pure rows

This function retrieves all entities of type a that match some query criteria. The function takes an HDBC connection and a WhereClauseExpr as parameters. The type a is determined by the context of the function call. The function returns a (possibly empty) list of all matching entities. The WhereClauseExpr is typically constructed using any tiny query dsl based on infix operators.

entitiesFromRows :: forall a. Entity a => Conn -> [[SqlValue]] -> IO [a] Source #

A function that constructs a list of entities from a list of rows. The function takes an HDBC connection and a list of rows as parameters. The type a is determined by the context of the function call. The function returns a list of entities. This can be useful if you want to use your own SQL queries.

persist :: forall a. Entity a => Conn -> a -> IO () Source #

A function that persists an entity to a database. The function takes an HDBC connection and an entity as parameters. The entity is either inserted or updated, depending on whether it already exists in the database. The required SQL statements are generated dynamically using Haskell generics and reflection

insert :: forall a. Entity a => Conn -> a -> IO () Source #

A function that explicitely inserts an entity into a database.

insertReturning :: forall a. Entity a => Conn -> a -> IO a Source #

insertMany :: forall a. Entity a => Conn -> [a] -> IO () Source #

A function that inserts a list of entities into a database. The function takes an HDBC connection and a list of entities as parameters. The insert-statement is compiled only once and then executed for each entity.

update :: forall a. Entity a => Conn -> a -> IO () Source #

A function that explicitely updates an entity in a database.

updateMany :: forall a. Entity a => Conn -> [a] -> IO () Source #

A function that updates a list of entities in a database. The function takes an HDBC connection and a list of entities as parameters. The update-statement is compiled only once and then executed for each entity.

delete :: forall a. Entity a => Conn -> a -> IO () Source #

A function that deletes an entity from a database. The function takes an HDBC connection and an entity as parameters.

deleteMany :: forall a. Entity a => Conn -> [a] -> IO () Source #

A function that deletes a list of entities from a database. The function takes an HDBC connection and a list of entities as parameters. The delete-statement is compiled only once and then executed for each entity.

setupTableFor :: forall a. Entity a => Database -> Conn -> IO () Source #

set up a table for a given entity type. The table is dropped (if existing) and recreated. The function takes an HDBC connection as parameter.

data Conn Source #

This module defines a wrapper around an HDBC IConnection. Using this wrapper Conn simplifies the signature of the functions in the GP module. It allows to use any HDBC connection without having to define a new function for each connection type. It also provides additional attributes to the connection, like the database type and the implicit commit flag. These attributes can be used to implement database specific functionality, modify transaction behaviour, etc.

This code has been inspired by the HDBC ConnectionWrapper and some parts have been copied verbatim from the HDBC Database.HDBC.Types module.

This module also defines a ConnectionPool type, which provides basic connection pooling functionality.

A wrapper around an HDBC IConnection.

Constructors

forall conn.IConnection conn => Conn 

Fields

  • implicitCommit :: Bool

    If True, the GenericPersistence functions will commit the transaction after each operation.

  • connection :: conn

    The wrapped connection

Instances

Instances details
IConnection Conn Source #

manually implement the IConnection type class for the Conn type.

Instance details

Defined in Database.GP.Conn

connect :: forall conn. IConnection conn => TxHandling -> conn -> Conn Source #

a smart constructor for the Conn type.

data Database Source #

An enumeration of the supported database types.

Constructors

Postgres 
SQLite 

Instances

Instances details
Show Database Source #

Oracle | MSSQL | MySQL

Instance details

Defined in Database.GP.SqlGenerator

Eq Database Source # 
Instance details

Defined in Database.GP.SqlGenerator

type ConnectionPool = Pool Conn Source #

A pool of connections.

createConnPool Source #

Arguments

:: IConnection conn 
=> TxHandling

the transaction mode

-> String

the connection string

-> (String -> IO conn)

a function that takes a connection string and returns an IConnection

-> Double

the time (in seconds) to keep idle connections open

-> Int

the maximum number of connections to keep open

-> IO ConnectionPool

the resulting connection pool

Creates a connection pool.

withResource :: Pool a -> (a -> IO r) -> IO r #

Take a resource from the pool, perform an action with it and return it to the pool afterwards.

  • If the pool has an idle resource available, it is used immediately.
  • Otherwise, if the maximum number of resources has not yet been reached, a new resource is created and used.
  • If the maximum number of resources has been reached, this function blocks until a resource becomes available.

If the action throws an exception of any type, the resource is destroyed and not returned to the pool.

It probably goes without saying that you should never manually destroy a pooled resource, as doing so will almost certainly cause a subsequent user (who expects the resource to be valid) to throw an exception.

class (Generic a, HasConstructor (Rep a), HasSelectors (Rep a)) => Entity a where Source #

This is the Entity class. It is a type class that is used to define the mapping between a Haskell product type in record notation and a database table. The class has a default implementation for all methods. The default implementation uses the type information to determine a simple 1:1 mapping.

That means that - the type name is used as the table name and the - field names are used as the column names. - A field named 'typeNameID' is used as the primary key field.

The default implementation can be overridden by defining a custom instance for a type.

Please note the following constraints, which apply to all valid Entity type, but that are not explicitely encoded in the type class definition:

  • The type must be a product type in record notation.
  • The type must have exactly one constructor.
  • There must be single primary key field, compund primary keys are not supported.

Minimal complete definition

Nothing

Methods

fromRow :: Conn -> [SqlValue] -> IO a Source #

Converts a database row to a value of type a.

default fromRow :: GFromRow (Rep a) => Conn -> [SqlValue] -> IO a Source #

toRow :: Conn -> a -> IO [SqlValue] Source #

Converts a value of type a to a database row.

default toRow :: GToRow (Rep a) => Conn -> a -> IO [SqlValue] Source #

idField :: String Source #

Returns the name of the primary key field for a type a.

default idField :: String Source #

fieldsToColumns :: [(String, String)] Source #

Returns a list of tuples that map field names to column names for a type a.

tableName :: String Source #

Returns the name of the table for a type a.

class GToRow f Source #

Minimal complete definition

gtoRow

Instances

Instances details
(GToRow a, GToRow b) => GToRow (a :*: b :: k -> Type) Source # 
Instance details

Defined in Database.GP.Entity

Methods

gtoRow :: forall (a0 :: k0). (a :*: b) a0 -> [SqlValue] Source #

Convertible a SqlValue => GToRow (K1 i a :: k -> Type) Source # 
Instance details

Defined in Database.GP.Entity

Methods

gtoRow :: forall (a0 :: k0). K1 i a a0 -> [SqlValue] Source #

GToRow a => GToRow (M1 i c a :: k -> Type) Source # 
Instance details

Defined in Database.GP.Entity

Methods

gtoRow :: forall (a0 :: k0). M1 i c a a0 -> [SqlValue] Source #

class GFromRow f Source #

Minimal complete definition

gfromRow

Instances

Instances details
(KnownNat (NumFields f), GFromRow f, GFromRow g) => GFromRow (f :*: g :: Type -> Type) Source #

This instance is the most interesting one. It splits the list of SqlValues into two parts, one for the first field and one for the rest. Then it uses the GFromRow instance for the first field to convert the first part of the list and the GFromRow instance for the rest of the fields to convert the second part of the list. Finally, it combines the two results using the :*: constructor. https://stackoverflow.com/questions/75485429/how-to-use-ghc-generics-to-convert-from-product-data-types-to-a-list-of-sqlvalue/75485650#75485650

Instance details

Defined in Database.GP.Entity

Methods

gfromRow :: forall (a :: k). [SqlValue] -> (f :*: g) a

Convertible SqlValue a => GFromRow (K1 i a :: k -> Type) Source # 
Instance details

Defined in Database.GP.Entity

Methods

gfromRow :: forall (a0 :: k0). [SqlValue] -> K1 i a a0

GFromRow a => GFromRow (M1 i c a :: k -> Type) Source # 
Instance details

Defined in Database.GP.Entity

Methods

gfromRow :: forall (a0 :: k0). [SqlValue] -> M1 i c a a0

columnNameFor :: forall a. Entity a => String -> String Source #

A convenience function: returns the name of the column for a field of a type a.

data TypeInfo a Source #

A data type holding meta-data about a type. The Phantom type parameter a ensures type safety for reflective functions that use this type to create type instances.

typeInfo :: forall a. (HasConstructor (Rep a), HasSelectors (Rep a), Generic a) => TypeInfo a Source #

this function is a smart constructor for TypeInfo objects. It takes a value of type a and returns a `TypeInfo a` object. If the type has no named fields, an error is thrown. If the type has more than one constructor, an error is thrown.

data PersistenceException Source #

This is the "safe" version of the module Database.GP.GenericPersistence. It uses Either to return errors.

This module defines RDBMS Persistence operations for Record Data Types that are instances of Data. I call instances of such a data type Entities.

The Persistence operations are using Haskell generics to provide compile time reflection capabilities. HDBC is used to access the RDBMS.

exceptions that may occur during persistence operations

in' :: Convertible b SqlValue => Field -> [b] -> WhereClauseExpr infixl 4 Source #

data SortOrder Source #

Constructors

ASC 
DESC 

Instances

Instances details
Show SortOrder Source # 
Instance details

Defined in Database.GP.Query

data NonEmpty a #

Non-empty (and non-strict) list type.

Since: base-4.9.0.0

Constructors

a :| [a] infixr 5 

Instances

Instances details
Foldable NonEmpty

Since: base-4.9.0.0

Instance details

Defined in Data.Foldable

Methods

fold :: Monoid m => NonEmpty m -> m #

foldMap :: Monoid m => (a -> m) -> NonEmpty a -> m #

foldMap' :: Monoid m => (a -> m) -> NonEmpty a -> m #

foldr :: (a -> b -> b) -> b -> NonEmpty a -> b #

foldr' :: (a -> b -> b) -> b -> NonEmpty a -> b #

foldl :: (b -> a -> b) -> b -> NonEmpty a -> b #

foldl' :: (b -> a -> b) -> b -> NonEmpty a -> b #

foldr1 :: (a -> a -> a) -> NonEmpty a -> a #

foldl1 :: (a -> a -> a) -> NonEmpty a -> a #

toList :: NonEmpty a -> [a] #

null :: NonEmpty a -> Bool #

length :: NonEmpty a -> Int #

elem :: Eq a => a -> NonEmpty a -> Bool #

maximum :: Ord a => NonEmpty a -> a #

minimum :: Ord a => NonEmpty a -> a #

sum :: Num a => NonEmpty a -> a #

product :: Num a => NonEmpty a -> a #

Traversable NonEmpty

Since: base-4.9.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> NonEmpty a -> f (NonEmpty b) #

sequenceA :: Applicative f => NonEmpty (f a) -> f (NonEmpty a) #

mapM :: Monad m => (a -> m b) -> NonEmpty a -> m (NonEmpty b) #

sequence :: Monad m => NonEmpty (m a) -> m (NonEmpty a) #

Applicative NonEmpty

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

pure :: a -> NonEmpty a #

(<*>) :: NonEmpty (a -> b) -> NonEmpty a -> NonEmpty b #

liftA2 :: (a -> b -> c) -> NonEmpty a -> NonEmpty b -> NonEmpty c #

(*>) :: NonEmpty a -> NonEmpty b -> NonEmpty b #

(<*) :: NonEmpty a -> NonEmpty b -> NonEmpty a #

Functor NonEmpty

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

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

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

Monad NonEmpty

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

(>>=) :: NonEmpty a -> (a -> NonEmpty b) -> NonEmpty b #

(>>) :: NonEmpty a -> NonEmpty b -> NonEmpty b #

return :: a -> NonEmpty a #

Generic1 NonEmpty 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 NonEmpty :: k -> Type #

Methods

from1 :: forall (a :: k). NonEmpty a -> Rep1 NonEmpty a #

to1 :: forall (a :: k). Rep1 NonEmpty a -> NonEmpty a #

Semigroup (NonEmpty a)

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

(<>) :: NonEmpty a -> NonEmpty a -> NonEmpty a #

sconcat :: NonEmpty (NonEmpty a) -> NonEmpty a #

stimes :: Integral b => b -> NonEmpty a -> NonEmpty a #

Generic (NonEmpty a) 
Instance details

Defined in GHC.Generics

Associated Types

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

Methods

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

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

Read a => Read (NonEmpty a)

Since: base-4.11.0.0

Instance details

Defined in GHC.Read

Show a => Show (NonEmpty a)

Since: base-4.11.0.0

Instance details

Defined in GHC.Show

Methods

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

show :: NonEmpty a -> String #

showList :: [NonEmpty a] -> ShowS #

Eq a => Eq (NonEmpty a)

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

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

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

Ord a => Ord (NonEmpty a)

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

compare :: NonEmpty a -> NonEmpty a -> Ordering #

(<) :: NonEmpty a -> NonEmpty a -> Bool #

(<=) :: NonEmpty a -> NonEmpty a -> Bool #

(>) :: NonEmpty a -> NonEmpty a -> Bool #

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

max :: NonEmpty a -> NonEmpty a -> NonEmpty a #

min :: NonEmpty a -> NonEmpty a -> NonEmpty a #

type Rep1 NonEmpty

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

type Rep (NonEmpty a)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

data SqlValue #

SqlValue is the 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.

Instances

Instances details
Show SqlValue 
Instance details

Defined in Database.HDBC.SqlValue

Eq SqlValue 
Instance details

Defined in Database.HDBC.SqlValue

Convertible SqlValue SqlValue 
Instance details

Defined in Database.HDBC.SqlValue

Convertible SqlValue Int32 
Instance details

Defined in Database.HDBC.SqlValue

Convertible SqlValue Int64 
Instance details

Defined in Database.HDBC.SqlValue

Convertible SqlValue Rational 
Instance details

Defined in Database.HDBC.SqlValue

Convertible SqlValue Word32 
Instance details

Defined in Database.HDBC.SqlValue

Convertible SqlValue Word64 
Instance details

Defined in Database.HDBC.SqlValue

Convertible SqlValue ByteString 
Instance details

Defined in Database.HDBC.SqlValue

Convertible SqlValue ByteString 
Instance details

Defined in Database.HDBC.SqlValue

Convertible SqlValue CalendarTime 
Instance details

Defined in Database.HDBC.SqlValue

Convertible SqlValue ClockTime 
Instance details

Defined in Database.HDBC.SqlValue

Convertible SqlValue TimeDiff 
Instance details

Defined in Database.HDBC.SqlValue

Convertible SqlValue Text 
Instance details

Defined in Database.HDBC.SqlValue

Convertible SqlValue Text 
Instance details

Defined in Database.HDBC.SqlValue

Convertible SqlValue Day 
Instance details

Defined in Database.HDBC.SqlValue

Convertible SqlValue DiffTime 
Instance details

Defined in Database.HDBC.SqlValue

Convertible SqlValue NominalDiffTime 
Instance details

Defined in Database.HDBC.SqlValue

Convertible SqlValue UTCTime 
Instance details

Defined in Database.HDBC.SqlValue

Convertible SqlValue LocalTime 
Instance details

Defined in Database.HDBC.SqlValue

Convertible SqlValue TimeOfDay 
Instance details

Defined in Database.HDBC.SqlValue

Convertible SqlValue ZonedTime 
Instance details

Defined in Database.HDBC.SqlValue

Convertible SqlValue String 
Instance details

Defined in Database.HDBC.SqlValue

Convertible SqlValue Integer 
Instance details

Defined in Database.HDBC.SqlValue

Convertible SqlValue Bool 
Instance details

Defined in Database.HDBC.SqlValue

Convertible SqlValue Char 
Instance details

Defined in Database.HDBC.SqlValue

Convertible SqlValue Double 
Instance details

Defined in Database.HDBC.SqlValue

Convertible SqlValue Int 
Instance details

Defined in Database.HDBC.SqlValue

Enum a => Convertible SqlValue a Source #

These instances are needed to make the Convertible type class work with Enum types out of the box. This is needed because the Convertible type class is used to convert SqlValues to Haskell types.

Instance details

Defined in Database.GP.GenericPersistenceSafe

Convertible Int32 SqlValue 
Instance details

Defined in Database.HDBC.SqlValue

Convertible Int64 SqlValue 
Instance details

Defined in Database.HDBC.SqlValue

Convertible Rational SqlValue 
Instance details

Defined in Database.HDBC.SqlValue

Convertible Word32 SqlValue 
Instance details

Defined in Database.HDBC.SqlValue

Convertible Word64 SqlValue 
Instance details

Defined in Database.HDBC.SqlValue

Convertible ByteString SqlValue 
Instance details

Defined in Database.HDBC.SqlValue

Convertible ByteString SqlValue 
Instance details

Defined in Database.HDBC.SqlValue

Convertible CalendarTime SqlValue 
Instance details

Defined in Database.HDBC.SqlValue

Convertible ClockTime SqlValue 
Instance details

Defined in Database.HDBC.SqlValue

Convertible TimeDiff SqlValue 
Instance details

Defined in Database.HDBC.SqlValue

Convertible Text SqlValue 
Instance details

Defined in Database.HDBC.SqlValue

Convertible Text SqlValue 
Instance details

Defined in Database.HDBC.SqlValue

Convertible Day SqlValue 
Instance details

Defined in Database.HDBC.SqlValue

Convertible DiffTime SqlValue 
Instance details

Defined in Database.HDBC.SqlValue

Convertible NominalDiffTime SqlValue 
Instance details

Defined in Database.HDBC.SqlValue

Convertible UTCTime SqlValue 
Instance details

Defined in Database.HDBC.SqlValue

Convertible LocalTime SqlValue 
Instance details

Defined in Database.HDBC.SqlValue

Convertible TimeOfDay SqlValue 
Instance details

Defined in Database.HDBC.SqlValue

Convertible ZonedTime SqlValue 
Instance details

Defined in Database.HDBC.SqlValue

Convertible String SqlValue 
Instance details

Defined in Database.HDBC.SqlValue

Convertible Integer SqlValue 
Instance details

Defined in Database.HDBC.SqlValue

Convertible Bool SqlValue 
Instance details

Defined in Database.HDBC.SqlValue

Convertible Char SqlValue 
Instance details

Defined in Database.HDBC.SqlValue

Convertible Double SqlValue 
Instance details

Defined in Database.HDBC.SqlValue

Convertible Int SqlValue 
Instance details

Defined in Database.HDBC.SqlValue

Enum a => Convertible a SqlValue Source # 
Instance details

Defined in Database.GP.GenericPersistenceSafe

Convertible SqlValue a => Convertible SqlValue (Maybe a) 
Instance details

Defined in Database.HDBC.SqlValue

Convertible SqlValue (TimeOfDay, TimeZone) 
Instance details

Defined in Database.HDBC.SqlValue

Convertible a SqlValue => Convertible (Maybe a) SqlValue 
Instance details

Defined in Database.HDBC.SqlValue

Convertible (TimeOfDay, TimeZone) SqlValue 
Instance details

Defined in Database.HDBC.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.

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.

quickQuery :: IConnection conn => conn -> String -> [SqlValue] -> IO [[SqlValue]] #

A quick way to do a query. Similar to preparing, executing, and then calling fetchAllRows on a statement. See also quickQuery'.

run :: IConnection conn => conn -> String -> [SqlValue] -> IO Integer #

Execute a single SQL query. Returns the number of rows modified (see execute for details). The second parameter is a list of replacement values, if any.

commit :: IConnection conn => conn -> IO () #

Commit any pending data to the database.

Required to make any changes take effect.

rollback :: IConnection conn => conn -> IO () #

Roll back to the state the database was in prior to the last commit or rollback.

withTransaction :: IConnection conn => conn -> (conn -> IO a) -> IO a #

Execute some code. If any uncaught exception occurs, run rollback and re-raise it. Otherwise, run commit and return.

This function, therefore, encapsulates the logical property that a transaction is all about: all or nothing.

The IConnection object passed in is passed directly to the specified function as a convenience.

This function traps all uncaught exceptions, not just SqlErrors. Therefore, you will get a rollback for any exception that you don't handle. That's probably what you want anyway.

Since all operations in HDBC are done in a transaction, this function doesn't issue an explicit "begin" to the server. You should ideally have called commit or rollback before calling this function. If you haven't, this function will commit or rollback more than just the changes made in the included action.

If there was an error while running rollback, this error will not be reported since the original exception will be propogated back. (You'd probably like to know about the root cause for all of this anyway.) Feedback on this behavior is solicited.

runRaw :: IConnection conn => conn -> String -> IO () #

Execute an SQL string, which may contain multiple queries. This is intended for situations where you need to run DML or DDL queries and aren't interested in results.

disconnect :: IConnection conn => conn -> IO () #

Disconnect from the remote database.

You do not need to explicitly close an IConnection object, but you may do so if you so desire. If you don't, the object will disconnect from the database in a sane way when it is garbage-collected. However, a disconnection may raise an error, so you are encouraged to explicitly call disconnect. Also, garbage collection may not run when the program terminates, and some databases really like an explicit disconnect.

So, bottom line is, you're best off calling disconnect directly, but the world won't end if you forget.

This function discards any data not committed already. Database driver implementators should explicitly call rollback if their databases don't do this automatically on disconnect.

Bad Things (TM) could happen if you call this while you have Statements active. In more precise language, the results in such situations are undefined and vary by database. So don't do it.