odbc-0.2.1: Haskell binding to the ODBC API, aimed at SQL Server driver

Safe HaskellNone
LanguageHaskell2010

Database.ODBC.Internal

Contents

Description

ODBC database API.

WARNING: This API is meant as a base for more high-level APIs, such as the one provided in Database.ODBC.SQLServer. The commands here are all vulerable to SQL injection attacks. See https://en.wikipedia.org/wiki/SQL_injection for more information.

Don't use this module if you don't know what you're doing.

Synopsis

Connect/disconnect

connect Source #

Arguments

:: MonadIO m 
=> Text

An ODBC connection string.

-> m Connection

A connection to the database. You should call close on it when you're done. If you forget to, then the connection will only be closed when there are no more references to the Connection value in your program, which might never happen. So take care. Use e.g. bracket from Control.Exception to do the open/close pattern, which will handle exceptions.

Connect using the given connection string.

close Source #

Arguments

:: MonadIO m 
=> Connection

A connection to the database.

-> m () 

Close the connection. Further use of the Connection will throw an exception. Double closes also throw an exception to avoid architectural mistakes.

withConnection Source #

Arguments

:: MonadUnliftIO m 
=> Text

An ODBC connection string.

-> (Connection -> m a)

Program that uses the ODBC connection.

-> m a 

Memory bracket around connect and close.

data Connection Source #

Connection to a database. Use of this connection is thread-safe. When garbage collected, the connection will be closed if not done already.

Executing queries

exec Source #

Arguments

:: MonadIO m 
=> Connection

A connection to the database.

-> Text

SQL statement.

-> m () 

Execute a statement on the database.

query Source #

Arguments

:: MonadIO m 
=> Connection

A connection to the database.

-> Text

SQL query.

-> m [[Value]]

A strict list of rows. This list is not lazy, so if you are retrieving a large data set, be aware that all of it will be loaded into memory.

Query and return a list of rows.

data Value Source #

A value used for input/output with the database.

Constructors

TextValue !Text

A Unicode text value.

ByteStringValue !ByteString

A vector of bytes. It might be binary, or a string, but we don't know the encoding. Use decodeUtf8 if the string is UTF-8 encoded, or decodeUtf16LE if it is UTF-16 encoded. For other encodings, see the Haskell text-icu package. For raw binary, see BinaryValue.

BinaryValue !Binary

Only a vector of bytes. Intended for binary data, not for ASCII text.

BoolValue !Bool

A simple boolean.

DoubleValue !Double

Floating point values that fit in a Double.

FloatValue !Float

Floating point values that fit in a Float.

IntValue !Int

Integer values that fit in an Int.

ByteValue !Word8

Values that fit in one byte.

DayValue !Day

Date (year, month, day) values.

TimeOfDayValue !TimeOfDay

Time of day (hh, mm, ss + fractional) values.

LocalTimeValue !LocalTime

Local date and time.

NullValue

SQL null value.

Instances
Eq Value Source # 
Instance details

Defined in Database.ODBC.Internal

Methods

(==) :: Value -> Value -> Bool #

(/=) :: Value -> Value -> Bool #

Data Value Source # 
Instance details

Defined in Database.ODBC.Internal

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Value -> c Value #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Value #

toConstr :: Value -> Constr #

dataTypeOf :: Value -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Value) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Value) #

gmapT :: (forall b. Data b => b -> b) -> Value -> Value #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Value -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Value -> r #

gmapQ :: (forall d. Data d => d -> u) -> Value -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Value -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Value -> m Value #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Value -> m Value #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Value -> m Value #

Ord Value Source # 
Instance details

Defined in Database.ODBC.Internal

Methods

compare :: Value -> Value -> Ordering #

(<) :: Value -> Value -> Bool #

(<=) :: Value -> Value -> Bool #

(>) :: Value -> Value -> Bool #

(>=) :: Value -> Value -> Bool #

max :: Value -> Value -> Value #

min :: Value -> Value -> Value #

Show Value Source # 
Instance details

Defined in Database.ODBC.Internal

Methods

showsPrec :: Int -> Value -> ShowS #

show :: Value -> String #

showList :: [Value] -> ShowS #

Generic Value Source # 
Instance details

Defined in Database.ODBC.Internal

Associated Types

type Rep Value :: * -> * #

Methods

from :: Value -> Rep Value x #

to :: Rep Value x -> Value #

NFData Value Source # 
Instance details

Defined in Database.ODBC.Internal

Methods

rnf :: Value -> () #

FromRow Value Source # 
Instance details

Defined in Database.ODBC.Conversion

FromValue Value Source # 
Instance details

Defined in Database.ODBC.Conversion

ToSql Value Source #

Converts whatever the Value is to SQL.

Instance details

Defined in Database.ODBC.SQLServer

Methods

