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

Safe HaskellNone
LanguageHaskell2010

Database.ODBC.SQLServer

Contents

Description

SQL Server database API.

Synopsis

Building

You have to compile your projects using the -threaded flag to GHC. In your .cabal file, this would look like: ghc-options: -threaded

Basic library usage

An example program using this library:

{-# LANGUAGE OverloadedStrings #-}
import Database.ODBC
main :: IO ()
main = do
  conn <-
    connect
      "DRIVER={ODBC Driver 13 for SQL Server};SERVER=192.168.99.100;Uid=SA;Pwd=Passw0rd"
  exec conn "DROP TABLE IF EXISTS example"
  exec conn "CREATE TABLE example (id int, name ntext, likes_tacos bit)"
  exec conn "INSERT INTO example VALUES (1, 'Chris', 0), (2, 'Mary', 1)"
  rows <- query conn "SELECT * FROM example" :: IO [[Value]]
  print rows
  rows2 <- query conn "SELECT * FROM example" :: IO [(Int,Text,Bool)]
  print rows2
  close conn

The rows list contains rows of some value that could be anything. The rows2 list contains tuples of exactly Int, Text and Bool. This is achieved via the FromRow class.

You need the OverloadedStrings extension so that you can write Text values for the queries and executions.

The output of this program for rows:

[[IntValue 1, TextValue "Chris", BoolValue False],[ IntValue 2, TextValue "Mary", BoolValue True]]

The output for rows2:

[(1,"Chris",False),(2,"Mary",True)]

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.

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.

-> Query

SQL statement.

-> m () 

Execute a statement on the database.

query Source #

Arguments

:: (MonadIO m, FromRow row) 
=> Connection

A connection to the database.

-> Query

SQL query.

-> m [row] 

Query and return a list of rows.

The row type is inferred based on use or type-signature. Examples might be (Int, Text, Bool) for concrete types, or [Maybe Value] if you don't know ahead of time how many columns you have and their type. See the top section for example use.

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 # 

Methods

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

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

Data Value Source # 

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 # 

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 # 

Methods

showsPrec :: Int -> Value -> ShowS #

show :: Value -> String #

showList :: [Value] -> ShowS #

Generic Value Source # 

Associated Types

type Rep Value :: * -> * #

Methods

from :: Value -> Rep Value x #

to :: Rep Value x -> Value #

NFData Value Source # 

Methods

rnf :: Value -> () #

FromRow Value Source # 
FromValue Value Source # 
ToSql Value Source #

Converts whatever the Value is to SQL.

Methods

toSql :: Value -> Query Source #

FromRow [Value] Source # 
type Rep Value Source # 
type Rep Value = D1 (MetaData "Value" "Database.ODBC.Internal" "odbc-0.2.0-TSQbOkv3Z22yPJ0JjTjMw" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "TextValue" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))) ((:+:) (C1 (MetaCons "ByteStringValue" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 ByteString))) (C1 (MetaCons "BinaryValue" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Binary))))) ((:+:) (C1 (MetaCons "BoolValue" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Bool))) ((:+:) (C1 (MetaCons "DoubleValue" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 Double))) (C1 (MetaCons "FloatValue" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 Float)))))) ((:+:) ((:+:) (C1 (MetaCons "IntValue" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 Int))) ((:+:) (C1 (MetaCons "ByteValue" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedUnpack) (Rec0 Word8))) (C1 (MetaCons "DayValue" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Day))))) ((:+:) (C1 (MetaCons "TimeOfDayValue" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 TimeOfDay))) ((:+:) (C1 (MetaCons "LocalTimeValue" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 LocalTime))) (C1 (MetaCons "NullValue" PrefixI False) U1)))))

data Query Source #

A query builder. Use toSql to convert Haskell values to this type safely.

It's an instance of IsString, so you can use OverloadedStrings to produce plain text values e.g. "SELECT 123".

It's an instance of Monoid, so you can append fragments together with <> e.g. "SELECT * FROM x WHERE id = " <> toSql 123.

This is meant as a bare-minimum of safety and convenience.

Instances

