http-api-data-0.2.2: Converting to/from HTTP API data like URL pieces, headers and query parameters.

Safe HaskellSafe
LanguageHaskell98

Web.HttpApiData

Contents

Description

Convert Haskell values to and from HTTP API data such as URL pieces, headers and query parameters.

Synopsis

Examples

Booleans:

>>> toUrlPiece True
"true"
>>> parseUrlPiece "false" :: Either Text Bool
Right False
>>> parseUrlPieces ["true", "false", "undefined"] :: Either Text [Bool]
Left "could not parse: `undefined'"

Numbers:

>>> toQueryParam 45.2
"45.2"
>>> parseQueryParam "452" :: Either Text Int
Right 452
>>> toQueryParams [1..5]
["1","2","3","4","5"]
>>> parseQueryParams ["127", "255"] :: Either Text [Int8]
Left "out of bounds: `255' (should be between -128 and 127)"

Strings:

>>> toHeader "hello"
"hello"
>>> parseHeader "world" :: Either Text String
Right "world"

Calendar day:

>>> toQueryParam (fromGregorian 2015 10 03)
"2015-10-03"
>>> toGregorian <$> parseQueryParam "2016-12-01"
Right (2016,12,1)

Classes

class ToHttpApiData a where Source

Convert value to HTTP API data.

Minimal complete definition

toUrlPiece | toQueryParam

Methods

toUrlPiece :: a -> Text Source

Convert to URL path piece.

toHeader :: a -> ByteString Source

Convert to HTTP header value.

toQueryParam :: a -> Text Source

Convert to query param value.

Instances

ToHttpApiData Bool Source 
ToHttpApiData Char Source 
ToHttpApiData Double Source 
ToHttpApiData Float Source 
ToHttpApiData Int Source 
ToHttpApiData Int8 Source 
ToHttpApiData Int16 Source 
ToHttpApiData Int32 Source 
ToHttpApiData Int64 Source 
ToHttpApiData Integer Source 
ToHttpApiData Ordering Source 
ToHttpApiData Word Source 
ToHttpApiData Word8 Source 
ToHttpApiData Word16 Source 
ToHttpApiData Word32 Source 
ToHttpApiData Word64 Source 
ToHttpApiData String Source 
ToHttpApiData () Source
>>> toUrlPiece ()
"_"
ToHttpApiData Void Source 
ToHttpApiData Version Source
>>> toUrlPiece (Version [1, 2, 3] [])
"1.2.3"
ToHttpApiData All Source 
ToHttpApiData Any Source 
ToHttpApiData Text Source 
ToHttpApiData Text Source 
ToHttpApiData LocalTime Source
>>> toUrlPiece $ LocalTime (fromGregorian 2015 10 03) (TimeOfDay 14 55 01)
"2015-10-03T14:55:01"
ToHttpApiData ZonedTime Source
>>> toUrlPiece $ ZonedTime (LocalTime (fromGregorian 2015 10 03) (TimeOfDay 14 55 01)) utc
"2015-10-03T14:55:01+0000"
ToHttpApiData UTCTime Source
>>> toUrlPiece $ UTCTime (fromGregorian 2015 10 03) 864
"2015-10-03T00:14:24Z"
ToHttpApiData NominalDiffTime Source 
ToHttpApiData Day Source
>>> toUrlPiece (fromGregorian 2015 10 03)
"2015-10-03"
ToHttpApiData a => ToHttpApiData (Dual a) Source 
ToHttpApiData a => ToHttpApiData (Sum a) Source 
ToHttpApiData a => ToHttpApiData (Product a) Source 
ToHttpApiData a => ToHttpApiData (First a) Source 
ToHttpApiData a => ToHttpApiData (Last a) Source 
ToHttpApiData a => ToHttpApiData (Maybe a) Source
>>> toUrlPiece (Just "Hello")
"just Hello"
(ToHttpApiData a, ToHttpApiData b) => ToHttpApiData (Either a b) Source
>>> toUrlPiece (Left "err" :: Either String Int)
"left err"
>>> toUrlPiece (Right 3 :: Either String Int)
"right 3"

