Remove bird-tracks

This commit is contained in:
Julian K. Arni 2016-01-27 22:28:58 +01:00 committed by Sönke Hahn
parent 7af73d63ea
commit 8b1bf02af8
5 changed files with 886 additions and 740 deletions

View file

@ -6,13 +6,15 @@ toc: true
The source for this tutorial section is a literate haskell file, so first we
need to have some language extensions and imports:
> {-# LANGUAGE DataKinds #-}
> {-# LANGUAGE TypeOperators #-}
>
> module ApiType where
>
> import Data.Text
> import Servant.API
``` haskell
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeOperators #-}
module ApiType where
import Data.Text
import Servant.API
```
Consider the following informal specification of an API:
@ -29,14 +31,16 @@ getting some client libraries, and documentation (and in the future, who knows
How would we describe it with servant? As mentioned earlier, an endpoint
description is a good old Haskell **type**:
> type UserAPI = "users" :> QueryParam "sortby" SortBy :> Get '[JSON] [User]
>
> data SortBy = Age | Name
>
> data User = User {
> name :: String,
> age :: Int
> }
``` haskell
type UserAPI = "users" :> QueryParam "sortby" SortBy :> Get '[JSON] [User]
data SortBy = Age | Name
data User = User {
name :: String,
age :: Int
}
```
Let's break that down:
@ -61,8 +65,10 @@ equivalent to `/`, but sometimes it just lets you chain another combinator.
We can also describe APIs with multiple endpoints by using the `:<|>`
combinators. Here's an example:
> type UserAPI2 = "users" :> "list-all" :> Get '[JSON] [User]
> :<|> "list-all" :> "users" :> Get '[JSON] [User]
``` haskell
type UserAPI2 = "users" :> "list-all" :> Get '[JSON] [User]
:<|> "list-all" :> "users" :> Get '[JSON] [User]
```
*servant* provides a fair amount of combinators out-of-the-box, but you can
always write your own when you need it. Here's a quick overview of all the
@ -78,9 +84,11 @@ As you've already seen, you can use type-level strings (enabled with the
`DataKinds` language extension) for static path fragments. Chaining
them amounts to `/`-separating them in a URL.
> type UserAPI3 = "users" :> "list-all" :> "now" :> Get '[JSON] [User]
> -- describes an endpoint reachable at:
> -- /users/list-all/now
``` haskell
type UserAPI3 = "users" :> "list-all" :> "now" :> Get '[JSON] [User]
-- describes an endpoint reachable at:
-- /users/list-all/now
```
`Delete`, `Get`, `Patch`, `Post` and `Put`
------------------------------------------
@ -99,8 +107,10 @@ data Put (contentTypes :: [*]) a
An endpoint ends with one of the 5 combinators above (unless you write your
own). Examples:
> type UserAPI4 = "users" :> Get '[JSON] [User]
> :<|> "admins" :> Get '[JSON] [User]
``` haskell
type UserAPI4 = "users" :> Get '[JSON] [User]
:<|> "admins" :> Get '[JSON] [User]
```
`Capture`
---------
@ -127,13 +137,15 @@ class, which the captured value must be an instance of.
Examples:
> type UserAPI5 = "user" :> Capture "userid" Integer :> Get '[JSON] User
> -- equivalent to 'GET /user/:userid'
> -- except that we explicitly say that "userid"
> -- must be an integer
>
> :<|> "user" :> Capture "userid" Integer :> Delete '[] ()
> -- equivalent to 'DELETE /user/:userid'
``` haskell
type UserAPI5 = "user" :> Capture "userid" Integer :> Get '[JSON] User
-- equivalent to 'GET /user/:userid'
-- except that we explicitly say that "userid"
-- must be an integer
:<|> "user" :> Capture "userid" Integer :> Delete '[] ()
-- equivalent to 'DELETE /user/:userid'
```
`QueryParam`, `QueryParams`, `QueryFlag`, `MatrixParam`, `MatrixParams` and `MatrixFlag`
----------------------------------------------------------------------------------------
@ -179,11 +191,13 @@ data MatrixFlag (sym :: Symbol)
Examples:
> type UserAPI6 = "users" :> QueryParam "sortby" SortBy :> Get '[JSON] [User]
> -- equivalent to 'GET /users?sortby={age, name}'
>
> :<|> "users" :> MatrixParam "sortby" SortBy :> Get '[JSON] [User]
> -- equivalent to 'GET /users;sortby={age, name}'
``` haskell
type UserAPI6 = "users" :> QueryParam "sortby" SortBy :> Get '[JSON] [User]
-- equivalent to 'GET /users?sortby={age, name}'
:<|> "users" :> MatrixParam "sortby" SortBy :> Get '[JSON] [User]
-- equivalent to 'GET /users;sortby={age, name}'
```
Again, your handlers don't have to deserialize these things (into, for example,
a `SortBy`). *servant* takes care of it.
@ -212,17 +226,19 @@ data ReqBody (contentTypes :: [*]) a
Examples:
> type UserAPI7 = "users" :> ReqBody '[JSON] User :> Post '[JSON] User
> -- - equivalent to 'POST /users' with a JSON object
> -- describing a User in the request body
> -- - returns a User encoded in JSON
>
> :<|> "users" :> Capture "userid" Integer
> :> ReqBody '[JSON] User
> :> Put '[JSON] User
> -- - equivalent to 'PUT /users/:userid' with a JSON
> -- object describing a User in the request body
> -- - returns a User encoded in JSON
``` haskell
type UserAPI7 = "users" :> ReqBody '[JSON] User :> Post '[JSON] User
-- - equivalent to 'POST /users' with a JSON object
-- describing a User in the request body
-- - returns a User encoded in JSON
:<|> "users" :> Capture "userid" Integer
:> ReqBody '[JSON] User
:> Put '[JSON] User
-- - equivalent to 'PUT /users/:userid' with a JSON
-- object describing a User in the request body
-- - returns a User encoded in JSON
```
Request `Header`s
-----------------
@ -243,7 +259,9 @@ Here's an example where we declare that an endpoint makes use of the
`User-Agent` header which specifies the name of the software/library used by
the client to send the request.
> type UserAPI8 = "users" :> Header "User-Agent" Text :> Get '[JSON] [User]
``` haskell
type UserAPI8 = "users" :> Header "User-Agent" Text :> Get '[JSON] [User]
```
Content types
-------------
@ -257,7 +275,9 @@ Four content-types are provided out-of-the-box by the core *servant* package:
reason you wanted one of your endpoints to make your user data available under
those 4 formats, you would write the API type as below:
> type UserAPI9 = "users" :> Get '[JSON, PlainText, FormUrlEncoded, OctetStream] [User]
``` haskell
type UserAPI9 = "users" :> Get '[JSON, PlainText, FormUrlEncoded, OctetStream] [User]
```
We also provide an HTML content-type, but since there's no single library
that everyone uses, we decided to release 2 packages, *servant-lucid* and
@ -281,7 +301,9 @@ data Headers (ls :: [*]) a
If you want to describe an endpoint that returns a "User-Count" header in each
response, you could write it as below:
> type UserAPI10 = "users" :> Get '[JSON] (Headers '[Header "User-Count" Integer] [User])
``` haskell
type UserAPI10 = "users" :> Get '[JSON] (Headers '[Header "User-Count" Integer] [User])
```
Interoperability with other WAI `Application`s: `Raw`
-----------------------------------------------------
@ -290,14 +312,16 @@ Finally, we also include a combinator named `Raw` that can be used for two reaso
- You want to serve static files from a given directory. In that case you can just say:
> type UserAPI11 = "users" :> Get '[JSON] [User]
> -- a /users endpoint
>
> :<|> Raw
> -- requests to anything else than /users
> -- go here, where the server will try to
> -- find a file with the right name
> -- at the right path
``` haskell
type UserAPI11 = "users" :> Get '[JSON] [User]
-- a /users endpoint
:<|> Raw
-- requests to anything else than /users
-- go here, where the server will try to
-- find a file with the right name
-- at the right path
```
- You more generally want to plug a [WAI `Application`](http://hackage.haskell.org/package/wai)
into your webservice. Static file serving is a specific example of that. The API type would look the

View file

@ -11,75 +11,85 @@ and friends. By *derive*, we mean that there's no code generation involved, the
The source for this tutorial section is a literate haskell file, so first we
need to have some language extensions and imports:
> {-# LANGUAGE DataKinds #-}
> {-# LANGUAGE DeriveGeneric #-}
> {-# LANGUAGE TypeOperators #-}
>
> module Client where
>
> import Control.Monad.Trans.Either
> import Data.Aeson
> import Data.Proxy
> import GHC.Generics
> import Servant.API
> import Servant.Client
``` haskell
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE TypeOperators #-}
module Client where
import Control.Monad.Trans.Either
import Data.Aeson
import Data.Proxy
import GHC.Generics
import Servant.API
import Servant.Client
```
Also, we need examples for some domain specific data types:
> 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
``` 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
```
Enough chitchat, let's see an example. Consider the following API type from the previous section:
> 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
``` 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
```
What we are going to get with *servant-client* here is 3 functions, one to query each endpoint:
> position :: Int -- ^ value for "x"
> -> Int -- ^ value for "y"
> -> EitherT ServantError IO Position
>
> hello :: Maybe String -- ^ an optional value for "name"
> -> EitherT ServantError IO HelloMessage
>
> marketing :: ClientInfo -- ^ value for the request body
> -> EitherT ServantError IO Email
``` haskell
position :: Int -- ^ value for "x"
-> Int -- ^ value for "y"
-> EitherT ServantError IO Position
hello :: Maybe String -- ^ an optional value for "name"
-> EitherT ServantError IO HelloMessage
marketing :: ClientInfo -- ^ value for the request body
-> EitherT ServantError IO Email
```
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:
> api :: Proxy API
> api = Proxy
>
> position :<|> hello :<|> marketing = client api (BaseUrl Http "localhost" 8081)
``` haskell
api :: Proxy API
api = Proxy
position :<|> hello :<|> marketing = client api (BaseUrl Http "localhost" 8081)
```
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:
@ -101,22 +111,24 @@ data BaseUrl = BaseUrl
That's it. Let's now write some code that uses our client functions.
> queries :: EitherT ServantError IO (Position, HelloMessage, Email)
> queries = do
> pos <- position 10 10
> msg <- hello (Just "servant")
> em <- marketing (ClientInfo "Alp" "alp@foo.com" 26 ["haskell", "mathematics"])
> return (pos, msg, em)
>
> run :: IO ()
> run = do
> res <- runEitherT queries
> case res of
> Left err -> putStrLn $ "Error: " ++ show err
> Right (pos, msg, em) -> do
> print pos
> print msg
> print em
``` haskell
queries :: EitherT ServantError IO (Position, HelloMessage, Email)
queries = do
pos <- position 10 10
msg <- hello (Just "servant")
em <- marketing (ClientInfo "Alp" "alp@foo.com" 26 ["haskell", "mathematics"])
return (pos, msg, em)
run :: IO ()
run = do
res <- runEitherT queries
case res of
Left err -> putStrLn $ "Error: " ++ show err
Right (pos, msg, em) -> do
print pos
print msg
print em
```
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.

View file

@ -6,89 +6,99 @@ toc: true
The source for this tutorial section is a literate haskell file, so first we
need to have some language extensions and imports:
> {-# LANGUAGE DataKinds #-}
> {-# LANGUAGE DeriveGeneric #-}
> {-# LANGUAGE FlexibleInstances #-}
> {-# LANGUAGE MultiParamTypeClasses #-}
> {-# LANGUAGE OverloadedStrings #-}
> {-# LANGUAGE TypeOperators #-}
> {-# OPTIONS_GHC -fno-warn-orphans #-}
>
> module Docs where
>
> import Data.ByteString.Lazy (ByteString)
> import Data.Proxy
> import Data.Text.Lazy.Encoding (encodeUtf8)
> import Data.Text.Lazy (pack)
> import Network.HTTP.Types
> import Network.Wai
> import Servant.API
> import Servant.Docs
> import Servant.Server
``` haskell
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeOperators #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module Docs where
import Data.ByteString.Lazy (ByteString)
import Data.Proxy
import Data.Text.Lazy.Encoding (encodeUtf8)
import Data.Text.Lazy (pack)
import Network.HTTP.Types
import Network.Wai
import Servant.API
import Servant.Docs
import Servant.Server
```
And we'll import some things from one of our earlier modules
([Serving an API](/tutorial/server.html)):
> import Server (Email(..), ClientInfo(..), Position(..), HelloMessage(..),
> server3, emailForClient)
``` haskell
import Server (Email(..), ClientInfo(..), Position(..), HelloMessage(..),
server3, emailForClient)
```
Like client function generation, documentation generation amounts to inspecting the API type and extracting all the data we need to then present it in some format to users of your API.
This time however, we have to assist *servant*. While it is able to deduce a lot of things about our API, it can't magically come up with descriptions of the various pieces of our APIs that are human-friendly and explain what's going on "at the business-logic level". A good example to study for documentation generation is our webservice with the `/position`, `/hello` and `/marketing` endpoints from earlier:
> type ExampleAPI = "position" :> Capture "x" Int :> Capture "y" Int :> Get '[JSON] Position
> :<|> "hello" :> QueryParam "name" String :> Get '[JSON] HelloMessage
> :<|> "marketing" :> ReqBody '[JSON] ClientInfo :> Post '[JSON] Email
>
> exampleAPI :: Proxy ExampleAPI
> exampleAPI = Proxy
``` haskell
type ExampleAPI = "position" :> Capture "x" Int :> Capture "y" Int :> Get '[JSON] Position
:<|> "hello" :> QueryParam "name" String :> Get '[JSON] HelloMessage
:<|> "marketing" :> ReqBody '[JSON] ClientInfo :> Post '[JSON] Email
exampleAPI :: Proxy ExampleAPI
exampleAPI = Proxy
```
While *servant* can see e.g. that there are 3 endpoints and that the response bodies will be in JSON, it doesn't know what influence the captures, parameters, request bodies and other combinators have on the webservice. This is where some manual work is required.
For every capture, request body, response body, query param, we have to give some explanations about how it influences the response, what values are possible and the likes. Here's how it looks like for the parameters we have above.
> instance ToCapture (Capture "x" Int) where
> toCapture _ =
> DocCapture "x" -- name
> "(integer) position on the x axis" -- description
>
> instance ToCapture (Capture "y" Int) where
> toCapture _ =
> DocCapture "y" -- name
> "(integer) position on the y axis" -- description
>
> instance ToSample Position Position where
> toSample _ = Just (Position 3 14) -- example of output
>
> instance ToParam (QueryParam "name" String) where
> toParam _ =
> DocQueryParam "name" -- name
> ["Alp", "John Doe", "..."] -- example of values (not necessarily exhaustive)
> "Name of the person to say hello to." -- description
> Normal -- Normal, List or Flag
>
> instance ToSample HelloMessage HelloMessage where
> toSamples _ =
> [ ("When a value is provided for 'name'", HelloMessage "Hello, Alp")
> , ("When 'name' is not specified", HelloMessage "Hello, anonymous coward")
> ]
> -- mutliple examples to display this time
>
> ci :: ClientInfo
> ci = ClientInfo "Alp" "alp@foo.com" 26 ["haskell", "mathematics"]
>
> instance ToSample ClientInfo ClientInfo where
> toSample _ = Just ci
>
> instance ToSample Email Email where
> toSample _ = Just (emailForClient ci)
``` haskell
instance ToCapture (Capture "x" Int) where
toCapture _ =
DocCapture "x" -- name
"(integer) position on the x axis" -- description
instance ToCapture (Capture "y" Int) where
toCapture _ =
DocCapture "y" -- name
"(integer) position on the y axis" -- description
instance ToSample Position Position where
toSample _ = Just (Position 3 14) -- example of output
instance ToParam (QueryParam "name" String) where
toParam _ =
DocQueryParam "name" -- name
["Alp", "John Doe", "..."] -- example of values (not necessarily exhaustive)
"Name of the person to say hello to." -- description
Normal -- Normal, List or Flag
instance ToSample HelloMessage HelloMessage where
toSamples _ =
[ ("When a value is provided for 'name'", HelloMessage "Hello, Alp")
, ("When 'name' is not specified", HelloMessage "Hello, anonymous coward")
]
-- mutliple examples to display this time
ci :: ClientInfo
ci = ClientInfo "Alp" "alp@foo.com" 26 ["haskell", "mathematics"]
instance ToSample ClientInfo ClientInfo where
toSample _ = Just ci
instance ToSample Email Email where
toSample _ = Just (emailForClient ci)
```
Types that are used as request or response bodies have to instantiate the `ToSample` typeclass which lets you specify one or more examples of values. `Capture`s and `QueryParam`s have to instantiate their respective `ToCapture` and `ToParam` classes and provide a name and some information about the concrete meaning of that argument, as illustrated in the code above.
With all of this, we can derive docs for our API.
> apiDocs :: API
> apiDocs = docs exampleAPI
``` haskell
apiDocs :: API
apiDocs = docs exampleAPI
```
`API` is a type provided by *servant-docs* that stores all the information one needs about a web API in order to generate documentation in some format. Out of the box, *servant-docs* only provides a pretty documentation printer that outputs [Markdown](http://en.wikipedia.org/wiki/Markdown), but the [servant-pandoc](http://hackage.haskell.org/package/servant-pandoc) package can be used to target many useful formats.
@ -192,33 +202,37 @@ That lets us see what our API docs look down in markdown, by looking at `markdow
However, we can also add one or more introduction sections to the document. We just need to tweak the way we generate `apiDocs`. We will also convert the content to a lazy `ByteString` since this is what *wai* expects for `Raw` endpoints.
> docsBS :: ByteString
> docsBS = encodeUtf8
> . pack
> . markdown
> $ docsWithIntros [intro] exampleAPI
>
> where intro = DocIntro "Welcome" ["This is our super webservice's API.", "Enjoy!"]
``` haskell
docsBS :: ByteString
docsBS = encodeUtf8
. pack
. markdown
$ docsWithIntros [intro] exampleAPI
where intro = DocIntro "Welcome" ["This is our super webservice's API.", "Enjoy!"]
```
`docsWithIntros` just takes an additional parameter, a list of `DocIntro`s that must be displayed before any endpoint docs.
We can now serve the API *and* the API docs with a simple server.
> type DocsAPI = ExampleAPI :<|> Raw
>
> api :: Proxy DocsAPI
> api = Proxy
>
> server :: Server DocsAPI
> server = Server.server3 :<|> serveDocs
>
> where serveDocs _ respond =
> respond $ responseLBS ok200 [plain] docsBS
>
> plain = ("Content-Type", "text/plain")
>
> app :: Application
> app = serve api server
``` haskell
type DocsAPI = ExampleAPI :<|> Raw
api :: Proxy DocsAPI
api = Proxy
server :: Server DocsAPI
server = Server.server3 :<|> serveDocs
where serveDocs _ respond =
respond $ responseLBS ok200 [plain] docsBS
plain = ("Content-Type", "text/plain")
app :: Application
app = serve api server
```
And if you spin up this server with `dist/build/tutorial/tutorial 10` and go to anywhere else than `/position`, `/hello` and `/marketing`, you will see the API docs in markdown. This is because `serveDocs` is attempted if the 3 other endpoints don't match and systematically succeeds since its definition is to just return some fixed bytestring with the `text/plain` content type.

View file

@ -22,117 +22,131 @@ query your API.
The source for this tutorial section is a literate haskell file, so first we
need to have some language extensions and imports:
> {-# LANGUAGE DataKinds #-}
> {-# LANGUAGE DeriveGeneric #-}
> {-# LANGUAGE OverloadedStrings #-}
> {-# LANGUAGE TypeOperators #-}
>
> module Javascript where
>
> import Control.Monad.IO.Class
> import Data.Aeson
> import Data.Proxy
> import Data.Text (Text)
> import qualified Data.Text as T
> import GHC.Generics
> import Language.Javascript.JQuery
> import Network.Wai
> import Servant
> import Servant.JQuery
> import System.Random
``` haskell
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeOperators #-}
module Javascript where
import Control.Monad.IO.Class
import Data.Aeson
import Data.Proxy
import Data.Text (Text)
import qualified Data.Text as T
import GHC.Generics
import Language.Javascript.JQuery
import Network.Wai
import Servant
import Servant.JQuery
import System.Random
```
Now let's have the API type(s) and the accompanying datatypes.
> type API = "point" :> Get '[JSON] Point
> :<|> "books" :> QueryParam "q" Text :> Get '[JSON] (Search Book)
>
> type API' = API :<|> Raw
>
> data Point = Point
> { x :: Double
> , y :: Double
> } deriving Generic
>
> instance ToJSON Point
>
> data Search a = Search
> { query :: Text
> , results :: [a]
> } deriving Generic
>
> mkSearch :: Text -> [a] -> Search a
> mkSearch = Search
>
> instance ToJSON a => ToJSON (Search a)
>
> data Book = Book
> { author :: Text
> , title :: Text
> , year :: Int
> } deriving Generic
>
> instance ToJSON Book
>
> book :: Text -> Text -> Int -> Book
> book = Book
``` haskell
type API = "point" :> Get '[JSON] Point
:<|> "books" :> QueryParam "q" Text :> Get '[JSON] (Search Book)
type API' = API :<|> Raw
data Point = Point
{ x :: Double
, y :: Double
} deriving Generic
instance ToJSON Point
data Search a = Search
{ query :: Text
, results :: [a]
} deriving Generic
mkSearch :: Text -> [a] -> Search a
mkSearch = Search
instance ToJSON a => ToJSON (Search a)
data Book = Book
{ author :: Text
, title :: Text
, year :: Int
} deriving Generic
instance ToJSON Book
book :: Text -> Text -> Int -> Book
book = Book
```
We need a "book database". For the purpose of this guide, let's restrict ourselves to the following books.
> books :: [Book]
> books =
> [ book "Paul Hudak" "The Haskell School of Expression: Learning Functional Programming through Multimedia" 2000
> , book "Bryan O'Sullivan, Don Stewart, and John Goerzen" "Real World Haskell" 2008
> , book "Miran Lipovača" "Learn You a Haskell for Great Good!" 2011
> , book "Graham Hutton" "Programming in Haskell" 2007
> , book "Simon Marlow" "Parallel and Concurrent Programming in Haskell" 2013
> , book "Richard Bird" "Introduction to Functional Programming using Haskell" 1998
> ]
``` haskell
books :: [Book]
books =
[ book "Paul Hudak" "The Haskell School of Expression: Learning Functional Programming through Multimedia" 2000
, book "Bryan O'Sullivan, Don Stewart, and John Goerzen" "Real World Haskell" 2008
, book "Miran Lipovača" "Learn You a Haskell for Great Good!" 2011
, book "Graham Hutton" "Programming in Haskell" 2007
, book "Simon Marlow" "Parallel and Concurrent Programming in Haskell" 2013
, book "Richard Bird" "Introduction to Functional Programming using Haskell" 1998
]
```
Now, given an optional search string `q`, we want to perform a case insensitive search in that list of books. We're obviously not going to try and implement the best possible algorithm, this is out of scope for this tutorial. The following simple linear scan will do, given how small our list is.
> searchBook :: Monad m => Maybe Text -> m (Search Book)
> searchBook Nothing = return (mkSearch "" books)
> searchBook (Just q) = return (mkSearch q books')
>
> where books' = filter (\b -> q' `T.isInfixOf` T.toLower (author b)
> || q' `T.isInfixOf` T.toLower (title b)
> )
> books
> q' = T.toLower q
``` haskell
searchBook :: Monad m => Maybe Text -> m (Search Book)
searchBook Nothing = return (mkSearch "" books)
searchBook (Just q) = return (mkSearch q books')
where books' = filter (\b -> q' `T.isInfixOf` T.toLower (author b)
|| q' `T.isInfixOf` T.toLower (title b)
)
books
q' = T.toLower q
```
We also need an endpoint that generates random points `(x, y)` with `-1 <= x,y <= 1`. The code below uses [random](http://hackage.haskell.org/package/random)'s `System.Random`.
> randomPoint :: MonadIO m => m Point
> randomPoint = liftIO . getStdRandom $ \g ->
> let (rx, g') = randomR (-1, 1) g
> (ry, g'') = randomR (-1, 1) g'
> in (Point rx ry, g'')
``` haskell
randomPoint :: MonadIO m => m Point
randomPoint = liftIO . getStdRandom $ \g ->
let (rx, g') = randomR (-1, 1) g
(ry, g'') = randomR (-1, 1) g'
in (Point rx ry, g'')
```
If we add static file serving, our server is now complete.
> api :: Proxy API
> api = Proxy
>
> api' :: Proxy API'
> api' = Proxy
>
> server :: Server API
> server = randomPoint
> :<|> searchBook
>
> server' :: Server API'
> server' = server
> :<|> serveDirectory "tutorial/t9"
>
> app :: Application
> app = serve api' server'
``` haskell
api :: Proxy API
api = Proxy
api' :: Proxy API'
api' = Proxy
server :: Server API
server = randomPoint
:<|> searchBook
server' :: Server API'
server' = server
:<|> serveDirectory "tutorial/t9"
app :: Application
app = serve api' server'
```
Why two different API types, proxies and servers though? Simply because we don't want to generate javascript functions for the `Raw` part of our API type, so we need a `Proxy` for our API type `API'` without its `Raw` endpoint.
Very similarly to how one can derive haskell functions, we can derive the javascript with just a simple function call to `jsForAPI` from `Servant.JQuery`.
> apiJS :: String
> apiJS = jsForAPI api
``` haskell
apiJS :: String
apiJS = jsForAPI api
```
This `String` contains 2 Javascript functions:
@ -161,11 +175,13 @@ function getbooks(q, onSuccess, onError)
Right before starting up our server, we will need to write this `String` to a file, say `api.js`, along with a copy of the *jQuery* library, as provided by the [js-jquery](http://hackage.haskell.org/package/js-jquery) package.
> writeJSFiles :: IO ()
> writeJSFiles = do
> writeFile "getting-started/gs9/api.js" apiJS
> jq <- readFile =<< Language.Javascript.JQuery.file
> writeFile "getting-started/gs9/jq.js" jq
``` haskell
writeJSFiles :: IO ()
writeJSFiles = do
writeFile "getting-started/gs9/api.js" apiJS
jq <- readFile =<< Language.Javascript.JQuery.file
writeFile "getting-started/gs9/jq.js" jq
```
And we're good to go. Start the server with `dist/build/tutorial/tutorial 9` and go to `http://localhost:8081/`. Start typing in the name of one of the authors in our database or part of a book title, and check out how long it takes to approximate &pi; using the method mentioned above.

File diff suppressed because it is too large Load diff