Bring parse call into common logic.
[haskell-cryptsy-api.git] / Cryptsy / API / Public / OrderData.hs
blob85df3c4065572b33bb9ce14da8a6d7030477c37c
1 {-# LANGUAGE FlexibleContexts #-}
2 module Cryptsy.API.Public.OrderData
3 ( GOrderData(..), OrderData
4 , withComponents, withOrderBook
5 , getOrderData, orderData, jsonOrderData
6 , module Cryptsy.API.Public.OrderBook
7 -- |Re-export from Cryptsy.API.Public
8 , CryptsyNum(..), Parser, Text, Value
9 -- |Re-export from Data.Aeson
10 , FromJSON(..), Object
11 -- |Re-exported from Data.HashMap.Strict
12 , HashMap
14 where
16 -- aeson
17 import Data.Aeson (FromJSON(..), Object, withObject)
19 -- base
20 import Control.Applicative (pure)
21 import Data.Function (($), (.))
22 import Data.Functor (fmap, (<$>))
23 import Data.String (String)
24 import Data.Traversable (mapM)
25 import Prelude ()
26 import Text.Show (Show)
28 -- unordered-containers
29 import Data.HashMap.Strict (HashMap)
31 -- this package
32 import Cryptsy.API.Public
33 import Cryptsy.API.Public.OrderBook (GOrderBook(..), OrderBook)
35 -- |general order data parameterized by types for prices, quantities,
36 -- and totals (price * quantity)
37 newtype GOrderData p q t =
38 OrderData { orderbooks :: HashMap Text (GOrderBook p q t) }
39 deriving Show
41 -- |default order data
42 type OrderData = GOrderData CryptsyNum CryptsyNum CryptsyNum
44 instance (FromJSON p, FromJSON q, FromJSON t) =>
45 FromJSON (GOrderData p q t)
46 where
47 parseJSON = withObject "OrderData" $ withComponents parseJSON
49 -- |Build parser for multiple orderbooks from parser for single orderbook.
50 withComponents :: (Value -> Parser (GOrderBook p q t)) -- ^ orderbook parser
51 -> Object -> Parser (GOrderData p q t)
52 withComponents parseBook = fmap OrderData <$> mapM parseBook
54 -- |Build parser for multiple orderbooks from parser for single orderbook
55 -- object.
56 withOrderBook :: (Object -> Parser (GOrderBook p q t)) -- ^ orderbook parser
57 -> Object -> Parser (GOrderData p q t)
58 withOrderBook parseBook = withComponents (withObject "OrderBook" parseBook)
60 -- |URL for API call
61 orderdataURL :: String
62 orderdataURL = pubURL "orderdata"
64 {-|
65 "Raw" request, does not convert the JSON value, but simply returns the JSON
66 value bound to the "return" key from the response body.
68 getOrderData :: PubCryptsy Value
69 getOrderData = pubCryptsy orderdataURL pure
71 -- |"Cooked" request, extracts the JSON object bound to the "return" key and
72 -- converts it.
73 orderData :: (Object -> Parser (GOrderData p q t)) -> PubCryptsy (GOrderData p q t)
74 orderData = pubCryptsy orderdataURL . withObject "OrderData"
76 -- |"Cooked" request with implicit parser.
77 jsonOrderData :: FromJSON (GOrderData p q t) => PubCryptsy (GOrderData p q t)
78 jsonOrderData = pubCryptsy orderdataURL parseJSON