2015-04-08 16:27:38 +02:00
|
|
|
{-# LANGUAGE DataKinds #-}
|
|
|
|
{-# LANGUAGE DeriveGeneric #-}
|
2015-09-16 12:42:05 +02:00
|
|
|
{-# LANGUAGE FlexibleContexts #-}
|
2016-01-16 19:17:46 +01:00
|
|
|
{-# LANGUAGE FlexibleInstances #-}
|
2015-04-08 16:27:38 +02:00
|
|
|
{-# LANGUAGE MultiParamTypeClasses #-}
|
2015-09-16 12:42:05 +02:00
|
|
|
{-# LANGUAGE OverloadedStrings #-}
|
2015-04-08 16:27:38 +02:00
|
|
|
{-# LANGUAGE TypeOperators #-}
|
|
|
|
{-# LANGUAGE TypeSynonymInstances #-}
|
|
|
|
{-# OPTIONS_GHC -fno-warn-orphans #-}
|
|
|
|
module Servant.DocsSpec where
|
|
|
|
|
2015-06-16 22:38:14 +02:00
|
|
|
import Control.Lens
|
2015-04-08 16:27:38 +02:00
|
|
|
import Data.Aeson
|
2015-06-16 22:38:14 +02:00
|
|
|
import Data.Monoid
|
2015-04-08 16:27:38 +02:00
|
|
|
import Data.Proxy
|
|
|
|
import Data.String.Conversions (cs)
|
|
|
|
import GHC.Generics
|
|
|
|
import Test.Hspec
|
|
|
|
|
|
|
|
import Servant.API
|
2016-01-16 19:17:46 +01:00
|
|
|
import Servant.API.Internal.Test.ComprehensiveAPI
|
2015-04-08 16:27:38 +02:00
|
|
|
import Servant.Docs.Internal
|
|
|
|
|
2016-01-16 19:17:46 +01:00
|
|
|
-- * comprehensive api
|
|
|
|
|
2016-01-18 19:55:14 +01:00
|
|
|
-- This declaration simply checks that all instances are in place.
|
2016-01-16 19:17:46 +01:00
|
|
|
_ = docs comprehensiveAPI
|
|
|
|
|
|
|
|
instance ToParam (QueryParam "foo" Int) where
|
|
|
|
toParam = error "unused"
|
|
|
|
instance ToParam (QueryParams "foo" Int) where
|
|
|
|
toParam = error "unused"
|
|
|
|
instance ToParam (QueryFlag "foo") where
|
|
|
|
toParam = error "unused"
|
|
|
|
instance ToCapture (Capture "foo" Int) where
|
|
|
|
toCapture = error "unused"
|
|
|
|
|
|
|
|
-- * specs
|
|
|
|
|
2015-04-08 16:27:38 +02:00
|
|
|
spec :: Spec
|
|
|
|
spec = describe "Servant.Docs" $ do
|
|
|
|
|
|
|
|
describe "markdown" $ do
|
|
|
|
let md = markdown (docs (Proxy :: Proxy TestApi1))
|
2015-06-16 22:38:14 +02:00
|
|
|
tests md
|
|
|
|
|
|
|
|
describe "markdown with extra info" $ do
|
|
|
|
let
|
|
|
|
extra = extraInfo
|
2015-09-24 13:02:21 +02:00
|
|
|
(Proxy :: Proxy (Get '[JSON, PlainText] (Headers '[Header "Location" String] Int)))
|
2015-06-16 22:38:14 +02:00
|
|
|
(defAction & notes <>~ [DocNote "Get an Integer" ["get an integer in Json or plain text"]])
|
|
|
|
<>
|
|
|
|
extraInfo
|
|
|
|
(Proxy :: Proxy (ReqBody '[JSON] String :> Post '[JSON] Datatype1))
|
|
|
|
(defAction & notes <>~ [DocNote "Post data" ["Posts some Json data"]])
|
2015-09-21 12:36:57 +02:00
|
|
|
md = markdown (docsWith defaultDocOptions [] extra (Proxy :: Proxy TestApi1))
|
2015-06-16 22:38:14 +02:00
|
|
|
tests md
|
|
|
|
it "contains the extra info provided" $ do
|
|
|
|
md `shouldContain` "Get an Integer"
|
|
|
|
md `shouldContain` "Post data"
|
|
|
|
md `shouldContain` "get an integer in Json or plain text"
|
|
|
|
md `shouldContain` "Posts some Json data"
|
|
|
|
|
2015-09-16 12:42:05 +02:00
|
|
|
describe "tuple samples" $ do
|
|
|
|
it "looks like expected" $ do
|
|
|
|
(toSample (Proxy :: Proxy (TT, UT))) `shouldBe` Just (TT1,UT1)
|
|
|
|
(toSample (Proxy :: Proxy (TT, UT, UT))) `shouldBe` Just (TT1,UT1,UT1)
|
|
|
|
(toSamples (Proxy :: Proxy (TT, UT))) `shouldBe`
|
2015-09-21 11:46:21 +02:00
|
|
|
[ ("eins, yks",(TT1,UT1)), ("eins, kaks",(TT1,UT2))
|
|
|
|
, ("zwei, yks",(TT2,UT1)), ("zwei, kaks",(TT2,UT2))
|
2015-09-16 12:42:05 +02:00
|
|
|
]
|
|
|
|
(toSamples (Proxy :: Proxy (TT, UT, UT))) `shouldBe`
|
2015-09-21 11:46:21 +02:00
|
|
|
[ ("eins, yks, yks",(TT1,UT1,UT1))
|
|
|
|
, ("eins, yks, kaks",(TT1,UT1,UT2))
|
|
|
|
, ("zwei, yks, yks",(TT2,UT1,UT1))
|
|
|
|
, ("eins, kaks, yks",(TT1,UT2,UT1))
|
|
|
|
, ("zwei, yks, kaks",(TT2,UT1,UT2))
|
|
|
|
, ("eins, kaks, kaks",(TT1,UT2,UT2))
|
|
|
|
, ("zwei, kaks, yks",(TT2,UT2,UT1))
|
|
|
|
, ("zwei, kaks, kaks",(TT2,UT2,UT2))
|
2015-09-16 12:42:05 +02:00
|
|
|
]
|
|
|
|
|
2016-01-11 13:37:20 +01:00
|
|
|
|
2015-06-16 22:38:14 +02:00
|
|
|
where
|
|
|
|
tests md = do
|
2015-04-08 16:27:38 +02:00
|
|
|
it "mentions supported content-types" $ do
|
|
|
|
md `shouldContain` "application/json"
|
|
|
|
md `shouldContain` "text/plain;charset=utf-8"
|
|
|
|
|
|
|
|
it "mentions status codes" $ do
|
|
|
|
md `shouldContain` "Status code 200"
|
|
|
|
|
2016-01-15 12:17:48 +01:00
|
|
|
it "has methods as section headers" $ do
|
|
|
|
md `shouldContain` "## POST"
|
|
|
|
md `shouldContain` "## GET"
|
2015-04-08 16:27:38 +02:00
|
|
|
|
2016-01-11 13:37:20 +01:00
|
|
|
it "mentions headers" $ do
|
|
|
|
md `shouldContain` "- This endpoint is sensitive to the value of the **X-Test** HTTP header."
|
|
|
|
|
2015-06-16 22:38:14 +02:00
|
|
|
it "contains response samples" $
|
2015-04-08 16:27:38 +02:00
|
|
|
md `shouldContain` "{\"dt1field1\":\"field 1\",\"dt1field2\":13}"
|
2015-06-16 22:38:14 +02:00
|
|
|
it "contains request body samples" $
|
2015-04-08 16:27:38 +02:00
|
|
|
md `shouldContain` "17"
|
2015-06-16 22:38:14 +02:00
|
|
|
|
2016-01-11 13:37:20 +01:00
|
|
|
|
2015-04-08 16:27:38 +02:00
|
|
|
-- * APIs
|
|
|
|
|
|
|
|
data Datatype1 = Datatype1 { dt1field1 :: String
|
|
|
|
, dt1field2 :: Int
|
|
|
|
} deriving (Eq, Show, Generic)
|
|
|
|
|
|
|
|
instance ToJSON Datatype1
|
|
|
|
|
2015-09-24 13:02:21 +02:00
|
|
|
instance ToSample Datatype1 where
|
2015-09-21 11:46:21 +02:00
|
|
|
toSamples _ = singleSample $ Datatype1 "field 1" 13
|
2015-04-08 16:27:38 +02:00
|
|
|
|
2015-09-24 13:02:21 +02:00
|
|
|
instance ToSample Char where
|
2015-09-21 11:51:00 +02:00
|
|
|
toSamples _ = samples ['a'..'z']
|
2015-04-08 16:27:38 +02:00
|
|
|
|
2015-09-24 13:02:21 +02:00
|
|
|
instance ToSample Int where
|
2015-09-21 11:46:21 +02:00
|
|
|
toSamples _ = singleSample 17
|
2015-04-08 16:27:38 +02:00
|
|
|
|
|
|
|
instance MimeRender PlainText Int where
|
2015-04-19 14:51:34 +02:00
|
|
|
mimeRender _ = cs . show
|
2015-04-08 16:27:38 +02:00
|
|
|
|
2015-09-24 13:02:21 +02:00
|
|
|
type TestApi1 = Get '[JSON, PlainText] (Headers '[Header "Location" String] Int)
|
2015-04-08 16:27:38 +02:00
|
|
|
:<|> ReqBody '[JSON] String :> Post '[JSON] Datatype1
|
2016-01-11 13:37:20 +01:00
|
|
|
:<|> Header "X-Test" Int :> Put '[JSON] Int
|
2015-04-08 16:27:38 +02:00
|
|
|
|
2015-09-16 12:42:05 +02:00
|
|
|
data TT = TT1 | TT2 deriving (Show, Eq)
|
|
|
|
data UT = UT1 | UT2 deriving (Show, Eq)
|
|
|
|
|
2015-09-24 13:02:21 +02:00
|
|
|
instance ToSample TT where
|
2015-09-16 12:42:05 +02:00
|
|
|
toSamples _ = [("eins", TT1), ("zwei", TT2)]
|
|
|
|
|
2015-09-24 13:02:21 +02:00
|
|
|
instance ToSample UT where
|
2015-09-16 12:42:05 +02:00
|
|
|
toSamples _ = [("yks", UT1), ("kaks", UT2)]
|