ribbit-1.1.0.0: Type-level Relational DB combinators.

Safe HaskellNone
LanguageHaskell2010

Database.Ribbit.PostgreSQL

Contents

Description

"postgresql-simple"-backed query ribbit implementation.

Synopsis

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.

Methods

psqlType :: proxy a -> PsqlType Source #

Instances
HasPsqlType Int Source # 
Instance details

Defined in Database.Ribbit.PostgreSQL

Methods

psqlType :: proxy Int -> PsqlType Source #

HasPsqlType Text Source # 
Instance details

Defined in Database.Ribbit.PostgreSQL

Methods

psqlType :: proxy Text -> PsqlType Source #

HasPsqlType Day Source # 
Instance details

Defined in Database.Ribbit.PostgreSQL

Methods

psqlType :: proxy Day -> PsqlType Source #

HasPsqlType a => HasPsqlType (Maybe a :: Type) Source # 
Instance details

Defined in Database.Ribbit.PostgreSQL

Methods

psqlType :: proxy (Maybe a) -> PsqlType Source #

newtype PsqlType 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"

Constructors

PsqlType 

Fields

Instances
IsString PsqlType Source # 
Instance details

Defined in Database.Ribbit.PostgreSQL

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.

class HasFields a Source #

Produce a list of field names from a schema.

Minimal complete definition

fields

Instances
HasFields ([] :: [k]) Source # 
Instance details

Defined in Database.Ribbit.PostgreSQL

Methods

fields :: proxy [] -> [Text]

(KnownSymbol name, HasFields more) => HasFields (Field name typ :> more :: Type) Source # 
Instance details

Defined in Database.Ribbit.PostgreSQL

Methods

fields :: proxy (Field name typ :> more) -> [Text]

(KnownSymbol name, HasFields more) => HasFields (name ': more :: [Symbol]) Source # 
Instance details

Defined in Database.Ribbit.PostgreSQL

Methods

fields :: proxy (name ': more) -> [Text]

KnownSymbol name => HasFields (Field name typ :: Type) Source # 
Instance details

Defined in Database.Ribbit.PostgreSQL

Methods

fields :: proxy (Field name typ) -> [Text]

class HasPsqlTypes a Source #

Minimal complete definition

psqlTypes

Instances
(HasIsNullable typ, HasPsqlType typ, HasPsqlTypes more) => HasPsqlTypes (Field name typ :> more :: Type) Source # 
Instance details

Defined in Database.Ribbit.PostgreSQL

Methods

psqlTypes :: proxy (Field name typ :> more) -> [Text]

(HasIsNullable typ, HasPsqlType typ) => HasPsqlTypes (Field name typ :: Type) Source # 
Instance details

Defined in Database.Ribbit.PostgreSQL

Methods

psqlTypes :: proxy (Field name typ) -> [Text]

class HasIsNullable a Source #

Figure out if a Haskell type is "nullable" in sql.

Minimal complete definition

isNullable

Instances
HasIsNullable (a :: k) Source # 
Instance details

Defined in Database.Ribbit.PostgreSQL

Methods

isNullable :: proxy a -> Bool

HasIsNullable (Maybe a :: Type) Source # 
Instance details

Defined in Database.Ribbit.PostgreSQL

Methods

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.

Equations

IsSubset '[] schema = True 
IsSubset (field ': more) schema = If (ValidField field schema) (IsSubset more schema) (TypeError ((Text "field " :<>: ShowType field) :<>: Text " is not part of the schema, so it cannot be used as a component of the primary key.")) 

class FromRow a Source #

Like FromRow, but defined here so we can avoid orphaned instances.

Minimal complete definition

fromRow

Instances
FromField a => FromRow (Only a) Source # 
Instance details

Defined in Database.Ribbit.PostgreSQL

Methods

fromRow :: RowParser (Only a)

(FromRow a, FromRow b) => FromRow (a :> b) Source # 
Instance details

Defined in Database.Ribbit.PostgreSQL

Methods

fromRow :: RowParser (a :> b)

class ToRow a Source #

Like ToRow, but defined here to avoid orphan instances.

Minimal complete definition

toRow

Instances
ToRow () Source # 
Instance details

Defined in Database.Ribbit.PostgreSQL

Methods

toRow :: () -> [Action]

ToField a => ToRow (Only a) Source # 
Instance details

Defined in Database.Ribbit.PostgreSQL

Methods

toRow :: Only a -> [Action]

(ToRow a, ToRow b) => ToRow (a :> b) Source # 
Instance details

Defined in Database.Ribbit.PostgreSQL

Methods

toRow :: (a :> b) -> [Action]