{-# LANGUAGE TemplateHaskell #-} module BtcLsp.Storage.Model.LnChan ( createUpdateSql, getByChannelPointSql, persistChannelUpdateSql, persistOpenedChannelsSql, persistClosedChannelsSql, getBySwapIdSql, getActiveNonSwapSql, ) where import BtcLsp.Import import qualified BtcLsp.Import.Psql as Psql import qualified BtcLsp.Storage.Model.SwapIntoLn as SwapIntoLn import qualified BtcLsp.Storage.Util as Util import qualified Data.Set as Set import qualified LndClient.Data.Channel as Channel import qualified LndClient.Data.Channel as Lnd import qualified LndClient.Data.ChannelBackup as Lnd import qualified LndClient.Data.ChannelPoint as ChannelPoint import qualified LndClient.Data.ChannelPoint as Lnd import qualified LndClient.Data.CloseChannel as CloseChannel import qualified LndClient.Data.CloseChannel as Lnd import qualified LndClient.Data.SubscribeChannelEvents as Lnd createUpdateSql :: ( MonadIO m ) => SwapIntoLnId -> TxId 'Funding -> Vout 'Funding -> ReaderT Psql.SqlBackend m (Entity LnChan) createUpdateSql :: forall (m :: * -> *). MonadIO m => SwapIntoLnId -> TxId 'Funding -> Vout 'Funding -> ReaderT SqlBackend m (Entity LnChan) createUpdateSql SwapIntoLnId swapId TxId 'Funding txid Vout 'Funding vout = do UTCTime ct <- ReaderT SqlBackend m UTCTime forall (m :: * -> *). MonadIO m => m UTCTime getCurrentTime Unique LnChan -> LnChan -> [SqlExpr (Entity LnChan) -> SqlExpr Update] -> ReaderT SqlBackend m (Entity LnChan) 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 (TxId 'Funding -> Vout 'Funding -> Unique LnChan UniqueLnChan TxId 'Funding txid Vout 'Funding vout) LnChan :: Maybe SwapIntoLnId -> TxId 'Funding -> Vout 'Funding -> Maybe (TxId 'Closing) -> Maybe ChanId -> Maybe SingleChanBackupBlob -> MSat -> MSat -> LnChanStatus -> UTCTime -> UTCTime -> UTCTime -> LnChan LnChan { lnChanSwapIntoLnId :: Maybe SwapIntoLnId lnChanSwapIntoLnId = SwapIntoLnId -> Maybe SwapIntoLnId forall a. a -> Maybe a Just SwapIntoLnId swapId, lnChanFundingTxId :: TxId 'Funding lnChanFundingTxId = TxId 'Funding txid, lnChanFundingVout :: Vout 'Funding lnChanFundingVout = Vout 'Funding vout, lnChanClosingTxId :: Maybe (TxId 'Closing) lnChanClosingTxId = Maybe (TxId 'Closing) forall a. Maybe a Nothing, lnChanExtId :: Maybe ChanId lnChanExtId = Maybe ChanId forall a. Maybe a Nothing, lnChanBak :: Maybe SingleChanBackupBlob lnChanBak = Maybe SingleChanBackupBlob forall a. Maybe a Nothing, lnChanStatus :: LnChanStatus lnChanStatus = LnChanStatus LnChanStatusPendingOpen, lnChanInsertedAt :: UTCTime lnChanInsertedAt = UTCTime ct, lnChanUpdatedAt :: UTCTime lnChanUpdatedAt = UTCTime ct, lnChanTransactedAt :: UTCTime lnChanTransactedAt = UTCTime ct, lnChanTotalSatoshisReceived :: MSat lnChanTotalSatoshisReceived = Word64 -> MSat MSat Word64 0, lnChanTotalSatoshisSent :: MSat lnChanTotalSatoshisSent = Word64 -> MSat MSat Word64 0 } [ EntityField LnChan (Maybe SwapIntoLnId) forall typ. (typ ~ Maybe SwapIntoLnId) => EntityField LnChan typ LnChanSwapIntoLnId EntityField LnChan (Maybe SwapIntoLnId) -> SqlExpr (Value (Maybe SwapIntoLnId)) -> SqlExpr (Entity LnChan) -> SqlExpr Update forall val typ. (PersistEntity val, PersistField typ) => EntityField val typ -> SqlExpr (Value typ) -> SqlExpr (Entity val) -> SqlExpr Update Psql.=. Maybe SwapIntoLnId -> SqlExpr (Value (Maybe SwapIntoLnId)) forall typ. PersistField typ => typ -> SqlExpr (Value typ) Psql.val (SwapIntoLnId -> Maybe SwapIntoLnId forall a. a -> Maybe a Just SwapIntoLnId swapId), EntityField LnChan UTCTime forall typ. (typ ~ UTCTime) => EntityField LnChan typ LnChanUpdatedAt EntityField LnChan UTCTime -> SqlExpr (Value UTCTime) -> SqlExpr (Entity LnChan) -> 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 ] getByChannelPointSql :: ( Storage m ) => TxId 'Funding -> Vout 'Funding -> ReaderT Psql.SqlBackend m (Maybe (Entity LnChan)) getByChannelPointSql :: forall (m :: * -> *). Storage m => TxId 'Funding -> Vout 'Funding -> ReaderT SqlBackend m (Maybe (Entity LnChan)) getByChannelPointSql TxId 'Funding txid = Unique LnChan -> SqlPersistT m (Maybe (Entity LnChan)) forall (m :: * -> *) a. (MonadIO m, HasTable a, ToBackendKey SqlBackend a) => Unique a -> SqlPersistT m (Maybe (Entity a)) Util.lockByUnique (Unique LnChan -> SqlPersistT m (Maybe (Entity LnChan))) -> (Vout 'Funding -> Unique LnChan) -> Vout 'Funding -> SqlPersistT m (Maybe (Entity LnChan)) forall b c a. (b -> c) -> (a -> b) -> a -> c . TxId 'Funding -> Vout 'Funding -> Unique LnChan UniqueLnChan TxId 'Funding txid getBySwapIdSql :: ( Storage m ) => SwapIntoLnId -> ReaderT Psql.SqlBackend m [Entity LnChan] getBySwapIdSql :: forall (m :: * -> *). Storage m => SwapIntoLnId -> ReaderT SqlBackend m [Entity LnChan] getBySwapIdSql SwapIntoLnId swpId = SqlQuery (SqlExpr (Entity LnChan)) -> ReaderT SqlBackend m [Entity LnChan] forall a r (m :: * -> *). (SqlSelect a r, MonadIO m) => SqlQuery a -> SqlReadT m [r] Psql.select (SqlQuery (SqlExpr (Entity LnChan)) -> ReaderT SqlBackend m [Entity LnChan]) -> SqlQuery (SqlExpr (Entity LnChan)) -> ReaderT SqlBackend m [Entity LnChan] forall a b. (a -> b) -> a -> b $ (SqlExpr (Entity LnChan) -> SqlQuery (SqlExpr (Entity LnChan))) -> SqlQuery (SqlExpr (Entity LnChan)) forall a b. From a => (a -> SqlQuery b) -> SqlQuery b Psql.from ((SqlExpr (Entity LnChan) -> SqlQuery (SqlExpr (Entity LnChan))) -> SqlQuery (SqlExpr (Entity LnChan))) -> (SqlExpr (Entity LnChan) -> SqlQuery (SqlExpr (Entity LnChan))) -> SqlQuery (SqlExpr (Entity LnChan)) forall a b. (a -> b) -> a -> b $ \SqlExpr (Entity LnChan) c -> do SqlExpr (Value Bool) -> SqlQuery () Psql.where_ (SqlExpr (Entity LnChan) c SqlExpr (Entity LnChan) -> EntityField LnChan (Maybe SwapIntoLnId) -> SqlExpr (Value (Maybe SwapIntoLnId)) forall typ val. (PersistEntity val, PersistField typ) => SqlExpr (Entity val) -> EntityField val typ -> SqlExpr (Value typ) Psql.^. EntityField LnChan (Maybe SwapIntoLnId) forall typ. (typ ~ Maybe SwapIntoLnId) => EntityField LnChan typ LnChanSwapIntoLnId 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.==. Maybe SwapIntoLnId -> SqlExpr (Value (Maybe SwapIntoLnId)) forall typ. PersistField typ => typ -> SqlExpr (Value typ) Psql.val (SwapIntoLnId -> Maybe SwapIntoLnId forall a. a -> Maybe a Just SwapIntoLnId swpId)) SqlExpr (Entity LnChan) -> SqlQuery (SqlExpr (Entity LnChan)) forall (f :: * -> *) a. Applicative f => a -> f a pure SqlExpr (Entity LnChan) c getActiveNonSwapSql :: ( Storage m ) => ReaderT Psql.SqlBackend m [Entity LnChan] getActiveNonSwapSql :: forall (m :: * -> *). Storage m => ReaderT SqlBackend m [Entity LnChan] getActiveNonSwapSql = SqlQuery (SqlExpr (Entity LnChan)) -> ReaderT SqlBackend m [Entity LnChan] forall a r (m :: * -> *). (SqlSelect a r, MonadIO m) => SqlQuery a -> SqlReadT m [r] Psql.select (SqlQuery (SqlExpr (Entity LnChan)) -> ReaderT SqlBackend m [Entity LnChan]) -> SqlQuery (SqlExpr (Entity LnChan)) -> ReaderT SqlBackend m [Entity LnChan] forall a b. (a -> b) -> a -> b $ (SqlExpr (Entity LnChan) -> SqlQuery (SqlExpr (Entity LnChan))) -> SqlQuery (SqlExpr (Entity LnChan)) forall a b. From a => (a -> SqlQuery b) -> SqlQuery b Psql.from ((SqlExpr (Entity LnChan) -> SqlQuery (SqlExpr (Entity LnChan))) -> SqlQuery (SqlExpr (Entity LnChan))) -> (SqlExpr (Entity LnChan) -> SqlQuery (SqlExpr (Entity LnChan))) -> SqlQuery (SqlExpr (Entity LnChan)) forall a b. (a -> b) -> a -> b $ \SqlExpr (Entity LnChan) row -> do SqlExpr (Value Bool) -> SqlQuery () Psql.where_ ( ( SqlExpr (Entity LnChan) row SqlExpr (Entity LnChan) -> EntityField LnChan LnChanStatus -> SqlExpr (Value LnChanStatus) forall typ val. (PersistEntity val, PersistField typ) => SqlExpr (Entity val) -> EntityField val typ -> SqlExpr (Value typ) Psql.^. EntityField LnChan LnChanStatus forall typ. (typ ~ LnChanStatus) => EntityField LnChan typ LnChanStatus SqlExpr (Value LnChanStatus) -> SqlExpr (Value LnChanStatus) -> SqlExpr (Value Bool) forall typ. PersistField typ => SqlExpr (Value typ) -> SqlExpr (Value typ) -> SqlExpr (Value Bool) Psql.==. LnChanStatus -> SqlExpr (Value LnChanStatus) forall typ. PersistField typ => typ -> SqlExpr (Value typ) Psql.val LnChanStatus LnChanStatusActive ) SqlExpr (Value Bool) -> SqlExpr (Value Bool) -> SqlExpr (Value Bool) Psql.&&. SqlExpr (Value (Maybe SwapIntoLnId)) -> SqlExpr (Value Bool) forall typ. PersistField typ => SqlExpr (Value (Maybe typ)) -> SqlExpr (Value Bool) Psql.isNothing ( SqlExpr (Entity LnChan) row SqlExpr (Entity LnChan) -> EntityField LnChan (Maybe SwapIntoLnId) -> SqlExpr (Value (Maybe SwapIntoLnId)) forall typ val. (PersistEntity val, PersistField typ) => SqlExpr (Entity val) -> EntityField val typ -> SqlExpr (Value typ) Psql.^. EntityField LnChan (Maybe SwapIntoLnId) forall typ. (typ ~ Maybe SwapIntoLnId) => EntityField LnChan typ LnChanSwapIntoLnId ) ) SqlExpr (Entity LnChan) -> SqlQuery (SqlExpr (Entity LnChan)) forall (f :: * -> *) a. Applicative f => a -> f a pure SqlExpr (Entity LnChan) row lazyUpdateSwapStatus :: ( MonadIO m ) => Entity LnChan -> ReaderT Psql.SqlBackend m () lazyUpdateSwapStatus :: forall (m :: * -> *). MonadIO m => Entity LnChan -> ReaderT SqlBackend m () lazyUpdateSwapStatus (Entity Key LnChan _ LnChan chanVal) = do Maybe SwapIntoLnId -> (SwapIntoLnId -> ReaderT SqlBackend m ()) -> ReaderT SqlBackend m () forall (f :: * -> *) a. Applicative f => Maybe a -> (a -> f ()) -> f () whenJust (LnChan -> Maybe SwapIntoLnId lnChanSwapIntoLnId LnChan chanVal) ((SwapIntoLnId -> ReaderT SqlBackend m ()) -> ReaderT SqlBackend m ()) -> (SwapIntoLnId -> ReaderT SqlBackend m ()) -> ReaderT SqlBackend m () forall a b. (a -> b) -> a -> b $ \SwapIntoLnId swapKey -> Bool -> ReaderT SqlBackend m () -> ReaderT SqlBackend m () forall (f :: * -> *). Applicative f => Bool -> f () -> f () when (LnChan -> LnChanStatus lnChanStatus LnChan chanVal LnChanStatus -> LnChanStatus -> Bool forall a. Eq a => a -> a -> Bool == LnChanStatus LnChanStatusActive) (ReaderT SqlBackend m () -> ReaderT SqlBackend m ()) -> (ReaderT SqlBackend m () -> ReaderT SqlBackend m ()) -> ReaderT SqlBackend m () -> ReaderT SqlBackend m () forall b c a. (b -> c) -> (a -> b) -> a -> c . ReaderT SqlBackend m (Either (Entity SwapIntoLn) ()) -> ReaderT SqlBackend m () forall (f :: * -> *) a. Functor f => f a -> f () void (ReaderT SqlBackend m (Either (Entity SwapIntoLn) ()) -> ReaderT SqlBackend m ()) -> (ReaderT SqlBackend m () -> ReaderT SqlBackend m (Either (Entity SwapIntoLn) ())) -> ReaderT SqlBackend m () -> ReaderT SqlBackend m () forall b c a. (b -> c) -> (a -> b) -> a -> c . SwapIntoLnId -> (SwapStatus -> Bool) -> (SwapIntoLn -> ReaderT SqlBackend m ()) -> ReaderT SqlBackend m (Either (Entity SwapIntoLn) ()) forall (m :: * -> *) a. MonadIO m => SwapIntoLnId -> (SwapStatus -> Bool) -> (SwapIntoLn -> ReaderT SqlBackend m a) -> ReaderT SqlBackend m (Either (Entity SwapIntoLn) a) SwapIntoLn.withLockedRowSql SwapIntoLnId swapKey (SwapStatus -> SwapStatus -> Bool forall a. Eq a => a -> a -> Bool == SwapStatus SwapWaitingChan) ((SwapIntoLn -> ReaderT SqlBackend m ()) -> ReaderT SqlBackend m (Either (Entity SwapIntoLn) ())) -> (ReaderT SqlBackend m () -> SwapIntoLn -> ReaderT SqlBackend m ()) -> ReaderT SqlBackend m () -> ReaderT SqlBackend m (Either (Entity SwapIntoLn) ()) forall b c a. (b -> c) -> (a -> b) -> a -> c . ReaderT SqlBackend m () -> SwapIntoLn -> ReaderT SqlBackend m () forall a b. a -> b -> a const (ReaderT SqlBackend m () -> ReaderT SqlBackend m ()) -> ReaderT SqlBackend m () -> ReaderT SqlBackend m () forall a b. (a -> b) -> a -> b $ SwapIntoLnId -> ReaderT SqlBackend m () forall (m :: * -> *). MonadIO m => SwapIntoLnId -> ReaderT SqlBackend m () SwapIntoLn.updateSucceededWithoutInvoiceSql SwapIntoLnId swapKey upsertChannelSql :: ( MonadIO m ) => UTCTime -> Maybe LnChanStatus -> Lnd.Channel -> Maybe Lnd.SingleChanBackupBlob -> ReaderT Psql.SqlBackend m (Entity LnChan) upsertChannelSql :: forall (m :: * -> *). MonadIO m => UTCTime -> Maybe LnChanStatus -> Channel -> Maybe SingleChanBackupBlob -> ReaderT SqlBackend m (Entity LnChan) upsertChannelSql UTCTime ct Maybe LnChanStatus mSS Channel chan Maybe SingleChanBackupBlob mBak = ReaderT SqlBackend m (Entity LnChan) -> (Entity LnChan -> ReaderT SqlBackend m (Entity LnChan)) -> ReaderT SqlBackend m (Maybe (Entity LnChan)) -> ReaderT SqlBackend m (Entity LnChan) forall (m :: * -> *) b a. Monad m => m b -> (a -> m b) -> m (Maybe a) -> m b maybeM ([SqlExpr (Entity LnChan) -> SqlExpr Update] -> ReaderT SqlBackend m (Entity LnChan) upsert [SqlExpr (Entity LnChan) -> SqlExpr Update] forall a. Monoid a => a mempty) ([SqlExpr (Entity LnChan) -> SqlExpr Update] -> ReaderT SqlBackend m (Entity LnChan) upsert ([SqlExpr (Entity LnChan) -> SqlExpr Update] -> ReaderT SqlBackend m (Entity LnChan)) -> (Entity LnChan -> [SqlExpr (Entity LnChan) -> SqlExpr Update]) -> Entity LnChan -> ReaderT SqlBackend m (Entity LnChan) forall b c a. (b -> c) -> (a -> b) -> a -> c . Entity LnChan -> [SqlExpr (Entity LnChan) -> SqlExpr Update] getOtherUpdates) (ReaderT SqlBackend m (Maybe (Entity LnChan)) -> ReaderT SqlBackend m (Entity LnChan)) -> ReaderT SqlBackend m (Maybe (Entity LnChan)) -> ReaderT SqlBackend m (Entity LnChan) forall a b. (a -> b) -> a -> b $ Unique LnChan -> ReaderT SqlBackend m (Maybe (Entity LnChan)) forall (m :: * -> *) a. (MonadIO m, HasTable a, ToBackendKey SqlBackend a) => Unique a -> SqlPersistT m (Maybe (Entity a)) Util.lockByUnique Unique LnChan uniq where upsert :: [SqlExpr (Entity LnChan) -> SqlExpr Update] -> ReaderT SqlBackend m (Entity LnChan) upsert [SqlExpr (Entity LnChan) -> SqlExpr Update] otherUpdates = do Entity LnChan chanEnt <- Unique LnChan -> LnChan -> [SqlExpr (Entity LnChan) -> SqlExpr Update] -> ReaderT SqlBackend m (Entity LnChan) 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 Unique LnChan uniq LnChan :: Maybe SwapIntoLnId -> TxId 'Funding -> Vout 'Funding -> Maybe (TxId 'Closing) -> Maybe ChanId -> Maybe SingleChanBackupBlob -> MSat -> MSat -> LnChanStatus -> UTCTime -> UTCTime -> UTCTime -> LnChan LnChan { lnChanSwapIntoLnId :: Maybe SwapIntoLnId lnChanSwapIntoLnId = Maybe SwapIntoLnId forall a. Maybe a Nothing, lnChanFundingTxId :: TxId 'Funding lnChanFundingTxId = TxId 'Funding txid, lnChanFundingVout :: Vout 'Funding lnChanFundingVout = Vout 'Funding vout, lnChanClosingTxId :: Maybe (TxId 'Closing) lnChanClosingTxId = Maybe (TxId 'Closing) forall a. Maybe a Nothing, lnChanExtId :: Maybe ChanId lnChanExtId = Maybe ChanId extId, lnChanBak :: Maybe SingleChanBackupBlob lnChanBak = Maybe SingleChanBackupBlob mBak, lnChanStatus :: LnChanStatus lnChanStatus = LnChanStatus ss, lnChanInsertedAt :: UTCTime lnChanInsertedAt = UTCTime ct, lnChanUpdatedAt :: UTCTime lnChanUpdatedAt = UTCTime ct, lnChanTransactedAt :: UTCTime lnChanTransactedAt = UTCTime ct, lnChanTotalSatoshisReceived :: MSat lnChanTotalSatoshisReceived = MSat rcv, lnChanTotalSatoshisSent :: MSat lnChanTotalSatoshisSent = MSat sent } ([SqlExpr (Entity LnChan) -> SqlExpr Update] -> ReaderT SqlBackend m (Entity LnChan)) -> [SqlExpr (Entity LnChan) -> SqlExpr Update] -> ReaderT SqlBackend m (Entity LnChan) forall a b. (a -> b) -> a -> b $ [ EntityField LnChan (Maybe ChanId) forall typ. (typ ~ Maybe ChanId) => EntityField LnChan typ LnChanExtId EntityField LnChan (Maybe ChanId) -> SqlExpr (Value (Maybe ChanId)) -> SqlExpr (Entity LnChan) -> SqlExpr Update forall val typ. (PersistEntity val, PersistField typ) => EntityField val typ -> SqlExpr (Value typ) -> SqlExpr (Entity val) -> SqlExpr Update Psql.=. Maybe ChanId -> SqlExpr (Value (Maybe ChanId)) forall typ. PersistField typ => typ -> SqlExpr (Value typ) Psql.val Maybe ChanId extId, EntityField LnChan LnChanStatus forall typ. (typ ~ LnChanStatus) => EntityField LnChan typ LnChanStatus EntityField LnChan LnChanStatus -> SqlExpr (Value LnChanStatus) -> SqlExpr (Entity LnChan) -> SqlExpr Update forall val typ. (PersistEntity val, PersistField typ) => EntityField val typ -> SqlExpr (Value typ) -> SqlExpr (Entity val) -> SqlExpr Update Psql.=. LnChanStatus -> SqlExpr (Value LnChanStatus) forall typ. PersistField typ => typ -> SqlExpr (Value typ) Psql.val LnChanStatus ss, EntityField LnChan UTCTime forall typ. (typ ~ UTCTime) => EntityField LnChan typ LnChanUpdatedAt EntityField LnChan UTCTime -> SqlExpr (Value UTCTime) -> SqlExpr (Entity LnChan) -> 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 (Entity LnChan) -> SqlExpr Update] -> [SqlExpr (Entity LnChan) -> SqlExpr Update] -> [SqlExpr (Entity LnChan) -> SqlExpr Update] forall a. Semigroup a => a -> a -> a <> [SqlExpr (Entity LnChan) -> SqlExpr Update] -> (SingleChanBackupBlob -> [SqlExpr (Entity LnChan) -> SqlExpr Update]) -> Maybe SingleChanBackupBlob -> [SqlExpr (Entity LnChan) -> SqlExpr Update] forall b a. b -> (a -> b) -> Maybe a -> b maybe [SqlExpr (Entity LnChan) -> SqlExpr Update] forall a. Monoid a => a mempty (\SingleChanBackupBlob x -> [EntityField LnChan (Maybe SingleChanBackupBlob) forall typ. (typ ~ Maybe SingleChanBackupBlob) => EntityField LnChan typ LnChanBak EntityField LnChan (Maybe SingleChanBackupBlob) -> SqlExpr (Value (Maybe SingleChanBackupBlob)) -> SqlExpr (Entity LnChan) -> SqlExpr Update forall val typ. (PersistEntity val, PersistField typ) => EntityField val typ -> SqlExpr (Value typ) -> SqlExpr (Entity val) -> SqlExpr Update Psql.=. Maybe SingleChanBackupBlob -> SqlExpr (Value (Maybe SingleChanBackupBlob)) forall typ. PersistField typ => typ -> SqlExpr (Value typ) Psql.val (SingleChanBackupBlob -> Maybe SingleChanBackupBlob forall a. a -> Maybe a Just SingleChanBackupBlob x)]) Maybe SingleChanBackupBlob mBak [SqlExpr (Entity LnChan) -> SqlExpr Update] -> [SqlExpr (Entity LnChan) -> SqlExpr Update] -> [SqlExpr (Entity LnChan) -> SqlExpr Update] forall a. Semigroup a => a -> a -> a <> [SqlExpr (Entity LnChan) -> SqlExpr Update] otherUpdates Entity LnChan -> ReaderT SqlBackend m () forall (m :: * -> *). MonadIO m => Entity LnChan -> ReaderT SqlBackend m () lazyUpdateSwapStatus Entity LnChan chanEnt Entity LnChan -> ReaderT SqlBackend m (Entity LnChan) forall (f :: * -> *) a. Applicative f => a -> f a pure Entity LnChan chanEnt getOtherUpdates :: Entity LnChan -> [SqlExpr (Entity LnChan) -> SqlExpr Update] getOtherUpdates (Entity Key LnChan _ LnChan x) = if LnChan -> MSat lnChanTotalSatoshisSent LnChan x MSat -> MSat -> Bool forall a. Eq a => a -> a -> Bool == MSat sent Bool -> Bool -> Bool && LnChan -> MSat lnChanTotalSatoshisReceived LnChan x MSat -> MSat -> Bool forall a. Eq a => a -> a -> Bool == MSat rcv then [SqlExpr (Entity LnChan) -> SqlExpr Update] forall a. Monoid a => a mempty else [ EntityField LnChan MSat forall typ. (typ ~ MSat) => EntityField LnChan typ LnChanTotalSatoshisSent EntityField LnChan MSat -> SqlExpr (Value MSat) -> SqlExpr (Entity LnChan) -> SqlExpr Update forall val typ. (PersistEntity val, PersistField typ) => EntityField val typ -> SqlExpr (Value typ) -> SqlExpr (Entity val) -> SqlExpr Update Psql.=. MSat -> SqlExpr (Value MSat) forall typ. PersistField typ => typ -> SqlExpr (Value typ) Psql.val MSat sent, EntityField LnChan MSat forall typ. (typ ~ MSat) => EntityField LnChan typ LnChanTotalSatoshisReceived EntityField LnChan MSat -> SqlExpr (Value MSat) -> SqlExpr (Entity LnChan) -> SqlExpr Update forall val typ. (PersistEntity val, PersistField typ) => EntityField val typ -> SqlExpr (Value typ) -> SqlExpr (Entity val) -> SqlExpr Update Psql.=. MSat -> SqlExpr (Value MSat) forall typ. PersistField typ => typ -> SqlExpr (Value typ) Psql.val MSat rcv, EntityField LnChan UTCTime forall typ. (typ ~ UTCTime) => EntityField LnChan typ LnChanTransactedAt EntityField LnChan UTCTime -> SqlExpr (Value UTCTime) -> SqlExpr (Entity LnChan) -> 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 ] ss :: LnChanStatus ss = LnChanStatus -> Maybe LnChanStatus -> LnChanStatus forall a. a -> Maybe a -> a fromMaybe ( if Channel -> Bool Channel.active Channel chan then LnChanStatus LnChanStatusActive else LnChanStatus LnChanStatusInactive ) Maybe LnChanStatus mSS cp :: ChannelPoint cp = Channel -> ChannelPoint Channel.channelPoint Channel chan txid :: TxId 'Funding txid = ChannelPoint -> TxId 'Funding ChannelPoint.fundingTxId ChannelPoint cp vout :: Vout 'Funding vout = ChannelPoint -> Vout 'Funding ChannelPoint.outputIndex ChannelPoint cp sent :: MSat sent = Channel -> MSat Channel.totalSatoshisSent Channel chan rcv :: MSat rcv = Channel -> MSat Channel.totalSatoshisReceived Channel chan extId :: Maybe ChanId extId = ChanId -> Maybe ChanId forall a. a -> Maybe a Just (ChanId -> Maybe ChanId) -> ChanId -> Maybe ChanId forall a b. (a -> b) -> a -> b $ Channel -> ChanId Channel.chanId Channel chan uniq :: Unique LnChan uniq = TxId 'Funding -> Vout 'Funding -> Unique LnChan UniqueLnChan TxId 'Funding txid Vout 'Funding vout upsertChannelPointSql :: ( MonadIO m ) => UTCTime -> LnChanStatus -> Lnd.ChannelPoint -> ReaderT Psql.SqlBackend m (Entity LnChan) upsertChannelPointSql :: forall (m :: * -> *). MonadIO m => UTCTime -> LnChanStatus -> ChannelPoint -> ReaderT SqlBackend m (Entity LnChan) upsertChannelPointSql UTCTime ct LnChanStatus ss (Lnd.ChannelPoint TxId 'Funding txid Vout 'Funding vout) = ReaderT SqlBackend m (Entity LnChan) -> (Entity LnChan -> ReaderT SqlBackend m (Entity LnChan)) -> ReaderT SqlBackend m (Maybe (Entity LnChan)) -> ReaderT SqlBackend m (Entity LnChan) forall (m :: * -> *) b a. Monad m => m b -> (a -> m b) -> m (Maybe a) -> m b maybeM ReaderT SqlBackend m (Entity LnChan) upsert (ReaderT SqlBackend m (Entity LnChan) -> Entity LnChan -> ReaderT SqlBackend m (Entity LnChan) forall a b. a -> b -> a const ReaderT SqlBackend m (Entity LnChan) upsert) (ReaderT SqlBackend m (Maybe (Entity LnChan)) -> ReaderT SqlBackend m (Entity LnChan)) -> ReaderT SqlBackend m (Maybe (Entity LnChan)) -> ReaderT SqlBackend m (Entity LnChan) forall a b. (a -> b) -> a -> b $ Unique LnChan -> ReaderT SqlBackend m (Maybe (Entity LnChan)) forall (m :: * -> *) a. (MonadIO m, HasTable a, ToBackendKey SqlBackend a) => Unique a -> SqlPersistT m (Maybe (Entity a)) Util.lockByUnique Unique LnChan uniq where uniq :: Unique LnChan uniq = TxId 'Funding -> Vout 'Funding -> Unique LnChan UniqueLnChan TxId 'Funding txid Vout 'Funding vout upsert :: ReaderT SqlBackend m (Entity LnChan) upsert = do Entity LnChan chanEnt <- Unique LnChan -> LnChan -> [SqlExpr (Entity LnChan) -> SqlExpr Update] -> ReaderT SqlBackend m (Entity LnChan) 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 Unique LnChan uniq LnChan :: Maybe SwapIntoLnId -> TxId 'Funding -> Vout 'Funding -> Maybe (TxId 'Closing) -> Maybe ChanId -> Maybe SingleChanBackupBlob -> MSat -> MSat -> LnChanStatus -> UTCTime -> UTCTime -> UTCTime -> LnChan LnChan { lnChanSwapIntoLnId :: Maybe SwapIntoLnId lnChanSwapIntoLnId = Maybe SwapIntoLnId forall a. Maybe a Nothing, lnChanFundingTxId :: TxId 'Funding lnChanFundingTxId = TxId 'Funding txid, lnChanFundingVout :: Vout 'Funding lnChanFundingVout = Vout 'Funding vout, lnChanExtId :: Maybe ChanId lnChanExtId = Maybe ChanId forall a. Maybe a Nothing, lnChanBak :: Maybe SingleChanBackupBlob lnChanBak = Maybe SingleChanBackupBlob forall a. Maybe a Nothing, lnChanClosingTxId :: Maybe (TxId 'Closing) lnChanClosingTxId = Maybe (TxId 'Closing) forall a. Maybe a Nothing, lnChanStatus :: LnChanStatus lnChanStatus = LnChanStatus ss, lnChanInsertedAt :: UTCTime lnChanInsertedAt = UTCTime ct, lnChanUpdatedAt :: UTCTime lnChanUpdatedAt = UTCTime ct, lnChanTransactedAt :: UTCTime lnChanTransactedAt = UTCTime ct, lnChanTotalSatoshisReceived :: MSat lnChanTotalSatoshisReceived = Word64 -> MSat MSat Word64 0, lnChanTotalSatoshisSent :: MSat lnChanTotalSatoshisSent = Word64 -> MSat MSat Word64 0 } [ EntityField LnChan LnChanStatus forall typ. (typ ~ LnChanStatus) => EntityField LnChan typ LnChanStatus EntityField LnChan LnChanStatus -> SqlExpr (Value LnChanStatus) -> SqlExpr (Entity LnChan) -> SqlExpr Update forall val typ. (PersistEntity val, PersistField typ) => EntityField val typ -> SqlExpr (Value typ) -> SqlExpr (Entity val) -> SqlExpr Update Psql.=. LnChanStatus -> SqlExpr (Value LnChanStatus) forall typ. PersistField typ => typ -> SqlExpr (Value typ) Psql.val LnChanStatus ss, EntityField LnChan UTCTime forall typ. (typ ~ UTCTime) => EntityField LnChan typ LnChanUpdatedAt EntityField LnChan UTCTime -> SqlExpr (Value UTCTime) -> SqlExpr (Entity LnChan) -> 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 ] Entity LnChan -> ReaderT SqlBackend m () forall (m :: * -> *). MonadIO m => Entity LnChan -> ReaderT SqlBackend m () lazyUpdateSwapStatus Entity LnChan chanEnt Entity LnChan -> ReaderT SqlBackend m (Entity LnChan) forall (f :: * -> *) a. Applicative f => a -> f a pure Entity LnChan chanEnt closedChannelUpsert :: ( MonadIO m ) => UTCTime -> Lnd.ChannelCloseSummary -> ReaderT Psql.SqlBackend m (Entity LnChan) closedChannelUpsert :: forall (m :: * -> *). MonadIO m => UTCTime -> ChannelCloseSummary -> ReaderT SqlBackend m (Entity LnChan) closedChannelUpsert UTCTime ct ChannelCloseSummary close = ReaderT SqlBackend m (Entity LnChan) -> (Entity LnChan -> ReaderT SqlBackend m (Entity LnChan)) -> ReaderT SqlBackend m (Maybe (Entity LnChan)) -> ReaderT SqlBackend m (Entity LnChan) forall (m :: * -> *) b a. Monad m => m b -> (a -> m b) -> m (Maybe a) -> m b maybeM ReaderT SqlBackend m (Entity LnChan) upsert (ReaderT SqlBackend m (Entity LnChan) -> Entity LnChan -> ReaderT SqlBackend m (Entity LnChan) forall a b. a -> b -> a const ReaderT SqlBackend m (Entity LnChan) upsert) (ReaderT SqlBackend m (Maybe (Entity LnChan)) -> ReaderT SqlBackend m (Entity LnChan)) -> ReaderT SqlBackend m (Maybe (Entity LnChan)) -> ReaderT SqlBackend m (Entity LnChan) forall a b. (a -> b) -> a -> b $ Unique LnChan -> ReaderT SqlBackend m (Maybe (Entity LnChan)) forall (m :: * -> *) a. (MonadIO m, HasTable a, ToBackendKey SqlBackend a) => Unique a -> SqlPersistT m (Maybe (Entity a)) Util.lockByUnique Unique LnChan uniq where upsert :: ReaderT SqlBackend m (Entity LnChan) upsert = Unique LnChan -> LnChan -> [SqlExpr (Entity LnChan) -> SqlExpr Update] -> ReaderT SqlBackend m (Entity LnChan) 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 Unique LnChan uniq LnChan :: Maybe SwapIntoLnId -> TxId 'Funding -> Vout 'Funding -> Maybe (TxId 'Closing) -> Maybe ChanId -> Maybe SingleChanBackupBlob -> MSat -> MSat -> LnChanStatus -> UTCTime -> UTCTime -> UTCTime -> LnChan LnChan { lnChanSwapIntoLnId :: Maybe SwapIntoLnId lnChanSwapIntoLnId = Maybe SwapIntoLnId forall a. Maybe a Nothing, lnChanFundingTxId :: TxId 'Funding lnChanFundingTxId = TxId 'Funding fundTxId, lnChanFundingVout :: Vout 'Funding lnChanFundingVout = Vout 'Funding fundVout, lnChanClosingTxId :: Maybe (TxId 'Closing) lnChanClosingTxId = Maybe (TxId 'Closing) closeTxId, lnChanExtId :: Maybe ChanId lnChanExtId = Maybe ChanId extId, lnChanBak :: Maybe SingleChanBackupBlob lnChanBak = Maybe SingleChanBackupBlob forall a. Maybe a Nothing, lnChanStatus :: LnChanStatus lnChanStatus = LnChanStatus ss, lnChanInsertedAt :: UTCTime lnChanInsertedAt = UTCTime ct, lnChanUpdatedAt :: UTCTime lnChanUpdatedAt = UTCTime ct, lnChanTransactedAt :: UTCTime lnChanTransactedAt = UTCTime ct, lnChanTotalSatoshisReceived :: MSat lnChanTotalSatoshisReceived = Word64 -> MSat MSat Word64 0, lnChanTotalSatoshisSent :: MSat lnChanTotalSatoshisSent = Word64 -> MSat MSat Word64 0 } [ EntityField LnChan (Maybe ChanId) forall typ. (typ ~ Maybe ChanId) => EntityField LnChan typ LnChanExtId EntityField LnChan (Maybe ChanId) -> SqlExpr (Value (Maybe ChanId)) -> SqlExpr (Entity LnChan) -> SqlExpr Update forall val typ. (PersistEntity val, PersistField typ) => EntityField val typ -> SqlExpr (Value typ) -> SqlExpr (Entity val) -> SqlExpr Update Psql.=. Maybe ChanId -> SqlExpr (Value (Maybe ChanId)) forall typ. PersistField typ => typ -> SqlExpr (Value typ) Psql.val Maybe ChanId extId, EntityField LnChan (Maybe (TxId 'Closing)) forall typ. (typ ~ Maybe (TxId 'Closing)) => EntityField LnChan typ LnChanClosingTxId EntityField LnChan (Maybe (TxId 'Closing)) -> SqlExpr (Value (Maybe (TxId 'Closing))) -> SqlExpr (Entity LnChan) -> SqlExpr Update forall val typ. (PersistEntity val, PersistField typ) => EntityField val typ -> SqlExpr (Value typ) -> SqlExpr (Entity val) -> SqlExpr Update Psql.=. Maybe (TxId 'Closing) -> SqlExpr (Value (Maybe (TxId 'Closing))) forall typ. PersistField typ => typ -> SqlExpr (Value typ) Psql.val Maybe (TxId 'Closing) closeTxId, EntityField LnChan LnChanStatus forall typ. (typ ~ LnChanStatus) => EntityField LnChan typ LnChanStatus EntityField LnChan LnChanStatus -> SqlExpr (Value LnChanStatus) -> SqlExpr (Entity LnChan) -> SqlExpr Update forall val typ. (PersistEntity val, PersistField typ) => EntityField val typ -> SqlExpr (Value typ) -> SqlExpr (Entity val) -> SqlExpr Update Psql.=. LnChanStatus -> SqlExpr (Value LnChanStatus) forall typ. PersistField typ => typ -> SqlExpr (Value typ) Psql.val LnChanStatus ss, EntityField LnChan UTCTime forall typ. (typ ~ UTCTime) => EntityField LnChan typ LnChanUpdatedAt EntityField LnChan UTCTime -> SqlExpr (Value UTCTime) -> SqlExpr (Entity LnChan) -> 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 ] ss :: LnChanStatus ss = LnChanStatus LnChanStatusClosed cp :: ChannelPoint cp = ChannelCloseSummary -> ChannelPoint CloseChannel.chPoint ChannelCloseSummary close fundTxId :: TxId 'Funding fundTxId = ChannelPoint -> TxId 'Funding ChannelPoint.fundingTxId ChannelPoint cp fundVout :: Vout 'Funding fundVout = ChannelPoint -> Vout 'Funding ChannelPoint.outputIndex ChannelPoint cp closeTxId :: Maybe (TxId 'Closing) closeTxId = TxId 'Closing -> Maybe (TxId 'Closing) forall a. a -> Maybe a Just (TxId 'Closing -> Maybe (TxId 'Closing)) -> TxId 'Closing -> Maybe (TxId 'Closing) forall a b. (a -> b) -> a -> b $ ChannelCloseSummary -> TxId 'Closing CloseChannel.closingTxId ChannelCloseSummary close extId :: Maybe ChanId extId = ChanId -> Maybe ChanId forall a. a -> Maybe a Just (ChanId -> Maybe ChanId) -> ChanId -> Maybe ChanId forall a b. (a -> b) -> a -> b $ ChannelCloseSummary -> ChanId CloseChannel.chanId ChannelCloseSummary close uniq :: Unique LnChan uniq = TxId 'Funding -> Vout 'Funding -> Unique LnChan UniqueLnChan TxId 'Funding fundTxId Vout 'Funding fundVout persistChannelUpdateSql :: ( KatipContext m ) => Lnd.ChannelEventUpdate -> ReaderT Psql.SqlBackend m (Entity LnChan) persistChannelUpdateSql :: forall (m :: * -> *). KatipContext m => ChannelEventUpdate -> ReaderT SqlBackend m (Entity LnChan) persistChannelUpdateSql (Lnd.ChannelEventUpdate UpdateChannel channelEvent UpdateType _) = do $(logTM) Severity DebugS (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 $ UpdateChannel -> Text forall a. Out a => a -> Text inspect UpdateChannel channelEvent UTCTime ct <- ReaderT SqlBackend m UTCTime forall (m :: * -> *). MonadIO m => m UTCTime getCurrentTime case UpdateChannel channelEvent of Lnd.ChannelEventUpdateChannelOpenChannel Channel chan -> UTCTime -> Maybe LnChanStatus -> Channel -> Maybe SingleChanBackupBlob -> ReaderT SqlBackend m (Entity LnChan) forall (m :: * -> *). MonadIO m => UTCTime -> Maybe LnChanStatus -> Channel -> Maybe SingleChanBackupBlob -> ReaderT SqlBackend m (Entity LnChan) upsertChannelSql UTCTime ct (LnChanStatus -> Maybe LnChanStatus forall a. a -> Maybe a Just LnChanStatus LnChanStatusOpened) Channel chan Maybe SingleChanBackupBlob forall a. Maybe a Nothing Lnd.ChannelEventUpdateChannelActiveChannel ChannelPoint cp -> UTCTime -> LnChanStatus -> ChannelPoint -> ReaderT SqlBackend m (Entity LnChan) forall (m :: * -> *). MonadIO m => UTCTime -> LnChanStatus -> ChannelPoint -> ReaderT SqlBackend m (Entity LnChan) upsertChannelPointSql UTCTime ct LnChanStatus LnChanStatusActive ChannelPoint cp Lnd.ChannelEventUpdateChannelInactiveChannel ChannelPoint cp -> UTCTime -> LnChanStatus -> ChannelPoint -> ReaderT SqlBackend m (Entity LnChan) forall (m :: * -> *). MonadIO m => UTCTime -> LnChanStatus -> ChannelPoint -> ReaderT SqlBackend m (Entity LnChan) upsertChannelPointSql UTCTime ct LnChanStatus LnChanStatusInactive ChannelPoint cp Lnd.ChannelEventUpdateChannelClosedChannel ChannelCloseSummary close -> UTCTime -> ChannelCloseSummary -> ReaderT SqlBackend m (Entity LnChan) forall (m :: * -> *). MonadIO m => UTCTime -> ChannelCloseSummary -> ReaderT SqlBackend m (Entity LnChan) closedChannelUpsert UTCTime ct ChannelCloseSummary close Lnd.ChannelEventUpdateChannelFullyResolved ChannelPoint cp -> UTCTime -> LnChanStatus -> ChannelPoint -> ReaderT SqlBackend m (Entity LnChan) forall (m :: * -> *). MonadIO m => UTCTime -> LnChanStatus -> ChannelPoint -> ReaderT SqlBackend m (Entity LnChan) upsertChannelPointSql UTCTime ct LnChanStatus LnChanStatusFullyResolved ChannelPoint cp Lnd.ChannelEventUpdateChannelPendingOpenChannel (Lnd.PendingUpdate TxId 'Funding txid Vout 'Funding vout) -> UTCTime -> LnChanStatus -> ChannelPoint -> ReaderT SqlBackend m (Entity LnChan) forall (m :: * -> *). MonadIO m => UTCTime -> LnChanStatus -> ChannelPoint -> ReaderT SqlBackend m (Entity LnChan) upsertChannelPointSql UTCTime ct LnChanStatus LnChanStatusPendingOpen (ChannelPoint -> ReaderT SqlBackend m (Entity LnChan)) -> ChannelPoint -> ReaderT SqlBackend m (Entity LnChan) forall a b. (a -> b) -> a -> b $ TxId 'Funding -> Vout 'Funding -> ChannelPoint Lnd.ChannelPoint TxId 'Funding txid Vout 'Funding vout persistOpenedChannelsSql :: ( MonadIO m ) => [(Lnd.Channel, Maybe Lnd.SingleChanBackupBlob)] -> ReaderT Psql.SqlBackend m [Entity LnChan] persistOpenedChannelsSql :: forall (m :: * -> *). MonadIO m => [(Channel, Maybe SingleChanBackupBlob)] -> ReaderT SqlBackend m [Entity LnChan] persistOpenedChannelsSql [(Channel, Maybe SingleChanBackupBlob)] cs = do UTCTime ct <- ReaderT SqlBackend m UTCTime forall (m :: * -> *). MonadIO m => m UTCTime getCurrentTime [(Channel, Maybe SingleChanBackupBlob)] -> ((Channel, Maybe SingleChanBackupBlob) -> ReaderT SqlBackend m (Entity LnChan)) -> ReaderT SqlBackend m [Entity LnChan] forall (t :: * -> *) (m :: * -> *) a b. (Traversable t, Monad m) => t a -> (a -> m b) -> m (t b) forM (((Channel, Maybe SingleChanBackupBlob) -> ChannelPoint) -> [(Channel, Maybe SingleChanBackupBlob)] -> [(Channel, Maybe SingleChanBackupBlob)] forall b a. Ord b => (a -> b) -> [a] -> [a] sortOn (Channel -> ChannelPoint Channel.channelPoint (Channel -> ChannelPoint) -> ((Channel, Maybe SingleChanBackupBlob) -> Channel) -> (Channel, Maybe SingleChanBackupBlob) -> ChannelPoint forall b c a. (b -> c) -> (a -> b) -> a -> c . (Channel, Maybe SingleChanBackupBlob) -> Channel forall a b. (a, b) -> a fst) [(Channel, Maybe SingleChanBackupBlob)] cs) (((Channel, Maybe SingleChanBackupBlob) -> ReaderT SqlBackend m (Entity LnChan)) -> ReaderT SqlBackend m [Entity LnChan]) -> ((Channel, Maybe SingleChanBackupBlob) -> ReaderT SqlBackend m (Entity LnChan)) -> ReaderT SqlBackend m [Entity LnChan] forall a b. (a -> b) -> a -> b $ (Channel -> Maybe SingleChanBackupBlob -> ReaderT SqlBackend m (Entity LnChan)) -> (Channel, Maybe SingleChanBackupBlob) -> ReaderT SqlBackend m (Entity LnChan) forall a b c. (a -> b -> c) -> (a, b) -> c uncurry (UTCTime -> Maybe LnChanStatus -> Channel -> Maybe SingleChanBackupBlob -> ReaderT SqlBackend m (Entity LnChan) forall (m :: * -> *). MonadIO m => UTCTime -> Maybe LnChanStatus -> Channel -> Maybe SingleChanBackupBlob -> ReaderT SqlBackend m (Entity LnChan) upsertChannelSql UTCTime ct Maybe LnChanStatus forall a. Maybe a Nothing) getNonClosedSql :: ( MonadIO m ) => ReaderT Psql.SqlBackend m [Entity LnChan] getNonClosedSql :: forall (m :: * -> *). MonadIO m => ReaderT SqlBackend m [Entity LnChan] getNonClosedSql = SqlQuery (SqlExpr (Entity LnChan)) -> ReaderT SqlBackend m [Entity LnChan] forall a r (m :: * -> *). (SqlSelect a r, MonadIO m) => SqlQuery a -> SqlReadT m [r] Psql.select (SqlQuery (SqlExpr (Entity LnChan)) -> ReaderT SqlBackend m [Entity LnChan]) -> SqlQuery (SqlExpr (Entity LnChan)) -> ReaderT SqlBackend m [Entity LnChan] forall a b. (a -> b) -> a -> b $ (SqlExpr (Entity LnChan) -> SqlQuery (SqlExpr (Entity LnChan))) -> SqlQuery (SqlExpr (Entity LnChan)) forall a b. From a => (a -> SqlQuery b) -> SqlQuery b Psql.from ((SqlExpr (Entity LnChan) -> SqlQuery (SqlExpr (Entity LnChan))) -> SqlQuery (SqlExpr (Entity LnChan))) -> (SqlExpr (Entity LnChan) -> SqlQuery (SqlExpr (Entity LnChan))) -> SqlQuery (SqlExpr (Entity LnChan)) forall a b. (a -> b) -> a -> b $ \SqlExpr (Entity LnChan) row -> do SqlExpr (Value Bool) -> SqlQuery () Psql.where_ ( SqlExpr (Entity LnChan) row SqlExpr (Entity LnChan) -> EntityField LnChan LnChanStatus -> SqlExpr (Value LnChanStatus) forall typ val. (PersistEntity val, PersistField typ) => SqlExpr (Entity val) -> EntityField val typ -> SqlExpr (Value typ) Psql.^. EntityField LnChan LnChanStatus forall typ. (typ ~ LnChanStatus) => EntityField LnChan typ LnChanStatus SqlExpr (Value LnChanStatus) -> SqlExpr (Value LnChanStatus) -> SqlExpr (Value Bool) forall typ. PersistField typ => SqlExpr (Value typ) -> SqlExpr (Value typ) -> SqlExpr (Value Bool) Psql.!=. LnChanStatus -> SqlExpr (Value LnChanStatus) forall typ. PersistField typ => typ -> SqlExpr (Value typ) Psql.val LnChanStatus LnChanStatusClosed ) SqlExpr (Entity LnChan) -> SqlQuery (SqlExpr (Entity LnChan)) forall (f :: * -> *) a. Applicative f => a -> f a pure SqlExpr (Entity LnChan) row persistClosedChannelsSql :: ( MonadIO m ) => [Lnd.ChannelCloseSummary] -> ReaderT Psql.SqlBackend m [Entity LnChan] persistClosedChannelsSql :: forall (m :: * -> *). MonadIO m => [ChannelCloseSummary] -> ReaderT SqlBackend m [Entity LnChan] persistClosedChannelsSql [] = [Entity LnChan] -> ReaderT SqlBackend m [Entity LnChan] forall (f :: * -> *) a. Applicative f => a -> f a pure [Entity LnChan] forall a. Monoid a => a mempty persistClosedChannelsSql [ChannelCloseSummary] csRaw = do UTCTime ct <- ReaderT SqlBackend m UTCTime forall (m :: * -> *). MonadIO m => m UTCTime getCurrentTime [Entity LnChan] nonClosedList <- ReaderT SqlBackend m [Entity LnChan] forall (m :: * -> *). MonadIO m => ReaderT SqlBackend m [Entity LnChan] getNonClosedSql let nonClosedSet :: Set ChannelPoint nonClosedSet = [ListElement (Set ChannelPoint)] -> Set ChannelPoint forall l. (FromList l, FromListC l) => [ListElement l] -> l fromList ([ListElement (Set ChannelPoint)] -> Set ChannelPoint) -> [ListElement (Set ChannelPoint)] -> Set ChannelPoint forall a b. (a -> b) -> a -> b $ ( \(Entity {entityVal :: forall record. Entity record -> record entityVal = LnChan x}) -> TxId 'Funding -> Vout 'Funding -> ChannelPoint Lnd.ChannelPoint (LnChan -> TxId 'Funding lnChanFundingTxId LnChan x) (LnChan -> Vout 'Funding lnChanFundingVout LnChan x) ) (Entity LnChan -> ChannelPoint) -> [Entity LnChan] -> [ChannelPoint] forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> [Entity LnChan] nonClosedList let csUpd :: [ChannelCloseSummary] csUpd = (ChannelCloseSummary -> ChannelPoint) -> [ChannelCloseSummary] -> [ChannelCloseSummary] forall b a. Ord b => (a -> b) -> [a] -> [a] sortOn ChannelCloseSummary -> ChannelPoint CloseChannel.chPoint ([ChannelCloseSummary] -> [ChannelCloseSummary]) -> [ChannelCloseSummary] -> [ChannelCloseSummary] forall a b. (a -> b) -> a -> b $ (ChannelCloseSummary -> Bool) -> [ChannelCloseSummary] -> [ChannelCloseSummary] forall a. (a -> Bool) -> [a] -> [a] filter ( (ChannelPoint -> Set ChannelPoint -> Bool forall a. Ord a => a -> Set a -> Bool `Set.member` Set ChannelPoint nonClosedSet) (ChannelPoint -> Bool) -> (ChannelCloseSummary -> ChannelPoint) -> ChannelCloseSummary -> Bool forall b c a. (b -> c) -> (a -> b) -> a -> c . ChannelCloseSummary -> ChannelPoint CloseChannel.chPoint ) [ChannelCloseSummary] csRaw [ChannelCloseSummary] -> (ChannelCloseSummary -> ReaderT SqlBackend m (Entity LnChan)) -> ReaderT SqlBackend m [Entity LnChan] forall (t :: * -> *) (m :: * -> *) a b. (Traversable t, Monad m) => t a -> (a -> m b) -> m (t b) forM [ChannelCloseSummary] csUpd ((ChannelCloseSummary -> ReaderT SqlBackend m (Entity LnChan)) -> ReaderT SqlBackend m [Entity LnChan]) -> (ChannelCloseSummary -> ReaderT SqlBackend m (Entity LnChan)) -> ReaderT SqlBackend m [Entity LnChan] forall a b. (a -> b) -> a -> b $ UTCTime -> ChannelCloseSummary -> ReaderT SqlBackend m (Entity LnChan) forall (m :: * -> *). MonadIO m => UTCTime -> ChannelCloseSummary -> ReaderT SqlBackend m (Entity LnChan) closedChannelUpsert UTCTime ct