servant-quickcheck-0.0.8.0: QuickCheck entire APIs

Safe HaskellNone
LanguageHaskell2010

Servant.QuickCheck

Contents

Description

Servant.QuickCheck provides utilities related to using QuickCheck over an API. Rather than specifying properties that individual handlers must satisfy, you can state properties that ought to hold true of the entire API.

While the API must be described with servant types, the server being tested itself need not be implemented with servant-server (or indeed, written in Haskell).

The documentation of the Useful predicates sections is meant to serve as a set of helpful pointers for learning more about best practices concerning REST APIs.

Synopsis

Property testing

serverSatisfies :: HasGenRequest a => Proxy a -> BaseUrl -> Args -> Predicates -> Expectation Source #

Check that a server satisfies the set of properties specified.

Note that, rather than having separate tests for each property you'd like to test, you should generally prefer to combine all properties into a single test. This enables a more parsimonious generation of requests and responses with the same testing depth.

Example usage:

goodAPISpec = describe "my server" $ do

  it "follows best practices" $ do
    withServantServer api server $ \burl ->
      serverSatisfies api burl stdArgs (not500
                                    <%> onlyJsonObjects
                                    <%> notAllowedContainsAllowHeader
                                    <%> mempty)

Since 0.0.0.0

Predicates

Useful predicates

The predicates below are often useful. Some check RFC compliance; some are best practice, and some are useful to check that APIs follow in-house best-practices. Included in the documentation for each is a list of references to any relevant RFCs and other links, as well as what type of predicate it is (RFC Compliance, Best Practice, Optional).

RFCs distinguish between the force of requirements (e.g. MUST vs. SHOULD). RFC Compliance includes any absolute requirements present in RFCs. The Best Practices includes, in addition to RFC recommendations, recommendations found elsewhere or generally accepted.

not500 :: ResponsePredicate Source #

Best Practice

500 Internal Server Error should be avoided - it may represent some issue with the application code, and it moreover gives the client little indication of how to proceed or what went wrong.

This function checks that the response code is not 500.

Since 0.0.0.0

notLongerThan :: Integer -> RequestPredicate Source #

Optional

This function checks that the response from the server does not take longer than the specified number of nanoseconds.

Since 0.0.2.1

onlyJsonObjects :: ResponsePredicate Source #

Best Practice

Returning anything other than an object when returning JSON is considered bad practice, as:

  1. it is hard to modify the returned value while maintaining backwards compatibility
  2. many older tools do not support top-level arrays
  3. whether top-level numbers, booleans, or strings are valid JSON depends on what RFC you're going by
  4. there are security issues with top-level arrays

This function checks that any application/json responses only return JSON objects (and not arrays, strings, numbers, or booleans) at the top level.

References:

Since 0.0.0.0

honoursAcceptHeader :: RequestPredicate Source #

RFC Compliance

When a request contains an Accept header, the server must either return content in one of the requested representations, or respond with 406 Not Acceptable.

This function checks that every *successful* response has a Content-Type header that matches the Accept header. It does *not* check that the server matches the quality descriptions of the Accept header correctly.

References:

Since 0.0.0.0

notAllowedContainsAllowHeader :: RequestPredicate Source #

RFC Compliance

When an HTTP request has a method that is not allowed, a 405 response should be returned. Additionally, it is good practice to return an Allow header with the list of allowed methods.

This function checks that every 405 Method Not Allowed response contains an Allow header with a list of standard HTTP methods.

Note that servant itself does not currently set the Allow headers.

References:

Since 0.0.0.0

unauthorizedContainsWWWAuthenticate :: ResponsePredicate Source #

RFC Compliance

Any 401 Unauthorized response must include a WWW-Authenticate header.

This function checks that, if a response has status code 401, it contains a WWW-Authenticate header.

References:

Since 0.0.0.0

getsHaveLastModifiedHeader :: RequestPredicate Source #

Optional

The Last-Modified header represents the time a resource was last modified. It is used to drive caching and conditional requests.

