Hi cafe, 

I'm  trying to interface BTCe and get my account info.

I have found following peace of code, which I would like to build on top: http://pastebin.com/AfDt8jcs

I have added to the request a POST method, but I'm still getting error from BTCe:
"{\"success\":0,\"error\":\"invalid nonce parameter; on key:0, you sent:\"}"

The API is documented here: https://btc-e.com/api/documentation
In short:

Authorization is performed by sending the following HTTP Headers:

Key — API key

Sign — POST data (?param=val&param1=val1) signed by a secret key according to HMAC-SHA512 method;

Sent on https://btc-e.com/tapi .

All requests must also include a special nonce POST parameter with increment integer. (>0)


The method name is sent via POST parameter method.

All the method parameters are sent via POST.






{-# LANGUAGE OverloadedStrings #-}
 
import Network.HTTP.Conduit
import Network.HTTP.Types.Header
 
import Data.Word
import Data.ByteString.Lazy(pack)
import qualified Data.ByteString.Char8 as B
 
import Data.Digest.Pure.SHA
import Data.Time.Clock.POSIX

-------------------------------------------------------------------------------
 
toWord8 :: String -> [Word8]
toWord8 = Prelude.map (fromIntegral . fromEnum)
 
-------------------------------------------------------------------------------
 
key :: B.ByteString
key = "key"
 
secret :: String
secret = "secret"
 
url :: String
url = "https://btc-e.com/tapi"
 
-------------------------------------------------------------------------------
 
querystring :: Int -> String
querystring nonce = "?method=getInfo&nonce=" ++ show nonce
 
sign :: Int -> B.ByteString
sign nonce = B.pack $ show $
  hmacSha512 (pack $ toWord8 secret) (pack $ toWord8 $ querystring nonce)
 
main :: IO ()
main = do
  nonce <- fmap floor getPOSIXTime
  putStrLn $ url ++ (querystring nonce)
  ticker <- parseUrl $ url ++ (querystring nonce)
  let request = ticker
        { secure = True
        , method = "POST"
        , requestHeaders = (requestHeaders ticker)  
                           ++ [ ("Content-Type", "application/x-www-form-urlencoded")
                              , ("Host", "btc-e.com")
                              , ("User-Agent", "Haskell Trading Robot")
                              , ("Key", key)
                              , ("Sign", sign nonce)]}
  putStrLn $ show request
  response <- withManager $ httpLbs request
  print $ responseBody response






any ideas more than welcome
cheers,
miro