curl-runnings-0.16.0: A framework for declaratively writing curl based API tests

Safe HaskellNone
LanguageHaskell2010

Testing.CurlRunnings.Types

Description

Data types for curl-runnings tests

Synopsis

Documentation

data AssertionFailure Source #

Represents the different type of test failures we can have. A single test case | might return many assertion failures.

Constructors

DataFailure CurlCase JsonMatcher (Maybe Value)

The json we got back was wrong. We include this redundant field (it's included in the CurlCase field above) in order to enforce at the type level that we have to be expecting some data in order to have this type of failure.

StatusFailure CurlCase Int

The status code we got back was wrong

HeaderFailure CurlCase HeaderMatcher Headers

The headers we got back were wrong

QueryFailure CurlCase QueryError

Something went wrong with a test case json query

UnexpectedFailure

Something else

Instances
Show AssertionFailure Source # 
Instance details

Defined in Testing.CurlRunnings.Types

Generic AssertionFailure Source # 
Instance details

Defined in Testing.CurlRunnings.Types

Associated Types

type Rep AssertionFailure :: Type -> Type #

ToJSON AssertionFailure Source # 
Instance details

Defined in Testing.CurlRunnings.Types

type Rep AssertionFailure Source # 
Instance details

Defined in Testing.CurlRunnings.Types

type Rep AssertionFailure = D1 (MetaData "AssertionFailure" "Testing.CurlRunnings.Types" "curl-runnings-0.16.0-KGucIP1ebVW8qKkwcHpkr4" False) ((C1 (MetaCons "DataFailure" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 CurlCase) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 JsonMatcher) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Value)))) :+: C1 (MetaCons "StatusFailure" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 CurlCase) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int))) :+: (C1 (MetaCons "HeaderFailure" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 CurlCase) :*: (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 HeaderMatcher) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Headers))) :+: (C1 (MetaCons "QueryFailure" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 CurlCase) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 QueryError)) :+: C1 (MetaCons "UnexpectedFailure" PrefixI False) (U1 :: Type -> Type))))

data CaseResult Source #

A type representing the result of a single curl, and all associated assertions

Instances
Show CaseResult Source # 
Instance details

Defined in Testing.CurlRunnings.Types

Generic CaseResult Source # 
Instance details

Defined in Testing.CurlRunnings.Types

Associated Types

type Rep CaseResult :: Type -> Type #

ToJSON CaseResult Source # 
Instance details

Defined in Testing.CurlRunnings.Types

type Rep CaseResult Source # 
Instance details

Defined in Testing.CurlRunnings.Types

data CurlCase Source #

A single curl test case, the basic foundation of a curl-runnings test.

Constructors

CurlCase 

Fields

Instances
Show CurlCase Source # 
Instance details

Defined in Testing.CurlRunnings.Types

Generic CurlCase Source # 
Instance details

Defined in Testing.CurlRunnings.Types

Associated Types

type Rep CurlCase :: Type -> Type #

Methods

from :: CurlCase -> Rep CurlCase x #

to :: Rep CurlCase x -> CurlCase #

ToJSON CurlCase Source # 
Instance details

Defined in Testing.CurlRunnings.Types

FromJSON CurlCase Source # 
Instance details

Defined in Testing.CurlRunnings.Types

type Rep CurlCase Source # 
Instance details

Defined in Testing.CurlRunnings.Types

data CurlRunningsState Source #

The state of a suite. Tracks environment variables, and all the test results so far

data CurlSuite Source #

A wrapper type around a set of test cases. This is the top level spec type that we parse a test spec file into

Constructors

CurlSuite 
Instances
Show CurlSuite Source # 
Instance details

Defined in Testing.CurlRunnings.Types

Generic CurlSuite Source # 
Instance details

Defined in Testing.CurlRunnings.Types

Associated Types

type Rep CurlSuite :: Type -> Type #

ToJSON CurlSuite Source # 
Instance details

Defined in Testing.CurlRunnings.Types

FromJSON CurlSuite Source # 
Instance details

Defined in Testing.CurlRunnings.Types

type Rep CurlSuite Source # 
Instance details

Defined in Testing.CurlRunnings.Types

type Rep CurlSuite = D1 (MetaData "CurlSuite" "Testing.CurlRunnings.Types" "curl-runnings-0.16.0-KGucIP1ebVW8qKkwcHpkr4" False) (C1 (MetaCons "CurlSuite" PrefixI True) (S1 (MetaSel (Just "suiteCases") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [CurlCase]) :*: S1 (MetaSel (Just "suiteCaseFilter") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))))

