hevm-0.16: Ethereum virtual machine evaluator

Safe HaskellNone
LanguageHaskell2010

EVM.Types

Documentation

data Word512 Source #

Constructors

Word512 !Word256 !Word256 

Instances

Bounded Word512 Source # 
Enum Word512 Source # 
Eq Word512 Source # 

Methods

(==) :: Word512 -> Word512 -> Bool #

(/=) :: Word512 -> Word512 -> Bool #

Integral Word512 Source # 
Data Word512 Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Word512 -> c Word512 #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Word512 #

toConstr :: Word512 -> Constr #

dataTypeOf :: Word512 -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Word512) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Word512) #

gmapT :: (forall b. Data b => b -> b) -> Word512 -> Word512 #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Word512 -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Word512 -> r #

gmapQ :: (forall d. Data d => d -> u) -> Word512 -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Word512 -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Word512 -> m Word512 #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Word512 -> m Word512 #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Word512 -> m Word512 #

Num Word512 Source # 
Ord Word512 Source # 
Read Word512 Source # 
Real Word512 Source # 
Show Word512 Source # 
Ix Word512 Source # 
Generic Word512 Source # 

Associated Types

type Rep Word512 :: * -> * #

Methods

from :: Word512 -> Rep Word512 x #

to :: Rep Word512 x -> Word512 #

Hashable Word512 Source # 

Methods

hashWithSalt :: Int -> Word512 -> Int #

hash :: Word512 -> Int #

Bits Word512 Source # 
FiniteBits Word512 Source # 
BinaryWord Word512 Source # 
DoubleWord Word512 Source # 
type Rep Word512 Source # 
type SignedWord Word512 Source # 
type UnsignedWord Word512 Source # 
type HiWord Word512 Source # 
type LoWord Word512 Source # 

data Int512 Source #

Constructors

Int512 !Int256 !Word256 

Instances

Bounded Int512 Source # 
Enum Int512 Source # 
Eq Int512 Source # 

Methods

(==) :: Int512 -> Int512 -> Bool #

(/=) :: Int512 -> Int512 -> Bool #

Integral Int512 Source # 
Data Int512 Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Int512 -> c Int512 #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Int512 #

toConstr :: Int512 -> Constr #

dataTypeOf :: Int512 -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Int512) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Int512) #

gmapT :: (forall b. Data b => b -> b) -> Int512 -> Int512 #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Int512 -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Int512 -> r #

gmapQ :: (forall d. Data d => d -> u) -> Int512 -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Int512 -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Int512 -> m Int512 #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Int512 -> m Int512 #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Int512 -> m Int512 #

Num Int512 Source # 
Ord Int512 Source # 
Read Int512 Source # 
Real Int512 Source # 
Show Int512 Source # 
Ix Int512 Source # 
Generic Int512 Source # 

Associated Types

type Rep Int512 :: * -> * #

Methods

from :: Int512 -> Rep Int512 x #

to :: Rep Int512 x -> Int512 #

Hashable Int512 Source # 

Methods

hashWithSalt :: Int -> Int512 -> Int #

hash :: Int512 -> Int #

Bits Int512 Source # 
FiniteBits Int512 Source # 
BinaryWord Int512 Source # 
DoubleWord Int512 Source # 
type Rep Int512 Source # 
type SignedWord Int512 Source # 
type UnsignedWord Int512 Source # 
type HiWord Int512 Source # 
type LoWord Int512 Source # 

newtype W256 Source #

Constructors

W256 Word256 

Instances

Bounded W256 Source # 
Enum W256 Source # 

Methods

succ :: W256 -> W256 #

pred :: W256 -> W256 #

toEnum :: Int -> W256 #

fromEnum :: W256 -> Int #

enumFrom :: W256 -> [W256] #

enumFromThen :: W256 -> W256 -> [W256] #

enumFromTo :: W256 -> W256 -> [W256] #

enumFromThenTo :: W256 -> W256 -> W256 -> [W256] #

Eq W256 Source # 

Methods

(==) :: W256 -> W256 -> Bool #

(/=) :: W256 -> W256 -> Bool #

Integral W256 Source # 

Methods

quot :: W256 -> W256 -> W256 #

rem :: W256 -> W256 -> W256 #

div :: W256 -> W256 -> W256 #

mod :: W256 -> W256 -> W256 #

quotRem :: W256 -> W256 -> (W256, W256) #

divMod :: W256 -> W256 -> (W256, W256) #

toInteger :: W256 -> Integer #

Num W256 Source # 

Methods

(+) :: W256 -> W256 -> W256 #

(-) :: W256 -> W256 -> W256 #

(*) :: W256 -> W256 -> W256 #

