web3-0.7.3.0: Ethereum API for Haskell

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

Network.Ethereum.ABI.Prim.List

Contents

Description

Ethereum ABI dynamic and static size vectors based on linked lists.

Synopsis

Documentation

data ListN (n :: Nat) a :: Nat -> * -> * #

A Typed-level sized List equivalent to [a]

Instances

Eq a => Eq (ListN n a) 

Methods

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

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

Ord a => Ord (ListN n a) 

Methods

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

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

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

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

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

max :: ListN n a -> ListN n a -> ListN n a #

min :: ListN n a -> ListN n a -> ListN n a #

Show a => Show (ListN n a) 

Methods

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

show :: ListN n a -> String #

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

Generic (ListN n a) 

Associated Types

type Rep (ListN n a) :: * -> * #

Methods

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

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

NormalForm a => NormalForm (ListN n a) 

Methods

toNormalForm :: ListN n a -> () #

type Rep (ListN n a) 
type Rep (ListN n a) = D1 * (MetaData "ListN" "Basement.Sized.List" "basement-0.0.7-AsRzReOE7L68EDipEfgoG3" True) (C1 * (MetaCons "ListN" PrefixI True) (S1 * (MetaSel (Just Symbol "unListN") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [a])))
type Item (ListN n a) # 
type Item (ListN n a) = a

Orphan instances

ABIGet a => ABIGet [a] Source # 

Methods

abiGet :: Get [a] Source #

ABIPut a => ABIPut [a] Source # 

Methods

abiPut :: Putter [a] Source #

ABIType [a] Source # 

Methods

isDynamic :: Proxy * [a] -> Bool Source #

(NatWithinBound Int n, KnownNat n) => IsList (ListN n a) Source # 

Associated Types

type Item (ListN n a) :: * #

Methods

fromList :: [Item (ListN n a)] -> ListN n a #

fromListN :: Int -> [Item (ListN n a)] -> ListN n a #

toList :: ListN n a -> [Item (ListN n a)] #

(NatWithinBound Int n, KnownNat n, ABIGet a) => ABIGet (ListN n a) Source # 

Methods

abiGet :: Get (ListN n a) Source #

ABIPut a => ABIPut (ListN n a) Source # 

Methods

abiPut :: Putter (ListN n a) Source #

ABIType (ListN n a) Source # 

Methods

isDynamic :: Proxy * (ListN n a) -> Bool Source #