Tests for Config.
This commit is contained in:
parent
207a807428
commit
da171780b8
4 changed files with 57 additions and 2 deletions
|
@ -49,6 +49,7 @@ library
|
||||||
, attoparsec >= 0.12 && < 0.14
|
, attoparsec >= 0.12 && < 0.14
|
||||||
, bytestring >= 0.10 && < 0.11
|
, bytestring >= 0.10 && < 0.11
|
||||||
, containers >= 0.5 && < 0.6
|
, containers >= 0.5 && < 0.6
|
||||||
|
, deepseq == 1.4.*
|
||||||
, http-api-data >= 0.1 && < 0.3
|
, http-api-data >= 0.1 && < 0.3
|
||||||
, http-types >= 0.8 && < 0.10
|
, http-types >= 0.8 && < 0.10
|
||||||
, network-uri >= 2.6 && < 2.7
|
, network-uri >= 2.6 && < 2.7
|
||||||
|
@ -96,6 +97,7 @@ test-suite spec
|
||||||
main-is: Spec.hs
|
main-is: Spec.hs
|
||||||
other-modules:
|
other-modules:
|
||||||
Servant.Server.Internal.EnterSpec
|
Servant.Server.Internal.EnterSpec
|
||||||
|
Servant.Server.Internal.ConfigSpec
|
||||||
Servant.ServerSpec
|
Servant.ServerSpec
|
||||||
Servant.Utils.StaticFilesSpec
|
Servant.Utils.StaticFilesSpec
|
||||||
Servant.Server.ErrorSpec
|
Servant.Server.ErrorSpec
|
||||||
|
@ -116,6 +118,7 @@ test-suite spec
|
||||||
, servant
|
, servant
|
||||||
, servant-server
|
, servant-server
|
||||||
, string-conversions
|
, string-conversions
|
||||||
|
, should-not-typecheck == 2.*
|
||||||
, temporary
|
, temporary
|
||||||
, text
|
, text
|
||||||
, transformers
|
, transformers
|
||||||
|
|
|
@ -11,6 +11,7 @@
|
||||||
{-# LANGUAGE KindSignatures #-}
|
{-# LANGUAGE KindSignatures #-}
|
||||||
{-# LANGUAGE MultiParamTypeClasses #-}
|
{-# LANGUAGE MultiParamTypeClasses #-}
|
||||||
{-# LANGUAGE ScopedTypeVariables #-}
|
{-# LANGUAGE ScopedTypeVariables #-}
|
||||||
|
{-# LANGUAGE PolyKinds #-}
|
||||||
{-# LANGUAGE TypeOperators #-}
|
{-# LANGUAGE TypeOperators #-}
|
||||||
{-# LANGUAGE UndecidableInstances #-}
|
{-# LANGUAGE UndecidableInstances #-}
|
||||||
#if !MIN_VERSION_base(4,8,0)
|
#if !MIN_VERSION_base(4,8,0)
|
||||||
|
@ -18,6 +19,7 @@
|
||||||
#endif
|
#endif
|
||||||
module Servant.Server.Internal.Config where
|
module Servant.Server.Internal.Config where
|
||||||
|
|
||||||
|
import Control.DeepSeq (NFData(rnf))
|
||||||
import GHC.Generics (Generic)
|
import GHC.Generics (Generic)
|
||||||
import Data.Typeable (Typeable)
|
import Data.Typeable (Typeable)
|
||||||
|
|
||||||
|
@ -25,7 +27,7 @@ import Data.Typeable (Typeable)
|
||||||
-- is used to lookup a @ConfigEntry@ in a @Config@.
|
-- is used to lookup a @ConfigEntry@ in a @Config@.
|
||||||
newtype ConfigEntry tag a = ConfigEntry { unConfigEntry :: a }
|
newtype ConfigEntry tag a = ConfigEntry { unConfigEntry :: a }
|
||||||
deriving ( Eq, Show, Read, Enum, Integral, Fractional, Generic, Typeable
|
deriving ( Eq, Show, Read, Enum, Integral, Fractional, Generic, Typeable
|
||||||
, Num, Ord, Real, Functor, Foldable, Traversable)
|
, Num, Ord, Real, Functor, Foldable, Traversable, NFData)
|
||||||
|
|
||||||
instance Applicative (ConfigEntry tag) where
|
instance Applicative (ConfigEntry tag) where
|
||||||
pure = ConfigEntry
|
pure = ConfigEntry
|
||||||
|
@ -40,11 +42,23 @@ data Config a where
|
||||||
EmptyConfig :: Config '[]
|
EmptyConfig :: Config '[]
|
||||||
ConsConfig :: x -> Config xs -> Config (x ': xs)
|
ConsConfig :: x -> Config xs -> Config (x ': xs)
|
||||||
|
|
||||||
|
instance Eq (Config '[]) where
|
||||||
|
_ == _ = True
|
||||||
|
instance (Eq a, Eq (Config as)) => Eq (Config (a ' : as)) where
|
||||||
|
ConsConfig x1 y1 == ConsConfig x2 y2 = x1 == x2 && y1 == y2
|
||||||
|
|
||||||
|
instance NFData (Config '[]) where
|
||||||
|
rnf EmptyConfig = ()
|
||||||
|
instance (NFData a, NFData (Config as)) => NFData (Config (a ': as)) where
|
||||||
|
rnf (x `ConsConfig` ys) = rnf x `seq` rnf ys
|
||||||
|
|
||||||
|
|
||||||
|
|
||||||
(.:) :: x -> Config xs -> Config (ConfigEntry tag x ': xs)
|
(.:) :: x -> Config xs -> Config (ConfigEntry tag x ': xs)
|
||||||
e .: cfg = ConsConfig (ConfigEntry e) cfg
|
e .: cfg = ConsConfig (ConfigEntry e) cfg
|
||||||
infixr 4 .:
|
infixr 4 .:
|
||||||
|
|
||||||
class HasConfigEntry (cfg :: [*]) a val | cfg a -> val where
|
class HasConfigEntry (cfg :: [*]) (a :: k) (val :: *) | cfg a -> val where
|
||||||
getConfigEntry :: proxy a -> Config cfg -> val
|
getConfigEntry :: proxy a -> Config cfg -> val
|
||||||
|
|
||||||
instance
|
instance
|
||||||
|
|
37
servant-server/test/Servant/Server/Internal/ConfigSpec.hs
Normal file
37
servant-server/test/Servant/Server/Internal/ConfigSpec.hs
Normal file
|
@ -0,0 +1,37 @@
|
||||||
|
{-# LANGUAGE DataKinds #-}
|
||||||
|
{-# OPTIONS_GHC -fdefer-type-errors #-}
|
||||||
|
module Servant.Server.Internal.ConfigSpec (spec) where
|
||||||
|
|
||||||
|
import Data.Proxy (Proxy (..))
|
||||||
|
import Test.Hspec (Spec, describe, it, shouldBe)
|
||||||
|
import Test.ShouldNotTypecheck (shouldNotTypecheck)
|
||||||
|
|
||||||
|
import Servant.Server.Internal.Config
|
||||||
|
|
||||||
|
spec :: Spec
|
||||||
|
spec = do
|
||||||
|
getConfigEntrySpec
|
||||||
|
|
||||||
|
getConfigEntrySpec :: Spec
|
||||||
|
getConfigEntrySpec = describe "getConfigEntry" $ do
|
||||||
|
|
||||||
|
let cfg1 = 0 .: EmptyConfig :: Config '[ConfigEntry "a" Int]
|
||||||
|
cfg2 = 1 .: cfg1 :: Config '[ConfigEntry "a" Int, ConfigEntry "a" Int]
|
||||||
|
|
||||||
|
it "gets the config if a matching one exists" $ do
|
||||||
|
|
||||||
|
getConfigEntry (Proxy :: Proxy "a") cfg1 `shouldBe` 0
|
||||||
|
|
||||||
|
it "gets the first matching config" $ do
|
||||||
|
|
||||||
|
getConfigEntry (Proxy :: Proxy "a") cfg2 `shouldBe` 1
|
||||||
|
|
||||||
|
it "does not typecheck if key does not exist" $ do
|
||||||
|
|
||||||
|
let x = getConfigEntry (Proxy :: Proxy "b") cfg1 :: Int
|
||||||
|
shouldNotTypecheck x
|
||||||
|
|
||||||
|
it "does not typecheck if key maps to a different type" $ do
|
||||||
|
|
||||||
|
let x = getConfigEntry (Proxy :: Proxy "a") cfg1 :: String
|
||||||
|
shouldNotTypecheck x
|
|
@ -16,4 +16,5 @@ packages:
|
||||||
extra-deps:
|
extra-deps:
|
||||||
- engine-io-wai-1.0.2
|
- engine-io-wai-1.0.2
|
||||||
- control-monad-omega-0.3.1
|
- control-monad-omega-0.3.1
|
||||||
|
- should-not-typecheck-2.0.1
|
||||||
resolver: nightly-2015-10-08
|
resolver: nightly-2015-10-08
|
||||||
|
|
Loading…
Reference in a new issue