squeal-postgresql-0.9.0.0: Squeal PostgreSQL Library
Copyright(c) Eitan Chatav 2019
Maintainereitan@morphism.tech
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Squeal.PostgreSQL.Session.Connection

Description

database connections

Synopsis

Documentation

data Connection #

Connection encapsulates a connection to the backend.

Instances

Instances details
Eq Connection 
Instance details

Defined in Database.PostgreSQL.LibPQ.Internal

connectdb Source #

Arguments

:: forall (db :: SchemasType) io. MonadIO io 
=> ByteString

conninfo

-> io (K Connection db) 

Makes a new connection to the database server.

This function opens a new database connection using the parameters taken from the string conninfo.

The passed string can be empty to use all default parameters, or it can contain one or more parameter settings separated by whitespace. Each parameter setting is in the form keyword = value. Spaces around the equal sign are optional. To write an empty value or a value containing spaces, surround it with single quotes, e.g., keyword = 'a value'. Single quotes and backslashes within the value must be escaped with a backslash, i.e., ' and .

To specify the schema you wish to connect with, use type application.

>>> :set -XDataKinds
>>> :set -XPolyKinds
>>> :set -XTypeOperators
>>> type DB = '["public" ::: '["tab" ::: 'Table ('[] :=> '["col" ::: 'NoDef :=> 'Null 'PGint2])]]
>>> :set -XTypeApplications
>>> :set -XOverloadedStrings
>>> conn <- connectdb @DB "host=localhost port=5432 dbname=exampledb user=postgres password=postgres"

Note that, for now, squeal doesn't offer any protection from connecting with the wrong schema!

finish :: MonadIO io => K Connection db -> io () Source #

Closes the connection to the server.

