Copyright | (c) Abhinav Gupta 2015 |
---|---|
License | BSD3 |
Maintainer | Abhinav Gupta <mail@abhinavg.net> |
Stability | experimental |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Implements support for automatically deriving Pinchable instances for types
that implement Generic
and follow a specific pattern.
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.
Field a |
Instances
Foldable (Field n) Source # | |
Defined in Pinch.Internal.Generic fold :: Monoid m => Field n m -> m # foldMap :: Monoid m => (a -> m) -> Field n a -> 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 # elem :: Eq a => a -> Field n a -> Bool # maximum :: Ord a => Field n a -> a # minimum :: Ord a => Field n a -> a # | |
Traversable (Field n) Source # | |
Functor (Field n) Source # | |
Monoid a => Monoid (Field n a) Source # | |
Semigroup a => Semigroup (Field n a) Source # | |
Bounded a => Bounded (Field n a) Source # | |
Enum a => Enum (Field n a) Source # | |
Defined in Pinch.Internal.Generic succ :: Field n a -> Field n a # pred :: Field n a -> 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] # | |
Generic (Field n a) Source # | |
Show a => Show (Field n a) Source # | |
NFData a => NFData (Field n a) Source # | |
Defined in Pinch.Internal.Generic | |
Eq a => Eq (Field n a) Source # | |
Ord a => Ord (Field n a) Source # | |
Defined in Pinch.Internal.Generic | |
(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 # | |
type Rep (Field n a) Source # | |
Defined in Pinch.Internal.Generic | |
type GTag (K1 i (Field n (Maybe a)) :: Type -> Type) Source # | |
type GTag (K1 i (Field n a) :: Type -> Type) Source # | |
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
Instances
enum :: Enumeration n Source #
Convenience function to construct Enumeration
objects.
let role = RoleUser enum
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
Orphan instances
(GPinchable a, GPinchable b, GTag a ~ GTag b, Combinable (GTag a)) => GPinchable (a :*: b) Source # | |
(GPinchable a, GPinchable b, GTag a ~ GTag b) => GPinchable (a :+: b) Source # | |
(Datatype d, GPinchable a) => GPinchable (D1 d a) Source # | |
GPinchable a => GPinchable (M1 i c a) Source # | |