When using this mechanism, the server adds the Last-Modified header to responses. Clients may then make requests with the If-Modified-Since header to conditionally request resources. If the resource has not changed since that date, the server responds with a status code of 304 (Not Modified) without a response body.

The Last-Modified header can also be used in conjunction with the If-Unmodified-Since header to drive optimistic concurrency.

The Last-Modified date must be in RFC 822 format.

References:

Since 0.0.2.1

getsHaveCacheControlHeader :: RequestPredicate Source #

Best Practice

Whether or not a representation should be cached, it is good practice to have a Cache-Control header for GET requests. If the representation should not be cached, used Cache-Control: no-cache.

This function checks that GET responses have Cache-Control header. It does NOT currently check that the header is valid.

References:

Since 0.0.0.0

headsHaveCacheControlHeader :: RequestPredicate Source #

Best Practice

Like getsHaveCacheControlHeader, but for HEAD requests.

Since 0.0.0.0

createContainsValidLocation :: RequestPredicate Source #

Optional

When creating a new resource, it is good practice to provide a Location header with a link to the created resource.

This function checks that every 201 Created response contains a Location header, and that the link in it responds with a 2XX response code to GET requests.

This is considered optional because other means of linking to the resource (e.g. via the response body) are also acceptable; linking to the resource in some way is considered best practice.

References:

Since 0.0.0.0

Html Predicates

htmlIncludesDoctype :: ResponsePredicate Source #

RFC Compliance
An HTML
document will start with exactly this string: html

This function checks that HTML documents (those with `Content-Type: text/html...`) include a DOCTYPE declaration at the top. We do not enforce capital case for the string DOCTYPE.

References:

Predicate utilities and types

(<%>) :: JoinPreds a => a -> Predicates -> Predicates infixr 6 Source #

Adds a new predicate (either ResponsePredicate or RequestPredicate) to the existing predicates.

not500 <%> onlyJsonObjects <%> empty

Since 0.0.0.0

data Predicates Source #

A set of predicates. Construct one with mempty and <%>.

Instances
Generic Predicates Source # 
Instance details

Defined in Servant.QuickCheck.Internal.Predicates

Associated Types

type Rep Predicates :: Type -> Type #

Semigroup Predicates Source # 
Instance details

Defined in Servant.QuickCheck.Internal.Predicates

Monoid Predicates Source # 
Instance details

Defined in Servant.QuickCheck.Internal.Predicates

type Rep Predicates Source # 
Instance details

Defined in Servant.QuickCheck.Internal.Predicates

type Rep Predicates = D1 (MetaData "Predicates" "Servant.QuickCheck.Internal.Predicates" "servant-quickcheck-0.0.8.0-6Q2MZs7NmCTAjXO2KLRcj3" False) (C1 (MetaCons "Predicates" PrefixI True) (S1 (MetaSel (Just "requestPredicates") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 RequestPredicate) :*: S1 (MetaSel (Just "responsePredicates") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ResponsePredicate)))

newtype ResponsePredicate Source #

A predicate that depends only on the response.

Since 0.0.0.0

newtype RequestPredicate Source #

A predicate that depends on both the request and the response.

Since 0.0.0.0

Equality testing

serversEqual :: HasGenRequest a => Proxy a -> BaseUrl -> BaseUrl -> Args -> ResponseEquality ByteString -> Expectation Source #

Check that the two servers running under the provided BaseUrls behave identically by randomly generating arguments (captures, query params, request bodies, headers, etc.) expected by the server. If, given the same request, the response is not the same (according to the definition of == for the return datatype), the Expectation fails, printing the counterexample.

The Int argument specifies maximum number of test cases to generate and run.

Evidently, if the behaviour of the server is expected to be non-deterministic, this function may produce spurious failures

