servant/example/greet.hs

63 lines
1.8 KiB
Haskell
Raw Normal View History

{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings #-}
import Data.Aeson
import Data.Proxy
import Data.Text
import GHC.Generics
import Servant.API
import Servant.Docs
-- * Example
-- | A greet message data type
newtype Greet = Greet { msg :: Text }
deriving (Generic, Show)
instance FromJSON Greet
instance ToJSON Greet
-- We add some useful annotations to our captures,
-- query parameters and request body to make the docs
-- really helpful.
instance ToCapture (Capture "name" Text) where
toCapture _ = DocCapture "name" "name of the person to greet"
instance ToCapture (Capture "greetid" Text) where
toCapture _ = DocCapture "greetid" "identifier of the greet msg to remove"
instance ToParam (QueryParam "capital" Bool) where
toParam _ =
DocQueryParam "capital"
["true", "false"]
"Get the greeting message in uppercase (true) or not (false). Default is false."
Normal
instance ToSample Greet where
toSample = Just $ Greet "Hello, haskeller!"
-- API specification
type TestApi =
-- GET /hello/:name?capital={true, false} returns a Greet as JSON
"hello" :> Capture "name" Text :> QueryParam "capital" Bool :> Get Greet
-- POST /greet with a Greet as JSON in the request body,
-- returns a Greet as JSON
:<|> "greet" :> ReqBody Greet :> Post Greet
-- DELETE /greet/:greetid
:<|> "greet" :> Capture "greetid" Text :> Delete
testApi :: Proxy TestApi
testApi = Proxy
-- Generate the data that lets us have API docs. This
-- is derived from the type as well as from
-- the 'ToCapture', 'ToParam' and 'ToSample' instances from above.
docsGreet :: API
docsGreet = docs testApi
main :: IO ()
main = putStrLn $ markdown docsGreet