| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Database.PostgreSQL.Query.Internal
- entityFields :: Entity a => ([FN] -> [FN]) -> (FN -> FN) -> Proxy a -> SqlBuilder
- entityFieldsId :: Entity a => (FN -> FN) -> Proxy a -> SqlBuilder
- selectEntity :: Entity a => (Proxy a -> SqlBuilder) -> Proxy a -> SqlBuilder
- selectEntitiesBy :: (Entity a, ToMarkedRow b) => ([FN] -> [FN]) -> Proxy a -> b -> SqlBuilder
- insertEntity :: forall a. (Entity a, ToRow a) => a -> SqlBuilder
- insertManyEntities :: forall a. (Entity a, ToRow a) => NonEmpty a -> SqlBuilder
- entityToMR :: forall a. (Entity a, ToRow a) => a -> MarkedRow
- buildFields :: [FN] -> SqlBuilder
- updateTable :: (ToSqlBuilder q, ToMarkedRow flds) => Text -> flds -> q -> SqlBuilder
- insertInto :: ToMarkedRow b => Text -> b -> SqlBuilder
Entity functions
Arguments
| :: Entity a | |
| => ([FN] -> [FN]) | modify list of fields. Applied second |
| -> (FN -> FN) | modify each field name, e.g. prepend each field with prefix, like ("t"<>). Applied first |
| -> Proxy a | |
| -> SqlBuilder |
Build entity fields
>>>data Foo = Foo { fName :: Text, fSize :: Int }>>>instance Entity Foo where {newtype EntityId Foo = FooId Int ; fieldNames _ = ["name", "size"] ; tableName _ = "foo"}>>>runSqlBuilder con $ entityFields id id (Proxy :: Proxy Foo)"\"name\", \"size\""
>>>runSqlBuilder con $ entityFields ("id":) id (Proxy :: Proxy Foo)"\"id\", \"name\", \"size\""
>>>runSqlBuilder con $ entityFields (\l -> ("id":l) ++ ["created"]) id (Proxy :: Proxy Foo)"\"id\", \"name\", \"size\", \"created\""
>>>runSqlBuilder con $ entityFields id ("f"<>) (Proxy :: Proxy Foo)"\"f\".\"name\", \"f\".\"size\""
>>>runSqlBuilder con $ entityFields ("f.id":) ("f"<>) (Proxy :: Proxy Foo)"\"f\".\"id\", \"f\".\"name\", \"f\".\"size\""
entityFieldsId :: Entity a => (FN -> FN) -> Proxy a -> SqlBuilder Source
Same as entityFields but prefixes list of names with id
field. This is shorthand function for often usage.
>>>data Foo = Foo { fName :: Text, fSize :: Int }>>>instance Entity Foo where {newtype EntityId Foo = FooId Int ; fieldNames _ = ["name", "size"] ; tableName _ = "foo"}>>>runSqlBuilder con $ entityFieldsId id (Proxy :: Proxy Foo)"\"id\", \"name\", \"size\""
>>>runSqlBuilder con $ entityFieldsId ("f"<>) (Proxy :: Proxy Foo)"\"f\".\"id\", \"f\".\"name\", \"f\".\"size\""
Arguments
| :: Entity a | |
| => (Proxy a -> SqlBuilder) | build fields part from proxy |
| -> Proxy a | |
| -> SqlBuilder |
Generate SELECT query string for entity
>>>data Foo = Foo { fName :: Text, fSize :: Int }>>>instance Entity Foo where {newtype EntityId Foo = FooId Int ; fieldNames _ = ["name", "size"] ; tableName _ = "foo"}>>>runSqlBuilder con $ selectEntity (entityFieldsId id) (Proxy :: Proxy Foo)"SELECT \"id\", \"name\", \"size\" FROM \"foo\""
>>>runSqlBuilder con $ selectEntity (entityFieldsId ("f"<>)) (Proxy :: Proxy Foo)"SELECT \"f\".\"id\", \"f\".\"name\", \"f\".\"size\" FROM \"foo\""
>>>runSqlBuilder con $ selectEntity (entityFields id id) (Proxy :: Proxy Foo)"SELECT \"name\", \"size\" FROM \"foo\""
selectEntitiesBy :: (Entity a, ToMarkedRow b) => ([FN] -> [FN]) -> Proxy a -> b -> SqlBuilder Source
Generates SELECT FROM WHERE query with most used conditions
>>>data Foo = Foo { fName :: Text, fSize :: Int }>>>instance Entity Foo where {newtype EntityId Foo = FooId Int ; fieldNames _ = ["name", "size"] ; tableName _ = "foo"}>>>runSqlBuilder con $ selectEntitiesBy id (Proxy :: Proxy Foo) $ MR []"SELECT \"name\", \"size\" FROM \"foo\""
>>>runSqlBuilder con $ selectEntitiesBy id (Proxy :: Proxy Foo) $ MR [("name", mkValue "fooname")]"SELECT \"name\", \"size\" FROM \"foo\" WHERE \"name\" = 'fooname' "
>>>runSqlBuilder con $ selectEntitiesBy id (Proxy :: Proxy Foo) $ MR [("name", mkValue "fooname"), ("size", mkValue 10)]"SELECT \"name\", \"size\" FROM \"foo\" WHERE \"name\" = 'fooname' AND \"size\" = 10 "
insertEntity :: forall a. (Entity a, ToRow a) => a -> SqlBuilder Source
Generates INSERT INTO query for any instance of Entity and ToRow
>>>data Foo = Foo { fName :: Text, fSize :: Int }>>>instance Entity Foo where {newtype EntityId Foo = FooId Int ; fieldNames _ = ["name", "size"] ; tableName _ = "foo"}>>>instance ToRow Foo where { toRow Foo{..} = [toField fName, toField fSize] }>>>runSqlBuilder con $ insertEntity $ Foo "Enterprise" 910"INSERT INTO \"foo\" (\"name\", \"size\") VALUES ('Enterprise', 910)"
insertManyEntities :: forall a. (Entity a, ToRow a) => NonEmpty a -> SqlBuilder Source
Same as insertEntity but generates query to insert many queries at same time
>>>data Foo = Foo { fName :: Text, fSize :: Int }>>>instance Entity Foo where {newtype EntityId Foo = FooId Int ; fieldNames _ = ["name", "size"] ; tableName _ = "foo"}>>>instance ToRow Foo where { toRow Foo{..} = [toField fName, toField fSize] }>>>runSqlBuilder con $ insertManyEntities $ NL.fromList [Foo "meter" 1, Foo "table" 2, Foo "earth" 151930000000]"INSERT INTO \"foo\" (\"name\",\"size\") VALUES ('meter',1),('table',2),('earth',151930000000)"
entityToMR :: forall a. (Entity a, ToRow a) => a -> MarkedRow Source
Convert entity instance to marked row to perform inserts updates and same stuff
>>>data Foo = Foo { fName :: Text, fSize :: Int }>>>instance Entity Foo where {newtype EntityId Foo = FooId Int ; fieldNames _ = ["name", "size"] ; tableName _ = "foo"}>>>instance ToRow Foo where { toRow Foo{..} = [toField fName, toField fSize] }>>>runSqlBuilder con $ mrToBuilder ", " $ entityToMR $ Foo "Enterprise" 610" \"name\" = 'Enterprise' , \"size\" = 610 "
Low level generators
buildFields :: [FN] -> SqlBuilder Source
Generates comma separated list of field names
>>>runSqlBuilder con $ buildFields ["u" <> "name", "u" <> "phone", "e" <> "email"]"\"u\".\"name\", \"u\".\"phone\", \"e\".\"email\""
Arguments
| :: (ToSqlBuilder q, ToMarkedRow flds) | |
| => Text | table name |
| -> flds | fields to update |
| -> q | condition |
| -> SqlBuilder |
generates UPDATE query
>>>let name = "%vip%">>>runSqlBuilder con $ updateTable "ships" (MR [("size", mkValue 15)]) [sqlExp|WHERE size > 15 AND name NOT LIKE #{name}|]"UPDATE \"ships\" SET \"size\" = 15 WHERE size > 15 AND name NOT LIKE '%vip%'"
Arguments
| :: ToMarkedRow b | |
| => Text | table name |
| -> b | list of pairs (name, value) to insert into |
| -> SqlBuilder |
Generate INSERT INTO query for entity
>>>runSqlBuilder con $ insertInto "foo" $ MR [("name", mkValue "vovka"), ("hobby", mkValue "president")]"INSERT INTO \"foo\" (\"name\", \"hobby\") VALUES ('vovka', 'president')"