Note that only valid requests are generated and tested. As an example of why this matters, let's say your API specifies that a particular endpoint can only generate JSON. serversEqual will then not generate any requests with an Accept header _other_ than application/json. It may therefore fail to notice that one application, when the request has Accept: text/html, returns a 406 Not Acceptable HTTP response, and another returns a 200 Success, but with application/json as the content-type.

The fact that only valid requests are tested also means that no endpoints not listed in the API type are tested.

Since 0.0.0.0

Response equality

Often the normal equality of responses is not what we want. For example, if responses contain a Date header with the time of the response, responses will fail to be equal even though they morally are. This datatype represents other means of checking equality *** Useful ResponseEqualitys

bodyEquality :: Eq b => ResponseEquality b Source #

ByteString Eq instance over the response body.

Since 0.0.0.0

jsonEquality :: JsonEq b => ResponseEquality b Source #

Equality as Value. This means that if two bodies are equal as JSON (e.g., insignificant whitespace difference) they are considered equal.

Since 0.0.3.0

allEquality :: Eq b => ResponseEquality b Source #

Use Eq instance for Response

Since 0.0.0.0

Response equality type

Test setup helpers

Helpers to setup and teardown servant servers during tests.

withServantServer :: HasServer a '[] => Proxy a -> IO (Server a) -> (BaseUrl -> IO r) -> IO r Source #

Start a servant application on an open port, run the provided function, then stop the application.

Since 0.0.0.0

withServantServerAndContext :: HasServer a ctx => Proxy a -> Context ctx -> IO (Server a) -> (BaseUrl -> IO r) -> IO r Source #

Like withServantServer, but allows passing in a Context to the application.

Since 0.0.0.0

defaultArgs :: Args Source #

QuickCheck Args with 1000 rather than 100 test cases.

Since 0.0.0.0

Re-exports

Types and constructors from other packages that are generally needed for using servant-quickcheck.

data BaseUrl #

Simple data type to represent the target of HTTP requests for servant's automatically-generated clients.

Constructors

BaseUrl 

Fields

Instances
Eq BaseUrl 
Instance details

Defined in Servant.Client.Core.BaseUrl

Methods

(==) :: BaseUrl -> BaseUrl -> Bool #

(/=) :: BaseUrl -> BaseUrl -> Bool #

Data BaseUrl 
Instance details

Defined in Servant.Client.Core.BaseUrl

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BaseUrl -> c BaseUrl #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BaseUrl #

toConstr :: BaseUrl -> Constr #

dataTypeOf :: BaseUrl -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c BaseUrl) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BaseUrl) #

gmapT :: (forall b. Data b => b -> b) -> BaseUrl -> BaseUrl #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BaseUrl -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BaseUrl -> r #

gmapQ :: (forall d. Data d => d -> u) -> BaseUrl -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BaseUrl -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BaseUrl -> m BaseUrl #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BaseUrl -> m BaseUrl #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BaseUrl -> m BaseUrl #

Ord BaseUrl 
Instance details

Defined in Servant.Client.Core.BaseUrl

Show BaseUrl 
Instance details

Defined in Servant.Client.Core.BaseUrl

Generic BaseUrl 
Instance details

Defined in Servant.Client.Core.BaseUrl

Associated Types

type Rep BaseUrl :: Type -> Type #

Methods

from :: BaseUrl -> Rep BaseUrl x #

to :: Rep BaseUrl x -> BaseUrl #

Lift BaseUrl 
Instance details

Defined in Servant.Client.Core.BaseUrl

Methods

lift :: BaseUrl -> Q Exp #

ToJSON BaseUrl
>>> traverse_ (LBS8.putStrLn . encode) $ parseBaseUrl "api.example.com"
"http://api.example.com"
Instance details

Defined in Servant.Client.Core.BaseUrl

ToJSONKey BaseUrl
>>> :{
traverse_ (LBS8.putStrLn . encode) $ do
  u1 <- parseBaseUrl "api.example.com"
  u2 <- parseBaseUrl "example.com"
  return $ Map.fromList [(u1, 'x'), (u2, 'y')]
:}
{"http://api.example.com":"x","http://example.com":"y"}
Instance details

