servant/test/Servant/Utils/LinksSpec.hs

60 lines
2.3 KiB
Haskell
Raw Normal View History

2014-10-27 08:52:18 +01:00
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE TypeOperators #-}
module Servant.Utils.LinksSpec where
2014-10-27 08:52:18 +01:00
2015-01-06 17:57:50 +01:00
import Test.Hspec ( Spec, it, describe )
2014-10-27 08:52:18 +01:00
import Servant.API
2015-01-15 10:44:45 +01:00
( type (:<|>), ReqBody, QueryParam, MatrixParam, MatrixParams, MatrixFlag, Get, Post, Capture, type (:>) )
2014-11-25 17:35:17 +01:00
import Servant.QQSpec ( (~>) )
2015-01-06 17:57:50 +01:00
import Servant.Utils.Links ( IsElem, IsLink )
2014-10-27 08:52:18 +01:00
type TestApi =
"hello" :> Capture "name" String :> QueryParam "capital" Bool :> Get Bool
:<|> "greet" :> ReqBody 'True :> Post Bool
:<|> "parent" :> MatrixParams "name" String :> "child" :> MatrixParam "gender" String :> Get String
2014-10-27 08:52:18 +01:00
type TestLink = "hello" :> "hi" :> Get Bool
type TestLink2 = "greet" :> Post Bool
type TestLink3 = "parent" :> "child" :> Get String
2014-10-27 08:52:18 +01:00
type BadTestLink = "hallo" :> "hi" :> Get Bool
type BadTestLink2 = "greet" :> Get Bool
type BadTestLink3 = "parent" :> "child" :> MatrixFlag "male" :> Get String
2014-10-27 08:52:18 +01:00
type NotALink = "hello" :> Capture "x" Bool :> Get Bool
type NotALink2 = "hello" :> ReqBody 'True :> Get Bool
data Proxy x = Proxy
class ReflectT (x::Bool) where { reflected :: Proxy x -> Bool }
instance ReflectT 'True where { reflected _ = True }
instance ReflectT 'False where { reflected _ = False }
spec :: Spec
spec = describe "Servant.API.Elem" $ do
isElem
isLink
isElem :: Spec
isElem = describe "IsElem" $ do
it "is True when the first argument is an url within the second" $ do
reflected (Proxy::Proxy (IsElem TestLink TestApi)) ~> True
reflected (Proxy::Proxy (IsElem TestLink2 TestApi)) ~> True
reflected (Proxy::Proxy (IsElem TestLink3 TestApi)) ~> True
2014-10-27 08:52:18 +01:00
it "is False when the first argument is not an url within the second" $ do
reflected (Proxy::Proxy (IsElem BadTestLink TestApi)) ~> False
reflected (Proxy::Proxy (IsElem BadTestLink2 TestApi)) ~> False
reflected (Proxy::Proxy (IsElem BadTestLink3 TestApi)) ~> False
2014-10-27 08:52:18 +01:00
isLink :: Spec
isLink = describe "IsLink" $ do
it "is True when all Subs are paths and the last is a method" $ do
reflected (Proxy::Proxy (IsLink TestLink)) ~> True
reflected (Proxy::Proxy (IsLink TestLink2)) ~> True
reflected (Proxy::Proxy (IsLink TestLink3)) ~> True
2014-10-27 08:52:18 +01:00
it "is False of anything with captures" $ do
reflected (Proxy::Proxy (IsLink NotALink)) ~> False
reflected (Proxy::Proxy (IsLink NotALink2)) ~> False