Portability | portable |
---|---|
Stability | experimental |
Maintainer | Joel Lehtonen <joel.lehtonen+curlaeson@iki.fi> |
Safe Haskell | None |
Functions for communicating with JSON over HTTP connection.
- curlAesonGet :: FromJSON a => URLString -> IO a
- curlAesonGetWith :: (Value -> Parser a) -> URLString -> IO a
- curlAeson :: ToJSON a => (Value -> Parser b) -> String -> URLString -> [CurlOption] -> Maybe a -> IO b
- cookie :: String -> String -> CurlOption
- rawJson :: String -> Maybe Value
- (...) :: FromJSON b => Parser Object -> Text -> Parser b
- noData :: Maybe Value
- data CurlAesonException = CurlAesonException {}
How to use this library
To get bid and ask levels as a pair from a Bitcoin exchange using its public API:
{-# LANGUAGE OverloadedStrings #-} import Control.Monad import Data.Aeson import Network.Curl.Aeson ticker ::IO
(Double
,Double
) ticker =curlAesonGetWith
p "https://bitcoin-central.net/api/v1/ticker/eur" where p (Object
o) = do bid <- o.:
"bid" ask <- o.:
"ask"return
(bid,ask) p _ =mzero
The same as above, but we define our own data type which is an instance of FromJSON:
{-# LANGUAGE OverloadedStrings #-} import Control.Applicative import Control.Monad import Data.Aeson import Network.Curl.Aeson data Ticker = Ticker { bid ::Double
, ask ::Double
} deriving (Show
) instanceFromJSON
Ticker where parseJSON (Object
o) = Ticker<$>
o.:
"bid"<*>
o.:
"ask" parseJSON _ =mzero
ticker ::IO
Ticker ticker =curlAesonGet
"https://bitcoin-central.net/api/v1/ticker/eur"
Sending HTTP request
curlAesonGet :: FromJSON a => URLString -> IO aSource
Shorthand for doing just a HTTP GET request and parsing the output to any FromJSON instance.
curlAesonGetWith :: (Value -> Parser a) -> URLString -> IO aSource
Shorthand for doing just a HTTP GET request and parsing the output with given parser p.
:: ToJSON a | |
=> (Value -> Parser b) | Parser for response. Use |
-> String | Request method |
-> URLString | Request URL |
-> [CurlOption] | Session cookies, or other cURL options. Use empty list if you don't need any. |
-> Maybe a | JSON data to send, or Nothing when sending request without any content. |
-> IO b | Received JSON data |
Send single HTTP request.
The request automatically has Content-type: application/json
header if you pass any data. This function is lenient on response
content type: everything is accepted as long as it is parseable
with decode
.
If you need authentication, you need to pass session cookie or
other means of authentication tokens via CurlOption
list.
Helper functions
cookie :: String -> String -> CurlOptionSource
Single cookie of given key and value.
rawJson :: String -> Maybe ValueSource
Useful for just giving the JSON as string when it is static anyway and doesn't need to be programmatically crafted.
:: FromJSON b | |
=> Parser Object | Parser to JSON object to look into |
-> Text | Key to look for |
-> Parser b | Parser to the resulting field |
Helper function for writing parsers for JSON objects which are not needed to be parsed completely.
In this example we are parsing JSON from
http://json.org/example.html. Note the use of the
OverloadedStrings
language extension which enables Text
values
to be written as string literals.
p (Object
o) =pure
obj...
"glossary"...
"title" p _ =mzero
To avoid ambiguity in type checker you may pass this value instead
of Nothing to curlAeson
.
Exception handling
data CurlAesonException Source
This exception is is thrown when Curl doesn't finish cleanly or the parsing of JSON response fails.