Eq Query Source # 

Methods

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

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

Data Query Source # 

Methods

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

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

toConstr :: Query -> Constr #

dataTypeOf :: Query -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Query Source # 

Methods

compare :: Query -> Query -> Ordering #

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

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

(>) :: Query -> Query -> Bool #

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

max :: Query -> Query -> Query #

min :: Query -> Query -> Query #

Show Query Source # 

Methods

showsPrec :: Int -> Query -> ShowS #

show :: Query -> String #

showList :: [Query] -> ShowS #

IsString Query Source # 

Methods

fromString :: String -> Query #

Generic Query Source # 

Associated Types

type Rep Query :: * -> * #

Methods

from :: Query -> Rep Query x #

to :: Rep Query x -> Query #

Semigroup Query Source # 

Methods

(<>) :: Query -> Query -> Query #

sconcat :: NonEmpty Query -> Query #

stimes :: Integral b => b -> Query -> Query #

Monoid Query Source # 

Methods

mempty :: Query #

mappend :: Query -> Query -> Query #

mconcat :: [Query] -> Query #

NFData Query Source # 

Methods

rnf :: Query -> () #

type Rep Query Source # 
type Rep Query

class ToSql a where Source #

Handy class for converting values to a query safely.

For example: query c ("SELECT * FROM demo WHERE id > " <> toSql 123)

WARNING: Note that if you insert a value like an Int (64-bit) into a column that is int (32-bit), then be sure that your number fits inside an int. Try using an Int32 instead to be sure.

Minimal complete definition

toSql

Methods

toSql :: a -> Query Source #

Instances

ToSql Bool Source #

Corresponds to BIT type of SQL Server.

Methods

toSql :: Bool -> Query Source #

ToSql Double Source #

Corresponds to FLOAT type of SQL Server.

Methods

toSql :: Double -> Query Source #

ToSql Float Source #

Corresponds to REAL type of SQL Server.

Methods

toSql :: Float -> Query Source #

ToSql Int Source #

Corresponds to BIGINT type of SQL Server.

Methods

toSql :: Int -> Query Source #

ToSql Int16 Source #

Corresponds to SMALLINT type of SQL Server.

Methods

toSql :: Int16 -> Query Source #

ToSql Int32 Source #

Corresponds to INT type of SQL Server.

Methods

toSql :: Int32 -> Query Source #

ToSql Word8 Source #

Corresponds to TINYINT type of SQL Server.

Methods

toSql :: Word8 -> Query Source #

ToSql ByteString Source #

Corresponds to TEXT (non-Unicode) of SQL Server. For Unicode, use the Text type.

ToSql ByteString Source #

Corresponds to TEXT (non-Unicode) of SQL Server. For proper BINARY, see the Binary type.

ToSql Text Source #

Corresponds to NTEXT (Unicode) of SQL Server. Note that if your character exceeds the range supported by a wide-char (16-bit), that cannot be sent to the server.

Methods

toSql :: Text -> Query Source #

ToSql Text Source #

Corresponds to NTEXT (Unicode) of SQL Server. Note that if your character exceeds the range supported by a wide-char (16-bit), that cannot be sent to the server.

Methods

toSql :: Text -> Query Source #

TypeError Constraint ((:$$:) (Text "Instance for LocalTime is disabled:") (Text "Wrap your value in either (Datetime2 foo) or (Smalldatetime foo).")) => ToSql LocalTime Source #

You cannot use this instance. Wrap your value in either Datetime2 or Smalldatetime.

ToSql TimeOfDay Source #

Corresponds to TIME type of SQL Server.

TimeOfDay supports more precision than the time type of SQL server, so you will lose precision and not get back what you inserted.

TypeError Constraint ((:$$:) ((:$$:) ((:$$:) (Text "Instance for UTCTime is not possible:") (Text "SQL Server does not support time zones. ")) (Text "You can use utcToLocalTime to make a LocalTime, and")) (Text "wrap your value in either (Datetime2 foo) or (Smalldatetime foo).")) => ToSql UTCTime Source #

You cannot use this instance. Wrap your value in either Datetime2 or Smalldatetime.