negate :: W256 -> W256 #

abs :: W256 -> W256 #

signum :: W256 -> W256 #

fromInteger :: Integer -> W256 #

Ord W256 Source # 

Methods

compare :: W256 -> W256 -> Ordering #

(<) :: W256 -> W256 -> Bool #

(<=) :: W256 -> W256 -> Bool #

(>) :: W256 -> W256 -> Bool #

(>=) :: W256 -> W256 -> Bool #

max :: W256 -> W256 -> W256 #

min :: W256 -> W256 -> W256 #

Read W256 Source # 
Real W256 Source # 

Methods

toRational :: W256 -> Rational #

Show W256 Source # 

Methods

showsPrec :: Int -> W256 -> ShowS #

show :: W256 -> String #

showList :: [W256] -> ShowS #

Generic W256 Source # 

Associated Types

type Rep W256 :: * -> * #

Methods

from :: W256 -> Rep W256 x #

to :: Rep W256 x -> W256 #

FromJSON W256 Source # 
FromJSONKey W256 Source # 
Bits W256 Source # 
FiniteBits W256 Source # 
ParseField W256 Source # 
ParseFields W256 Source # 
ParseRecord W256 Source # 
ToRPC W256 Source # 

Methods

toRPC :: W256 -> String Source #

SDisplay W256 Source # 

Methods

sexp :: W256 -> SExpr Text Source #

type Rep W256 Source # 
type Rep W256 = D1 * (MetaData "W256" "EVM.Types" "hevm-0.16-5a74lCQx1KPFycEOS1YSBh" True) (C1 * (MetaCons "W256" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Word256)))

newtype Addr Source #

Constructors

Addr 

Instances

Enum Addr Source # 

Methods

succ :: Addr -> Addr #

pred :: Addr -> Addr #

toEnum :: Int -> Addr #

fromEnum :: Addr -> Int #

enumFrom :: Addr -> [Addr] #

enumFromThen :: Addr -> Addr -> [Addr] #

enumFromTo :: Addr -> Addr -> [Addr] #

enumFromThenTo :: Addr -> Addr -> Addr -> [Addr] #

Eq Addr Source # 

Methods

(==) :: Addr -> Addr -> Bool #

(/=) :: Addr -> Addr -> Bool #

Integral Addr Source # 

Methods

quot :: Addr -> Addr -> Addr #

rem :: Addr -> Addr -> Addr #

div :: Addr -> Addr -> Addr #

mod :: Addr -> Addr -> Addr #

quotRem :: Addr -> Addr -> (Addr, Addr) #

divMod :: Addr -> Addr -> (Addr, Addr) #

toInteger :: Addr -> Integer #

Num Addr Source # 

Methods

(+) :: Addr -> Addr -> Addr #

(-) :: Addr -> Addr -> Addr #

(*) :: Addr -> Addr -> Addr #

negate :: Addr -> Addr #

abs :: Addr -> Addr #

signum :: Addr -> Addr #

fromInteger :: Integer -> Addr #

Ord Addr Source # 

Methods

compare :: Addr -> Addr -> Ordering #

(<) :: Addr -> Addr -> Bool #

(<=) :: Addr -> Addr -> Bool #

(>) :: Addr -> Addr -> Bool #

(>=) :: Addr -> Addr -> Bool #

max :: Addr -> Addr -> Addr #

min :: Addr -> Addr -> Addr #

Read Addr Source # 
Real Addr Source # 

Methods

toRational :: Addr -> Rational #

Show Addr Source # 

Methods

showsPrec :: Int -> Addr -> ShowS #

show :: Addr -> String #

showList :: [Addr] -> ShowS #

Generic Addr Source # 

Associated Types

type Rep Addr :: * -> * #

Methods

from :: Addr -> Rep Addr x #

to :: Rep Addr x -> Addr #

FromJSON Addr Source # 
FromJSONKey Addr Source # 
Bits Addr Source # 
ParseField Addr Source # 
ParseFields Addr Source # 
ParseRecord Addr Source # 
ToRPC Addr Source # 

Methods

toRPC :: Addr -> String Source #

SDisplay Addr Source # 

Methods

sexp :: Addr -> SExpr Text Source #

type Rep Addr Source # 
type Rep Addr = D1 * (MetaData "Addr" "EVM.Types" "hevm-0.16-5a74lCQx1KPFycEOS1YSBh" True) (C1 * (MetaCons "Addr" PrefixI True) (S1 * (MetaSel (Just Symbol "addressWord160") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Word160)))

num :: (Integral a, Num b) => a -> b Source #

byteAt :: (Bits a, Bits b, Integral a, Num b) => a -> Int -> b Source #