class FromHttpApiData a where Source

Parse value from HTTP API data.

Minimal complete definition

parseUrlPiece | parseQueryParam

Methods

parseUrlPiece :: Text -> Either Text a Source

Parse URL path piece.

parseHeader :: ByteString -> Either Text a Source

Parse HTTP header value.

parseQueryParam :: Text -> Either Text a Source

Parse query param value.

Instances

FromHttpApiData Bool Source 
FromHttpApiData Char Source 
FromHttpApiData Double Source 
FromHttpApiData Float Source 
FromHttpApiData Int Source 
FromHttpApiData Int8 Source 
FromHttpApiData Int16 Source 
FromHttpApiData Int32 Source 
FromHttpApiData Int64 Source 
FromHttpApiData Integer Source 
FromHttpApiData Ordering Source 
FromHttpApiData Word Source 
FromHttpApiData Word8 Source 
FromHttpApiData Word16 Source 
FromHttpApiData Word32 Source 
FromHttpApiData Word64 Source 
FromHttpApiData String Source 
FromHttpApiData () Source
>>> parseUrlPiece "_" :: Either Text ()
Right ()
FromHttpApiData Void Source

Parsing a Void value is always an error, considering Void as a data type with no constructors.

FromHttpApiData Version Source
>>> showVersion <$> parseUrlPiece "1.2.3"
Right "1.2.3"
FromHttpApiData All Source 
FromHttpApiData Any Source 
FromHttpApiData Text Source 
FromHttpApiData Text Source 
FromHttpApiData LocalTime Source
>>> parseUrlPiece "2015-10-03T14:55:01" :: Either Text LocalTime
Right 2015-10-03 14:55:01
FromHttpApiData ZonedTime Source
>>> parseUrlPiece "2015-10-03T14:55:01+0000" :: Either Text ZonedTime
Right 2015-10-03 14:55:01 +0000
FromHttpApiData UTCTime Source
>>> parseUrlPiece "2015-10-03T00:14:24Z" :: Either Text UTCTime
Right 2015-10-03 00:14:24 UTC
FromHttpApiData NominalDiffTime Source 
FromHttpApiData Day Source
>>> toGregorian <$> parseUrlPiece "2016-12-01"
Right (2016,12,1)
FromHttpApiData a => FromHttpApiData (Dual a) Source 
FromHttpApiData a => FromHttpApiData (Sum a) Source 
FromHttpApiData a => FromHttpApiData (Product a) Source 
FromHttpApiData a => FromHttpApiData (First a) Source 
FromHttpApiData a => FromHttpApiData (Last a) Source 
FromHttpApiData a => FromHttpApiData (Maybe a) Source
>>> parseUrlPiece "Just 123" :: Either Text (Maybe Int)
Right (Just 123)
(FromHttpApiData a, FromHttpApiData b) => FromHttpApiData (Either a b) Source
>>> parseUrlPiece "Right 123" :: Either Text (Either String Int)
Right (Right 123)

Maybe parsers

parseUrlPieceMaybe :: FromHttpApiData a => Text -> Maybe a Source

Parse URL path piece in a Maybe.

>>> parseUrlPieceMaybe "12" :: Maybe Int
Just 12

parseHeaderMaybe :: FromHttpApiData a => ByteString -> Maybe a Source

Parse HTTP header value in a Maybe.

>>> parseHeaderMaybe "hello" :: Maybe Text
Just "hello"

parseQueryParamMaybe :: FromHttpApiData a => Text -> Maybe a Source

Parse query param value in a Maybe.

>>> parseQueryParamMaybe "true" :: Maybe Bool
Just True

Prefix parsers

parseUrlPieceWithPrefix :: FromHttpApiData a => Text -> Text -> Either Text a Source

Case insensitive.

Parse given text case insensitive and then parse the rest of the input using parseUrlPiece.

>>> parseUrlPieceWithPrefix "Just " "just 10" :: Either Text Int
Right 10
>>> parseUrlPieceWithPrefix "Left " "left" :: Either Text Bool
Left "could not parse: `left'"

