groundhog-postgresql-0.9.0.1: PostgreSQL backend for the groundhog library.

Safe HaskellNone
LanguageHaskell98

Database.Groundhog.Postgresql

Synopsis

Documentation

withPostgresqlPool Source #

Arguments

:: (MonadBaseControl IO m, MonadIO m) 
=> String

connection string in keyword/value format like "host=localhost port=5432 dbname=mydb". For more details and options see http://www.postgresql.org/docs/9.4/static/libpq-connect.html#LIBPQ-PARAMKEYWORDS

-> Int

number of connections to open

-> (Pool Postgresql -> m a) 
-> m a 

withPostgresqlConn Source #

Arguments

:: (MonadBaseControl IO m, MonadIO m) 
=> String

connection string

-> (Postgresql -> m a) 
-> m a 

createPostgresqlPool Source #

Arguments

:: MonadIO m 
=> String

connection string

-> Int

number of connections to open

-> m (Pool Postgresql) 

runDbConn :: (MonadIO m, MonadBaseControl IO m, ConnectionManager conn, ExtractConnection cm conn) => Action conn a -> cm -> m a #

Runs action within connection. It can handle a simple connection, a pool of them, etc.

newtype Postgresql Source #

Constructors

Postgresql Connection 
Instances
SchemaAnalyzer Postgresql Source # 
Instance details

Defined in Database.Groundhog.Postgresql

SqlDb Postgresql Source # 
Instance details

Defined in Database.Groundhog.Postgresql

FloatingSqlDb Postgresql Source # 
Instance details

Defined in Database.Groundhog.Postgresql

Methods

log' :: (ExpressionOf Postgresql r x a, Floating a) => x -> Expr Postgresql r a #

logBase' :: (ExpressionOf Postgresql r b a, ExpressionOf Postgresql r x a, Floating a) => b -> x -> Expr Postgresql r a #

DbDescriptor Postgresql Source # 
Instance details

Defined in Database.Groundhog.Postgresql

Associated Types

type AutoKeyType Postgresql :: * #

type QueryRaw Postgresql :: * -> * #

Methods

backendName :: proxy Postgresql -> String #

PersistBackendConn Postgresql Source # 
Instance details

Defined in Database.Groundhog.Postgresql

Methods

insert :: (PersistEntity v, PersistBackend m, Conn m ~ Postgresql) => v -> m (AutoKey v) #

insert_ :: (PersistEntity v, PersistBackend m, Conn m ~ Postgresql) => v -> m () #

insertBy :: (PersistEntity v, IsUniqueKey (Key v (Unique u)), PersistBackend m, Conn m ~ Postgresql) => u (UniqueMarker v) -> v -> m (Either (AutoKey v) (AutoKey v)) #

insertByAll :: (PersistEntity v, PersistBackend m, Conn m ~ Postgresql) => v -> m (Either (AutoKey v) (AutoKey v)) #

replace :: (PersistEntity v, PrimitivePersistField (Key v BackendSpecific), PersistBackend m, Conn m ~ Postgresql) => Key v BackendSpecific -> v -> m () #

replaceBy :: (PersistEntity v, IsUniqueKey (Key v (Unique u)), PersistBackend m, Conn m ~ Postgresql) => u (UniqueMarker v) -> v -> m () #

select :: (PersistEntity v, EntityConstr v c, HasSelectOptions opts Postgresql (RestrictionHolder v c), PersistBackend m, Conn m ~ Postgresql) => opts -> m [v] #

selectStream :: (PersistEntity v, EntityConstr v c, HasSelectOptions opts Postgresql (RestrictionHolder v c), PersistBackend m, Conn m ~ Postgresql) => opts -> m (RowStream v) #

selectAll :: (PersistEntity v, PersistBackend m, Conn m ~ Postgresql) => m [(AutoKey v, v)] #

selectAllStream :: (PersistEntity v, PersistBackend m, Conn m ~ Postgresql) => m (RowStream (AutoKey v, v)) #

get :: (PersistEntity v, PrimitivePersistField (Key v BackendSpecific), PersistBackend m, Conn m ~ Postgresql) => Key v BackendSpecific -> m (Maybe v) #

getBy :: (PersistEntity v, IsUniqueKey (Key v (Unique u)), PersistBackend m, Conn m ~ Postgresql) => Key v (Unique u) -> m (Maybe v) #

update :: (PersistEntity v, EntityConstr v c, PersistBackend m, Conn m ~ Postgresql) => [Update Postgresql (RestrictionHolder v c)] -> Cond Postgresql (RestrictionHolder v c) -> m () #

