pinch-0.3.2.0: An alternative implementation of Thrift for Haskell.

Copyright(c) Abhinav Gupta 2015
LicenseBSD3
MaintainerAbhinav Gupta <mail@abhinavg.net>
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Pinch.Internal.Pinchable

Description

Provides the core Pinchable typeclass and the GPinchable typeclass used to derive instances automatically.

Synopsis

Documentation

class IsTType (Tag a) => Pinchable a where Source #

The Pinchable type class is implemented by types that can be sent or received over the wire as Thrift payloads.

Associated Types

type Tag a Source #

TType tag for this type.

For most custom types, this will be TStruct, TUnion, or TException. For enums, it will be TEnum. If the instance automatically derived with use of Generic, this is not required because it is automatically determined by use of Field or Enumeration.

Methods

pinch :: a -> Value (Tag a) Source #

Convert an a into a Value.

For structs, struct, .=, and ?= may be used to construct Value objects tagged with TStruct.

unpinch :: Value (Tag a) -> Parser a Source #

Read a Value back into an a.

For structs, .: and .:? may be used to retrieve field values.

pinch :: (Generic a, Tag a ~ GTag (Rep a), GPinchable (Rep a)) => a -> Value (Tag a) Source #

Convert an a into a Value.

For structs, struct, .=, and ?= may be used to construct Value objects tagged with TStruct.

unpinch :: (Generic a, Tag a ~ GTag (Rep a), GPinchable (Rep a)) => Value (Tag a) -> Parser a Source #

Read a Value back into an a.

For structs, .: and .:? may be used to retrieve field values.

Instances

Pinchable Bool Source # 

Associated Types

type Tag Bool :: * Source #

Pinchable Double Source # 

Associated Types

type Tag Double :: * Source #

Pinchable Int8 Source # 

Associated Types

type Tag Int8 :: * Source #

Pinchable Int16 Source # 

Associated Types

type Tag Int16 :: * Source #

Pinchable Int32 Source # 

Associated Types

type Tag Int32 :: * Source #

Pinchable Int64 Source # 

Associated Types

type Tag Int64 :: * Source #

Pinchable ByteString Source # 
Pinchable ByteString Source # 
Pinchable Text Source # 

Associated Types

type Tag Text :: * Source #

Pinchable Text Source # 

Associated Types

type Tag Text :: * Source #

Pinchable a => Pinchable [a] Source # 

Associated Types

type Tag [a] :: * Source #

Methods

pinch :: [a] -> Value (Tag [a]) Source #

unpinch :: Value (Tag [a]) -> Parser [a] Source #

(Ord a, Pinchable a) => Pinchable (Set a) Source # 

Associated Types

type Tag (Set a) :: * Source #

Methods

pinch :: Set a -> Value (Tag (Set a)) Source #

unpinch :: Value (Tag (Set a)) -> Parser (Set a) Source #

(Eq a, Hashable a, Pinchable a) => Pinchable (HashSet a) Source # 

Associated Types

type Tag (HashSet a) :: * Source #

Pinchable a => Pinchable (Vector a) Source # 

Associated Types

type Tag (Vector a) :: * Source #

Methods

pinch :: Vector a -> Value (Tag (Vector a)) Source #

unpinch :: Value (Tag (Vector a)) -> Parser (Vector a) Source #

IsTType a => Pinchable (Value a) Source # 

Associated Types

type Tag (Value a) :: * Source #

Methods

pinch :: Value a -> Value (Tag (Value a)) Source #

unpinch :: Value (Tag (Value a)) -> Parser (Value a) Source #

(Ord k, Pinchable k, Pinchable v) => Pinchable (Map k v) Source # 

Associated Types

type Tag (Map k v) :: * Source #

Methods

pinch :: Map k v -> Value (Tag (Map k v)) Source #

unpinch :: Value (Tag (Map k v)) -> Parser (Map k v) Source #

(Eq k, Hashable k, Pinchable k, Pinchable v) => Pinchable (HashMap k v) Source # 

Associated Types

type Tag (HashMap k v) :: * Source #

Methods

pinch :: HashMap k v -> Value (Tag (HashMap k v)) Source #

unpinch :: Value (Tag (HashMap k v)) -> Parser (HashMap k v) Source #

(.=) :: Pinchable a => Int16 -> a -> FieldPair Source #

Construct a FieldPair from a field identifier and a Pinchable value.

(?=) :: Pinchable a => Int16 -> Maybe a -> FieldPair Source #

Construct a FieldPair from a field identifier and an optional Pinchable value.

struct :: [FieldPair] -> Value TStruct Source #

Construct a Value tagged with a TStruct from the given key-value pairs. Optional fields whose values were omitted will be ignored.

struct [1 .= ("Hello" :: Text), 2 .= (42 :: Int16)]

