{-# LANGUAGE OverloadedStrings #-} module Main where import Control.Monad.IO.Class (liftIO) import Data.Maybe (fromJust) import Data.Time (defaultTimeLocale, parseTimeOrError) import Data.UUID (fromText) import CoinbasePro.Authenticated import CoinbasePro.Authenticated.Accounts import CoinbasePro.Authenticated.Headers import CoinbasePro.Authenticated.Orders import CoinbasePro.Authenticated.Report import CoinbasePro.Authenticated.Request import CoinbasePro.Environment import CoinbasePro.MarketData.Types hiding (time) import CoinbasePro.Request import CoinbasePro.Types hiding (time) import CoinbasePro.Unauthenticated main :: IO () main = do -- run Sandbox (stats btcusd) >>= print -- run Sandbox (candles btcusd Nothing Nothing Minute) >>= print -- run Sandbox (trades btcusd) >>= print -- run Sandbox time >>= print -- run Sandbox products >>= print -- run Sandbox (aggregateOrderBook btcusd (Just Best)) >>= print -- run Sandbox (aggregateOrderBook btcusd (Just TopFifty)) >>= print -- run Sandbox (fullOrderBook btcusd) >>= print runCbAuthT (run Sandbox) cpc $ do -- resp <- createReport fillReportReq getReport rid >>= liftIO . print -- profiles Nothing >>= liftIO . print -- profile "94fa1f9e-131f-4295-b0d5-695b8a92c382" >>= liftIO . print -- accounts >>= liftIO . print -- account aid >>= liftIO . print -- accountHistory aid >>= liftIO . print -- fills (Just btcusd) Nothing >>= liftIO . print -- listOrders (Just [All]) (Just btcusd) >>= liftIO . print -- placeOrder Nothing btcusd Sell (Size 0.001) (Price 99999.00) True Nothing Nothing Nothing >>= liftIO . print -- placeOrder Nothing btcusd Buy (Size 1.0) (Price 1.00) True Nothing Nothing Nothing >>= liftIO . print -- cancelAll (Just btcusd) >>= liftIO . print where accessKey = CBAccessKey "6e5972897a617f9c7807190c72019f2e" secretKey = CBSecretKey "1MJfkRmYd+AgSo6SeGlKD1XZS7AkTikEagz0EKKn6hNHzY9Ff7+H2cc76E0vbzo+0yvwCNCBsIedi0QXwRSdGw==" passphrase = CBAccessPassphrase "83f2vnptwln" cpc = CoinbaseProCredentials accessKey secretKey passphrase aid = AccountId "74598a56-abef-4ffe-8d98-dd3c878d718d" btcusd = ProductId "BTC-USD" startDate = parseTimeOrError False defaultTimeLocale "%Y-%m-%d" "2020-01-01" endDate = parseTimeOrError False defaultTimeLocale "%Y-%m-%d" "2021-01-01" actReportReq = accountsReportRequest aid Nothing startDate endDate Nothing Nothing fillReportReq = fillsReportRequest btcusd Nothing startDate endDate Nothing Nothing rid = ReportId $ fromJust $ fromText "5b99f31a-7bcb-43f4-b8b3-7e1299e67a3e"