Some tests.
Mostly instrumentation for them.
This commit is contained in:
parent
c6264dd202
commit
4ebd52b106
1 changed files with 37 additions and 0 deletions
37
test/Servant/API/QQSpec.hs
Normal file
37
test/Servant/API/QQSpec.hs
Normal file
|
@ -0,0 +1,37 @@
|
||||||
|
{-# LANGUAGE DataKinds #-}
|
||||||
|
{-# LANGUAGE FlexibleInstances #-}
|
||||||
|
{-# LANGUAGE FunctionalDependencies #-}
|
||||||
|
{-# LANGUAGE MultiParamTypeClasses #-}
|
||||||
|
{-# LANGUAGE OverlappingInstances #-}
|
||||||
|
{-# LANGUAGE QuasiQuotes #-}
|
||||||
|
{-# LANGUAGE TypeFamilies #-}
|
||||||
|
{-# LANGUAGE TypeOperators #-}
|
||||||
|
{-# LANGUAGE UndecidableInstances #-}
|
||||||
|
module Servant.API.QQSpec where
|
||||||
|
|
||||||
|
import Test.Hspec
|
||||||
|
|
||||||
|
import Servant.API
|
||||||
|
{-import Servant.API.QQ-}
|
||||||
|
|
||||||
|
data HTrue
|
||||||
|
data HFalse
|
||||||
|
|
||||||
|
-- Kiselyov's Type Equality predicate
|
||||||
|
class TypeEq x y b | x y -> b where { areEq :: x -> y -> Bool }
|
||||||
|
instance TypeEq x x HTrue where { areEq _ _ = True }
|
||||||
|
instance b ~ HFalse => TypeEq x y b where { areEq _ _ = False}
|
||||||
|
|
||||||
|
type SimpleGet = [sitemap|
|
||||||
|
GET hello ()
|
||||||
|
|]
|
||||||
|
|
||||||
|
type SimpleGet' = "hello" :> Get ()
|
||||||
|
type SimpleGet'' = "hello" :> Get Bool
|
||||||
|
|
||||||
|
spec :: Spec
|
||||||
|
spec = do
|
||||||
|
describe "'sitemap' QuasiQuoter" $ do
|
||||||
|
it "Handles simple GET types" $ do
|
||||||
|
areEq (undefined::SimpleGet) (undefined::SimpleGet') `shouldBe` True
|
||||||
|
areEq (undefined::SimpleGet) (undefined::SimpleGet'') `shouldBe` False
|
Loading…
Reference in a new issue