pinch-0.4.0.0: An alternative implementation of Thrift for Haskell.
Copyright(c) Abhinav Gupta 2015
LicenseBSD3
MaintainerAbhinav Gupta <mail@abhinavg.net>
Stabilityexperimental
Safe HaskellSafe-Inferred
LanguageHaskell2010

Pinch.Internal.Value

Description

This module defines an intermediate representation for Thrift values and functions to work with the intermediate representation.

Synopsis

Documentation

data Value a where Source #

Value maps directly to serialized representation of Thrift types. It contains about as much information as what gets sent over the wire. Value objects are tagged with different TType values to indicate the type of the value.

Typical usage will not involve accessing the constructors for this type. Pinchable must be used to construct Value objects or convert them back to original types.

Constructors

VBool :: !Bool -> Value TBool 
VByte :: !Int8 -> Value TByte 
VDouble :: !Double -> Value TDouble 
VInt16 :: !Int16 -> Value TInt16 
VInt32 :: !Int32 -> Value TInt32 
VInt64 :: !Int64 -> Value TInt64 
VBinary :: !ByteString -> Value TBinary 
VStruct :: !(HashMap Int16 SomeValue) -> Value TStruct 
VMap :: forall k v. (IsTType k, IsTType v) => !(FoldList (MapItem k v)) -> Value TMap 
VNullMap :: Value TMap 
VSet :: forall a. IsTType a => !(FoldList (Value a)) -> Value TSet 
VList :: forall a. IsTType a => !(FoldList (Value a)) -> Value TList 

Instances

Instances details
Eq (Value a) Source # 
Instance details

Defined in Pinch.Internal.Value

Methods

(==) :: Value a -> Value a -> Bool #

(/=) :: Value a -> Value a -> Bool #

Show (Value a) Source # 
Instance details

Defined in Pinch.Internal.Value

Methods

showsPrec :: Int -> Value a -> ShowS #

show :: Value a -> String #

showList :: [Value a] -> ShowS #

NFData (Value a) Source # 
Instance details

Defined in Pinch.Internal.Value

Methods

rnf :: Value a -> () #

Hashable (Value a) Source # 
Instance details

Defined in Pinch.Internal.Value

Methods

hashWithSalt :: Int -> Value a -> Int #

hash :: Value a -> Int #

IsTType a => Pinchable (Value a) Source # 
Instance details

Defined in Pinch.Internal.Pinchable

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 #

type Tag (Value a) Source # 
Instance details

Defined in Pinch.Internal.Pinchable

type Tag (Value a) = a

data MapItem k v Source #

A single item in a map

Constructors

MapItem !(Value k) !(Value v) 

Instances

Instances details
Eq (MapItem k v) Source # 
Instance details

Defined in Pinch.Internal.Value

Methods

(==) :: MapItem k v -> MapItem k v -> Bool #

(/=) :: MapItem k v -> MapItem k v -> Bool #

Show (MapItem k v) Source # 
Instance details

Defined in Pinch.Internal.Value

Methods

showsPrec :: Int -> MapItem k v -> ShowS #

show :: MapItem k v -> String #

showList :: [MapItem k v] -> ShowS #

NFData (MapItem k v) Source # 
Instance details

Defined in Pinch.Internal.Value

Methods

rnf :: MapItem k v -> () #

Hashable (MapItem k v) Source # 
Instance details

Defined in Pinch.Internal.Value

Methods

hashWithSalt :: Int -> MapItem k v -> Int #

hash :: MapItem k v -> Int #

data SomeValue where Source #

SomeValue holds any value, regardless of type. This may be used when the type of the value is not necessarily known at compile time. Typically, this will be pattern matched on and code that depends on the value's TType will go inside the scope of the match.

Constructors

SomeValue :: IsTType a => !(Value a) -> SomeValue 

Instances

Instances details
Eq SomeValue Source # 
Instance details

Defined in Pinch.Internal.Value

Show SomeValue Source # 
Instance details

Defined in Pinch.Internal.Value

NFData SomeValue Source # 
Instance details

Defined in Pinch.Internal.Value

Methods

rnf :: SomeValue -> () #

Hashable SomeValue Source # 
Instance details

Defined in Pinch.Internal.Value

castValue :: forall a b. (IsTType a, IsTType b) => Value a -> Maybe (Value b) Source #

Safely attempt to cast a Value into another.

valueTType :: IsTType a => Value a -> TType a Source #

Get the TType of a Value.