hsql-1.8.2: Database access from Haskell.

Safe HaskellSafe-Infered

Database.HSQL.Types

Description

Basic type class & type definitions for DB interfacing.

Synopsis

Documentation

type SQL = StringSource

An SQL Query.

type TableId = StringSource

A table ID.

data Connection Source

A Connection type represents a connection to a database, through which you can operate on the it. In order to create the connection you need to use the connect function from the module for your prefered backend.

Constructors

Connection 

Fields

connDisconnect :: IO ()

disconnect action

connExecute :: SQL -> IO ()

query execution action (without return value)

connQuery :: SQL -> IO Statement

query action with return value

connTables :: IO [TableId]

retrieval of the names of the tables in reach

connDescribe :: TableId -> IO [ColDef]

retrieval of the field defs of a table

connBeginTransaction :: IO ()

begin of a transaction

connCommitTransaction :: IO ()

commit of a pending transaction

connRollbackTransaction :: IO ()

rollback of a pending transaction

connClosed :: MVar Bool

closing state of the connection

type ColId = StringSource

A table column ID.

type Nullability = BoolSource

Whether fields of a table col may be NULL.

type ColDef = (ColId, SqlType, Nullability)Source

Description of the properties of a table column.

type FieldReader tSource

Arguments

 = ColDef

field type spec

-> CString

field content code

-> Int

field content length

-> IO t

field read action

A DB generic field extraction function, specifiable by field definition, receiving the content code and its length.

type FieldReadingSource

Arguments

 = forall t .  
=> Int

field (column) index

-> ColDef

source field type spec

-> FieldReader t

field reader to be applied

-> IO t

field read action

An extraction of a field of type to be specified by requester, from a row index with source ColDef, applying an appropriate FieldReader.

data Statement Source

The Statement type represents a result from the execution of given SQL query.

Constructors

Statement 

Fields

stmtConn :: Connection

DB connection the statement depends on

stmtClose :: IO ()

close action

stmtFetch :: IO Bool

incrementation of the row pointer and indication whether this is still in range of available rows

stmtGetCol :: FieldReading

a FieldReading function applicable for each row

stmtFields :: [ColDef]

field descriptors for each result table column

stmtClosed :: MVar Bool

check whether the statement is closed

class SqlBind a whereSource

Equivalent to Show and Read adapted to SQL expressions.

Methods

toSqlValue :: a -> SQLSource

show as an SQL expression

fromSqlValue :: SqlType -> SQL -> Maybe aSource

read from an SQL expression in text representation, by support of its SqlType

fromSqlCStringLenSource

Arguments

:: ColDef 
-> CString

binary content of SQL expression

-> Int

size of binary content

-> IO a 

read from SQL expression in binary representation, by support of its ColDef and code size info. This allows for faster conversion for e.g. integral numeric types, etc.

data SqlType Source

Variety of common data types used in databases.

Constructors

SqlInteger 
SqlBigInt 
SqlSmallInt 
SqlTinyInt 
SqlMedInt 
SqlDecimal 

Fields

typeSize :: Int
 
typeDecimals :: Int
 
SqlNumeric 

Fields

typeSize :: Int
 
typeDecimals :: Int
 
SqlReal 
SqlDouble 
SqlFloat 
SqlMoney 
SqlChar 

Fields

typeSize :: Int
 
SqlVarChar 

Fields

typeSize :: Int
 
SqlLongVarChar 

Fields

typeSize :: Int
 
SqlText 
SqlWChar 

Fields

typeSize :: Int
 
SqlWVarChar 

Fields

typeSize :: Int
 
SqlWLongVarChar 

Fields

typeSize :: Int
 
SqlDate 
SqlTime 
SqlTimeTZ 
SqlAbsTime 
SqlRelTime 
SqlTimeInterval 
SqlAbsTimeInterval 
SqlTimeStamp 
SqlDateTime 
SqlDateTimeTZ 
SqlYear 
SqlBit 
SqlENUM 
SqlPoint 
SqlLSeg 
SqlPath 
SqlBox 
SqlPolygon 
SqlLine 
SqlCircle 
SqlINetAddr 
SqlCIDRAddr 
SqlMacAddr 
SqlBinary 

Fields

typeSize :: Int
 
SqlVarBinary 

Fields

typeSize :: Int
 
SqlLongVarBinary 

Fields

typeSize :: Int
 
SqlSET 
SqlBLOB 
SqlUnknown

HSQL returns SqlUnknown for all columns for which it cannot determine the right type. The backendTypeCode here is the internal type code returned from the backend library

Fields

typeCode :: Int
 

data SqlError Source

Constructors

SqlError

generic error condition, with further specification

SqlNoMoreData

no more data was available

SqlInvalidHandle

requested handle is invalid

SqlStillExecuting

connection is blocked by running transaction

SqlNeedMoreData

more data is needed, e.g. additional connection specs

SqlBadTypeCast

requested field can't be converted to requested type

SqlFetchNull

requested field returns NULL

Fields

seFieldName :: String
 
SqlUnknownField

requested field isn't known

Fields

seFieldName :: String
 
SqlUnsupportedOperation

requested operation isn't supported

SqlClosedHandle

referenced handle is already closed