servant-validate-0.1.0.0: Chekc static properties of servant APIs
Copyright(c) Justin Le 2021
LicenseBSD3
Maintainerjustin@jle.im
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Servant.Validate

Description

A package with "test suites" to help verify that your servant APIs are valid at compile-time. Currently the only property tested is that there are no duplicated paths. See README for more information on usage.

Synopsis

Documentation

class HasApiTree (api :: Type) where Source #

Has a valid well-formed API Tree

Associated Types

type ToApiTree api :: ApiTree Source #

Methods

sApiTree :: SApiTree (ToApiTree api) Source #

Useful runtime witness of the API tree; use to inspect it with reflectApiTree. This is not used in any part of the actual validation; is just an extra treat.

Instances

Instances details
(HasApiTree a, HasApiTree b) => HasApiTree (a :<|> b) Source # 
Instance details

Defined in Servant.Validate

Associated Types

type ToApiTree (a :<|> b) :: ApiTree Source #

HasApiTree api => HasApiTree (HttpVersion :> api) Source # 
Instance details

Defined in Servant.Validate

Associated Types

type ToApiTree (HttpVersion :> api) :: ApiTree Source #

HasApiTree api => HasApiTree (StreamBody' mods framing ct a :> api) Source # 
Instance details

Defined in Servant.Validate

Associated Types

type ToApiTree (StreamBody' mods framing ct a :> api) :: ApiTree Source #

Methods

sApiTree :: SApiTree (ToApiTree (StreamBody' mods framing ct a :> api)) Source #

HasApiTree api => HasApiTree (ReqBody' mods ct a :> api) Source # 
Instance details

Defined in Servant.Validate

Associated Types

type ToApiTree (ReqBody' mods ct a :> api) :: ApiTree Source #

Methods

sApiTree :: SApiTree (ToApiTree (ReqBody' mods ct a :> api)) Source #

HasApiTree api => HasApiTree (RemoteHost :> api) Source # 
Instance details

Defined in Servant.Validate

Associated Types

type ToApiTree (RemoteHost :> api) :: ApiTree Source #

HasApiTree api => HasApiTree (QueryParam' mods sym a :> api) Source # 
Instance details

Defined in Servant.Validate

Associated Types

type ToApiTree (QueryParam' mods sym a :> api) :: ApiTree Source #

Methods

sApiTree :: SApiTree (ToApiTree (QueryParam' mods sym a :> api)) Source #

HasApiTree api => HasApiTree (QueryParams s a :> api) Source # 
Instance details

Defined in Servant.Validate

Associated Types

type ToApiTree (QueryParams s a :> api) :: ApiTree Source #

HasApiTree api => HasApiTree (QueryFlag s :> api) Source # 
Instance details

Defined in Servant.Validate

Associated Types

type ToApiTree (QueryFlag s :> api) :: ApiTree Source #

HasApiTree api => HasApiTree (Header' mods sym a :> api) Source # 
Instance details

Defined in Servant.Validate

Associated Types

type ToApiTree (Header' mods sym a :> api) :: ApiTree Source #

Methods

sApiTree :: SApiTree (ToApiTree (Header' mods sym a :> api)) Source #

HasApiTree api => HasApiTree (IsSecure :> api) Source # 
Instance details

Defined in Servant.Validate

Associated Types

type ToApiTree (IsSecure :> api) :: ApiTree Source #

HasApiTree api => HasApiTree (AuthProtect tag :> api) Source # 
Instance details

Defined in Servant.Validate

Associated Types

type ToApiTree (AuthProtect tag :> api) :: ApiTree Source #

HasApiTree api => HasApiTree (Summary s :> api) Source # 
Instance details

Defined in Servant.Validate

Associated Types

type ToApiTree (Summary s :> api) :: ApiTree Source #

HasApiTree api => HasApiTree (Description s :> api) Source # 
Instance details

Defined in Servant.Validate

Associated Types

type ToApiTree (Description s :> api) :: ApiTree Source #

HasApiTree api => HasApiTree (Capture' mods sym a :> api) Source # 
Instance details

Defined in Servant.Validate

Associated Types

type ToApiTree (Capture' mods sym a :> api) :: ApiTree Source #

Methods

sApiTree :: SApiTree (ToApiTree (Capture' mods sym a :> api)) Source #

HasApiTree api => HasApiTree (CaptureAll sym v :> api) Source # 
Instance details

Defined in Servant.Validate

Associated Types

type ToApiTree (CaptureAll sym v :> api) :: ApiTree Source #

Methods

sApiTree :: SApiTree (ToApiTree (CaptureAll sym v :> api)) Source #

HasApiTree api => HasApiTree (BasicAuth realm a :> api) Source # 
Instance details

Defined in Servant.Validate

Associated Types

type ToApiTree (BasicAuth realm a :> api) :: ApiTree Source #

Methods

sApiTree :: SApiTree (ToApiTree (BasicAuth realm a :> api)) Source #

HasApiTree api => HasApiTree (Vault :> api) Source # 
Instance details

Defined in Servant.Validate

Associated Types

type ToApiTree (Vault :> api) :: ApiTree Source #

(KnownSymbol path, HasApiTree api) => HasApiTree (path :> api) Source # 
Instance details

Defined in Servant.Validate

Associated Types

type ToApiTree (path :> api) :: ApiTree Source #

Methods

sApiTree :: SApiTree (ToApiTree (path :> api)) Source #

(MethodString k, KnownSymbol (ToMethodString m)) => HasApiTree (Verb m s t a) Source # 
Instance details

Defined in Servant.Validate

Associated Types

type ToApiTree (Verb m s t a) :: ApiTree Source #

Methods

sApiTree :: SApiTree (ToApiTree (Verb m s t a)) Source #

class MethodString k Source #

A type-level version of ReflectMethod.

Associated Types

type ToMethodString (x :: k) :: Symbol Source #

Instances

Instances details
MethodString Symbol Source # 
Instance details

Defined in Servant.Validate

Associated Types

type ToMethodString x :: Symbol Source #

MethodString StdMethod Source # 
Instance details

Defined in Servant.Validate

Associated Types

type ToMethodString x :: Symbol Source #

validApiTree :: forall api. (HasApiTree api, Typeable (ToApiTree api)) => Proxy api -> ValidApiTree api Source #

The full validator. To use:

serverApi :: Proxy ServerApi
serverApi = Proxy

validServerApi :: ValidApiTree ServerApi
validServerApi = validApiTree serverApi

type ValidApiTree api = TypeRep (ToApiTree api) Source #

To be used with validApiTree.

reflectApiTree :: forall api. (HasApiTree api, Typeable (ToApiTree api)) => ApiTreeMap Source #

Useful utility to view the routing structure of a tree; similar to layout.

reflectApiTree_ :: TypeRep (apiTree :: ApiTree) -> ApiTreeMap Source #

Version of reflectApiTree taking an explicit TypeRep.

data SApiTree :: ApiTree -> Type where Source #

Constructors

SBranch :: Prod SSym ms -> Prod (Tup SSym SApiTree) ts -> SApiTree ('Branch ms ts) 

Instances

Instances details
Show (SApiTree api) Source # 
Instance details

Defined in Servant.Validate.Internal

Methods

showsPrec :: Int -> SApiTree api -> ShowS #

show :: SApiTree api -> String #

showList :: [SApiTree api] -> ShowS #

reflectSApiTree :: SApiTree api -> ApiTreeMap Source #