lowerConnection :: K Connection (schema ': db) -> K Connection db Source #

Safely lowerConnection to a smaller schema.

newtype K a (b :: k) #

The constant type functor.

Like Constant, but kind-polymorphic in its second argument and with a shorter name.

Constructors

K a 

Instances

Instances details
IsPGlabel label (y -> NP (K y :: Symbol -> Type) '[label]) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type.Schema

Methods

label :: y -> NP (K y) '[label] Source #

IsPGlabel label (y -> K y label) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type.Schema

Methods

label :: y -> K y label Source #

ToPG db x => ToPG db (K x tag) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Encode

Methods

toPG :: K x tag -> ReaderT (K Connection db) IO Encoding Source #

Eq2 (K :: Type -> Type -> Type)

Since: sop-core-0.2.4.0

Instance details

Defined in Data.SOP.BasicFunctors

Methods

liftEq2 :: (a -> b -> Bool) -> (c -> d -> Bool) -> K a c -> K b d -> Bool #

Ord2 (K :: Type -> Type -> Type)

Since: sop-core-0.2.4.0

Instance details

Defined in Data.SOP.BasicFunctors

Methods

liftCompare2 :: (a -> b -> Ordering) -> (c -> d -> Ordering) -> K a c -> K b d -> Ordering #

Read2 (K :: Type -> Type -> Type)

Since: sop-core-0.2.4.0

Instance details

Defined in Data.SOP.BasicFunctors

Methods

liftReadsPrec2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> Int -> ReadS (K a b) #

liftReadList2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [K a b] #

liftReadPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (K a b) #

liftReadListPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [K a b] #

Show2 (K :: Type -> Type -> Type)

Since: sop-core-0.2.4.0

Instance details

Defined in Data.SOP.BasicFunctors

Methods

liftShowsPrec2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> Int -> K a b -> ShowS #

liftShowList2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> [K a b] -> ShowS #

NFData2 (K :: Type -> Type -> Type)

Since: sop-core-0.2.5.0

Instance details

Defined in Data.SOP.BasicFunctors

Methods

liftRnf2 :: (a -> ()) -> (b -> ()) -> K a b -> () #

Functor (K a :: Type -> Type) 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

fmap :: (a0 -> b) -> K a a0 -> K a b #

(<$) :: a0 -> K a b -> K a a0 #

Monoid a => Applicative (K a :: Type -> Type) 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

pure :: a0 -> K a a0 #

(<*>) :: K a (a0 -> b) -> K a a0 -> K a b #

liftA2 :: (a0 -> b -> c) -> K a a0 -> K a b -> K a c #

(*>) :: K a a0 -> K a b -> K a b #

(<*) :: K a a0 -> K a b -> K a a0 #

Foldable (K a :: Type -> Type) 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

fold :: Monoid m => K a m -> m #

foldMap :: Monoid m => (a0 -> m) -> K a a0 -> m #

foldMap' :: Monoid m => (a0 -> m) -> K a a0 -> m #

foldr :: (a0 -> b -> b) -> b -> K a a0 -> b #

foldr' :: (a0 -> b -> b) -> b -> K a a0 -> b #

foldl :: (b -> a0 -> b) -> b -> K a a0 -> b #

foldl' :: (b -> a0 -> b) -> b -> K a a0 -> b #

foldr1 :: (a0 -> a0 -> a0) -> K a a0 -> a0 #

foldl1 :: (a0 -> a0 -> a0) -> K a a0 -> a0 #

toList :: K a a0 -> [a0] #

null :: K a a0 -> Bool #

length :: K a a0 -> Int #

elem :: Eq a0 => a0 -> K a a0 -> Bool #

maximum :: Ord a0 => K a a0 -> a0 #

minimum :: Ord a0 => K a a0 -> a0 #

sum :: Num a0 => K a a0 -> a0 #

product :: Num a0 => K a a0 -> a0 #

Traversable (K a :: Type -> Type) 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

traverse :: Applicative f => (a0 -> f b) -> K a a0 -> f (K a b) #

sequenceA :: Applicative f => K a (f a0) -> f (K a a0) #

mapM :: Monad m => (a0 -> m b) -> K a a0 -> m (K a b) #

sequence :: Monad m => K a (m a0) -> m (K a a0) #

Eq a => Eq1 (K a :: Type -> Type)

Since: sop-core-0.2.4.0

Instance details

Defined in Data.SOP.BasicFunctors

Methods

liftEq :: (a0 -> b -> Bool) -> K a a0 -> K a b -> Bool #

Ord a => Ord1 (K a :: Type -> Type)

Since: sop-core-0.2.4.0

Instance details

Defined in Data.SOP.BasicFunctors

Methods

liftCompare :: (a0 -> b -> Ordering) -> K a a0 -> K a b -> Ordering #

Read a => Read1 (K a :: Type -> Type)

Since: sop-core-0.2.4.0

Instance details

Defined in Data.SOP.BasicFunctors

Methods

liftReadsPrec :: (Int -> ReadS a0) -> ReadS [a0] -> Int -> ReadS (K a a0) #

liftReadList :: (Int -> ReadS a0) -> ReadS [a0] -> ReadS [K a a0] #

liftReadPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec (K a a0) #

liftReadListPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec [K a a0] #

Show a => Show1 (K a :: Type -> Type)

Since: sop-core-0.2.4.0

Instance details

Defined in Data.SOP.BasicFunctors

Methods

liftShowsPrec :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> Int -> K a a0 -> ShowS #

liftShowList :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> [K a a0] -> ShowS #

NFData a => NFData1 (K a :: Type -> Type)

Since: sop-core-0.2.5.0

Instance details

Defined in Data.SOP.BasicFunctors

Methods

liftRnf :: (a0 -> ()) -> K a a0 -> () #

Eq a => Eq (K a b) 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

(==) :: K a b -> K a b -> Bool #

(/=) :: K a b -> K a b -> Bool #

Ord a => Ord (K a b) 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

compare :: K a b -> K a b -> Ordering #

(<) :: K a b -> K a b -> Bool #

(<=) :: K a b -> K a b -> Bool #

(>) :: K a b -> K a b -> Bool #

(>=) :: K a b -> K a b -> Bool #

max :: K a b -> K a b -> K a b #

min :: K a b -> K a b -> K a b #

Read a => Read (K a b) 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

readsPrec :: Int -> ReadS (K a b) #

readList :: ReadS [K a b] #

readPrec :: ReadPrec (K a b) #

readListPrec :: ReadPrec [K a b] #

Show a => Show (K a b) 
Instance details

Defined in Data.SOP.BasicFunctors

Methods

showsPrec :: Int -> K a b -> ShowS #

show :: K a b -> String #

showList :: [K a b] -> ShowS #

Generic (K a b) 
Instance details

Defined in Data.SOP.BasicFunctors

Associated Types

type Rep (K a b) :: Type -> Type #

Methods

from :: K a b -> Rep (K a b) x #

to :: Rep (K a b) x -> K a b #

Semigroup a => Semigroup (K a b)

Since: sop-core-0.4.0.0

Instance details

Defined in Data.SOP.BasicFunctors

Methods

(<>) :: K a b -> K a b -> K a b #

sconcat :: NonEmpty (K a b) -> K a b #

stimes :: Integral b0 => b0 -> K a b -> K a b #

Monoid a => Monoid (K a b)

Since: sop-core-0.4.0.0

Instance details

Defined in Data.SOP.BasicFunctors

Methods

mempty :: K a b #

mappend :: K a b -> K a b -> K a b #

mconcat :: [K a b] -> K a b #

NFData a => NFData (K a b)

Since: sop-core-0.2.5.0

Instance details

Defined in Data.SOP.BasicFunctors

Methods

rnf :: K a b -> () #

IsPG hask => IsPG (K hask tag) Source #

`PG hask`

Instance details

Defined in Squeal.PostgreSQL.Type.PG

Associated Types

type PG (K hask tag) :: PGType Source #

FromPG x => FromPG (K x tag) Source # 
Instance details

Defined in Squeal.PostgreSQL.Session.Decode

Methods

fromPG :: StateT ByteString (Except Text) (K x tag) Source #

Inline x => Inline (K x tag) Source # 
Instance details

Defined in Squeal.PostgreSQL.Expression.Inline

Methods

inline :: forall (null :: PGType -> NullType). K x tag -> Expr (null (PG (K x tag))) Source #

type Rep (K a b) 
Instance details

Defined in Data.SOP.BasicFunctors

type Rep (K a b) = D1 ('MetaData "K" "Data.SOP.BasicFunctors" "sop-core-0.5.0.2-JiJuIvMQflQ495Q0ZwTtHX" 'True) (C1 ('MetaCons "K" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))
type Code (K a b) 
Instance details

Defined in Generics.SOP.Instances

type Code (K a b) = '['[a]]
type DatatypeInfoOf (K a b) 
Instance details

Defined in Generics.SOP.Instances

type DatatypeInfoOf (K a b) = 'Newtype "Data.SOP.BasicFunctors" "K" ('Constructor "K")
type PG (K hask tag) Source # 
Instance details

Defined in Squeal.PostgreSQL.Type.PG

type PG (K hask tag) = PG hask

unK :: forall k a (b :: k). K a b -> a #

Extract the contents of a K value.