module Network.Bitcoin.Api.Wallet where
import           Data.Aeson
import           Data.Aeson.Types
import qualified Data.HashMap.Strict                          as HM
import qualified Data.Text                                    as T
import qualified Data.Bitcoin.Types                           as BT
import qualified Network.Bitcoin.Api.Internal                 as I
import qualified Network.Bitcoin.Api.Types                    as T
import           Network.Bitcoin.Api.Types.UnspentTransaction (UnspentTransaction)
listUnspent :: T.Client
            -> IO [UnspentTransaction]
listUnspent client = listUnspentWith client 1 9999999
listUnspentWith :: T.Client 
                -> Integer  
                -> Integer  
                -> IO [UnspentTransaction]
listUnspentWith client confMin confMax =
  let configuration = [toJSON confMin, toJSON confMax, emptyArray]
  in I.call client "listunspent" configuration
listAccounts :: T.Client
             -> IO [(BT.Account, BT.Btc)]
listAccounts client = listAccountsWith client 1 False
listAccountsWith :: T.Client 
                 -> Integer  
                 -> Bool     
                 -> IO [(BT.Account, BT.Btc)]
listAccountsWith client confirmations watchOnly =
  let configuration        = [toJSON confirmations, toJSON watchOnly]
  in
    return . HM.toList =<< I.call client "listaccounts" configuration
newAddress :: T.Client         
           -> IO BT.Address    
newAddress client =
  I.call client "getnewaddress" emptyArray
newAddressWith :: T.Client      
               -> BT.Account    
               -> IO BT.Address 
newAddressWith client account =
  let configuration = [account]
  in I.call client "getnewaddress" configuration
newChangeAddress :: T.Client         
                 -> IO BT.Address    
newChangeAddress client =
  I.call client "getrawchangeaddress" emptyArray
getAddressAccount :: T.Client
                  -> BT.Address
                  -> IO BT.Account
getAddressAccount client address =
  let configuration = [address]
  in I.call client "getaccount" configuration