postgresql-query-1.4.0: Sql interpolating quasiquote plus some kind of primitive ORM using it

Safe HaskellNone
LanguageHaskell2010

Database.PostgreSQL.Query.TH

Contents

Synopsis

Deriving instances

deriveFromRow :: Name -> Q [Dec] Source

Derive FromRow instance. i.e. you have type like that

data Entity = Entity
              { eField :: Text
              , eField2 :: Int
              , efield3 :: Bool }

then deriveFromRow will generate this instance: instance FromRow Entity where

instance FromRow Entity where
    fromRow = Entity
              <$> field
              <*> field
              <*> field

Datatype must have just one constructor with arbitrary count of fields

deriveToRow :: Name -> Q [Dec] Source

derives ToRow instance for datatype like

data Entity = Entity
              { eField :: Text
              , eField2 :: Int
              , efield3 :: Bool }

it will derive instance like that:

instance ToRow Entity where
     toRow (Entity e1 e2 e3) =
         [ toField e1
         , toField e2
         , toField e3 ]

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     = toUnderscore
      , eoColumnNames   = 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

deriveEverything :: EntityOptions -> Name -> Q [Dec] Source

Calls sequently deriveFromRow deriveToRow deriveEntity. E.g. code like this:

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

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

will generate that:

instance ToRow Agent where
    toRow (Agent a_aE3w a_aE3x a_aE3y)
        = [toField a_aE3w, toField a_aE3x, toField a_aE3y]
instance FromRow Agent where
  fromRow
      = Agent $ Database.PostgreSQL.Simple.FromRow.field
        * Database.PostgreSQL.Simple.FromRow.field
        * Database.PostgreSQL.Simple.FromRow.field
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

data EntityOptions Source

Options for deriving Entity

Constructors

EntityOptions 

Fields

eoTableName :: String -> String

Type name to table name converter

eoColumnNames :: String -> String

Record field to column name converter

eoDeriveClasses :: [Name]

Typeclasses to derive for Id

eoIdType :: Name

Base type for Id

Embedding sql files

embedSql Source

Arguments

:: String

File path

-> Q Exp 

Deprecated: use sqlExpEmbed instead

sqlFile Source

Arguments

:: String

sql file pattern

-> Q Exp 

Deprecated: use sqlExpFile instead

Sql string interpolation

sqlExp :: QuasiQuoter Source

Maybe the main feature of all library. Quasiquoter which builds SqlBuilder from string query. Removes line comments and block comments (even nested) and sequences of spaces. Correctly works handles string literals and quoted identifiers. Here is examples of usage

>>> let name = "name"
>>> let val = "some 'value'"
>>> runSqlBuilder c [sqlExp|SELECT * FROM tbl WHERE ^{mkIdent name} = #{val}|]
"SELECT * FROM tbl WHERE \"name\" = 'some ''value'''"

And more comples example:

>>> let name = Just "name"
>>> let size = Just 10
>>> let active = Nothing :: Maybe Bool
>>> let condlist = catMaybes [ fmap (\a -> [sqlExp|name = #{a}|]) name, fmap (\a -> [sqlExp|size = #{a}|]) size, fmap (\a -> [sqlExp|active = #{a}|]) active]
>>> let cond = if L.null condlist then mempty else [sqlExp| WHERE ^{mconcat $ L.intersperse " AND " $ condlist} |]
>>> runSqlBuilder c [sqlExp|SELECT *   FROM tbl ^{cond} -- line comment|]
"SELECT * FROM tbl  WHERE name = 'name' AND size = 10  "

sqlExpEmbed Source

Arguments

:: String

file path

-> Q Exp

Expression of type SqlBuilder

Embed sql template and perform interpolation

let name = "name"
    foo = "bar"
    query = $(sqlExpEmbed "sqlfoobar.sql") -- using foo and bar inside

sqlExpFile :: String -> Q Exp Source

Just like sqlExpEmbed but uses pattern instead of file name. So, code

let query = $(sqlExpFile "foo/bar")

is just the same as

let query = $(sqlExpEmbed "sqlfoobar.sql")

This function inspired by Yesod's widgetFile