type FullQueryText = Text Source #

The full string in which a query appears, eg "prefix-${{RESPONSES[0].key.another_key[0].last_key}}"

data Header Source #

A representation of a single header

Constructors

Header Text Text 
Instances
Eq Header Source # 
Instance details

Defined in Testing.CurlRunnings.Internal.Headers

Methods

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

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

Show Header Source # 
Instance details

Defined in Testing.CurlRunnings.Internal.Headers

Generic Header Source # 
Instance details

Defined in Testing.CurlRunnings.Internal.Headers

Associated Types

type Rep Header :: Type -> Type #

Methods

from :: Header -> Rep Header x #

to :: Rep Header x -> Header #

ToJSON Header Source # 
Instance details

Defined in Testing.CurlRunnings.Internal.Headers

type Rep Header Source # 
Instance details

Defined in Testing.CurlRunnings.Internal.Headers

type Rep Header = D1 (MetaData "Header" "Testing.CurlRunnings.Internal.Headers" "curl-runnings-0.16.0-KGucIP1ebVW8qKkwcHpkr4" False) (C1 (MetaCons "Header" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

data HeaderMatcher Source #

Collection of matchers to run against a single curl response

newtype Headers Source #

Simple container for a list of headers, useful for a vehicle for defining a fromJSON

Constructors

HeaderSet [Header] 
Instances
Eq Headers Source # 
Instance details

Defined in Testing.CurlRunnings.Internal.Headers

Methods

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

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

Show Headers Source # 
Instance details

Defined in Testing.CurlRunnings.Internal.Headers

Generic Headers Source # 
Instance details

Defined in Testing.CurlRunnings.Internal.Headers

Associated Types

type Rep Headers :: Type -> Type #

Methods

from :: Headers -> Rep Headers x #

to :: Rep Headers x -> Headers #

ToJSON Headers Source # 
Instance details

Defined in Testing.CurlRunnings.Internal.Headers

FromJSON Headers Source # 
Instance details

Defined in Testing.CurlRunnings.Internal.Headers

type Rep Headers Source # 
Instance details

Defined in Testing.CurlRunnings.Internal.Headers

type Rep Headers = D1 (MetaData "Headers" "Testing.CurlRunnings.Internal.Headers" "curl-runnings-0.16.0-KGucIP1ebVW8qKkwcHpkr4" True) (C1 (MetaCons "HeaderSet" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Header])))

data HttpMethod Source #

A basic enum for supported HTTP verbs

Constructors

GET 
POST 
PUT 
PATCH 
DELETE 
Instances
Show HttpMethod Source # 
Instance details

Defined in Testing.CurlRunnings.Types

Generic HttpMethod Source # 
Instance details

Defined in Testing.CurlRunnings.Types

Associated Types

type Rep HttpMethod :: Type -> Type #

ToJSON HttpMethod Source # 
Instance details

Defined in Testing.CurlRunnings.Types

FromJSON HttpMethod Source # 
Instance details

Defined in Testing.CurlRunnings.Types

type Rep HttpMethod Source # 
Instance details

Defined in Testing.CurlRunnings.Types

type Rep HttpMethod = D1 (MetaData "HttpMethod" "Testing.CurlRunnings.Types" "curl-runnings-0.16.0-KGucIP1ebVW8qKkwcHpkr4" False) ((C1 (MetaCons "GET" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "POST" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "PUT" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "PATCH" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "DELETE" PrefixI False) (U1 :: Type -> Type))))

data Index Source #

A single lookup operation in a json query

Constructors

CaseResultIndex Integer

Drill into the json of a specific test case. The RESPONSES object is accessible as an array of values that have come back from previous test cases

KeyIndex Text

A standard json key lookup.

ArrayIndex Integer

A standard json array index lookup.

Instances
Show Index Source # 
Instance details

Defined in Testing.CurlRunnings.Types

Methods

showsPrec :: Int -> Index -> ShowS #

show :: Index -> String #

showList :: [Index] -> ShowS #

data InterpolatedQuery Source #

A distinct parsed unit in a query

Constructors

LiteralText Text

Regular text, no query

InterpolatedQuery Text Query

Some leading text, then a query

NonInterpolatedQuery Query

Just a query, no leading text

data JsonMatcher Source #

A predicate to apply to the json body from the response

Constructors

Exactly Value

Performs ==

Contains [JsonSubExpr]

A list of matchers to make assertions that contains values exist in the response

NotContains [JsonSubExpr]

A list of matchers to make assertions that contains values do not exist in the response

