{-# LANGUAGE TypeApplications #-} {-# OPTIONS_GHC -Wno-orphans #-} module BtcLsp.Data.Orphan () where import BtcLsp.Import.External import qualified BtcLsp.Import.Psql as Psql import qualified BtcLsp.Text as T import qualified Data.Time.ISO8601 as Time import qualified LndClient as Lnd import qualified Network.Bitcoin.BlockChain as Btc import qualified Network.Bitcoin.RawTransaction as Btc import qualified Network.Bitcoin.Types as Btc import qualified Text.PrettyPrint as PP import qualified Universum import qualified Witch deriving stock instance Generic Btc.TxnOutputType deriving stock instance Generic Btc.ScriptSig deriving stock instance Generic Btc.ScriptPubKey deriving stock instance Generic Btc.TxIn deriving stock instance Generic Btc.TxOut deriving stock instance Generic Btc.BlockVerbose deriving stock instance Generic Btc.DecodedRawTransaction deriving stock instance Generic Btc.BlockChainInfo deriving stock instance Generic Btc.TransactionID instance Out Btc.TransactionID instance Out Btc.TxnOutputType instance Out Btc.ScriptSig instance Out Btc.ScriptPubKey instance Out Btc.TxIn instance Out Btc.TxOut instance Out Btc.BlockVerbose instance Out Btc.DecodedRawTransaction instance Out Btc.BlockChainInfo instance From Text Lnd.PaymentRequest instance From Lnd.PaymentRequest Text instance From Word64 MSat instance From MSat Word64 instance From Word64 Lnd.Seconds instance From Lnd.Seconds Word64 deriving stock instance Generic Btc.Block deriving newtype instance PathPiece Lnd.PaymentRequest instance Out Btc.Block instance Out Natural where docPrec :: Int -> Natural -> Doc docPrec Int x = Int -> Integer -> Doc forall a. Out a => Int -> a -> Doc docPrec Int x (Integer -> Doc) -> (Natural -> Integer) -> Natural -> Doc forall b c a. (b -> c) -> (a -> b) -> a -> c . forall target source. (From source target, 'False ~ (source == target)) => source -> target into @Integer doc :: Natural -> Doc doc = Int -> Natural -> Doc forall a. Out a => Int -> a -> Doc docPrec Int 0 instance Out PortNumber where docPrec :: Int -> PortNumber -> Doc docPrec Int x = Int -> Integer -> Doc forall a. Out a => Int -> a -> Doc docPrec Int x (Integer -> Doc) -> (PortNumber -> Integer) -> PortNumber -> Doc forall b c a. (b -> c) -> (a -> b) -> a -> c . PortNumber -> Integer forall a. Integral a => a -> Integer toInteger doc :: PortNumber -> Doc doc = Int -> PortNumber -> Doc forall a. Out a => Int -> a -> Doc docPrec Int 0 instance (Psql.ToBackendKey Psql.SqlBackend a) => TryFrom (Psql.Key a) Natural where tryFrom :: Key a -> Either (TryFromException (Key a) Natural) Natural tryFrom = Int64 -> Either (TryFromException Int64 Natural) Natural forall source target. (TryFrom source target, 'False ~ (source == target)) => source -> Either (TryFromException source target) target tryFrom (Int64 -> Either (TryFromException Int64 Natural) Natural) -> (Key a -> Int64) -> Key a -> Either (TryFromException (Key a) Natural) Natural forall through source target. ('False ~ (source == through), 'False ~ (through == target)) => (through -> Either (TryFromException through target) target) -> (source -> through) -> source -> Either (TryFromException source target) target `composeTryLhs` Key a -> Int64 forall record. ToBackendKey SqlBackend record => Key record -> Int64 Psql.fromSqlKey instance (Psql.ToBackendKey Psql.SqlBackend a) => TryFrom Natural (Psql.Key a) where tryFrom :: Natural -> Either (TryFromException Natural (Key a)) (Key a) tryFrom = Int64 -> Key a forall record. ToBackendKey SqlBackend record => Int64 -> Key record Psql.toSqlKey (Int64 -> Key a) -> (Natural -> Either (TryFromException Natural Int64) Int64) -> Natural -> Either (TryFromException Natural (Key a)) (Key a) forall through source target. ('False ~ (source == through), 'False ~ (through == target)) => (through -> target) -> (source -> Either (TryFromException source through) through) -> source -> Either (TryFromException source target) target `composeTryRhs` Natural -> Either (TryFromException Natural Int64) Int64 forall source target. (TryFrom source target, 'False ~ (source == target)) => source -> Either (TryFromException source target) target tryFrom instance Out SomeException where docPrec :: Int -> SomeException -> Doc docPrec Int _ = String -> Doc PP.text (String -> Doc) -> (SomeException -> String) -> SomeException -> Doc forall b c a. (b -> c) -> (a -> b) -> a -> c . SomeException -> String forall b a. (Show a, IsString b) => a -> b Universum.show doc :: SomeException -> Doc doc = Int -> SomeException -> Doc forall a. Out a => Int -> a -> Doc docPrec Int 0 instance From Word32 (Vout 'Funding) instance From ByteString (TxId 'Funding) instance TryFrom Integer (Vout 'Funding) where tryFrom :: Integer -> Either (TryFromException Integer (Vout 'Funding)) (Vout 'Funding) tryFrom = forall source target. (From source target, 'False ~ (source == target)) => source -> target from @Word32 (Word32 -> Vout 'Funding) -> (Integer -> Either (TryFromException Integer Word32) Word32) -> Integer -> Either (TryFromException Integer (Vout 'Funding)) (Vout 'Funding) forall through source target. ('False ~ (source == through), 'False ~ (through == target)) => (through -> target) -> (source -> Either (TryFromException source through) through) -> source -> Either (TryFromException source target) target `composeTryRhs` Integer -> Either (TryFromException Integer Word32) Word32 forall source target. (TryFrom source target, 'False ~ (source == target)) => source -> Either (TryFromException source target) target tryFrom instance PathPiece UTCTime where fromPathPiece :: Text -> Maybe UTCTime fromPathPiece :: Text -> Maybe UTCTime fromPathPiece = String -> Maybe UTCTime Time.parseISO8601 (String -> Maybe UTCTime) -> (Text -> String) -> Text -> Maybe UTCTime forall b c a. (b -> c) -> (a -> b) -> a -> c . Text -> String unpack toPathPiece :: UTCTime -> Text toPathPiece :: UTCTime -> Text toPathPiece = String -> Text pack (String -> Text) -> (UTCTime -> String) -> UTCTime -> Text forall b c a. (b -> c) -> (a -> b) -> a -> c . UTCTime -> String Time.formatISO8601 instance ToMessage MSat where toMessage :: MSat -> Text toMessage = Int -> Rational -> Text T.displayRational Int 1 (Rational -> Text) -> (MSat -> Rational) -> MSat -> Text forall b c a. (b -> c) -> (a -> b) -> a -> c . (Rational -> Rational -> Rational forall a. Fractional a => a -> a -> a / Rational 1000) (Rational -> Rational) -> (MSat -> Rational) -> MSat -> Rational forall b c a. (b -> c) -> (a -> b) -> a -> c . forall through source target. (From source through, From through target, 'False ~ (source == through), 'False ~ (through == target)) => source -> target via @Integer (Word64 -> Rational) -> (MSat -> Word64) -> MSat -> Rational forall b c a. (b -> c) -> (a -> b) -> a -> c . forall target source. (From source target, 'False ~ (source == target)) => source -> target into @Word64 instance Out (Ratio Natural) where docPrec :: Int -> Ratio Natural -> Doc docPrec Int x = Int -> Rational -> Doc forall a. Out a => Int -> a -> Doc docPrec Int x (Rational -> Doc) -> (Ratio Natural -> Rational) -> Ratio Natural -> Doc forall b c a. (b -> c) -> (a -> b) -> a -> c . forall target source. (From source target, 'False ~ (source == target)) => source -> target into @Rational doc :: Ratio Natural -> Doc doc = Int -> Ratio Natural -> Doc forall a. Out a => Int -> a -> Doc docPrec Int 0 instance Out (Psql.BackendKey Psql.SqlBackend)