{-# LANGUAGE CPP #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
#include "overlapping-compat.h"
module Servant.Mock ( HasMock(..) ) where
import Prelude ()
import Prelude.Compat
import Control.Monad.IO.Class
import Data.ByteString.Lazy.Char8 (pack)
import Data.Proxy
import GHC.TypeLits
import Network.HTTP.Types.Status
import Network.Wai
import Servant
import Servant.API.ContentTypes
import Servant.API.Modifiers
import Test.QuickCheck.Arbitrary (Arbitrary (..), vector)
import Test.QuickCheck.Gen (Gen, generate)
class HasServer api context => HasMock api context where
mock :: Proxy api -> Proxy context -> Server api
instance (HasMock a context, HasMock b context) => HasMock (a :<|> b) context where
mock _ context = mock (Proxy :: Proxy a) context :<|> mock (Proxy :: Proxy b) context
instance (KnownSymbol path, HasMock rest context) => HasMock (path :> rest) context where
mock _ = mock (Proxy :: Proxy rest)
instance (KnownSymbol s, FromHttpApiData a, HasMock rest context) => HasMock (Capture' mods s a :> rest) context where
mock _ context = \_ -> mock (Proxy :: Proxy rest) context
instance (KnownSymbol s, FromHttpApiData a, HasMock rest context) => HasMock (CaptureAll s a :> rest) context where
mock _ context = \_ -> mock (Proxy :: Proxy rest) context
instance (AllCTUnrender ctypes a, HasMock rest context, SBoolI (FoldLenient mods))
=> HasMock (ReqBody' mods ctypes a :> rest) context where
mock _ context = \_ -> mock (Proxy :: Proxy rest) context
instance (MimeUnrender ctype chunk, FramingUnrender fr, FromSourceIO chunk a, HasMock rest context)
=> HasMock (StreamBody' mods fr ctype a :> rest) context where
mock _ context = \_ -> mock (Proxy :: Proxy rest) context
instance HasMock rest context => HasMock (RemoteHost :> rest) context where
mock _ context = \_ -> mock (Proxy :: Proxy rest) context
instance HasMock rest context => HasMock (IsSecure :> rest) context where
mock _ context = \_ -> mock (Proxy :: Proxy rest) context
instance HasMock rest context => HasMock (Vault :> rest) context where
mock _ context = \_ -> mock (Proxy :: Proxy rest) context
instance HasMock rest context => HasMock (HttpVersion :> rest) context where
mock _ context = \_ -> mock (Proxy :: Proxy rest) context
instance (KnownSymbol s, FromHttpApiData a, HasMock rest context, SBoolI (FoldRequired mods), SBoolI (FoldLenient mods))
=> HasMock (QueryParam' mods s a :> rest) context where
mock _ context = \_ -> mock (Proxy :: Proxy rest) context
instance (KnownSymbol s, FromHttpApiData a, HasMock rest context)
=> HasMock (QueryParams s a :> rest) context where
mock _ context = \_ -> mock (Proxy :: Proxy rest) context
instance (KnownSymbol s, HasMock rest context) => HasMock (QueryFlag s :> rest) context where
mock _ context = \_ -> mock (Proxy :: Proxy rest) context
instance (KnownSymbol h, FromHttpApiData a, HasMock rest context, SBoolI (FoldRequired mods), SBoolI (FoldLenient mods))
=> HasMock (Header' mods h a :> rest) context where
mock _ context = \_ -> mock (Proxy :: Proxy rest) context
instance (Arbitrary a, KnownNat status, ReflectMethod method, AllCTRender ctypes a)
=> HasMock (Verb method status ctypes a) context where
mock _ _ = mockArbitrary
instance (Arbitrary a, KnownNat status, ReflectMethod method, MimeRender ctype chunk, FramingRender fr, ToSourceIO chunk a)
=> HasMock (Stream method status fr ctype a) context where
mock _ _ = mockArbitrary
instance OVERLAPPING_
(GetHeaders (Headers headerTypes a), Arbitrary (HList headerTypes),
Arbitrary a, KnownNat status, ReflectMethod method, AllCTRender ctypes a)
=> HasMock (Verb method status ctypes (Headers headerTypes a)) context where
mock _ _ = mockArbitrary
instance HasMock Raw context where
mock _ _ = Tagged $ \_req respond -> do
bdy <- genBody
respond $ responseLBS status200 [] bdy
where genBody = pack <$> generate (vector 100 :: Gen [Char])
instance HasMock EmptyAPI context where
mock _ _ = emptyServer
instance HasMock api context => HasMock (Summary d :> api) context where
mock _ context = mock (Proxy :: Proxy api) context
instance HasMock api context => HasMock (Description d :> api) context where
mock _ context = mock (Proxy :: Proxy api) context
instance (HasContextEntry context (NamedContext name subContext), HasMock rest subContext) =>
HasMock (WithNamedContext name subContext rest) context where
mock _ _ = mock (Proxy :: Proxy rest) (Proxy :: Proxy subContext)
mockArbitrary :: (MonadIO m, Arbitrary a) => m a
mockArbitrary = liftIO (generate arbitrary)
instance (Arbitrary (HList ls), Arbitrary a)
=> Arbitrary (Headers ls a) where
arbitrary = Headers <$> arbitrary <*> arbitrary
instance Arbitrary (HList '[]) where
arbitrary = pure HNil
instance (Arbitrary a, Arbitrary (HList hs))
=> Arbitrary (HList (Header h a ': hs)) where
arbitrary = HCons <$> fmap Header arbitrary <*> arbitrary
instance Arbitrary NoContent where
arbitrary = pure NoContent