Methods

toSql :: UTCTime -> Query Source #

ToSql Day Source #

Corresponds to DATE type of SQL Server.

Methods

toSql :: Day -> Query Source #

ToSql Binary Source # 

Methods

toSql :: Binary -> Query Source #

ToSql Value Source #

Converts whatever the Value is to SQL.

Methods

toSql :: Value -> Query Source #

ToSql Smalldatetime Source #

Corresponds to SMALLDATETIME type of SQL Server. Precision up to minutes. Consider the seconds field always 0.

ToSql Datetime2 Source #

Corresponds to DATETIME/DATETIME2 type of SQL Server.

The Datetime2 type has more accuracy than the datetime type and the datetime2 types can hold; so you will lose precision when you insert.

ToSql a => ToSql (Maybe a) Source # 

Methods

toSql :: Maybe a -> Query Source #

class FromValue a where Source #

Convert from a Value to a regular Haskell value.

Minimal complete definition

fromValue

Methods

fromValue :: Value -> Either String a Source #

The String is used for a helpful error message.

Instances

FromValue Bool Source # 
FromValue Double Source # 
FromValue Float Source # 
FromValue Int Source # 
FromValue Word8 Source # 
FromValue ByteString Source # 
FromValue ByteString Source # 
FromValue Text Source # 
FromValue Text Source # 
FromValue LocalTime Source # 
FromValue TimeOfDay Source # 
FromValue Day Source # 
FromValue Binary Source # 
FromValue Value Source # 
FromValue Smalldatetime Source # 
FromValue Datetime2 Source # 
FromValue a => FromValue (Maybe a) Source # 

class FromRow r where Source #

For producing rows from a list of column values.

You can get a row of a single type like Text or a list e.g. [Maybe Value] if you don't know what you're dealing with, or a tuple e.g. (Text, Int, Bool).

Minimal complete definition

fromRow

Methods

fromRow :: [Value] -> Either String r Source #

Instances

FromRow Bool Source # 
FromRow Double Source # 
FromRow Float Source # 
FromRow Int Source # 
FromRow Word8 Source # 
FromRow ByteString Source # 
FromRow ByteString Source # 
FromRow Text Source # 
FromRow Text Source # 
FromRow LocalTime Source # 
FromRow TimeOfDay Source # 
FromRow Day Source # 
FromRow Binary Source # 
FromRow Value Source # 
FromRow [Value] Source # 
FromValue v => FromRow (Maybe v) Source # 

Methods

fromRow :: [Value] -> Either String (Maybe v) Source #

FromValue v => FromRow (Identity v) Source # 
(FromValue a, FromValue b) => FromRow (a, b) Source # 

Methods

fromRow :: [Value] -> Either String (a, b) Source #

(FromValue a, FromValue b, FromValue c) => FromRow (a, b, c) Source # 

Methods

fromRow :: [Value] -> Either String (a, b, c) Source #

(FromValue a, FromValue b, FromValue c, FromValue d) => FromRow (a, b, c, d) Source # 

Methods

fromRow :: [Value] -> Either String (a, b, c, d) Source #

(FromValue a, FromValue b, FromValue c, FromValue d, FromValue e) => FromRow (a, b, c, d, e) Source # 

Methods

fromRow :: [Value] -> Either String (a, b, c, d, e) Source #

(FromValue a, FromValue b, FromValue c, FromValue d, FromValue e, FromValue f) => FromRow (a, b, c, d, e, f) Source # 

Methods

fromRow :: [Value] -> Either String (a, b, c, d, e, f) Source #

(FromValue a, FromValue b, FromValue c, FromValue d, FromValue e, FromValue f, FromValue g) => FromRow (a, b, c, d, e, f, g) Source # 

Methods

fromRow :: [Value] -> Either String (a, b, c, d, e, f, g) Source #

(FromValue a, FromValue b, FromValue c, FromValue d, FromValue e, FromValue f, FromValue g, FromValue h) => FromRow (a, b, c, d, e, f, g, h) Source # 

Methods

