{-# LANGUAGE TemplateHaskell #-}
module BtcLsp.Storage.Model.SwapIntoLn
( createIgnoreSql,
updateWaitingPeerSql,
updateWaitingChanSql,
updateExpiredSql,
updateSucceededSql,
getSwapsWaitingPeerSql,
getSwapsWaitingChanSql,
getSwapsAboutToExpirySql,
updateSucceededWithoutInvoiceSql,
getByUuidSql,
getByFundAddressSql,
withLockedRowSql,
UtxoInfo (..),
SwapInfo (..),
)
where
import BtcLsp.Import hiding (Storage (..))
import qualified BtcLsp.Import.Psql as Psql
import qualified BtcLsp.Math.Swap as Math
import qualified BtcLsp.Storage.Util as Util
createIgnoreSql ::
( MonadIO m
) =>
Entity User ->
OnChainAddress 'Fund ->
OnChainAddress 'Gain ->
OnChainAddress 'Refund ->
UTCTime ->
Privacy ->
ReaderT Psql.SqlBackend m (Entity SwapIntoLn)
createIgnoreSql :: forall (m :: * -> *).
MonadIO m =>
Entity User
-> OnChainAddress 'Fund
-> OnChainAddress 'Gain
-> OnChainAddress 'Refund
-> UTCTime
-> Privacy
-> ReaderT SqlBackend m (Entity SwapIntoLn)
createIgnoreSql Entity User
userEnt OnChainAddress 'Fund
fundAddr OnChainAddress 'Gain
feeAndChangeAddr OnChainAddress 'Refund
refundAddr UTCTime
expAt Privacy
chanPrivacy = do
UTCTime
ct <- ReaderT SqlBackend m UTCTime
forall (m :: * -> *). MonadIO m => m UTCTime
getCurrentTime
Uuid 'SwapIntoLnTable
uuid <- ReaderT SqlBackend m (Uuid 'SwapIntoLnTable)
forall (m :: * -> *) (tab :: Table). MonadIO m => m (Uuid tab)
newUuid
Unique SwapIntoLn
-> SwapIntoLn
-> [SqlExpr (Entity SwapIntoLn) -> SqlExpr Update]
-> ReaderT SqlBackend m (Entity SwapIntoLn)
forall (m :: * -> *) record.
(MonadIO m, PersistEntity record,
IsPersistBackend (PersistEntityBackend record)) =>
Unique record
-> record
-> [SqlExpr (Entity record) -> SqlExpr Update]
-> ReaderT SqlBackend m (Entity record)
Psql.upsertBy
(OnChainAddress 'Fund -> Unique SwapIntoLn
UniqueSwapIntoLnFundAddress OnChainAddress 'Fund
fundAddr)
SwapIntoLn :: Uuid 'SwapIntoLnTable
-> UserId
-> OnChainAddress 'Fund
-> OnChainAddress 'Gain
-> OnChainAddress 'Refund
-> Money 'Usr 'Ln 'Fund
-> Money 'Lsp 'Ln 'Fund
-> Money 'Lsp 'OnChain 'Gain
-> Money 'Lsp 'OnChain 'Loss
-> SwapStatus
-> Privacy
-> UTCTime
-> UTCTime
-> UTCTime
-> SwapIntoLn
SwapIntoLn
{ swapIntoLnUuid :: Uuid 'SwapIntoLnTable
swapIntoLnUuid = Uuid 'SwapIntoLnTable
uuid,
swapIntoLnUserId :: UserId
swapIntoLnUserId = Entity User -> UserId
forall record. Entity record -> Key record
entityKey Entity User
userEnt,
swapIntoLnFundAddress :: OnChainAddress 'Fund
swapIntoLnFundAddress = OnChainAddress 'Fund
fundAddr,
swapIntoLnLspFeeAndChangeAddress :: OnChainAddress 'Gain
swapIntoLnLspFeeAndChangeAddress = OnChainAddress 'Gain
feeAndChangeAddr,
swapIntoLnRefundAddress :: OnChainAddress 'Refund
swapIntoLnRefundAddress = OnChainAddress 'Refund
refundAddr,
swapIntoLnChanCapUser :: Money 'Usr 'Ln 'Fund
swapIntoLnChanCapUser = MSat -> Money 'Usr 'Ln 'Fund
forall (owner :: Owner) (btcl :: BitcoinLayer)
(mrel :: MoneyRelation).
MSat -> Money owner btcl mrel
Money MSat
0,
swapIntoLnChanCapLsp :: Money 'Lsp 'Ln 'Fund
swapIntoLnChanCapLsp = MSat -> Money 'Lsp 'Ln 'Fund
forall (owner :: Owner) (btcl :: BitcoinLayer)
(mrel :: MoneyRelation).
MSat -> Money owner btcl mrel
Money MSat
0,
swapIntoLnFeeLsp :: Money 'Lsp 'OnChain 'Gain
swapIntoLnFeeLsp = MSat -> Money 'Lsp 'OnChain 'Gain
forall (owner :: Owner) (btcl :: BitcoinLayer)
(mrel :: MoneyRelation).
MSat -> Money owner btcl mrel
Money MSat
0,
swapIntoLnFeeMiner :: Money 'Lsp 'OnChain 'Loss
swapIntoLnFeeMiner = MSat -> Money 'Lsp 'OnChain 'Loss
forall (owner :: Owner) (btcl :: BitcoinLayer)
(mrel :: MoneyRelation).
MSat -> Money owner btcl mrel
Money MSat
0,
swapIntoLnStatus :: SwapStatus
swapIntoLnStatus = SwapStatus
SwapWaitingFundChain,
swapIntoLnPrivacy :: Privacy
swapIntoLnPrivacy = Privacy
chanPrivacy,
swapIntoLnExpiresAt :: UTCTime
swapIntoLnExpiresAt = UTCTime
expAt,
swapIntoLnInsertedAt :: UTCTime
swapIntoLnInsertedAt = UTCTime
ct,
swapIntoLnUpdatedAt :: UTCTime
swapIntoLnUpdatedAt = UTCTime
ct
}
[ EntityField SwapIntoLn UTCTime
forall typ. (typ ~ UTCTime) => EntityField SwapIntoLn typ
SwapIntoLnUpdatedAt
EntityField SwapIntoLn UTCTime
-> SqlExpr (Value UTCTime)
-> SqlExpr (Entity SwapIntoLn)
-> 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
]
updateWaitingPeerSql ::
( MonadIO m
) =>
SwapIntoLnId ->
SwapCap ->
ReaderT Psql.SqlBackend m ()
updateWaitingPeerSql :: forall (m :: * -> *).
MonadIO m =>
SwapIntoLnId -> SwapCap -> ReaderT SqlBackend m ()
updateWaitingPeerSql SwapIntoLnId
sid SwapCap
cap = do
UTCTime
ct <- ReaderT SqlBackend m UTCTime
forall (m :: * -> *). MonadIO m => m UTCTime
getCurrentTime
(SqlExpr (Entity SwapIntoLn) -> 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 SwapIntoLn) -> SqlQuery ())
-> ReaderT SqlBackend m ())
-> (SqlExpr (Entity SwapIntoLn) -> SqlQuery ())
-> ReaderT SqlBackend m ()
forall a b. (a -> b) -> a -> b
$ \SqlExpr (Entity SwapIntoLn)
row -> do
SqlExpr (Entity SwapIntoLn)
-> [SqlExpr (Entity SwapIntoLn) -> SqlExpr Update] -> SqlQuery ()
forall val.
PersistEntity val =>
SqlExpr (Entity val)
-> [SqlExpr (Entity val) -> SqlExpr Update] -> SqlQuery ()
Psql.set
SqlExpr (Entity SwapIntoLn)
row
[ EntityField SwapIntoLn (Money 'Usr 'Ln 'Fund)
forall typ.
(typ ~ Money 'Usr 'Ln 'Fund) =>
EntityField SwapIntoLn typ
SwapIntoLnChanCapUser
EntityField SwapIntoLn (Money 'Usr 'Ln 'Fund)
-> SqlExpr (Value (Money 'Usr 'Ln 'Fund))
-> SqlExpr (Entity SwapIntoLn)
-> SqlExpr Update
forall val typ.
(PersistEntity val, PersistField typ) =>
EntityField val typ
-> SqlExpr (Value typ) -> SqlExpr (Entity val) -> SqlExpr Update
Psql.=. Money 'Usr 'Ln 'Fund -> SqlExpr (Value (Money 'Usr 'Ln 'Fund))
forall typ. PersistField typ => typ -> SqlExpr (Value typ)
Psql.val (SwapCap -> Money 'Usr 'Ln 'Fund
swapCapUsr SwapCap
cap),
EntityField SwapIntoLn (Money 'Lsp 'Ln 'Fund)
forall typ.
(typ ~ Money 'Lsp 'Ln 'Fund) =>
EntityField SwapIntoLn typ
SwapIntoLnChanCapLsp
EntityField SwapIntoLn (Money 'Lsp 'Ln 'Fund)
-> SqlExpr (Value (Money 'Lsp 'Ln 'Fund))
-> SqlExpr (Entity SwapIntoLn)
-> SqlExpr Update
forall val typ.
(PersistEntity val, PersistField typ) =>
EntityField val typ
-> SqlExpr (Value typ) -> SqlExpr (Entity val) -> SqlExpr Update
Psql.=. Money 'Lsp 'Ln 'Fund -> SqlExpr (Value (Money 'Lsp 'Ln 'Fund))
forall typ. PersistField typ => typ -> SqlExpr (Value typ)
Psql.val (SwapCap -> Money 'Lsp 'Ln 'Fund
swapCapLsp SwapCap
cap),
EntityField SwapIntoLn (Money 'Lsp 'OnChain 'Gain)
forall typ.
(typ ~ Money 'Lsp 'OnChain 'Gain) =>
EntityField SwapIntoLn typ
SwapIntoLnFeeLsp
EntityField SwapIntoLn (Money 'Lsp 'OnChain 'Gain)
-> SqlExpr (Value (Money 'Lsp 'OnChain 'Gain))
-> SqlExpr (Entity SwapIntoLn)
-> SqlExpr Update
forall val typ.
(PersistEntity val, PersistField typ) =>
EntityField val typ
-> SqlExpr (Value typ) -> SqlExpr (Entity val) -> SqlExpr Update
Psql.=. Money 'Lsp 'OnChain 'Gain
-> SqlExpr (Value (Money 'Lsp 'OnChain 'Gain))
forall typ. PersistField typ => typ -> SqlExpr (Value typ)
Psql.val (SwapCap -> Money 'Lsp 'OnChain 'Gain
swapCapFee SwapCap
cap),
EntityField SwapIntoLn SwapStatus
forall typ. (typ ~ SwapStatus) => EntityField SwapIntoLn typ
SwapIntoLnStatus
EntityField SwapIntoLn SwapStatus
-> SqlExpr (Value SwapStatus)
-> SqlExpr (Entity SwapIntoLn)
-> SqlExpr Update
forall val typ.
(PersistEntity val, PersistField typ) =>
EntityField val typ
-> SqlExpr (Value typ) -> SqlExpr (Entity val) -> SqlExpr Update
Psql.=. SwapStatus -> SqlExpr (Value SwapStatus)
forall typ. PersistField typ => typ -> SqlExpr (Value typ)
Psql.val SwapStatus
SwapWaitingPeer,
EntityField SwapIntoLn UTCTime
forall typ. (typ ~ UTCTime) => EntityField SwapIntoLn typ
SwapIntoLnUpdatedAt
EntityField SwapIntoLn UTCTime
-> SqlExpr (Value UTCTime)
-> SqlExpr (Entity SwapIntoLn)
-> 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 SwapIntoLn)
row 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.==. SwapIntoLnId -> SqlExpr (Value SwapIntoLnId)
forall typ. PersistField typ => typ -> SqlExpr (Value typ)
Psql.val SwapIntoLnId
sid
)
SqlExpr (Value Bool)
-> SqlExpr (Value Bool) -> SqlExpr (Value Bool)
Psql.&&. ( SqlExpr (Entity SwapIntoLn)
row 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 (ValueList SwapStatus) -> SqlExpr (Value Bool)
forall typ.
PersistField typ =>
SqlExpr (Value typ)
-> SqlExpr (ValueList typ) -> SqlExpr (Value Bool)
`Psql.in_` [SwapStatus] -> SqlExpr (ValueList SwapStatus)
forall typ. PersistField typ => [typ] -> SqlExpr (ValueList typ)
Psql.valList
[ SwapStatus
SwapWaitingFundChain,
SwapStatus
SwapWaitingPeer
]
)
updateWaitingChanSql ::
( MonadIO m
) =>
SwapIntoLnId ->
ReaderT Psql.SqlBackend m ()
updateWaitingChanSql :: forall (m :: * -> *).
MonadIO m =>
SwapIntoLnId -> ReaderT SqlBackend m ()
updateWaitingChanSql SwapIntoLnId
id0 = do
UTCTime
ct <- ReaderT SqlBackend m UTCTime
forall (m :: * -> *). MonadIO m => m UTCTime
getCurrentTime
(SqlExpr (Entity SwapIntoLn) -> 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 SwapIntoLn) -> SqlQuery ())
-> ReaderT SqlBackend m ())
-> (SqlExpr (Entity SwapIntoLn) -> SqlQuery ())
-> ReaderT SqlBackend m ()
forall a b. (a -> b) -> a -> b
$ \SqlExpr (Entity SwapIntoLn)
row -> do
SqlExpr (Entity SwapIntoLn)
-> [SqlExpr (Entity SwapIntoLn) -> SqlExpr Update] -> SqlQuery ()
forall val.
PersistEntity val =>
SqlExpr (Entity val)
-> [SqlExpr (Entity val) -> SqlExpr Update] -> SqlQuery ()
Psql.set
SqlExpr (Entity SwapIntoLn)
row
[ EntityField SwapIntoLn SwapStatus
forall typ. (typ ~ SwapStatus) => EntityField SwapIntoLn typ
SwapIntoLnStatus
EntityField SwapIntoLn SwapStatus
-> SqlExpr (Value SwapStatus)
-> SqlExpr (Entity SwapIntoLn)
-> SqlExpr Update
forall val typ.
(PersistEntity val, PersistField typ) =>
EntityField val typ
-> SqlExpr (Value typ) -> SqlExpr (Entity val) -> SqlExpr Update
Psql.=. SwapStatus -> SqlExpr (Value SwapStatus)
forall typ. PersistField typ => typ -> SqlExpr (Value typ)
Psql.val SwapStatus
SwapWaitingChan,
EntityField SwapIntoLn UTCTime
forall typ. (typ ~ UTCTime) => EntityField SwapIntoLn typ
SwapIntoLnUpdatedAt
EntityField SwapIntoLn UTCTime
-> SqlExpr (Value UTCTime)
-> SqlExpr (Entity SwapIntoLn)
-> 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 SwapIntoLn)
row 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.==. 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 SwapIntoLn)
row 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
SwapWaitingPeer
)
updateExpiredSql ::
( MonadIO m,
KatipContext m
) =>
SwapIntoLnId ->
ReaderT Psql.SqlBackend m ()
updateExpiredSql :: forall (m :: * -> *).
(MonadIO m, KatipContext m) =>
SwapIntoLnId -> ReaderT SqlBackend m ()
updateExpiredSql SwapIntoLnId
rowId = do
UTCTime
ct <- ReaderT SqlBackend m UTCTime
forall (m :: * -> *). MonadIO m => m UTCTime
getCurrentTime
Int64
qty <- (SqlExpr (Entity SwapIntoLn) -> 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 SwapIntoLn) -> SqlQuery ())
-> ReaderT SqlBackend m Int64)
-> (SqlExpr (Entity SwapIntoLn) -> SqlQuery ())
-> ReaderT SqlBackend m Int64
forall a b. (a -> b) -> a -> b
$ \SqlExpr (Entity SwapIntoLn)
row -> do
SqlExpr (Entity SwapIntoLn)
-> [SqlExpr (Entity SwapIntoLn) -> SqlExpr Update] -> SqlQuery ()
forall val.
PersistEntity val =>
SqlExpr (Entity val)
-> [SqlExpr (Entity val) -> SqlExpr Update] -> SqlQuery ()
Psql.set
SqlExpr (Entity SwapIntoLn)
row
[ EntityField SwapIntoLn SwapStatus
forall typ. (typ ~ SwapStatus) => EntityField SwapIntoLn typ
SwapIntoLnStatus
EntityField SwapIntoLn SwapStatus
-> SqlExpr (Value SwapStatus)
-> SqlExpr (Entity SwapIntoLn)
-> SqlExpr Update
forall val typ.
(PersistEntity val, PersistField typ) =>
EntityField val typ
-> SqlExpr (Value typ) -> SqlExpr (Entity val) -> SqlExpr Update
Psql.=. SwapStatus -> SqlExpr (Value SwapStatus)
forall typ. PersistField typ => typ -> SqlExpr (Value typ)
Psql.val SwapStatus
SwapExpired,
EntityField SwapIntoLn UTCTime
forall typ. (typ ~ UTCTime) => EntityField SwapIntoLn typ
SwapIntoLnUpdatedAt
EntityField SwapIntoLn UTCTime
-> SqlExpr (Value UTCTime)
-> SqlExpr (Entity SwapIntoLn)
-> 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 SwapIntoLn)
row 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.==. SwapIntoLnId -> SqlExpr (Value SwapIntoLnId)
forall typ. PersistField typ => typ -> SqlExpr (Value typ)
Psql.val SwapIntoLnId
rowId
)
SqlExpr (Value Bool)
-> SqlExpr (Value Bool) -> SqlExpr (Value Bool)
Psql.&&. ( SqlExpr (Entity SwapIntoLn)
row 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 (ValueList SwapStatus) -> SqlExpr (Value Bool)
forall typ.
PersistField typ =>
SqlExpr (Value typ)
-> SqlExpr (ValueList typ) -> SqlExpr (Value Bool)
`Psql.in_` [SwapStatus] -> SqlExpr (ValueList SwapStatus)
forall typ. PersistField typ => [typ] -> SqlExpr (ValueList typ)
Psql.valList
[ SwapStatus
SwapWaitingFundChain,
SwapStatus
SwapWaitingPeer
]
)
Bool -> ReaderT SqlBackend m () -> ReaderT SqlBackend m ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Int64
qty Int64 -> Int64 -> Bool
forall a. Eq a => a -> a -> Bool
/= Int64
1)
(ReaderT SqlBackend m () -> ReaderT SqlBackend m ())
-> (Text -> ReaderT SqlBackend m ())
-> Text
-> ReaderT SqlBackend m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. $(logTM) Severity
ErrorS
(LogStr -> ReaderT SqlBackend m ())
-> (Text -> LogStr) -> Text -> ReaderT SqlBackend m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> LogStr
forall a. StringConv a Text => a -> LogStr
logStr
(Text -> ReaderT SqlBackend m ())
-> Text -> ReaderT SqlBackend m ()
forall a b. (a -> b) -> a -> b
$ Text
"Wrong expiry update result "
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Int64 -> Text
forall a. Out a => a -> Text
inspect Int64
qty
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" for the swap "
Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> SwapIntoLnId -> Text
forall a. Out a => a -> Text
inspect SwapIntoLnId
rowId
updateSucceededWithoutInvoiceSql ::
( MonadIO m
) =>
SwapIntoLnId ->
ReaderT Psql.SqlBackend m ()
updateSucceededWithoutInvoiceSql :: forall (m :: * -> *).
MonadIO m =>
SwapIntoLnId -> ReaderT SqlBackend m ()
updateSucceededWithoutInvoiceSql SwapIntoLnId
sid = do
UTCTime
ct <- ReaderT SqlBackend m UTCTime
forall (m :: * -> *). MonadIO m => m UTCTime
getCurrentTime
(SqlExpr (Entity SwapIntoLn) -> 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 SwapIntoLn) -> SqlQuery ())
-> ReaderT SqlBackend m ())
-> (SqlExpr (Entity SwapIntoLn) -> SqlQuery ())
-> ReaderT SqlBackend m ()
forall a b. (a -> b) -> a -> b
$ \SqlExpr (Entity SwapIntoLn)
row -> do
SqlExpr (Entity SwapIntoLn)
-> [SqlExpr (Entity SwapIntoLn) -> SqlExpr Update] -> SqlQuery ()
forall val.
PersistEntity val =>
SqlExpr (Entity val)
-> [SqlExpr (Entity val) -> SqlExpr Update] -> SqlQuery ()
Psql.set
SqlExpr (Entity SwapIntoLn)
row
[ EntityField SwapIntoLn SwapStatus
forall typ. (typ ~ SwapStatus) => EntityField SwapIntoLn typ
SwapIntoLnStatus
EntityField SwapIntoLn SwapStatus
-> SqlExpr (Value SwapStatus)
-> SqlExpr (Entity SwapIntoLn)
-> SqlExpr Update
forall val typ.
(PersistEntity val, PersistField typ) =>
EntityField val typ
-> SqlExpr (Value typ) -> SqlExpr (Entity val) -> SqlExpr Update
Psql.=. SwapStatus -> SqlExpr (Value SwapStatus)
forall typ. PersistField typ => typ -> SqlExpr (Value typ)
Psql.val SwapStatus
SwapSucceeded,
EntityField SwapIntoLn UTCTime
forall typ. (typ ~ UTCTime) => EntityField SwapIntoLn typ
SwapIntoLnUpdatedAt
EntityField SwapIntoLn UTCTime
-> SqlExpr (Value UTCTime)
-> SqlExpr (Entity SwapIntoLn)
-> 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 SwapIntoLn)
row 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.==. SwapIntoLnId -> SqlExpr (Value SwapIntoLnId)
forall typ. PersistField typ => typ -> SqlExpr (Value typ)
Psql.val SwapIntoLnId
sid
)
SqlExpr (Value Bool)
-> SqlExpr (Value Bool) -> SqlExpr (Value Bool)
Psql.&&. ( SqlExpr (Entity SwapIntoLn)
row 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
SwapWaitingChan
)
updateSucceededSql ::
( MonadIO m
) =>
SwapIntoLnId ->
ReaderT Psql.SqlBackend m ()
updateSucceededSql :: forall (m :: * -> *).
MonadIO m =>
SwapIntoLnId -> ReaderT SqlBackend m ()
updateSucceededSql SwapIntoLnId
sid = do
UTCTime
ct <- ReaderT SqlBackend m UTCTime
forall (m :: * -> *). MonadIO m => m UTCTime
getCurrentTime
(SqlExpr (Entity SwapIntoLn) -> 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 SwapIntoLn) -> SqlQuery ())
-> ReaderT SqlBackend m ())
-> (SqlExpr (Entity SwapIntoLn) -> SqlQuery ())
-> ReaderT SqlBackend m ()
forall a b. (a -> b) -> a -> b
$ \SqlExpr (Entity SwapIntoLn)
row -> do
SqlExpr (Entity SwapIntoLn)
-> [SqlExpr (Entity SwapIntoLn) -> SqlExpr Update] -> SqlQuery ()
forall val.
PersistEntity val =>
SqlExpr (Entity val)
-> [SqlExpr (Entity val) -> SqlExpr Update] -> SqlQuery ()
Psql.set
SqlExpr (Entity SwapIntoLn)
row
[ EntityField SwapIntoLn SwapStatus
forall typ. (typ ~ SwapStatus) => EntityField SwapIntoLn typ
SwapIntoLnStatus
EntityField SwapIntoLn SwapStatus
-> SqlExpr (Value SwapStatus)
-> SqlExpr (Entity SwapIntoLn)
-> SqlExpr Update
forall val typ.
(PersistEntity val, PersistField typ) =>
EntityField val typ
-> SqlExpr (Value typ) -> SqlExpr (Entity val) -> SqlExpr Update
Psql.=. SwapStatus -> SqlExpr (Value SwapStatus)
forall typ. PersistField typ => typ -> SqlExpr (Value typ)
Psql.val SwapStatus
SwapSucceeded,
EntityField SwapIntoLn UTCTime
forall typ. (typ ~ UTCTime) => EntityField SwapIntoLn typ
SwapIntoLnUpdatedAt
EntityField SwapIntoLn UTCTime
-> SqlExpr (Value UTCTime)
-> SqlExpr (Entity SwapIntoLn)
-> 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 SwapIntoLn)
row 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.==. SwapIntoLnId -> SqlExpr (Value SwapIntoLnId)
forall typ. PersistField typ => typ -> SqlExpr (Value typ)
Psql.val SwapIntoLnId
sid
)
SqlExpr (Value Bool)
-> SqlExpr (Value Bool) -> SqlExpr (Value Bool)
Psql.&&. ( SqlExpr (Entity SwapIntoLn)
row 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
SwapWaitingChan
)
getSwapsWaitingPeerSql ::
( MonadIO m
) =>
ReaderT
Psql.SqlBackend
m
[ ( Entity SwapIntoLn,
Entity User
)
]
getSwapsWaitingPeerSql :: forall (m :: * -> *).
MonadIO m =>
ReaderT SqlBackend m [(Entity SwapIntoLn, Entity User)]
getSwapsWaitingPeerSql =
SqlQuery (SqlExpr (Entity SwapIntoLn), SqlExpr (Entity User))
-> ReaderT SqlBackend m [(Entity SwapIntoLn, Entity User)]
forall a r (m :: * -> *).
(SqlSelect a r, MonadIO m) =>
SqlQuery a -> SqlReadT m [r]
Psql.select (SqlQuery (SqlExpr (Entity SwapIntoLn), SqlExpr (Entity User))
-> ReaderT SqlBackend m [(Entity SwapIntoLn, Entity User)])
-> SqlQuery (SqlExpr (Entity SwapIntoLn), SqlExpr (Entity User))
-> ReaderT SqlBackend m [(Entity SwapIntoLn, Entity User)]
forall a b. (a -> b) -> a -> b
$
(InnerJoin (SqlExpr (Entity SwapIntoLn)) (SqlExpr (Entity User))
-> SqlQuery (SqlExpr (Entity SwapIntoLn), SqlExpr (Entity User)))
-> SqlQuery (SqlExpr (Entity SwapIntoLn), SqlExpr (Entity User))
forall a b. From a => (a -> SqlQuery b) -> SqlQuery b
Psql.from ((InnerJoin (SqlExpr (Entity SwapIntoLn)) (SqlExpr (Entity User))
-> SqlQuery (SqlExpr (Entity SwapIntoLn), SqlExpr (Entity User)))
-> SqlQuery (SqlExpr (Entity SwapIntoLn), SqlExpr (Entity User)))
-> (InnerJoin (SqlExpr (Entity SwapIntoLn)) (SqlExpr (Entity User))
-> SqlQuery (SqlExpr (Entity SwapIntoLn), SqlExpr (Entity User)))
-> SqlQuery (SqlExpr (Entity SwapIntoLn), SqlExpr (Entity User))
forall a b. (a -> b) -> a -> b
$ \(SqlExpr (Entity SwapIntoLn)
swap `Psql.InnerJoin` SqlExpr (Entity User)
user) -> do
LockingKind -> SqlQuery ()
Psql.locking LockingKind
Psql.ForUpdate
SqlExpr (Value Bool) -> SqlQuery ()
Psql.on
( SqlExpr (Entity SwapIntoLn)
swap SqlExpr (Entity SwapIntoLn)
-> EntityField SwapIntoLn UserId -> SqlExpr (Value UserId)
forall typ val.
(PersistEntity val, PersistField typ) =>
SqlExpr (Entity val) -> EntityField val typ -> SqlExpr (Value typ)
Psql.^. EntityField SwapIntoLn UserId
forall typ. (typ ~ UserId) => EntityField SwapIntoLn typ
SwapIntoLnUserId
SqlExpr (Value UserId)
-> SqlExpr (Value UserId) -> SqlExpr (Value Bool)
forall typ.
PersistField typ =>
SqlExpr (Value typ) -> SqlExpr (Value typ) -> SqlExpr (Value Bool)
Psql.==. SqlExpr (Entity User)
user SqlExpr (Entity User)
-> EntityField User UserId -> SqlExpr (Value UserId)
forall typ val.
(PersistEntity val, PersistField typ) =>
SqlExpr (Entity val) -> EntityField val typ -> SqlExpr (Value typ)
Psql.^. EntityField User UserId
forall typ. (typ ~ UserId) => EntityField User typ
UserId
)
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
SwapWaitingPeer
)
(SqlExpr (Entity SwapIntoLn), SqlExpr (Entity User))
-> SqlQuery (SqlExpr (Entity SwapIntoLn), SqlExpr (Entity User))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SqlExpr (Entity SwapIntoLn)
swap, SqlExpr (Entity User)
user)
getSwapsWaitingChanSql ::
( MonadIO m
) =>
ReaderT
Psql.SqlBackend
m
[ ( Entity SwapIntoLn,
Entity User
)
]
getSwapsWaitingChanSql :: forall (m :: * -> *).
MonadIO m =>
ReaderT SqlBackend m [(Entity SwapIntoLn, Entity User)]
getSwapsWaitingChanSql =
SqlQuery (SqlExpr (Entity SwapIntoLn), SqlExpr (Entity User))
-> ReaderT SqlBackend m [(Entity SwapIntoLn, Entity User)]
forall a r (m :: * -> *).
(SqlSelect a r, MonadIO m) =>
SqlQuery a -> SqlReadT m [r]
Psql.select (SqlQuery (SqlExpr (Entity SwapIntoLn), SqlExpr (Entity User))
-> ReaderT SqlBackend m [(Entity SwapIntoLn, Entity User)])
-> SqlQuery (SqlExpr (Entity SwapIntoLn), SqlExpr (Entity User))
-> ReaderT SqlBackend m [(Entity SwapIntoLn, Entity User)]
forall a b. (a -> b) -> a -> b
$
(InnerJoin (SqlExpr (Entity SwapIntoLn)) (SqlExpr (Entity User))
-> SqlQuery (SqlExpr (Entity SwapIntoLn), SqlExpr (Entity User)))
-> SqlQuery (SqlExpr (Entity SwapIntoLn), SqlExpr (Entity User))
forall a b. From a => (a -> SqlQuery b) -> SqlQuery b
Psql.from ((InnerJoin (SqlExpr (Entity SwapIntoLn)) (SqlExpr (Entity User))
-> SqlQuery (SqlExpr (Entity SwapIntoLn), SqlExpr (Entity User)))
-> SqlQuery (SqlExpr (Entity SwapIntoLn), SqlExpr (Entity User)))
-> (InnerJoin (SqlExpr (Entity SwapIntoLn)) (SqlExpr (Entity User))
-> SqlQuery (SqlExpr (Entity SwapIntoLn), SqlExpr (Entity User)))
-> SqlQuery (SqlExpr (Entity SwapIntoLn), SqlExpr (Entity User))
forall a b. (a -> b) -> a -> b
$ \(SqlExpr (Entity SwapIntoLn)
swap `Psql.InnerJoin` SqlExpr (Entity User)
user) -> do
LockingKind -> SqlQuery ()
Psql.locking LockingKind
Psql.ForUpdate
SqlExpr (Value Bool) -> SqlQuery ()
Psql.on
( SqlExpr (Entity SwapIntoLn)
swap SqlExpr (Entity SwapIntoLn)
-> EntityField SwapIntoLn UserId -> SqlExpr (Value UserId)
forall typ val.
(PersistEntity val, PersistField typ) =>
SqlExpr (Entity val) -> EntityField val typ -> SqlExpr (Value typ)
Psql.^. EntityField SwapIntoLn UserId
forall typ. (typ ~ UserId) => EntityField SwapIntoLn typ
SwapIntoLnUserId
SqlExpr (Value UserId)
-> SqlExpr (Value UserId) -> SqlExpr (Value Bool)
forall typ.
PersistField typ =>
SqlExpr (Value typ) -> SqlExpr (Value typ) -> SqlExpr (Value Bool)
Psql.==. SqlExpr (Entity User)
user SqlExpr (Entity User)
-> EntityField User UserId -> SqlExpr (Value UserId)
forall typ val.
(PersistEntity val, PersistField typ) =>
SqlExpr (Entity val) -> EntityField val typ -> SqlExpr (Value typ)
Psql.^. EntityField User UserId
forall typ. (typ ~ UserId) => EntityField User typ
UserId
)
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
SwapWaitingChan
)
(SqlExpr (Entity SwapIntoLn), SqlExpr (Entity User))
-> SqlQuery (SqlExpr (Entity SwapIntoLn), SqlExpr (Entity User))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SqlExpr (Entity SwapIntoLn)
swap, SqlExpr (Entity User)
user)
getSwapsAboutToExpirySql ::
( MonadIO m
) =>
ReaderT Psql.SqlBackend m [Entity SwapIntoLn]
getSwapsAboutToExpirySql :: forall (m :: * -> *).
MonadIO m =>
ReaderT SqlBackend m [Entity SwapIntoLn]
getSwapsAboutToExpirySql = do
UTCTime
nearExpTime <- Seconds -> ReaderT SqlBackend m UTCTime
forall (m :: * -> *). MonadIO m => Seconds -> m UTCTime
getFutureTime Seconds
Math.swapExpiryLimitInternal
SqlQuery (SqlExpr (Entity SwapIntoLn))
-> ReaderT SqlBackend m [Entity SwapIntoLn]
forall a r (m :: * -> *).
(SqlSelect a r, MonadIO m) =>
SqlQuery a -> SqlReadT m [r]
Psql.select (SqlQuery (SqlExpr (Entity SwapIntoLn))
-> ReaderT SqlBackend m [Entity SwapIntoLn])
-> SqlQuery (SqlExpr (Entity SwapIntoLn))
-> ReaderT SqlBackend m [Entity SwapIntoLn]
forall a b. (a -> b) -> a -> b
$
(SqlExpr (Entity SwapIntoLn)
-> SqlQuery (SqlExpr (Entity SwapIntoLn)))
-> SqlQuery (SqlExpr (Entity SwapIntoLn))
forall a b. From a => (a -> SqlQuery b) -> SqlQuery b
Psql.from ((SqlExpr (Entity SwapIntoLn)
-> SqlQuery (SqlExpr (Entity SwapIntoLn)))
-> SqlQuery (SqlExpr (Entity SwapIntoLn)))
-> (SqlExpr (Entity SwapIntoLn)
-> SqlQuery (SqlExpr (Entity SwapIntoLn)))
-> SqlQuery (SqlExpr (Entity SwapIntoLn))
forall a b. (a -> b) -> a -> b
$ \SqlExpr (Entity SwapIntoLn)
row -> do
LockingKind -> SqlQuery ()
Psql.locking LockingKind
Psql.ForUpdate
SqlExpr (Value Bool) -> SqlQuery ()
Psql.where_
( ( SqlExpr (Entity SwapIntoLn)
row 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 (ValueList SwapStatus) -> SqlExpr (Value Bool)
forall typ.
PersistField typ =>
SqlExpr (Value typ)
-> SqlExpr (ValueList typ) -> SqlExpr (Value Bool)
`Psql.in_` [SwapStatus] -> SqlExpr (ValueList SwapStatus)
forall typ. PersistField typ => [typ] -> SqlExpr (ValueList typ)
Psql.valList
[ SwapStatus
SwapWaitingFundChain,
SwapStatus
SwapWaitingPeer
]
)
SqlExpr (Value Bool)
-> SqlExpr (Value Bool) -> SqlExpr (Value Bool)
Psql.&&. ( SqlExpr (Entity SwapIntoLn)
row SqlExpr (Entity SwapIntoLn)
-> EntityField SwapIntoLn UTCTime -> SqlExpr (Value UTCTime)
forall typ val.
(PersistEntity val, PersistField typ) =>
SqlExpr (Entity val) -> EntityField val typ -> SqlExpr (Value typ)
Psql.^. EntityField SwapIntoLn UTCTime
forall typ. (typ ~ UTCTime) => EntityField SwapIntoLn typ
SwapIntoLnExpiresAt
SqlExpr (Value UTCTime)
-> SqlExpr (Value UTCTime) -> SqlExpr (Value Bool)
forall typ.
PersistField typ =>
SqlExpr (Value typ) -> SqlExpr (Value typ) -> SqlExpr (Value Bool)
Psql.<. UTCTime -> SqlExpr (Value UTCTime)
forall typ. PersistField typ => typ -> SqlExpr (Value typ)
Psql.val UTCTime
nearExpTime
)
)
SqlExpr (Entity SwapIntoLn)
-> SqlQuery (SqlExpr (Entity SwapIntoLn))
forall (f :: * -> *) a. Applicative f => a -> f a
pure SqlExpr (Entity SwapIntoLn)
row
data UtxoInfo = UtxoInfo
{ UtxoInfo -> Entity SwapUtxo
utxoInfoUtxo :: Entity SwapUtxo,
UtxoInfo -> Entity Block
utxoInfoBlock :: Entity Block
}
deriving stock
( UtxoInfo -> UtxoInfo -> Bool
(UtxoInfo -> UtxoInfo -> Bool)
-> (UtxoInfo -> UtxoInfo -> Bool) -> Eq UtxoInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UtxoInfo -> UtxoInfo -> Bool
$c/= :: UtxoInfo -> UtxoInfo -> Bool
== :: UtxoInfo -> UtxoInfo -> Bool
$c== :: UtxoInfo -> UtxoInfo -> Bool
Eq,
Int -> UtxoInfo -> ShowS
[UtxoInfo] -> ShowS
UtxoInfo -> String
(Int -> UtxoInfo -> ShowS)
-> (UtxoInfo -> String) -> ([UtxoInfo] -> ShowS) -> Show UtxoInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [UtxoInfo] -> ShowS
$cshowList :: [UtxoInfo] -> ShowS
show :: UtxoInfo -> String
$cshow :: UtxoInfo -> String
showsPrec :: Int -> UtxoInfo -> ShowS
$cshowsPrec :: Int -> UtxoInfo -> ShowS
Show
)
data SwapInfo = SwapInfo
{ SwapInfo -> Entity SwapIntoLn
swapInfoSwap :: Entity SwapIntoLn,
SwapInfo -> Entity User
swapInfoUser :: Entity User,
SwapInfo -> [UtxoInfo]
swapInfoUtxo :: [UtxoInfo],
SwapInfo -> [Entity LnChan]
swapInfoChan :: [Entity LnChan]
}
deriving stock
( SwapInfo -> SwapInfo -> Bool
(SwapInfo -> SwapInfo -> Bool)
-> (SwapInfo -> SwapInfo -> Bool) -> Eq SwapInfo
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SwapInfo -> SwapInfo -> Bool
$c/= :: SwapInfo -> SwapInfo -> Bool
== :: SwapInfo -> SwapInfo -> Bool
$c== :: SwapInfo -> SwapInfo -> Bool
Eq,
Int -> SwapInfo -> ShowS
[SwapInfo] -> ShowS
SwapInfo -> String
(Int -> SwapInfo -> ShowS)
-> (SwapInfo -> String) -> ([SwapInfo] -> ShowS) -> Show SwapInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [SwapInfo] -> ShowS
$cshowList :: [SwapInfo] -> ShowS
show :: SwapInfo -> String
$cshow :: SwapInfo -> String
showsPrec :: Int -> SwapInfo -> ShowS
$cshowsPrec :: Int -> SwapInfo -> ShowS
Show
)
getByUuidSql ::
( MonadIO m
) =>
Uuid 'SwapIntoLnTable ->
ReaderT Psql.SqlBackend m (Maybe SwapInfo)
getByUuidSql :: forall (m :: * -> *).
MonadIO m =>
Uuid 'SwapIntoLnTable -> ReaderT SqlBackend m (Maybe SwapInfo)
getByUuidSql Uuid 'SwapIntoLnTable
uuid =
([(Maybe (Entity SwapUtxo), Maybe (Entity Block),
Maybe (Entity LnChan), Entity SwapIntoLn, Entity User)]
-> Maybe SwapInfo
prettifyGetByUuid ([(Maybe (Entity SwapUtxo), Maybe (Entity Block),
Maybe (Entity LnChan), Entity SwapIntoLn, Entity User)]
-> Maybe SwapInfo)
-> ReaderT
SqlBackend
m
[(Maybe (Entity SwapUtxo), Maybe (Entity Block),
Maybe (Entity LnChan), Entity SwapIntoLn, Entity User)]
-> ReaderT SqlBackend m (Maybe SwapInfo)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>) (ReaderT
SqlBackend
m
[(Maybe (Entity SwapUtxo), Maybe (Entity Block),
Maybe (Entity LnChan), Entity SwapIntoLn, Entity User)]
-> ReaderT SqlBackend m (Maybe SwapInfo))
-> ReaderT
SqlBackend
m
[(Maybe (Entity SwapUtxo), Maybe (Entity Block),
Maybe (Entity LnChan), Entity SwapIntoLn, Entity User)]
-> ReaderT SqlBackend m (Maybe SwapInfo)
forall a b. (a -> b) -> a -> b
$
SqlQuery
(SqlExpr (Maybe (Entity SwapUtxo)), SqlExpr (Maybe (Entity Block)),
SqlExpr (Maybe (Entity LnChan)), SqlExpr (Entity SwapIntoLn),
SqlExpr (Entity User))
-> ReaderT
SqlBackend
m
[(Maybe (Entity SwapUtxo), Maybe (Entity Block),
Maybe (Entity LnChan), Entity SwapIntoLn, Entity User)]
forall a r (m :: * -> *).
(SqlSelect a r, MonadIO m) =>
SqlQuery a -> SqlReadT m [r]
Psql.select (SqlQuery
(SqlExpr (Maybe (Entity SwapUtxo)), SqlExpr (Maybe (Entity Block)),
SqlExpr (Maybe (Entity LnChan)), SqlExpr (Entity SwapIntoLn),
SqlExpr (Entity User))
-> ReaderT
SqlBackend
m
[(Maybe (Entity SwapUtxo), Maybe (Entity Block),
Maybe (Entity LnChan), Entity SwapIntoLn, Entity User)])
-> SqlQuery
(SqlExpr (Maybe (Entity SwapUtxo)), SqlExpr (Maybe (Entity Block)),
SqlExpr (Maybe (Entity LnChan)), SqlExpr (Entity SwapIntoLn),
SqlExpr (Entity User))
-> ReaderT
SqlBackend
m
[(Maybe (Entity SwapUtxo), Maybe (Entity Block),
Maybe (Entity LnChan), Entity SwapIntoLn, Entity User)]
forall a b. (a -> b) -> a -> b
$
(InnerJoin
(LeftOuterJoin
(RightOuterJoin
(InnerJoin
(SqlExpr (Maybe (Entity SwapUtxo)))
(SqlExpr (Maybe (Entity Block))))
(SqlExpr (Entity SwapIntoLn)))
(SqlExpr (Maybe (Entity LnChan))))
(SqlExpr (Entity User))
-> SqlQuery
(SqlExpr (Maybe (Entity SwapUtxo)), SqlExpr (Maybe (Entity Block)),
SqlExpr (Maybe (Entity LnChan)), SqlExpr (Entity SwapIntoLn),
SqlExpr (Entity User)))
-> SqlQuery
(SqlExpr (Maybe (Entity SwapUtxo)), SqlExpr (Maybe (Entity Block)),
SqlExpr (Maybe (Entity LnChan)), SqlExpr (Entity SwapIntoLn),
SqlExpr (Entity User))
forall a b. From a => (a -> SqlQuery b) -> SqlQuery b
Psql.from ((InnerJoin
(LeftOuterJoin
(RightOuterJoin
(InnerJoin
(SqlExpr (Maybe (Entity SwapUtxo)))
(SqlExpr (Maybe (Entity Block))))
(SqlExpr (Entity SwapIntoLn)))
(SqlExpr (Maybe (Entity LnChan))))
(SqlExpr (Entity User))
-> SqlQuery
(SqlExpr (Maybe (Entity SwapUtxo)), SqlExpr (Maybe (Entity Block)),
SqlExpr (Maybe (Entity LnChan)), SqlExpr (Entity SwapIntoLn),
SqlExpr (Entity User)))
-> SqlQuery
(SqlExpr (Maybe (Entity SwapUtxo)), SqlExpr (Maybe (Entity Block)),
SqlExpr (Maybe (Entity LnChan)), SqlExpr (Entity SwapIntoLn),
SqlExpr (Entity User)))
-> (InnerJoin
(LeftOuterJoin
(RightOuterJoin
(InnerJoin
(SqlExpr (Maybe (Entity SwapUtxo)))
(SqlExpr (Maybe (Entity Block))))
(SqlExpr (Entity SwapIntoLn)))
(SqlExpr (Maybe (Entity LnChan))))
(SqlExpr (Entity User))
-> SqlQuery
(SqlExpr (Maybe (Entity SwapUtxo)), SqlExpr (Maybe (Entity Block)),
SqlExpr (Maybe (Entity LnChan)), SqlExpr (Entity SwapIntoLn),
SqlExpr (Entity User)))
-> SqlQuery
(SqlExpr (Maybe (Entity SwapUtxo)), SqlExpr (Maybe (Entity Block)),
SqlExpr (Maybe (Entity LnChan)), SqlExpr (Entity SwapIntoLn),
SqlExpr (Entity User))
forall a b. (a -> b) -> a -> b
$
\( SqlExpr (Maybe (Entity SwapUtxo))
mUtxo
`Psql.InnerJoin` SqlExpr (Maybe (Entity Block))
mBlock
`Psql.RightOuterJoin` SqlExpr (Entity SwapIntoLn)
swap
`Psql.LeftOuterJoin` SqlExpr (Maybe (Entity LnChan))
mChan
`Psql.InnerJoin` SqlExpr (Entity User)
user
) -> do
SqlExpr (Value Bool) -> SqlQuery ()
Psql.on
( SqlExpr (Entity SwapIntoLn)
swap SqlExpr (Entity SwapIntoLn)
-> EntityField SwapIntoLn UserId -> SqlExpr (Value UserId)
forall typ val.
(PersistEntity val, PersistField typ) =>
SqlExpr (Entity val) -> EntityField val typ -> SqlExpr (Value typ)
Psql.^. EntityField SwapIntoLn UserId
forall typ. (typ ~ UserId) => EntityField SwapIntoLn typ
SwapIntoLnUserId
SqlExpr (Value UserId)
-> SqlExpr (Value UserId) -> SqlExpr (Value Bool)
forall typ.
PersistField typ =>
SqlExpr (Value typ) -> SqlExpr (Value typ) -> SqlExpr (Value Bool)
Psql.==. SqlExpr (Entity User)
user SqlExpr (Entity User)
-> EntityField User UserId -> SqlExpr (Value UserId)
forall typ val.
(PersistEntity val, PersistField typ) =>
SqlExpr (Entity val) -> EntityField val typ -> SqlExpr (Value typ)
Psql.^. EntityField User UserId
forall typ. (typ ~ UserId) => EntityField User typ
UserId
)
SqlExpr (Value Bool) -> SqlQuery ()
Psql.on
( SqlExpr (Maybe (Entity LnChan))
mChan SqlExpr (Maybe (Entity LnChan))
-> EntityField LnChan (Maybe SwapIntoLnId)
-> SqlExpr (Value (Maybe (Maybe SwapIntoLnId)))
forall val typ.
(PersistEntity val, PersistField typ) =>
SqlExpr (Maybe (Entity val))
-> EntityField val typ -> SqlExpr (Value (Maybe typ))
Psql.?. EntityField LnChan (Maybe SwapIntoLnId)
forall typ. (typ ~ Maybe SwapIntoLnId) => EntityField LnChan typ
LnChanSwapIntoLnId
SqlExpr (Value (Maybe (Maybe SwapIntoLnId)))
-> SqlExpr (Value (Maybe (Maybe SwapIntoLnId)))
-> SqlExpr (Value Bool)
forall typ.
PersistField typ =>
SqlExpr (Value typ) -> SqlExpr (Value typ) -> SqlExpr (Value Bool)
Psql.==. SqlExpr (Value (Maybe SwapIntoLnId))
-> SqlExpr (Value (Maybe (Maybe SwapIntoLnId)))
forall typ. SqlExpr (Value typ) -> SqlExpr (Value (Maybe typ))
Psql.just
( SqlExpr (Value SwapIntoLnId)
-> SqlExpr (Value (Maybe SwapIntoLnId))
forall typ. SqlExpr (Value typ) -> SqlExpr (Value (Maybe typ))
Psql.just (SqlExpr (Value SwapIntoLnId)
-> SqlExpr (Value (Maybe SwapIntoLnId)))
-> SqlExpr (Value SwapIntoLnId)
-> SqlExpr (Value (Maybe SwapIntoLnId))
forall a b. (a -> b) -> a -> b
$
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 Bool) -> SqlQuery ()
Psql.on
( SqlExpr (Maybe (Entity SwapUtxo))
mUtxo SqlExpr (Maybe (Entity SwapUtxo))
-> EntityField SwapUtxo SwapIntoLnId
-> SqlExpr (Value (Maybe SwapIntoLnId))
forall val typ.
(PersistEntity val, PersistField typ) =>
SqlExpr (Maybe (Entity val))
-> EntityField val typ -> SqlExpr (Value (Maybe typ))
Psql.?. EntityField SwapUtxo SwapIntoLnId
forall typ. (typ ~ SwapIntoLnId) => EntityField SwapUtxo typ
SwapUtxoSwapIntoLnId
SqlExpr (Value (Maybe SwapIntoLnId))
-> SqlExpr (Value (Maybe SwapIntoLnId)) -> SqlExpr (Value Bool)
forall typ.
PersistField typ =>
SqlExpr (Value typ) -> SqlExpr (Value typ) -> SqlExpr (Value Bool)
Psql.==. SqlExpr (Value SwapIntoLnId)
-> SqlExpr (Value (Maybe SwapIntoLnId))
forall typ. SqlExpr (Value typ) -> SqlExpr (Value (Maybe typ))
Psql.just (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 Bool) -> SqlQuery ()
Psql.on
( SqlExpr (Maybe (Entity SwapUtxo))
mUtxo SqlExpr (Maybe (Entity SwapUtxo))
-> EntityField SwapUtxo (Key Block)
-> SqlExpr (Value (Maybe (Key Block)))
forall val typ.
(PersistEntity val, PersistField typ) =>
SqlExpr (Maybe (Entity val))
-> EntityField val typ -> SqlExpr (Value (Maybe typ))
Psql.?. EntityField SwapUtxo (Key Block)
forall typ. (typ ~ Key Block) => EntityField SwapUtxo typ
SwapUtxoBlockId
SqlExpr (Value (Maybe (Key Block)))
-> SqlExpr (Value (Maybe (Key Block))) -> SqlExpr (Value Bool)
forall typ.
PersistField typ =>
SqlExpr (Value typ) -> SqlExpr (Value typ) -> SqlExpr (Value Bool)
Psql.==. SqlExpr (Maybe (Entity Block))
mBlock SqlExpr (Maybe (Entity Block))
-> EntityField Block (Key Block)
-> SqlExpr (Value (Maybe (Key Block)))
forall val typ.
(PersistEntity val, PersistField typ) =>
SqlExpr (Maybe (Entity val))
-> EntityField val typ -> SqlExpr (Value (Maybe typ))
Psql.?. EntityField Block (Key Block)
forall typ. (typ ~ Key Block) => EntityField Block typ
BlockId
)
SqlExpr (Value Bool) -> SqlQuery ()
Psql.where_
( SqlExpr (Entity SwapIntoLn)
swap SqlExpr (Entity SwapIntoLn)
-> EntityField SwapIntoLn (Uuid 'SwapIntoLnTable)
-> SqlExpr (Value (Uuid 'SwapIntoLnTable))
forall typ val.
(PersistEntity val, PersistField typ) =>
SqlExpr (Entity val) -> EntityField val typ -> SqlExpr (Value typ)
Psql.^. EntityField SwapIntoLn (Uuid 'SwapIntoLnTable)
forall typ.
(typ ~ Uuid 'SwapIntoLnTable) =>
EntityField SwapIntoLn typ
SwapIntoLnUuid
SqlExpr (Value (Uuid 'SwapIntoLnTable))
-> SqlExpr (Value (Uuid 'SwapIntoLnTable)) -> SqlExpr (Value Bool)
forall typ.
PersistField typ =>
SqlExpr (Value typ) -> SqlExpr (Value typ) -> SqlExpr (Value Bool)
Psql.==. Uuid 'SwapIntoLnTable -> SqlExpr (Value (Uuid 'SwapIntoLnTable))
forall typ. PersistField typ => typ -> SqlExpr (Value typ)
Psql.val Uuid 'SwapIntoLnTable
uuid
)
(SqlExpr (Maybe (Entity SwapUtxo)), SqlExpr (Maybe (Entity Block)),
SqlExpr (Maybe (Entity LnChan)), SqlExpr (Entity SwapIntoLn),
SqlExpr (Entity User))
-> SqlQuery
(SqlExpr (Maybe (Entity SwapUtxo)), SqlExpr (Maybe (Entity Block)),
SqlExpr (Maybe (Entity LnChan)), SqlExpr (Entity SwapIntoLn),
SqlExpr (Entity User))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (SqlExpr (Maybe (Entity SwapUtxo))
mUtxo, SqlExpr (Maybe (Entity Block))
mBlock, SqlExpr (Maybe (Entity LnChan))
mChan, SqlExpr (Entity SwapIntoLn)
swap, SqlExpr (Entity User)
user)
prettifyGetByUuid ::
[ ( Maybe (Entity SwapUtxo),
Maybe (Entity Block),
Maybe (Entity LnChan),
Entity SwapIntoLn,
Entity User
)
] ->
Maybe SwapInfo
prettifyGetByUuid :: [(Maybe (Entity SwapUtxo), Maybe (Entity Block),
Maybe (Entity LnChan), Entity SwapIntoLn, Entity User)]
-> Maybe SwapInfo
prettifyGetByUuid = \case
[] ->
Maybe SwapInfo
forall a. Maybe a
Nothing
xs :: [(Maybe (Entity SwapUtxo), Maybe (Entity Block),
Maybe (Entity LnChan), Entity SwapIntoLn, Entity User)]
xs@((Maybe (Entity SwapUtxo)
_, Maybe (Entity Block)
_, Maybe (Entity LnChan)
_, Entity SwapIntoLn
swap, Entity User
user) : [(Maybe (Entity SwapUtxo), Maybe (Entity Block),
Maybe (Entity LnChan), Entity SwapIntoLn, Entity User)]
_) ->
SwapInfo -> Maybe SwapInfo
forall a. a -> Maybe a
Just
SwapInfo :: Entity SwapIntoLn
-> Entity User -> [UtxoInfo] -> [Entity LnChan] -> SwapInfo
SwapInfo
{ swapInfoSwap :: Entity SwapIntoLn
swapInfoSwap = Entity SwapIntoLn
swap,
swapInfoUser :: Entity User
swapInfoUser = Entity User
user,
swapInfoUtxo :: [UtxoInfo]
swapInfoUtxo =
( \(Maybe (Entity SwapUtxo)
mUtxo, Maybe (Entity Block)
mBlock, Maybe (Entity LnChan)
_, Entity SwapIntoLn
_, Entity User
_) ->
[UtxoInfo]
-> (UtxoInfo -> [UtxoInfo]) -> Maybe UtxoInfo -> [UtxoInfo]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe
[UtxoInfo]
forall a. Monoid a => a
mempty
UtxoInfo -> [UtxoInfo]
forall (f :: * -> *) a. Applicative f => a -> f a
pure
(Maybe UtxoInfo -> [UtxoInfo]) -> Maybe UtxoInfo -> [UtxoInfo]
forall a b. (a -> b) -> a -> b
$ Entity SwapUtxo -> Entity Block -> UtxoInfo
UtxoInfo
(Entity SwapUtxo -> Entity Block -> UtxoInfo)
-> Maybe (Entity SwapUtxo) -> Maybe (Entity Block -> UtxoInfo)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe (Entity SwapUtxo)
mUtxo
Maybe (Entity Block -> UtxoInfo)
-> Maybe (Entity Block) -> Maybe UtxoInfo
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe (Entity Block)
mBlock
)
((Maybe (Entity SwapUtxo), Maybe (Entity Block),
Maybe (Entity LnChan), Entity SwapIntoLn, Entity User)
-> [UtxoInfo])
-> [(Maybe (Entity SwapUtxo), Maybe (Entity Block),
Maybe (Entity LnChan), Entity SwapIntoLn, Entity User)]
-> [UtxoInfo]
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< [(Maybe (Entity SwapUtxo), Maybe (Entity Block),
Maybe (Entity LnChan), Entity SwapIntoLn, Entity User)]
xs,
swapInfoChan :: [Entity LnChan]
swapInfoChan =
[Entity LnChan] -> [Entity LnChan]
forall a. Ord a => [a] -> [a]
nubOrd ([Entity LnChan] -> [Entity LnChan])
-> [Entity LnChan] -> [Entity LnChan]
forall a b. (a -> b) -> a -> b
$
( \(Maybe (Entity SwapUtxo)
_, Maybe (Entity Block)
_, Maybe (Entity LnChan)
mChan, Entity SwapIntoLn
_, Entity User
_) ->
[Entity LnChan]
-> (Entity LnChan -> [Entity LnChan])
-> Maybe (Entity LnChan)
-> [Entity LnChan]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe
[Entity LnChan]
forall a. Monoid a => a
mempty
Entity LnChan -> [Entity LnChan]
forall (f :: * -> *) a. Applicative f => a -> f a
pure
Maybe (Entity LnChan)
mChan
)
((Maybe (Entity SwapUtxo), Maybe (Entity Block),
Maybe (Entity LnChan), Entity SwapIntoLn, Entity User)
-> [Entity LnChan])
-> [(Maybe (Entity SwapUtxo), Maybe (Entity Block),
Maybe (Entity LnChan), Entity SwapIntoLn, Entity User)]
-> [Entity LnChan]
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< [(Maybe (Entity SwapUtxo), Maybe (Entity Block),
Maybe (Entity LnChan), Entity SwapIntoLn, Entity User)]
xs
}
getByFundAddressSql ::
( MonadIO m
) =>
OnChainAddress 'Fund ->
ReaderT Psql.SqlBackend m (Maybe (Entity SwapIntoLn))
getByFundAddressSql :: forall (m :: * -> *).
MonadIO m =>
OnChainAddress 'Fund
-> ReaderT SqlBackend m (Maybe (Entity SwapIntoLn))
getByFundAddressSql =
Unique SwapIntoLn -> SqlPersistT m (Maybe (Entity SwapIntoLn))
forall (m :: * -> *) a.
(MonadIO m, HasTable a, ToBackendKey SqlBackend a) =>
Unique a -> SqlPersistT m (Maybe (Entity a))
Util.lockByUnique
(Unique SwapIntoLn -> SqlPersistT m (Maybe (Entity SwapIntoLn)))
-> (OnChainAddress 'Fund -> Unique SwapIntoLn)
-> OnChainAddress 'Fund
-> SqlPersistT m (Maybe (Entity SwapIntoLn))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. OnChainAddress 'Fund -> Unique SwapIntoLn
UniqueSwapIntoLnFundAddress
withLockedRowSql ::
( MonadIO m
) =>
SwapIntoLnId ->
(SwapStatus -> Bool) ->
(SwapIntoLn -> ReaderT Psql.SqlBackend m a) ->
ReaderT Psql.SqlBackend m (Either (Entity SwapIntoLn) a)
withLockedRowSql :: forall (m :: * -> *) a.
MonadIO m =>
SwapIntoLnId
-> (SwapStatus -> Bool)
-> (SwapIntoLn -> ReaderT SqlBackend m a)
-> ReaderT SqlBackend m (Either (Entity SwapIntoLn) a)
withLockedRowSql SwapIntoLnId
rowId SwapStatus -> Bool
pre SwapIntoLn -> ReaderT SqlBackend m a
action = do
SwapIntoLn
rowVal <- SwapIntoLnId -> SqlPersistT m SwapIntoLn
forall (m :: * -> *) a.
(MonadIO m, HasTable a, ToBackendKey SqlBackend a) =>
Key a -> SqlPersistT m a
Util.lockByRow SwapIntoLnId
rowId
if SwapStatus -> Bool
pre (SwapStatus -> Bool) -> SwapStatus -> Bool
forall a b. (a -> b) -> a -> b
$ SwapIntoLn -> SwapStatus
swapIntoLnStatus SwapIntoLn
rowVal
then a -> Either (Entity SwapIntoLn) a
forall a b. b -> Either a b
Right (a -> Either (Entity SwapIntoLn) a)
-> ReaderT SqlBackend m a
-> ReaderT SqlBackend m (Either (Entity SwapIntoLn) a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SwapIntoLn -> ReaderT SqlBackend m a
action SwapIntoLn
rowVal
else Either (Entity SwapIntoLn) a
-> ReaderT SqlBackend m (Either (Entity SwapIntoLn) a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Either (Entity SwapIntoLn) a
-> ReaderT SqlBackend m (Either (Entity SwapIntoLn) a))
-> (Entity SwapIntoLn -> Either (Entity SwapIntoLn) a)
-> Entity SwapIntoLn
-> ReaderT SqlBackend m (Either (Entity SwapIntoLn) a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Entity SwapIntoLn -> Either (Entity SwapIntoLn) a
forall a b. a -> Either a b
Left (Entity SwapIntoLn
-> ReaderT SqlBackend m (Either (Entity SwapIntoLn) a))
-> Entity SwapIntoLn
-> ReaderT SqlBackend m (Either (Entity SwapIntoLn) a)
forall a b. (a -> b) -> a -> b
$ SwapIntoLnId -> SwapIntoLn -> Entity SwapIntoLn
forall record. Key record -> record -> Entity record
Entity SwapIntoLnId
rowId SwapIntoLn
rowVal