2015-12-26 15:30:39 +01:00
|
|
|
{-# LANGUAGE DataKinds #-}
|
|
|
|
{-# OPTIONS_GHC -fdefer-type-errors #-}
|
|
|
|
module Servant.Server.Internal.ConfigSpec (spec) where
|
|
|
|
|
|
|
|
import Data.Proxy (Proxy (..))
|
2016-01-08 18:15:01 +01:00
|
|
|
import Test.Hspec (Spec, describe, it, shouldBe, pending, context)
|
2015-12-26 15:30:39 +01:00
|
|
|
import Test.ShouldNotTypecheck (shouldNotTypecheck)
|
|
|
|
|
2016-01-08 18:15:01 +01:00
|
|
|
import Servant.API
|
2015-12-26 15:30:39 +01:00
|
|
|
import Servant.Server.Internal.Config
|
|
|
|
|
|
|
|
spec :: Spec
|
|
|
|
spec = do
|
|
|
|
getConfigEntrySpec
|
|
|
|
|
2016-01-10 16:40:56 +01:00
|
|
|
newtype Wrapped a = Wrap { unwrap :: a }
|
|
|
|
|
2015-12-26 15:30:39 +01:00
|
|
|
getConfigEntrySpec :: Spec
|
|
|
|
getConfigEntrySpec = describe "getConfigEntry" $ do
|
|
|
|
|
2016-01-10 16:40:56 +01:00
|
|
|
let cfg1 = 0 .:. EmptyConfig :: Config '[Int]
|
|
|
|
cfg2 = 1 .:. cfg1 :: Config '[Int, Int]
|
2015-12-26 15:30:39 +01:00
|
|
|
|
|
|
|
it "gets the config if a matching one exists" $ do
|
|
|
|
|
2016-01-10 16:40:56 +01:00
|
|
|
getConfigEntry cfg1 `shouldBe` (0 :: Int)
|
2015-12-26 15:30:39 +01:00
|
|
|
|
|
|
|
it "gets the first matching config" $ do
|
|
|
|
|
2016-01-10 16:40:56 +01:00
|
|
|
getConfigEntry cfg2 `shouldBe` (1 :: Int)
|
2015-12-26 15:30:39 +01:00
|
|
|
|
2016-01-08 18:15:01 +01:00
|
|
|
it "allows to distinguish between different config entries with the same type by tag" $ do
|
2016-01-10 16:40:56 +01:00
|
|
|
let cfg = 'a' .:. Wrap 'b' .:. EmptyConfig :: Config '[Char, Wrapped Char]
|
|
|
|
getConfigEntry cfg `shouldBe` 'a'
|
2016-01-08 18:15:01 +01:00
|
|
|
|
|
|
|
context "Show instance" $ do
|
2016-01-10 11:43:07 +01:00
|
|
|
let cfg = 1 .:. 2 .:. EmptyConfig
|
2016-01-08 18:15:01 +01:00
|
|
|
it "has a Show instance" $ do
|
2016-01-10 11:43:07 +01:00
|
|
|
show cfg `shouldBe` "1 .:. 2 .:. EmptyConfig"
|
2016-01-08 18:15:01 +01:00
|
|
|
|
|
|
|
it "bracketing works" $ do
|
2016-01-10 11:43:07 +01:00
|
|
|
show (Just cfg) `shouldBe` "Just (1 .:. 2 .:. EmptyConfig)"
|
2016-01-08 18:15:01 +01:00
|
|
|
|
|
|
|
it "bracketing works with operators" $ do
|
2016-01-10 11:43:07 +01:00
|
|
|
let cfg = (1 .:. 'a' .:. EmptyConfig) :<|> ('b' .:. True .:. EmptyConfig)
|
|
|
|
show cfg `shouldBe` "(1 .:. 'a' .:. EmptyConfig) :<|> ('b' .:. True .:. EmptyConfig)"
|
2016-01-08 18:15:01 +01:00
|
|
|
|
2016-01-10 16:40:56 +01:00
|
|
|
it "does not typecheck if type does not exist" $ do
|
2015-12-26 15:30:39 +01:00
|
|
|
|
2016-01-10 16:40:56 +01:00
|
|
|
let x = getConfigEntry cfg1 :: Bool
|
2015-12-26 15:30:39 +01:00
|
|
|
shouldNotTypecheck x
|