fromRow :: [Value] -> Either String (a, b, c, d, e, f, g, h) Source #

(FromValue a, FromValue b, FromValue c, FromValue d, FromValue e, FromValue f, FromValue g, FromValue h, FromValue i) => FromRow (a, b, c, d, e, f, g, h, i) Source # 

Methods

fromRow :: [Value] -> Either String (a, b, c, d, e, f, g, h, i) Source #

(FromValue a, FromValue b, FromValue c, FromValue d, FromValue e, FromValue f, FromValue g, FromValue h, FromValue i, FromValue j) => FromRow (a, b, c, d, e, f, g, h, i, j) Source # 

Methods

fromRow :: [Value] -> Either String (a, b, c, d, e, f, g, h, i, j) Source #

(FromValue a, FromValue b, FromValue c, FromValue d, FromValue e, FromValue f, FromValue g, FromValue h, FromValue i, FromValue j, FromValue k) => FromRow (a, b, c, d, e, f, g, h, i, j, k) Source # 

Methods

fromRow :: [Value] -> Either String (a, b, c, d, e, f, g, h, i, j, k) Source #

(FromValue a, FromValue b, FromValue c, FromValue d, FromValue e, FromValue f, FromValue g, FromValue h, FromValue i, FromValue j, FromValue k, FromValue l) => FromRow (a, b, c, d, e, f, g, h, i, j, k, l) Source # 

Methods

fromRow :: [Value] -> Either String (a, b, c, d, e, f, g, h, i, j, k, l) Source #

(FromValue a, FromValue b, FromValue c, FromValue d, FromValue e, FromValue f, FromValue g, FromValue h, FromValue i, FromValue j, FromValue k, FromValue l, FromValue m) => FromRow (a, b, c, d, e, f, g, h, i, j, k, l, m) Source # 

Methods

fromRow :: [Value] -> Either String (a, b, c, d, e, f, g, h, i, j, k, l, m) Source #