MixedContains [JsonMatcher]

We're specifiying both Contains and NotContains matchers

Instances
Show JsonMatcher Source # 
Instance details

Defined in Testing.CurlRunnings.Types

Generic JsonMatcher Source # 
Instance details

Defined in Testing.CurlRunnings.Types

Associated Types

type Rep JsonMatcher :: Type -> Type #

ToJSON JsonMatcher Source # 
Instance details

Defined in Testing.CurlRunnings.Types

FromJSON JsonMatcher Source # 
Instance details

Defined in Testing.CurlRunnings.Types

type Rep JsonMatcher Source # 
Instance details

Defined in Testing.CurlRunnings.Types

data JsonSubExpr Source #

A matcher for a subvalue of a json payload

Constructors

ValueMatch Value

Assert some value anywhere in the json has a value equal to a given value. The motivation for this field is largely for checking contents of a top level array. It's also useful if you don't know the key ahead of time.

KeyMatch Text

Assert a key exists anywhere in the json

KeyValueMatch

Assert the key value pair can be found somewhere the json.

Fields

Instances
Show JsonSubExpr Source # 
Instance details

Defined in Testing.CurlRunnings.Types

Generic JsonSubExpr Source # 
Instance details

Defined in Testing.CurlRunnings.Types

Associated Types

type Rep JsonSubExpr :: Type -> Type #

ToJSON JsonSubExpr Source # 
Instance details

Defined in Testing.CurlRunnings.Types

FromJSON JsonSubExpr Source # 
Instance details

Defined in Testing.CurlRunnings.Types

type Rep JsonSubExpr Source # 
Instance details

Defined in Testing.CurlRunnings.Types

data KeyValuePair Source #

A representation of a single key-value pair

Constructors

KeyValuePair Text Text 

data PartialHeaderMatcher Source #

Specify a key, value, or both to match against in the returned headers of a response.

data Query Source #

A single entity to be queries from a json value

Constructors

Query [Index]

A single query contains a list of discrete index operations

EnvironmentVariable Text

Lookup a string in the environment

Instances
Show Query Source # 
Instance details

Defined in Testing.CurlRunnings.Types

Methods

showsPrec :: Int -> Query -> ShowS #

show :: Query -> String #

showList :: [Query] -> ShowS #

data QueryError Source #

Different errors relating to querying json from previous test cases

Constructors

QueryParseError Text Text

The query was malformed and couldn't be parsed

QueryTypeMismatch Text Value

The retrieved a value of the wrong type or was otherwise operating on the wrong type of thing

QueryValidationError Text

The query was parse-able

NullPointer Text Text

Tried to access a value in a null object.

Instances
Show QueryError Source # 
Instance details

Defined in Testing.CurlRunnings.Types

Generic QueryError Source # 
Instance details

Defined in Testing.CurlRunnings.Types

Associated Types

type Rep QueryError :: Type -> Type #

ToJSON QueryError Source # 
Instance details

Defined in Testing.CurlRunnings.Types

type Rep QueryError Source # 
Instance details

Defined in Testing.CurlRunnings.Types

type SingleQueryText = Text Source #

The string for one query given the FullQueryText above, the single query text would be RESPONSES[0].key.another_key[0].last_key

data StatusCodeMatcher Source #

Check the status code of a response. You can specify one or many valid codes.

Constructors

ExactCode Int 
AnyCodeIn [Int] 
Instances
Show StatusCodeMatcher Source # 
Instance details

Defined in Testing.CurlRunnings.Types

Generic StatusCodeMatcher Source # 
Instance details

Defined in Testing.CurlRunnings.Types

Associated Types

type Rep StatusCodeMatcher :: Type -> Type #

ToJSON StatusCodeMatcher Source # 
Instance details

Defined in Testing.CurlRunnings.Types

FromJSON StatusCodeMatcher Source # 
Instance details

Defined in Testing.CurlRunnings.Types

type Rep StatusCodeMatcher Source # 
Instance details

Defined in Testing.CurlRunnings.Types

type Rep StatusCodeMatcher = D1 (MetaData "StatusCodeMatcher" "Testing.CurlRunnings.Types" "curl-runnings-0.16.0-KGucIP1ebVW8qKkwcHpkr4" False) (C1 (MetaCons "ExactCode" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Int)) :+: C1 (MetaCons "AnyCodeIn" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Int])))

isFailing :: CaseResult -> Bool Source #

Simple predicate that checks if the result is failing

isPassing :: CaseResult -> Bool Source #

Simple predicate that checks if the result is passing