web3-0.8.3.0: Ethereum API for Haskell

CopyrightAlexander Krupenkin 2017-2018
LicenseBSD3
Maintainermail@akru.me
Stabilityexperimental
Portabilityunportable
Safe HaskellNone
LanguageHaskell2010

Data.Solidity.Event.Internal

Description

This module is internal, the purpose is to define helper classes and types to assist in event decoding. The user of this library should have no need to use this directly in application code.

Synopsis

Documentation

data HList :: [Type] -> Type where Source #

Constructors

HNil :: HList '[] 
(:<) :: a -> HList as -> HList (a ': as) infixr 0 

class HListRep a xs | a -> xs, a -> xs where Source #

Generic representation to HList representation

Methods

toHList :: a -> HList xs Source #

fromHList :: HList xs -> a Source #

Instances
HListRep (NP f as') as => HListRep (SOP f (as' ': ([] :: [[k]]))) as Source # 
Instance details

Defined in Data.Solidity.Event.Internal

Methods

toHList :: SOP f (as' ': []) -> HList as Source #

fromHList :: HList as -> SOP f (as' ': []) Source #

HListRep (NP I ([] :: [Type])) ([] :: [Type]) Source # 
Instance details

Defined in Data.Solidity.Event.Internal

Methods

toHList :: NP I [] -> HList [] Source #

fromHList :: HList [] -> NP I [] Source #

HListRep (NP I as) as => HListRep (NP I (a ': as)) (a ': as) Source # 
Instance details

Defined in Data.Solidity.Event.Internal

Methods

toHList :: NP I (a ': as) -> HList (a ': as) Source #

fromHList :: HList (a ': as) -> NP I (a ': as) Source #

class Sort (xs :: [Type]) where Source #

Sort a Tagged HList

Associated Types

type Sort' xs :: [Type] Source #

Methods

sort :: HList xs -> HList (Sort' xs) Source #

Instances
Sort ([] :: [Type]) Source # 
Instance details

Defined in Data.Solidity.Event.Internal

Associated Types

type Sort' [] :: [Type] Source #

Methods

sort :: HList [] -> HList (Sort' []) Source #

(Sort xs, Insert x (Sort' xs)) => Sort (x ': xs) Source # 
Instance details

Defined in Data.Solidity.Event.Internal

Associated Types

type Sort' (x ': xs) :: [Type] Source #

Methods

sort :: HList (x ': xs) -> HList (Sort' (x ': xs)) Source #

class Insert (x :: Type) (xs :: [Type]) where Source #

Associated Types

type Insert' x xs :: [Type] Source #

Methods

insert :: x -> HList xs -> HList (Insert' x xs) Source #

Instances
Insert x ([] :: [Type]) Source # 
Instance details

Defined in Data.Solidity.Event.Internal

Associated Types

type Insert' x [] :: [Type] Source #

Methods

insert :: x -> HList [] -> HList (Insert' x []) Source #

InsertCmp (CmpNat n m) (Tagged n x) (Tagged m y) ys => Insert (Tagged n x) (Tagged m y ': ys) Source # 
Instance details

Defined in Data.Solidity.Event.Internal

Associated Types

type Insert' (Tagged n x) (Tagged m y ': ys) :: [Type] Source #

Methods

insert :: Tagged n x -> HList (Tagged m y ': ys) -> HList (Insert' (Tagged n x) (Tagged m y ': ys)) Source #

class InsertCmp (b :: Ordering) (x :: Type) (y :: Type) (ys :: [Type]) where Source #

Associated Types

type InsertCmp' b x y ys :: [Type] Source #

Methods

insertCmp :: Proxy (b :: Ordering) -> x -> y -> HList ys -> HList (InsertCmp' b x y ys) Source #

Instances
InsertCmp LT x y ys Source # 
Instance details

Defined in Data.Solidity.Event.Internal

Associated Types

type InsertCmp' LT x y ys :: [Type] Source #

Methods

insertCmp :: Proxy LT -> x -> y -> HList ys -> HList (InsertCmp' LT x y ys) Source #

Insert x ys => InsertCmp GT x y ys Source # 
Instance details

Defined in Data.Solidity.Event.Internal

Associated Types

type InsertCmp' GT x y ys :: [Type] Source #

Methods

insertCmp :: Proxy GT -> x -> y -> HList ys -> HList (InsertCmp' GT x y ys) Source #

class UnTag t where Source #

Unwrap all the Tagged items in an HList

Associated Types

type UnTag' t :: [Type] Source #

Methods

unTag :: HList t -> HList (UnTag' t) Source #

Instances
UnTag ([] :: [Type]) Source # 
Instance details

Defined in Data.Solidity.Event.Internal

Associated Types

type UnTag' [] :: [Type] Source #

Methods

unTag :: HList [] -> HList (UnTag' []) Source #

UnTag ts => UnTag (Tagged n a ': ts) Source # 
Instance details

Defined in Data.Solidity.Event.Internal

Associated Types

type UnTag' (Tagged n a ': ts) :: [Type] Source #

Methods

unTag :: HList (Tagged n a ': ts) -> HList (UnTag' (Tagged n a ': ts)) Source #

class HListMerge (as :: [Type]) (bs :: [Type]) where Source #

Associated Types

type Concat as bs :: [Type] Source #

Methods

mergeHList :: HList as -> HList bs -> HList (Concat as bs) Source #

Instances
HListMerge ([] :: [Type]) bs Source # 
Instance details

Defined in Data.Solidity.Event.Internal

Associated Types

type Concat [] bs :: [Type] Source #

Methods

mergeHList :: HList [] -> HList bs -> HList (Concat [] bs) Source #

HListMerge as bs => HListMerge (a ': as) bs Source # 
Instance details

Defined in Data.Solidity.Event.Internal

Associated Types

type Concat (a ': as) bs :: [Type] Source #

Methods

mergeHList :: HList (a ': as) -> HList bs -> HList (Concat (a ': as) bs) Source #

class HListMergeSort as bs where Source #

Associated Types

type MergeSort' as bs :: [Type] Source #

Methods

mergeSortHList :: HList as -> HList bs -> HList (MergeSort' as bs) Source #

Instances
(HListMerge as bs, Concat as bs ~ cs, Sort cs, Sort' cs ~ cs') => HListMergeSort as bs Source # 
Instance details

Defined in Data.Solidity.Event.Internal

Associated Types

type MergeSort' as bs :: [Type] Source #

Methods

mergeSortHList :: HList as -> HList bs -> HList (MergeSort' as bs) Source #

class MergeIndexedArguments as bs where Source #

Associated Types

type MergeIndexedArguments' as bs :: [Type] Source #

Instances
(HListMergeSort as bs, MergeSort' as bs ~ cs, UnTag cs, UnTag cs' ~ ds) => MergeIndexedArguments as bs Source # 
Instance details

Defined in Data.Solidity.Event.Internal

Associated Types

type MergeIndexedArguments' as bs :: [Type] Source #