web3-0.7.2.0: Ethereum API for Haskell

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

Network.Ethereum.ABI.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

Minimal complete definition

toHList, fromHList

Methods

toHList :: a -> HList xs Source #

fromHList :: HList xs -> a Source #

Instances

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

Methods

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

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

HListRep (NP * I ([] *)) ([] Type) Source # 

Methods

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

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

HListRep (NP * I as) as => HListRep (NP * I ((:) * a as)) ((:) * a as) Source # 

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

Minimal complete definition

sort

Associated Types

type Sort' xs :: [Type] Source #

Methods

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

Instances

Sort ([] Type) Source # 

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Minimal complete definition

insert

Associated Types

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

Methods

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

Instances

Insert x ([] Type) Source # 

Associated Types

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

Methods

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

InsertCmp (CmpNat n m) (Tagged Nat n x) (Tagged Nat m y) ys => Insert (Tagged Nat n x) ((:) * (Tagged Nat m y) ys) Source # 

Associated Types

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

Methods

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

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

Minimal complete definition

insertCmp

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 # 

Associated Types

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

Methods

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

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

Associated Types

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

Methods

insertCmp :: Proxy Ordering 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

Minimal complete definition

unTag

Associated Types

type UnTag' t :: [Type] Source #

Methods

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

Instances

UnTag ([] Type) Source # 

Associated Types

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

Methods

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

UnTag ts => UnTag ((:) * (Tagged k n a) ts) Source # 

Associated Types

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

Methods

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

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

Minimal complete definition

mergeHList

Associated Types

type Concat as bs :: [Type] Source #

Methods

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

Instances

HListMerge ([] Type) bs Source # 

Associated Types

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

Methods

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

HListMerge as bs => HListMerge ((:) Type a as) bs Source # 

Associated Types

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

Methods

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

class HListMergeSort as bs where Source #

Minimal complete definition

mergeSortHList

Associated Types

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

Methods

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

Instances

(HListMerge as bs, (~) [Type] (Concat as bs) cs, Sort cs, (~) [Type] (Sort' cs) cs') => HListMergeSort as bs Source # 

Associated Types

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

Methods

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

class MergeIndexedArguments as bs where Source #

Minimal complete definition

mergeIndexedArguments

Associated Types

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

Instances

(HListMergeSort as bs, (~) [Type] (MergeSort' as bs) cs, UnTag cs, (~) Constraint (UnTag cs') ds) => MergeIndexedArguments as bs Source # 

Associated Types

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