This can be used to implement FromHttpApiData for single field constructors:

>>> data Foo = Foo Int deriving (Show)
>>> instance FromHttpApiData Foo where parseUrlPiece s = Foo <$> parseUrlPieceWithPrefix "Foo " s
>>> parseUrlPiece "foo 1" :: Either Text Foo
Right (Foo 1)

parseHeaderWithPrefix :: FromHttpApiData a => ByteString -> ByteString -> Either Text a Source

Parse given bytestring then parse the rest of the input using parseHeader.

data BasicAuthToken = BasicAuthToken Text deriving (Show)

instance FromHttpApiData BasicAuthToken where
  parseHeader h     = BasicAuthToken <$> parseHeaderWithPrefix "Basic " h
  parseQueryParam p = BasicAuthToken <$> parseQueryParam p
>>> parseHeader "Basic QWxhZGRpbjpvcGVuIHNlc2FtZQ==" :: Either Text BasicAuthToken
Right (BasicAuthToken "QWxhZGRpbjpvcGVuIHNlc2FtZQ==")

parseQueryParamWithPrefix :: FromHttpApiData a => Text -> Text -> Either Text a Source

Case insensitive.

Parse given text case insensitive and then parse the rest of the input using parseQueryParam.

>>> parseQueryParamWithPrefix "z" "z10" :: Either Text Int
Right 10

Multiple URL pieces

toUrlPieces :: (Functor t, ToHttpApiData a) => t a -> t Text Source

Convert multiple values to a list of URL pieces.

>>> toUrlPieces [1, 2, 3]
["1","2","3"]

parseUrlPieces :: (Traversable t, FromHttpApiData a) => t Text -> Either Text (t a) Source

Parse multiple URL pieces.

>>> parseUrlPieces ["true", "false"] :: Either Text [Bool]
Right [True,False]
>>> parseUrlPieces ["123", "hello", "world"] :: Either Text [Int]
Left "could not parse: `hello' (input does not start with a digit)"

Multiple query params

toQueryParams :: (Functor t, ToHttpApiData a) => t a -> t Text Source

Convert multiple values to a list of query parameter values.

>>> toQueryParams [fromGregorian 2015 10 03, fromGregorian 2015 12 01]
["2015-10-03","2015-12-01"]

parseQueryParams :: (Traversable t, FromHttpApiData a) => t Text -> Either Text (t a) Source

Parse multiple query parameters.

>>> parseQueryParams ["1", "2", "3"] :: Either Text [Int]
Right [1,2,3]
>>> parseQueryParams ["64", "128", "256"] :: Either Text [Word8]
Left "out of bounds: `256' (should be between 0 and 255)"

Other helpers

showTextData :: Show a => a -> Text Source

Lower case.

Convert to URL piece using Show instance. The result is always lower cased.

>>> showTextData True
"true"

This can be used as a default implementation for enumeration types:

>>> data MyData = Foo | Bar | Baz deriving (Show)
>>> instance ToHttpApiData MyData where toUrlPiece = showTextData
>>> toUrlPiece Foo
"foo"

readTextData :: Read a => Text -> Either Text a Source

Parse URL piece using Read instance.

Use for types which do not involve letters:

>>> readTextData "1991-06-02" :: Either Text Day
Right 1991-06-02

This parser is case sensitive and will not match showTextData in presense of letters:

>>> readTextData (showTextData True) :: Either Text Bool
Left "could not parse: `true'"

See parseBoundedTextData.

parseBoundedTextData :: (Show a, Bounded a, Enum a) => Text -> Either Text a Source

Case insensitive.

Parse values case insensitively based on Show instance.

>>> parseBoundedTextData "true" :: Either Text Bool
Right True
>>> parseBoundedTextData "FALSE" :: Either Text Bool
Right False

This can be used as a default implementation for enumeration types:

>>> data MyData = Foo | Bar | Baz deriving (Show, Bounded, Enum)
>>> instance FromHttpApiData MyData where parseUrlPiece = parseBoundedTextData
>>> parseUrlPiece "foo" :: Either Text MyData
Right Foo