querystring-pickle-0.1.2: Picklers for de/serialising Generic data types to and from query strings

Safe HaskellNone

Network.HTTP.QueryString.Pickle

Contents

Synopsis

Class

class IsQuery a whereSource

A type that has a pairing of pickler + unpickler.

Using the DeriveGeneric language extension, this class specifies a default generic implementation using genericQueryPickler.

For example:

{-# LANGUAGE DeriveGeneric #-}

import GHC.Generics

data Foo { fooIntX :: Int, fooIntY :: Int } deriving (Generic)

instance IsQuery Foo

Note that you can parameterise some of the options to genericQueryPickler by specifying an implementation instead of using DefaultSignatures.

The previous example:

 instance IsQuery Foo where
     queryPickler = genericQueryPickler defaultOptions

More examples of creating queryPickler implementations can be found in the README or in the tests.

Functions

toQuery :: IsQuery a => a -> [(ByteString, ByteString)]Source

Pickle a data type with an IsQuery instance to an association list.

fromQuery :: IsQuery a => [(ByteString, ByteString)] -> Either String aSource

Unpickle an association list to an IsQuery type, returning an error message when unpickling fails.

encodeQuerySource

Arguments

:: (ByteString -> ByteString)

URL Value Encoder

-> [(ByteString, ByteString)]

Key/Value Pairs

-> ByteString 

Helper to encode an association list as a single canonical query string.

decodeQuerySource

Arguments

:: (ByteString -> ByteString)

URL Value Decoder

-> ByteString

Input Query String

-> [(ByteString, ByteString)] 

Helper to decode a query string to an association list.

Data Types

data Query Source

Internal tree representation for queries.

data PU a Source

Pairing of pickler to unpickler.

Constructors

PU 

Fields

pickle :: a -> Query
 
unpickle :: Query -> Either String a
 

Options

data Options Source

Options for genericQueryPickler to parameterise how constructor and record field labels are un/pickled.

For example:

import GHC.Generics

data Bar { barThisIsAByteString :: ByteString } deriving (Generic)

instance IsQuery Foo where
     queryPickler = genericQueryPickler $ Options
         { constructorTagModifier = id
         , fieldLabelModifier     = dropWhile isLower
         }

Would remove bar from the record field barThisIsAByteString so the resulting pair for that field in the association list would be (ThisIsAByteString, n :: Int).

The above example is how defaultOptions behaves.

Constructors

Options 

Fields

constructorTagModifier :: String -> String

Function applied to constructor tags.

fieldLabelModifier :: String -> String

Function applied to record field labels.

defaultOptions :: OptionsSource

Strips lowercase prefixes from record fields.

loweredOptions :: OptionsSource

Strips lowercase prefixes from record fields and subsequently lowercases the remaining identifier.

Generics

genericQueryPickler :: (Generic x, GIsQuery (Rep x)) => Options -> PU xSource

Combinators

qpWrap :: (a -> b, b -> a) -> PU a -> PU bSource

qpPair :: PU a -> PU b -> PU (a, b)Source

qpLift :: a -> PU aSource

qpPrim :: (Read a, Show a) => PU aSource

qpDefault :: a -> PU a -> PU aSource

qpSum :: PU (f r) -> PU (g r) -> PU ((f :+: g) r)Source

qpEither :: PU a -> PU b -> PU (Either a b)Source

qpList :: PU a -> PU [a]Source