polysemy-hasql-0.0.1.0: Polysemy effects for databases
Safe HaskellSafe-Inferred
LanguageHaskell2010

Polysemy.Hasql

Synopsis

Introduction

This library provides Hasql-specific interpreters for the effects in Polysemy.Db

Hasql interpreters for Polysemy.Db

interpretQStoreDb :: forall f q d e r. ResultShape d (f d) => Member (DbTable d !! e) r => TableSchema d -> QuerySchema q d -> InterpreterFor (QStore f q d !! e) r Source #

interpretQStoreXa :: forall f err i d r. ResultShape d (f d) => Members [Scoped ConnectionSource (DbTable d !! err), Log, Embed IO] r => TableSchema d -> QuerySchema i d -> InterpreterFor (Scoped Connection (QStore f i d !! err) !! err) r Source #

interpretQStores :: forall f err q d r. ResultShape d (f d) => Members [Scoped ConnectionSource (DbTable d !! err), DbTable d !! err, Log, Embed IO] r => TableSchema d -> QuerySchema q d -> InterpretersFor [QStore f q d !! err, Scoped Connection (QStore f q d !! err) !! err] r Source #

interpretStoreDb :: forall i d e r. Member (StoreTable i d !! e) r => TableSchema (Uid i d) -> QuerySchema i (Uid i d) -> InterpreterFor (Store i d !! e) r Source #

interpretStoreXa :: forall err i d r. Members [Scoped ConnectionSource (DbTable (Uid i d) !! err), Log, Embed IO] r => TableSchema (Uid i d) -> QuerySchema i (Uid i d) -> InterpreterFor (Scoped Connection (Store i d !! err) !! err) r Source #

interpretStores :: forall err i d r. Members [Scoped ConnectionSource (DbTable (Uid i d) !! err), StoreTable i d !! err, Log, Embed IO] r => TableSchema (Uid i d) -> QuerySchema i (Uid i d) -> InterpretersFor [Store i d !! err, Scoped Connection (Store i d !! err) !! err] r Source #

interpretQuery :: forall result query proj table r. ResultShape proj result => Member (DbTable table !! DbError) r => Projection proj table -> QuerySchema query table -> InterpreterFor (Query query result !! DbError) r Source #

interpretQueryDd :: forall result query proj table r. MkTableSchema proj => MkTableSchema table => CheckedProjection proj table => CheckQuery query table => ResultShape (DdType proj) result => Member (DbTable (DdType table) !! DbError) r => Dd table -> Dd proj -> Dd query -> InterpreterFor (Query (DdType query) result !! DbError) r Source #

Database effects

data Database :: Effect Source #

This effect provides the capability to execute Statements. Additionally, it exposes managed access to the raw Connection resource and automatic table initialization as higher-order actions.

With the minimal stack, an SQL query can be executed in two fashions. One is to use automatically derived codecs:

prog :: Member Database r => Sem r ()
prog = do
  user :: Maybe User <- Database.sql () "select * from users where id = 1"
  user :: [User] <- Database.sql ("guest", True) "select * from users where name = $1 and locked = $2"

The other works by providing an explicit Statement:

statement :: Statement Text User
statement = ...

prog :: Member Database r => Sem r ()
prog = do
  user <- Database.runStatement "guest" statement

For documentation on the individual constructors, see the module page.

type StoreTable i a = DbTable (Uid i a) Source #

abort :: forall res r a. Member (Transaction res) r => Sem r a Source #

Database interpeters

interpretTableViewDd :: CheckedProjection view table => Member (DbTable (DdType table) !! DbError) r => Dd table -> Dd view -> InterpreterFor (DbTable (DdType view) !! DbError) r Source #

Misc combinators

queryVia :: (q1 -> Sem (Stop DbError ': r) q2) -> (r2 -> Sem (Stop DbError ': r) r1) -> Sem ((Query q1 r1 !! DbError) ': r) a -> Sem ((Query q2 r2 !! DbError) ': r) a Source #

mapQuery :: (q1 -> Sem (Stop DbError ': r) q2) -> Sem ((Query q1 result !! DbError) ': r) a -> Sem ((Query q2 result !! DbError) ': r) a Source #

Misc

interpretAtomicStateDb :: Members [DbTable d !! e, Error InitDbError, Mask, Resource, Race, Embed IO] r => TableSchema d -> Sem r d -> InterpreterFor (AtomicState d !! e) r Source #

Interpret AtomicState as a singleton table.

Given an action that produces an initial value, every state action reads the value from the database and writes it back.

interpretReaderDb :: forall d e r. Member (DbTable d !! e) r => TableSchema d -> Sem r d -> InterpreterFor (Reader d !! e) r Source #

Interpret Reader as a singleton table.

Given an initial value, every state action reads the value from the database, potentially writing it on first access.