Adds migration guides to some of the most common legacy functions

This begins adding migration guides for moving from legacy orville to
the new orville. More migration guides will be coming as well.
This commit is contained in:
David Vollbracht 2023-09-18 12:11:48 -05:00
parent b31247e9db
commit bc3258abed
4 changed files with 162 additions and 25 deletions

View File

@ -2,11 +2,15 @@
Module : Database.Orville.PostgreSQL.Core
Copyright : Flipstone Technology Partners 2016-2018
License : MIT
Migration Guide: Although not all exports are identical, most of the items in
this module can now be import from @Orville.PostgreSQL@.
-}
{-# LANGUAGE FlexibleContexts #-}
module Database.Orville.PostgreSQL.Core
( TableDefinition(..)
( TableDefinition(..) -- migration guide added
, PrimaryKey
, primaryKeyIn
, primaryKeyEquals
@ -15,7 +19,7 @@ module Database.Orville.PostgreSQL.Core
, primaryKey
, compositePrimaryKey
, primaryKeyPart
, mkTableDefinition
, mkTableDefinition -- migration guide added
, SqlType(..)
, serial
, bigserial
@ -31,17 +35,17 @@ module Database.Orville.PostgreSQL.Core
, textSearchVector
, convertSqlType
, maybeConvertSqlType
, TableParams(..)
, RelationalMap
, fields
, mapAttr
, mapField
, attrField
, maybeMapper
, prefixMap
, partialMap
, readOnlyMap
, readOnlyField
, TableParams(..) -- migration guide added
, RelationalMap -- migration guide added
, fields -- migration guide added
, mapAttr -- migration guide added
, mapField -- migration guide added
, attrField -- migration guide added
, maybeMapper -- migration guide added
, prefixMap -- migration guide added
, partialMap -- migration guide added
, readOnlyMap -- migration guide added
, readOnlyField -- migration guide added
, OrvilleEnv
, newOrvilleEnv
, setStartTransactionSQL
@ -168,18 +172,18 @@ module Database.Orville.PostgreSQL.Core
, migrationPlanItems
, Pagination(..)
, buildPagination
, selectAll
, selectFirst
, deleteRecord
, deleteWhere
, findRecord
, findRecords
, findRecordsBy
, insertRecord
, insertRecordMany
, insertRecordManyReturning
, updateFields
, updateRecord
, selectAll -- migration guide added
, selectFirst -- migraiton guide added
, deleteRecord -- migration guide added
, deleteWhere -- migration guide added
, findRecord -- migration guide added
, findRecords -- migration guide added
, findRecordsBy -- migration guide added
, insertRecord -- migration guide added
, insertRecordMany -- migration guide added
, insertRecordManyReturning -- migration guide added
, updateFields -- migration guide added
, updateRecord -- migration guide added
, sequenceNextVal
, sequenceSetVal
, sequenceCurrVal
@ -231,6 +235,9 @@ getField f = do
sqlValues <- get
put (convert value : sqlValues)
{- |
Migration Guide: @selectAll@ has been renamed to @findEntitiesBy@
-}
selectAll ::
MonadOrville conn m
=> TableDefinition readEntity writeEntity key
@ -238,6 +245,10 @@ selectAll ::
-> m [readEntity]
selectAll tableDef = runSelect . selectQueryTable tableDef
{- |
Migration Guide: @selectFirst@ has been renamed to @findFirstEntityBy@
-}
selectFirst ::
MonadOrville conn m
=> TableDefinition readEntity writeEntity key
@ -259,6 +270,10 @@ deleteWhereBuild tableDef conds = do
withConnection $ \conn -> do
executingSql DeleteQuery querySql $ do run conn querySql values
{- |
Migration Guide: @deleteWhere@ has been renamed to @deleteEntities@. It
now takes a @Maybe BooleanExpr@ rather than @[WhereCondition]@
-}
deleteWhere ::
MonadOrville conn m
=> TableDefinition readEntity writeEntity key
@ -266,6 +281,11 @@ deleteWhere ::
-> m Integer
deleteWhere tableDef = deleteWhereBuild tableDef
{- |
Migration Guide: @findRecords@ has been renamed to @findEntities@. It now
requires a @NonEmpty key@ rather than simply @[key]@ and returns a
@[readEntity]@ instead of a @Map@.
-}
findRecords ::
(Ord key, MonadOrville conn m)
=> TableDefinition readEntity writeEntity key
@ -278,6 +298,11 @@ findRecords tableDef keys = do
recordList <- selectAll tableDef (where_ $ primaryKeyIn keyDef keys)
pure $ Map.fromList (map mkEntry recordList)
{- |
Migration Guide: @findRecordsBy@ has been renamed to @findEntitiesBy@. It
no longer takes a @FieldDefinition@ to group by. Instead it simply returns
a @[readEntity]@
-}
findRecordsBy ::
(Ord fieldValue, MonadOrville conn m)
=> TableDefinition readEntity writeEntity key
@ -289,6 +314,9 @@ findRecordsBy tableDef field opts = do
query = selectQuery builder (fromClauseTable tableDef) opts
Map.groupBy' id <$> runSelect query
{- |
Migration Guide: @findRecord@ has been renamed to @findEntity@
-}
findRecord ::
MonadOrville conn m
=> TableDefinition readEntity writeEntity key
@ -298,6 +326,15 @@ findRecord tableDef key =
let keyDef = tablePrimaryKey tableDef
in selectFirst tableDef (where_ $ primaryKeyEquals keyDef key)
{- |
Migration Guide: @updateFields@ has been renamed to
@updateFieldsAndReturnRowCount@, but now takes a @NonEmpty SetClause@ instead
of a @[Field Update]@ and a @Maybe BooleanExpr@ instead of a
@[WhereCondition]@.
@updateFields@ still exists a variant of this function, but returns @()@
rather than @Int@. @updateFieldsAndReturnEntities@ is now available as well.
-}
updateFields ::
MonadOrville conn m
=> TableDefinition readEntity writeEntity key
@ -313,6 +350,11 @@ updateFields tableDef updates conds =
updateNames = map fieldUpdateName updates
updateClause = mkUpdateClause (tableName tableDef) updateNames
{- |
Migration Guide: @updateRecord@ has been renamed to @updateEntity. Note that
there are also new variant functions @updateAndReturnEntity@ and
@updateEntityAndReturnRowCount@.
-}
updateRecord ::
MonadOrville conn m
=> TableDefinition readEntity writeEntity key
@ -327,6 +369,11 @@ updateRecord tableDef key record = do
updates = zipWith FieldUpdate fields (runToSql builder record)
void $ updateFields tableDef updates conds
{- |
Migration Guide: @insertRecord@ has been renamed to @insertAndReturnEntity@.
Note there are is are also new variant functions @insertEntity@ and
@insertEntityAndReturnRowCount@ that return @()@ and @Int@ respectively.
-}
insertRecord ::
MonadOrville conn m
=> TableDefinition readEntity writeEntity key
@ -339,6 +386,10 @@ insertRecord tableDef newRecord = do
[] -> error "Didn't get a record back from the database!"
_ -> error "Got more than one record back from the database!"
{- |
Migration Guide: @insertRecordManyReturning@ has been renamed to
@insertAndReturnEntities@.
-}
insertRecordManyReturning ::
MonadOrville conn m
=> TableDefinition readEntity writeEntity key
@ -365,6 +416,12 @@ insertRecordManyReturning tableDef newRecords = do
fetchAllRowsAL' insert
decodeSqlRows builder rows
{- |
Migration Guide: @insertRecordMany@ has been renamed to @insertEntities@. It
now requires a @NonEmpty writeEntity@ rather than @[writeEntity]@. Note that
there are also new variant functions @insertAndReturnEntities@ and
@insertEntitiesAndReturnRowCount@.
-}
insertRecordMany ::
MonadOrville conn m
=> TableDefinition readEntity writeEntity key
@ -383,6 +440,12 @@ insertRecordMany tableDef newRecords = do
insert <- prepare conn insertSql
void $ execute insert (concatMap (runToSql builder) newRecords)
{- |
Migration Guide: @deleteRecord@ has been renamed to @deleteEntity@. Note
that there are also new variant function @deleteAndReturnEntity@ and
@deleteEntityAndReturnRowCount@ that return @Maybe readEntity@ and @Int@
respectively.
-}
deleteRecord ::
MonadOrville conn m
=> TableDefinition readEntity writeEntity key

View File

@ -32,6 +32,9 @@ import Database.Orville.PostgreSQL.Internal.FromSql
import Database.Orville.PostgreSQL.Internal.Types
{-|
MigrationGuide: @TableParams@ no longer exists. See the migration guide
for 'mkTableDefinition'
'TableParams' is the simplest way to make a 'TableDefinition'. You
can use 'mkTableDefinition' to make a definition from the simplified
params. Where 'TableDefinition' requires the 'tableFields', 'tableFromSql',
@ -61,6 +64,13 @@ data TableParams readEntity writeEntity key = TableParams
}
{-|
Migration Guide: This function has in the new orville to take the table name,
primary key definition and a @SqlMarshaller@ (formerly @RelationalMap@).
Other options such as constraints, indexes, and columns to drop can be added
to the @TableDefinition@ after the initial instatiation. The @TableParams@
type has been dropped for the new orville.
'mkTableDefinition' converts a 'TableParams' to 'TableDefinition'. Usually
this is used directly on a record literal of the 'TableParams'. For
example:
@ -95,6 +105,12 @@ mkTableDefinition (TableParams {..}) =
, tableComments = tblComments
}
{- |
Migration guide: This type has been replaced with the @SqlMarshaller@ type in
the new orville. The interface is similar, though the names of the functions
have been updated in many cases. See the migration guides for those functions
to find their new names.
-}
data RelationalMap a b where
RM_Field :: FieldDefinition nullability a -> RelationalMap a a
RM_Nest :: (a -> b) -> RelationalMap b c -> RelationalMap a c
@ -117,24 +133,46 @@ instance Profunctor RelationalMap where
rmap = fmap
lmap = mapAttr
{- |
Migration Guide: @mapAttr@ has been renamed to @marshallNested@
-}
mapAttr :: (a -> b) -> RelationalMap b c -> RelationalMap a c
mapAttr = RM_Nest
{- |
Migration Guide: @mapField@ has been removed, though its functional
equivalent is @marshallReadOnlyField@
-}
mapField :: FieldDefinition nullability a -> RelationalMap a a
mapField = RM_Field
{- |
Migration Guide: @partialMap@ has been renamed to @marshallPartial@
-}
partialMap :: RelationalMap a (Either String a) -> RelationalMap a a
partialMap = RM_Partial
{- |
Migration Guide: @readOnlyMap@ has been renamed to @marshallReadOnly@
-}
readOnlyMap :: RelationalMap a b -> RelationalMap c b
readOnlyMap = RM_ReadOnly
{- |
Migration Guide: @attrField@ has been renamed to @marshallField@
-}
attrField :: (a -> b) -> FieldDefinition nullability b -> RelationalMap a b
attrField get = mapAttr get . mapField
{- |
Migration Guide: @readOnlyField@ has been renamed to @marshallReadOnlyField@
-}
readOnlyField :: FieldDefinition nullability a -> RelationalMap b a
readOnlyField = readOnlyMap . mapField
{- |
Migration Guide: @prefixMap@ has been renamed to @prefixMarshaller@
-}
prefixMap :: String -> RelationalMap a b -> RelationalMap a b
prefixMap prefix (RM_Nest f rm) = RM_Nest f (prefixMap prefix rm)
prefixMap prefix (RM_Field f) = RM_Field (f `withPrefix` prefix)
@ -145,6 +183,9 @@ prefixMap prefix (RM_ReadOnly rm) = RM_ReadOnly (prefixMap prefix rm)
prefixMap prefix (RM_MaybeTag rm) = RM_MaybeTag (prefixMap prefix rm)
prefixMap _ rm@(RM_Pure _) = rm
{- |
Migration Guide: @maybeMapper@ has been renamed to @marshallMaybe@
-}
maybeMapper :: RelationalMap a b -> RelationalMap (Maybe a) (Maybe b)
maybeMapper
-- rewrite the mapper to handle null fields, then tag
@ -178,6 +219,13 @@ maybeMapper
go (RM_ReadOnly rm) = RM_ReadOnly (go rm)
go rm@(RM_MaybeTag _) = fmap Just $ mapAttr join $ rm
{- |
Migration Guide: The fields in new orville's @SqlMarshaller@ are somewhat
more sophisticated than those of a @RelationalMap@. The 'fields' function is
no longer offered with this simple interface as a result, but the
@foldMarshallerFields@ function can be used in combination with the
@collectFromField@ helper to collect the desired information from each field.
-}
fields :: RelationalMap a b -> [SomeField]
fields (RM_Field field) = [SomeField field]
fields (RM_Apply rm1 rm2) = fields rm1 ++ fields rm2

View File

@ -296,6 +296,13 @@ getComponent getComp (ToSql serializer) =
ToSql (withReaderT getComp serializer)
{-|
Migration Guide: 'TableDefinition' can now be imported from
'Orville.PostgreSQL'. The ordered of the type parameter has changed from
@TableDefinition readEnity writeEntity key@ to @TableDefinition key
writeEntity readEntity@. In the new Orville tables without primary keys are
supported, so the @key@ parameter must now be instatiated as either @HasKey
keyType@ or @NoKey@.
A 'TableDefinition' is the center of the Orville universe. A 'TableDefinition'
defines the structure of a table in the database and associates it with a Haskell
datatype, usually a Haskell record type. The 'TableDefinition' must specify how

View File

@ -0,0 +1,19 @@
# This file was autogenerated by Stack.
# You should not edit this file by hand.
# For more information, please see the documentation at:
# https://docs.haskellstack.org/en/stable/lock_files
packages:
- completed:
hackage: HDBC-postgresql-2.3.2.5@sha256:5d46e19ddd92349546117d5558b7d1a9d0f7fa363a394e21bb41cc39acc6d0d7,3213
pantry-tree:
sha256: c75821e0c0d10b785a19999d635f2c10a5891b33c48ffcc3e0963e681a861618
size: 1730
original:
hackage: HDBC-postgresql-2.3.2.5
snapshots:
- completed:
sha256: d0ee122a83faa02a679829d43b3485b21827c3cc1cce0db8ac8957b78d45bee3
size: 566883
url: https://raw.githubusercontent.com/commercialhaskell/stackage-snapshots/master/lts/10/0.yaml
original: lts-10.0