module BtcLsp.Storage.Model.SwapUtxo ( createIgnoreManySql, getSpendableUtxosBySwapIdSql, updateUnspentChanReserveSql, updateSpentChanSwappedSql, updateRefundedSql, updateOrphanSql, getUtxosForRefundSql, getUtxosBySwapIdSql, updateRefundBlockIdSql, revertRefundedSql, ) where import BtcLsp.Import hiding (Storage (..)) import qualified BtcLsp.Import.Psql as Psql createIgnoreManySql :: ( MonadIO m ) => [SwapUtxo] -> ReaderT Psql.SqlBackend m () createIgnoreManySql :: forall (m :: * -> *). MonadIO m => [SwapUtxo] -> ReaderT SqlBackend m () createIgnoreManySql [SwapUtxo] us = [SwapUtxo] -> [HandleUpdateCollision SwapUtxo] -> [Update SwapUtxo] -> [Filter SwapUtxo] -> ReaderT SqlBackend m () forall record backend (m :: * -> *). (backend ~ PersistEntityBackend record, BackendCompatible SqlBackend backend, PersistEntityBackend record ~ SqlBackend, PersistEntity record, OnlyOneUniqueKey record, MonadIO m) => [record] -> [HandleUpdateCollision record] -> [Update record] -> [Filter record] -> ReaderT backend m () Psql.upsertManyWhere [SwapUtxo] us [EntityField SwapUtxo UTCTime -> HandleUpdateCollision SwapUtxo forall typ record. PersistField typ => EntityField record typ -> HandleUpdateCollision record Psql.copyField EntityField SwapUtxo UTCTime forall typ. (typ ~ UTCTime) => EntityField SwapUtxo typ SwapUtxoUpdatedAt] [Update SwapUtxo] forall a. Monoid a => a mempty [Filter SwapUtxo] forall a. Monoid a => a mempty getSpendableUtxosBySwapIdSql :: ( MonadIO m ) => SwapIntoLnId -> ReaderT Psql.SqlBackend m [Entity SwapUtxo] getSpendableUtxosBySwapIdSql :: forall (m :: * -> *). MonadIO m => SwapIntoLnId -> ReaderT SqlBackend m [Entity SwapUtxo] getSpendableUtxosBySwapIdSql SwapIntoLnId swapId = do SqlQuery (SqlExpr (Entity SwapUtxo)) -> ReaderT SqlBackend m [Entity SwapUtxo] forall a r (m :: * -> *). (SqlSelect a r, MonadIO m) => SqlQuery a -> SqlReadT m [r] Psql.select (SqlQuery (SqlExpr (Entity SwapUtxo)) -> ReaderT SqlBackend m [Entity SwapUtxo]) -> SqlQuery (SqlExpr (Entity SwapUtxo)) -> ReaderT SqlBackend m [Entity SwapUtxo] forall a b. (a -> b) -> a -> b $ (SqlExpr (Entity SwapUtxo) -> SqlQuery (SqlExpr (Entity SwapUtxo))) -> SqlQuery (SqlExpr (Entity SwapUtxo)) forall a b. From a => (a -> SqlQuery b) -> SqlQuery b Psql.from ((SqlExpr (Entity SwapUtxo) -> SqlQuery (SqlExpr (Entity SwapUtxo))) -> SqlQuery (SqlExpr (Entity SwapUtxo))) -> (SqlExpr (Entity SwapUtxo) -> SqlQuery (SqlExpr (Entity SwapUtxo))) -> SqlQuery (SqlExpr (Entity SwapUtxo)) forall a b. (a -> b) -> a -> b $ \SqlExpr (Entity SwapUtxo) row -> do LockingKind -> SqlQuery () Psql.locking LockingKind Psql.ForUpdate SqlExpr (Value Bool) -> SqlQuery () Psql.where_ ( ( SqlExpr (Entity SwapUtxo) row SqlExpr (Entity SwapUtxo) -> EntityField SwapUtxo SwapIntoLnId -> SqlExpr (Value SwapIntoLnId) forall typ val. (PersistEntity val, PersistField typ) => SqlExpr (Entity val) -> EntityField val typ -> SqlExpr (Value typ) Psql.^. EntityField SwapUtxo SwapIntoLnId forall typ. (typ ~ SwapIntoLnId) => EntityField SwapUtxo typ SwapUtxoSwapIntoLnId SqlExpr (Value SwapIntoLnId) -> SqlExpr (Value SwapIntoLnId) -> SqlExpr (Value Bool) forall typ. PersistField typ => SqlExpr (Value typ) -> SqlExpr (Value typ) -> SqlExpr (Value Bool) Psql.==. SwapIntoLnId -> SqlExpr (Value SwapIntoLnId) forall typ. PersistField typ => typ -> SqlExpr (Value typ) Psql.val SwapIntoLnId swapId ) SqlExpr (Value Bool) -> SqlExpr (Value Bool) -> SqlExpr (Value Bool) Psql.&&. ( SqlExpr (Entity SwapUtxo) row SqlExpr (Entity SwapUtxo) -> EntityField SwapUtxo SwapUtxoStatus -> SqlExpr (Value SwapUtxoStatus) forall typ val. (PersistEntity val, PersistField typ) => SqlExpr (Entity val) -> EntityField val typ -> SqlExpr (Value typ) Psql.^. EntityField SwapUtxo SwapUtxoStatus forall typ. (typ ~ SwapUtxoStatus) => EntityField SwapUtxo typ SwapUtxoStatus SqlExpr (Value SwapUtxoStatus) -> SqlExpr (ValueList SwapUtxoStatus) -> SqlExpr (Value Bool) forall typ. PersistField typ => SqlExpr (Value typ) -> SqlExpr (ValueList typ) -> SqlExpr (Value Bool) `Psql.in_` [SwapUtxoStatus] -> SqlExpr (ValueList SwapUtxoStatus) forall typ. PersistField typ => [typ] -> SqlExpr (ValueList typ) Psql.valList [ SwapUtxoStatus SwapUtxoUnspent, SwapUtxoStatus SwapUtxoUnspentChanReserve ] ) ) SqlExpr (Entity SwapUtxo) -> SqlQuery (SqlExpr (Entity SwapUtxo)) forall (f :: * -> *) a. Applicative f => a -> f a pure SqlExpr (Entity SwapUtxo) row updateUnspentChanReserveSql :: ( MonadIO m ) => [SwapUtxoId] -> ReaderT Psql.SqlBackend m RowQty updateUnspentChanReserveSql :: forall (m :: * -> *). MonadIO m => [SwapUtxoId] -> ReaderT SqlBackend m RowQty updateUnspentChanReserveSql [SwapUtxoId] ids = do UTCTime ct <- ReaderT SqlBackend m UTCTime forall (m :: * -> *). MonadIO m => m UTCTime getCurrentTime Int64 res <- (SqlExpr (Entity SwapUtxo) -> SqlQuery ()) -> ReaderT SqlBackend m Int64 forall (m :: * -> *) val. (MonadIO m, PersistEntity val, BackendCompatible SqlBackend (PersistEntityBackend val)) => (SqlExpr (Entity val) -> SqlQuery ()) -> SqlWriteT m Int64 Psql.updateCount ((SqlExpr (Entity SwapUtxo) -> SqlQuery ()) -> ReaderT SqlBackend m Int64) -> (SqlExpr (Entity SwapUtxo) -> SqlQuery ()) -> ReaderT SqlBackend m Int64 forall a b. (a -> b) -> a -> b $ \SqlExpr (Entity SwapUtxo) row -> do SqlExpr (Entity SwapUtxo) -> [SqlExpr (Entity SwapUtxo) -> SqlExpr Update] -> SqlQuery () forall val. PersistEntity val => SqlExpr (Entity val) -> [SqlExpr (Entity val) -> SqlExpr Update] -> SqlQuery () Psql.set SqlExpr (Entity SwapUtxo) row [ EntityField SwapUtxo SwapUtxoStatus forall typ. (typ ~ SwapUtxoStatus) => EntityField SwapUtxo typ SwapUtxoStatus EntityField SwapUtxo SwapUtxoStatus -> SqlExpr (Value SwapUtxoStatus) -> SqlExpr (Entity SwapUtxo) -> SqlExpr Update forall val typ. (PersistEntity val, PersistField typ) => EntityField val typ -> SqlExpr (Value typ) -> SqlExpr (Entity val) -> SqlExpr Update Psql.=. SwapUtxoStatus -> SqlExpr (Value SwapUtxoStatus) forall typ. PersistField typ => typ -> SqlExpr (Value typ) Psql.val SwapUtxoStatus SwapUtxoUnspentChanReserve, EntityField SwapUtxo UTCTime forall typ. (typ ~ UTCTime) => EntityField SwapUtxo typ SwapUtxoUpdatedAt EntityField SwapUtxo UTCTime -> SqlExpr (Value UTCTime) -> SqlExpr (Entity SwapUtxo) -> SqlExpr Update forall val typ. (PersistEntity val, PersistField typ) => EntityField val typ -> SqlExpr (Value typ) -> SqlExpr (Entity val) -> SqlExpr Update Psql.=. UTCTime -> SqlExpr (Value UTCTime) forall typ. PersistField typ => typ -> SqlExpr (Value typ) Psql.val UTCTime ct ] SqlExpr (Value Bool) -> SqlQuery () Psql.where_ (SqlExpr (Value Bool) -> SqlQuery ()) -> SqlExpr (Value Bool) -> SqlQuery () forall a b. (a -> b) -> a -> b $ ( SqlExpr (Entity SwapUtxo) row SqlExpr (Entity SwapUtxo) -> EntityField SwapUtxo SwapUtxoId -> SqlExpr (Value SwapUtxoId) forall typ val. (PersistEntity val, PersistField typ) => SqlExpr (Entity val) -> EntityField val typ -> SqlExpr (Value typ) Psql.^. EntityField SwapUtxo SwapUtxoId forall typ. (typ ~ SwapUtxoId) => EntityField SwapUtxo typ SwapUtxoId SqlExpr (Value SwapUtxoId) -> SqlExpr (ValueList SwapUtxoId) -> SqlExpr (Value Bool) forall typ. PersistField typ => SqlExpr (Value typ) -> SqlExpr (ValueList typ) -> SqlExpr (Value Bool) `Psql.in_` [SwapUtxoId] -> SqlExpr (ValueList SwapUtxoId) forall typ. PersistField typ => [typ] -> SqlExpr (ValueList typ) Psql.valList [SwapUtxoId] ids ) SqlExpr (Value Bool) -> SqlExpr (Value Bool) -> SqlExpr (Value Bool) Psql.&&. ( SqlExpr (Entity SwapUtxo) row SqlExpr (Entity SwapUtxo) -> EntityField SwapUtxo SwapUtxoStatus -> SqlExpr (Value SwapUtxoStatus) forall typ val. (PersistEntity val, PersistField typ) => SqlExpr (Entity val) -> EntityField val typ -> SqlExpr (Value typ) Psql.^. EntityField SwapUtxo SwapUtxoStatus forall typ. (typ ~ SwapUtxoStatus) => EntityField SwapUtxo typ SwapUtxoStatus SqlExpr (Value SwapUtxoStatus) -> SqlExpr (ValueList SwapUtxoStatus) -> SqlExpr (Value Bool) forall typ. PersistField typ => SqlExpr (Value typ) -> SqlExpr (ValueList typ) -> SqlExpr (Value Bool) `Psql.in_` [SwapUtxoStatus] -> SqlExpr (ValueList SwapUtxoStatus) forall typ. PersistField typ => [typ] -> SqlExpr (ValueList typ) Psql.valList [ SwapUtxoStatus SwapUtxoUnspent, SwapUtxoStatus SwapUtxoUnspentChanReserve ] ) RowQty -> ReaderT SqlBackend m RowQty forall (f :: * -> *) a. Applicative f => a -> f a pure (RowQty -> ReaderT SqlBackend m RowQty) -> RowQty -> ReaderT SqlBackend m RowQty forall a b. (a -> b) -> a -> b $ Int64 -> RowQty forall source target. (From source target, 'False ~ (source == target)) => source -> target from Int64 res updateSpentChanSwappedSql :: ( MonadIO m ) => SwapIntoLnId -> ReaderT Psql.SqlBackend m () updateSpentChanSwappedSql :: forall (m :: * -> *). MonadIO m => SwapIntoLnId -> ReaderT SqlBackend m () updateSpentChanSwappedSql SwapIntoLnId id0 = do UTCTime ct <- ReaderT SqlBackend m UTCTime forall (m :: * -> *). MonadIO m => m UTCTime getCurrentTime (SqlExpr (Entity SwapUtxo) -> SqlQuery ()) -> ReaderT SqlBackend m () forall (m :: * -> *) val. (MonadIO m, PersistEntity val, BackendCompatible SqlBackend (PersistEntityBackend val)) => (SqlExpr (Entity val) -> SqlQuery ()) -> SqlWriteT m () Psql.update ((SqlExpr (Entity SwapUtxo) -> SqlQuery ()) -> ReaderT SqlBackend m ()) -> (SqlExpr (Entity SwapUtxo) -> SqlQuery ()) -> ReaderT SqlBackend m () forall a b. (a -> b) -> a -> b $ \SqlExpr (Entity SwapUtxo) row -> do SqlExpr (Entity SwapUtxo) -> [SqlExpr (Entity SwapUtxo) -> SqlExpr Update] -> SqlQuery () forall val. PersistEntity val => SqlExpr (Entity val) -> [SqlExpr (Entity val) -> SqlExpr Update] -> SqlQuery () Psql.set SqlExpr (Entity SwapUtxo) row [ EntityField SwapUtxo SwapUtxoStatus forall typ. (typ ~ SwapUtxoStatus) => EntityField SwapUtxo typ SwapUtxoStatus EntityField SwapUtxo SwapUtxoStatus -> SqlExpr (Value SwapUtxoStatus) -> SqlExpr (Entity SwapUtxo) -> SqlExpr Update forall val typ. (PersistEntity val, PersistField typ) => EntityField val typ -> SqlExpr (Value typ) -> SqlExpr (Entity val) -> SqlExpr Update Psql.=. SwapUtxoStatus -> SqlExpr (Value SwapUtxoStatus) forall typ. PersistField typ => typ -> SqlExpr (Value typ) Psql.val SwapUtxoStatus SwapUtxoSpentChanSwapped, EntityField SwapUtxo UTCTime forall typ. (typ ~ UTCTime) => EntityField SwapUtxo typ SwapUtxoUpdatedAt EntityField SwapUtxo UTCTime -> SqlExpr (Value UTCTime) -> SqlExpr (Entity SwapUtxo) -> SqlExpr Update forall val typ. (PersistEntity val, PersistField typ) => EntityField val typ -> SqlExpr (Value typ) -> SqlExpr (Entity val) -> SqlExpr Update Psql.=. UTCTime -> SqlExpr (Value UTCTime) forall typ. PersistField typ => typ -> SqlExpr (Value typ) Psql.val UTCTime ct ] SqlExpr (Value Bool) -> SqlQuery () Psql.where_ (SqlExpr (Value Bool) -> SqlQuery ()) -> SqlExpr (Value Bool) -> SqlQuery () forall a b. (a -> b) -> a -> b $ ( SqlExpr (Entity SwapUtxo) row SqlExpr (Entity SwapUtxo) -> EntityField SwapUtxo SwapIntoLnId -> SqlExpr (Value SwapIntoLnId) forall typ val. (PersistEntity val, PersistField typ) => SqlExpr (Entity val) -> EntityField val typ -> SqlExpr (Value typ) Psql.^. EntityField SwapUtxo SwapIntoLnId forall typ. (typ ~ SwapIntoLnId) => EntityField SwapUtxo typ SwapUtxoSwapIntoLnId SqlExpr (Value SwapIntoLnId) -> SqlExpr (Value SwapIntoLnId) -> SqlExpr (Value Bool) forall typ. PersistField typ => SqlExpr (Value typ) -> SqlExpr (Value typ) -> SqlExpr (Value Bool) Psql.==. SwapIntoLnId -> SqlExpr (Value SwapIntoLnId) forall typ. PersistField typ => typ -> SqlExpr (Value typ) Psql.val SwapIntoLnId id0 ) SqlExpr (Value Bool) -> SqlExpr (Value Bool) -> SqlExpr (Value Bool) Psql.&&. ( SqlExpr (Entity SwapUtxo) row SqlExpr (Entity SwapUtxo) -> EntityField SwapUtxo SwapUtxoStatus -> SqlExpr (Value SwapUtxoStatus) forall typ val. (PersistEntity val, PersistField typ) => SqlExpr (Entity val) -> EntityField val typ -> SqlExpr (Value typ) Psql.^. EntityField SwapUtxo SwapUtxoStatus forall typ. (typ ~ SwapUtxoStatus) => EntityField SwapUtxo typ SwapUtxoStatus SqlExpr (Value SwapUtxoStatus) -> SqlExpr (ValueList SwapUtxoStatus) -> SqlExpr (Value Bool) forall typ. PersistField typ => SqlExpr (Value typ) -> SqlExpr (ValueList typ) -> SqlExpr (Value Bool) `Psql.in_` [SwapUtxoStatus] -> SqlExpr (ValueList SwapUtxoStatus) forall typ. PersistField typ => [typ] -> SqlExpr (ValueList typ) Psql.valList [ SwapUtxoStatus SwapUtxoUnspentChanReserve ] ) updateRefundedSql :: ( MonadIO m ) => [SwapUtxoId] -> TxId 'Funding -> ReaderT Psql.SqlBackend m () updateRefundedSql :: forall (m :: * -> *). MonadIO m => [SwapUtxoId] -> TxId 'Funding -> ReaderT SqlBackend m () updateRefundedSql [SwapUtxoId] ids TxId 'Funding rTxId = do UTCTime ct <- ReaderT SqlBackend m UTCTime forall (m :: * -> *). MonadIO m => m UTCTime getCurrentTime (SqlExpr (Entity SwapUtxo) -> SqlQuery ()) -> ReaderT SqlBackend m () forall (m :: * -> *) val. (MonadIO m, PersistEntity val, BackendCompatible SqlBackend (PersistEntityBackend val)) => (SqlExpr (Entity val) -> SqlQuery ()) -> SqlWriteT m () Psql.update ((SqlExpr (Entity SwapUtxo) -> SqlQuery ()) -> ReaderT SqlBackend m ()) -> (SqlExpr (Entity SwapUtxo) -> SqlQuery ()) -> ReaderT SqlBackend m () forall a b. (a -> b) -> a -> b $ \SqlExpr (Entity SwapUtxo) row -> do SqlExpr (Entity SwapUtxo) -> [SqlExpr (Entity SwapUtxo) -> SqlExpr Update] -> SqlQuery () forall val. PersistEntity val => SqlExpr (Entity val) -> [SqlExpr (Entity val) -> SqlExpr Update] -> SqlQuery () Psql.set SqlExpr (Entity SwapUtxo) row [ EntityField SwapUtxo SwapUtxoStatus forall typ. (typ ~ SwapUtxoStatus) => EntityField SwapUtxo typ SwapUtxoStatus EntityField SwapUtxo SwapUtxoStatus -> SqlExpr (Value SwapUtxoStatus) -> SqlExpr (Entity SwapUtxo) -> SqlExpr Update forall val typ. (PersistEntity val, PersistField typ) => EntityField val typ -> SqlExpr (Value typ) -> SqlExpr (Entity val) -> SqlExpr Update Psql.=. SwapUtxoStatus -> SqlExpr (Value SwapUtxoStatus) forall typ. PersistField typ => typ -> SqlExpr (Value typ) Psql.val SwapUtxoStatus SwapUtxoSpentRefund, EntityField SwapUtxo (Maybe (TxId 'Funding)) forall typ. (typ ~ Maybe (TxId 'Funding)) => EntityField SwapUtxo typ SwapUtxoRefundTxId EntityField SwapUtxo (Maybe (TxId 'Funding)) -> SqlExpr (Value (Maybe (TxId 'Funding))) -> SqlExpr (Entity SwapUtxo) -> SqlExpr Update forall val typ. (PersistEntity val, PersistField typ) => EntityField val typ -> SqlExpr (Value typ) -> SqlExpr (Entity val) -> SqlExpr Update Psql.=. Maybe (TxId 'Funding) -> SqlExpr (Value (Maybe (TxId 'Funding))) forall typ. PersistField typ => typ -> SqlExpr (Value typ) Psql.val (TxId 'Funding -> Maybe (TxId 'Funding) forall a. a -> Maybe a Just TxId 'Funding rTxId), EntityField SwapUtxo UTCTime forall typ. (typ ~ UTCTime) => EntityField SwapUtxo typ SwapUtxoUpdatedAt EntityField SwapUtxo UTCTime -> SqlExpr (Value UTCTime) -> SqlExpr (Entity SwapUtxo) -> SqlExpr Update forall val typ. (PersistEntity val, PersistField typ) => EntityField val typ -> SqlExpr (Value typ) -> SqlExpr (Entity val) -> SqlExpr Update Psql.=. UTCTime -> SqlExpr (Value UTCTime) forall typ. PersistField typ => typ -> SqlExpr (Value typ) Psql.val UTCTime ct ] SqlExpr (Value Bool) -> SqlQuery () Psql.where_ (SqlExpr (Value Bool) -> SqlQuery ()) -> SqlExpr (Value Bool) -> SqlQuery () forall a b. (a -> b) -> a -> b $ ( SqlExpr (Entity SwapUtxo) row SqlExpr (Entity SwapUtxo) -> EntityField SwapUtxo SwapUtxoId -> SqlExpr (Value SwapUtxoId) forall typ val. (PersistEntity val, PersistField typ) => SqlExpr (Entity val) -> EntityField val typ -> SqlExpr (Value typ) Psql.^. EntityField SwapUtxo SwapUtxoId forall typ. (typ ~ SwapUtxoId) => EntityField SwapUtxo typ SwapUtxoId SqlExpr (Value SwapUtxoId) -> SqlExpr (ValueList SwapUtxoId) -> SqlExpr (Value Bool) forall typ. PersistField typ => SqlExpr (Value typ) -> SqlExpr (ValueList typ) -> SqlExpr (Value Bool) `Psql.in_` [SwapUtxoId] -> SqlExpr (ValueList SwapUtxoId) forall typ. PersistField typ => [typ] -> SqlExpr (ValueList typ) Psql.valList [SwapUtxoId] ids ) SqlExpr (Value Bool) -> SqlExpr (Value Bool) -> SqlExpr (Value Bool) Psql.&&. ( SqlExpr (Entity SwapUtxo) row SqlExpr (Entity SwapUtxo) -> EntityField SwapUtxo SwapUtxoStatus -> SqlExpr (Value SwapUtxoStatus) forall typ val. (PersistEntity val, PersistField typ) => SqlExpr (Entity val) -> EntityField val typ -> SqlExpr (Value typ) Psql.^. EntityField SwapUtxo SwapUtxoStatus forall typ. (typ ~ SwapUtxoStatus) => EntityField SwapUtxo typ SwapUtxoStatus SqlExpr (Value SwapUtxoStatus) -> SqlExpr (ValueList SwapUtxoStatus) -> SqlExpr (Value Bool) forall typ. PersistField typ => SqlExpr (Value typ) -> SqlExpr (ValueList typ) -> SqlExpr (Value Bool) `Psql.in_` [SwapUtxoStatus] -> SqlExpr (ValueList SwapUtxoStatus) forall typ. PersistField typ => [typ] -> SqlExpr (ValueList typ) Psql.valList [ SwapUtxoStatus SwapUtxoUnspent, SwapUtxoStatus SwapUtxoUnspentChanReserve ] ) getUtxosForRefundSql :: ( MonadIO m ) => ReaderT Psql.SqlBackend m [(Entity SwapUtxo, Entity SwapIntoLn)] getUtxosForRefundSql :: forall (m :: * -> *). MonadIO m => ReaderT SqlBackend m [(Entity SwapUtxo, Entity SwapIntoLn)] getUtxosForRefundSql = SqlQuery (SqlExpr (Entity SwapUtxo), SqlExpr (Entity SwapIntoLn)) -> ReaderT SqlBackend m [(Entity SwapUtxo, Entity SwapIntoLn)] forall a r (m :: * -> *). (SqlSelect a r, MonadIO m) => SqlQuery a -> SqlReadT m [r] Psql.select (SqlQuery (SqlExpr (Entity SwapUtxo), SqlExpr (Entity SwapIntoLn)) -> ReaderT SqlBackend m [(Entity SwapUtxo, Entity SwapIntoLn)]) -> SqlQuery (SqlExpr (Entity SwapUtxo), SqlExpr (Entity SwapIntoLn)) -> ReaderT SqlBackend m [(Entity SwapUtxo, Entity SwapIntoLn)] forall a b. (a -> b) -> a -> b $ (InnerJoin (SqlExpr (Entity SwapIntoLn)) (SqlExpr (Entity SwapUtxo)) -> SqlQuery (SqlExpr (Entity SwapUtxo), SqlExpr (Entity SwapIntoLn))) -> SqlQuery (SqlExpr (Entity SwapUtxo), SqlExpr (Entity SwapIntoLn)) forall a b. From a => (a -> SqlQuery b) -> SqlQuery b Psql.from ((InnerJoin (SqlExpr (Entity SwapIntoLn)) (SqlExpr (Entity SwapUtxo)) -> SqlQuery (SqlExpr (Entity SwapUtxo), SqlExpr (Entity SwapIntoLn))) -> SqlQuery (SqlExpr (Entity SwapUtxo), SqlExpr (Entity SwapIntoLn))) -> (InnerJoin (SqlExpr (Entity SwapIntoLn)) (SqlExpr (Entity SwapUtxo)) -> SqlQuery (SqlExpr (Entity SwapUtxo), SqlExpr (Entity SwapIntoLn))) -> SqlQuery (SqlExpr (Entity SwapUtxo), SqlExpr (Entity SwapIntoLn)) forall a b. (a -> b) -> a -> b $ \(SqlExpr (Entity SwapIntoLn) swap `Psql.InnerJoin` SqlExpr (Entity SwapUtxo) utxo) -> do LockingKind -> SqlQuery () Psql.locking LockingKind Psql.ForUpdate SqlExpr (Value Bool) -> SqlQuery () Psql.on ( (SqlExpr (Entity SwapIntoLn) swap SqlExpr (Entity SwapIntoLn) -> EntityField SwapIntoLn SwapIntoLnId -> SqlExpr (Value SwapIntoLnId) forall typ val. (PersistEntity val, PersistField typ) => SqlExpr (Entity val) -> EntityField val typ -> SqlExpr (Value typ) Psql.^. EntityField SwapIntoLn SwapIntoLnId forall typ. (typ ~ SwapIntoLnId) => EntityField SwapIntoLn typ SwapIntoLnId) SqlExpr (Value SwapIntoLnId) -> SqlExpr (Value SwapIntoLnId) -> SqlExpr (Value Bool) forall typ. PersistField typ => SqlExpr (Value typ) -> SqlExpr (Value typ) -> SqlExpr (Value Bool) Psql.==. (SqlExpr (Entity SwapUtxo) utxo SqlExpr (Entity SwapUtxo) -> EntityField SwapUtxo SwapIntoLnId -> SqlExpr (Value SwapIntoLnId) forall typ val. (PersistEntity val, PersistField typ) => SqlExpr (Entity val) -> EntityField val typ -> SqlExpr (Value typ) Psql.^. EntityField SwapUtxo SwapIntoLnId forall typ. (typ ~ SwapIntoLnId) => EntityField SwapUtxo typ SwapUtxoSwapIntoLnId) ) SqlExpr (Value Bool) -> SqlQuery () Psql.where_ ( ( ( SqlExpr (Entity SwapIntoLn) swap SqlExpr (Entity SwapIntoLn) -> EntityField SwapIntoLn SwapStatus -> SqlExpr (Value SwapStatus) forall typ val. (PersistEntity val, PersistField typ) => SqlExpr (Entity val) -> EntityField val typ -> SqlExpr (Value typ) Psql.^. EntityField SwapIntoLn SwapStatus forall typ. (typ ~ SwapStatus) => EntityField SwapIntoLn typ SwapIntoLnStatus SqlExpr (Value SwapStatus) -> SqlExpr (Value SwapStatus) -> SqlExpr (Value Bool) forall typ. PersistField typ => SqlExpr (Value typ) -> SqlExpr (Value typ) -> SqlExpr (Value Bool) Psql.==. SwapStatus -> SqlExpr (Value SwapStatus) forall typ. PersistField typ => typ -> SqlExpr (Value typ) Psql.val SwapStatus SwapExpired ) SqlExpr (Value Bool) -> SqlExpr (Value Bool) -> SqlExpr (Value Bool) Psql.&&. ( SqlExpr (Entity SwapUtxo) utxo SqlExpr (Entity SwapUtxo) -> EntityField SwapUtxo SwapUtxoStatus -> SqlExpr (Value SwapUtxoStatus) forall typ val. (PersistEntity val, PersistField typ) => SqlExpr (Entity val) -> EntityField val typ -> SqlExpr (Value typ) Psql.^. EntityField SwapUtxo SwapUtxoStatus forall typ. (typ ~ SwapUtxoStatus) => EntityField SwapUtxo typ SwapUtxoStatus SqlExpr (Value SwapUtxoStatus) -> SqlExpr (ValueList SwapUtxoStatus) -> SqlExpr (Value Bool) forall typ. PersistField typ => SqlExpr (Value typ) -> SqlExpr (ValueList typ) -> SqlExpr (Value Bool) `Psql.in_` [SwapUtxoStatus] -> SqlExpr (ValueList SwapUtxoStatus) forall typ. PersistField typ => [typ] -> SqlExpr (ValueList typ) Psql.valList [ SwapUtxoStatus SwapUtxoUnspent, SwapUtxoStatus SwapUtxoUnspentChanReserve ] ) ) SqlExpr (Value Bool) -> SqlExpr (Value Bool) -> SqlExpr (Value Bool) Psql.||. ( ( SqlExpr (Entity SwapIntoLn) swap SqlExpr (Entity SwapIntoLn) -> EntityField SwapIntoLn SwapStatus -> SqlExpr (Value SwapStatus) forall typ val. (PersistEntity val, PersistField typ) => SqlExpr (Entity val) -> EntityField val typ -> SqlExpr (Value typ) Psql.^. EntityField SwapIntoLn SwapStatus forall typ. (typ ~ SwapStatus) => EntityField SwapIntoLn typ SwapIntoLnStatus SqlExpr (Value SwapStatus) -> SqlExpr (Value SwapStatus) -> SqlExpr (Value Bool) forall typ. PersistField typ => SqlExpr (Value typ) -> SqlExpr (Value typ) -> SqlExpr (Value Bool) Psql.==. SwapStatus -> SqlExpr (Value SwapStatus) forall typ. PersistField typ => typ -> SqlExpr (Value typ) Psql.val SwapStatus SwapSucceeded ) SqlExpr (Value Bool) -> SqlExpr (Value Bool) -> SqlExpr (Value Bool) Psql.&&. ( SqlExpr (Entity SwapUtxo) utxo SqlExpr (Entity SwapUtxo) -> EntityField SwapUtxo SwapUtxoStatus -> SqlExpr (Value SwapUtxoStatus) forall typ val. (PersistEntity val, PersistField typ) => SqlExpr (Entity val) -> EntityField val typ -> SqlExpr (Value typ) Psql.^. EntityField SwapUtxo SwapUtxoStatus forall typ. (typ ~ SwapUtxoStatus) => EntityField SwapUtxo typ SwapUtxoStatus SqlExpr (Value SwapUtxoStatus) -> SqlExpr (Value SwapUtxoStatus) -> SqlExpr (Value Bool) forall typ. PersistField typ => SqlExpr (Value typ) -> SqlExpr (Value typ) -> SqlExpr (Value Bool) Psql.==. SwapUtxoStatus -> SqlExpr (Value SwapUtxoStatus) forall typ. PersistField typ => typ -> SqlExpr (Value typ) Psql.val SwapUtxoStatus SwapUtxoUnspent ) ) ) (SqlExpr (Entity SwapUtxo), SqlExpr (Entity SwapIntoLn)) -> SqlQuery (SqlExpr (Entity SwapUtxo), SqlExpr (Entity SwapIntoLn)) forall (f :: * -> *) a. Applicative f => a -> f a pure (SqlExpr (Entity SwapUtxo) utxo, SqlExpr (Entity SwapIntoLn) swap) getUtxosBySwapIdSql :: ( MonadIO m ) => SwapIntoLnId -> ReaderT Psql.SqlBackend m [Entity SwapUtxo] getUtxosBySwapIdSql :: forall (m :: * -> *). MonadIO m => SwapIntoLnId -> ReaderT SqlBackend m [Entity SwapUtxo] getUtxosBySwapIdSql SwapIntoLnId swapId = do SqlQuery (SqlExpr (Entity SwapUtxo)) -> ReaderT SqlBackend m [Entity SwapUtxo] forall a r (m :: * -> *). (SqlSelect a r, MonadIO m) => SqlQuery a -> SqlReadT m [r] Psql.select (SqlQuery (SqlExpr (Entity SwapUtxo)) -> ReaderT SqlBackend m [Entity SwapUtxo]) -> SqlQuery (SqlExpr (Entity SwapUtxo)) -> ReaderT SqlBackend m [Entity SwapUtxo] forall a b. (a -> b) -> a -> b $ (SqlExpr (Entity SwapUtxo) -> SqlQuery (SqlExpr (Entity SwapUtxo))) -> SqlQuery (SqlExpr (Entity SwapUtxo)) forall a b. From a => (a -> SqlQuery b) -> SqlQuery b Psql.from ((SqlExpr (Entity SwapUtxo) -> SqlQuery (SqlExpr (Entity SwapUtxo))) -> SqlQuery (SqlExpr (Entity SwapUtxo))) -> (SqlExpr (Entity SwapUtxo) -> SqlQuery (SqlExpr (Entity SwapUtxo))) -> SqlQuery (SqlExpr (Entity SwapUtxo)) forall a b. (a -> b) -> a -> b $ \SqlExpr (Entity SwapUtxo) row -> do LockingKind -> SqlQuery () Psql.locking LockingKind Psql.ForUpdate SqlExpr (Value Bool) -> SqlQuery () Psql.where_ ( SqlExpr (Entity SwapUtxo) row SqlExpr (Entity SwapUtxo) -> EntityField SwapUtxo SwapIntoLnId -> SqlExpr (Value SwapIntoLnId) forall typ val. (PersistEntity val, PersistField typ) => SqlExpr (Entity val) -> EntityField val typ -> SqlExpr (Value typ) Psql.^. EntityField SwapUtxo SwapIntoLnId forall typ. (typ ~ SwapIntoLnId) => EntityField SwapUtxo typ SwapUtxoSwapIntoLnId SqlExpr (Value SwapIntoLnId) -> SqlExpr (Value SwapIntoLnId) -> SqlExpr (Value Bool) forall typ. PersistField typ => SqlExpr (Value typ) -> SqlExpr (Value typ) -> SqlExpr (Value Bool) Psql.==. SwapIntoLnId -> SqlExpr (Value SwapIntoLnId) forall typ. PersistField typ => typ -> SqlExpr (Value typ) Psql.val SwapIntoLnId swapId ) SqlExpr (Entity SwapUtxo) -> SqlQuery (SqlExpr (Entity SwapUtxo)) forall (f :: * -> *) a. Applicative f => a -> f a pure SqlExpr (Entity SwapUtxo) row updateRefundBlockIdSql :: ( MonadIO m ) => BlockId -> ReaderT Psql.SqlBackend m () updateRefundBlockIdSql :: forall (m :: * -> *). MonadIO m => BlockId -> ReaderT SqlBackend m () updateRefundBlockIdSql BlockId blkId = do [Entity SwapUtxo] utxos <- SqlQuery (SqlExpr (Entity SwapUtxo)) -> ReaderT SqlBackend m [Entity SwapUtxo] forall a r (m :: * -> *). (SqlSelect a r, MonadIO m) => SqlQuery a -> SqlReadT m [r] Psql.select (SqlQuery (SqlExpr (Entity SwapUtxo)) -> ReaderT SqlBackend m [Entity SwapUtxo]) -> SqlQuery (SqlExpr (Entity SwapUtxo)) -> ReaderT SqlBackend m [Entity SwapUtxo] forall a b. (a -> b) -> a -> b $ (SqlExpr (Entity SwapUtxo) -> SqlQuery (SqlExpr (Entity SwapUtxo))) -> SqlQuery (SqlExpr (Entity SwapUtxo)) forall a b. From a => (a -> SqlQuery b) -> SqlQuery b Psql.from ((SqlExpr (Entity SwapUtxo) -> SqlQuery (SqlExpr (Entity SwapUtxo))) -> SqlQuery (SqlExpr (Entity SwapUtxo))) -> (SqlExpr (Entity SwapUtxo) -> SqlQuery (SqlExpr (Entity SwapUtxo))) -> SqlQuery (SqlExpr (Entity SwapUtxo)) forall a b. (a -> b) -> a -> b $ \SqlExpr (Entity SwapUtxo) row -> do SqlExpr (Value Bool) -> SqlQuery () Psql.where_ ( SqlExpr (Entity SwapUtxo) row SqlExpr (Entity SwapUtxo) -> EntityField SwapUtxo BlockId -> SqlExpr (Value BlockId) forall typ val. (PersistEntity val, PersistField typ) => SqlExpr (Entity val) -> EntityField val typ -> SqlExpr (Value typ) Psql.^. EntityField SwapUtxo BlockId forall typ. (typ ~ BlockId) => EntityField SwapUtxo typ SwapUtxoBlockId SqlExpr (Value BlockId) -> SqlExpr (Value BlockId) -> SqlExpr (Value Bool) forall typ. PersistField typ => SqlExpr (Value typ) -> SqlExpr (Value typ) -> SqlExpr (Value Bool) Psql.==. BlockId -> SqlExpr (Value BlockId) forall typ. PersistField typ => typ -> SqlExpr (Value typ) Psql.val BlockId blkId ) SqlExpr (Entity SwapUtxo) -> SqlQuery (SqlExpr (Entity SwapUtxo)) forall (f :: * -> *) a. Applicative f => a -> f a pure SqlExpr (Entity SwapUtxo) row (SqlExpr (Entity SwapUtxo) -> SqlQuery ()) -> ReaderT SqlBackend m () forall (m :: * -> *) val. (MonadIO m, PersistEntity val, BackendCompatible SqlBackend (PersistEntityBackend val)) => (SqlExpr (Entity val) -> SqlQuery ()) -> SqlWriteT m () Psql.update ((SqlExpr (Entity SwapUtxo) -> SqlQuery ()) -> ReaderT SqlBackend m ()) -> (SqlExpr (Entity SwapUtxo) -> SqlQuery ()) -> ReaderT SqlBackend m () forall a b. (a -> b) -> a -> b $ \SqlExpr (Entity SwapUtxo) row -> do SqlExpr (Entity SwapUtxo) -> [SqlExpr (Entity SwapUtxo) -> SqlExpr Update] -> SqlQuery () forall val. PersistEntity val => SqlExpr (Entity val) -> [SqlExpr (Entity val) -> SqlExpr Update] -> SqlQuery () Psql.set SqlExpr (Entity SwapUtxo) row [ EntityField SwapUtxo (Maybe BlockId) forall typ. (typ ~ Maybe BlockId) => EntityField SwapUtxo typ SwapUtxoRefundBlockId EntityField SwapUtxo (Maybe BlockId) -> SqlExpr (Value (Maybe BlockId)) -> SqlExpr (Entity SwapUtxo) -> SqlExpr Update forall val typ. (PersistEntity val, PersistField typ) => EntityField val typ -> SqlExpr (Value typ) -> SqlExpr (Entity val) -> SqlExpr Update Psql.=. Maybe BlockId -> SqlExpr (Value (Maybe BlockId)) forall typ. PersistField typ => typ -> SqlExpr (Value typ) Psql.val (BlockId -> Maybe BlockId forall a. a -> Maybe a Just BlockId blkId) ] SqlExpr (Value Bool) -> SqlQuery () Psql.where_ (SqlExpr (Value Bool) -> SqlQuery ()) -> SqlExpr (Value Bool) -> SqlQuery () forall a b. (a -> b) -> a -> b $ SqlExpr (Entity SwapUtxo) row SqlExpr (Entity SwapUtxo) -> EntityField SwapUtxo (Maybe (TxId 'Funding)) -> SqlExpr (Value (Maybe (TxId 'Funding))) forall typ val. (PersistEntity val, PersistField typ) => SqlExpr (Entity val) -> EntityField val typ -> SqlExpr (Value typ) Psql.^. EntityField SwapUtxo (Maybe (TxId 'Funding)) forall typ. (typ ~ Maybe (TxId 'Funding)) => EntityField SwapUtxo typ SwapUtxoRefundTxId SqlExpr (Value (Maybe (TxId 'Funding))) -> SqlExpr (ValueList (Maybe (TxId 'Funding))) -> SqlExpr (Value Bool) forall typ. PersistField typ => SqlExpr (Value typ) -> SqlExpr (ValueList typ) -> SqlExpr (Value Bool) `Psql.in_` [Maybe (TxId 'Funding)] -> SqlExpr (ValueList (Maybe (TxId 'Funding))) forall typ. PersistField typ => [typ] -> SqlExpr (ValueList typ) Psql.valList (TxId 'Funding -> Maybe (TxId 'Funding) forall a. a -> Maybe a Just (TxId 'Funding -> Maybe (TxId 'Funding)) -> [TxId 'Funding] -> [Maybe (TxId 'Funding)] forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> (SwapUtxo -> TxId 'Funding swapUtxoTxid (SwapUtxo -> TxId 'Funding) -> (Entity SwapUtxo -> SwapUtxo) -> Entity SwapUtxo -> TxId 'Funding forall b c a. (b -> c) -> (a -> b) -> a -> c . Entity SwapUtxo -> SwapUtxo forall record. Entity record -> record entityVal (Entity SwapUtxo -> TxId 'Funding) -> [Entity SwapUtxo] -> [TxId 'Funding] forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> [Entity SwapUtxo] utxos)) SqlExpr (Value Bool) -> SqlExpr (Value Bool) -> SqlExpr (Value Bool) Psql.&&. ( SqlExpr (Entity SwapUtxo) row SqlExpr (Entity SwapUtxo) -> EntityField SwapUtxo SwapUtxoStatus -> SqlExpr (Value SwapUtxoStatus) forall typ val. (PersistEntity val, PersistField typ) => SqlExpr (Entity val) -> EntityField val typ -> SqlExpr (Value typ) Psql.^. EntityField SwapUtxo SwapUtxoStatus forall typ. (typ ~ SwapUtxoStatus) => EntityField SwapUtxo typ SwapUtxoStatus SqlExpr (Value SwapUtxoStatus) -> SqlExpr (Value SwapUtxoStatus) -> SqlExpr (Value Bool) forall typ. PersistField typ => SqlExpr (Value typ) -> SqlExpr (Value typ) -> SqlExpr (Value Bool) Psql.==. SwapUtxoStatus -> SqlExpr (Value SwapUtxoStatus) forall typ. PersistField typ => typ -> SqlExpr (Value typ) Psql.val SwapUtxoStatus SwapUtxoSpentRefund ) updateOrphanSql :: ( MonadIO m ) => [BlockId] -> ReaderT Psql.SqlBackend m () updateOrphanSql :: forall (m :: * -> *). MonadIO m => [BlockId] -> ReaderT SqlBackend m () updateOrphanSql [BlockId] ids = do UTCTime ct <- ReaderT SqlBackend m UTCTime forall (m :: * -> *). MonadIO m => m UTCTime getCurrentTime (SqlExpr (Entity SwapUtxo) -> SqlQuery ()) -> ReaderT SqlBackend m () forall (m :: * -> *) val. (MonadIO m, PersistEntity val, BackendCompatible SqlBackend (PersistEntityBackend val)) => (SqlExpr (Entity val) -> SqlQuery ()) -> SqlWriteT m () Psql.update ((SqlExpr (Entity SwapUtxo) -> SqlQuery ()) -> ReaderT SqlBackend m ()) -> (SqlExpr (Entity SwapUtxo) -> SqlQuery ()) -> ReaderT SqlBackend m () forall a b. (a -> b) -> a -> b $ \SqlExpr (Entity SwapUtxo) row -> do SqlExpr (Entity SwapUtxo) -> [SqlExpr (Entity SwapUtxo) -> SqlExpr Update] -> SqlQuery () forall val. PersistEntity val => SqlExpr (Entity val) -> [SqlExpr (Entity val) -> SqlExpr Update] -> SqlQuery () Psql.set SqlExpr (Entity SwapUtxo) row [ EntityField SwapUtxo SwapUtxoStatus forall typ. (typ ~ SwapUtxoStatus) => EntityField SwapUtxo typ SwapUtxoStatus EntityField SwapUtxo SwapUtxoStatus -> SqlExpr (Value SwapUtxoStatus) -> SqlExpr (Entity SwapUtxo) -> SqlExpr Update forall val typ. (PersistEntity val, PersistField typ) => EntityField val typ -> SqlExpr (Value typ) -> SqlExpr (Entity val) -> SqlExpr Update Psql.=. SwapUtxoStatus -> SqlExpr (Value SwapUtxoStatus) forall typ. PersistField typ => typ -> SqlExpr (Value typ) Psql.val SwapUtxoStatus SwapUtxoOrphan, EntityField SwapUtxo UTCTime forall typ. (typ ~ UTCTime) => EntityField SwapUtxo typ SwapUtxoUpdatedAt EntityField SwapUtxo UTCTime -> SqlExpr (Value UTCTime) -> SqlExpr (Entity SwapUtxo) -> SqlExpr Update forall val typ. (PersistEntity val, PersistField typ) => EntityField val typ -> SqlExpr (Value typ) -> SqlExpr (Entity val) -> SqlExpr Update Psql.=. UTCTime -> SqlExpr (Value UTCTime) forall typ. PersistField typ => typ -> SqlExpr (Value typ) Psql.val UTCTime ct ] SqlExpr (Value Bool) -> SqlQuery () Psql.where_ (SqlExpr (Value Bool) -> SqlQuery ()) -> SqlExpr (Value Bool) -> SqlQuery () forall a b. (a -> b) -> a -> b $ SqlExpr (Entity SwapUtxo) row SqlExpr (Entity SwapUtxo) -> EntityField SwapUtxo BlockId -> SqlExpr (Value BlockId) forall typ val. (PersistEntity val, PersistField typ) => SqlExpr (Entity val) -> EntityField val typ -> SqlExpr (Value typ) Psql.^. EntityField SwapUtxo BlockId forall typ. (typ ~ BlockId) => EntityField SwapUtxo typ SwapUtxoBlockId SqlExpr (Value BlockId) -> SqlExpr (ValueList BlockId) -> SqlExpr (Value Bool) forall typ. PersistField typ => SqlExpr (Value typ) -> SqlExpr (ValueList typ) -> SqlExpr (Value Bool) `Psql.in_` [BlockId] -> SqlExpr (ValueList BlockId) forall typ. PersistField typ => [typ] -> SqlExpr (ValueList typ) Psql.valList [BlockId] ids revertRefundedSql :: ( MonadIO m ) => [BlockId] -> ReaderT Psql.SqlBackend m () revertRefundedSql :: forall (m :: * -> *). MonadIO m => [BlockId] -> ReaderT SqlBackend m () revertRefundedSql [BlockId] ids = do UTCTime ct <- ReaderT SqlBackend m UTCTime forall (m :: * -> *). MonadIO m => m UTCTime getCurrentTime (SqlExpr (Entity SwapUtxo) -> SqlQuery ()) -> ReaderT SqlBackend m () forall (m :: * -> *) val. (MonadIO m, PersistEntity val, BackendCompatible SqlBackend (PersistEntityBackend val)) => (SqlExpr (Entity val) -> SqlQuery ()) -> SqlWriteT m () Psql.update ((SqlExpr (Entity SwapUtxo) -> SqlQuery ()) -> ReaderT SqlBackend m ()) -> (SqlExpr (Entity SwapUtxo) -> SqlQuery ()) -> ReaderT SqlBackend m () forall a b. (a -> b) -> a -> b $ \SqlExpr (Entity SwapUtxo) row -> do SqlExpr (Entity SwapUtxo) -> [SqlExpr (Entity SwapUtxo) -> SqlExpr Update] -> SqlQuery () forall val. PersistEntity val => SqlExpr (Entity val) -> [SqlExpr (Entity val) -> SqlExpr Update] -> SqlQuery () Psql.set SqlExpr (Entity SwapUtxo) row [ EntityField SwapUtxo SwapUtxoStatus forall typ. (typ ~ SwapUtxoStatus) => EntityField SwapUtxo typ SwapUtxoStatus EntityField SwapUtxo SwapUtxoStatus -> SqlExpr (Value SwapUtxoStatus) -> SqlExpr (Entity SwapUtxo) -> SqlExpr Update forall val typ. (PersistEntity val, PersistField typ) => EntityField val typ -> SqlExpr (Value typ) -> SqlExpr (Entity val) -> SqlExpr Update Psql.=. SwapUtxoStatus -> SqlExpr (Value SwapUtxoStatus) forall typ. PersistField typ => typ -> SqlExpr (Value typ) Psql.val SwapUtxoStatus SwapUtxoUnspent, EntityField SwapUtxo (Maybe (TxId 'Funding)) forall typ. (typ ~ Maybe (TxId 'Funding)) => EntityField SwapUtxo typ SwapUtxoRefundTxId EntityField SwapUtxo (Maybe (TxId 'Funding)) -> SqlExpr (Value (Maybe (TxId 'Funding))) -> SqlExpr (Entity SwapUtxo) -> SqlExpr Update forall val typ. (PersistEntity val, PersistField typ) => EntityField val typ -> SqlExpr (Value typ) -> SqlExpr (Entity val) -> SqlExpr Update Psql.=. Maybe (TxId 'Funding) -> SqlExpr (Value (Maybe (TxId 'Funding))) forall typ. PersistField typ => typ -> SqlExpr (Value typ) Psql.val Maybe (TxId 'Funding) forall a. Maybe a Nothing, EntityField SwapUtxo (Maybe BlockId) forall typ. (typ ~ Maybe BlockId) => EntityField SwapUtxo typ SwapUtxoRefundBlockId EntityField SwapUtxo (Maybe BlockId) -> SqlExpr (Value (Maybe BlockId)) -> SqlExpr (Entity SwapUtxo) -> SqlExpr Update forall val typ. (PersistEntity val, PersistField typ) => EntityField val typ -> SqlExpr (Value typ) -> SqlExpr (Entity val) -> SqlExpr Update Psql.=. Maybe BlockId -> SqlExpr (Value (Maybe BlockId)) forall typ. PersistField typ => typ -> SqlExpr (Value typ) Psql.val Maybe BlockId forall a. Maybe a Nothing, EntityField SwapUtxo UTCTime forall typ. (typ ~ UTCTime) => EntityField SwapUtxo typ SwapUtxoUpdatedAt EntityField SwapUtxo UTCTime -> SqlExpr (Value UTCTime) -> SqlExpr (Entity SwapUtxo) -> SqlExpr Update forall val typ. (PersistEntity val, PersistField typ) => EntityField val typ -> SqlExpr (Value typ) -> SqlExpr (Entity val) -> SqlExpr Update Psql.=. UTCTime -> SqlExpr (Value UTCTime) forall typ. PersistField typ => typ -> SqlExpr (Value typ) Psql.val UTCTime ct ] SqlExpr (Value Bool) -> SqlQuery () Psql.where_ (SqlExpr (Value Bool) -> SqlQuery ()) -> SqlExpr (Value Bool) -> SqlQuery () forall a b. (a -> b) -> a -> b $ SqlExpr (Entity SwapUtxo) row SqlExpr (Entity SwapUtxo) -> EntityField SwapUtxo (Maybe BlockId) -> SqlExpr (Value (Maybe BlockId)) forall typ val. (PersistEntity val, PersistField typ) => SqlExpr (Entity val) -> EntityField val typ -> SqlExpr (Value typ) Psql.^. EntityField SwapUtxo (Maybe BlockId) forall typ. (typ ~ Maybe BlockId) => EntityField SwapUtxo typ SwapUtxoRefundBlockId SqlExpr (Value (Maybe BlockId)) -> SqlExpr (ValueList (Maybe BlockId)) -> SqlExpr (Value Bool) forall typ. PersistField typ => SqlExpr (Value typ) -> SqlExpr (ValueList typ) -> SqlExpr (Value Bool) `Psql.in_` [Maybe BlockId] -> SqlExpr (ValueList (Maybe BlockId)) forall typ. PersistField typ => [typ] -> SqlExpr (ValueList typ) Psql.valList (BlockId -> Maybe BlockId forall a. a -> Maybe a Just (BlockId -> Maybe BlockId) -> [BlockId] -> [Maybe BlockId] forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> [BlockId] ids) SqlExpr (Value Bool) -> SqlExpr (Value Bool) -> SqlExpr (Value Bool) Psql.&&. ( SqlExpr (Entity SwapUtxo) row SqlExpr (Entity SwapUtxo) -> EntityField SwapUtxo SwapUtxoStatus -> SqlExpr (Value SwapUtxoStatus) forall typ val. (PersistEntity val, PersistField typ) => SqlExpr (Entity val) -> EntityField val typ -> SqlExpr (Value typ) Psql.^. EntityField SwapUtxo SwapUtxoStatus forall typ. (typ ~ SwapUtxoStatus) => EntityField SwapUtxo typ SwapUtxoStatus SqlExpr (Value SwapUtxoStatus) -> SqlExpr (Value SwapUtxoStatus) -> SqlExpr (Value Bool) forall typ. PersistField typ => SqlExpr (Value typ) -> SqlExpr (Value typ) -> SqlExpr (Value Bool) Psql.==. SwapUtxoStatus -> SqlExpr (Value SwapUtxoStatus) forall typ. PersistField typ => typ -> SqlExpr (Value typ) Psql.val SwapUtxoStatus SwapUtxoSpentRefund )