| Copyright | (c) Abhinav Gupta 2015 | 
|---|---|
| License | BSD3 | 
| Maintainer | Abhinav Gupta <mail@abhinavg.net> | 
| Stability | experimental | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Pinch.Internal.Pinchable
Description
Provides the core Pinchable typeclass and the GPinchable typeclass used
 to derive instances automatically.
Synopsis
- class IsTType (Tag a) => Pinchable a where
- (.=) :: Pinchable a => Int16 -> a -> FieldPair
- (?=) :: Pinchable a => Int16 -> Maybe a -> FieldPair
- struct :: [FieldPair] -> Value TStruct
- union :: Pinchable a => Int16 -> a -> Value TUnion
- type FieldPair = (Int16, Maybe SomeValue)
- (.:) :: forall a. Pinchable a => Value TStruct -> Int16 -> Parser a
- (.:?) :: forall a. Pinchable a => Value TStruct -> Int16 -> Parser (Maybe a)
- class IsTType (GTag f) => GPinchable (f :: Type -> Type) where
- genericPinch :: (Generic a, GPinchable (Rep a)) => a -> Value (GTag (Rep a))
- genericUnpinch :: (Generic a, GPinchable (Rep a)) => Value (GTag (Rep a)) -> Parser a
- data Parser a
- runParser :: Parser a -> Either String a
- parserCatch :: Parser a -> (String -> Parser b) -> (a -> Parser b) -> Parser b
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.
Minimal complete definition
Nothing
Associated Types
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.
Instances
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 :: Type -> Type) where Source #
GPinchable is used to impelment support for automatically deriving instances of Pinchable via generics.
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 :: Type -> Type) Source # | |
| KnownNat n => GPinchable (K1 i (Enumeration n) :: Type -> Type) Source # | |
| Defined in Pinch.Internal.Generic 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)) :: Type -> Type) Source # | |
| (Pinchable a, KnownNat n) => GPinchable (K1 i (Field n a) :: Type -> Type) Source # | |
| (GPinchable a, GPinchable b, GTag a ~ GTag b) => GPinchable (a :+: b) Source # | |
| (GPinchable a, GPinchable b, GTag a ~ GTag b, Combinable (GTag a)) => GPinchable (a :*: b) Source # | |
| (Datatype d, GPinchable a) => GPinchable (D1 d a) Source # | |
| GPinchable a => GPinchable (M1 i c 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.
A simple continuation-based parser.
This is just Either e a in continuation-passing style.