Copyright | (c) Eitan Chatav 2019 |
---|---|
Maintainer | eitan@morphism.tech |
Stability | experimental |
Safe Haskell | None |
Language | Haskell2010 |
database connections
Synopsis
- data Connection
- connectdb :: forall (db :: SchemasType) io. MonadIO io => ByteString -> io (K Connection db)
- finish :: MonadIO io => K Connection db -> io ()
- lowerConnection :: K Connection (schema ': db) -> K Connection db
- newtype K a (b :: k) = K a
- unK :: forall k a (b :: k). K a b -> a
Documentation
data Connection #
Connection
encapsulates a connection to the backend.
Instances
Eq Connection | |
Defined in Database.PostgreSQL.LibPQ.Internal (==) :: Connection -> Connection -> Bool # (/=) :: Connection -> Connection -> Bool # |
:: 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!
lowerConnection :: K Connection (schema ': db) -> K Connection db Source #
Safely lowerConnection
to a smaller schema.
The constant type functor.
Like Constant
, but kind-polymorphic
in its second argument and with a shorter name.
K a |
Instances
IsPGlabel label (y -> NP (K y :: Symbol -> Type) '[label]) Source # | |
IsPGlabel label (y -> K y label) Source # | |
Defined in Squeal.PostgreSQL.Type.Schema | |
ToPG db x => ToPG db (K x tag) Source # | |
Defined in Squeal.PostgreSQL.Session.Encode | |
Eq2 (K :: Type -> Type -> Type) | Since: sop-core-0.2.4.0 |
Ord2 (K :: Type -> Type -> Type) | Since: sop-core-0.2.4.0 |
Defined in Data.SOP.BasicFunctors | |
Read2 (K :: Type -> Type -> Type) | Since: sop-core-0.2.4.0 |
Defined in Data.SOP.BasicFunctors 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 |
NFData2 (K :: Type -> Type -> Type) | Since: sop-core-0.2.5.0 |
Defined in Data.SOP.BasicFunctors | |
Functor (K a :: Type -> Type) | |
Monoid a => Applicative (K a :: Type -> Type) | |
Foldable (K a :: Type -> Type) | |
Defined in Data.SOP.BasicFunctors 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 # elem :: Eq a0 => a0 -> K a a0 -> Bool # maximum :: Ord a0 => K a a0 -> a0 # minimum :: Ord a0 => K a a0 -> a0 # | |
Traversable (K a :: Type -> Type) | |
Eq a => Eq1 (K a :: Type -> Type) | Since: sop-core-0.2.4.0 |
Ord a => Ord1 (K a :: Type -> Type) | Since: sop-core-0.2.4.0 |
Defined in Data.SOP.BasicFunctors | |
Read a => Read1 (K a :: Type -> Type) | Since: sop-core-0.2.4.0 |
Defined in Data.SOP.BasicFunctors | |
Show a => Show1 (K a :: Type -> Type) | Since: sop-core-0.2.4.0 |
NFData a => NFData1 (K a :: Type -> Type) | Since: sop-core-0.2.5.0 |
Defined in Data.SOP.BasicFunctors | |
Eq a => Eq (K a b) | |
Ord a => Ord (K a b) | |
Read a => Read (K a b) | |
Show a => Show (K a b) | |
Generic (K a b) | |
Semigroup a => Semigroup (K a b) | Since: sop-core-0.4.0.0 |
Monoid a => Monoid (K a b) | Since: sop-core-0.4.0.0 |
NFData a => NFData (K a b) | Since: sop-core-0.2.5.0 |
Defined in Data.SOP.BasicFunctors | |
IsPG hask => IsPG (K hask tag) Source # | `PG hask` |
FromPG x => FromPG (K x tag) Source # | |
Defined in Squeal.PostgreSQL.Session.Decode | |
Inline x => Inline (K x tag) Source # | |
type Rep (K a b) | |
Defined in Data.SOP.BasicFunctors | |
type Code (K a b) | |
Defined in Generics.SOP.Instances | |
type DatatypeInfoOf (K a b) | |
Defined in Generics.SOP.Instances | |
type PG (K hask tag) Source # | |
Defined in Squeal.PostgreSQL.Type.PG |