Copyright | © Clément Delafargue 2018 Théophile Choutri 2021 |
---|---|
License | MIT |
Maintainer | theophile@choutri.eu |
Stability | stable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Types and classes
Synopsis
- class Entity e where
- data Field
- field :: QuasiQuoter
- fieldName :: Field -> Text
- fieldType :: Field -> Maybe Text
- newtype UpdateRow a = UpdateRow {
- getUpdate :: a
- data SortKeyword
- data Options = Options {
- tableNameModifiers :: Text -> Text
- schemaModifier :: Maybe Text
- primaryKeyModifiers :: Text -> Text
- fieldModifiers :: Text -> Text
- defaultEntityOptions :: Options
- newtype GenericEntity t e = GenericEntity {
- getGenericEntity :: e
- class EntityOptions xs where
- data PrimaryKey (t :: Symbol)
- data Schema (t :: Symbol)
- data TableName (t :: Symbol)
- data FieldModifiers ms
- class TextModifier t where
- getTextModifier :: Text -> Text
- data StripPrefix (prefix :: Symbol)
- data CamelTo (separator :: Symbol)
- type CamelToSnake = CamelTo "_"
- type CamelToKebab = CamelTo "-"
The Entity Typeclass
An Entity
stores the following information about the structure of a database table:
- Its name
- Its primary key
- The fields it contains
Example
data ExampleEntity = E { key :: Key , field1 :: Int , field2 :: Bool } deriving stock (Eq, Show, Generic) deriving anyclass (FromRow, ToRow) deriving Entity via (GenericEntity '[TableName "entities"] ExampleEntity)
When using the functions provided by this library, you will sometimes need to be explicit about the Entity you are referring to.
Since: 0.0.1.0
Nothing
The name of the table in the PostgreSQL database.
The name of the schema; will be appended to the table name: schema."tablename"
primaryKey :: Field Source #
The name of the primary key for the table.
default primaryKey :: GetFields (Rep e) => Field Source #
fields :: Vector Field Source #
The fields of the table.
Associated Types
A wrapper for table fields.
Since: 0.0.1.0
field :: QuasiQuoter Source #
A quasi-quoter for safely constructing Field
s.
Example:
instance Entity BlogPost where tableName = "blogposts" primaryKey = [field| blogpost_id |] fields = [ [field| blogpost_id |] , [field| author_id |] , [field| uuid_list :: uuid[] |] -- ← This is where we specify an optional PostgreSQL type annotation , [field| title |] , [field| content |] , [field| created_at |] ]
Since: 0.1.0.0
Wrapper used by the update function in order to have the primary key as the last parameter passed, since it appears in the WHERE clause.
Since: 0.0.1.0
data SortKeyword Source #
Since: 0.0.2.0
Instances
Show SortKeyword Source # | |
Defined in Database.PostgreSQL.Entity.Types showsPrec :: Int -> SortKeyword -> ShowS # show :: SortKeyword -> String # showList :: [SortKeyword] -> ShowS # | |
Eq SortKeyword Source # | |
Defined in Database.PostgreSQL.Entity.Types (==) :: SortKeyword -> SortKeyword -> Bool # (/=) :: SortKeyword -> SortKeyword -> Bool # | |
Display SortKeyword Source # | |
Defined in Database.PostgreSQL.Entity.Types displayBuilder :: SortKeyword -> Builder # displayList :: [SortKeyword] -> Builder # displayPrec :: Int -> SortKeyword -> Builder # |
Generics
Term-level options
Options | |
|
DerivingVia Options
newtype GenericEntity t e Source #
class EntityOptions xs where Source #
Type-level options for Deriving Via
Instances
EntityOptions ('[] :: [k]) Source # | |
Defined in Database.PostgreSQL.Entity.Types | |
(TextModifier mods, EntityOptions xs) => EntityOptions (FieldModifiers mods ': xs :: [Type]) Source # | |
Defined in Database.PostgreSQL.Entity.Types | |
(GetName name, EntityOptions xs) => EntityOptions (PrimaryKey name ': xs :: [Type]) Source # | |
Defined in Database.PostgreSQL.Entity.Types | |
(GetName name, EntityOptions xs) => EntityOptions (Schema name ': xs :: [Type]) Source # | |
Defined in Database.PostgreSQL.Entity.Types | |
(GetName name, EntityOptions xs) => EntityOptions (TableName name ': xs :: [Type]) Source # | |
Defined in Database.PostgreSQL.Entity.Types |
data PrimaryKey (t :: Symbol) Source #
Instances
(GetName name, EntityOptions xs) => EntityOptions (PrimaryKey name ': xs :: [Type]) Source # | |
Defined in Database.PostgreSQL.Entity.Types |
data Schema (t :: Symbol) Source #
Instances
(GetName name, EntityOptions xs) => EntityOptions (Schema name ': xs :: [Type]) Source # | |
Defined in Database.PostgreSQL.Entity.Types |
data TableName (t :: Symbol) Source #
Instances
(GetName name, EntityOptions xs) => EntityOptions (TableName name ': xs :: [Type]) Source # | |
Defined in Database.PostgreSQL.Entity.Types |
data FieldModifiers ms Source #
Contains a list of TextModifiers
modifiers
Instances
(TextModifier mods, EntityOptions xs) => EntityOptions (FieldModifiers mods ': xs :: [Type]) Source # | |
Defined in Database.PostgreSQL.Entity.Types |
class TextModifier t where Source #
The modifiers that you can apply to the fields:
StripPrefix
CamelTo
, and its variationsCamelToSnake
CamelToKebab
getTextModifier :: Text -> Text Source #
Instances
(KnownSymbol separator, NonEmptyText separator) => TextModifier (CamelTo separator :: Type) Source # | |
Defined in Database.PostgreSQL.Entity.Types getTextModifier :: Text -> Text Source # | |
KnownSymbol prefix => TextModifier (StripPrefix prefix :: Type) Source # | |
Defined in Database.PostgreSQL.Entity.Types getTextModifier :: Text -> Text Source # | |
TextModifier ('[] :: [k]) Source # | |
Defined in Database.PostgreSQL.Entity.Types getTextModifier :: Text -> Text Source # | |
(TextModifier x, TextModifier xs) => TextModifier (x ': xs :: [a]) Source # | |
Defined in Database.PostgreSQL.Entity.Types getTextModifier :: Text -> Text Source # |
data StripPrefix (prefix :: Symbol) Source #
TextModifier
to remove a certain prefix from the fields
Instances
KnownSymbol prefix => TextModifier (StripPrefix prefix :: Type) Source # | |
Defined in Database.PostgreSQL.Entity.Types getTextModifier :: Text -> Text Source # |
data CamelTo (separator :: Symbol) Source #
FieldModifier
taking a separator Char when transforming from CamelCase.
Instances
(KnownSymbol separator, NonEmptyText separator) => TextModifier (CamelTo separator :: Type) Source # | |
Defined in Database.PostgreSQL.Entity.Types getTextModifier :: Text -> Text Source # |
type CamelToSnake = CamelTo "_" Source #
CamelCase to snake_case
type CamelToKebab = CamelTo "-" Source #
CamelCase to kebab-case