Safe Haskell | None |
---|---|
Language | Haskell2010 |
A small library for querying a Web API.
import Data.Text.IO as T import Network.HTTP.Query main = do let api = "http://www.example.com/api/1" endpoint = api +/+ "search" res <- webAPIQuery endpoint $ makeKey "q" "needle" T.putStrLn $ case lookupKey "results" res of Nothing -> fromMaybe "search failed" $ lookupKey "error" res Just results -> lookupKey' "location" results
Synopsis
- withURLQuery :: String -> Query -> (Request -> a) -> a
- webAPIQuery :: (MonadIO m, FromJSON a) => String -> Query -> m a
- apiQueryURI :: String -> Query -> URI
- (+/+) :: String -> String -> String
- type Query = [QueryItem]
- type QueryItem = (ByteString, Maybe ByteString)
- maybeKey :: String -> Maybe String -> Query
- makeKey :: String -> String -> Query
- makeItem :: String -> String -> QueryItem
- lookupKey :: FromJSON a => Text -> Object -> Maybe a
- lookupKeyEither :: FromJSON a => Text -> Object -> Either String a
- lookupKey' :: FromJSON a => Text -> Object -> a
Queries
withURLQuery :: String -> Query -> (Request -> a) -> a Source #
Sets up an API request for some action
Low-level web api query
(+/+) :: String -> String -> String infixr 5 Source #
Combine two path segments with a slash
"abc" +/+ "def" == "abc/def" "abc/" +/+ "def" == "abc/def" "abc" +/+ "/def" == "abc/def"
Query parameters
Query.
General form: a=b&c=d
, but if the value is Nothing, it becomes
a&c=d
.
type QueryItem = (ByteString, Maybe ByteString) #
Query item