data-basic-0.3.0.0: A database library with a focus on ease of use, type safety and useful error messages

Safe HaskellNone
LanguageHaskell2010

Internal.Control.Effects.Basic

Synopsis

Documentation

newtype SqlRequest a Source #

Constructors

SqlRequest 

Instances

Show (SqlRequest k a) Source # 

Methods

showsPrec :: Int -> SqlRequest k a -> ShowS #

show :: SqlRequest k a -> String #

showList :: [SqlRequest k a] -> ShowS #

data Basic Source #

Instances

Effect Basic Source # 

Associated Types

data EffMethods Basic (m :: * -> *) :: * #

type CanLift Basic (t :: (* -> *) -> * -> *) :: Constraint #

data EffMethods Basic Source # 
data EffMethods Basic = BasicMethods {}
type CanLift Basic t Source # 

runSql :: MonadEffect Basic m => forall a. FromRow a => SqlRequest a -> m [a] Source #

handleBasicPsqlWithLogging :: forall m a. (MonadEffects '[Logging, Signal BasicException Query] m, MonadIO m) => Connection -> RuntimeImplemented Basic m a -> m a Source #

Handles SQL by querying a PostgreSQL database. Leaves logs unhandled.

throwBasicToIO :: forall m a. MonadIO m => ExceptT BasicException m a -> m a Source #

handleBasicPsql :: MonadIO m => Connection -> RuntimeImplemented Basic (RuntimeImplemented Logging (ExceptT BasicException m)) a -> m a Source #

Handles SQL by querying a PostgreSQL database. Writes logs to console.

type family AllTables tables where ... Source #

Equations

AllTables '[x] = x 
AllTables (x ': xs) = x :. AllTables xs 

class FromRow (AllTables ts) => AllHaveFromRowInstance ts where Source #

Minimal complete definition

compositeToTuple

Methods

compositeToTuple :: proxy ts -> AllTables ts -> DbResult ts Source #

Instances

(FromRow a, FromRow b, FromRow c) => AllHaveFromRowInstance ((:) * a ((:) * b ((:) * c ([] *)))) Source # 

Methods

compositeToTuple :: proxy ((* ': a) ((* ': b) ((* ': c) [*]))) -> AllTables ((* ': a) ((* ': b) ((* ': c) [*]))) -> DbResult ((* ': a) ((* ': b) ((* ': c) [*]))) Source #

(FromRow a, FromRow b) => AllHaveFromRowInstance ((:) * a ((:) * b ([] *))) Source # 

Methods

compositeToTuple :: proxy ((* ': a) ((* ': b) [*])) -> AllTables ((* ': a) ((* ': b) [*])) -> DbResult ((* ': a) ((* ': b) [*])) Source #

FromRow a => AllHaveFromRowInstance ((:) * a ([] *)) Source # 

Methods

compositeToTuple :: proxy ((* ': a) [*]) -> AllTables ((* ': a) [*]) -> DbResult ((* ': a) [*]) Source #

type family WithoutOnly a where ... Source #

Equations

WithoutOnly (Only a) = a 
WithoutOnly a = a 

class NoOnly a where Source #

Minimal complete definition

noOnly

Methods

noOnly :: a -> WithoutOnly a Source #

Instances

(~) * (WithoutOnly a) a => NoOnly a Source # 

Methods

noOnly :: a -> WithoutOnly a Source #

NoOnly (Only a) Source # 

Methods

noOnly :: Only a -> WithoutOnly (Only a) Source #

runMapStatement :: forall res m f. (MonadEffect Basic m, FromRow res, NoOnly res) => DbStatement f '[res] -> m [WithoutOnly res] Source #