delete :: (PersistEntity v, EntityConstr v c, PersistBackend m, Conn m ~ Postgresql) => Cond Postgresql (RestrictionHolder v c) -> m () #

deleteBy :: (PersistEntity v, PrimitivePersistField (Key v BackendSpecific), PersistBackend m, Conn m ~ Postgresql) => Key v BackendSpecific -> m () #

deleteAll :: (PersistEntity v, PersistBackend m, Conn m ~ Postgresql) => v -> m () #

count :: (PersistEntity v, EntityConstr v c, PersistBackend m, Conn m ~ Postgresql) => Cond Postgresql (RestrictionHolder v c) -> m Int #

countAll :: (PersistEntity v, PersistBackend m, Conn m ~ Postgresql) => v -> m Int #

project :: (PersistEntity v, EntityConstr v c, Projection' p Postgresql (RestrictionHolder v c) a, HasSelectOptions opts Postgresql (RestrictionHolder v c), PersistBackend m, Conn m ~ Postgresql) => p -> opts -> m [a] #

projectStream :: (PersistEntity v, EntityConstr v c, Projection' p Postgresql (RestrictionHolder v c) a, HasSelectOptions opts Postgresql (RestrictionHolder v c), PersistBackend m, Conn m ~ Postgresql) => p -> opts -> m (RowStream a) #

migrate :: (PersistEntity v, PersistBackend m, Conn m ~ Postgresql) => v -> Migration m #

executeRaw :: (PersistBackend m, Conn m ~ Postgresql) => Bool -> String -> [PersistValue] -> m () #

queryRaw :: (PersistBackend m, Conn m ~ Postgresql) => Bool -> String -> [PersistValue] -> m (RowStream [PersistValue]) #

insertList :: (PersistField a, PersistBackend m, Conn m ~ Postgresql) => [a] -> m Int64 #

getList :: (PersistField a, PersistBackend m, Conn m ~ Postgresql) => Int64 -> m [a] #

ConnectionManager Postgresql Source # 
Instance details

Defined in Database.Groundhog.Postgresql

Methods

withConn :: (MonadBaseControl IO m, MonadIO m) => (Postgresql -> m a) -> Postgresql -> m a #

TryConnectionManager Postgresql Source # 
Instance details

Defined in Database.Groundhog.Postgresql

Methods

tryWithConn :: (MonadBaseControl IO m, MonadIO m, MonadCatch m) => (Postgresql -> n a) -> (n a -> m (Either SomeException a)) -> Postgresql -> m (Either SomeException a) #

Savepoint Postgresql Source # 
Instance details

Defined in Database.Groundhog.Postgresql

Methods

withConnSavepoint :: (MonadBaseControl IO m, MonadIO m) => String -> m a -> Postgresql -> m a #

ExtractConnection Postgresql Postgresql Source # 
Instance details

Defined in Database.Groundhog.Postgresql

Methods

extractConn :: (MonadBaseControl IO m, MonadIO m) => (Postgresql -> m a) -> Postgresql -> m a #

ExtractConnection (Pool Postgresql) Postgresql Source # 
Instance details

Defined in Database.Groundhog.Postgresql

Methods

extractConn :: (MonadBaseControl IO m, MonadIO m) => (Postgresql -> m a) -> Pool Postgresql -> m a #

type QueryRaw Postgresql Source # 
Instance details

Defined in Database.Groundhog.Postgresql

type AutoKeyType Postgresql Source # 
Instance details

Defined in Database.Groundhog.Postgresql

explicitType :: (Expression Postgresql r a, PersistField a) => a -> Expr Postgresql r a Source #

Put explicit type for expression. It is useful for values which are defaulted to a wrong type. For example, a literal Int from a 64bit machine can be defaulted to a 32bit int by Postgresql. Also a value entered as an external string (geometry, arrays and other complex types have this representation) may need an explicit type.

castType :: Expression Postgresql r a => a -> String -> Expr Postgresql r a Source #

Casts expression to a type. castType value "INT" results in value::INT.

distinctOn :: (db ~ Postgresql, HasSelectOptions a db r, HasDistinct a ~ HFalse, Projection' p db r p') => a -> p -> SelectOptions db r (HasLimit a) (HasOffset a) (HasOrder a) HTrue Source #

Distinct only on certain fields or expressions. For example, select $ CondEmpty distinctOn (lower EmailField, IpField).