union :: Pinchable a => Int16 -> a -> Value TUnion Source #

Constructs a Value tagged with TUnion.

union 1 ("foo" :: ByteString)

type FieldPair = (Int16, Maybe SomeValue) Source #

A pair of field identifier and maybe a value stored in the field. If the value is absent, the field will be ignored.

(.:) :: forall a. Pinchable a => Value TStruct -> Int16 -> Parser a Source #

Given a field ID and a Value TStruct, get the value stored in the struct under that field ID. The lookup fails if the field is absent or if it's not the same type as expected by this call's context.

(.:?) :: forall a. Pinchable a => Value TStruct -> Int16 -> Parser (Maybe a) Source #

Given a field ID and a Value TStruct, get the optional value stored in the struct under the given field ID. The value returned is Nothing if it was absent or the wrong type. The lookup fails only if the value retrieved fails to unpinch.

class IsTType (GTag f) => GPinchable f where Source #

GPinchable is used to impelment support for automatically deriving instances of Pinchable via generics.

Minimal complete definition

gPinch, gUnpinch

Associated Types

type GTag f Source #

TType tag to use for objects of this type.

Methods

gPinch :: f a -> Value (GTag f) Source #

Converts a generic representation of a value into a Value.

gUnpinch :: Value (GTag f) -> Parser (f a) Source #

Converts a Value back into the generic representation of the object.

Instances

GPinchable (K1 i Void) Source # 

Associated Types

type GTag (K1 i Void :: * -> *) :: * Source #

Methods

gPinch :: K1 i Void a -> Value (GTag (K1 i Void)) Source #

gUnpinch :: Value (GTag (K1 i Void)) -> Parser (K1 i Void a) Source #

KnownNat n => GPinchable (K1 i (Enumeration n)) Source # 

Associated Types

type GTag (K1 i (Enumeration n) :: * -> *) :: * Source #

Methods

gPinch :: K1 i (Enumeration n) a -> Value (GTag (K1 i (Enumeration n))) Source #

gUnpinch :: Value (GTag (K1 i (Enumeration n))) -> Parser (K1 i (Enumeration n) a) Source #

(Pinchable a, KnownNat n) => GPinchable (K1 i (Field n (Maybe a))) Source # 

Associated Types

type GTag (K1 i (Field n (Maybe a)) :: * -> *) :: * Source #

Methods

gPinch :: K1 i (Field n (Maybe a)) a -> Value (GTag (K1 i (Field n (Maybe a)))) Source #

gUnpinch :: Value (GTag (K1 i (Field n (Maybe a)))) -> Parser (K1 i (Field n (Maybe a)) a) Source #

(Pinchable a, KnownNat n) => GPinchable (K1 i (Field n a)) Source # 

Associated Types

type GTag (K1 i (Field n a) :: * -> *) :: * Source #

Methods

gPinch :: K1 i (Field n a) a -> Value (GTag (K1 i (Field n a))) Source #

gUnpinch :: Value (GTag (K1 i (Field n a))) -> Parser (K1 i (Field n a) a) Source #

genericPinch :: (Generic a, GPinchable (Rep a)) => a -> Value (GTag (Rep a)) Source #

Implementation of pinch based on GPinchable.

genericUnpinch :: (Generic a, GPinchable (Rep a)) => Value (GTag (Rep a)) -> Parser a Source #

Implementation of unpinch based on GPinchable.

data Parser a Source #

A simple continuation-based parser.

This is just Either e a in continuation-passing style.

Instances

Monad Parser Source # 

Methods

(>>=) :: Parser a -> (a -> Parser b) -> Parser b #

(>>) :: Parser a -> Parser b -> Parser b #

return :: a -> Parser a #

fail :: String -> Parser a #

Functor Parser Source # 

Methods

fmap :: (a -> b) -> Parser a -> Parser b #

(<$) :: a -> Parser b -> Parser a #

Applicative Parser Source # 

Methods

pure :: a -> Parser a #

(<*>) :: Parser (a -> b) -> Parser a -> Parser b #

(*>) :: Parser a -> Parser b -> Parser b #

(<*) :: Parser a -> Parser b -> Parser a #

Alternative Parser Source # 

Methods

empty :: Parser a #

(<|>) :: Parser a -> Parser a -> Parser a #

some :: Parser a -> Parser [a] #

many :: Parser a -> Parser [a] #

MonadPlus Parser Source # 

Methods

mzero :: Parser a #

mplus :: Parser a -> Parser a -> Parser a #

runParser :: Parser a -> Either String a Source #

Run a Parser and return the result inside an Either.

parserCatch :: Parser a -> (String -> Parser b) -> (a -> Parser b) -> Parser b Source #

Allows handling parse errors.