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

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

Pinch.Internal.Generic

Contents

Description

Implements support for automatically deriving Pinchable instances for types that implement Generic and follow a specific pattern.

Synopsis

Documentation

newtype Field (n :: Nat) a Source #

Fields of data types that represent structs, unions, and exceptions should be wrapped inside Field and tagged with the field identifier.

data Foo = Foo (Field 1 Text) (Field 2 (Maybe Int32)) deriving Generic
instance Pinchable Foo
data A = A (Field 1 Int32) | B (Field 2 Text) deriving Generic
instance Pinchable Foo

Fields which hold Maybe values are treated as optional. All fields values must be Pinchable to automatically derive a Pinchable instance for the new data type.

Constructors

Field a 
Instances
Functor (Field n) Source # 
Instance details

Defined in Pinch.Internal.Generic

Methods

fmap :: (a -> b) -> Field n a -> Field n b #

(<$) :: a -> Field n b -> Field n a #

Foldable (Field n) Source # 
Instance details

Defined in Pinch.Internal.Generic

Methods

fold :: Monoid m => Field n m -> m #

foldMap :: Monoid m => (a -> m) -> Field n a -> m #

foldr :: (a -> b -> b) -> b -> Field n a -> b #

foldr' :: (a -> b -> b) -> b -> Field n a -> b #

foldl :: (b -> a -> b) -> b -> Field n a -> b #

foldl' :: (b -> a -> b) -> b -> Field n a -> b #

foldr1 :: (a -> a -> a) -> Field n a -> a #

foldl1 :: (a -> a -> a) -> Field n a -> a #

toList :: Field n a -> [a] #

null :: Field n a -> Bool #

length :: Field n a -> Int #

elem :: Eq a => a -> Field n a -> Bool #

maximum :: Ord a => Field n a -> a #

minimum :: Ord a => Field n a -> a #

sum :: Num a => Field n a -> a #

product :: Num a => Field n a -> a #

Traversable (Field n) Source # 
Instance details

Defined in Pinch.Internal.Generic

Methods

traverse :: Applicative f => (a -> f b) -> Field n a -> f (Field n b) #

sequenceA :: Applicative f => Field n (f a) -> f (Field n a) #

mapM :: Monad m => (a -> m b) -> Field n a -> m (Field n b) #

sequence :: Monad m => Field n (m a) -> m (Field n a) #

Bounded a => Bounded (Field n a) Source # 
Instance details

Defined in Pinch.Internal.Generic

Methods

minBound :: Field n a #

maxBound :: Field n a #

Enum a => Enum (Field n a) Source # 
Instance details

Defined in Pinch.Internal.Generic

Methods

succ :: Field n a -> Field n a #

pred :: Field n a -> Field n a #

toEnum :: Int -> Field n a #

fromEnum :: Field n a -> Int #

enumFrom :: Field n a -> [Field n a] #

enumFromThen :: Field n a -> Field n a -> [Field n a] #

enumFromTo :: Field n a -> Field n a -> [Field n a] #

enumFromThenTo :: Field n a -> Field n a -> Field n a -> [Field n a] #

Eq a => Eq (Field n a) Source # 
Instance details

Defined in Pinch.Internal.Generic

Methods

(==) :: Field n a -> Field n a -> Bool #

(/=) :: Field n a -> Field n a -> Bool #

Ord a => Ord (Field n a) Source # 
Instance details

Defined in Pinch.Internal.Generic

Methods

compare :: Field n a -> Field n a -> Ordering #

(<) :: Field n a -> Field n a -> Bool #

(<=) :: Field n a -> Field n a -> Bool #

(>) :: Field n a -> Field n a -> Bool #

(>=) :: Field n a -> Field n a -> Bool #

max :: Field n a -> Field n a -> Field n a #

min :: Field n a -> Field n a -> Field n a #

Show a => Show (Field n a) Source # 
Instance details

Defined in Pinch.Internal.Generic

Methods

showsPrec :: Int -> Field n a -> ShowS #

show :: Field n a -> String #

showList :: [Field n a] -> ShowS #

Generic (Field n a) Source # 
Instance details

Defined in Pinch.Internal.Generic

Associated Types

type Rep (Field n a) :: Type -> Type #

Methods