(FromValue a, FromValue b, FromValue c, FromValue d, FromValue e, FromValue f, FromValue g, FromValue h, FromValue i, FromValue j, FromValue k, FromValue l, FromValue m, FromValue n) => FromRow (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source # 

Methods

fromRow :: [Value] -> Either String (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source #

(FromValue a, FromValue b, FromValue c, FromValue d, FromValue e, FromValue f, FromValue g, FromValue h, FromValue i, FromValue j, FromValue k, FromValue l, FromValue m, FromValue n, FromValue o) => FromRow (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source # 

Methods

fromRow :: [Value] -> Either String (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source #

(FromValue a, FromValue b, FromValue c, FromValue d, FromValue e, FromValue f, FromValue g, FromValue h, FromValue i, FromValue j, FromValue k, FromValue l, FromValue m, FromValue n, FromValue o, FromValue p) => FromRow (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) Source # 

Methods

fromRow :: [Value] -> Either String (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) Source #

(FromValue a, FromValue b, FromValue c, FromValue d, FromValue e, FromValue f, FromValue g, FromValue h, FromValue i, FromValue j, FromValue k, FromValue l, FromValue m, FromValue n, FromValue o, FromValue p, FromValue q) => FromRow (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q) Source # 

Methods

fromRow :: [Value] -> Either String (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q) Source #

(FromValue a, FromValue b, FromValue c, FromValue d, FromValue e, FromValue f, FromValue g, FromValue h, FromValue i, FromValue j, FromValue k, FromValue l, FromValue m, FromValue n, FromValue o, FromValue p, FromValue q, FromValue r) => FromRow (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r) Source # 

Methods

fromRow :: [Value] -> Either String (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r) Source #

(FromValue a, FromValue b, FromValue c, FromValue d, FromValue e, FromValue f, FromValue g, FromValue h, FromValue i, FromValue j, FromValue k, FromValue l, FromValue m, FromValue n, FromValue o, FromValue p, FromValue q, FromValue r, FromValue s) => FromRow (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s) Source # 

Methods

fromRow :: [Value] -> Either String (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s) Source #

(FromValue a, FromValue b, FromValue c, FromValue d, FromValue e, FromValue f, FromValue g, FromValue h, FromValue i, FromValue j, FromValue k, FromValue l, FromValue m, FromValue n, FromValue o, FromValue p, FromValue q, FromValue r, FromValue s, FromValue t) => FromRow (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t) Source # 

Methods

fromRow :: [Value] -> Either String (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t) Source #

(FromValue a, FromValue b, FromValue c, FromValue d, FromValue e, FromValue f, FromValue g, FromValue h, FromValue i, FromValue j, FromValue k, FromValue l, FromValue m, FromValue n, FromValue o, FromValue p, FromValue q, FromValue r, FromValue s, FromValue t, FromValue u) => FromRow (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u) Source # 

Methods

fromRow :: [Value] -> Either String (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u) Source #

(FromValue a, FromValue b, FromValue c, FromValue d, FromValue e, FromValue f, FromValue g, FromValue h, FromValue i, FromValue j, FromValue k, FromValue l, FromValue m, FromValue n, FromValue o, FromValue p, FromValue q, FromValue r, FromValue s, FromValue t, FromValue u, FromValue v) => FromRow (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v) Source # 

Methods

fromRow :: [Value] -> Either String (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v) Source #

(FromValue a, FromValue b, FromValue c, FromValue d, FromValue e, FromValue f, FromValue g, FromValue h, FromValue i, FromValue j, FromValue k, FromValue l, FromValue m, FromValue n, FromValue o, FromValue p, FromValue q, FromValue r, FromValue s, FromValue t, FromValue u, FromValue v, FromValue w) => FromRow (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w) Source # 

Methods

fromRow :: [Value] -> Either String (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w) Source #

(FromValue a, FromValue b, FromValue c, FromValue d, FromValue e, FromValue f, FromValue g, FromValue h, FromValue i, FromValue j, FromValue k, FromValue l, FromValue m, FromValue n, FromValue o, FromValue p, FromValue q, FromValue r, FromValue s, FromValue t, FromValue u, FromValue v, FromValue w, FromValue x) => FromRow (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x) Source # 

Methods

fromRow :: [Value] -> Either String (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x) Source #

(FromValue a, FromValue b, FromValue c, FromValue d, FromValue e, FromValue f, FromValue g, FromValue h, FromValue i, FromValue j, FromValue k, FromValue l, FromValue m, FromValue n, FromValue o, FromValue p, FromValue q, FromValue r, FromValue s, FromValue t, FromValue u, FromValue v, FromValue w, FromValue x, FromValue y) => FromRow (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y) Source # 

Methods

fromRow :: [Value] -> Either String (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y) Source #

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 # 

Methods

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

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

Data Binary Source # 

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 # 
Show Binary Source # 
Generic Binary Source # 

Associated Types

type Rep Binary :: * -> * #

Methods

from :: Binary -> Rep Binary x #

to :: Rep Binary x -> Binary #

NFData Binary Source # 

Methods

rnf :: Binary -> () #

FromRow Binary Source # 
FromValue Binary Source # 
ToSql Binary Source # 

Methods

toSql :: Binary -> Query Source #

type Rep Binary Source # 
type Rep Binary = D1 (MetaData "Binary" "Database.ODBC.Internal" "odbc-0.2.0-TSQbOkv3Z22yPJ0JjTjMw" True) (C1 (MetaCons "Binary" PrefixI True) (S1 (MetaSel (Just Symbol "unBinary") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ByteString)))

newtype Datetime2 Source #

The LocalTime type has more accuracy than the datetime type and the datetime2 types can hold; so you will lose precision when you insert. Use this type to indicate that you are aware of the precision loss and fine with it.

https://docs.microsoft.com/en-us/sql/t-sql/data-types/datetime2-transact-sql?view=sql-server-2017

If you are using smalldatetime in SQL Server, use instead the Smalldatetime type.

Constructors

Datetime2 

Instances

Eq Datetime2 Source # 
Data Datetime2 Source # 

Methods

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

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

toConstr :: Datetime2 -> Constr #

dataTypeOf :: Datetime2 -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Datetime2 Source # 
Show Datetime2 Source # 
Generic Datetime2 Source # 

Associated Types

type Rep Datetime2 :: * -> * #

FromValue Datetime2 Source # 
ToSql Datetime2 Source #

Corresponds to DATETIME/DATETIME2 type of SQL Server.

The Datetime2 type has more accuracy than the datetime type and the datetime2 types can hold; so you will lose precision when you insert.

type Rep Datetime2 Source # 
type Rep Datetime2 = D1 (MetaData "Datetime2" "Database.ODBC.SQLServer" "odbc-0.2.0-TSQbOkv3Z22yPJ0JjTjMw" True) (C1 (MetaCons "Datetime2" PrefixI True) (S1 (MetaSel (Just Symbol "unDatetime2") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 LocalTime)))

newtype Smalldatetime Source #

Use this type to discard higher precision than seconds in your LocalTime values for a schema using smalldatetime.

https://docs.microsoft.com/en-us/sql/t-sql/data-types/smalldatetime-transact-sql?view=sql-server-2017

Constructors

Smalldatetime 

Instances

Eq Smalldatetime Source # 
Data Smalldatetime Source # 

Methods

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

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

toConstr :: Smalldatetime -> Constr #

dataTypeOf :: Smalldatetime -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Smalldatetime Source # 
Show Smalldatetime Source # 
Generic Smalldatetime Source # 

Associated Types

type Rep Smalldatetime :: * -> * #

FromValue Smalldatetime Source # 
ToSql Smalldatetime Source #

Corresponds to SMALLDATETIME type of SQL Server. Precision up to minutes. Consider the seconds field always 0.

type Rep Smalldatetime Source # 
type Rep Smalldatetime = D1 (MetaData "Smalldatetime" "Database.ODBC.SQLServer" "odbc-0.2.0-TSQbOkv3Z22yPJ0JjTjMw" True) (C1 (MetaCons "Smalldatetime" PrefixI True) (S1 (MetaSel (Just Symbol "unSmalldatetime") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 LocalTime)))

Streaming results

Loading all rows of a query result can be expensive and use a lot of memory. Another way to load data is by fetching one row at a time, called streaming.

Here's an example of finding the longest string from a set of rows. It outputs "Hello!". We only work on Text, we ignore for example the NULL row.

{-# LANGUAGE OverloadedStrings, LambdaCase #-}
import qualified Data.Text as T
import           Control.Exception
import           Database.ODBC.SQLServer
main :: IO ()
main =
  bracket
    (connect
       "DRIVER={ODBC Driver 13 for SQL Server};SERVER=192.168.99.101;Uid=SA;Pwd=Passw0rd")
    close
    (\conn -> do
       exec conn "DROP TABLE IF EXISTS example"
       exec conn "CREATE TABLE example (name ntext)"
       exec
         conn
         "INSERT INTO example VALUES ('foo'),('bar'),(NULL),('mu'),('Hello!')"
       longest <-
         stream
           conn
           "SELECT * FROM example"
           (\longest text ->
              pure
                (Continue
                   (if T.length text > T.length longest
                       then text
                       else longest)))
           ""
       print longest)

stream Source #

Arguments

:: (MonadUnliftIO m, FromRow row) 
=> Connection

A connection to the database.

-> Query

SQL query.

-> (state -> row -> 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 # 

Methods

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

show :: Step a -> String #

showList :: [Step a] -> ShowS #

Exceptions

Proper connection handling should guarantee that a close happens at the right time. Here is a better way to write it:

{-# LANGUAGE OverloadedStrings #-}
import Control.Exception
import Database.ODBC.SQLServer
main :: IO ()
main =
  bracket
    (connect
       "DRIVER={ODBC Driver 13 for SQL Server};SERVER=192.168.99.100;Uid=SA;Pwd=Passw0rd")
    close
    (\conn -> do
       rows <- query conn "SELECT N'Hello, World!'"
       print rows)

If an exception occurs inside the lambda, bracket ensures that close is called.

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.

Debugging

renderQuery :: Query -> Text Source #

Render a query to a plain text string. Useful for debugging and testing.