update examples for servant-docs. fixes #76

This commit is contained in:
Alp Mestanogullari 2015-05-14 01:01:41 +02:00
parent ff6c04cf1a
commit 46d48946b0
2 changed files with 6 additions and 5 deletions

View file

@ -32,7 +32,7 @@ instance ToJSON Greet
-- We can also implement 'MimeRender' explicitly for additional formats. -- We can also implement 'MimeRender' explicitly for additional formats.
instance MimeRender PlainText Greet where instance MimeRender PlainText Greet where
toByteString Proxy (Greet s) = "<h1>" <> cs s <> "</h1>" mimeRender Proxy (Greet s) = "<h1>" <> cs s <> "</h1>"
-- we provide a sample value for the 'Greet' type -- we provide a sample value for the 'Greet' type
instance ToSample Greet where instance ToSample Greet where
@ -56,7 +56,7 @@ instance ToCapture (Capture "greetid" Text) where
type TestApi = type TestApi =
"hello" :> Capture "name" Text :> QueryParam "capital" Bool :> Get '[JSON,PlainText] Greet "hello" :> Capture "name" Text :> QueryParam "capital" Bool :> Get '[JSON,PlainText] Greet
:<|> "greet" :> RQBody '[JSON] Greet :> Post '[JSON] Greet :<|> "greet" :> RQBody '[JSON] Greet :> Post '[JSON] Greet
:<|> "delete" :> Capture "greetid" Text :> Delete :<|> "delete" :> Capture "greetid" Text :> Delete '[] ()
testApi :: Proxy TestApi testApi :: Proxy TestApi
testApi = Proxy testApi = Proxy

View file

@ -30,6 +30,7 @@
-- > {-# LANGUAGE OverloadedStrings #-} -- > {-# LANGUAGE OverloadedStrings #-}
-- > {-# LANGUAGE TypeOperators #-} -- > {-# LANGUAGE TypeOperators #-}
-- > {-# OPTIONS_GHC -fno-warn-orphans #-} -- > {-# OPTIONS_GHC -fno-warn-orphans #-}
-- > import Control.Lens
-- > import Data.Aeson -- > import Data.Aeson
-- > import Data.Proxy -- > import Data.Proxy
-- > import Data.String.Conversions -- > import Data.String.Conversions
@ -51,7 +52,7 @@
-- > -- >
-- > -- | We can also implement 'MimeRender' for additional formats like 'PlainText'. -- > -- | We can also implement 'MimeRender' for additional formats like 'PlainText'.
-- > instance MimeRender PlainText Greet where -- > instance MimeRender PlainText Greet where
-- > toByteString Proxy (Greet s) = "\"" <> cs s <> "\"" -- > mimeRender Proxy (Greet s) = "\"" <> cs s <> "\""
-- > -- >
-- > -- We add some useful annotations to our captures, -- > -- We add some useful annotations to our captures,
-- > -- query parameters and request body to make the docs -- > -- query parameters and request body to make the docs
@ -111,7 +112,7 @@
-- > :<|> "greet" :> ReqBody '[JSON] Greet :> Post '[JSON] Greet -- > :<|> "greet" :> ReqBody '[JSON] Greet :> Post '[JSON] Greet
-- > -- >
-- > -- DELETE /greet/:greetid -- > -- DELETE /greet/:greetid
-- > :<|> "greet" :> Capture "greetid" Text :> Delete -- > :<|> "greet" :> Capture "greetid" Text :> Delete '[JSON] ()
-- > -- >
-- > testApi :: Proxy TestApi -- > testApi :: Proxy TestApi
-- > testApi = Proxy -- > testApi = Proxy
@ -121,7 +122,7 @@
-- > -- notes. -- > -- notes.
-- > extra :: ExtraInfo TestApi -- > extra :: ExtraInfo TestApi
-- > extra = -- > extra =
-- > extraInfo (Proxy :: Proxy ("greet" :> Capture "greetid" Text :> Delete)) $ -- > extraInfo (Proxy :: Proxy ("greet" :> Capture "greetid" Text :> Delete '[JSON] ())) $
-- > defAction & headers <>~ ["unicorns"] -- > defAction & headers <>~ ["unicorns"]
-- > & notes <>~ [ DocNote "Title" ["This is some text"] -- > & notes <>~ [ DocNote "Title" ["This is some text"]
-- > , DocNote "Second secton" ["And some more"] -- > , DocNote "Second secton" ["And some more"]