fradrive/test/Foundation/ServantSpec.hs

37 lines
1.2 KiB
Haskell

{-# LANGUAGE UndecidableInstances #-}
module Foundation.ServantSpec where
import TestImport hiding ((:>))
import ModelSpec ()
import Foundation.Servant.Types
import Servant.API
import Servant.QuickCheck.Internal.HasGenRequest (HasGenRequest(..))
import Data.CryptoID.Class.ImplicitNamespace
import Network.HTTP.Client (path)
instance (Arbitrary (CryptoID ciphertext plaintext), ToHttpApiData ciphertext, HasGenRequest sub) => HasGenRequest (CaptureCryptoID' mods ciphertext sym plaintext :> sub) where
genRequest _ = (oldf, ) $ do
old' <- old
new' <- toUrlPiece <$> new
return $ \burl -> let r = old' burl in r { path = encodeUtf8 new' <> path r }
where (oldf, old) = genRequest $ Proxy @sub
new = arbitrary @(CryptoID ciphertext plaintext)
instance HasGenRequest sub => HasGenRequest (CaptureBearerToken' mods :> sub) where
genRequest _ = genRequest $ Proxy @sub
instance HasGenRequest sub => HasGenRequest (CaptureBearerRestriction' mods restr :> sub) where
genRequest _ = genRequest $ Proxy @sub
instance HasGenRequest sub => HasGenRequest (ApiVersion major minor patch :> sub) where
genRequest _ = genRequest $ Proxy @sub
spec :: Spec
spec = return ()