| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
IHP.ModelSupport
Contents
Synopsis
- class CanCreate a where
- create :: a -> IO a
- createMany :: [a] -> IO [a]
- createRecordDiscardResult :: a -> IO ()
- class KnownSymbol (GetTableName record) => Table record where
- tableName :: Text
- tableNameByteString :: ByteString
- columnNames :: [ByteString]
- primaryKeyColumnNames :: [ByteString]
- primaryKeyConditionForId :: Id record -> Action
- data FieldWithDefault valueType
- = Default
- | NonDefault valueType
- isValid :: HasField "meta" record MetaBag => record -> Bool
- type Id model = Id' (GetTableName model)
- newtype Id' (table :: Symbol) = Id (PrimaryKey table)
- type FieldName = ByteString
- class Record model where
- newRecord :: model
- withTransaction :: (?modelContext :: ModelContext) => ((?modelContext :: ModelContext) => IO a) -> IO a
- data Violation
- = TextViolation { }
- | HtmlViolation { }
- getModelName :: KnownSymbol (GetModelName model) => Text
- class InputValue a where
- inputValue :: a -> Text
- isNew :: HasField "meta" model MetaBag => model -> Bool
- didTouchField :: forall (fieldName :: Symbol) fieldValue record. (KnownSymbol fieldName, HasField fieldName record fieldValue, HasField "meta" record MetaBag, Eq fieldValue, Typeable record) => Proxy fieldName -> record -> Bool
- type family Include (name :: Symbol) model
- type family PrimaryKey (tableName :: Symbol)
- type family GetModelByTableName (tableName :: Symbol)
- data ModelContext = ModelContext {}
- class CanUpdate a where
- updateRecord :: a -> IO a
- updateRecordDiscardResult :: a -> IO ()
- type NormalizeModel model = GetModelByTableName (GetTableName model)
- type family GetTableName model :: Symbol
- type family GetModelName model :: Symbol
- createRecord :: (?modelContext :: ModelContext, CanCreate model) => model -> IO model
- deleteRecord :: forall record (table :: Symbol). (?modelContext :: ModelContext, Table record, Show (PrimaryKey table), HasField "id" record (Id record), GetTableName record ~ table, record ~ GetModelByTableName table) => record -> IO ()
- data MetaBag = MetaBag {
- annotations :: ![(Text, Violation)]
- touchedFields :: ![Text]
- originalDatabaseRecord :: Maybe Dynamic
- createModelContext :: NominalDiffTime -> Int -> ByteString -> Logger -> IO ModelContext
- sqlQuery :: (?modelContext :: ModelContext, ToRow q, FromRow r) => Query -> q -> IO [r]
- sqlQueryScalar :: (?modelContext :: ModelContext, ToRow q, FromField value) => Query -> q -> IO value
- data RowLevelSecurityContext = RowLevelSecurityContext {}
- notConnectedModelContext :: Logger -> ModelContext
- type family GetModelById id where ...
- unpackId :: forall (model :: Symbol). Id' model -> PrimaryKey model
- recordToInputValue :: (HasField "id" entity (Id entity), Show (PrimaryKey (GetTableName entity))) => entity -> Text
- packId :: forall (model :: Symbol). PrimaryKey model -> Id' model
- data LabeledData a b = LabeledData {
- labelValue :: a
- contentValue :: b
- class ParsePrimaryKey primaryKey where
- parsePrimaryKey :: Text -> Maybe primaryKey
- textToId :: forall (model :: Symbol) text. (HasCallStack, ParsePrimaryKey (PrimaryKey model), ConvertibleStrings text Text) => text -> Id' model
- measureTimeIfLogging :: (?modelContext :: ModelContext, ToRow q) => Text -> Connection -> IO a -> Query -> q -> IO a
- logQuery :: (?modelContext :: ModelContext, ToRow parameters) => Text -> Connection -> Query -> parameters -> NominalDiffTime -> IO ()
- withDatabaseConnection :: (?modelContext :: ModelContext) => (Connection -> IO a) -> IO a
- enhanceSqlError :: ToRow parameters => Query -> parameters -> IO a -> IO a
- withRLSParams :: (?modelContext :: ModelContext, ToRow params) => (Query -> [Action] -> result) -> Query -> params -> result
- sqlQuerySingleRow :: (?modelContext :: ModelContext, ToRow query, FromRow record) => Query -> query -> IO record
- sqlExec :: (?modelContext :: ModelContext, ToRow q) => Query -> q -> IO Int64
- sqlExecDiscardResult :: (?modelContext :: ModelContext, ToRow q) => Query -> q -> IO ()
- sqlQueryScalarOrNothing :: (?modelContext :: ModelContext, ToRow q, FromField value) => Query -> q -> IO (Maybe value)
- withTransactionConnection :: (?modelContext :: ModelContext) => ((?modelContext :: ModelContext) => IO a) -> IO a
- withRowLevelSecurityDisabled :: (?modelContext :: ModelContext) => ((?modelContext :: ModelContext) => IO a) -> IO a
- transactionConnectionOrError :: (?modelContext :: ModelContext) => Connection
- commitTransaction :: (?modelContext :: ModelContext) => IO ()
- rollbackTransaction :: (?modelContext :: ModelContext) => IO ()
- primaryKeyConditionColumnSelector :: Table record => ByteString
- primaryKeyCondition :: (HasField "id" record (Id record), Table record) => record -> Action
- deleteRecordById :: forall record (table :: Symbol). (?modelContext :: ModelContext, Table record, Show (PrimaryKey table), GetTableName record ~ table, record ~ GetModelByTableName table) => Id' table -> IO ()
- deleteRecords :: forall record (table :: Symbol). (?modelContext :: ModelContext, Show (PrimaryKey table), Table record, HasField "id" record (Id' table), GetTableName record ~ table, record ~ GetModelByTableName table) => [record] -> IO ()
- deleteRecordByIds :: forall record (table :: Symbol). (?modelContext :: ModelContext, Show (PrimaryKey table), Table record, GetTableName record ~ table, record ~ GetModelByTableName table) => [Id' table] -> IO ()
- ids :: HasField "id" record id => [record] -> [id]
- deleteAll :: (?modelContext :: ModelContext, Table record) => IO ()
- type family Include' (name :: [Symbol]) model where ...
- didChangeRecord :: HasField "meta" record MetaBag => record -> Bool
- didChange :: forall (fieldName :: Symbol) fieldValue record. (KnownSymbol fieldName, HasField fieldName record fieldValue, HasField "meta" record MetaBag, Eq fieldValue, Typeable record) => Proxy fieldName -> record -> Bool
- fieldWithDefault :: forall (name :: Symbol) model value. (KnownSymbol name, HasField name model value, HasField "meta" model MetaBag) => Proxy name -> model -> FieldWithDefault value
- data FieldWithUpdate (name :: k) value
- fieldWithUpdate :: forall (name :: Symbol) model value. (KnownSymbol name, HasField name model value, HasField "meta" model MetaBag) => Proxy name -> model -> FieldWithUpdate name value
- data RecordNotFoundException = RecordNotFoundException {
- queryAndParams :: (ByteString, [Action])
- data EnhancedSqlError = EnhancedSqlError {}
- trackTableRead :: (?modelContext :: ModelContext) => ByteString -> IO ()
- withTableReadTracker :: (?modelContext :: ModelContext) => ((?modelContext :: ModelContext, ?touchedTables :: IORef (Set ByteString)) => IO ()) -> IO ()
- onlyWhere :: forall record (fieldName :: Symbol) value. (KnownSymbol fieldName, HasField fieldName record value, Eq value) => Proxy fieldName -> value -> [record] -> [record]
- onlyWhereReferences :: forall record (fieldName :: Symbol) value referencedRecord. (KnownSymbol fieldName, HasField fieldName record value, Eq value, HasField "id" referencedRecord value) => Proxy fieldName -> referencedRecord -> [record] -> [record]
- onlyWhereReferencesMaybe :: forall record (fieldName :: Symbol) value referencedRecord. (KnownSymbol fieldName, HasField fieldName record (Maybe value), Eq value, HasField "id" referencedRecord value) => Proxy fieldName -> referencedRecord -> [record] -> [record]
- copyRecord :: (Table record, SetField "id" record id, Default id, SetField "meta" record MetaBag) => record -> record
- withoutQueryLogging :: (?modelContext :: ModelContext) => ((?modelContext :: ModelContext) => result) -> result
- module IHP.Postgres.Point
- module IHP.Postgres.Polygon
- module IHP.Postgres.Inet
- module IHP.Postgres.TSVector
- module IHP.Postgres.TimeParser
Documentation
class CanCreate a where Source #
Minimal complete definition
Methods
createMany :: [a] -> IO [a] Source #
createRecordDiscardResult :: a -> IO () Source #
Like createRecord but doesn't return the created record
class KnownSymbol (GetTableName record) => Table record where Source #
Access meta data for a database table
Minimal complete definition
columnNames, primaryKeyColumnNames, primaryKeyConditionForId
Methods
Returns the table name of a given model.
Example:
>>>tableName @User"users"
tableNameByteString :: ByteString Source #
Returns the table name of a given model as a bytestring.
Example:
>>>tableNameByteString @User"users"
columnNames :: [ByteString] Source #
Returns the list of column names for a given model
Example:
>>>columnNames @User["id", "email", "created_at"]
primaryKeyColumnNames :: [ByteString] Source #
Returns the list of column names, that are contained in the primary key for a given model
Example:
>>>primaryKeyColumnNames @User["id"]
>>>primaryKeyColumnNames @PostTagging["post_id", "tag_id"]
primaryKeyConditionForId :: Id record -> Action Source #
Returns the parameters for a WHERE conditions to match an entity by it's primary key, given the entities id
For tables with a simple primary key this simply the id:
>>>primaryKeyConditionForId project.idPlain "d619f3cf-f355-4614-8a4c-e9ea4f301e39"
If the table has a composite primary key, this returns multiple elements:
>>>primaryKeyConditionForId postTag.idMany [Plain "(", Plain "0ace9270-568f-4188-b237-3789aa520588", Plain ",", Plain "0b58fdf5-4bbb-4e57-a5b7-aa1c57148e1c", Plain ")"]
The order of the elements for a composite primary key must match the order of the columns returned by primaryKeyColumnNames
data FieldWithDefault valueType Source #
Represents fields that have a default value in an SQL schema
The Default constructor represents the default value from the schema,
while the NonDefault constructor holds some other value for the field
Constructors
| Default | |
| NonDefault valueType |
Instances
| Show valueType => Show (FieldWithDefault valueType) Source # | |
Defined in IHP.ModelSupport Methods showsPrec :: Int -> FieldWithDefault valueType -> ShowS # show :: FieldWithDefault valueType -> String # showList :: [FieldWithDefault valueType] -> ShowS # | |
| Eq valueType => Eq (FieldWithDefault valueType) Source # | |
Defined in IHP.ModelSupport Methods (==) :: FieldWithDefault valueType -> FieldWithDefault valueType -> Bool # (/=) :: FieldWithDefault valueType -> FieldWithDefault valueType -> Bool # | |
| ToField valueType => ToField (FieldWithDefault valueType) Source # | |
Defined in IHP.ModelSupport Methods toField :: FieldWithDefault valueType -> Action Source # | |
isValid :: HasField "meta" record MetaBag => record -> Bool Source #
Returns True when a record has no validation errors attached from a previous validation call
Example:
isValidProject :: Project -> Bool
isValidProject project =
project
|> validateField #name isNonEmpty
|> isValidtype Id model = Id' (GetTableName model) Source #
We need to map the model to its table name to prevent infinite recursion in the model data definition E.g. `type Project = Project' { id :: Id Project }` will not work But `type Project = Project' { id :: Id "projects" }` will
newtype Id' (table :: Symbol) Source #
Constructors
| Id (PrimaryKey table) |
Instances
| FromJSON (PrimaryKey a) => FromJSON (Id' a) Source # | |||||
| ToJSON (PrimaryKey a) => ToJSON (Id' a) Source # | |||||
| (KnownSymbol table, Data (PrimaryKey table)) => Data (Id' table) Source # | |||||
Defined in IHP.ModelSupport Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Id' table -> c (Id' table) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Id' table) # toConstr :: Id' table -> Constr # dataTypeOf :: Id' table -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Id' table)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Id' table)) # gmapT :: (forall b. Data b => b -> b) -> Id' table -> Id' table # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Id' table -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Id' table -> r # gmapQ :: (forall d. Data d => d -> u) -> Id' table -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Id' table -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Id' table -> m (Id' table) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Id' table -> m (Id' table) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Id' table -> m (Id' table) # | |||||
| (Read (PrimaryKey model), ParsePrimaryKey (PrimaryKey model)) => IsString (Id' model) Source # | Sometimes you have a hardcoded UUID value which represents some record id. This instance allows you to write the Id like a string: let projectId = "ca63aace-af4b-4e6c-bcfa-76ca061dbdc6" :: Id Project | ||||
Defined in IHP.ModelSupport Methods fromString :: String -> Id' model # | |||||
| Show (PrimaryKey model) => Show (Id' model) Source # | |||||
| PrimaryKey table ~ UUID => Serialize (Id' table) Source # | |||||
| (KnownSymbol table, NFData (PrimaryKey table)) => NFData (Id' table) Source # | |||||
Defined in IHP.ModelSupport | |||||
| Eq (PrimaryKey table) => Eq (Id' table) Source # | |||||
| Ord (PrimaryKey table) => Ord (Id' table) Source # | |||||
| Hashable (PrimaryKey table) => Hashable (Id' table) Source # | |||||
| ParamReader (PrimaryKey model') => ParamReader (Id' model') Source # | |||||
Defined in IHP.Controller.Param Methods readParameter :: ByteString -> Either ByteString (Id' model') Source # readParameterJSON :: Value -> Either ByteString (Id' model') Source # | |||||
| IsEmpty (PrimaryKey table) => IsEmpty (Id' table) Source # | |||||
| InputValue (PrimaryKey model') => InputValue (Id' model') Source # | |||||
Defined in IHP.ModelSupport Methods inputValue :: Id' model' -> Text Source # | |||||
| InputValue (PrimaryKey table) => ApplyAttribute (Id' table) Source # | |||||
Defined in IHP.ViewSupport | |||||
| FromField (PrimaryKey model) => FromField (Id' model) Source # | |||||
Defined in IHP.ModelSupport Methods fromField :: FieldParser (Id' model) Source # | |||||
| ToField (PrimaryKey model) => ToField (Id' model) Source # | |||||
| (model ~ GetModelById (Id' table), GetTableName model ~ table, FilterPrimaryKey table) => Fetchable (Id' table) model Source # | |||||
Defined in IHP.Fetch Associated Types
| |||||
| (model ~ GetModelById (Id' table), GetTableName model ~ table, FilterPrimaryKey table) => Fetchable (Maybe (Id' table)) model Source # | |||||
Defined in IHP.Fetch Associated Types
| |||||
| (model ~ GetModelById (Id' table), GetModelByTableName table ~ model, GetTableName model ~ table) => Fetchable [Id' table] model Source # | |||||
Defined in IHP.Fetch Associated Types
| |||||
| (TypeError (('Text "Looks like you forgot to pass a " ':<>: 'ShowType (GetModelByTableName record)) ':<>: 'Text " id to this data constructor.") :: Constraint) => Eq (Id' record -> controller) Source # | |||||
| type FetchResult (Id' table) model Source # | |||||
Defined in IHP.Fetch | |||||
| type FetchResult (Maybe (Id' table)) model Source # | |||||
Defined in IHP.Fetch | |||||
| type FetchResult [Id' table] model Source # | |||||
Defined in IHP.Fetch | |||||
type FieldName = ByteString Source #
withTransaction :: (?modelContext :: ModelContext) => ((?modelContext :: ModelContext) => IO a) -> IO a Source #
Executes the given block with a database transaction
Example:
withTransaction do
company <- newRecord @Company |> createRecord
-- When creating the user fails, there will be no company left over
user <- newRecord @User
|> set #companyId company.id
|> createRecord
company <- company
|> set #ownerId user.id
|> updateRecordThe error message of a validator can be either a plain text value or a HTML formatted value
Constructors
| TextViolation | Plain text validation error, like "cannot be empty" |
| HtmlViolation | HTML formatted, already pre-escaped validation error, like "Invalid, please href="http://example.com"check the documentation/a" |
getModelName :: KnownSymbol (GetModelName model) => Text Source #
Returns the model name of a given model as Text
Example:
>>>modelName @User"User"
>>>modelName @Project"Project"
class InputValue a where Source #
Methods
inputValue :: a -> Text Source #
Instances
isNew :: HasField "meta" model MetaBag => model -> Bool Source #
Returns True when the record has not been saved to the database yet. Returns False otherwise.
Example: Returns True when a record has not been inserted yet.
>>>let project = newRecord @Project>>>isNew projectTrue
Example: Returns False after inserting a record.
>>>project <- createRecord project>>>isNew projectFalse
Example: Returns False for records which have been fetched from the database.
>>>book <- query @Book |> fetchOne>>>isNew bookFalse
didTouchField :: forall (fieldName :: Symbol) fieldValue record. (KnownSymbol fieldName, HasField fieldName record fieldValue, HasField "meta" record MetaBag, Eq fieldValue, Typeable record) => Proxy fieldName -> record -> Bool Source #
Returns True if set was called on that field
Example: Returns False for freshly fetched records
>>>let projectId = "227fbba3-0578-4eb8-807d-b9b692c3644f" :: Id Project>>>project <- fetch projectId>>>didTouchField #name projectFalse
Example: Returns True after setting a field
>>>let projectId = "227fbba3-0578-4eb8-807d-b9b692c3644f" :: Id Project>>>project <- fetch projectId>>>project |> set #name project.name |> didTouchField #nameTrue
type family PrimaryKey (tableName :: Symbol) Source #
Provides the primary key type for a given table. The instances are usually declared by the generated haskell code in Generated.Types
Example: Defining the primary key for a users table
type instance PrimaryKey "users" = UUID
Example: Defining the primary key for a table with a SERIAL pk
type instance PrimaryKey "projects" = Int
type family GetModelByTableName (tableName :: Symbol) Source #
data ModelContext Source #
Provides the db connection and some IHP-specific db configuration
Constructors
| ModelContext | |
Fields
| |
class CanUpdate a where Source #
Minimal complete definition
Methods
updateRecord :: a -> IO a Source #
updateRecordDiscardResult :: a -> IO () Source #
Like updateRecord but doesn't return the updated record
type NormalizeModel model = GetModelByTableName (GetTableName model) Source #
Helper type to deal with models where relations are included or that are only partially fetched Examples:
>>>NormalizeModel (Include "author_id" Post)Post
>>>NormalizeModel PostPost
type family GetTableName model :: Symbol Source #
type family GetModelName model :: Symbol Source #
createRecord :: (?modelContext :: ModelContext, CanCreate model) => model -> IO model Source #
deleteRecord :: forall record (table :: Symbol). (?modelContext :: ModelContext, Table record, Show (PrimaryKey table), HasField "id" record (Id record), GetTableName record ~ table, record ~ GetModelByTableName table) => record -> IO () Source #
Runs a DELETE query for a record.
>>>let project :: Project = ...>>>deleteRecord projectDELETE FROM projects WHERE id = '..'
Use deleteRecords if you want to delete multiple records.
Every IHP database record has a magic meta field which keeps a MetaBag inside. This data structure is used e.g. to keep track of the validation errors that happend.
Constructors
| MetaBag | |
Fields
| |
createModelContext :: NominalDiffTime -> Int -> ByteString -> Logger -> IO ModelContext Source #
sqlQuery :: (?modelContext :: ModelContext, ToRow q, FromRow r) => Query -> q -> IO [r] Source #
Runs a raw sql query
Example:
users <- sqlQuery "SELECT id, firstname, lastname FROM users" ()
Take a look at IHP.QueryBuilder for a typesafe approach on building simple queries.
- AutoRefresh:* When using
sqlQuerywith AutoRefresh, you need to usetrackTableReadto let AutoRefresh know that you have accessed a certain table. Otherwise AutoRefresh will not watch table of your custom sql query.
Use sqlQuerySingleRow if you expect only a single row to be returned.
sqlQueryScalar :: (?modelContext :: ModelContext, ToRow q, FromField value) => Query -> q -> IO value Source #
Runs a raw sql query which results in a single scalar value such as an integer or string
Example:
usersCount <- sqlQueryScalar "SELECT COUNT(*) FROM users"
Take a look at IHP.QueryBuilder for a typesafe approach on building simple queries.
data RowLevelSecurityContext Source #
When row level security is enabled at runtime, this keeps track of the current logged in user and the postgresql role to switch to.
Constructors
| RowLevelSecurityContext | |
Fields
| |
notConnectedModelContext :: Logger -> ModelContext Source #
Provides a mock ModelContext to be used when a database connection is not available
type family GetModelById id where ... Source #
Equations
| GetModelById (Maybe (Id' tableName)) = Maybe (GetModelByTableName tableName) | |
| GetModelById (Id' tableName) = GetModelByTableName tableName |
unpackId :: forall (model :: Symbol). Id' model -> PrimaryKey model Source #
Unwraps a Id value into an UUID
>>>unpackId ("296e5a50-b237-4ee9-83b0-17fb1e6f208f" :: Id User)"296e5a50-b237-4ee9-83b0-17fb1e6f208f" :: UUID
recordToInputValue :: (HasField "id" entity (Id entity), Show (PrimaryKey (GetTableName entity))) => entity -> Text Source #
packId :: forall (model :: Symbol). PrimaryKey model -> Id' model Source #
Turns an UUID into a Id type
let uuid :: UUID = "5240e79c-97ff-4a5f-8567-84112541aaba" let userId :: Id User = packId uuid
data LabeledData a b Source #
Record type for objects of model types labeled with values from different database tables. (e.g. comments labeled with the IDs of the posts they belong to).
Constructors
| LabeledData | |
Fields
| |
Instances
| (Show a, Show b) => Show (LabeledData a b) Source # | |
Defined in IHP.ModelSupport Methods showsPrec :: Int -> LabeledData a b -> ShowS # show :: LabeledData a b -> String # showList :: [LabeledData a b] -> ShowS # | |
| (FromField label, FromRow a) => FromRow (LabeledData label a) Source # | |
Defined in IHP.ModelSupport Methods fromRow :: RowParser (LabeledData label a) Source # | |
class ParsePrimaryKey primaryKey where Source #
Methods
parsePrimaryKey :: Text -> Maybe primaryKey Source #
Instances
| ParsePrimaryKey Text Source # | |
Defined in IHP.ModelSupport | |
| ParsePrimaryKey UUID Source # | |
Defined in IHP.ModelSupport | |
textToId :: forall (model :: Symbol) text. (HasCallStack, ParsePrimaryKey (PrimaryKey model), ConvertibleStrings text Text) => text -> Id' model Source #
Transforms a text, bytestring or string into an Id. Throws an exception if the input is invalid.
Example:
let projectIdText = "7cbc76e2-1c4f-49b6-a7d9-5015e7575a9b" :: Text let projectId = (textToId projectIdText) :: Id Project
In case your UUID value is hardcoded, there is also an IsString instance, so you
can just write it like:
let projectId = "ca63aace-af4b-4e6c-bcfa-76ca061dbdc6" :: Id Project
measureTimeIfLogging :: (?modelContext :: ModelContext, ToRow q) => Text -> Connection -> IO a -> Query -> q -> IO a Source #
Measure and log the query time for a given query action if the log level is Debug. If the log level is greater than debug, just perform the query action without measuring time.
logQuery :: (?modelContext :: ModelContext, ToRow parameters) => Text -> Connection -> Query -> parameters -> NominalDiffTime -> IO () Source #
withDatabaseConnection :: (?modelContext :: ModelContext) => (Connection -> IO a) -> IO a Source #
enhanceSqlError :: ToRow parameters => Query -> parameters -> IO a -> IO a Source #
Catches SqlError and wraps them in EnhancedSqlError
withRLSParams :: (?modelContext :: ModelContext, ToRow params) => (Query -> [Action] -> result) -> Query -> params -> result Source #
Wraps the query with Row level security boilerplate, if a row level security context was provided
Example:
If a row level security context is given, this will turn a query like the following
withRLSParams runQuery "SELECT * FROM projects WHERE id = ?" (Only "..")
Into the following equivalent:
runQuery "SET LOCAL ROLE ?; SET LOCAL rls.ihp_user_id = ?; SELECT * FROM projects WHERE id = ?" ["ihp_authenticated", "<user id>", .."]
sqlQuerySingleRow :: (?modelContext :: ModelContext, ToRow query, FromRow record) => Query -> query -> IO record Source #
Runs a raw sql query, that is expected to return a single result row
Like sqlQuery, but useful when you expect only a single row as the result
Example:
user <- sqlQuerySingleRow "SELECT id, firstname, lastname FROM users WHERE id = ?" (Only user.id)
Take a look at IHP.QueryBuilder for a typesafe approach on building simple queries.
- AutoRefresh:* When using
sqlQuerySingleRowwith AutoRefresh, you need to usetrackTableReadto let AutoRefresh know that you have accessed a certain table. Otherwise AutoRefresh will not watch table of your custom sql query.
sqlExec :: (?modelContext :: ModelContext, ToRow q) => Query -> q -> IO Int64 Source #
Runs a sql statement (like a CREATE statement)
Example:
sqlExec "CREATE TABLE users ()" ()
sqlExecDiscardResult :: (?modelContext :: ModelContext, ToRow q) => Query -> q -> IO () Source #
Runs a sql statement (like a CREATE statement), but doesn't return any result
Example:
sqlExecDiscardResult "CREATE TABLE users ()" ()
sqlQueryScalarOrNothing :: (?modelContext :: ModelContext, ToRow q, FromField value) => Query -> q -> IO (Maybe value) Source #
Runs a raw sql query which results in a single scalar value such as an integer or string, or nothing
Example:
usersCount <- sqlQueryScalarOrNothing "SELECT COUNT(*) FROM users"
Take a look at IHP.QueryBuilder for a typesafe approach on building simple queries.
withTransactionConnection :: (?modelContext :: ModelContext) => ((?modelContext :: ModelContext) => IO a) -> IO a Source #
withRowLevelSecurityDisabled :: (?modelContext :: ModelContext) => ((?modelContext :: ModelContext) => IO a) -> IO a Source #
Executes the given block with the main database role and temporarly sidesteps the row level security policies.
This is used e.g. by IHP AutoRefresh to be able to set up it's database triggers. When trying to set up a database
trigger from the ihp_authenticated role, it typically fails because it's missing permissions. Using withRowLevelSecurityDisabled
we switch to the main role which is allowed to set up database triggers.
SQL queries run from within the passed block are executed in their own transaction.
Example:
-- SQL code executed here might be run from the ihp_authenticated role withRowLevelSecurityDisabled do -- SQL code executed here is run as the main IHP db role sqlExec "CREATE OR REPLACE FUNCTION .." ()
transactionConnectionOrError :: (?modelContext :: ModelContext) => Connection Source #
Returns the postgres connection when called within a withTransaction block
Throws an error if called from outside a withTransaction
commitTransaction :: (?modelContext :: ModelContext) => IO () Source #
rollbackTransaction :: (?modelContext :: ModelContext) => IO () Source #
primaryKeyConditionColumnSelector :: Table record => ByteString Source #
Returns ByteString, that represents the part of an SQL where clause, that matches on a tuple consisting of all the primary keys
For table with simple primary keys this simply returns the name of the primary key column, without wrapping in a tuple
>>> primaryKeyColumnSelector PostTag
"(post_tags.post_id, post_tags.tag_id)"
>>> primaryKeyColumnSelector Post
"post_tags.post_id"
primaryKeyCondition :: (HasField "id" record (Id record), Table record) => record -> Action Source #
Returns WHERE conditions to match an entity by it's primary key
For tables with a simple primary key this returns a tuple with the id:
>>>primaryKeyCondition projectPlain "d619f3cf-f355-4614-8a4c-e9ea4f301e39"
If the table has a composite primary key, this returns multiple elements:
>>>primaryKeyCondition postTagMany [Plain "(", Plain "0ace9270-568f-4188-b237-3789aa520588", Plain ",", Plain "0b58fdf5-4bbb-4e57-a5b7-aa1c57148e1c", Plain ")"]
deleteRecordById :: forall record (table :: Symbol). (?modelContext :: ModelContext, Table record, Show (PrimaryKey table), GetTableName record ~ table, record ~ GetModelByTableName table) => Id' table -> IO () Source #
Like deleteRecord but using an Id
>>>let project :: Id Project = ...>>>delete projectIdDELETE FROM projects WHERE id = '..'
deleteRecords :: forall record (table :: Symbol). (?modelContext :: ModelContext, Show (PrimaryKey table), Table record, HasField "id" record (Id' table), GetTableName record ~ table, record ~ GetModelByTableName table) => [record] -> IO () Source #
Runs a DELETE query for a list of records.
>>>let projects :: [Project] = ...>>>deleteRecords projectsDELETE FROM projects WHERE id IN (..)
deleteRecordByIds :: forall record (table :: Symbol). (?modelContext :: ModelContext, Show (PrimaryKey table), Table record, GetTableName record ~ table, record ~ GetModelByTableName table) => [Id' table] -> IO () Source #
Like deleteRecordById but for a list of Ids.
>>>let projectIds :: [ Id Project ] = ...>>>delete projectIdsDELETE FROM projects WHERE id IN ('..')
ids :: HasField "id" record id => [record] -> [id] Source #
Returns the ids for a list of models
Shorthand for map (.id) records.
>>>users <- query @User |> fetch>>>ids users[227fbba3-0578-4eb8-807d-b9b692c3644f, 9d7874f2-5343-429b-bcc4-8ee62a5a6895, ...] :: [Id User]
deleteAll :: (?modelContext :: ModelContext, Table record) => IO () Source #
Runs a DELETE query to delete all rows in a table.
>>>deleteAll @ProjectDELETE FROM projects
didChangeRecord :: HasField "meta" record MetaBag => record -> Bool Source #
Returns True if any fields of the record have unsaved changes
Example: Returns False for freshly fetched records
>>>let projectId = "227fbba3-0578-4eb8-807d-b9b692c3644f" :: Id Project>>>project <- fetch projectId>>>didChangeRecord projectFalse
Example: Returns True after setting a field
>>>let projectId = "227fbba3-0578-4eb8-807d-b9b692c3644f" :: Id Project>>>project <- fetch projectId>>>project |> set #name "New Name" |> didChangeRecordTrue
didChange :: forall (fieldName :: Symbol) fieldValue record. (KnownSymbol fieldName, HasField fieldName record fieldValue, HasField "meta" record MetaBag, Eq fieldValue, Typeable record) => Proxy fieldName -> record -> Bool Source #
Returns True if the specific field of the record has unsaved changes
Example: Returns False for freshly fetched records
>>>let projectId = "227fbba3-0578-4eb8-807d-b9b692c3644f" :: Id Project>>>project <- fetch projectId>>>didChange #name projectFalse
Example: Returns True after setting a field
>>>let projectId = "227fbba3-0578-4eb8-807d-b9b692c3644f" :: Id Project>>>project <- fetch projectId>>>project |> set #name "New Name" |> didChange #nameTrue
Example: Setting a flash message after updating the profile picture
when (user |> didChange #profilePictureUrl) (setSuccessMessage "Your Profile Picture has been updated. It might take a few minutes until it shows up everywhere")
fieldWithDefault :: forall (name :: Symbol) model value. (KnownSymbol name, HasField name model value, HasField "meta" model MetaBag) => Proxy name -> model -> FieldWithDefault value Source #
Construct a FieldWithDefault
Use the default SQL value when the field hasn't been touched since the
record was created. This information is stored in the touchedFields
attribute of the meta field.
data FieldWithUpdate (name :: k) value Source #
Represents fields that may have been updated
The NoUpdate constructor represents the existing value in the database,
while the Update constructor holds some new value for the field
Instances
| Show value => Show (FieldWithUpdate name value) Source # | |
Defined in IHP.ModelSupport Methods showsPrec :: Int -> FieldWithUpdate name value -> ShowS # show :: FieldWithUpdate name value -> String # showList :: [FieldWithUpdate name value] -> ShowS # | |
| Eq value => Eq (FieldWithUpdate name value) Source # | |
Defined in IHP.ModelSupport Methods (==) :: FieldWithUpdate name value -> FieldWithUpdate name value -> Bool # (/=) :: FieldWithUpdate name value -> FieldWithUpdate name value -> Bool # | |
| (KnownSymbol name, ToField value) => ToField (FieldWithUpdate name value) Source # | |
Defined in IHP.ModelSupport Methods toField :: FieldWithUpdate name value -> Action Source # | |
fieldWithUpdate :: forall (name :: Symbol) model value. (KnownSymbol name, HasField name model value, HasField "meta" model MetaBag) => Proxy name -> model -> FieldWithUpdate name value Source #
Construct a FieldWithUpdate
Use the current database value when the field hasn't been touched since the
record was accessed. This information is stored in the touchedFields
attribute of the meta field.
data RecordNotFoundException Source #
Thrown by fetchOne when the query result is empty
Constructors
| RecordNotFoundException | |
Fields
| |
Instances
| Exception RecordNotFoundException Source # | |
Defined in IHP.ModelSupport | |
| Show RecordNotFoundException Source # | |
Defined in IHP.ModelSupport Methods showsPrec :: Int -> RecordNotFoundException -> ShowS # show :: RecordNotFoundException -> String # showList :: [RecordNotFoundException] -> ShowS # | |
data EnhancedSqlError Source #
Whenever calls to query or execute
raise an SqlError exception, we wrap that exception in this data structure.
This allows us to show the actual database query that has triggered the error.
Constructors
| EnhancedSqlError | |
Fields
| |
Instances
| ToJSON EnhancedSqlError Source # | |
Defined in IHP.DataSync.REST.Controller Methods toJSON :: EnhancedSqlError -> Value Source # toEncoding :: EnhancedSqlError -> Encoding Source # toJSONList :: [EnhancedSqlError] -> Value Source # toEncodingList :: [EnhancedSqlError] -> Encoding Source # omitField :: EnhancedSqlError -> Bool Source # | |
| Exception EnhancedSqlError Source # | |
Defined in IHP.ModelSupport Methods toException :: EnhancedSqlError -> SomeException # | |
| Show EnhancedSqlError Source # | |
Defined in IHP.ModelSupport Methods showsPrec :: Int -> EnhancedSqlError -> ShowS # show :: EnhancedSqlError -> String # showList :: [EnhancedSqlError] -> ShowS # | |
trackTableRead :: (?modelContext :: ModelContext) => ByteString -> IO () Source #
Useful to manually mark a table read when doing a custom sql query inside AutoRefresh or withTableReadTracker.
When using fetch on a query builder, this function is automatically called. That's why you only need to call
it yourself when using sqlQuery to run a custom query.
Example:
action MyAction = autoRefresh do
users <- sqlQuery "SELECT * FROM users WHERE .."
trackTableRead "users"
render MyView { .. }withTableReadTracker :: (?modelContext :: ModelContext) => ((?modelContext :: ModelContext, ?touchedTables :: IORef (Set ByteString)) => IO ()) -> IO () Source #
Track all tables in SELECT queries executed within the given IO action.
You can read the touched tables by this function by accessing the variable ?touchedTables inside your given IO action.
Example:
withTableReadTracker do
project <- query @Project |> fetchOne
user <- query @User |> fetchOne
tables <- readIORef ?touchedTables
-- tables = Set.fromList ["projects", "users"]
onlyWhere :: forall record (fieldName :: Symbol) value. (KnownSymbol fieldName, HasField fieldName record value, Eq value) => Proxy fieldName -> value -> [record] -> [record] Source #
Shorthand filter function
In IHP code bases you often write filter functions such as these:
getUserPosts user posts =
filter (\p -> p.userId == user.id) postsThis can be written in a shorter way using onlyWhere:
getUserPosts user posts =
posts |> onlyWhere #userId user.idBecause the userId field is an Id, we can use onlyWhereReferences to make it even shorter:
getUserPosts user posts =
posts |> onlyWhereReferences #userId userIf the Id field is nullable, we need to use onlyWhereReferencesMaybe:
getUserTasks user tasks =
tasks |> onlyWhereReferencesMaybe #optionalUserId useronlyWhereReferences :: forall record (fieldName :: Symbol) value referencedRecord. (KnownSymbol fieldName, HasField fieldName record value, Eq value, HasField "id" referencedRecord value) => Proxy fieldName -> referencedRecord -> [record] -> [record] Source #
Shorthand filter function for Id fields
In IHP code bases you often write filter functions such as these:
getUserPosts user posts =
filter (\p -> p.userId == user.id) postsThis can be written in a shorter way using onlyWhereReferences:
getUserPosts user posts =
posts |> onlyWhereReferences #userId userIf the Id field is nullable, we need to use onlyWhereReferencesMaybe:
getUserTasks user tasks =
tasks |> onlyWhereReferencesMaybe #optionalUserId userSee onlyWhere for more details.
onlyWhereReferencesMaybe :: forall record (fieldName :: Symbol) value referencedRecord. (KnownSymbol fieldName, HasField fieldName record (Maybe value), Eq value, HasField "id" referencedRecord value) => Proxy fieldName -> referencedRecord -> [record] -> [record] Source #
Shorthand filter function for nullable Id fields
In IHP code bases you often write filter functions such as these:
getUserTasks user tasks =
filter (\task -> task.optionalUserId == Just user.id) tasksThis can be written in a shorter way using onlyWhereReferencesMaybe:
getUserTasks user tasks =
tasks |> onlyWhereReferencesMaybe #optionalUserId userSee onlyWhere for more details.
copyRecord :: (Table record, SetField "id" record id, Default id, SetField "meta" record MetaBag) => record -> record Source #
Copies all the fields (except the id field) into a new record
Example: Duplicate a database record (except the primary key of course)
project <- fetch projectId duplicatedProject <- createRecord (copyRecord project)
withoutQueryLogging :: (?modelContext :: ModelContext) => ((?modelContext :: ModelContext) => result) -> result Source #
Runs sql queries without logging them
Example:
users <- withoutQueryLogging (sqlQuery "SELECT * FROM users" ())
module IHP.Postgres.Point
module IHP.Postgres.Polygon
module IHP.Postgres.Inet
module IHP.Postgres.TSVector
module IHP.Postgres.TimeParser
Orphan instances
| Default Value Source # | |
| Default Point Source # | |
| Default Polygon Source # | |
| Default TSVector Source # | |
| Default PGInterval Source # | |
Methods def :: PGInterval Source # | |
| Default Scientific Source # | |
Methods def :: Scientific Source # | |
| Default Text Source # | |
| Default Day Source # | |
| Default NominalDiffTime Source # | |
Methods | |
| Default UTCTime Source # | |
| Default LocalTime Source # | |
| Default TimeOfDay Source # | |
| Default Bool Source # | |
| Default (Binary ByteString) Source # | |
Methods def :: Binary ByteString Source # | |
| (FromField value, Typeable value) => FromField [value] Source # | This instancs allows us to avoid wrapping lists with PGArray when
using sql types such as |
Methods fromField :: FieldParser [value] Source # | |
| ToField value => ToField [value] Source # | This instance allows us to avoid wrapping lists with PGArray when
using sql types such as |