| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Network.HTTP.Kinder.Query
Contents
Description
A request can be thought of as having a query component which is
 a mapping from a set of query keys (which are just strings) to values of
 .QueryKeyState Text
This module provides tools for extracting information from this mapping or constructing them.
- class QueryEncode s a where
- queryEncode :: sing s -> a -> QueryKeyState Text
 
 - class QueryDecode s a where
- queryDecode :: sing s -> QueryKeyState Text -> Either String a
 
 - type family AllQueryEncodes hs :: Constraint
 - type family AllQueryDecodes hs :: Constraint
 - data QueryKeyState a
 - data Flag
 - queryEncodePair :: (KnownSymbol n, QueryEncode n a) => Sing n -> a -> Maybe (Text, Maybe Text)
 
Classes for encoding and decoding
class QueryEncode s a where Source
Determines a representation of a query value for a given query key.
Methods
queryEncode :: sing s -> a -> QueryKeyState Text Source
Instances
| QueryEncode s Flag Source | |
| QueryEncode s a => QueryEncode s (Maybe a) Source | |
| QueryEncode s (Raw Text) Source | |
| QueryEncode s a => QueryEncode s (QueryKeyState a) Source | 
class QueryDecode s a where Source
Attempts to parse a representation of a query value at a given query key.
Methods
queryDecode :: sing s -> QueryKeyState Text -> Either String a Source
Instances
| QueryDecode s Flag Source | This instance act "strictly" in that if the key is present but given
 a value then it will fail to parse for this type. To be lenient use
   | 
| QueryDecode s a => QueryDecode s (Maybe a) Source | |
| QueryDecode s (Raw Text) Source | |
| QueryDecode s a => QueryDecode s (QueryKeyState a) Source | 
Listing constraints to type-level lists
type family AllQueryEncodes hs :: Constraint Source
For a given concrete type a, a list of pairs ts satisfies
  if each AllQueryEncode a ts(n, a) in ts has .QueryEncode
 n a
Equations
| AllQueryEncodes `[]` = () | |
| AllQueryEncodes (`(s, a)` : hs) = (QueryEncode s a, AllQueryEncodes hs) | 
type family AllQueryDecodes hs :: Constraint Source
For a given concrete type a, a list of pairs ts satisfies
  if each AllQueryDecode a ts(n, a) in ts has .QueryDecode
 n a
Equations
| AllQueryDecodes `[]` = () | |
| AllQueryDecodes (`(s, a)` : hs) = (QueryDecode s a, AllQueryDecodes hs) | 
Types for encoding/decoding request queries
data QueryKeyState a Source
QueryKeyState describes the state of a given key within a query-map.
 The key may be complete absent, it may exist without a value, or it may
 exist with some value at a given type.
Constructors
| QueryKeyPresent | |
| QueryKeyValued a | |
| QueryKeyAbsent | 
Instances
| Monad QueryKeyState Source | Monad instance equivalent to   | 
| Functor QueryKeyState Source | |
| Applicative QueryKeyState Source | |
| QueryDecode s a => QueryDecode s (QueryKeyState a) Source | |
| QueryEncode s a => QueryEncode s (QueryKeyState a) Source | |
| Eq a => Eq (QueryKeyState a) Source | |
| Ord a => Ord (QueryKeyState a) Source | |
| Read a => Read (QueryKeyState a) Source | |
| Show a => Show (QueryKeyState a) Source | 
Flag provides semantics for query parameters which may merely exist
 without actually storing a value---"flag" semantics.
Instances
| QueryDecode s Flag Source | This instance act "strictly" in that if the key is present but given
 a value then it will fail to parse for this type. To be lenient use
   | 
| QueryEncode s Flag Source | 
Extra serialization utilities
queryEncodePair :: (KnownSymbol n, QueryEncode n a) => Sing n -> a -> Maybe (Text, Maybe Text) Source
Produces a pair of (name, representation) from a given query encoding.