sq-0.0.1: High-level SQLite client.
Safe HaskellNone
LanguageGHC2021

Sq

Description

High-level SQLite client library

⚠️ This is an early preview release of this library. Use at your own risk.

import qualified Sq

Things currently supported:

Things not supported yet:

  • Type-safe SQL.
  • Manual and automatic migrations solution.
  • Probably other things.

If you have questions or suggestions, just say so at https://github.com/k0001/hs-sq/issues.

⚠️ This is an early preview release of this library. Use at your own risk.

Synopsis

Statement

data Statement (s :: Mode) i o Source #

  • A SQL statement taking a value i as input and producing rows of o values as output.
  • s indicates whether the statement is Read-only or read-Write.
  • Construct with readStatement or writeStatement.

Instances

Instances details
Profunctor (Statement s) Source # 
Instance details

Defined in Sq.Statement

Methods

dimap :: (a -> b) -> (c -> d) -> Statement s b c -> Statement s a d #

lmap :: (a -> b) -> Statement s b c -> Statement s a c #

rmap :: (b -> c) -> Statement s a b -> Statement s a c #

(#.) :: forall a b c q. Coercible c b => q b c -> Statement s a b -> Statement s a c #

(.#) :: forall a b c q. Coercible b a => Statement s b c -> q a b -> Statement s a c #

Functor (Statement s i) Source # 
Instance details

Defined in Sq.Statement

Methods

fmap :: (a -> b) -> Statement s i a -> Statement s i b #

(<$) :: a -> Statement s i b -> Statement s i a #

Show (Statement s i o) Source # 
Instance details

Defined in Sq.Statement

Methods

showsPrec :: Int -> Statement s i o -> ShowS #

show :: Statement s i o -> String #

showList :: [Statement s i o] -> ShowS #

readStatement :: Input i -> Output o -> SQL -> Statement 'Read i o Source #

Construct a Read-only Statement.

WARNING: This library doesn't yet provide a safe way to construct Statements. You can potentially write anything in your SQL string. Don't do that.

  • The SQL must be read-only.
  • The SQL must contain a single statement.
  • The SQL must not contain any transaction nor savepoint management statements.

writeStatement :: Input i -> Output o -> SQL -> Statement 'Write i o Source #

Construct a Statement that can only be executed as part of a Write Transaction.

WARNING: This library doesn't yet provide a safe way to construct Statements. You can potentially write anything in your SQL string. Don't do that.

  • The SQL must contain a single statement.
  • The SQL must not contain any transaction nor savepoint management statements.

SQL

data SQL Source #

Raw SQL string. Completely unchecked.

Instances

Instances details
IsString SQL Source # 
Instance details

Defined in Sq.Statement

Methods

fromString :: String -> SQL #

Semigroup SQL Source # 
Instance details

Defined in Sq.Statement

Methods

(<>) :: SQL -> SQL -> SQL #

sconcat :: NonEmpty SQL -> SQL #

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

Show SQL Source #

Raw SQL string.

Instance details

Defined in Sq.Statement

Methods

showsPrec :: Int -> SQL -> ShowS #

show :: SQL -> String #

showList :: [SQL] -> ShowS #

NFData SQL Source # 
Instance details

Defined in Sq.Statement

Methods

rnf :: SQL -> () #

ToMessage SQL Source # 
Instance details

Defined in Sq.Statement

Methods

message :: SQL -> Message #

Eq SQL Source # 
Instance details

Defined in Sq.Statement

Methods

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

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

Ord SQL Source # 
Instance details

Defined in Sq.Statement

Methods

compare :: SQL -> SQL -> Ordering #

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

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

(>) :: SQL -> SQL -> Bool #

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

max :: SQL -> SQL -> SQL #

min :: SQL -> SQL -> SQL #

HasField "text" SQL Text Source #

Raw SQL string as Text.

Instance details

Defined in Sq.Statement

Methods

getField :: SQL -> Text #

sql :: QuasiQuoter Source #

A QuasiQuoter for raw SQL strings.

WARNING: This doesn't check the validity of the SQL. It is offered simply because writing multi-line strings in Haskell is otherwise very annoying.

Input

data Input i Source #

How to encode all the input to a single Statement.

Instances

Instances details
Contravariant Input Source # 
Instance details

Defined in Sq.Input

Methods

contramap :: (a' -> a) -> Input a -> Input a' #

(>$) :: b -> Input b -> Input a #

Decidable Input Source # 
Instance details

Defined in Sq.Input

Methods

lose :: (a -> Void) -> Input a #

choose :: (a -> Either b c) -> Input b -> Input c -> Input a #

Divisible Input Source #

Left-biased in case of overlapping BindingNames.

Instance details

Defined in Sq.Input

Methods

divide :: (a -> (b, c)) -> Input b -> Input c -> Input a #

conquer :: Input a #

EncodeDefault i => IsString (Input i) Source #
writeStatement
        "a"
        mempty
        "INSERT INTO t (x) VALUES ($a)"
   :: (EncodeDefault a)
   => Statement Write a ()
Instance details

Defined in Sq.Input

Methods

fromString :: String -> Input i #

Monoid (Input i) Source # 
Instance details

Defined in Sq.Input

Methods

mempty :: Input i #

mappend :: Input i -> Input i -> Input i #

mconcat :: [Input i] -> Input i #

Semigroup (Input i) Source #

Left-biased in case of overlapping BindingNames.

Instance details

Defined in Sq.Input

Methods

(<>) :: Input i -> Input i -> Input i #

sconcat :: NonEmpty (Input i) -> Input i #

stimes :: Integral b => b -> Input i -> Input i #

NFData (Input i) Source # 
Instance details

Defined in Sq.Input

Methods

rnf :: Input i -> () #

encode :: Name -> Encode i -> Input i Source #

Encode a single input parameter. The value will be reachable from the SQL query through the specified Name, with a $ prefix.

writeStatement
        (encode "foo" encodeDefault)
        mempty
        "INSERT INTO t (a) VALUES ($foo)"
   :: (EncodeDefault x)
   => Statement Write x ()

Note that by design, this library doesn't support positional Input parameters. You must always pick a Name.

Multiple Inputs can be composed with Contravariant, Divisible, Decidable and Monoid tools.

writeStatement
        (divided (encode "foo" encodeDefault)
                 (encode "bar" encodeDefault))
        mempty
        "INSERT INTO t (a, b) VALUES ($foo, $bar)"
   :: (EncodeDefault x, EncodeDefault y)
   => Statement Write (x, y) ()

Pro-tip: Consider using the IsString instance for Input. For example, "foo" means encode "foo" encodeDefault. That is, the last example could be written as follows:

writeStatement
        (divided "foo" "bar")
        mempty
        "INSERT INTO t (a, b) VALUES ($foo, $bar)"
   :: (EncodeDefault x, EncodeDefault y)
   => Statement Write (x, y) ()

input :: Name -> Input i -> Input i Source #

Add a prefix Name to parameters names in the given Input, separated by __

This is useful for making reusable Inputs. For example, consider the following.

data Point = Point { x :: Int, y :: Int }

pointInput :: Input Point
pointInput = contramap (\case Point x _ -> x) "x" <>
             contramap (\case Point _ y -> y) "y"

After input:

writeStatement
        (divided (input "p1" pointInput)
                 (input "p2" pointInput))
        mempty
        [sql|
          INSERT INTO vectors (ax, ay, bx, by)
          VALUES ($p1__x, $p1__y, $p2__x, $p2__y) |]
   :: Statement Write (Point, Point) ()

Encode

newtype Encode a Source #

How to encode a single Haskell value of type a into a SQLite value.

Constructors

Encode (a -> Either ErrEncode SQLData)

Encode a value of type a as SQLData.

Ideally, the type a should be small enough that this function always returns Right. However, that can sometimes be annoying, so we allow this function to fail with ErrEncode if necessary, in which case an ErrInput exception will be eventually thrown while trying to bind the relevant Input to a Statement. Why? Because for example, not all Strings can be safely encoded as a SQLText seeing as some non-unicode characters will silently be lost in the conversion. So, we could either not have an Encoder for String at all, which would be annoying, or we could have ErrEncode as we do here in order to safely deal with those obscure corner cases.

Instances

Instances details
Contravariant Encode Source # 
Instance details

Defined in Sq.Encoders

Methods

contramap :: (a' -> a) -> Encode a -> Encode a' #

(>$) :: b -> Encode b -> Encode a #

encodeRefine :: HasCallStack => (a -> Either String b) -> Encode b -> Encode a Source #

A convenience function for refining an Encoder through a function that may fail with a String error message. The CallStack is preserved.

If you need a more sophisticated refinement, use the Encode constructor.

class EncodeDefault a where Source #

Default way to encode a Haskell value of type a into a single SQLite column value.

If there there exist also a DecodeDefault instance for a, then it must roundtrip with the EncodeDefault instance for a.

Methods

encodeDefault :: Encode a Source #

Default way to encode a Haskell value of type a into a single SQLite column value.

Instances

Instances details
EncodeDefault Void Source #

This is absurd.

Instance details

Defined in Sq.Encoders

EncodeDefault Int16 Source #

IntegerColumn.

Instance details

Defined in Sq.Encoders

EncodeDefault Int32 Source #

IntegerColumn.

Instance details

Defined in Sq.Encoders

EncodeDefault Int64 Source #

IntegerColumn.

Instance details

Defined in Sq.Encoders

EncodeDefault Int8 Source #

IntegerColumn.

Instance details

Defined in Sq.Encoders

EncodeDefault Word16 Source #

IntegerColumn.

Instance details

Defined in Sq.Encoders

EncodeDefault Word32 Source #

IntegerColumn.

Instance details

Defined in Sq.Encoders

EncodeDefault Word64 Source #

IntegerColumn if it fits in Int64, otherwise TextColumn.

Instance details

Defined in Sq.Encoders

EncodeDefault Word8 Source #

IntegerColumn.

Instance details

Defined in Sq.Encoders

EncodeDefault Builder Source #

BlobColumn.

Instance details

Defined in Sq.Encoders

EncodeDefault ByteString Source #

BlobColumn.

Instance details

Defined in Sq.Encoders

EncodeDefault ByteString Source #

BlobColumn.

Instance details

Defined in Sq.Encoders

EncodeDefault ShortByteString Source #

BlobColumn.

Instance details

Defined in Sq.Encoders

EncodeDefault SQLData Source #

Literal SQLData Encode.

Instance details

Defined in Sq.Encoders

EncodeDefault Null Source #

NullColumn.

Instance details

Defined in Sq.Encoders

EncodeDefault Text Source #

TextColumn.

Instance details

Defined in Sq.Encoders

EncodeDefault Builder Source #

TextColumn.

Instance details

Defined in Sq.Encoders

EncodeDefault Text Source #

TextColumn.

Instance details

Defined in Sq.Encoders

EncodeDefault CalendarDiffDays Source #

ISO8601 in a @TextColumn.

PyYmMdD
Instance details

Defined in Sq.Encoders

EncodeDefault Day Source #

ISO-8601 in a @TextColumn.

yyyy-mm-dd
  • Sorting these lexicographically in SQL corresponds to sorting them by time.
Instance details

Defined in Sq.Encoders

EncodeDefault UTCTime Source #

ISO8601 in a @TextColumn.

yyyy-mm-ddThh:mm:ss[.ssssssssssss]+00:00
  • Sorting these lexicographically in SQL corresponds to sorting them by time.
  • WARNING: SQLite date and time functions support resolution only up to milliseconds.
  • WARNING: SQLite date and time functions don't support leap seconds.
Instance details

Defined in Sq.Encoders

EncodeDefault CalendarDiffTime Source #

ISO8601 in a @TextColumn.

PyYmMdDThHmMs[.ssssssssssss]S
  • WARNING: SQLite date and time functions support resolution only up to milliseconds.
Instance details

Defined in Sq.Encoders

EncodeDefault LocalTime Source #

ISO8601 in a @TextColumn.

yyyy-mm-ddThh:mm:ss[.ssssssssssss]
  • Sorting these lexicographically in SQL corresponds to sorting them by time.
  • WARNING: SQLite date and time functions support resolution only up to milliseconds.
  • WARNING: SQLite date and time functions don't support leap seconds.
Instance details

Defined in Sq.Encoders

EncodeDefault TimeOfDay Source #

ISO8601 in a @TextColumn.

hh:mm:ss[.ssssssssssss]
  • Sorting these lexicographically in SQL corresponds to sorting them by time.
  • WARNING: SQLite date and time functions support resolution only up to milliseconds.
  • WARNING: SQLite date and time functions don't support leap seconds.
Instance details

Defined in Sq.Encoders

EncodeDefault TimeZone Source #

ISO8601 in a @TextColumn.

±hh:mm
Instance details

Defined in Sq.Encoders

EncodeDefault ZonedTime Source #

ISO8601 in a @TextColumn.

yyyy-mm-ddThh:mm:ss[.ssssssssssss]±hh:mm
  • WARNING: Sorting these lexicographically in SQL won't work unless the offset is always the same! Convert to UTCTime first.
  • WARNING: SQLite date and time functions support resolution only up to milliseconds.
  • WARNING: SQLite date and time functions don't support leap seconds.
Instance details

Defined in Sq.Encoders

EncodeDefault String Source #

TextColumn.

Instance details

Defined in Sq.Encoders

EncodeDefault Integer Source #

IntegerColumn if it fits in Int64, otherwise TextColumn.

Instance details

Defined in Sq.Encoders

EncodeDefault Natural Source #

IntegerColumn if it fits in Int64, otherwise TextColumn.

Instance details

Defined in Sq.Encoders

EncodeDefault Bool Source #

IntegerColumn. Encodes False as 0 and True as 1.

Instance details

Defined in Sq.Encoders

EncodeDefault Char Source #

TextColumn.

Instance details

Defined in Sq.Encoders

EncodeDefault Double Source #

FloatColumn.

Instance details

Defined in Sq.Encoders

EncodeDefault Float Source #

FloatColumn.

Instance details

Defined in Sq.Encoders

EncodeDefault Int Source #

IntegerColumn.

Instance details

Defined in Sq.Encoders

EncodeDefault Word Source #

IntegerColumn if it fits in Int64, otherwise TextColumn.

Instance details

Defined in Sq.Encoders

EncodeDefault a => EncodeDefault (Maybe a) Source #

See encodeMaybe.

Instance details

Defined in Sq.Encoders

(EncodeDefault a, EncodeDefault b) => EncodeDefault (Either a b) Source #

See encodeEither.

Instance details

Defined in Sq.Encoders

encodeEither :: Encode a -> Encode b -> Encode (Either a b) Source #

a's ColumnType if Left, otherwise b's ColumnType.

encodeAeson :: (a -> Value) -> Encode a Source #

Encodes as TextColumn.

Output

data Output o Source #

How to decode an output row from a single Statement.

Instances

Instances details
MonadFail Output Source # 
Instance details

Defined in Sq.Output

Methods

fail :: String -> Output a #

Alternative Output Source # 
Instance details

Defined in Sq.Output

Methods

empty :: Output a #

(<|>) :: Output a -> Output a -> Output a #

some :: Output a -> Output [a] #

many :: Output a -> Output [a] #

Applicative Output Source # 
Instance details

Defined in Sq.Output

Methods

pure :: a -> Output a #

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

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

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

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

Functor Output Source # 
Instance details

Defined in Sq.Output

Methods

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

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

Monad Output Source # 
Instance details

Defined in Sq.Output

Methods

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

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

return :: a -> Output a #

MonadPlus Output Source # 
Instance details

Defined in Sq.Output

Methods

mzero :: Output a #

mplus :: Output a -> Output a -> Output a #

MonadThrow Output Source # 
Instance details

Defined in Sq.Output

Methods

throwM :: (HasCallStack, Exception e) => e -> Output a #

DecodeDefault i => IsString (Output i) Source # 
Instance details

Defined in Sq.Output

Methods

fromString :: String -> Output i #

Monoid o => Monoid (Output o) Source # 
Instance details

Defined in Sq.Output

Methods

mempty :: Output o #

mappend :: Output o -> Output o -> Output o #

mconcat :: [Output o] -> Output o #

Semigroup o => Semigroup (Output o) Source # 
Instance details

Defined in Sq.Output

Methods

(<>) :: Output o -> Output o -> Output o #

sconcat :: NonEmpty (Output o) -> Output o #

stimes :: Integral b => b -> Output o -> Output o #

decode :: Name -> Decode o -> Output o Source #

Decode the column with the given Name.

readStatement
        mempty
        (decode "foo" decodeDefault)
        "SELECT foo FROM t"
   :: (DecodeDefault x)
   => Statement Read () x

Note that by design, this library doesn't support positional Output parameters. You must always pick a Name. In the raw SQL, you can use AS to rename your output columns as necessary.

readStatement
        mempty
        (decode "abc" decodeDefault)
        "SELECT foo AS abc FROM t"
   :: (DecodeDefault x)
   => Statement Read () x

Multiple Outputss can be composed with Monoid, Functor, Applicative, Alternative, Monad, MonadPlus, MonadFail and MonadThrow tools.

readStatement
        mempty
        (do foo <- decode "foo" decodeDefault
            when (foo > 10) do
               fail "Oh no!"
            bar <- decode "bar" decodeDefault
            pure (foo, bar))
        "SELECT foo, bar FROM t"
   :: (DecodeDefault y)
   => Statement Read () (Int, y)

Pro-tip: Consider using the IsString instance for Output, where for example "foo" means decode "foo" decodeDefault:

readStatement
        (liftA2 (,) "foo" "bar")
        mempty
        "SELECT foo, bar FROM t"
   :: (DecodeDefault x, DecodeDefault y)
   => Statement Read () (x, y)

output :: Name -> Output o -> Output o Source #

Add a prefix Name to column names in the given Output, separated by __

This is useful for making reusable Outputs. For example, consider the following.

data Point = Point { x :: Int, y :: Int }

pointOutput :: Output Point
pointOutput = Point <$> "x" <*> "y"

After using output:

readStatement
        mempty
        (liftA2 (output "p1" pointInput)
                (output "p2" pointInput))
        [sql|
          SELECT ax AS p1__x, ay AS p1__y,
                 bx AS p2__x, by AS p2__y
          FROM vectors|]
   :: Statement Read () (Point, Point)

Decode

newtype Decode a Source #

How to decode a single SQLite column value into a Haskell value of type a.

Constructors

Decode (SQLData -> Either ErrDecode a)

Decode a SQLData value into a value of type a.

Instances

Instances details
MonadFail Decode Source # 
Instance details

Defined in Sq.Decoders

Methods

fail :: String -> Decode a #

Alternative Decode Source #

Leftmost result on success, rightmost error on failure.

Instance details

Defined in Sq.Decoders

Methods

empty :: Decode a #

(<|>) :: Decode a -> Decode a -> Decode a #

some :: Decode a -> Decode [a] #

many :: Decode a -> Decode [a] #

Applicative Decode Source # 
Instance details

Defined in Sq.Decoders

Methods

pure :: a -> Decode a #

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

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

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

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

Functor Decode Source # 
Instance details

Defined in Sq.Decoders

Methods

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

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

Monad Decode Source # 
Instance details

Defined in Sq.Decoders

Methods

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

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

return :: a -> Decode a #

MonadPlus Decode Source #

Leftmost result on success, rightmost error on failure.

Instance details

Defined in Sq.Decoders

Methods

mzero :: Decode a #

mplus :: Decode a -> Decode a -> Decode a #

MonadThrow Decode Source # 
Instance details

Defined in Sq.Decoders

Methods

throwM :: (HasCallStack, Exception e) => e -> Decode a #

Monoid a => Monoid (Decode a) Source #
mempty = pure mempty
Instance details

Defined in Sq.Decoders

Methods

mempty :: Decode a #

mappend :: Decode a -> Decode a -> Decode a #

mconcat :: [Decode a] -> Decode a #

Semigroup a => Semigroup (Decode a) Source #
(<>) == liftA2 (<>)
Instance details

Defined in Sq.Decoders

Methods

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

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

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

decodeRefine :: HasCallStack => (a -> Either String b) -> Decode a -> Decode b Source #

A convenience function for refining a Decoder through a function that may fail with a String error message. The CallStack is preserved.

If you need a more sophisticated refinement, use the Decode constructor.

class DecodeDefault a where Source #

Default way to decode a SQLite value into a Haskell value of type a.

If there there exist also a EncodeDefault instance for a, then it must roundtrip with the DecodeDefault instance for a.

Methods

decodeDefault :: Decode a Source #

Default way to decode a SQLite value into a Haskell value of type a.

Instances

Instances details
DecodeDefault Int16 Source #

IntegerColumn.

Instance details

Defined in Sq.Decoders

DecodeDefault Int32 Source #

IntegerColumn.

Instance details

Defined in Sq.Decoders

DecodeDefault Int64 Source #

IntegerColumn.

Instance details

Defined in Sq.Decoders

DecodeDefault Int8 Source #

IntegerColumn.

Instance details

Defined in Sq.Decoders

DecodeDefault Word16 Source #

IntegerColumn.

Instance details

Defined in Sq.Decoders

DecodeDefault Word32 Source #

IntegerColumn.

Instance details

Defined in Sq.Decoders

DecodeDefault Word64 Source #

IntegerColumn if it fits in Int64, otherwise TextColumn.

Instance details

Defined in Sq.Decoders

DecodeDefault Word8 Source #

IntegerColumn.

Instance details

Defined in Sq.Decoders

DecodeDefault ByteString Source #

BlobColumn.

Instance details

Defined in Sq.Decoders

DecodeDefault ByteString Source #

BlobColumn.

Instance details

Defined in Sq.Decoders

DecodeDefault SQLData Source #

Literal SQLData Decode.

Instance details

Defined in Sq.Decoders

DecodeDefault Null Source #

NullColumn.

Instance details

Defined in Sq.Decoders

DecodeDefault Text Source #

TextColumn.

Instance details

Defined in Sq.Decoders

DecodeDefault Text Source #

TextColumn.

Instance details

Defined in Sq.Decoders

DecodeDefault CalendarDiffDays Source #

ISO8601 in a @TextColumn.

TODO: Currently precission over picoseconds is successfully parsed but silently floored. This is an issue in Data.Time.Format.ISO8601. Fix.

Instance details

Defined in Sq.Decoders

DecodeDefault Day Source #

ISO8601 in a @TextColumn.

Instance details

Defined in Sq.Decoders

DecodeDefault UTCTime Source #

Like for ZonedTime.

Instance details

Defined in Sq.Decoders

DecodeDefault CalendarDiffTime Source #

ISO8601 in a @TextColumn.

TODO: Currently precission over picoseconds is successfully parsed but silently floored. This is an issue in Data.Time.Format.ISO8601. Fix.

Instance details

Defined in Sq.Decoders

DecodeDefault LocalTime Source #

ISO8601 in a @TextColumn.

Instance details

Defined in Sq.Decoders

DecodeDefault TimeOfDay Source #

ISO8601 in a @TextColumn.

TODO: Currently precission over picoseconds is successfully parsed but silently floored. This is an issue in Data.Time.Format.ISO8601. Fix.

Instance details

Defined in Sq.Decoders

DecodeDefault TimeZone Source #

ISO8601 in a @TextColumn.

Instance details

Defined in Sq.Decoders

DecodeDefault ZonedTime Source #

TextColumn (ISO8601, or seconds since Epoch with optional decimal part of up to picosecond precission), or Integer (seconds since Epoch).

TODO: Currently precission over picoseconds is successfully parsed but silently floored. This is an issue in Data.Time.Format.ISO8601. Fix.

Instance details

Defined in Sq.Decoders

DecodeDefault String Source #

TextColumn.

Instance details

Defined in Sq.Decoders

DecodeDefault Integer Source #

IntegerColumn, FloatColumn, TextColumn depicting a literal integer.

Instance details

Defined in Sq.Decoders

DecodeDefault Natural Source #

IntegerColumn if it fits in Int64, otherwise TextColumn.

Instance details

Defined in Sq.Decoders

DecodeDefault Bool Source #

IntegerColumn and FloatColumn only.

0 is False, every other number is True.

Instance details

Defined in Sq.Decoders

DecodeDefault Char Source #

TextColumn.

Instance details

Defined in Sq.Decoders

DecodeDefault Double Source #

FloatColumn.

Instance details

Defined in Sq.Decoders

DecodeDefault Float Source #

FloatColumn.

Instance details

Defined in Sq.Decoders

DecodeDefault Int Source #

IntegerColumn.

Instance details

Defined in Sq.Decoders

DecodeDefault Word Source #

IntegerColumn if it fits in Int64, otherwise TextColumn.

Instance details

Defined in Sq.Decoders

DecodeDefault a => DecodeDefault (Maybe a) Source #

See decodeMaybe.

Instance details

Defined in Sq.Decoders

(DecodeDefault a, DecodeDefault b) => DecodeDefault (Either a b) Source #

See decodeEither.

Instance details

Defined in Sq.Decoders

decodeMaybe :: Decode a -> Decode (Maybe a) Source #

Attempt to decode a first, otherwise attempt decode a NullColumn as Nothing.

decodeEither :: Decode a -> Decode b -> Decode (Either a b) Source #

decodeEither da db = fmap Left da <|> fmap Right db

Name

data Name Source #

Part of a binding name suitable to use with encode, decode, input and output.

Construct with name or IsString.

Instances

Instances details
IsString Name Source # 
Instance details

Defined in Sq.Names

Methods

fromString :: String -> Name #

Show Name Source # 
Instance details

Defined in Sq.Names

Methods

showsPrec :: Int -> Name -> ShowS #

show :: Name -> String #

showList :: [Name] -> ShowS #

NFData Name Source # 
Instance details

Defined in Sq.Names

Methods

rnf :: Name -> () #

Eq Name Source # 
Instance details

Defined in Sq.Names

Methods

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

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

Ord Name Source # 
Instance details

Defined in Sq.Names

Methods

compare :: Name -> Name -> Ordering #

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

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

(>) :: Name -> Name -> Bool #

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

max :: Name -> Name -> Name #

min :: Name -> Name -> Name #

HasField "text" Name Text Source # 
Instance details

Defined in Sq.Names

Methods

getField :: Name -> Text #

name :: Text -> Either String Name Source #

  • First character must be ASCII letter.
  • Last character, if any, must be ASCII letter or ASCII digit.
  • Characters between the first and last, if any, must be ASCII letters, ASCII digits, or underscore.

Transactional

data Transactional (g :: k) (r :: Retry) (t :: Mode) a Source #

Transactional g r t a groups together multiple interactions with a same Transaction t that finally produce a value of type a. Think of Transactional as if it was STM.

  • g is an ephemeral tag for the whole inteaction group that prevents Refs and streams from escaping its intended scope (like ST does it). Just ignore it, it will always be polymorphic.
  • r says whether the Transactional could potentially be retried from scratch in order to observe a new snapshot of the database (like STM does it). Learn more about this in Retry.
  • t says whether the Transactional could potentially perform Write or Read-only operations.
  • a is the Haskell value finally produced by a successfu execution of the Transactional.

To execute a Transactional you will normally use one of read or commit (or rollback or embed, but those are less common).

-- We are using commit to execute the Transactional. This means
-- that the Transactional will have read and Write capabilities, that
-- it can retry, and that ultimately, unless there are unhandled
-- exceptions, the changes will be commited to the database.
Sq.commit pool do

   -- We can execute Write Statements:
   userId1 <- Sq.one insertUser "haskell@example.com"

   -- And Read Statements:
   userId2 <- Sq.one getUserIdByEmail "haskell@example.com"

   -- We have MonadFail too:
   when (userId1 /= userId2) do
       fail "Something unexpected happened!"

   -- We also have Refs, which work just like TVars:
   ref <- newRef (0 :: Int)

   -- catch behaves like catchSTM, undoing changes to Refs
   -- and to the database itself when the original action fails:
   userId3 <- catch
       -- Something will fail ...
       (do modifyRef ref (+ 1)
           _ <- Sq.one insertUser "sqlite@example.com"
           throwM FakeException123)
       -- ... but there is a catch!
       (\FakeException123 -> do
           -- The observable universe has been reset to what it
           -- was before the catch:
           Sq.zero getUserIdByEmail "sqlite@example.com"
           modifyRef ref (+ 10))

   -- Only the effects from the exception handling function were preserved:
   Sq.zero getUserIdByEmail "sqlite@example.com"
   10 <- readRef ref

   -- retry and its synonyms mzero and empty not only discard changes as
   -- catch does, but they also cause the ongoing Transaction to be
   -- discarded, and the entire Transactional to be executed again on a
   -- brand new Transaction observing a new snapshot of the database. For
   -- example, the following code will keep retrying the whole Transactional
   -- until the user with the specified email exists.
   userId4 <- Sq.maybe getUserIdByEmail "nix@example.com" >>= \case
       Just x -> pure x
       Nothing -> retry

   -- Presumably, this example was waiting for a concurrent connection to
   -- insert said user. If we got here, it is because that happened.

   -- As usual, mzero and empty can be handled by means of <|> and mplus,
   -- or its synonym orElse.
   False <- mplus (writeRef ref 8 >> mzero >> pure True)
                  (pure False)

   -- The recent writeRef to 8 on the retryied Transactional was discarded:
   10 <- readRef ref

   pure ()

Instances

Instances details
MonadFail (Transactional g r t) Source # 
Instance details

Defined in Sq.Transactional

Methods

fail :: String -> Transactional g r t a #

Alternative (Transactional g 'Retry t) Source #
empty = retry
(<|>) = orElse
Instance details

Defined in Sq.Transactional

Methods

empty :: Transactional g 'Retry t a #

(<|>) :: Transactional g 'Retry t a -> Transactional g 'Retry t a -> Transactional g 'Retry t a #

some :: Transactional g 'Retry t a -> Transactional g 'Retry t [a] #

many :: Transactional g 'Retry t a -> Transactional g 'Retry t [a] #

Applicative (Transactional g r t) Source # 
Instance details

Defined in Sq.Transactional

Methods

pure :: a -> Transactional g r t a #

(<*>) :: Transactional g r t (a -> b) -> Transactional g r t a -> Transactional g r t b #

liftA2 :: (a -> b -> c) -> Transactional g r t a -> Transactional g r t b -> Transactional g r t c #

(*>) :: Transactional g r t a -> Transactional g r t b -> Transactional g r t b #

(<*) :: Transactional g r t a -> Transactional g r t b -> Transactional g r t a #

Functor (Transactional g r t) Source # 
Instance details

Defined in Sq.Transactional

Methods

fmap :: (a -> b) -> Transactional g r t a -> Transactional g r t b #

(<$) :: a -> Transactional g r t b -> Transactional g r t a #

Monad (Transactional g r t) Source # 
Instance details

Defined in Sq.Transactional

Methods

(>>=) :: Transactional g r t a -> (a -> Transactional g r t b) -> Transactional g r t b #

(>>) :: Transactional g r t a -> Transactional g r t b -> Transactional g r t b #

return :: a -> Transactional g r t a #

MonadPlus (Transactional g 'Retry t) Source #
mzero = retry
mplus = orElse
Instance details

Defined in Sq.Transactional

Methods

mzero :: Transactional g 'Retry t a #

mplus :: Transactional g 'Retry t a -> Transactional g 'Retry t a -> Transactional g 'Retry t a #

MonadCatch (Transactional g r t) Source #

catch behaves like STM's catchSTM.

In catch ma f, if an exception is thrown by ma, then any database or Ref changes made by ma will be discarded. Furthermore, if f can handle said exception, then the action resulting from applying f will be executed. Otherwise, if f can't handle the exception, it will bubble up.

Note: This instance's catch catches async exceptions because that's what MonadCatch instances normaly do. As a user of this instance, you probably want to use Control.Exceptions.Safe to make sure you don't catch async exceptions unless you really want to.

Instance details

Defined in Sq.Transactional

Methods

catch :: (HasCallStack, Exception e) => Transactional g r t a -> (e -> Transactional g r t a) -> Transactional g r t a #

MonadMask (Transactional g r t) Source # 
Instance details

Defined in Sq.Transactional

Methods

mask :: HasCallStack => ((forall a. Transactional g r t a -> Transactional g r t a) -> Transactional g r t b) -> Transactional g r t b #

uninterruptibleMask :: HasCallStack => ((forall a. Transactional g r t a -> Transactional g r t a) -> Transactional g r t b) -> Transactional g r t b #

generalBracket :: HasCallStack => Transactional g r t a -> (a -> ExitCase b -> Transactional g r t c) -> (a -> Transactional g r t b) -> Transactional g r t (b, c) #

MonadThrow (Transactional g r t) Source # 
Instance details

Defined in Sq.Transactional

Methods

throwM :: (HasCallStack, Exception e) => e -> Transactional g r t a #

MonadAtomicRef (Transactional g r t) Source # 
Instance details

Defined in Sq.Transactional

Methods

atomicModifyRef :: Ref (Transactional g r t) a -> (a -> (a, b)) -> Transactional g r t b #

atomicModifyRef' :: Ref (Transactional g r t) a -> (a -> (a, b)) -> Transactional g r t b #

MonadRef (Transactional g r t) Source #

All operations are atomic.

Instance details

Defined in Sq.Transactional

Associated Types

type Ref (Transactional g r t) 
Instance details

Defined in Sq.Transactional

type Ref (Transactional g r t) = Ref g

Methods

newRef :: a -> Transactional g r t (Ref (Transactional g r t) a) #

readRef :: Ref (Transactional g r t) a -> Transactional g r t a #

writeRef :: Ref (Transactional g r t) a -> a -> Transactional g r t () #

modifyRef :: Ref (Transactional g r t) a -> (a -> a) -> Transactional g r t () #

modifyRef' :: Ref (Transactional g r t) a -> (a -> a) -> Transactional g r t () #

type Ref (Transactional g r t) Source # 
Instance details

Defined in Sq.Transactional

type Ref (Transactional g r t) = Ref g

read :: forall {k} m (p :: Mode) a. (MonadIO m, SubMode p 'Read) => Pool p -> (forall (g :: k). Transactional g 'Retry 'Read a) -> m a Source #

Execute a Read-only Transactional in a fresh Transaction that will be automatically released when done.

commit :: forall {k} m a. MonadIO m => Pool 'Write -> (forall (g :: k). Transactional g 'Retry 'Write a) -> m a Source #

Execute a read-Write Transactional in a fresh Transaction that will be automatically committed when done.

rollback :: forall {k} m a. MonadIO m => Pool 'Write -> (forall (g :: k). Transactional g 'Retry 'Write a) -> m a Source #

Execute a read-Write Transactional in a fresh Transaction that will be automatically rolled-back when done.

This is mostly useful for testing.

embed Source #

Arguments

:: forall {k} m (t :: Mode) a. MonadIO m 
=> Transaction t

Ongoing transaction.

-> (forall (g :: k). Transactional g 'NoRetry t a) 
-> m a 

Embeds all the actions in a Transactional as part of an ongoing Transaction.

data Ref (g :: k) a Source #

Like TVar, but you can use it inside Transactional through the MonadRef and MonadAtomicRef vocabulary.

Instances

Instances details
Eq (Ref g a) Source #

Pointer equality

Instance details

Defined in Sq.Transactional

Methods

(==) :: Ref g a -> Ref g a -> Bool #

(/=) :: Ref g a -> Ref g a -> Bool #

retry :: forall {k} (g :: k) (t :: Mode) a. Transactional g 'Retry t a Source #

retry behaves like STM's retry. It causes the current Transaction to be cancelled so that a new one can take its place and the entire Transactional is executed again. This allows the Transactional to observe a new snapshot of the database.

  • retry, empty and mzero all do fundamentally the same thing, however retry leads to better type inferrence because it forces the r type-parameter to be Retry.
  • NOTICE You only need to use mzero if you need access to a newer database snapshot. If all you want to do is undo some Ref transformation effects, or undo database changes, then use catch which doesn't abandon the Transaction.
  • WARNING If we keep retrying and the database never changes, then we will be stuck in a loop forever. To mitigate this, when executing the Transactional through read, commit or rollback, you may want to use timeout to abort at some point in the future.

orElse :: forall {k} (g :: k) (r :: Retry) (t :: Mode) a. Transactional g r t a -> Transactional g r t a -> Transactional g r t a Source #

orElse ma mb behaves like STM's orElse ma mb. If ma completes without executing retry, then that constitutes the entirety of orElse ma mb. Otherwise, if ma executed retry, then all the effects from ma are discared and mb is tried in its place.

  • orElse, <|> and mplus all do the same thing, but orElse has a more general type because it doesn't force the r type-parameter to be Retry.

Querying

one :: forall {k} (t :: Mode) (s :: Mode) i o (g :: k) (r :: Retry). SubMode t s => Statement s i o -> i -> Transactional g r t o Source #

Executes a Statement expected to return exactly one row.

maybe :: forall {k} (t :: Mode) (s :: Mode) i o (g :: k) (r :: Retry). SubMode t s => Statement s i o -> i -> Transactional g r t (Maybe o) Source #

Executes a Statement expected to return zero or one rows.

zero :: forall {k} (t :: Mode) (s :: Mode) i o (g :: k) (r :: Retry). SubMode t s => Statement s i o -> i -> Transactional g r t () Source #

Executes a Statement expected to return exactly zero rows.

some :: forall {k} (t :: Mode) (s :: Mode) i o (g :: k) (r :: Retry). SubMode t s => Statement s i o -> i -> Transactional g r t (Int64, NonEmpty o) Source #

Executes a Statement expected to return one or more rows.

list :: forall {k} (t :: Mode) (s :: Mode) i o (g :: k) (r :: Retry). SubMode t s => Statement s i o -> i -> Transactional g r t (Int64, [o]) Source #

Executes a Statement expected to return zero or more rows.

  • Returns the length of the list, too.

fold :: forall {k} (t :: Mode) (s :: Mode) o z i (g :: k) (r :: Retry). SubMode t s => Fold o z -> Statement s i o -> i -> Transactional g r t z Source #

Purely fold all the output rows.

foldM :: forall {k} (t :: Mode) (s :: Mode) (g :: k) (r :: Retry) o z i. SubMode t s => FoldM (Transactional g r t) o z -> Statement s i o -> i -> Transactional g r t z Source #

Impurely fold the output rows.

Interleaving

streamIO Source #

Arguments

:: forall (m :: Type -> Type) (t :: Mode) (s :: Mode) i o. (MonadResource m, SubMode t s) 
=> Acquire (Transaction t)

How to acquire the Transaction once the Stream starts being consumed, and how to release it when it's not needed anymore.

If you want this Statement to be the only one in the Transaction, then use one of readTransaction, 'Sq.commitTransaction or rollbackTransaction.

Otherwise, if you already obtained a Transaction by other means, then simply use pure to wrap a Transaction in Acquire.

-> Statement s i o 
-> i 
-> Stream (Of o) m ()

A Stream from the streaming library.

We use the streaming library because it is fast and doesn't add any transitive dependencies to this project.

Stream the output rows from a Statement in a way that allows interleaving IO actions.

  • An exclusive lock will be held on the Transaction while the Stream is producing rows.
  • The Transaction lock is released automatically if the Stream is consumed until exhaustion.
  • If you won't consume the Stream until exhaustion, then be sure to exit m by means of runResourceT or similar as soon as possible in order to release the Transaction lock.

foldIO Source #

Arguments

:: forall m (t :: Mode) (s :: Mode) o z i. (MonadIO m, MonadMask m, SubMode t s) 
=> FoldM m o z 
-> Acquire (Transaction t)

How to acquire the Transaction once the m is executed, and how to release it when it's not needed anymore.

If you want this Statement to be the only one in the Transaction, then use one of readTransaction, commitTransaction or rollbackTransaction.

Otherwise, if you already obtained a Transaction by other means, then simply use pure to wrap a Transaction in Acquire.

-> Statement s i o 
-> i 
-> m z 

Fold the output rows from a Statement in a way that allows interleaving IO actions.

  • This is simpler alternative to streamIO for when all you need to do is fold.
  • If you don't need to interleave IO actions, then consider using fold.

Pool

data Pool (p :: Mode) Source #

Pool of connections to a SQLite database.

  • p indicates whether Read-only or read-Write Statements are supported by this Pool.
  • Obtain with readPool, writePool or tempPool.
  • It's safe and efficient to use a Pool concurrently as is. Concurrency is handled internally.

Instances

Instances details
NFData (Pool p) Source # 
Instance details

Defined in Sq.Pool

Methods

rnf :: Pool p -> () #

readPool :: Df1 -> Settings -> Acquire (Pool 'Read) Source #

Acquire a Read-only Pool according to the given Settings.

writePool :: Df1 -> Settings -> Acquire (Pool 'Write) Source #

Acquire a read-Write Pool according to the given Settings.

tempPool :: Df1 -> Acquire (Pool 'Write) Source #

Acquire a read-Write Pool temporarily persisted in the file-system. It will be deleted once released. This can be useful for testing.

subPool :: Pool 'Write -> Pool 'Read Source #

Use subPool to obtain the Read-only subset from a read-Write Pool.

  • Useful if you are passing the Pool as an argument to some code, and you want to ensure that it can't performs Write operations on it.
  • The “new” Pool is not new. It shares all the underlying resources with the original one, including their lifetime.

Settings

data Settings Source #

SQLite connection settings.

Constructors

Settings 

Fields

  • file :: FilePath

    Database file path. Not an URI.

    Note: To keep things simple, native :memory: SQLite databases are not supported. Maybe use poolTemp or tmpfs if you need that?

  • vfs :: SQLVFS
     
  • timeout :: Word32

    SQLite busy Timeout in milliseconds.

Instances

Instances details
Show Settings Source # 
Instance details

Defined in Sq.Connection

NFData Settings Source # 
Instance details

Defined in Sq.Connection

Methods

rnf :: Settings -> () #

Eq Settings Source # 
Instance details

Defined in Sq.Connection

settings Source #

Arguments

:: FilePath

Database file path. Not an URI, not :memory:

-> Settings 

Default connection settings.

Transaction

data Transaction (t :: Mode) Source #

A database transaction handle.

  • t indicates whether Read-only or read-Write Statements are supported.
  • Prefer to use a Read-only Transaction if you are solely performing Read-only Statements. It will be more efficient in concurrent settings.
  • Obtain with readTransaction or commitTransaction. Or, if you are testing, with rollbackTransaction.
  • If you have access to a Transaction within its intended scope, then you can assume that a database transaction has started, and will eventually be automatically commited or rolled back as requested when it was obtained.
  • It's safe and efficient to use a Transaction concurrently as is. Concurrency is handled internally.

Instances

Instances details
Show (Transaction t) Source # 
Instance details

Defined in Sq.Connection

NFData (Transaction t) Source # 
Instance details

Defined in Sq.Connection

Methods

rnf :: Transaction t -> () #

readTransaction :: forall (mode :: Mode). Pool mode -> Acquire (Transaction 'Read) Source #

Acquire a read-only transaction.

commitTransaction :: Pool 'Write -> Acquire (Transaction 'Write) Source #

Acquire a read-write transaction where changes are finally commited to the database unless there is an unhandled exception during the transaction, in which case they are rolled back.

rollbackTransaction :: Pool 'Write -> Acquire (Transaction 'Write) Source #

Acquire a read-write transaction where changes are always rolled back. This is mostly useful for testing purposes.

Resources

Sq relies heavily on Acquire for safe resource management in light of concurrency and dependencies between resources.

As a user of Sq, you mostly just have to figure out how to obtain a Pool. For that, you will probably benefit use one of these functions:

If you have no idea what I'm talking about, just use with. Here is an example:

with tempPool \(pool :: Pool 'Write) ->
    -- Here use pool as necessary.
    -- The resources associated with it will be
    -- automatically released after leaving this scope.

Now that you have a Pool, try to solve your problems within Transactional by means of read, commit or rollback.

However, if you need to interleave IO actions while streaming result rows out of the database, Transactional won't be enough. You will need to use foldIO or streamIO.

uith :: MonadUnliftIO m => Acquire a -> (a -> m b) -> m b Source #

Savepoint

data Savepoint Source #

See savepoint, savepointRollback and savepointRelease.

Instances

Instances details
Show Savepoint Source # 
Instance details

Defined in Sq.Connection

NFData Savepoint Source # 
Instance details

Defined in Sq.Connection

Methods

rnf :: Savepoint -> () #

savepoint :: MonadIO m => Transaction 'Write -> m Savepoint Source #

Obtain savepoint to which one can later savepointRollback or savepointRelease.

savepointRollback :: MonadIO m => Savepoint -> m () Source #

Disregard all the changes that happened to the Transaction related to this Savepoint since the time it was obtained through savepoint.

savepointRelease :: MonadIO m => Savepoint -> m () Source #

Release a Savepoint so that it, together with any previous Savepoints on the same Transaction, become unreachable to future uses of savepointRollback or savepointRelease.

Miscellaneuos

data Retry Source #

Used as the r type-parameter in Transactional g r t a.

Constructors

NoRetry 
Retry 

Instances

Instances details
Show Retry Source # 
Instance details

Defined in Sq.Transactional

Methods

showsPrec :: Int -> Retry -> ShowS #

show :: Retry -> String #

showList :: [Retry] -> ShowS #

Eq Retry Source # 
Instance details

Defined in Sq.Transactional

Methods

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

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

Ord Retry Source # 
Instance details

Defined in Sq.Transactional

Methods

compare :: Retry -> Retry -> Ordering #

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

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

(>) :: Retry -> Retry -> Bool #

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

max :: Retry -> Retry -> Retry #

min :: Retry -> Retry -> Retry #

data BindingName Source #

A non-empty list of Names that can be rendered as Input or Output parameters in a Statement.

As a user of Sq, you never construct a BindingName manually. Rather, uses of input and output build one for you from its Name constituents. BindingNames are only exposed to you through ErrInput, ErrOutput and ErrStatement.

data Mode Source #

Constructors

Read
Write

Instances

Instances details
Show Mode Source # 
Instance details

Defined in Sq.Mode

Methods

showsPrec :: Int -> Mode -> ShowS #

show :: Mode -> String #

showList :: [Mode] -> ShowS #

ToValue Mode Source # 
Instance details

Defined in Sq.Mode

Methods

value :: Mode -> Value #

Eq Mode Source # 
Instance details

Defined in Sq.Mode

Methods

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

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

Ord Mode Source # 
Instance details

Defined in Sq.Mode

Methods

compare :: Mode -> Mode -> Ordering #

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

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

(>) :: Mode -> Mode -> Bool #

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

max :: Mode -> Mode -> Mode #

min :: Mode -> Mode -> Mode #

class SubMode (sup :: Mode) (sub :: Mode) Source #

Instances

Instances details
SubMode 'Read 'Read Source # 
Instance details

Defined in Sq.Mode

(TypeError ('Text "Write mode is not a subset of Read mode") :: Constraint) => SubMode 'Read 'Write Source # 
Instance details

Defined in Sq.Mode

SubMode 'Write 'Read Source # 
Instance details

Defined in Sq.Mode

SubMode 'Write 'Write Source # 
Instance details

Defined in Sq.Mode

data Null Source #

The NULL SQL datatype.

Mostly useful if you want to encode or decode a literal NULL value through EncodeDefault and DecodeDefault instances.

However, often you can benefit from encodeMaybe and decodeMaybe instead.

Constructors

Null 

Instances

Instances details
Monoid Null Source # 
Instance details

Defined in Sq.Null

Methods

mempty :: Null #

mappend :: Null -> Null -> Null #

mconcat :: [Null] -> Null #

Semigroup Null Source # 
Instance details

Defined in Sq.Null

Methods

(<>) :: Null -> Null -> Null #

sconcat :: NonEmpty Null -> Null #

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

Show Null Source # 
Instance details

Defined in Sq.Null

Methods

showsPrec :: Int -> Null -> ShowS #

show :: Null -> String #

showList :: [Null] -> ShowS #

Eq Null Source # 
Instance details

Defined in Sq.Null

Methods

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

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

Ord Null Source # 
Instance details

Defined in Sq.Null

Methods

compare :: Null -> Null -> Ordering #

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

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

(>) :: Null -> Null -> Bool #

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

max :: Null -> Null -> Null #

min :: Null -> Null -> Null #

DecodeDefault Null Source #

NullColumn.

Instance details

Defined in Sq.Decoders

EncodeDefault Null Source #

NullColumn.

Instance details

Defined in Sq.Encoders

Errors

newtype ErrEncode Source #

See Encode.

Constructors

ErrEncode SomeException 

Instances

Instances details
Exception ErrEncode Source # 
Instance details

Defined in Sq.Encoders

Show ErrEncode Source # 
Instance details

Defined in Sq.Encoders

data ErrInput Source #

See Encode.

Instances

Instances details
Exception ErrInput Source # 
Instance details

Defined in Sq.Input

Show ErrInput Source # 
Instance details

Defined in Sq.Input

data ErrOutput Source #

Instances

Instances details
Exception ErrOutput Source # 
Instance details

Defined in Sq.Output

Show ErrOutput Source # 
Instance details

Defined in Sq.Output

data ErrStatement Source #

Constructors

ErrStatement_DuplicateColumnName BindingName

A same column name appears twice or more in the raw SQL.

data ErrRows Source #

Constructors

ErrRows_TooFew

Fewer rows than requested were available.

ErrRows_TooMany

More rows than requested were available.

Instances

Instances details
Exception ErrRows Source # 
Instance details

Defined in Sq.Connection

Show ErrRows Source # 
Instance details

Defined in Sq.Connection

Eq ErrRows Source # 
Instance details

Defined in Sq.Connection

Methods

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

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

Re-exports

data SQLData #

Instances

Instances details
Generic SQLData 
Instance details

Defined in Database.SQLite3

Associated Types

type Rep SQLData 
Instance details

Defined in Database.SQLite3

Methods

from :: SQLData -> Rep SQLData x #

to :: Rep SQLData x -> SQLData #

Show SQLData 
Instance details

Defined in Database.SQLite3

Eq SQLData 
Instance details

Defined in Database.SQLite3

Methods

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

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

DecodeDefault SQLData Source #

Literal SQLData Decode.

Instance details

Defined in Sq.Decoders

EncodeDefault SQLData Source #

Literal SQLData Encode.

Instance details

Defined in Sq.Encoders

type Rep SQLData 
Instance details

Defined in Database.SQLite3

data SQLVFS #

These VFS names are used when using the open2 function.

Instances

Instances details
Show SQLVFS 
Instance details

Defined in Database.SQLite3

Eq SQLVFS 
Instance details

Defined in Database.SQLite3

Methods

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

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