from :: Field n a -> Rep (Field n a) x #

to :: Rep (Field n a) x -> Field n a #

Semigroup a => Semigroup (Field n a) Source # 
Instance details

Defined in Pinch.Internal.Generic

Methods

(<>) :: Field n a -> Field n a -> Field n a #

sconcat :: NonEmpty (Field n a) -> Field n a #

stimes :: Integral b => b -> Field n a -> Field n a #

Monoid a => Monoid (Field n a) Source # 
Instance details

Defined in Pinch.Internal.Generic

Methods

mempty :: Field n a #

mappend :: Field n a -> Field n a -> Field n a #

mconcat :: [Field n a] -> Field n a #

NFData a => NFData (Field n a) Source # 
Instance details

Defined in Pinch.Internal.Generic

Methods

rnf :: Field n a -> () #

(Pinchable a, KnownNat n) => GPinchable (K1 i (Field n (Maybe a)) :: Type -> Type) Source # 
Instance details

Defined in Pinch.Internal.Generic

Associated Types

type GTag (K1 i (Field n (Maybe a))) :: Type Source #

Methods

gPinch :: K1 i (Field n (Maybe a)) a0 -> 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)) a0) Source #

(Pinchable a, KnownNat n) => GPinchable (K1 i (Field n a) :: Type -> Type) Source # 
Instance details

Defined in Pinch.Internal.Generic

Associated Types

type GTag (K1 i (Field n a)) :: Type Source #

Methods

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

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

type Rep (Field n a) Source # 
Instance details

Defined in Pinch.Internal.Generic

