hreq-core-0.1.0.0: Core functionality for Hreq Http client library

Safe HaskellNone
LanguageHaskell2010

Hreq.Core.API

Contents

Description

This module re-exports types and combinators required for type level construction of API request components and expected type structure of an http request response.

Synopsis

Request

Response

API Types and Kinds

MediaType

Streaming

TypeLevel

Verb

API Type Synonyms

type EmptyResponse v = Verb v ('[] :: [ResContent Type]) Source #

type RawResponse v = Verb v '[Raw] Source #

type PutJson a = Put '[ResBody JSON a] Source #

type GetJson a = Get '[ResBody JSON a] Source #

Response Type synonyms

type JsonBody (a :: Type) = ReqBody JSON a Source #

Re-exports

class ToHttpApiData a where #

Convert value to HTTP API data.

WARNING: Do not derive this using DeriveAnyClass as the generated instance will loop indefinitely.

Minimal complete definition

toUrlPiece | toQueryParam

Methods

toUrlPiece :: a -> Text #

Convert to URL path piece.

toEncodedUrlPiece :: a -> Builder #

Convert to a URL path piece, making sure to encode any special chars. The default definition uses encodePathSegmentsRelative, but this may be overriden with a more efficient version.

toHeader :: a -> ByteString #

Convert to HTTP header value.

toQueryParam :: a -> Text #

Convert to query param value.

Instances
ToHttpApiData Bool 
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData Char 
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData Double 
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData Float 
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData Int 
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData Int8 
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData Int16 
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData Int32 
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData Int64 
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData Integer 
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData Natural 
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData Ordering 
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData Word 
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData Word8 
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData Word16 
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData Word32 
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData Word64 
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData ()
>>> toUrlPiece ()
"_"
Instance details

Defined in Web.Internal.HttpApiData

Methods

toUrlPiece :: () -> Text #

toEncodedUrlPiece :: () -> Builder #

toHeader :: () -> ByteString #

toQueryParam :: () -> Text #

ToHttpApiData Void 
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData Version
>>> toUrlPiece (Version [1, 2, 3] [])
"1.2.3"
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData All 
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData Any 
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData String 
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData UTCTime
>>> toUrlPiece $ UTCTime (fromGregorian 2015 10 03) 864.5
"2015-10-03T00:14:24.5Z"
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData SetCookie

Note: this instance works correctly for alphanumeric name and value

>>> let Right c = parseUrlPiece "SESSID=r2t5uvjq435r4q7ib3vtdjq120" :: Either Text SetCookie
>>> toUrlPiece c
"SESSID=r2t5uvjq435r4q7ib3vtdjq120"
>>> toHeader c
"SESSID=r2t5uvjq435r4q7ib3vtdjq120"
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData Text 
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData UUID 
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData ZonedTime
>>> toUrlPiece $ ZonedTime (LocalTime (fromGregorian 2015 10 03) (TimeOfDay 14 55 51.001)) utc
"2015-10-03T14:55:51.001+0000"
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData LocalTime
>>> toUrlPiece $ LocalTime (fromGregorian 2015 10 03) (TimeOfDay 14 55 21.687)
"2015-10-03T14:55:21.687"
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData TimeOfDay
>>> toUrlPiece $ TimeOfDay 14 55 23.1
"14:55:23.1"
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData NominalDiffTime 
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData Day
>>> toUrlPiece (fromGregorian 2015 10 03)
"2015-10-03"
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData DayOfWeek
>>> toUrlPiece Monday
"monday"
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData Text 
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData a => ToHttpApiData (Maybe a)
>>> toUrlPiece (Just "Hello")
"just Hello"
Instance details

Defined in Web.Internal.HttpApiData

HasResolution a => ToHttpApiData (Fixed a) 
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData a => ToHttpApiData (Min a) 
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData a => ToHttpApiData (Max a) 
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData a => ToHttpApiData (First a) 
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData a => ToHttpApiData (Last a) 
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData a => ToHttpApiData (First a) 
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData a => ToHttpApiData (Last a) 
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData a => ToHttpApiData (Dual a) 
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData a => ToHttpApiData (Sum a) 
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData a => ToHttpApiData (Product a) 
Instance details

Defined in Web.Internal.HttpApiData

(ToHttpApiData a, ToHttpApiData b) => ToHttpApiData (Either a b)
>>> toUrlPiece (Left "err" :: Either String Int)
"left err"
>>> toUrlPiece (Right 3 :: Either String Int)
"right 3"
Instance details

Defined in Web.Internal.HttpApiData

ToHttpApiData a => ToHttpApiData (Tagged b a) 
Instance details

Defined in Web.Internal.HttpApiData

type Header = (HeaderName, ByteString) #

Header

data Status #

HTTP Status.

Only the statusCode is used for comparisons.

Please use mkStatus to create status codes from code and message, or the Enum instance or the status code constants (like ok200). There might be additional record members in the future.

Note that the Show instance is only for debugging.

Constructors

Status 
Instances
Bounded Status 
Instance details

Defined in Network.HTTP.Types.Status

Enum Status 
Instance details

Defined in Network.HTTP.Types.Status

Eq Status 
Instance details

Defined in Network.HTTP.Types.Status

Methods

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

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

Ord Status 
Instance details

Defined in Network.HTTP.Types.Status

Show Status 
Instance details

Defined in Network.HTTP.Types.Status

type HeaderName = CI ByteString #

Header name