Defined in Servant.Client.Core.BaseUrl

FromJSON BaseUrl
>>> parseBaseUrl "api.example.com" >>= decode . encode :: Maybe BaseUrl
Just (BaseUrl {baseUrlScheme = Http, baseUrlHost = "api.example.com", baseUrlPort = 80, baseUrlPath = ""})
Instance details

Defined in Servant.Client.Core.BaseUrl

FromJSONKey BaseUrl 
Instance details

Defined in Servant.Client.Core.BaseUrl

NFData BaseUrl 
Instance details

Defined in Servant.Client.Core.BaseUrl

Methods

rnf :: BaseUrl -> () #

type Rep BaseUrl 
Instance details

Defined in Servant.Client.Core.BaseUrl

type Rep BaseUrl = D1 (MetaData "BaseUrl" "Servant.Client.Core.BaseUrl" "servant-client-core-0.17-6TEb4JOolq16hAUWK9fzoL" False) (C1 (MetaCons "BaseUrl" PrefixI True) ((S1 (MetaSel (Just "baseUrlScheme") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Scheme) :*: S1 (MetaSel (Just "baseUrlHost") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) :*: (S1 (MetaSel (Just "baseUrlPort") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int) :*: S1 (MetaSel (Just "baseUrlPath") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String))))

data Scheme #

URI scheme to use

Constructors

Http

http://

Https

https://

Instances
Eq Scheme 
Instance details

Defined in Servant.Client.Core.BaseUrl

Methods

(==) :: Scheme -> Scheme -> Bool #

(/=) :: Scheme -> Scheme -> Bool #

Data Scheme 
Instance details

Defined in Servant.Client.Core.BaseUrl

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Scheme -> c Scheme #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Scheme #

toConstr :: Scheme -> Constr #

dataTypeOf :: Scheme -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Scheme) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Scheme) #

gmapT :: (forall b. Data b => b -> b) -> Scheme -> Scheme #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Scheme -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Scheme -> r #

gmapQ :: (forall d. Data d => d -> u) -> Scheme -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Scheme -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Scheme -> m Scheme #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Scheme -> m Scheme #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Scheme -> m Scheme #

Ord Scheme 
Instance details

Defined in Servant.Client.Core.BaseUrl

Show Scheme 
Instance details

Defined in Servant.Client.Core.BaseUrl

Generic Scheme 
Instance details

Defined in Servant.Client.Core.BaseUrl

Associated Types

type Rep Scheme :: Type -> Type #

Methods

from :: Scheme -> Rep Scheme x #

to :: Rep Scheme x -> Scheme #

Lift Scheme 
Instance details

Defined in Servant.Client.Core.BaseUrl

Methods

lift :: Scheme -> Q Exp #

type Rep Scheme 
Instance details

Defined in Servant.Client.Core.BaseUrl

