Safe Haskell | None |
---|---|
Language | Haskell2010 |
"postgresql-simple"-backed query ribbit implementation.
Synopsis
- class HasPsqlType a where
- newtype PsqlType = PsqlType {
- unPsqlType :: Text
- execute :: forall m query. (MonadIO m, ToRow (ParamsType query), KnownSymbol (Render query)) => Connection -> Proxy query -> ParamsType query -> m Int64
- query :: forall m query. (MonadIO m, KnownSymbol (Render query), ToRow (ParamsType query), FromRow (ResultType query)) => Connection -> Proxy query -> ParamsType query -> m [ResultType query]
- createTable :: forall proxy1 proxy2 key table m. (KnownSymbol (Name table), HasPsqlTypes (DBSchema table), HasFields (DBSchema table), HasFields key, IsSubset key (DBSchema table) ~ True, MonadIO m) => Connection -> proxy1 key -> proxy2 table -> m ()
- createTableStatement :: forall proxy1 proxy2 table key. (KnownSymbol (Name table), HasPsqlTypes (DBSchema table), HasFields (DBSchema table), HasFields key, IsSubset key (DBSchema table) ~ True) => proxy1 key -> proxy2 table -> Text
- class HasFields a
- class HasPsqlTypes a
- class HasIsNullable a
- type family IsSubset fields schema where ...
- class FromRow a
- class ToRow a
Integrating your types.
class HasPsqlType a where Source #
Given a Haskell type, produce the PostgreSQL type of columns that store values of that haskell type.
Instances
HasPsqlType Int Source # | |
HasPsqlType Text Source # | |
HasPsqlType Day Source # | |
HasPsqlType a => HasPsqlType (Maybe a :: Type) Source # | |
Represents the "base" PostgreSQL type. We say "base" type because whether the type is nullable is handle automatically.
e.g.
PsqlType "integer"
PsqlType "timestamp with time zone"
Instances
IsString PsqlType Source # | |
Defined in Database.Ribbit.PostgreSQL fromString :: String -> PsqlType # |
Performing queries.
execute :: forall m query. (MonadIO m, ToRow (ParamsType query), KnownSymbol (Render query)) => Connection -> Proxy query -> ParamsType query -> m Int64 Source #
Execute a statement.
query :: forall m query. (MonadIO m, KnownSymbol (Render query), ToRow (ParamsType query), FromRow (ResultType query)) => Connection -> Proxy query -> ParamsType query -> m [ResultType query] Source #
Execute a query against a PostgreSQL database connection.
Creating tables.
createTable :: forall proxy1 proxy2 key table m. (KnownSymbol (Name table), HasPsqlTypes (DBSchema table), HasFields (DBSchema table), HasFields key, IsSubset key (DBSchema table) ~ True, MonadIO m) => Connection -> proxy1 key -> proxy2 table -> m () Source #
Create the indicated table in the database.
See createTableStatement
for details.
createTableStatement :: forall proxy1 proxy2 table key. (KnownSymbol (Name table), HasPsqlTypes (DBSchema table), HasFields (DBSchema table), HasFields key, IsSubset key (DBSchema table) ~ True) => proxy1 key -> proxy2 table -> Text Source #
Produce the statement used to create a table.
In this example, we create an employee table with a multi-part primary key, one nullable field, and a few non-nullable fields.
data Employee instance Table Employee where type Name = "employees" type DBSchema = Field "company_id" Int :> Field "id" Int :> Field "name" Text :> Field "quit_date" (Maybe Day) let primaryKey :: Proxy '["company_id", "id"] primaryKey = Proxy table :: Proxy Employee table = Proxy in createTableStatement primaryKey table
This will produce the statement:
"create table employees (company_id integer not null, id integer not null, name text not null, quit_date date, primary key (company_id, id));"
Other types.
These type classes/families are not meant to be used directly. They are exported primarily because they appear in the type signatures of some of the above functions and documenting them can be helpful when trying to figure out how to use those functions.
Produce a list of field names from a schema.
fields
Instances
HasFields ([] :: [k]) Source # | |
Defined in Database.Ribbit.PostgreSQL | |
(KnownSymbol name, HasFields more) => HasFields (Field name typ :> more :: Type) Source # | |
Defined in Database.Ribbit.PostgreSQL | |
(KnownSymbol name, HasFields more) => HasFields (name ': more :: [Symbol]) Source # | |
Defined in Database.Ribbit.PostgreSQL | |
KnownSymbol name => HasFields (Field name typ :: Type) Source # | |
Defined in Database.Ribbit.PostgreSQL |
class HasPsqlTypes a Source #
psqlTypes
Instances
(HasIsNullable typ, HasPsqlType typ, HasPsqlTypes more) => HasPsqlTypes (Field name typ :> more :: Type) Source # | |
Defined in Database.Ribbit.PostgreSQL | |
(HasIsNullable typ, HasPsqlType typ) => HasPsqlTypes (Field name typ :: Type) Source # | |
Defined in Database.Ribbit.PostgreSQL |
class HasIsNullable a Source #
Figure out if a Haskell type is "nullable" in sql.
isNullable
Instances
HasIsNullable (a :: k) Source # | |
Defined in Database.Ribbit.PostgreSQL isNullable :: proxy a -> Bool | |
HasIsNullable (Maybe a :: Type) Source # | |
Defined in Database.Ribbit.PostgreSQL isNullable :: proxy (Maybe a) -> Bool |
type family IsSubset fields schema where ... Source #
Make sure the fields in the list are actually part of the schema.
Like FromRow
, but defined here so we can avoid orphaned instances.
fromRow