{-# LANGUAGE RecordWildCards #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TypeApplications #-} module BtcLsp.Yesod.Handler.SwapIntoLnSelect ( getSwapIntoLnSelectR, ) where import BtcLsp.Data.Type import qualified BtcLsp.Math.Swap as Math import BtcLsp.Storage.Model import qualified BtcLsp.Storage.Model.SwapIntoLn as SwapIntoLn import BtcLsp.Yesod.Data.Widget import qualified BtcLsp.Yesod.Handler.SwapUpdates as SU import BtcLsp.Yesod.Import import qualified Data.UUID as UUID getSwapIntoLnSelectR :: Uuid 'SwapIntoLnTable -> Handler Html getSwapIntoLnSelectR :: Uuid 'SwapIntoLnTable -> Handler Html getSwapIntoLnSelectR Uuid 'SwapIntoLnTable uuid = do app :: App app@App {appMRunner :: () appMRunner = UnliftIO forall a. m a -> IO a run} <- HandlerFor App App forall (m :: * -> *). MonadHandler m => m (HandlerSite m) getYesod NodeUri nodeUri <- IO NodeUri -> HandlerFor App NodeUri forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO NodeUri -> HandlerFor App NodeUri) -> IO NodeUri -> HandlerFor App NodeUri forall a b. (a -> b) -> a -> b $ m NodeUri -> IO NodeUri forall a. m a -> IO a run m NodeUri forall (m :: * -> *). Env m => m NodeUri getLndNodeUri Text nodeUriHex <- (TryFromException NodeUri NodeUriHex -> HandlerFor App Text) -> (NodeUriHex -> HandlerFor App Text) -> HandlerFor App (Either (TryFromException NodeUri NodeUriHex) NodeUriHex) -> HandlerFor App Text forall (m :: * -> *) a c b. Monad m => (a -> m c) -> (b -> m c) -> m (Either a b) -> m c eitherM (HandlerFor App Text -> TryFromException NodeUri NodeUriHex -> HandlerFor App Text forall a b. a -> b -> a const HandlerFor App Text forall (m :: * -> *) a. MonadHandler m => m a badMethod) (Text -> HandlerFor App Text forall (f :: * -> *) a. Applicative f => a -> f a pure (Text -> HandlerFor App Text) -> (NodeUriHex -> Text) -> NodeUriHex -> HandlerFor App Text forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k). Category cat => cat b c -> cat a b -> cat a c . forall source target. (From source target, 'False ~ (source == target)) => source -> target from @NodeUriHex @Text) (HandlerFor App (Either (TryFromException NodeUri NodeUriHex) NodeUriHex) -> HandlerFor App Text) -> (Either (TryFromException NodeUri NodeUriHex) NodeUriHex -> HandlerFor App (Either (TryFromException NodeUri NodeUriHex) NodeUriHex)) -> Either (TryFromException NodeUri NodeUriHex) NodeUriHex -> HandlerFor App Text forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k). Category cat => cat b c -> cat a b -> cat a c . Either (TryFromException NodeUri NodeUriHex) NodeUriHex -> HandlerFor App (Either (TryFromException NodeUri NodeUriHex) NodeUriHex) forall (f :: * -> *) a. Applicative f => a -> f a pure (Either (TryFromException NodeUri NodeUriHex) NodeUriHex -> HandlerFor App Text) -> Either (TryFromException NodeUri NodeUriHex) NodeUriHex -> HandlerFor App Text forall a b. (a -> b) -> a -> b $ NodeUri -> Either (TryFromException NodeUri NodeUriHex) NodeUriHex forall source target. (TryFrom source target, 'False ~ (source == target)) => source -> Either (TryFromException source target) target tryFrom NodeUri nodeUri Text nodeUriQr <- HandlerFor App Text -> (Text -> HandlerFor App Text) -> HandlerFor App (Maybe Text) -> HandlerFor App Text forall (m :: * -> *) b a. Monad m => m b -> (a -> m b) -> m (Maybe a) -> m b maybeM HandlerFor App Text forall (m :: * -> *) a. MonadHandler m => m a badMethod Text -> HandlerFor App Text forall (f :: * -> *) a. Applicative f => a -> f a pure (HandlerFor App (Maybe Text) -> HandlerFor App Text) -> (Maybe Text -> HandlerFor App (Maybe Text)) -> Maybe Text -> HandlerFor App Text forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k). Category cat => cat b c -> cat a b -> cat a c . Maybe Text -> HandlerFor App (Maybe Text) forall (f :: * -> *) a. Applicative f => a -> f a pure (Maybe Text -> HandlerFor App Text) -> Maybe Text -> HandlerFor App Text forall a b. (a -> b) -> a -> b $ Text -> Maybe Text toQr Text nodeUriHex SwapHash swapHash <- HandlerFor App SwapHash -> (SwapHash -> HandlerFor App SwapHash) -> HandlerFor App (Maybe SwapHash) -> HandlerFor App SwapHash forall (m :: * -> *) b a. Monad m => m b -> (a -> m b) -> m (Maybe a) -> m b maybeM HandlerFor App SwapHash forall (m :: * -> *) a. MonadHandler m => m a notFound SwapHash -> HandlerFor App SwapHash forall (f :: * -> *) a. Applicative f => a -> f a pure (App -> Uuid 'SwapIntoLnTable -> HandlerFor App (Maybe SwapHash) forall (m :: * -> *). MonadHandler m => App -> Uuid 'SwapIntoLnTable -> m (Maybe SwapHash) SU.getSwapUpdate App app Uuid 'SwapIntoLnTable uuid) Handler Html -> (SwapInfo -> Handler Html) -> HandlerFor App (Maybe SwapInfo) -> Handler Html forall (m :: * -> *) b a. Monad m => m b -> (a -> m b) -> m (Maybe a) -> m b maybeM Handler Html forall (m :: * -> *) a. MonadHandler m => m a notFound ( \swapInfo :: SwapInfo swapInfo@SwapIntoLn.SwapInfo {[Entity LnChan] [UtxoInfo] Entity SwapIntoLn Entity User swapInfoChan :: SwapInfo -> [Entity LnChan] swapInfoUtxo :: SwapInfo -> [UtxoInfo] swapInfoUser :: SwapInfo -> Entity User swapInfoSwap :: SwapInfo -> Entity SwapIntoLn swapInfoChan :: [Entity LnChan] swapInfoUtxo :: [UtxoInfo] swapInfoUser :: Entity User swapInfoSwap :: Entity SwapIntoLn ..} -> do Money 'Usr 'OnChain 'Fund minAmt <- IO (Money 'Usr 'OnChain 'Fund) -> HandlerFor App (Money 'Usr 'OnChain 'Fund) forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO (Money 'Usr 'OnChain 'Fund) -> HandlerFor App (Money 'Usr 'OnChain 'Fund)) -> IO (Money 'Usr 'OnChain 'Fund) -> HandlerFor App (Money 'Usr 'OnChain 'Fund) forall a b. (a -> b) -> a -> b $ m (Money 'Usr 'OnChain 'Fund) -> IO (Money 'Usr 'OnChain 'Fund) forall a. m a -> IO a run m (Money 'Usr 'OnChain 'Fund) forall (m :: * -> *). Env m => m (Money 'Usr 'OnChain 'Fund) getSwapIntoLnMinAmt let SwapIntoLn {UTCTime UserId Uuid 'SwapIntoLnTable Privacy SwapStatus Money 'Lsp 'OnChain 'Gain Money 'Lsp 'OnChain 'Loss Money 'Lsp 'Ln 'Fund Money 'Usr 'Ln 'Fund OnChainAddress 'Fund OnChainAddress 'Refund OnChainAddress 'Gain swapIntoLnUpdatedAt :: SwapIntoLn -> UTCTime swapIntoLnInsertedAt :: SwapIntoLn -> UTCTime swapIntoLnExpiresAt :: SwapIntoLn -> UTCTime swapIntoLnPrivacy :: SwapIntoLn -> Privacy swapIntoLnStatus :: SwapIntoLn -> SwapStatus swapIntoLnFeeMiner :: SwapIntoLn -> Money 'Lsp 'OnChain 'Loss swapIntoLnFeeLsp :: SwapIntoLn -> Money 'Lsp 'OnChain 'Gain swapIntoLnChanCapLsp :: SwapIntoLn -> Money 'Lsp 'Ln 'Fund swapIntoLnChanCapUser :: SwapIntoLn -> Money 'Usr 'Ln 'Fund swapIntoLnRefundAddress :: SwapIntoLn -> OnChainAddress 'Refund swapIntoLnLspFeeAndChangeAddress :: SwapIntoLn -> OnChainAddress 'Gain swapIntoLnFundAddress :: SwapIntoLn -> OnChainAddress 'Fund swapIntoLnUserId :: SwapIntoLn -> UserId swapIntoLnUuid :: SwapIntoLn -> Uuid 'SwapIntoLnTable swapIntoLnUpdatedAt :: UTCTime swapIntoLnInsertedAt :: UTCTime swapIntoLnExpiresAt :: UTCTime swapIntoLnPrivacy :: Privacy swapIntoLnStatus :: SwapStatus swapIntoLnFeeMiner :: Money 'Lsp 'OnChain 'Loss swapIntoLnFeeLsp :: Money 'Lsp 'OnChain 'Gain swapIntoLnChanCapLsp :: Money 'Lsp 'Ln 'Fund swapIntoLnChanCapUser :: Money 'Usr 'Ln 'Fund swapIntoLnRefundAddress :: OnChainAddress 'Refund swapIntoLnLspFeeAndChangeAddress :: OnChainAddress 'Gain swapIntoLnFundAddress :: OnChainAddress 'Fund swapIntoLnUserId :: UserId swapIntoLnUuid :: Uuid 'SwapIntoLnTable ..} = Entity SwapIntoLn -> SwapIntoLn forall record. Entity record -> record entityVal Entity SwapIntoLn swapInfoSwap let (AppMessage msgShort, AppMessage msgLong, BootstrapColor color) = case SwapStatus swapIntoLnStatus of SwapStatus SwapWaitingFundChain -> ( AppMessage MsgSwapIntoLnWaitingFundChainShort, Money 'Usr 'OnChain 'Fund -> Money 'Usr 'OnChain 'Fund -> AppMessage MsgSwapIntoLnWaitingFundChainLong Money 'Usr 'OnChain 'Fund minAmt Money 'Usr 'OnChain 'Fund forall (btcl :: BitcoinLayer). Money 'Usr btcl 'Fund Math.swapLnMaxAmt, BootstrapColor Info ) SwapStatus SwapWaitingPeer -> ( AppMessage MsgSwapIntoLnFundedShort, AppMessage MsgSwapIntoLnFundedLong, BootstrapColor Info ) SwapStatus SwapWaitingChan -> ( AppMessage MsgSwapIntoLnWaitingChanShort, AppMessage MsgSwapIntoLnWaitingChanLong, BootstrapColor Info ) SwapStatus SwapSucceeded -> ( AppMessage MsgSwapIntoLnSucceededShort, AppMessage MsgSwapIntoLnSucceededLong, BootstrapColor Success ) SwapStatus SwapExpired -> ( AppMessage MsgSwapIntoLnExpiredShort, AppMessage MsgSwapIntoLnExpiredLong, BootstrapColor Danger ) Text fundAddrQr <- HandlerFor App Text -> (Text -> HandlerFor App Text) -> HandlerFor App (Maybe Text) -> HandlerFor App Text forall (m :: * -> *) b a. Monad m => m b -> (a -> m b) -> m (Maybe a) -> m b maybeM HandlerFor App Text forall (m :: * -> *) a. MonadHandler m => m a badMethod Text -> HandlerFor App Text forall (f :: * -> *) a. Applicative f => a -> f a pure (HandlerFor App (Maybe Text) -> HandlerFor App Text) -> (Text -> HandlerFor App (Maybe Text)) -> Text -> HandlerFor App Text forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k). Category cat => cat b c -> cat a b -> cat a c . Maybe Text -> HandlerFor App (Maybe Text) forall (f :: * -> *) a. Applicative f => a -> f a pure (Maybe Text -> HandlerFor App (Maybe Text)) -> (Text -> Maybe Text) -> Text -> HandlerFor App (Maybe Text) forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k). Category cat => cat b c -> cat a b -> cat a c . Text -> Maybe Text toQr (Text -> HandlerFor App Text) -> Text -> HandlerFor App Text forall a b. (a -> b) -> a -> b $ OnChainAddress 'Fund -> Text forall source target. (From source target, 'False ~ (source == target)) => source -> target from OnChainAddress 'Fund swapIntoLnFundAddress let mSwapWidget :: Maybe Widget mSwapWidget = SwapInfo -> Maybe Widget newSwapWidget SwapInfo swapInfo let mUtxoWidget :: Maybe Widget mUtxoWidget = [UtxoInfo] -> Maybe Widget newUtxoWidget [UtxoInfo] swapInfoUtxo let mChanWidget :: Maybe Widget mChanWidget = [Entity LnChan] -> Maybe Widget newChanWidget [Entity LnChan] swapInfoChan BootstrapColor -> AppMessage -> AppMessage -> Widget -> Handler Html panelLayout BootstrapColor color AppMessage msgShort AppMessage msgLong (Widget -> Handler Html) -> Widget -> Handler Html forall a b. (a -> b) -> a -> b $ do AppMessage -> Widget forall (m :: * -> *) msg. (MonadWidget m, RenderMessage (HandlerSite m) msg) => msg -> m () setTitleI (AppMessage -> Widget) -> AppMessage -> Widget forall a b. (a -> b) -> a -> b $ Uuid 'SwapIntoLnTable -> AppMessage MsgSwapIntoLnSelectRTitle Uuid 'SwapIntoLnTable swapIntoLnUuid $(widgetFile "swap_updates") $(widgetFile "swap_into_ln_select") ) (HandlerFor App (Maybe SwapInfo) -> Handler Html) -> (ReaderT SqlBackend m (Maybe SwapInfo) -> HandlerFor App (Maybe SwapInfo)) -> ReaderT SqlBackend m (Maybe SwapInfo) -> Handler Html forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k). Category cat => cat b c -> cat a b -> cat a c . IO (Maybe SwapInfo) -> HandlerFor App (Maybe SwapInfo) forall (m :: * -> *) a. MonadIO m => IO a -> m a liftIO (IO (Maybe SwapInfo) -> HandlerFor App (Maybe SwapInfo)) -> (ReaderT SqlBackend m (Maybe SwapInfo) -> IO (Maybe SwapInfo)) -> ReaderT SqlBackend m (Maybe SwapInfo) -> HandlerFor App (Maybe SwapInfo) forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k). Category cat => cat b c -> cat a b -> cat a c . m (Maybe SwapInfo) -> IO (Maybe SwapInfo) forall a. m a -> IO a run (m (Maybe SwapInfo) -> IO (Maybe SwapInfo)) -> (ReaderT SqlBackend m (Maybe SwapInfo) -> m (Maybe SwapInfo)) -> ReaderT SqlBackend m (Maybe SwapInfo) -> IO (Maybe SwapInfo) forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k). Category cat => cat b c -> cat a b -> cat a c . ReaderT SqlBackend m (Maybe SwapInfo) -> m (Maybe SwapInfo) forall (m :: * -> *) a. Storage m => ReaderT SqlBackend m a -> m a runSql (ReaderT SqlBackend m (Maybe SwapInfo) -> Handler Html) -> ReaderT SqlBackend m (Maybe SwapInfo) -> Handler Html forall a b. (a -> b) -> a -> b $ Uuid 'SwapIntoLnTable -> ReaderT SqlBackend m (Maybe SwapInfo) forall (m :: * -> *). MonadIO m => Uuid 'SwapIntoLnTable -> ReaderT SqlBackend m (Maybe SwapInfo) SwapIntoLn.getByUuidSql Uuid 'SwapIntoLnTable uuid where htmlUuid :: Text htmlUuid = $(mkHtmlUuid) newSwapWidget :: SwapIntoLn.SwapInfo -> Maybe Widget newSwapWidget :: SwapInfo -> Maybe Widget newSwapWidget SwapInfo swapInfo = AppMessage -> [[(AppMessage, AppMessage)]] -> Maybe Widget newNamedListWidget AppMessage MsgSwapIntoLnHeaderInfo ([[(AppMessage, AppMessage)]] -> Maybe Widget) -> ([(AppMessage, AppMessage)] -> [[(AppMessage, AppMessage)]]) -> [(AppMessage, AppMessage)] -> Maybe Widget forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k). Category cat => cat b c -> cat a b -> cat a c . [(AppMessage, AppMessage)] -> [[(AppMessage, AppMessage)]] forall seq. MonoPointed seq => Element seq -> seq singleton ([(AppMessage, AppMessage)] -> Maybe Widget) -> [(AppMessage, AppMessage)] -> Maybe Widget forall a b. (a -> b) -> a -> b $ [ ( AppMessage MsgSwapIntoLnTotalOnChainReceived, AppMessage -> Maybe AppMessage forall a. a -> Maybe a Just (AppMessage -> Maybe AppMessage) -> (MSat -> AppMessage) -> MSat -> Maybe AppMessage forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k). Category cat => cat b c -> cat a b -> cat a c . MSat -> AppMessage MsgSatoshi (MSat -> Maybe AppMessage) -> MSat -> Maybe AppMessage forall a b. (a -> b) -> a -> b $ (SwapUtxoStatus -> Bool) -> SwapInfo -> MSat totalOnChainAmt (SwapUtxoStatus -> SwapUtxoStatus -> Bool forall a. Eq a => a -> a -> Bool /= SwapUtxoStatus SwapUtxoOrphan) SwapInfo swapInfo ), ( AppMessage MsgSwapIntoLnTotalOnChainReserved, AppMessage -> Maybe AppMessage forall a. a -> Maybe a Just (AppMessage -> Maybe AppMessage) -> (MSat -> AppMessage) -> MSat -> Maybe AppMessage forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k). Category cat => cat b c -> cat a b -> cat a c . MSat -> AppMessage MsgSatoshi (MSat -> Maybe AppMessage) -> MSat -> Maybe AppMessage forall a b. (a -> b) -> a -> b $ (SwapUtxoStatus -> Bool) -> SwapInfo -> MSat totalOnChainAmt ( Element [SwapUtxoStatus] -> [SwapUtxoStatus] -> Bool forall mono. (MonoFoldable mono, Eq (Element mono)) => Element mono -> mono -> Bool `elem` [ SwapUtxoStatus SwapUtxoUnspentChanReserve ] ) SwapInfo swapInfo ), ( AppMessage MsgSwapIntoLnTotalOnChainSwapped, AppMessage -> Maybe AppMessage forall a. a -> Maybe a Just (AppMessage -> Maybe AppMessage) -> (MSat -> AppMessage) -> MSat -> Maybe AppMessage forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k). Category cat => cat b c -> cat a b -> cat a c . MSat -> AppMessage MsgSatoshi (MSat -> Maybe AppMessage) -> MSat -> Maybe AppMessage forall a b. (a -> b) -> a -> b $ (SwapUtxoStatus -> Bool) -> SwapInfo -> MSat totalOnChainAmt (SwapUtxoStatus -> SwapUtxoStatus -> Bool forall a. Eq a => a -> a -> Bool == SwapUtxoStatus SwapUtxoSpentChanSwapped) SwapInfo swapInfo ), ( AppMessage MsgSwapIntoLnTotalOnChainRefunded, AppMessage -> Maybe AppMessage forall a. a -> Maybe a Just (AppMessage -> Maybe AppMessage) -> (MSat -> AppMessage) -> MSat -> Maybe AppMessage forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k). Category cat => cat b c -> cat a b -> cat a c . MSat -> AppMessage MsgSatoshi (MSat -> Maybe AppMessage) -> MSat -> Maybe AppMessage forall a b. (a -> b) -> a -> b $ (SwapUtxoStatus -> Bool) -> SwapInfo -> MSat totalOnChainAmt (SwapUtxoStatus -> SwapUtxoStatus -> Bool forall a. Eq a => a -> a -> Bool == SwapUtxoStatus SwapUtxoSpentRefund) SwapInfo swapInfo ), ( AppMessage MsgSwapIntoLnTotalOnChainDust, AppMessage -> Maybe AppMessage forall a. a -> Maybe a Just (AppMessage -> Maybe AppMessage) -> (MSat -> AppMessage) -> MSat -> Maybe AppMessage forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k). Category cat => cat b c -> cat a b -> cat a c . MSat -> AppMessage MsgSatoshi (MSat -> Maybe AppMessage) -> MSat -> Maybe AppMessage forall a b. (a -> b) -> a -> b $ (SwapUtxoStatus -> Bool) -> SwapInfo -> MSat totalOnChainAmt (SwapUtxoStatus -> SwapUtxoStatus -> Bool forall a. Eq a => a -> a -> Bool == SwapUtxoStatus SwapUtxoUnspentDust) SwapInfo swapInfo ), ( AppMessage MsgSwapIntoLnFeeLsp, AppMessage -> Maybe AppMessage forall a. a -> Maybe a Just (AppMessage -> Maybe AppMessage) -> (MSat -> AppMessage) -> MSat -> Maybe AppMessage forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k). Category cat => cat b c -> cat a b -> cat a c . MSat -> AppMessage MsgSatoshi (MSat -> Maybe AppMessage) -> MSat -> Maybe AppMessage forall a b. (a -> b) -> a -> b $ Money 'Lsp 'OnChain 'Gain -> MSat forall source target. (From source target, 'False ~ (source == target)) => source -> target from Money 'Lsp 'OnChain 'Gain swapIntoLnFeeLsp ), ( AppMessage MsgSwapIntoLnChanCapUser, AppMessage -> Maybe AppMessage forall a. a -> Maybe a Just (AppMessage -> Maybe AppMessage) -> (MSat -> AppMessage) -> MSat -> Maybe AppMessage forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k). Category cat => cat b c -> cat a b -> cat a c . MSat -> AppMessage MsgSatoshi (MSat -> Maybe AppMessage) -> MSat -> Maybe AppMessage forall a b. (a -> b) -> a -> b $ Money 'Usr 'Ln 'Fund -> MSat forall source target. (From source target, 'False ~ (source == target)) => source -> target from Money 'Usr 'Ln 'Fund swapIntoLnChanCapUser ), ( AppMessage MsgSwapIntoLnChanCapLsp, AppMessage -> Maybe AppMessage forall a. a -> Maybe a Just (AppMessage -> Maybe AppMessage) -> (MSat -> AppMessage) -> MSat -> Maybe AppMessage forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k). Category cat => cat b c -> cat a b -> cat a c . MSat -> AppMessage MsgSatoshi (MSat -> Maybe AppMessage) -> MSat -> Maybe AppMessage forall a b. (a -> b) -> a -> b $ Money 'Lsp 'Ln 'Fund -> MSat forall source target. (From source target, 'False ~ (source == target)) => source -> target from Money 'Lsp 'Ln 'Fund swapIntoLnChanCapLsp ), ( AppMessage MsgSwapIntoLnChanCapTotal, AppMessage -> Maybe AppMessage forall a. a -> Maybe a Just (AppMessage -> Maybe AppMessage) -> (MSat -> AppMessage) -> MSat -> Maybe AppMessage forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k). Category cat => cat b c -> cat a b -> cat a c . MSat -> AppMessage MsgSatoshi (MSat -> Maybe AppMessage) -> MSat -> Maybe AppMessage forall a b. (a -> b) -> a -> b $ Money 'Usr 'Ln 'Fund -> MSat forall source target. (From source target, 'False ~ (source == target)) => source -> target from Money 'Usr 'Ln 'Fund swapIntoLnChanCapUser MSat -> MSat -> MSat forall a. Num a => a -> a -> a + Money 'Lsp 'Ln 'Fund -> MSat forall source target. (From source target, 'False ~ (source == target)) => source -> target from Money 'Lsp 'Ln 'Fund swapIntoLnChanCapLsp ), ( AppMessage MsgChannelPrivacy, AppMessage -> Maybe AppMessage forall a. a -> Maybe a Just (AppMessage -> Maybe AppMessage) -> AppMessage -> Maybe AppMessage forall a b. (a -> b) -> a -> b $ Privacy -> AppMessage chanPrivacyMsg Privacy swapIntoLnPrivacy ), ( AppMessage MsgStatus, AppMessage -> Maybe AppMessage forall a. a -> Maybe a Just (AppMessage -> Maybe AppMessage) -> AppMessage -> Maybe AppMessage forall a b. (a -> b) -> a -> b $ SwapStatus -> AppMessage swapStatusMsg SwapStatus swapIntoLnStatus ), ( AppMessage MsgExpiresAt, AppMessage -> Maybe AppMessage forall a. a -> Maybe a Just (AppMessage -> Maybe AppMessage) -> AppMessage -> Maybe AppMessage forall a b. (a -> b) -> a -> b $ UTCTime -> AppMessage MsgUtcTime UTCTime swapIntoLnExpiresAt ), ( AppMessage MsgSwapIntoLnUuid, AppMessage -> Maybe AppMessage forall a. a -> Maybe a Just (AppMessage -> Maybe AppMessage) -> (Uuid 'SwapIntoLnTable -> AppMessage) -> Uuid 'SwapIntoLnTable -> Maybe AppMessage forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k). Category cat => cat b c -> cat a b -> cat a c . Text -> AppMessage MsgProxy (Text -> AppMessage) -> (Uuid 'SwapIntoLnTable -> Text) -> Uuid 'SwapIntoLnTable -> AppMessage forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k). Category cat => cat b c -> cat a b -> cat a c . UUID -> Text UUID.toText (UUID -> Text) -> (Uuid 'SwapIntoLnTable -> UUID) -> Uuid 'SwapIntoLnTable -> Text forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k). Category cat => cat b c -> cat a b -> cat a c . Uuid 'SwapIntoLnTable -> UUID forall (tab :: Table). Uuid tab -> UUID unUuid (Uuid 'SwapIntoLnTable -> Maybe AppMessage) -> Uuid 'SwapIntoLnTable -> Maybe AppMessage forall a b. (a -> b) -> a -> b $ Uuid 'SwapIntoLnTable swapIntoLnUuid ), ( AppMessage MsgSwapIntoLnUserId, AppMessage -> Maybe AppMessage forall a. a -> Maybe a Just (AppMessage -> Maybe AppMessage) -> AppMessage -> Maybe AppMessage forall a b. (a -> b) -> a -> b $ Text -> AppMessage MsgProxy Text userPub ), ( AppMessage MsgSwapIntoLnFundAddress, AppMessage -> Maybe AppMessage forall a. a -> Maybe a Just (AppMessage -> Maybe AppMessage) -> (Text -> AppMessage) -> Text -> Maybe AppMessage forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k). Category cat => cat b c -> cat a b -> cat a c . Text -> AppMessage MsgProxy (Text -> Maybe AppMessage) -> Text -> Maybe AppMessage forall a b. (a -> b) -> a -> b $ OnChainAddress 'Fund -> Text forall a. (From a Text, 'False ~ (Text == a), 'False ~ (a == Text)) => a -> Text toText OnChainAddress 'Fund swapIntoLnFundAddress ), ( AppMessage MsgSwapIntoLnRefundAddress, AppMessage -> Maybe AppMessage forall a. a -> Maybe a Just (AppMessage -> Maybe AppMessage) -> (Text -> AppMessage) -> Text -> Maybe AppMessage forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k). Category cat => cat b c -> cat a b -> cat a c . Text -> AppMessage MsgProxy (Text -> Maybe AppMessage) -> Text -> Maybe AppMessage forall a b. (a -> b) -> a -> b $ OnChainAddress 'Refund -> Text forall a. (From a Text, 'False ~ (Text == a), 'False ~ (a == Text)) => a -> Text toText OnChainAddress 'Refund swapIntoLnRefundAddress ), ( AppMessage MsgInsertedAt, AppMessage -> Maybe AppMessage forall a. a -> Maybe a Just (AppMessage -> Maybe AppMessage) -> AppMessage -> Maybe AppMessage forall a b. (a -> b) -> a -> b $ UTCTime -> AppMessage MsgUtcTime UTCTime swapIntoLnInsertedAt ), ( AppMessage MsgUpdatedAt, AppMessage -> Maybe AppMessage forall a. a -> Maybe a Just (AppMessage -> Maybe AppMessage) -> AppMessage -> Maybe AppMessage forall a b. (a -> b) -> a -> b $ UTCTime -> AppMessage MsgUtcTime UTCTime swapIntoLnUpdatedAt ) ] [(AppMessage, Maybe AppMessage)] -> ((AppMessage, Maybe AppMessage) -> [(AppMessage, AppMessage)]) -> [(AppMessage, AppMessage)] forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b >>= \case (AppMessage msg, Just AppMessage txt) -> [(AppMessage msg, AppMessage txt)] (AppMessage _, Maybe AppMessage Nothing) -> [] where SwapIntoLn {UTCTime UserId Uuid 'SwapIntoLnTable Privacy SwapStatus Money 'Lsp 'OnChain 'Gain Money 'Lsp 'OnChain 'Loss Money 'Lsp 'Ln 'Fund Money 'Usr 'Ln 'Fund OnChainAddress 'Fund OnChainAddress 'Refund OnChainAddress 'Gain swapIntoLnFeeMiner :: Money 'Lsp 'OnChain 'Loss swapIntoLnLspFeeAndChangeAddress :: OnChainAddress 'Gain swapIntoLnUserId :: UserId swapIntoLnUpdatedAt :: UTCTime swapIntoLnInsertedAt :: UTCTime swapIntoLnRefundAddress :: OnChainAddress 'Refund swapIntoLnFundAddress :: OnChainAddress 'Fund swapIntoLnUuid :: Uuid 'SwapIntoLnTable swapIntoLnExpiresAt :: UTCTime swapIntoLnStatus :: SwapStatus swapIntoLnPrivacy :: Privacy swapIntoLnChanCapLsp :: Money 'Lsp 'Ln 'Fund swapIntoLnChanCapUser :: Money 'Usr 'Ln 'Fund swapIntoLnFeeLsp :: Money 'Lsp 'OnChain 'Gain swapIntoLnUpdatedAt :: SwapIntoLn -> UTCTime swapIntoLnInsertedAt :: SwapIntoLn -> UTCTime swapIntoLnExpiresAt :: SwapIntoLn -> UTCTime swapIntoLnPrivacy :: SwapIntoLn -> Privacy swapIntoLnStatus :: SwapIntoLn -> SwapStatus swapIntoLnFeeMiner :: SwapIntoLn -> Money 'Lsp 'OnChain 'Loss swapIntoLnFeeLsp :: SwapIntoLn -> Money 'Lsp 'OnChain 'Gain swapIntoLnChanCapLsp :: SwapIntoLn -> Money 'Lsp 'Ln 'Fund swapIntoLnChanCapUser :: SwapIntoLn -> Money 'Usr 'Ln 'Fund swapIntoLnRefundAddress :: SwapIntoLn -> OnChainAddress 'Refund swapIntoLnLspFeeAndChangeAddress :: SwapIntoLn -> OnChainAddress 'Gain swapIntoLnFundAddress :: SwapIntoLn -> OnChainAddress 'Fund swapIntoLnUserId :: SwapIntoLn -> UserId swapIntoLnUuid :: SwapIntoLn -> Uuid 'SwapIntoLnTable ..} = Entity SwapIntoLn -> SwapIntoLn forall record. Entity record -> record entityVal (Entity SwapIntoLn -> SwapIntoLn) -> Entity SwapIntoLn -> SwapIntoLn forall a b. (a -> b) -> a -> b $ SwapInfo -> Entity SwapIntoLn SwapIntoLn.swapInfoSwap SwapInfo swapInfo userPub :: Text userPub = ByteString -> Text toHex (ByteString -> Text) -> (Entity User -> ByteString) -> Entity User -> Text forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k). Category cat => cat b c -> cat a b -> cat a c . NodePubKey -> ByteString coerce (NodePubKey -> ByteString) -> (Entity User -> NodePubKey) -> Entity User -> ByteString forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k). Category cat => cat b c -> cat a b -> cat a c . User -> NodePubKey userNodePubKey (User -> NodePubKey) -> (Entity User -> User) -> Entity User -> NodePubKey forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k). Category cat => cat b c -> cat a b -> cat a c . Entity User -> User forall record. Entity record -> record entityVal (Entity User -> Text) -> Entity User -> Text forall a b. (a -> b) -> a -> b $ SwapInfo -> Entity User SwapIntoLn.swapInfoUser SwapInfo swapInfo totalOnChainAmt :: (SwapUtxoStatus -> Bool) -> SwapIntoLn.SwapInfo -> MSat totalOnChainAmt :: (SwapUtxoStatus -> Bool) -> SwapInfo -> MSat totalOnChainAmt SwapUtxoStatus -> Bool only = Money 'Usr 'OnChain 'Fund -> MSat forall source target. (From source target, 'False ~ (source == target)) => source -> target from (Money 'Usr 'OnChain 'Fund -> MSat) -> (SwapInfo -> Money 'Usr 'OnChain 'Fund) -> SwapInfo -> MSat forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k). Category cat => cat b c -> cat a b -> cat a c . [Money 'Usr 'OnChain 'Fund] -> Money 'Usr 'OnChain 'Fund forall mono. (MonoFoldable mono, Num (Element mono)) => mono -> Element mono sum ([Money 'Usr 'OnChain 'Fund] -> Money 'Usr 'OnChain 'Fund) -> (SwapInfo -> [Money 'Usr 'OnChain 'Fund]) -> SwapInfo -> Money 'Usr 'OnChain 'Fund forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k). Category cat => cat b c -> cat a b -> cat a c . (SwapUtxo -> Money 'Usr 'OnChain 'Fund) -> [SwapUtxo] -> [Money 'Usr 'OnChain 'Fund] forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap SwapUtxo -> Money 'Usr 'OnChain 'Fund swapUtxoAmount ([SwapUtxo] -> [Money 'Usr 'OnChain 'Fund]) -> (SwapInfo -> [SwapUtxo]) -> SwapInfo -> [Money 'Usr 'OnChain 'Fund] forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k). Category cat => cat b c -> cat a b -> cat a c . (Element [SwapUtxo] -> Bool) -> [SwapUtxo] -> [SwapUtxo] forall seq. IsSequence seq => (Element seq -> Bool) -> seq -> seq filter (SwapUtxoStatus -> Bool only (SwapUtxoStatus -> Bool) -> (SwapUtxo -> SwapUtxoStatus) -> SwapUtxo -> Bool forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k). Category cat => cat b c -> cat a b -> cat a c . SwapUtxo -> SwapUtxoStatus swapUtxoStatus) ([SwapUtxo] -> [SwapUtxo]) -> (SwapInfo -> [SwapUtxo]) -> SwapInfo -> [SwapUtxo] forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k). Category cat => cat b c -> cat a b -> cat a c . (UtxoInfo -> SwapUtxo) -> [UtxoInfo] -> [SwapUtxo] forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap (Entity SwapUtxo -> SwapUtxo forall record. Entity record -> record entityVal (Entity SwapUtxo -> SwapUtxo) -> (UtxoInfo -> Entity SwapUtxo) -> UtxoInfo -> SwapUtxo forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k). Category cat => cat b c -> cat a b -> cat a c . UtxoInfo -> Entity SwapUtxo SwapIntoLn.utxoInfoUtxo) ([UtxoInfo] -> [SwapUtxo]) -> (SwapInfo -> [UtxoInfo]) -> SwapInfo -> [SwapUtxo] forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k). Category cat => cat b c -> cat a b -> cat a c . SwapInfo -> [UtxoInfo] SwapIntoLn.swapInfoUtxo newUtxoWidget :: [SwapIntoLn.UtxoInfo] -> Maybe Widget newUtxoWidget :: [UtxoInfo] -> Maybe Widget newUtxoWidget [UtxoInfo] utxos = AppMessage -> [[(AppMessage, AppMessage)]] -> Maybe Widget newNamedListWidget AppMessage MsgSwapIntoLnHeaderUtxos ([[(AppMessage, AppMessage)]] -> Maybe Widget) -> [[(AppMessage, AppMessage)]] -> Maybe Widget forall a b. (a -> b) -> a -> b $ ( \UtxoInfo row -> let SwapUtxo {Maybe BlockId Maybe (TxId 'Funding) Maybe UtxoLockId UTCTime BlockId SwapIntoLnId TxId 'Funding Vout 'Funding SwapUtxoStatus Money 'Usr 'OnChain 'Fund swapUtxoUpdatedAt :: SwapUtxo -> UTCTime swapUtxoInsertedAt :: SwapUtxo -> UTCTime swapUtxoLockId :: SwapUtxo -> Maybe UtxoLockId swapUtxoRefundTxId :: SwapUtxo -> Maybe (TxId 'Funding) swapUtxoRefundBlockId :: SwapUtxo -> Maybe BlockId swapUtxoVout :: SwapUtxo -> Vout 'Funding swapUtxoTxid :: SwapUtxo -> TxId 'Funding swapUtxoBlockId :: SwapUtxo -> BlockId swapUtxoSwapIntoLnId :: SwapUtxo -> SwapIntoLnId swapUtxoUpdatedAt :: UTCTime swapUtxoInsertedAt :: UTCTime swapUtxoLockId :: Maybe UtxoLockId swapUtxoRefundTxId :: Maybe (TxId 'Funding) swapUtxoRefundBlockId :: Maybe BlockId swapUtxoStatus :: SwapUtxoStatus swapUtxoAmount :: Money 'Usr 'OnChain 'Fund swapUtxoVout :: Vout 'Funding swapUtxoTxid :: TxId 'Funding swapUtxoBlockId :: BlockId swapUtxoSwapIntoLnId :: SwapIntoLnId swapUtxoStatus :: SwapUtxo -> SwapUtxoStatus swapUtxoAmount :: SwapUtxo -> Money 'Usr 'OnChain 'Fund ..} = Entity SwapUtxo -> SwapUtxo forall record. Entity record -> record entityVal (Entity SwapUtxo -> SwapUtxo) -> Entity SwapUtxo -> SwapUtxo forall a b. (a -> b) -> a -> b $ UtxoInfo -> Entity SwapUtxo SwapIntoLn.utxoInfoUtxo UtxoInfo row Block {UTCTime BlkStatus BlkHeight BlkHash blockUpdatedAt :: Block -> UTCTime blockInsertedAt :: Block -> UTCTime blockStatus :: Block -> BlkStatus blockHash :: Block -> BlkHash blockHeight :: Block -> BlkHeight blockUpdatedAt :: UTCTime blockInsertedAt :: UTCTime blockStatus :: BlkStatus blockHash :: BlkHash blockHeight :: BlkHeight ..} = Entity Block -> Block forall record. Entity record -> record entityVal (Entity Block -> Block) -> Entity Block -> Block forall a b. (a -> b) -> a -> b $ UtxoInfo -> Entity Block SwapIntoLn.utxoInfoBlock UtxoInfo row in [ ( AppMessage MsgBlock, Text -> AppMessage MsgProxy (Text -> AppMessage) -> (Word64 -> Text) -> Word64 -> AppMessage forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k). Category cat => cat b c -> cat a b -> cat a c . forall a. Out a => a -> Text inspectPlain @Word64 (Word64 -> AppMessage) -> Word64 -> AppMessage forall a b. (a -> b) -> a -> b $ BlkHeight -> Word64 forall source target. (From source target, 'False ~ (source == target)) => source -> target from BlkHeight blockHeight ), ( AppMessage MsgAmount, MSat -> AppMessage MsgSatoshi (MSat -> AppMessage) -> MSat -> AppMessage forall a b. (a -> b) -> a -> b $ Money 'Usr 'OnChain 'Fund -> MSat forall source target. (From source target, 'False ~ (source == target)) => source -> target from Money 'Usr 'OnChain 'Fund swapUtxoAmount ), ( AppMessage MsgStatus, SwapUtxoStatus -> AppMessage swapUtxoStatusMsg SwapUtxoStatus swapUtxoStatus ), ( AppMessage MsgTxId, Text -> AppMessage MsgProxy (Text -> AppMessage) -> (ByteString -> Text) -> ByteString -> AppMessage forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k). Category cat => cat b c -> cat a b -> cat a c . ByteString -> Text txIdHex (ByteString -> AppMessage) -> ByteString -> AppMessage forall a b. (a -> b) -> a -> b $ TxId 'Funding -> ByteString coerce TxId 'Funding swapUtxoTxid ), ( AppMessage MsgVout, Text -> AppMessage MsgProxy (Text -> AppMessage) -> (Word32 -> Text) -> Word32 -> AppMessage forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k). Category cat => cat b c -> cat a b -> cat a c . forall a. Out a => a -> Text inspectPlain @Word32 (Word32 -> AppMessage) -> Word32 -> AppMessage forall a b. (a -> b) -> a -> b $ Vout 'Funding -> Word32 coerce Vout 'Funding swapUtxoVout ), ( AppMessage MsgInsertedAt, UTCTime -> AppMessage MsgUtcTime UTCTime swapUtxoInsertedAt ), ( AppMessage MsgUpdatedAt, UTCTime -> AppMessage MsgUtcTime UTCTime swapUtxoUpdatedAt ) ] ) (UtxoInfo -> [(AppMessage, AppMessage)]) -> [UtxoInfo] -> [[(AppMessage, AppMessage)]] forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> [UtxoInfo] utxos newChanWidget :: [Entity LnChan] -> Maybe Widget newChanWidget :: [Entity LnChan] -> Maybe Widget newChanWidget [Entity LnChan] chans = AppMessage -> [[(AppMessage, AppMessage)]] -> Maybe Widget newNamedListWidget AppMessage MsgSwapIntoLnHeaderChans ([[(AppMessage, AppMessage)]] -> Maybe Widget) -> [[(AppMessage, AppMessage)]] -> Maybe Widget forall a b. (a -> b) -> a -> b $ ( \Entity LnChan row -> let LnChan {Maybe SwapIntoLnId Maybe ChanId Maybe (TxId 'Closing) Maybe SingleChanBackupBlob UTCTime MSat TxId 'Funding Vout 'Funding LnChanStatus lnChanTransactedAt :: LnChan -> UTCTime lnChanUpdatedAt :: LnChan -> UTCTime lnChanInsertedAt :: LnChan -> UTCTime lnChanStatus :: LnChan -> LnChanStatus lnChanTotalSatoshisReceived :: LnChan -> MSat lnChanTotalSatoshisSent :: LnChan -> MSat lnChanBak :: LnChan -> Maybe SingleChanBackupBlob lnChanExtId :: LnChan -> Maybe ChanId lnChanClosingTxId :: LnChan -> Maybe (TxId 'Closing) lnChanFundingVout :: LnChan -> Vout 'Funding lnChanFundingTxId :: LnChan -> TxId 'Funding lnChanSwapIntoLnId :: LnChan -> Maybe SwapIntoLnId lnChanTransactedAt :: UTCTime lnChanUpdatedAt :: UTCTime lnChanInsertedAt :: UTCTime lnChanStatus :: LnChanStatus lnChanTotalSatoshisReceived :: MSat lnChanTotalSatoshisSent :: MSat lnChanBak :: Maybe SingleChanBackupBlob lnChanExtId :: Maybe ChanId lnChanClosingTxId :: Maybe (TxId 'Closing) lnChanFundingVout :: Vout 'Funding lnChanFundingTxId :: TxId 'Funding lnChanSwapIntoLnId :: Maybe SwapIntoLnId ..} = Entity LnChan -> LnChan forall record. Entity record -> record entityVal Entity LnChan row in [ ( AppMessage MsgStatus, LnChanStatus -> AppMessage lnChanStatusMsg LnChanStatus lnChanStatus ), ( AppMessage MsgTxId, Text -> AppMessage MsgProxy (Text -> AppMessage) -> (ByteString -> Text) -> ByteString -> AppMessage forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k). Category cat => cat b c -> cat a b -> cat a c . ByteString -> Text txIdHex (ByteString -> AppMessage) -> ByteString -> AppMessage forall a b. (a -> b) -> a -> b $ TxId 'Funding -> ByteString coerce TxId 'Funding lnChanFundingTxId ), ( AppMessage MsgVout, Text -> AppMessage MsgProxy (Text -> AppMessage) -> (Word32 -> Text) -> Word32 -> AppMessage forall {k} (cat :: k -> k -> *) (b :: k) (c :: k) (a :: k). Category cat => cat b c -> cat a b -> cat a c . forall a. Out a => a -> Text inspectPlain @Word32 (Word32 -> AppMessage) -> Word32 -> AppMessage forall a b. (a -> b) -> a -> b $ Vout 'Funding -> Word32 coerce Vout 'Funding lnChanFundingVout ), ( AppMessage MsgInsertedAt, UTCTime -> AppMessage MsgUtcTime UTCTime lnChanInsertedAt ), ( AppMessage MsgUpdatedAt, UTCTime -> AppMessage MsgUtcTime UTCTime lnChanUpdatedAt ) ] ) (Entity LnChan -> [(AppMessage, AppMessage)]) -> [Entity LnChan] -> [[(AppMessage, AppMessage)]] forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> [Entity LnChan] chans swapStatusMsg :: SwapStatus -> AppMessage swapStatusMsg :: SwapStatus -> AppMessage swapStatusMsg = \case SwapStatus SwapWaitingFundChain -> AppMessage MsgSwapWaitingFundChain SwapStatus SwapWaitingPeer -> AppMessage MsgSwapWaitingPeer SwapStatus SwapWaitingChan -> AppMessage MsgSwapWaitingChan SwapStatus SwapSucceeded -> AppMessage MsgSwapSucceeded SwapStatus SwapExpired -> AppMessage MsgSwapExpired chanPrivacyMsg :: Privacy -> AppMessage chanPrivacyMsg :: Privacy -> AppMessage chanPrivacyMsg = \case Privacy Private -> AppMessage MsgChanPrivate Privacy Public -> AppMessage MsgChanPublic swapUtxoStatusMsg :: SwapUtxoStatus -> AppMessage swapUtxoStatusMsg :: SwapUtxoStatus -> AppMessage swapUtxoStatusMsg = \case SwapUtxoStatus SwapUtxoUnspent -> AppMessage MsgSwapUtxoUnspent SwapUtxoStatus SwapUtxoUnspentDust -> AppMessage MsgSwapUtxoUnspentDust SwapUtxoStatus SwapUtxoUnspentChanReserve -> AppMessage MsgSwapUtxoUnspentChanReserve SwapUtxoStatus SwapUtxoSpentChanSwapped -> AppMessage MsgSwapUtxoSpentChanSwapped SwapUtxoStatus SwapUtxoSpentRefund -> AppMessage MsgSwapUtxoSpentRefund SwapUtxoStatus SwapUtxoOrphan -> AppMessage MsgSwapUtxoOrphan lnChanStatusMsg :: LnChanStatus -> AppMessage lnChanStatusMsg :: LnChanStatus -> AppMessage lnChanStatusMsg = \case LnChanStatus LnChanStatusPendingOpen -> AppMessage MsgLnChanStatusPendingOpen LnChanStatus LnChanStatusOpened -> AppMessage MsgLnChanStatusOpened LnChanStatus LnChanStatusActive -> AppMessage MsgLnChanStatusActive LnChanStatus LnChanStatusFullyResolved -> AppMessage MsgLnChanStatusFullyResolved LnChanStatus LnChanStatusInactive -> AppMessage MsgLnChanStatusInactive LnChanStatus LnChanStatusPendingClose -> AppMessage MsgLnChanStatusPendingClose LnChanStatus LnChanStatusClosed -> AppMessage MsgLnChanStatusClosed