servant/doc/tutorial/Client.lhs

150 lines
5.1 KiB
Plaintext
Raw Normal View History

2016-01-27 22:58:38 +01:00
# Deriving Haskell functions to query an API
2016-01-25 14:11:40 +01:00
While defining handlers that serve an API has a lot to it, querying an API is simpler: we do not care about what happens inside the webserver, we just need to know how to talk to it and get a response back. Except that we usually have to write the querying functions by hand because the structure of the API isn't a first class citizen and can't be inspected to generate a bunch of client-side functions.
*servant* however has a way to inspect API, because APIs are just Haskell types and (GHC) Haskell lets us do quite a few things with types. In the same way that we look at an API type to deduce the types the handlers should have, we can inspect the structure of the API to *derive* Haskell functions that take one argument for each occurence of `Capture`, `ReqBody`, `QueryParam`
and friends. By *derive*, we mean that there's no code generation involved, the functions are defined just by the structure of the API type.
The source for this tutorial section is a literate haskell file, so first we
need to have some language extensions and imports:
2016-01-27 22:28:58 +01:00
``` haskell
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE TypeOperators #-}
module Client where
2016-01-28 13:22:20 +01:00
import Control.Monad.Trans.Except
2016-01-27 22:28:58 +01:00
import Data.Aeson
import Data.Proxy
import GHC.Generics
2016-01-28 13:22:20 +01:00
import Network.HTTP.Client (Manager, newManager, defaultManagerSettings)
2016-01-27 22:28:58 +01:00
import Servant.API
import Servant.Client
2016-01-28 13:22:20 +01:00
import System.IO.Unsafe
2016-01-27 22:28:58 +01:00
```
2016-01-25 14:11:40 +01:00
Also, we need examples for some domain specific data types:
2016-01-27 22:28:58 +01:00
``` haskell
data Position = Position
{ x :: Int
, y :: Int
} deriving (Show, Generic)
instance FromJSON Position
newtype HelloMessage = HelloMessage { msg :: String }
deriving (Show, Generic)
instance FromJSON HelloMessage
data ClientInfo = ClientInfo
{ clientName :: String
, clientEmail :: String
, clientAge :: Int
, clientInterestedIn :: [String]
} deriving Generic
instance ToJSON ClientInfo
data Email = Email
{ from :: String
, to :: String
, subject :: String
, body :: String
} deriving (Show, Generic)
instance FromJSON Email
```
2016-01-25 14:11:40 +01:00
Enough chitchat, let's see an example. Consider the following API type from the previous section:
2016-01-27 22:28:58 +01:00
``` haskell
type API = "position" :> Capture "x" Int :> Capture "y" Int :> Get '[JSON] Position
:<|> "hello" :> QueryParam "name" String :> Get '[JSON] HelloMessage
:<|> "marketing" :> ReqBody '[JSON] ClientInfo :> Post '[JSON] Email
```
2016-01-25 14:11:40 +01:00
What we are going to get with *servant-client* here is 3 functions, one to query each endpoint:
2016-01-27 22:28:58 +01:00
``` haskell
position :: Int -- ^ value for "x"
-> Int -- ^ value for "y"
2016-01-28 13:22:20 +01:00
-> ExceptT ServantError IO Position
2016-01-27 22:28:58 +01:00
hello :: Maybe String -- ^ an optional value for "name"
2016-01-28 13:22:20 +01:00
-> ExceptT ServantError IO HelloMessage
2016-01-27 22:28:58 +01:00
marketing :: ClientInfo -- ^ value for the request body
2016-01-28 13:22:20 +01:00
-> ExceptT ServantError IO Email
2016-01-27 22:28:58 +01:00
```
2016-01-25 14:11:40 +01:00
Each function makes available as an argument any value that the response may depend on, as evidenced in the API type. How do we get these functions? Just give a `Proxy` to your API and a host to make the requests to:
2016-01-27 22:28:58 +01:00
``` haskell
api :: Proxy API
api = Proxy
2016-01-28 13:22:20 +01:00
{-# NOINLINE __manager #-}
__manager :: Manager
__manager = unsafePerformIO $ newManager defaultManagerSettings
position :<|> hello :<|> marketing =
client api (BaseUrl Http "localhost" 8081 "") __manager
2016-01-27 22:28:58 +01:00
```
2016-01-25 14:11:40 +01:00
As you can see in the code above, we just "pattern match our way" to these functions. If we try to derive less or more functions than there are endpoints in the API, we obviously get an error. The `BaseUrl` value there is just:
2016-01-27 22:26:59 +01:00
``` haskell ignore
2016-01-25 14:11:40 +01:00
-- | URI scheme to use
data Scheme =
Http -- ^ http://
| Https -- ^ https://
deriving
-- | Simple data type to represent the target of HTTP requests
-- for servant's automatically-generated clients.
data BaseUrl = BaseUrl
{ baseUrlScheme :: Scheme -- ^ URI scheme to use
, baseUrlHost :: String -- ^ host (eg "haskell.org")
, baseUrlPort :: Int -- ^ port (eg 80)
}
```
That's it. Let's now write some code that uses our client functions.
2016-01-27 22:28:58 +01:00
``` haskell
2016-01-28 13:22:20 +01:00
queries :: ExceptT ServantError IO (Position, HelloMessage, Email)
2016-01-27 22:28:58 +01:00
queries = do
pos <- position 10 10
2016-01-28 13:22:20 +01:00
message <- hello (Just "servant")
2016-01-27 22:28:58 +01:00
em <- marketing (ClientInfo "Alp" "alp@foo.com" 26 ["haskell", "mathematics"])
2016-01-28 13:22:20 +01:00
return (pos, message, em)
2016-01-27 22:28:58 +01:00
run :: IO ()
run = do
2016-01-28 13:22:20 +01:00
res <- runExceptT queries
2016-01-27 22:28:58 +01:00
case res of
Left err -> putStrLn $ "Error: " ++ show err
2016-01-28 13:22:20 +01:00
Right (pos, message, em) -> do
2016-01-27 22:28:58 +01:00
print pos
2016-01-28 13:22:20 +01:00
print message
2016-01-27 22:28:58 +01:00
print em
```
2016-01-25 14:11:40 +01:00
You can now run `dist/build/tutorial/tutorial 8` (the server) and
`dist/build/t8-main/t8-main` (the client) to see them both in action.
``` bash
$ dist/build/tutorial/tutorial 8
# and in another terminal:
$ dist/build/t8-main/t8-main
Position {x = 10, y = 10}
HelloMessage {msg = "Hello, servant"}
Email {from = "great@company.com", to = "alp@foo.com", subject = "Hey Alp, we miss you!", body = "Hi Alp,\n\nSince you've recently turned 26, have you checked out our latest haskell, mathematics products? Give us a visit!"}
```
The types of the arguments for the functions are the same as for (server-side) request handlers. You now know how to use *servant-client*!