type Rep Scheme = D1 (MetaData "Scheme" "Servant.Client.Core.BaseUrl" "servant-client-core-0.17-6TEb4JOolq16hAUWK9fzoL" False) (C1 (MetaCons "Http" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Https" PrefixI False) (U1 :: Type -> Type))

data Args #

Args specifies arguments to the QuickCheck driver

Constructors

Args 

Fields

  • replay :: Maybe (QCGen, Int)

    Should we replay a previous test? Note: saving a seed from one version of QuickCheck and replaying it in another is not supported. If you want to store a test case permanently you should save the test case itself.

  • maxSuccess :: Int

    Maximum number of successful tests before succeeding. Testing stops at the first failure. If all tests are passing and you want to run more tests, increase this number.

  • maxDiscardRatio :: Int

    Maximum number of discarded tests per successful test before giving up

  • maxSize :: Int

    Size to use for the biggest test cases

  • chatty :: Bool

    Whether to print anything

  • maxShrinks :: Int

    Maximum number of shrinks to before giving up. Setting this to zero turns shrinking off.

Instances
Read Args 
Instance details

Defined in Test.QuickCheck.Test

Show Args 
Instance details

Defined in Test.QuickCheck.Test

Methods

showsPrec :: Int -> Args -> ShowS #

show :: Args -> String #

showList :: [Args] -> ShowS #

data Proxy (t :: k) :: forall k. k -> Type #

Proxy is a type that holds no data, but has a phantom parameter of arbitrary type (or even kind). Its use is to provide type information, even though there is no value available of that type (or it may be too costly to create one).

Historically, Proxy :: Proxy a is a safer alternative to the 'undefined :: a' idiom.

>>> Proxy :: Proxy (Void, Int -> Int)
Proxy

Proxy can even hold types of higher kinds,

>>> Proxy :: Proxy Either
Proxy
>>> Proxy :: Proxy Functor
Proxy
>>> Proxy :: Proxy complicatedStructure
Proxy

Constructors

Proxy 
Instances
Generic1 (Proxy :: k -> Type) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 Proxy :: k -> Type #

Methods

from1 :: Proxy a -> Rep1 Proxy a #

to1 :: Rep1 Proxy a -> Proxy a #

Monad (Proxy :: Type -> Type)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

(>>=) :: Proxy a -> (a -> Proxy b) -> Proxy b #

(>>) :: Proxy a -> Proxy b -> Proxy b #

return :: a -> Proxy a #

fail :: String -> Proxy a #

Functor (Proxy :: Type -> Type)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

fmap :: (a -> b) -> Proxy a -> Proxy b #

(<$) :: a -> Proxy b -> Proxy a #

Applicative (Proxy :: Type -> Type)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

pure :: a -> Proxy a #

(<*>) :: Proxy (a -> b) -> Proxy a -> Proxy b #

liftA2 :: (a -> b -> c) -> Proxy a -> Proxy b -> Proxy c #

(*>) :: Proxy a -> Proxy b -> Proxy b #

(<*) :: Proxy a -> Proxy b -> Proxy a #

Foldable (Proxy :: Type -> Type)

Since: base-4.7.0.0

Instance details

Defined in Data.Foldable

Methods

fold :: Monoid m => Proxy m -> m #

foldMap :: Monoid m => (a -> m) -> Proxy a -> m #

foldr :: (a -> b -> b) -> b -> Proxy a -> b #

foldr' :: (a -> b -> b) -> b -> Proxy a -> b #

foldl :: (b -> a -> b) -> b -> Proxy a -> b #

foldl' :: (b -> a -> b) -> b -> Proxy a -> b #

foldr1 :: (a -> a -> a) -> Proxy a -> a #

foldl1 :: (a -> a -> a) -> Proxy a -> a #

toList :: Proxy a -> [a] #

null :: Proxy a -> Bool #

length :: Proxy a -> Int #

elem :: Eq a => a -> Proxy a -> Bool #

maximum :: Ord a => Proxy a -> a #

minimum :: Ord a => Proxy a -> a #

sum :: Num a => Proxy a -> a #

product :: Num a => Proxy a -> a #

Traversable (Proxy :: Type -> Type)

Since: base-4.7.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> Proxy a -> f (Proxy b) #

sequenceA :: Applicative f => Proxy (f a) -> f (Proxy a) #

mapM :: Monad m => (a -> m b) -> Proxy a -> m (Proxy b) #

sequence :: Monad m => Proxy (m a) -> m (Proxy a) #

FromJSON1 (Proxy :: Type -> Type) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

liftParseJSON :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (Proxy a) #

liftParseJSONList :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [Proxy a] #

Alternative (Proxy :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Proxy

Methods

empty :: Proxy a #

(<|>) :: Proxy a -> Proxy a -> Proxy a #

some :: Proxy a -> Proxy [a] #

many :: Proxy a -> Proxy [a] #

MonadPlus (Proxy :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Proxy

Methods

mzero :: Proxy a #

mplus :: Proxy a -> Proxy a -> Proxy a #

Eq1 (Proxy :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftEq :: (a -> b -> Bool) -> Proxy a -> Proxy b -> Bool #

Ord1 (Proxy :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftCompare :: (a -> b -> Ordering) -> Proxy a -> Proxy b -> Ordering #

Read1 (Proxy :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Proxy a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Proxy a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Proxy a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Proxy a] #

Show1 (Proxy :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Proxy a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Proxy a] -> ShowS #

Hashable1 (Proxy :: Type -> Type) 
Instance details

Defined in Data.Hashable.Class

Methods

liftHashWithSalt :: (Int -> a -> Int) -> Int -> Proxy a -> Int #

Bounded (Proxy t)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

minBound :: Proxy t #

maxBound :: Proxy t #

Enum (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

succ :: Proxy s -> Proxy s #

pred :: Proxy s -> Proxy s #

toEnum :: Int -> Proxy s #

fromEnum :: Proxy s -> Int #

enumFrom :: Proxy s -> [Proxy s] #

enumFromThen :: Proxy s -> Proxy s -> [Proxy s] #

enumFromTo :: Proxy s -> Proxy s -> [Proxy s] #

enumFromThenTo :: Proxy s -> Proxy s -> Proxy s -> [Proxy s] #

Eq (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

(==) :: Proxy s -> Proxy s -> Bool #

(/=) :: Proxy s -> Proxy s -> Bool #

Ord (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

compare :: Proxy s -> Proxy s -> Ordering #

(<) :: Proxy s -> Proxy s -> Bool #

(<=) :: Proxy s -> Proxy s -> Bool #

(>) :: Proxy s -> Proxy s -> Bool #

(>=) :: Proxy s -> Proxy s -> Bool #

max :: Proxy s -> Proxy s -> Proxy s #

min :: Proxy s -> Proxy s -> Proxy s #

Read (Proxy t)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Show (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

showsPrec :: Int -> Proxy s -> ShowS #

show :: Proxy s -> String #

showList :: [Proxy s] -> ShowS #

Ix (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

range :: (Proxy s, Proxy s) -> [Proxy s] #

index :: (Proxy s, Proxy s) -> Proxy s -> Int #

unsafeIndex :: (Proxy s, Proxy s) -> Proxy s -> Int

inRange :: (Proxy s, Proxy s) -> Proxy s -> Bool #

rangeSize :: (Proxy s, Proxy s) -> Int #

unsafeRangeSize :: (Proxy s, Proxy s) -> Int

Generic (Proxy t) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (Proxy t) :: Type -> Type #

Methods

from :: Proxy t -> Rep (Proxy t) x #

to :: Rep (Proxy t) x -> Proxy t #

Semigroup (Proxy s)

Since: base-4.9.0.0

Instance details

Defined in Data.Proxy

Methods

(<>) :: Proxy s -> Proxy s -> Proxy s #

sconcat :: NonEmpty (Proxy s) -> Proxy s #

stimes :: Integral b => b -> Proxy s -> Proxy s #

Monoid (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

mempty :: Proxy s #

mappend :: Proxy s -> Proxy s -> Proxy s #

mconcat :: [Proxy s] -> Proxy s #

Hashable (Proxy a) 
Instance details

Defined in Data.Hashable.Class

Methods

hashWithSalt :: Int -> Proxy a -> Int #

hash :: Proxy a -> Int #

FromJSON (Proxy a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

type Rep1 (Proxy :: k -> Type)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

type Rep1 (Proxy :: k -> Type) = D1 (MetaData "Proxy" "Data.Proxy" "base" False) (C1 (MetaCons "Proxy" PrefixI False) (U1 :: k -> Type))
type Rep (Proxy t)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

type Rep (Proxy t) = D1 (MetaData "Proxy" "Data.Proxy" "base" False) (C1 (MetaCons "Proxy" PrefixI False) (U1 :: Type -> Type))