toSql :: Value -> Query Source #

FromRow [Value] Source # 
Instance details

Defined in Database.ODBC.Conversion

type Rep Value Source # 
Instance details

Defined in Database.ODBC.Internal

type Rep Value = D1 (MetaData "Value" "Database.ODBC.Internal" "odbc-0.2.1-5KIQ0I4keIaLwwEU89qJgJ" False) (((C1 (MetaCons "TextValue" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) :+: (C1 (MetaCons "ByteStringValue" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ByteString)) :+: C1 (MetaCons "BinaryValue" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Binary)))) :+: (C1 (MetaCons "BoolValue" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Bool)) :+: (C1 (MetaCons "DoubleValue" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Double)) :+: C1 (MetaCons "FloatValue" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Float))))) :+: ((C1 (MetaCons "IntValue" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Int)) :+: (C1 (MetaCons "ByteValue" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Word8)) :+: C1 (MetaCons "DayValue" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Day)))) :+: (C1 (MetaCons "TimeOfDayValue" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 TimeOfDay)) :+: (C1 (MetaCons "LocalTimeValue" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 LocalTime)) :+: C1 (MetaCons "NullValue" PrefixI False) (U1 :: * -> *)))))

newtype Binary Source #

A simple newtype wrapper around the ByteString type to use when you want to mean the binary type of SQL, and render to binary literals e.g. 0xFFEF01.

The ByteString type is already mapped to the non-Unicode text type.

Constructors

Binary 

Fields

Instances
Eq Binary Source # 
Instance details

Defined in Database.ODBC.Internal

Methods

(==) :: Binary -> Binary -> Bool #

(/=) :: Binary -> Binary -> Bool #

Data Binary Source # 
Instance details

Defined in Database.ODBC.Internal

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Binary -> c Binary #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Binary #

toConstr :: Binary -> Constr #

dataTypeOf :: Binary -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Binary) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Binary) #

gmapT :: (forall b. Data b => b -> b) -> Binary -> Binary #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Binary -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Binary -> r #

gmapQ :: (forall d. Data d => d -> u) -> Binary -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Binary -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Binary -> m Binary #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Binary -> m Binary #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Binary -> m Binary #

Ord Binary Source # 
Instance details

Defined in Database.ODBC.Internal

Show Binary Source # 
Instance details

Defined in Database.ODBC.Internal

Generic Binary Source # 
Instance details

Defined in Database.ODBC.Internal

Associated Types

type Rep Binary :: * -> * #

Methods

from :: Binary -> Rep Binary x #

to :: Rep Binary x -> Binary #

NFData Binary Source # 
Instance details

Defined in Database.ODBC.Internal

Methods

rnf :: Binary -> () #

FromRow Binary Source # 
Instance details

Defined in Database.ODBC.Conversion

FromValue Binary Source # 
Instance details

Defined in Database.ODBC.Conversion

ToSql Binary Source # 
Instance details

Defined in Database.ODBC.SQLServer

Methods

toSql :: Binary -> Query Source #

type Rep Binary Source # 
Instance details

Defined in Database.ODBC.Internal

type Rep Binary = D1 (MetaData "Binary" "Database.ODBC.Internal" "odbc-0.2.1-5KIQ0I4keIaLwwEU89qJgJ" True) (C1 (MetaCons "Binary" PrefixI True) (S1 (MetaSel (Just "unBinary") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ByteString)))

Streaming results

stream Source #

Arguments

:: (MonadIO m, MonadUnliftIO m) 
=> Connection

A connection to the database.

-> Text

SQL query.

-> (state -> [Value] -> m (Step state))

A stepping function that gets as input the current state and a row, returning either a new state or a final result.

-> state

A state that you can use for the computation. Strictly evaluated each iteration.

-> m state

Final result, produced by the stepper function.

Stream results like a fold with the option to stop at any time.

data Step a Source #

A step in the streaming process for the stream function.

Constructors

Stop !a

Stop with this value.

Continue !a

Continue with this value.

Instances
Show a => Show (Step a) Source # 
Instance details

Defined in Database.ODBC.Internal

Methods

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

show :: Step a -> String #

showList :: [Step a] -> ShowS #

Exceptions

data ODBCException Source #

A database exception. Any of the functions in this library may throw this exception type.

Constructors

UnsuccessfulReturnCode !String !Int16 !String

An ODBC operation failed with the given return code.

AllocationReturnedNull !String

Allocating an ODBC resource failed.

UnknownDataType !String !Int16

An unsupported/unknown data type was returned from the ODBC driver.

DatabaseIsClosed !String

You tried to use the database connection after it was closed.

DatabaseAlreadyClosed

You attempted to close the database twice.

NoTotalInformation !Int

No total length information for column.

DataRetrievalError !String

There was a general error retrieving data. String will contain the reason why.