| Safe Haskell | None |
|---|---|
| Language | GHC2021 |
Sq
Description
High-level SQLite client library
import qualified Sq
Things currently supported:
- Type-safe encoding of SQL query parameters and columns (
Encode,Input). - Type-safe decoding of SQL output rows and columns (
Decode,Output). - Type-safe concurrent connections with read and write database access
(
Pool). - Type-safe
STM-like transactional interactions with the database, includingretry-like,TVar-like, andcatchSTM-like tools (Transactional,retry,Ref). - Type-safe distinction between
Read-only and read-Writethings. - Type-safe streaming and interleaving of
IOwith output rows (streamIO,foldIO). - Type-safe resource management (via
Acquire, seenew,with,uith). - Manual transactional migrations (
migrate). Savepoints.- A lot of logging.
Things not supported yet:
- Type-safe
SQL. - Probably other things.
If you have questions or suggestions, just say so at https://github.com/k0001/hs-sq/issues.
Note: This library is young and needs more testing.
Synopsis
- data Statement (s :: Mode) i o
- readStatement :: Input i -> Output o -> SQL -> Statement 'Read i o
- writeStatement :: Input i -> Output o -> SQL -> Statement 'Write i o
- data SQL
- sql :: QuasiQuoter
- data Input i
- encode :: Name -> Encode i -> Input i
- input :: Name -> Input i -> Input i
- newtype Encode a = Encode (a -> Either ErrEncode SQLData)
- encodeRefine :: HasCallStack => (a -> Either String b) -> Encode b -> Encode a
- class EncodeDefault a where
- encodeDefault :: Encode a
- encodeMaybe :: Encode a -> Encode (Maybe a)
- encodeEither :: Encode a -> Encode b -> Encode (Either a b)
- encodeSizedIntegral :: (Integral a, Bits a, HasCallStack) => Encode a
- encodeAeson :: (a -> Value) -> Encode a
- encodeBinary :: (a -> Put) -> Encode a
- encodeShow :: Show a => Encode a
- data Output o
- decode :: Name -> Decode o -> Output o
- output :: Name -> Output o -> Output o
- newtype Decode a = Decode (SQLData -> Either ErrDecode a)
- decodeRefine :: HasCallStack => (a -> Either String b) -> Decode a -> Decode b
- class DecodeDefault a where
- decodeDefault :: Decode a
- decodeMaybe :: Decode a -> Decode (Maybe a)
- decodeEither :: Decode a -> Decode b -> Decode (Either a b)
- decodeSizedIntegral :: (Integral a, Bits a) => Decode a
- decodeAeson :: (Value -> Parser a) -> Decode a
- decodeBinary :: Get a -> Decode a
- decodeRead :: Read a => Decode a
- data Name
- name :: Text -> Either String Name
- data Transactional (g :: k) (r :: Retry) (t :: Mode) a
- read :: forall {k} m (p :: Mode) a. (MonadIO m, SubMode p 'Read) => Pool p -> (forall (g :: k). Transactional g 'Retry 'Read a) -> m a
- commit :: forall {k} m a. MonadIO m => Pool 'Write -> (forall (g :: k). Transactional g 'Retry 'Write a) -> m a
- rollback :: forall {k} m a. MonadIO m => Pool 'Write -> (forall (g :: k). Transactional g 'Retry 'Write a) -> m a
- embed :: forall {k} m (t :: Mode) a. MonadIO m => Transaction t -> (forall (g :: k). Transactional g 'NoRetry t a) -> m a
- data Ref (g :: k) a
- retry :: forall {k} (g :: k) (t :: Mode) a. Transactional g 'Retry t a
- 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
- one :: forall {k} o i (t :: Mode) (s :: Mode) (g :: k) (r :: Retry). SubMode t s => Statement s i o -> i -> Transactional g r t o
- maybe :: forall {k} o i (t :: Mode) (s :: Mode) (g :: k) (r :: Retry). SubMode t s => Statement s i o -> i -> Transactional g r t (Maybe o)
- zero :: forall {k} o i (t :: Mode) (s :: Mode) (g :: k) (r :: Retry). SubMode t s => Statement s i o -> i -> Transactional g r t ()
- some :: forall {k} o i (t :: Mode) (s :: Mode) (g :: k) (r :: Retry). SubMode t s => Statement s i o -> i -> Transactional g r t (Int64, NonEmpty o)
- list :: forall {k} o i (t :: Mode) (s :: Mode) (g :: k) (r :: Retry). SubMode t s => Statement s i o -> i -> Transactional g r t (Int64, [o])
- fold :: forall {k} o z i (t :: Mode) (s :: Mode) (g :: k) (r :: Retry). SubMode t s => Fold o z -> Statement s i o -> i -> Transactional g r t z
- foldM :: forall {k} o z i (t :: Mode) (s :: Mode) (g :: k) (r :: Retry). SubMode t s => FoldM (Transactional g r t) o z -> Statement s i o -> i -> Transactional g r t z
- streamIO :: forall o i (t :: Mode) (s :: Mode) (m :: Type -> Type). (MonadResource m, SubMode t s) => Acquire (Transaction t) -> Statement s i o -> i -> Stream (Of o) m ()
- foldIO :: forall o z i (t :: Mode) (s :: Mode) m. (MonadIO m, MonadMask m, SubMode t s) => FoldM m o z -> Acquire (Transaction t) -> Statement s i o -> i -> m z
- data Pool (p :: Mode)
- readPool :: Df1 -> Settings -> Acquire (Pool 'Read)
- writePool :: Df1 -> Settings -> Acquire (Pool 'Write)
- tempPool :: Df1 -> Acquire (Pool 'Write)
- subPool :: Pool 'Write -> Pool 'Read
- data Settings = Settings {}
- settings :: FilePath -> Settings
- data Transaction (t :: Mode)
- readTransaction :: forall (mode :: Mode). Pool mode -> Acquire (Transaction 'Read)
- commitTransaction :: Pool 'Write -> Acquire (Transaction 'Write)
- rollbackTransaction :: Pool 'Write -> Acquire (Transaction 'Write)
- new :: MonadResource m => Acquire a -> m a
- with :: (MonadMask m, MonadIO m) => Acquire a -> (a -> m b) -> m b
- uith :: MonadUnliftIO m => Acquire a -> (a -> m b) -> m b
- data Savepoint
- savepoint :: MonadIO m => Transaction 'Write -> m Savepoint
- savepointRollback :: MonadIO m => Savepoint -> m ()
- savepointRelease :: MonadIO m => Savepoint -> m ()
- migrate :: forall a m. (MonadIO m, MonadMask m) => Pool 'Write -> MigrationsTable -> [Migration] -> ([MigrationId] -> m a) -> m a
- migration :: MigrationId -> (forall (g :: k). Transactional g 'NoRetry 'Write ()) -> Migration
- data Migration
- data MigrationId
- data MigrationsTable
- data Retry
- data BindingName
- data Mode
- class SubMode (sup :: Mode) (sub :: Mode)
- data Null = Null
- newtype ErrEncode = ErrEncode SomeException
- data ErrInput = ErrInput BindingName ErrEncode
- data ErrDecode
- data ErrOutput
- data ErrStatement = ErrStatement_DuplicateColumnName BindingName
- data ErrRows
- data SQLData
- = SQLInteger !Int64
- | SQLFloat !Double
- | SQLText !Text
- | SQLBlob !ByteString
- | SQLNull
- data SQLVFS
Statement
data Statement (s :: Mode) i o Source #
- A SQL statement taking a value
ias input and producing rows ofovalues as output. sindicates whether the statement isRead-only or read-Write.- Construct with
readStatementorwriteStatement.
Instances
| Profunctor (Statement s) Source # | |
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 # | |
| Show (Statement s i o) Source # | |
readStatement :: Input i -> Output o -> SQL -> Statement 'Read i o Source #
writeStatement :: Input i -> Output o -> SQL -> Statement 'Write i o Source #
SQL
Raw SQL string. Completely unchecked.
Instances
| IsString SQL Source # | |
Defined in Sq.Statement Methods fromString :: String -> SQL # | |
| Semigroup SQL Source # | |
| Show SQL Source # | Raw SQL string. |
| NFData SQL Source # | |
Defined in Sq.Statement | |
| ToMessage SQL Source # | |
Defined in Sq.Statement | |
| Eq SQL Source # | |
| Ord SQL Source # | |
| HasField "text" SQL Text Source # | Raw SQL string as |
Defined in Sq.Statement | |
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
How to encode all the input to a single Statement.
Instances
| Contravariant Input Source # | |
| Decidable Input Source # | |
| Divisible Input Source # | Left-biased in case of overlapping |
| EncodeDefault i => IsString (Input i) Source # |
|
Defined in Sq.Input Methods fromString :: String -> Input i # | |
| Monoid (Input i) Source # | |
| Semigroup (Input i) Source # | Left-biased in case of overlapping |
| NFData (Input i) Source # | |
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)" :: (EncodeDefaultx) =>StatementWritex ()
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)" :: (EncodeDefaultx,EncodeDefaulty) =>StatementWrite(x, y) ()
Pro-tip: Consider using the IsString instance for Input.
For example, "foo" means .
That is, the last example could be written as follows:encode "foo" encodeDefault
writeStatement(divided"foo" "bar")mempty"INSERT INTO t (a, b) VALUES ($foo, $bar)" :: (EncodeDefaultx,EncodeDefaulty) =>StatementWrite(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) |] ::StatementWrite(Point, Point) ()
Encode
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 Ideally, the type |
encodeRefine :: HasCallStack => (a -> Either String b) -> Encode b -> Encode a Source #
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
| EncodeDefault Void Source # | This is |
Defined in Sq.Encoders Methods | |
| EncodeDefault Int16 Source # | |
Defined in Sq.Encoders Methods | |
| EncodeDefault Int32 Source # | |
Defined in Sq.Encoders Methods | |
| EncodeDefault Int64 Source # | |
Defined in Sq.Encoders Methods | |
| EncodeDefault Int8 Source # | |
Defined in Sq.Encoders Methods | |
| EncodeDefault Word16 Source # | |
Defined in Sq.Encoders Methods | |
| EncodeDefault Word32 Source # | |
Defined in Sq.Encoders Methods | |
| EncodeDefault Word64 Source # |
|
Defined in Sq.Encoders Methods | |
| EncodeDefault Word8 Source # | |
Defined in Sq.Encoders Methods | |
| EncodeDefault Builder Source # | |
Defined in Sq.Encoders Methods | |
| EncodeDefault ByteString Source # | |
Defined in Sq.Encoders Methods | |
| EncodeDefault ByteString Source # | |
Defined in Sq.Encoders Methods | |
| EncodeDefault ShortByteString Source # | |
Defined in Sq.Encoders Methods | |
| EncodeDefault SQLData Source # | |
Defined in Sq.Encoders Methods | |
| EncodeDefault MigrationId Source # | |
Defined in Sq.Migrations Methods | |
| EncodeDefault Null Source # | |
Defined in Sq.Encoders Methods | |
| EncodeDefault Text Source # | |
Defined in Sq.Encoders Methods | |
| EncodeDefault Builder Source # | |
Defined in Sq.Encoders Methods | |
| EncodeDefault Text Source # | |
Defined in Sq.Encoders Methods | |
| EncodeDefault CalendarDiffDays Source # |
PyYmMdD |
Defined in Sq.Encoders Methods | |
| EncodeDefault Day Source # | ISO-8601 in a @ yyyy-mm-dd
|
Defined in Sq.Encoders Methods | |
| EncodeDefault UTCTime Source # |
yyyy-mm-ddThh:mm:ss[.ssssssssssss]+00:00
|
Defined in Sq.Encoders Methods | |
| EncodeDefault CalendarDiffTime Source # |
PyYmMdDThHmMs[.ssssssssssss]S
|
Defined in Sq.Encoders Methods | |
| EncodeDefault LocalTime Source # |
yyyy-mm-ddThh:mm:ss[.ssssssssssss]
|
Defined in Sq.Encoders Methods | |
| EncodeDefault TimeOfDay Source # |
hh:mm:ss[.ssssssssssss]
|
Defined in Sq.Encoders Methods | |
| EncodeDefault TimeZone Source # |
±hh:mm |
Defined in Sq.Encoders Methods | |
| EncodeDefault ZonedTime Source # |
yyyy-mm-ddThh:mm:ss[.ssssssssssss]±hh:mm
|
Defined in Sq.Encoders Methods | |
| EncodeDefault String Source # | |
Defined in Sq.Encoders Methods | |
| EncodeDefault Integer Source # |
|
Defined in Sq.Encoders Methods | |
| EncodeDefault Natural Source # |
|
Defined in Sq.Encoders Methods | |
| EncodeDefault Bool Source # |
|
Defined in Sq.Encoders Methods | |
| EncodeDefault Char Source # | |
Defined in Sq.Encoders Methods | |
| EncodeDefault Double Source # | |
Defined in Sq.Encoders Methods | |
| EncodeDefault Float Source # | |
Defined in Sq.Encoders Methods | |
| EncodeDefault Int Source # | |
Defined in Sq.Encoders Methods | |
| EncodeDefault Word Source # |
|
Defined in Sq.Encoders Methods | |
| EncodeDefault a => EncodeDefault (Maybe a) Source # | See |
Defined in Sq.Encoders Methods encodeDefault :: Encode (Maybe a) Source # | |
| (EncodeDefault a, EncodeDefault b) => EncodeDefault (Either a b) Source # | See |
Defined in Sq.Encoders Methods encodeDefault :: Encode (Either a b) Source # | |
encodeMaybe :: Encode a -> Encode (Maybe a) Source #
a's ColumnType if Just, otherwise NullColumn.
encodeEither :: Encode a -> Encode b -> Encode (Either a b) Source #
a's ColumnType if Left, otherwise b's ColumnType.
encodeSizedIntegral :: (Integral a, Bits a, HasCallStack) => Encode a Source #
IntegerColumn if it fits in Int64, otherwise TextColumn.
encodeAeson :: (a -> Value) -> Encode a Source #
Encodes as TextColumn.
encodeBinary :: (a -> Put) -> Encode a Source #
encodeShow :: Show a => Encode a Source #
Output
How to decode an output row from a single Statement.
- Construct with
decode,IsString. - Nest with
output. - Compose with
Monoid,Functor,Applicative,Alternative,Monad,MonadPlus,MonadFailandMonadThrowtools.
Instances
| MonadFail Output Source # | |
| Alternative Output Source # | |
| Applicative Output Source # | |
| Functor Output Source # | |
| Monad Output Source # | |
| MonadPlus Output Source # | |
| MonadThrow Output Source # | |
| DecodeDefault i => IsString (Output i) Source # | |
Defined in Sq.Output Methods fromString :: String -> Output i # | |
| Monoid o => Monoid (Output o) Source # | |
| Semigroup o => Semigroup (Output o) Source # | |
decode :: Name -> Decode o -> Output o Source #
Decode the column with the given Name.
readStatementmempty(decode"foo"decodeDefault) "SELECT foo FROM t" :: (DecodeDefaultx) =>StatementRead() 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.
readStatementmempty(decode"abc"decodeDefault) "SELECT foo AS abc FROM t" :: (DecodeDefaultx) =>StatementRead() x
Multiple Outputss can be composed with Monoid, Functor, Applicative,
Alternative, Monad, MonadPlus, MonadFail and MonadThrow tools.
readStatementmempty(do foo <-decode"foo"decodeDefaultwhen(foo > 10) dofail"Oh no!" bar <-decode"bar"decodeDefaultpure(foo, bar)) "SELECT foo, bar FROM t" :: (DecodeDefaulty) =>StatementRead() (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" :: (DecodeDefaultx,DecodeDefaulty) =>StatementRead() (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:
readStatementmempty(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|] ::StatementRead() (Point, Point)
Decode
How to decode a single SQLite column value into a Haskell value of type
a.
Instances
| MonadFail Decode Source # | |
Defined in Sq.Decoders | |
| Alternative Decode Source # | Leftmost result on success, rightmost error on failure. |
| Applicative Decode Source # | |
| Functor Decode Source # | |
| Monad Decode Source # | |
| MonadPlus Decode Source # | Leftmost result on success, rightmost error on failure. |
| MonadThrow Decode Source # | |
Defined in Sq.Decoders Methods throwM :: (HasCallStack, Exception e) => e -> Decode a # | |
| Monoid a => Monoid (Decode a) Source # |
|
| Semigroup a => Semigroup (Decode a) Source # | ( |
decodeRefine :: HasCallStack => (a -> Either String b) -> Decode a -> Decode b Source #
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
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 #
decodeEitherda db = fmapLeftda<|>fmapRightdb
decodeBinary :: Get a -> Decode a Source #
decodeRead :: Read a => Decode a Source #
Name
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 #
groups together multiple interactions with a same
Transactional g r t a that finally produce a value of type Transaction ta. Think of
Transactional as if it was STM.
gis an ephemeral tag for the whole inteaction group that preventsRefs andstreams from escaping its intended scope (likeSTdoes it). Just ignore it, it will always be polymorphic.rsays whether theTransactionalcould potentially be retried from scratch in order to observe a new snapshot of the database (likeSTMdoes it). Learn more about this inRetry.tsays whether theTransactionalcould potentially performWriteorRead-only operations.ais the Haskell value finally produced by a successfu execution of theTransactional.
To execute a Transactional you will normally use one of read or
commit (or rollback or embed, but those are less common).
-- We are usingcommitto execute theTransactional. This means -- that theTransactionalwill have read andWritecapabilities, that -- it canretry, and that ultimately, unless there are unhandled -- exceptions, the changes will be commited to the database. Sq.commitpool do -- We can executeWriteStatements: userId1 <- Sq.oneinsertUser "haskell@example.com" -- AndReadStatements: userId2 <- Sq.onegetUserIdByEmail "haskell@example.com" -- We haveMonadFailtoo:when(userId1 /= userId2) dofail"Something unexpected happened!" -- We also haveRefs, which work just likeTVars: ref <-newRef(0 ::Int) --catchbehaves likecatchSTM, undoing changes toRefs -- and to the database itself when the original action fails: userId3 <-catch-- Something will fail ... (domodifyRefref (+ 1) _ <- Sq.oneinsertUser "sqlite@example.com"throwMFakeException123) -- ... but there is a catch! (\FakeException123 -> do -- The observable universe has been reset to what it -- was before thecatch: Sq.zerogetUserIdByEmail "sqlite@example.com"modifyRefref (+ 10)) -- Only the effects from the exception handling function were preserved: Sq.zerogetUserIdByEmail "sqlite@example.com" 10 <-readRefref --retryand its synonymsmzeroandemptynot only discard changes as --catchdoes, but they also cause the ongoingTransactionto be -- discarded, and the entireTransactionalto be executed again on a -- brand newTransactionobserving a new snapshot of the database. For -- example, the following code will keep retrying the wholeTransactional-- until the user with the specified email exists. userId4 <- Sq.maybegetUserIdByEmail "nix@example.com" >>= \caseJustx ->purexNothing->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,mzeroandemptycan be handled by means of<|>andmplus, -- or its synonymorElse.False<-mplus(writeRefref 8 >>mzero>>pureTrue) (pureFalse) -- The recentwriteRefto 8 on theretryiedTransactionalwas discarded: 10 <-readRefrefpure()
Instances
| MonadFail (Transactional g r t) Source # | |||||
Defined in Sq.Transactional Methods fail :: String -> Transactional g r t a # | |||||
| Alternative (Transactional g 'Retry t) Source # |
| ||||
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 # | |||||
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 # | |||||
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 # | |||||
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 # |
| ||||
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 # |
In Note: This instance's | ||||
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 # | |||||
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 # | |||||
Defined in Sq.Transactional Methods throwM :: (HasCallStack, Exception e) => e -> Transactional g r t a # | |||||
| MonadAtomicRef (Transactional g r t) Source # | |||||
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. | ||||
Defined in Sq.Transactional Associated Types
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 # | |||||
Defined in Sq.Transactional | |||||
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.
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.
- NOTICE Contrary to
read,commitorrollback, thisTransactionalcannotretry, as doing so would require cancelling the ongoingTransaction.
Like TVar, but you can use it inside Transactional through the
MonadRef and MonadAtomicRef vocabulary.
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,emptyandmzeroall do fundamentally the same thing, howeverretryleads to better type inferrence because it forces thertype-parameter to beRetry.- NOTICE You only need to use
mzeroif you need access to a newer database snapshot. If all you want to do is undo someReftransformation effects, or undo database changes, then usecatchwhich doesn't abandon theTransaction. - WARNING If we keep
retrying and the database never changes, then we will be stuck in a loop forever. To mitigate this, when executing theTransactionalthroughread,commitorrollback, you may want to usetimeoutto 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 #
Querying
one :: forall {k} o i (t :: Mode) (s :: Mode) (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.
- Throws
ErrRows_TooFewif zero rows,ErrRows_TooManyif more than one row.
maybe :: forall {k} o i (t :: Mode) (s :: Mode) (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.
- Throws
ErrRows_TooManyif more than one row.
zero :: forall {k} o i (t :: Mode) (s :: Mode) (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.
- Throws
ErrRows_TooManyif more than zero rows.
some :: forall {k} o i (t :: Mode) (s :: Mode) (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.
- Returns the length of the
NonEmptylist, too. - Throws
ErrRows_TooFewif zero rows.
list :: forall {k} o i (t :: Mode) (s :: Mode) (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} o z i (t :: Mode) (s :: Mode) (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} o z i (t :: Mode) (s :: Mode) (g :: k) (r :: Retry). 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.
- For a non-
Transactionalversion of this function, seefoldIO.
Interleaving
Arguments
| :: forall o i (t :: Mode) (s :: Mode) (m :: Type -> Type). (MonadResource m, SubMode t s) | |
| => Acquire (Transaction t) | How to acquire the If you want this Otherwise, if you already obtained a |
| -> Statement s i o | |
| -> i | |
| -> Stream (Of o) m () | A We use the |
Stream the output rows from a Statement in a way that allows
interleaving IO actions.
- An exclusive lock will be held on the
Transactionwhile theStreamis producing rows. - The
Transactionlock is released automatically if theStreamis consumed until exhaustion. - If you won't consume the
Streamuntil exhaustion, then be sure to exitmby means ofrunResourceTor similar as soon as possible in order to release theTransactionlock.
Arguments
| :: forall o z i (t :: Mode) (s :: Mode) m. (MonadIO m, MonadMask m, SubMode t s) | |
| => FoldM m o z | |
| -> Acquire (Transaction t) | How to acquire the If you want this Otherwise, if you already obtained a |
| -> Statement s i o | |
| -> i | |
| -> m z |
Pool
Settings
SQLite connection settings.
Constructors
| Settings | |
Default connection settings.
Transaction
data Transaction (t :: Mode) Source #
A database transaction handle.
tindicates whetherRead-only or read-WriteStatements are supported.- Prefer to use a
Read-onlyTransactionif you are solely performingRead-onlyStatements. It will be more efficient in concurrent settings. - Obtain with
readTransactionorcommitTransaction. Or, if you are testing, withrollbackTransaction. - If you have access to a
Transactionwithin 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
Transactionconcurrently as is. Concurrency is handled internally.
Instances
| Show (Transaction t) Source # | |
Defined in Sq.Connection Methods showsPrec :: Int -> Transaction t -> ShowS # show :: Transaction t -> String # showList :: [Transaction t] -> ShowS # | |
| NFData (Transaction t) Source # | |
Defined in Sq.Connection Methods rnf :: Transaction t -> () # | |
readTransaction :: forall (mode :: Mode). Pool mode -> Acquire (Transaction 'Read) Source #
commitTransaction :: Pool 'Write -> Acquire (Transaction 'Write) Source #
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.
- You may need this function if you are using one of
embed,foldIOorstreamIO. Otherwise, just usecommit. - An equivalent behavior can be achieved by
bracketing changes betweensavepointandrollbackToin acommitTransactionting transaction. Or by usingthrowMandcatchwithinTransactional. However, using arollbackTransactionis much faster than usingSavepoints.
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:
withfor integrating withMonadMaskfrom theexceptionslibrary.newfor integrating withMonadResourcefrom theresourcetlibrary.uithfor integrating withMonadUnliftIOfrom theunliftiolibrary.
If you have no idea what I'm talking about, just use with.
Here is an example:
withtempPool\(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.
new :: MonadResource m => Acquire a -> m a Source #
Acquire through MonadResource.
new=fmapsnd. Data.Acquire.allocateAcquire
uith :: MonadUnliftIO m => Acquire a -> (a -> m b) -> m b Source #
Acquire through MonadUnliftIO.
uith= Data.Acquire.with
Savepoint
See savepoint, savepointRollback and savepointRelease.
- WARNING safely dealing with
Savepoints can be tricky. Consider usingcatchonTransactional, which is implemented usingSavepointand does the right thing.
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.
- Trying to
savepointRollbackaSavepointthat isn't reachable anymore throws an exception. - A
Savepointstops being reachable when the relevantTransactionends, or when asavepointRollbackto an earlierSavepointon the sameTransactionis performed, or when it or a laterSavepointis explicitely released throughsavepointRelease.
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.
- Trying to
savepointReleaseaSavepointthat isn't reachable anymore throws an exception. - A
Savepointstops being reachable when the relevantTransactionends, or when asavepointRollbackto an earlierSavepointon the sameTransactionis performed, or when it or a laterSavepointis explicitely released throughsavepointRelease.
Migrations
List all the
Migrations in chronological order. EachMigrationis aTransactionalaction on the database, identified by a uniqueMigrationId. Construct withmigration.migrations :: [Sq.
Migration] migrations = [ Sq.migration"create users table" createUsersTable , Sq.migration"add email column to users" addUserEmailColumn , Sq.migration"create articles table" createArticlesTable , ... more migrations ... ]Run any
Migrations that haven't been run yet, if necessary, by performingmigrateonce as soon as you obtain yourWriteconnectionPool.migratewill enforce that theMigrationIds, be unique, and will make sure that any migration history in theMigrationsTableis compatible with the specifiedMigrations.Sq.
migratepool "migrations" migrations \case [] -> ... No migrations will run. ... mIds -> ... Some migrations will run. Maybe backup things here? ...- Don't change your
MigrationIds over time. If you do, then the history inMigrationsTablewill become unrecognizable bymigrate. Also, avoid having theTransactionalcode in eachMigrationuse your domain types and functions, as doing so may force you to alter pastTransactionalif your domain types and functions change. Ideally, you should write eachMigrationin such a way that you never have to modify them in the future.
Arguments
| :: forall a m. (MonadIO m, MonadMask m) | |
| => Pool 'Write | Connection |
| -> MigrationsTable | Name of the table where the registry of ran |
| -> [Migration] |
|
| -> ([MigrationId] -> m a) | This will be performed while the write transaction is active,
letting you know which This can be a good place to perform a backup of the database if
necessary. Presumably, Don't try to acquire a |
| -> m a |
Run all the migrations in Migrations that haven't been run yet.
- If the
MigrationIds are not compatible with the current migration history as reported byMigrationsTable, there will be an exception. - If
MigrationsTabledoesn't exist, it will be created. - All the changes are run in a single
Transaction, including those toMigrationsTable.
Arguments
| :: MigrationId | |
| -> (forall (g :: k). Transactional g 'NoRetry 'Write ()) | Notice the |
| -> Migration |
Define a single Migration that, when executed, will perform
the given Transactional.
- See
Migration.
A single Migration consisting of a Transactional action uniquely
identified by a MigrationId.
Instances
| HasField "id" Migration MigrationId Source # | |
Defined in Sq.Migrations Methods getField :: Migration -> MigrationId # | |
data MigrationId Source #
Unique identifier for a Migration within a MigrationsTable.
- You are supposed to type these statically, so construct a
MigrationIdby typing down the literal string.
Instances
data MigrationsTable Source #
Name of the database table keeping a registry of executed Migrations, by
their MigrationId.
Instances
Miscellaneuos
Used as the r type-parameter in .Transactional g r t a
- If the
Transactionaluses anyAlternativeorMonadPlusfeature, thenrmust beRetry, and theTransactionalcan only be executed throughread,commitorrollback. - Otherwise,
rcan beNoRetry. In that case,embedcan also be used to execute theTransactional.
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.
Instances
| Semigroup BindingName Source # | |
Defined in Sq.Names Methods (<>) :: BindingName -> BindingName -> BindingName # sconcat :: NonEmpty BindingName -> BindingName # stimes :: Integral b => b -> BindingName -> BindingName # | |
| Show BindingName Source # | |
Defined in Sq.Names Methods showsPrec :: Int -> BindingName -> ShowS # show :: BindingName -> String # showList :: [BindingName] -> ShowS # | |
| NFData BindingName Source # | |
Defined in Sq.Names Methods rnf :: BindingName -> () # | |
| Eq BindingName Source # | |
Defined in Sq.Names | |
| Ord BindingName Source # | |
Defined in Sq.Names Methods compare :: BindingName -> BindingName -> Ordering # (<) :: BindingName -> BindingName -> Bool # (<=) :: BindingName -> BindingName -> Bool # (>) :: BindingName -> BindingName -> Bool # (>=) :: BindingName -> BindingName -> Bool # max :: BindingName -> BindingName -> BindingName # min :: BindingName -> BindingName -> BindingName # | |
Constructors
| Read |
|
| Write |
|
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 |
Errors
See Encode.
Constructors
| ErrEncode SomeException |
Instances
| Exception ErrEncode Source # | |
Defined in Sq.Encoders Methods toException :: ErrEncode -> SomeException # fromException :: SomeException -> Maybe ErrEncode # displayException :: ErrEncode -> String # | |
| Show ErrEncode Source # | |
See Encode.
Constructors
| ErrInput BindingName ErrEncode |
Instances
| Exception ErrInput Source # | |
Defined in Sq.Input Methods toException :: ErrInput -> SomeException # fromException :: SomeException -> Maybe ErrInput # displayException :: ErrInput -> String # | |
| Show ErrInput Source # | |
See Decode.
Constructors
| ErrDecode_Type ColumnType [ColumnType] | Received |
| ErrDecode_Fail SomeException |
Instances
| Exception ErrDecode Source # | |
Defined in Sq.Decoders Methods toException :: ErrDecode -> SomeException # fromException :: SomeException -> Maybe ErrDecode # displayException :: ErrDecode -> String # | |
| Show ErrDecode Source # | |
Constructors
| ErrOutput_ColumnValue BindingName ErrDecode | Error from |
| ErrOutput_ColumnMissing BindingName | Missing column name in the raw |
| ErrOutput_Fail SomeException | Error from |
Instances
| Exception ErrOutput Source # | |
Defined in Sq.Output Methods toException :: ErrOutput -> SomeException # fromException :: SomeException -> Maybe ErrOutput # displayException :: ErrOutput -> String # | |
| Show ErrOutput Source # | |
data ErrStatement Source #
Constructors
| ErrStatement_DuplicateColumnName BindingName | A same column name appears twice or more in the raw |
Instances
| Exception ErrStatement Source # | |
Defined in Sq.Connection Methods toException :: ErrStatement -> SomeException # fromException :: SomeException -> Maybe ErrStatement # displayException :: ErrStatement -> String # | |
| Show ErrStatement Source # | |
Defined in Sq.Connection Methods showsPrec :: Int -> ErrStatement -> ShowS # show :: ErrStatement -> String # showList :: [ErrStatement] -> ShowS # | |
| Eq ErrStatement Source # | |
Defined in Sq.Connection | |
Constructors
| ErrRows_TooFew | Fewer rows than requested were available. |
| ErrRows_TooMany | More rows than requested were available. |
Instances
| Exception ErrRows Source # | |
Defined in Sq.Connection Methods toException :: ErrRows -> SomeException # fromException :: SomeException -> Maybe ErrRows # displayException :: ErrRows -> String # | |
| Show ErrRows Source # | |
| Eq ErrRows Source # | |
Re-exports
Constructors
| SQLInteger !Int64 | |
| SQLFloat !Double | |
| SQLText !Text | |
| SQLBlob !ByteString | |
| SQLNull |
Instances
These VFS names are used when using the open2 function.