postgresql-query-3.10.0: Sql interpolating quasiquote plus some kind of primitive ORM using it
Safe HaskellNone
LanguageHaskell2010

Database.PostgreSQL.Query.TH.Entity

Synopsis

Documentation

data EntityOptions Source #

Options for deriving Entity

Constructors

EntityOptions 

Fields

Instances

Instances details
Generic EntityOptions Source # 
Instance details

Defined in Database.PostgreSQL.Query.TH.Entity

Associated Types

type Rep EntityOptions :: Type -> Type #

Default EntityOptions Source # 
Instance details

Defined in Database.PostgreSQL.Query.TH.Entity

Methods

def :: EntityOptions #

type Rep EntityOptions Source # 
Instance details

Defined in Database.PostgreSQL.Query.TH.Entity

type Rep EntityOptions = D1 ('MetaData "EntityOptions" "Database.PostgreSQL.Query.TH.Entity" "postgresql-query-3.10.0-5LISmCzCf6YHFrJlgDAYDl" 'False) (C1 ('MetaCons "EntityOptions" 'PrefixI 'True) ((S1 ('MetaSel ('Just "eoTableName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Text -> FN)) :*: S1 ('MetaSel ('Just "eoColumnNames") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Text -> FN))) :*: (S1 ('MetaSel ('Just "eoDeriveClasses") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Name]) :*: S1 ('MetaSel ('Just "eoIdType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Name))))

deriveEntity :: EntityOptions -> Name -> Q [Dec] Source #

Derives instance for Entity using type name and field names. Also generates type synonim for ID. E.g. code like this:

data Agent = Agent
    { aName          :: !Text
    , aAttributes    :: !HStoreMap
    , aLongWeirdName :: !Int
    } deriving (Ord, Eq, Show)

$(deriveEntity
  def { eoIdType        = ''Id
      , eoTableName     = textFN . toUnderscore'
      , eoColumnNames   = textFN . toUnderscore' . drop 1
      , eoDeriveClasses =
        [''Show, ''Read, ''Ord, ''Eq
        , ''FromField, ''ToField, ''PathPiece]
      }
  ''Agent )

Will generate code like this:

instance Database.PostgreSQL.Query.Entity Agent where
    newtype EntityId Agent
        = AgentId {getAgentId :: Id}
        deriving (Show, Read, Ord, Eq, FromField, ToField, PathPiece)
    tableName _ = "agent"
    fieldNames _ = ["name", "attributes", "long_weird_name"]
type AgentId = EntityId Agent

So, you dont need to write it by hands any more.

NOTE: toUnderscore is from package inflections here