module PaymentChannel.Types
(
    
    FundingTxInfo(..)
  , ChanParams(..)
  , PaymentChannel(..), PayChan
  , PaymentChannelRecv(..)
  , SharedSecret, HasSharedSecret(..) 
  , fundingAddress
  , clientChangeAddress
  , getFundingAmount
    
  , ClientPayChanI(..)
    
  , ServerPayChan, ServerPayChanG(rpcMetadata)
  , PayChanStatus(..), MetadataI(..), OpenError(..)
  , S.getChannelStatus, S.setChannelStatus
  , S.markAsBusy, S.isReadyForPayment
  , ServerSettings(..), Hour(..)
  
    
  , ServerPayChanX
  , S.mkExtendedDerivRpc
  , Script.UserParams(..)
  , Script.deriveRecvPub
    
  , SignedPayment
    
  , ClosedServerChanI, ClosedServerChan, ClosedServerChanX
  , getClosedState, cscClosingPayment
  , SettleTx
    
  , PayChanError(..), IsPayChanError(..)
    
  , module X
  , module Bitcoin.Fee
  , PaymentValueSpec(..)
  , Capped(..)
    
  , SendPubKey(..),RecvPubKey(..),IsPubKey(..),HasSendPubKey(..),HasRecvPubKey(..)
    
  , module Bitcoin.SpendCond.Util
  , fromDate
  , getChanState
  , clientChangeVal
  , toHaskoinTx
)
where
import PaymentChannel.Internal.Types
import PaymentChannel.Internal.Receiver.Types
import PaymentChannel.Internal.Metadata.Util
import PaymentChannel.Internal.Serialization ()
import PaymentChannel.Internal.Class.Value     (HasValue(..))
import PaymentChannel.Internal.Receiver.Open   (OpenError(..))
import Bitcoin.SpendCond.Util
import Bitcoin.Types                  as X hiding (fromDate)
import Bitcoin.Conversion (toHaskoinTx)
import qualified PaymentChannel.Internal.Receiver.Util as S
import qualified PaymentChannel.Internal.ChanScript as Script
import PaymentChannel.Internal.Error 
import Bitcoin.Fee
import qualified  Network.Haskoin.Crypto as HC
class HasSignedPayChanState a where
    getChanState :: a -> PayChanState BtcSig
instance HasSignedPayChanState ClientPayChan where
    getChanState = spcState
instance HasSignedPayChanState (ServerPayChanI s) where
    getChanState = rpcState
    
class HasPayChanState a where
    getPayChanState :: a -> PayChanState ()
instance HasPayChanState (ClientPayChanI a) where
    getPayChanState = mapSigData (const ()) . spcState
instance HasPayChanState (ServerPayChanG kd a) where
    getPayChanState = mapSigData (const ()) . rpcState
    
getFundingAmount  :: HasPayChanState a => a -> BtcAmount
getFundingAmount = fundingValue . pcsPayment . getPayChanState
fundingAddress :: HasPayChanState a => a -> HC.Address
fundingAddress = Script.getP2SHFundingAddress . pairRedeemScript . pcsPayment . getPayChanState
clientChangeAddress :: HasPayChanState a => a -> HC.Address
clientChangeAddress = clientChangeAddr . pcsPayment . getPayChanState
class HasSignedPayChanState a => PaymentChannel a where
    
    valueToMe :: a -> BtcAmount
    
    channelValueLeft :: a -> BtcAmount
    
    getStatePayment :: a -> SignedPayment
instance PaymentChannel ClientPayChan where
    valueToMe = clientChangeVal . pcsPayment . spcState
    channelValueLeft = valueToMe
    getStatePayment = pcsPayment . spcState
instance PaymentChannel (ServerPayChanI s) where
    valueToMe (MkServerPayChan s _) = valueOf s
    channelValueLeft = clientChangeVal . getStatePayment
    getStatePayment = pcsPayment . rpcState
class PaymentChannel a => PaymentChannelRecv a where
    
    clientTotalValueSent :: a -> BtcAmount
instance PaymentChannelRecv (ServerPayChanI (MetadataI a)) where
    clientTotalValueSent = metaTotalValXfer . rpcMetadata
class HasSharedSecret a where
    getSecret :: a -> SharedSecret
instance HasSharedSecret (PayChanState a)       where getSecret = pcsSecret
instance HasSharedSecret (ServerPayChanG sd s)  where getSecret = getSecret . rpcState
instance HasSharedSecret ClientPayChan          where getSecret = getSecret . spcState
class PaymentChannel a => PayChan a
class PaymentValueSpec val where
    paymentValue :: BtcAmount           
                 -> ServerSettings
                 -> val                 
                 -> BtcAmount           
instance PaymentValueSpec BtcAmount where
    paymentValue _ = const id
instance PaymentValueSpec (Capped BtcAmount) where
    paymentValue valueAvailable ServerSettings{..} (Capped amt) =
        if amt >= valueAvailable
            then valueAvailable
            else min amt (valueAvailable - serverConfDustLimit)