| Copyright | Flipstone Technology Partners 2023 |
|---|---|
| License | MIT |
| Stability | Stable |
| Safe Haskell | Safe-Inferred |
| Language | Haskell2010 |
Orville.PostgreSQL.Marshall.SqlMarshaller
Description
This module provides functions for constructing a mapping between Haskell data
types and SQL column schemas. The SqlMarshaller that represents this mapping
can be used to serialize Haskell values both to and from SQL column sets. In
most cases, you construct a SqlMarshaller as part of building your
TableDefinition and Orville handles the rest. In
other cases, you might use a SqlMarshaller with a lower-level Orville
function. For instance, to decode the result set of a custom SQL query.
Since: 1.0.0.0
Synopsis
- data SqlMarshaller a b
- data AnnotatedSqlMarshaller writeEntity readEntity
- annotateSqlMarshaller :: [FieldName] -> SqlMarshaller writeEntity readEntity -> AnnotatedSqlMarshaller writeEntity readEntity
- annotateSqlMarshallerEmptyAnnotation :: SqlMarshaller writeEntity readEntity -> AnnotatedSqlMarshaller writeEntity readEntity
- unannotatedSqlMarshaller :: AnnotatedSqlMarshaller writeEntity readEntity -> SqlMarshaller writeEntity readEntity
- mapSqlMarshaller :: (SqlMarshaller readEntityA writeEntityA -> SqlMarshaller readEntityB writeEntityB) -> AnnotatedSqlMarshaller readEntityA writeEntityA -> AnnotatedSqlMarshaller readEntityB writeEntityB
- data MarshallerField writeEntity where
- Natural :: FieldDefinition nullability a -> Maybe (writeEntity -> a) -> MarshallerField writeEntity
- Synthetic :: SyntheticField a -> MarshallerField writeEntity
- marshallResultFromSql :: ExecutionResult result => ErrorDetailLevel -> AnnotatedSqlMarshaller writeEntity readEntity -> result -> IO (Either MarshallError [readEntity])
- marshallResultFromSqlUsingRowIdExtractor :: ExecutionResult result => ErrorDetailLevel -> RowIdentityExtractor -> SqlMarshaller writeEntity readEntity -> result -> IO (Either MarshallError [readEntity])
- data RowIdentityExtractor
- mkRowIdentityExtractor :: ExecutionResult result => [FieldName] -> result -> RowIdentityExtractor
- marshallField :: (writeEntity -> fieldValue) -> FieldDefinition nullability fieldValue -> SqlMarshaller writeEntity fieldValue
- marshallSyntheticField :: SyntheticField fieldValue -> SqlMarshaller writeEntity fieldValue
- marshallReadOnlyField :: FieldDefinition nullability fieldValue -> SqlMarshaller writeEntity fieldValue
- marshallReadOnly :: SqlMarshaller a b -> SqlMarshaller c b
- marshallNested :: (parentEntity -> nestedWriteEntity) -> SqlMarshaller nestedWriteEntity nestedReadEntity -> SqlMarshaller parentEntity nestedReadEntity
- marshallMaybe :: SqlMarshaller a b -> SqlMarshaller (Maybe a) (Maybe b)
- marshallPartial :: SqlMarshaller a (Either String b) -> SqlMarshaller a b
- prefixMarshaller :: String -> SqlMarshaller readEntity writeEntity -> SqlMarshaller readEntity writeEntity
- data ReadOnlyColumnOption
- collectFromField :: ReadOnlyColumnOption -> (forall nullability a. FieldDefinition nullability a -> result) -> MarshallerField entity -> [result] -> [result]
- marshallEntityToSetClauses :: SqlMarshaller writeEntity readEntity -> writeEntity -> [SetClause]
- foldMarshallerFields :: SqlMarshaller writeEntity readEntity -> result -> (MarshallerField writeEntity -> result -> result) -> result
- marshallerDerivedColumns :: SqlMarshaller writeEntity readEntity -> [DerivedColumn]
- marshallerTableConstraints :: SqlMarshaller writeEntity readEntity -> TableConstraints
- mkRowSource :: ExecutionResult result => SqlMarshaller writeEntity readEntity -> result -> IO (RowSource readEntity)
- data RowSource readEntity
- mapRowSource :: (a -> b) -> RowSource a -> RowSource b
- applyRowSource :: RowSource (a -> b) -> RowSource a -> RowSource b
- constRowSource :: readEntity -> RowSource readEntity
- failRowSource :: MarshallErrorDetails -> RowSource a
Documentation
data SqlMarshaller a b Source #
SqlMarshaller is how we group the lowest-level translation of single fields
into a higher-level marshalling of full SQL records into Haskell records.
This is a flexible abstraction that allows us to ultimately model SQL tables
and work with them as potentially nested Haskell records. We can then
"marshall" the data as we want to model it in SQL and Haskell.
Since: 1.0.0.0
Instances
| Applicative (SqlMarshaller a) Source # | |
Defined in Orville.PostgreSQL.Marshall.SqlMarshaller Methods pure :: a0 -> SqlMarshaller a a0 # (<*>) :: SqlMarshaller a (a0 -> b) -> SqlMarshaller a a0 -> SqlMarshaller a b # liftA2 :: (a0 -> b -> c) -> SqlMarshaller a a0 -> SqlMarshaller a b -> SqlMarshaller a c # (*>) :: SqlMarshaller a a0 -> SqlMarshaller a b -> SqlMarshaller a b # (<*) :: SqlMarshaller a a0 -> SqlMarshaller a b -> SqlMarshaller a a0 # | |
| Functor (SqlMarshaller a) Source # | |
Defined in Orville.PostgreSQL.Marshall.SqlMarshaller Methods fmap :: (a0 -> b) -> SqlMarshaller a a0 -> SqlMarshaller a b # (<$) :: a0 -> SqlMarshaller a b -> SqlMarshaller a a0 # | |
data AnnotatedSqlMarshaller writeEntity readEntity Source #
An AnnotatedSqlMarshaller is a SqlMarshaller that contains extra
annotations which cannot necessarily be determined from the data in the
marshaller itself. In particular, it includes the names of fields that can be
used to identify a row in the database when an error is encountered during
decoding.
Normally you will not need to interact with this type directly -- the
TableDefinition type creates it for you using the information it has about
the primary key of the table to identify rows in decoding errors. If you are
executing custom queries directly, you may need to annotate a raw
SqlMarshaller yourself so that rows can be identified. See
annotateSqlMarshaller and annotateSqlMarshallerEmptyAnnotation.
Since: 1.0.0.0
annotateSqlMarshaller :: [FieldName] -> SqlMarshaller writeEntity readEntity -> AnnotatedSqlMarshaller writeEntity readEntity Source #
Creates an AnnotatedSqlMarshaller that will use the given column names
to identify rows in error messages when decoding fails. Any column names
in the list that are not present in the result set will simply be omitted
from the error message.
Since: 1.0.0.0
annotateSqlMarshallerEmptyAnnotation :: SqlMarshaller writeEntity readEntity -> AnnotatedSqlMarshaller writeEntity readEntity Source #
Creates an AnnotatedSqlMarshaller that will identify rows in decoding
errors by any columns. This is the equivalent of annotateSqlMarshaller [].
Since: 1.0.0.0
unannotatedSqlMarshaller :: AnnotatedSqlMarshaller writeEntity readEntity -> SqlMarshaller writeEntity readEntity Source #
mapSqlMarshaller :: (SqlMarshaller readEntityA writeEntityA -> SqlMarshaller readEntityB writeEntityB) -> AnnotatedSqlMarshaller readEntityA writeEntityA -> AnnotatedSqlMarshaller readEntityB writeEntityB Source #
Applies the provided function to a SqlMarshaller that has been annotated,
preserving the annotations.
Since: 1.0.0.0
data MarshallerField writeEntity where Source #
Represents a primitive entry in a SqlMarshaller. This type is used with
foldMarshallerFields to provided the entry from the marshaller to the
folding function to be incorporated in the result of the fold.
Since: 1.0.0.0
Constructors
| Natural :: FieldDefinition nullability a -> Maybe (writeEntity -> a) -> MarshallerField writeEntity | |
| Synthetic :: SyntheticField a -> MarshallerField writeEntity |
marshallResultFromSql :: ExecutionResult result => ErrorDetailLevel -> AnnotatedSqlMarshaller writeEntity readEntity -> result -> IO (Either MarshallError [readEntity]) Source #
Decodes all the rows found in an execution result at once. The first row that
fails to decode will return the MarshallErrorDetails that
results, otherwise all decoded rows will be returned.
Note that this function loads all decoded rows into memory at once, so it should only be used with result sets that you know will fit into memory.
Since: 1.0.0.0
marshallResultFromSqlUsingRowIdExtractor :: ExecutionResult result => ErrorDetailLevel -> RowIdentityExtractor -> SqlMarshaller writeEntity readEntity -> result -> IO (Either MarshallError [readEntity]) Source #
Decodes all the rows found in a execution result at once. The first row that
fails to decode will return the MarshallErrorDetails that
results, otherwise all decoded rows will be returned. If an error occurs
while decoding a row, the RowIdentityExtractor will be used to extract
values to identify the row in the error details.
Note that this function loads all decoded rows into memory at once, so it should only be used with result sets that you know will fit into memory.
Since: 1.0.0.0
data RowIdentityExtractor Source #
A RowIdentityExtractor is used to retrieve identifying information for a
row when a MarshallError occurs reading it from the database.
You should only need to worry about this type if you're using
marshallResultFromSqlUsingRowIdExtractor and need to manually provide it.
When possible, it's easier to annotate a SqlMarshaller with the field names
you would like rows to be identified by and then use marshallResultFromSql
instead.
Since: 1.0.0.0
mkRowIdentityExtractor :: ExecutionResult result => [FieldName] -> result -> RowIdentityExtractor Source #
Constructs a RowIdentityExtractor that will extract values for the given
fields from the result set to identify rows in decoding errors. Any of the
named fields that are missing from the result set will not be included in the
extracted row identity.
Since: 1.0.0.0
marshallField :: (writeEntity -> fieldValue) -> FieldDefinition nullability fieldValue -> SqlMarshaller writeEntity fieldValue Source #
Builds a SqlMarshaller that maps a single field of a Haskell entity to
a single column in the database. That value to store in the database will be
retrieved from the entity using a provided accessor function. This function
is intended to be used inside of a stanza of Applicative syntax that will
pass values read from the database to a constructor function to rebuild the
entity containing the field, like so:
data Foo = Foo { bar :: Int32, baz :: Text }
fooMarshaller :: SqlMarshaller Foo Foo
fooMarshaller =
Foo
<$> marshallField bar (integerField "bar")
<*> marshallField baz (unboundedTextField "baz")
Since: 1.0.0.0
marshallSyntheticField :: SyntheticField fieldValue -> SqlMarshaller writeEntity fieldValue Source #
Builds a SqlMarshaller that will include a SQL expression in select
statements to calculate a value using the columns of the table being selected
from. The columns being used in the calculation do not themselves need
to be selected, though they must be present in the table so they can
be referenced.
data AgeCheck
{ atLeast21 :: Bool
}
fooMarshaller :: SqlMarshaller Void AgeCheck
fooMarshaller =
AgeCheck
<*> Orville.marshallSyntheticField atLeast21Field
atLeast21Field :: SyntheticField Bool
atLeast21Field =
SyntheticField
{ syntheticFieldExpression = RawSql.unsafeSqlExpression "age >= 21"
, syntheticFieldAlias = Orville.stringToFieldName "over21"
, syntheticFieldValueFromSqlValue = SqlValue.toBool
}
Since: 1.0.0.0
marshallReadOnlyField :: FieldDefinition nullability fieldValue -> SqlMarshaller writeEntity fieldValue Source #
A version of marshallField that uses marshallReadOnly to make a single
read-only field. You will usually use this in conjunction with a
FieldDefinition like serialField where the value is populated by the
database.
Since: 1.0.0.0
marshallReadOnly :: SqlMarshaller a b -> SqlMarshaller c b Source #
Marks a SqlMarshaller as read-only so that it will not attempt to
read any values from the writeEntity. You should use this if you have
a group of fields which are populated by database rather than the application.
Since: 1.0.0.0
marshallNested :: (parentEntity -> nestedWriteEntity) -> SqlMarshaller nestedWriteEntity nestedReadEntity -> SqlMarshaller parentEntity nestedReadEntity Source #
Nests a SqlMarshaller inside another, using the given accessor to retrieve
values to be marshalled. The resulting marshaller can then be used in the same
way as marshallField within the applicative syntax of a larger marshaller.
For Example:
data Person =
Person
{ personId :: PersonId
, personName :: Name
}
data Name =
Name
{ firstName :: Text
, lastName :: Text
}
personMarshaller :: SqlMarshaller Person Person
personMarshaller =
Person
<$> marshallField personId personIdField
<*> marshallNested personName nameMarshaller
nameMarshaller :: SqlMarshaller Name Name
nameMarshaller =
Name
<$> marshallField firstName firstNameField
<*> marshallField lastName lastNameField
Since: 1.0.0.0
marshallMaybe :: SqlMarshaller a b -> SqlMarshaller (Maybe a) (Maybe b) Source #
Lifts a SqlMarshaller to have both read/write entities be Maybe,
and applies a tag to avoid double mapping.
Since: 1.0.0.0
marshallPartial :: SqlMarshaller a (Either String b) -> SqlMarshaller a b Source #
Builds a SqlMarshaller that will raise a decoding error when the value
produced is a Left.
Since: 1.0.0.0
prefixMarshaller :: String -> SqlMarshaller readEntity writeEntity -> SqlMarshaller readEntity writeEntity Source #
Adds a prefix, followed by an underscore, to the names of all of the fields
and synthetic fields in a SqlMarshaller.
Since: 1.0.0.0
data ReadOnlyColumnOption Source #
Specifies whether read-only fields should be included when using functions
such as collectFromField.
Since: 1.0.0.0
Constructors
| IncludeReadOnlyColumns | |
| ExcludeReadOnlyColumns |
collectFromField :: ReadOnlyColumnOption -> (forall nullability a. FieldDefinition nullability a -> result) -> MarshallerField entity -> [result] -> [result] Source #
A fold function that can be used with foldMarshallerFields to collect
a value calculated from a FieldDefinition via the given function. The calculated
value is added to the list of values being built.
Note: Folds executed with collectFromField ignore Synthetic entries in
the marshaller. You should only use collectFromField in situations where
you only care about the actual columns referenced by the marshaller.
Since: 1.0.0.0
marshallEntityToSetClauses :: SqlMarshaller writeEntity readEntity -> writeEntity -> [SetClause] Source #
Uses the field definitions in the marshaller to construct SQL expressions
that will set columns of the field definitions to their corresponding values
found in the Haskell writeEntity value.
Since: 1.0.0.0
foldMarshallerFields :: SqlMarshaller writeEntity readEntity -> result -> (MarshallerField writeEntity -> result -> result) -> result Source #
foldMarshallerFields allows you to consume the FieldDefinitions that
are contained within the SqlMarshaller to process them however is
required. This can be used to collect the names of all the fields, encode
them to SqlValue, etc.
Since: 1.0.0.0
marshallerDerivedColumns :: SqlMarshaller writeEntity readEntity -> [DerivedColumn] Source #
Returns a list of DerivedColumn expressions that can be used in a
select statement to select values from the database for the SqlMarshaller
decode.
Since: 1.0.0.0
marshallerTableConstraints :: SqlMarshaller writeEntity readEntity -> TableConstraints Source #
Returns the table constraints for all the FieldDefinitions used in the
SqlMarshaller.
Since: 1.0.0.0
mkRowSource :: ExecutionResult result => SqlMarshaller writeEntity readEntity -> result -> IO (RowSource readEntity) Source #
Uses the SqlMarshaller given to build a RowSource that will decode
from the given result set. The returned RowSource can then be used to
decode rows as desired by the user. Note that the entire result set is
held in memory for potential decoding until the RowSource is garbage
collected.
Since: 1.0.0.0
data RowSource readEntity Source #
A RowSource can fetch and decode rows from a database result set. Using
a RowSource gives random access to the rows in the result set, only
attempting to decode them when they are requested by the user via decodeRow.
Note that even though the rows are not decoded into Haskell until decodeRow
is called, all the rows returned from the query are held in memory on the
client waiting to be decoded until the RowSource is garbage collected.
As such, you can't use RowSource (alone) to achieve any form of streaming
or pagination of rows between the database server and the client.
Since: 1.0.0.0
Instances
mapRowSource :: (a -> b) -> RowSource a -> RowSource b Source #
Adds a function to the decoding proocess to transform the value returned
by a RowSource.
Since: 1.0.0.0
applyRowSource :: RowSource (a -> b) -> RowSource a -> RowSource b Source #
Applies a function that will be decoded from the result set to another value decoded from the result set.
Since: 1.0.0.0
constRowSource :: readEntity -> RowSource readEntity Source #
Creates a RowSource that always returns the value given, rather than
attempting to access the result set and decoding anything.
Since: 1.0.0.0
failRowSource :: MarshallErrorDetails -> RowSource a Source #
Creates a RowSource that will always fail to decode by returning the
provided error. This can be used in cases where a RowSource must
be provided but it is already known at run time that decoding is impossible.
For instance, this is used internally when a FieldDefinition references
a column that does not exist in the result set.
Since: 1.0.0.0