{-# LANGUAGE TypeApplications #-} module BtcLsp.Math.Swap ( SwapCap (..), swapExpiryLimitInput, swapExpiryLimitInternal, swapLnMaxAmt, swapLnFeeRate, swapLnMinFee, newSwapCapM, newSwapIntoLnMinAmt, ) where import BtcLsp.Class.Env import BtcLsp.Data.Kind import BtcLsp.Data.Type import BtcLsp.Import.External import qualified LndClient as Lnd data SwapCap = SwapCap { SwapCap -> Money 'Usr 'Ln 'Fund swapCapUsr :: Money 'Usr 'Ln 'Fund, SwapCap -> Money 'Lsp 'Ln 'Fund swapCapLsp :: Money 'Lsp 'Ln 'Fund, SwapCap -> Money 'Lsp 'OnChain 'Gain swapCapFee :: Money 'Lsp 'OnChain 'Gain } deriving stock ( SwapCap -> SwapCap -> Bool (SwapCap -> SwapCap -> Bool) -> (SwapCap -> SwapCap -> Bool) -> Eq SwapCap forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: SwapCap -> SwapCap -> Bool $c/= :: SwapCap -> SwapCap -> Bool == :: SwapCap -> SwapCap -> Bool $c== :: SwapCap -> SwapCap -> Bool Eq, Eq SwapCap Eq SwapCap -> (SwapCap -> SwapCap -> Ordering) -> (SwapCap -> SwapCap -> Bool) -> (SwapCap -> SwapCap -> Bool) -> (SwapCap -> SwapCap -> Bool) -> (SwapCap -> SwapCap -> Bool) -> (SwapCap -> SwapCap -> SwapCap) -> (SwapCap -> SwapCap -> SwapCap) -> Ord SwapCap SwapCap -> SwapCap -> Bool SwapCap -> SwapCap -> Ordering SwapCap -> SwapCap -> SwapCap forall a. Eq a -> (a -> a -> Ordering) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> Bool) -> (a -> a -> a) -> (a -> a -> a) -> Ord a min :: SwapCap -> SwapCap -> SwapCap $cmin :: SwapCap -> SwapCap -> SwapCap max :: SwapCap -> SwapCap -> SwapCap $cmax :: SwapCap -> SwapCap -> SwapCap >= :: SwapCap -> SwapCap -> Bool $c>= :: SwapCap -> SwapCap -> Bool > :: SwapCap -> SwapCap -> Bool $c> :: SwapCap -> SwapCap -> Bool <= :: SwapCap -> SwapCap -> Bool $c<= :: SwapCap -> SwapCap -> Bool < :: SwapCap -> SwapCap -> Bool $c< :: SwapCap -> SwapCap -> Bool compare :: SwapCap -> SwapCap -> Ordering $ccompare :: SwapCap -> SwapCap -> Ordering Ord, Int -> SwapCap -> ShowS [SwapCap] -> ShowS SwapCap -> String (Int -> SwapCap -> ShowS) -> (SwapCap -> String) -> ([SwapCap] -> ShowS) -> Show SwapCap forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [SwapCap] -> ShowS $cshowList :: [SwapCap] -> ShowS show :: SwapCap -> String $cshow :: SwapCap -> String showsPrec :: Int -> SwapCap -> ShowS $cshowsPrec :: Int -> SwapCap -> ShowS Show, (forall x. SwapCap -> Rep SwapCap x) -> (forall x. Rep SwapCap x -> SwapCap) -> Generic SwapCap forall x. Rep SwapCap x -> SwapCap forall x. SwapCap -> Rep SwapCap x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cto :: forall x. Rep SwapCap x -> SwapCap $cfrom :: forall x. SwapCap -> Rep SwapCap x Generic ) instance Out SwapCap swapExpiryLimitInput :: Lnd.Seconds swapExpiryLimitInput :: Seconds swapExpiryLimitInput = Word64 -> Seconds Lnd.Seconds (Word64 -> Seconds) -> Word64 -> Seconds forall a b. (a -> b) -> a -> b $ (Word64 7 Word64 -> Word64 -> Word64 forall a. Num a => a -> a -> a * Word64 24 Word64 -> Word64 -> Word64 forall a. Num a => a -> a -> a - Word64 1) Word64 -> Word64 -> Word64 forall a. Num a => a -> a -> a * Word64 3600 swapExpiryLimitInternal :: Lnd.Seconds swapExpiryLimitInternal :: Seconds swapExpiryLimitInternal = Word64 -> Seconds Lnd.Seconds Word64 3600 swapLnMaxAmt :: Money 'Usr btcl 'Fund swapLnMaxAmt :: forall (btcl :: BitcoinLayer). Money 'Usr btcl 'Fund swapLnMaxAmt = MSat -> Money 'Usr btcl 'Fund forall (owner :: Owner) (btcl :: BitcoinLayer) (mrel :: MoneyRelation). MSat -> Money owner btcl mrel Money (MSat -> Money 'Usr btcl 'Fund) -> MSat -> Money 'Usr btcl 'Fund forall a b. (a -> b) -> a -> b $ Word64 -> MSat MSat Word64 10000000000 swapLnFeeRate :: FeeRate swapLnFeeRate :: FeeRate swapLnFeeRate = Ratio Word64 -> FeeRate FeeRate Ratio Word64 0.004 swapLnMinFee :: Money 'Lsp btcl 'Gain swapLnMinFee :: forall (btcl :: BitcoinLayer). Money 'Lsp btcl 'Gain swapLnMinFee = MSat -> Money 'Lsp btcl 'Gain forall (owner :: Owner) (btcl :: BitcoinLayer) (mrel :: MoneyRelation). MSat -> Money owner btcl mrel Money (MSat -> Money 'Lsp btcl 'Gain) -> MSat -> Money 'Lsp btcl 'Gain forall a b. (a -> b) -> a -> b $ Word64 -> MSat MSat Word64 2000000 newSwapCapM :: ( Env m ) => Money 'Usr 'OnChain 'Fund -> m (Maybe SwapCap) newSwapCapM :: forall (m :: * -> *). Env m => Money 'Usr 'OnChain 'Fund -> m (Maybe SwapCap) newSwapCapM Money 'Usr 'OnChain 'Fund usrAmt = do Money 'Usr 'OnChain 'Fund minAmt <- m (Money 'Usr 'OnChain 'Fund) forall (m :: * -> *). Env m => m (Money 'Usr 'OnChain 'Fund) getSwapIntoLnMinAmt Maybe SwapCap -> m (Maybe SwapCap) forall (f :: * -> *) a. Applicative f => a -> f a pure (Maybe SwapCap -> m (Maybe SwapCap)) -> Maybe SwapCap -> m (Maybe SwapCap) forall a b. (a -> b) -> a -> b $ if Money 'Usr 'OnChain 'Fund usrAmt Money 'Usr 'OnChain 'Fund -> Money 'Usr 'OnChain 'Fund -> Bool forall a. Ord a => a -> a -> Bool < Money 'Usr 'OnChain 'Fund minAmt then Maybe SwapCap forall a. Maybe a Nothing else SwapCap -> Maybe SwapCap forall a. a -> Maybe a Just SwapCap :: Money 'Usr 'Ln 'Fund -> Money 'Lsp 'Ln 'Fund -> Money 'Lsp 'OnChain 'Gain -> SwapCap SwapCap { swapCapUsr :: Money 'Usr 'Ln 'Fund swapCapUsr = Money 'Usr 'Ln 'Fund usrLn, swapCapLsp :: Money 'Lsp 'Ln 'Fund swapCapLsp = Money 'Usr 'Ln 'Fund -> Money 'Lsp 'Ln 'Fund coerce Money 'Usr 'Ln 'Fund usrLn, swapCapFee :: Money 'Lsp 'OnChain 'Gain swapCapFee = forall source target. (From source target, 'False ~ (source == target)) => source -> target from @Word64 (Word64 -> Money 'Lsp 'OnChain 'Gain) -> Word64 -> Money 'Lsp 'OnChain 'Gain forall a b. (a -> b) -> a -> b $ Ratio Word64 -> Word64 forall a b. (RealFrac a, Integral b) => a -> b ceiling Ratio Word64 feeRat } where usrFin :: Ratio Word64 usrFin :: Ratio Word64 usrFin = Money 'Usr 'OnChain 'Fund -> Word64 forall source target. (From source target, 'False ~ (source == target)) => source -> target from Money 'Usr 'OnChain 'Fund usrAmt Word64 -> Word64 -> Ratio Word64 forall a. Integral a => a -> a -> Ratio a % Word64 1 feeRat :: Ratio Word64 feeRat :: Ratio Word64 feeRat = forall source target. (From source target, 'False ~ (source == target)) => source -> target from @Word64 (Word64 -> Ratio Word64) -> (Ratio Word64 -> Word64) -> Ratio Word64 -> Ratio Word64 forall b c a. (b -> c) -> (a -> b) -> a -> c . (Word64 -> Word64 -> Word64 forall a. Num a => a -> a -> a * Word64 1000) (Word64 -> Word64) -> (Ratio Word64 -> Word64) -> Ratio Word64 -> Word64 forall b c a. (b -> c) -> (a -> b) -> a -> c . Ratio Word64 -> Word64 forall a b. (RealFrac a, Integral b) => a -> b ceiling (Ratio Word64 -> Word64) -> (Ratio Word64 -> Ratio Word64) -> Ratio Word64 -> Word64 forall b c a. (b -> c) -> (a -> b) -> a -> c . (Ratio Word64 -> Ratio Word64 -> Ratio Word64 forall a. Fractional a => a -> a -> a / Ratio Word64 1000) (Ratio Word64 -> Ratio Word64) -> (Ratio Word64 -> Ratio Word64) -> Ratio Word64 -> Ratio Word64 forall b c a. (b -> c) -> (a -> b) -> a -> c . Ratio Word64 -> Ratio Word64 -> Ratio Word64 forall a. Ord a => a -> a -> a max (Money 'Lsp Any 'Gain -> Word64 forall source target. (From source target, 'False ~ (source == target)) => source -> target from Money 'Lsp Any 'Gain forall (btcl :: BitcoinLayer). Money 'Lsp btcl 'Gain swapLnMinFee Word64 -> Word64 -> Ratio Word64 forall a. Integral a => a -> a -> Ratio a % Word64 1) (Ratio Word64 -> Ratio Word64) -> Ratio Word64 -> Ratio Word64 forall a b. (a -> b) -> a -> b $ Ratio Word64 usrFin Ratio Word64 -> Ratio Word64 -> Ratio Word64 forall a. Num a => a -> a -> a * FeeRate -> Ratio Word64 forall source target. (From source target, 'False ~ (source == target)) => source -> target from FeeRate swapLnFeeRate usrLn :: Money 'Usr 'Ln 'Fund usrLn :: Money 'Usr 'Ln 'Fund usrLn = forall source target. (From source target, 'False ~ (source == target)) => source -> target from @Word64 (Word64 -> Money 'Usr 'Ln 'Fund) -> (Ratio Word64 -> Word64) -> Ratio Word64 -> Money 'Usr 'Ln 'Fund forall b c a. (b -> c) -> (a -> b) -> a -> c . Ratio Word64 -> Word64 forall a b. (RealFrac a, Integral b) => a -> b floor (Ratio Word64 -> Money 'Usr 'Ln 'Fund) -> Ratio Word64 -> Money 'Usr 'Ln 'Fund forall a b. (a -> b) -> a -> b $ Ratio Word64 usrFin Ratio Word64 -> Ratio Word64 -> Ratio Word64 forall a. Num a => a -> a -> a - Ratio Word64 feeRat newSwapIntoLnMinAmt :: Money 'Chan 'Ln 'Fund -> Money 'Usr 'OnChain 'Fund newSwapIntoLnMinAmt :: Money 'Chan 'Ln 'Fund -> Money 'Usr 'OnChain 'Fund newSwapIntoLnMinAmt Money 'Chan 'Ln 'Fund minCap = forall source target. (From source target, 'False ~ (source == target)) => source -> target from @Word64 (Word64 -> Money 'Usr 'OnChain 'Fund) -> (Ratio Word64 -> Word64) -> Ratio Word64 -> Money 'Usr 'OnChain 'Fund forall b c a. (b -> c) -> (a -> b) -> a -> c . (Word64 -> Word64 -> Word64 forall a. Num a => a -> a -> a * Word64 1000) (Word64 -> Word64) -> (Ratio Word64 -> Word64) -> Ratio Word64 -> Word64 forall b c a. (b -> c) -> (a -> b) -> a -> c . Ratio Word64 -> Word64 forall a b. (RealFrac a, Integral b) => a -> b ceiling (Ratio Word64 -> Money 'Usr 'OnChain 'Fund) -> Ratio Word64 -> Money 'Usr 'OnChain 'Fund forall a b. (a -> b) -> a -> b $ Ratio Word64 usrInitMsat Ratio Word64 -> Ratio Word64 -> Ratio Word64 forall a. Fractional a => a -> a -> a / Ratio Word64 1000 where minFee :: Ratio Word64 minFee :: Ratio Word64 minFee = Money 'Lsp Any 'Gain -> Word64 forall source target. (From source target, 'False ~ (source == target)) => source -> target from Money 'Lsp Any 'Gain forall (btcl :: BitcoinLayer). Money 'Lsp btcl 'Gain swapLnMinFee Word64 -> Word64 -> Ratio Word64 forall a. Integral a => a -> a -> Ratio a % Word64 1 usrFin :: Ratio Word64 usrFin :: Ratio Word64 usrFin = Money 'Chan 'Ln 'Fund -> Word64 forall source target. (From source target, 'False ~ (source == target)) => source -> target from Money 'Chan 'Ln 'Fund minCap Word64 -> Word64 -> Ratio Word64 forall a. Integral a => a -> a -> Ratio a % Word64 2 usrPerc :: Ratio Word64 usrPerc :: Ratio Word64 usrPerc = Ratio Word64 usrFin Ratio Word64 -> Ratio Word64 -> Ratio Word64 forall a. Fractional a => a -> a -> a / (Ratio Word64 1 Ratio Word64 -> Ratio Word64 -> Ratio Word64 forall a. Num a => a -> a -> a - FeeRate -> Ratio Word64 forall source target. (From source target, 'False ~ (source == target)) => source -> target from FeeRate swapLnFeeRate) usrInitMsat :: Ratio Word64 usrInitMsat :: Ratio Word64 usrInitMsat = if Ratio Word64 usrPerc Ratio Word64 -> Ratio Word64 -> Ratio Word64 forall a. Num a => a -> a -> a - Ratio Word64 usrFin Ratio Word64 -> Ratio Word64 -> Bool forall a. Ord a => a -> a -> Bool >= Ratio Word64 minFee then Ratio Word64 usrPerc else Ratio Word64 usrFin Ratio Word64 -> Ratio Word64 -> Ratio Word64 forall a. Num a => a -> a -> a + Ratio Word64 minFee