type Rep (Field n a) = D1 (MetaData "Field" "Pinch.Internal.Generic" "pinch-0.3.4.1-6i8lWHA1d5m12B6E7SIAjq" True) (C1 (MetaCons "Field" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type GTag (K1 i (Field n (Maybe a)) :: Type -> Type) Source # 
Instance details

Defined in Pinch.Internal.Generic

type GTag (K1 i (Field n (Maybe a)) :: Type -> Type) = TStruct
type GTag (K1 i (Field n a) :: Type -> Type) Source # 
Instance details

Defined in Pinch.Internal.Generic

type GTag (K1 i (Field n a) :: Type -> Type) = TStruct

getField :: Field n a -> a Source #

Gets the current value of a field.

let Foo a' _ = {- ... -}
    a = getField a'

putField :: a -> Field n a Source #

Puts a value inside a field.

Foo (putField "Hello") (putField (Just 42))

field :: Functor f => (a -> f b) -> Field n a -> f (Field n b) Source #

A lens on Field wrappers for use with the lens library.

person & name . field .~ "new value"

data Enumeration (n :: Nat) Source #

Data types that represent Thrift enums must have one constructor for each enum item accepting an Enumeration object tagged with the corresponding enum value.

data Role = RoleUser (Enumeration 1) | RoleAdmin (Enumeration 2)
  deriving Generic
instance Pinchable Role

Constructors

Enumeration 
Instances
Eq (Enumeration n) Source # 
Instance details

Defined in Pinch.Internal.Generic

Ord (Enumeration n) Source # 
Instance details

Defined in Pinch.Internal.Generic

Show (Enumeration n) Source # 
Instance details

Defined in Pinch.Internal.Generic

Generic (Enumeration n) Source # 
Instance details

Defined in Pinch.Internal.Generic

Associated Types

type Rep (Enumeration n) :: Type -> Type #

Methods

from :: Enumeration n -> Rep (Enumeration n) x #

to :: Rep (Enumeration n) x -> Enumeration n #

NFData (Enumeration n) Source # 
Instance details

Defined in Pinch.Internal.Generic

Methods

rnf :: Enumeration n -> () #

KnownNat n => GPinchable (K1 i (Enumeration n) :: Type -> Type) Source # 
Instance details

Defined in Pinch.Internal.Generic

Associated Types

type GTag (K1 i (Enumeration n)) :: Type 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 #

type Rep (Enumeration n) Source # 
Instance details

Defined in Pinch.Internal.Generic

type Rep (Enumeration n) = D1 (MetaData "Enumeration" "Pinch.Internal.Generic" "pinch-0.3.4.1-6i8lWHA1d5m12B6E7SIAjq" False) (C1 (MetaCons "Enumeration" PrefixI False) (U1 :: Type -> Type))
type GTag (K1 i (Enumeration n) :: Type -> Type) Source # 
Instance details

Defined in Pinch.Internal.Generic

type GTag (K1 i (Enumeration n) :: Type -> Type) = TEnum

enum :: Enumeration n Source #

Convenience function to construct Enumeration objects.

let role = RoleUser enum

data Void Source #

Represents a void result for methods.

This should be used as an element in a response union along with Field tags.

For a method,

void setValue(..) throws
  (1: ValueAlreadyExists alreadyExists,
   2: InternalError internalError)

Something similar to the following can be used.

data SetValueResponse
  = SetValueAlreadyExists (Field 1 ValueAlreadyExists)
  | SetValueInternalError (Field 2 InternalError)
  | SetValueSuccess Void
  deriving (Generic)

instance Pinchable SetValueResponse

Constructors

Void 
Instances
Eq Void Source # 
Instance details

Defined in Pinch.Internal.Generic

Methods

(==) :: Void -> Void -> Bool #

(/=) :: Void -> Void -> Bool #

Ord Void Source # 
Instance details

Defined in Pinch.Internal.Generic

Methods

compare :: Void -> Void -> Ordering #

(<) :: Void -> Void -> Bool #

(<=) :: Void -> Void -> Bool #

(>) :: Void -> Void -> Bool #

(>=) :: Void -> Void -> Bool #

max :: Void -> Void -> Void #

min :: Void -> Void -> Void #

Show Void Source # 
Instance details

Defined in Pinch.Internal.Generic

Methods

showsPrec :: Int -> Void -> ShowS #

show :: Void -> String #

showList :: [Void] -> ShowS #

Generic Void Source # 
Instance details

Defined in Pinch.Internal.Generic

Associated Types

type Rep Void :: Type -> Type #

Methods

from :: Void -> Rep Void x #

to :: Rep Void x -> Void #

GPinchable (K1 i Void :: Type -> Type) Source # 
Instance details

Defined in Pinch.Internal.Generic

Associated Types

type GTag (K1 i Void) :: Type 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 #

type Rep Void Source # 
Instance details

Defined in Pinch.Internal.Generic

type Rep Void = D1 (MetaData "Void" "Pinch.Internal.Generic" "pinch-0.3.4.1-6i8lWHA1d5m12B6E7SIAjq" False) (C1 (MetaCons "Void" PrefixI False) (U1 :: Type -> Type))
type GTag (K1 i Void :: Type -> Type) Source # 
Instance details

Defined in Pinch.Internal.Generic

type GTag (K1 i Void :: Type -> Type) = TStruct

Orphan instances

(GPinchable a, GPinchable b, GTag a ~ GTag b) => GPinchable (a :+: b) Source # 
Instance details

Associated Types

type GTag (a :+: b) :: Type Source #

Methods

gPinch :: (a :+: b) a0 -> Value (GTag (a :+: b)) Source #

gUnpinch :: Value (GTag (a :+: b)) -> Parser ((a :+: b) a0) Source #

(GPinchable a, GPinchable b, GTag a ~ GTag b, Combinable (GTag a)) => GPinchable (a :*: b) Source # 
Instance details

Associated Types

type GTag (a :*: b) :: Type Source #

Methods

gPinch :: (a :*: b) a0 -> Value (GTag (a :*: b)) Source #

gUnpinch :: Value (GTag (a :*: b)) -> Parser ((a :*: b) a0) Source #

(Datatype d, GPinchable a) => GPinchable (D1 d a) Source # 
Instance details

Associated Types

type GTag (D1 d a) :: Type Source #

Methods

gPinch :: D1 d a a0 -> Value (GTag (D1 d a)) Source #

gUnpinch :: Value (GTag (D1 d a)) -> Parser (D1 d a a0) Source #

GPinchable a => GPinchable (M1 i c a) Source # 
Instance details

Associated Types

type GTag (M1 i c a) :: Type Source #

Methods

gPinch :: M1 i c a a0 -> Value (GTag (M1 i c a)) Source #

gUnpinch :: Value (GTag (M1 i c a)) -> Parser (M1 i c a a0) Source #