Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data Word512 = Word512 !Word256 !Word256
- data Int512 = Int512 !Int256 !Word256
- newtype W256 = W256 Word256
- type family ToSizzle (t :: Type) :: Type where ...
- class ToSizzleBV a where
- type family FromSizzle (t :: Type) :: Type where ...
- class FromSizzleBV a where
- fromSizzle :: a -> FromSizzle a
- litBytes :: ByteString -> [SWord 8]
- data Buffer
- newtype Addr = Addr {}
- newtype SAddr = SAddr {
- saddressWord160 :: SWord 160
- strip0x :: ByteString -> ByteString
- newtype ByteStringS = ByteStringS ByteString
- hexByteString :: String -> ByteString -> ByteString
- hexText :: Text -> ByteString
- readN :: Integral a => String -> a
- readNull :: Read a => a -> String -> a
- wordField :: Object -> Text -> Parser W256
- addrField :: Object -> Text -> Parser Addr
- addrFieldMaybe :: Object -> Text -> Parser (Maybe Addr)
- dataField :: Object -> Text -> Parser ByteString
- toWord512 :: W256 -> Word512
- fromWord512 :: Word512 -> W256
- num :: (Integral a, Num b) => a -> b
- padLeft :: Int -> ByteString -> ByteString
- padRight :: Int -> ByteString -> ByteString
- truncpad :: Int -> [SWord 8] -> [SWord 8]
- word256 :: ByteString -> Word256
- word :: ByteString -> W256
- byteAt :: (Bits a, Bits b, Integral a, Num b) => a -> Int -> b
- fromBE :: Integral a => ByteString -> a
- asBE :: Integral a => a -> ByteString
- word256Bytes :: W256 -> ByteString
- word160Bytes :: Addr -> ByteString
- newtype Nibble = Nibble Word8
- hi :: Word8 -> Nibble
- lo :: Word8 -> Nibble
- toByte :: Nibble -> Nibble -> Word8
- unpackNibbles :: ByteString -> [Nibble]
- packNibbles :: [Nibble] -> ByteString
Documentation
Instances
Instances
Instances
class ToSizzleBV a where Source #
Conversion from a fixed-sized BV to a sized bit-vector.
Nothing
type family FromSizzle (t :: Type) :: Type where ... Source #
Capture the correspondence between sized and fixed-sized BVs
FromSizzle (WordN 256) = W256 | |
FromSizzle (WordN 160) = Addr |
class FromSizzleBV a where Source #
Conversion from a sized BV to a fixed-sized bit-vector.
Nothing
fromSizzle :: a -> FromSizzle a Source #
Convert a sized bit-vector to the corresponding fixed-sized bit-vector,
for instance 'SWord 16' to SWord16
. See also toSized
.
fromSizzle :: (Num (FromSizzle a), Integral a) => a -> FromSizzle a Source #
Instances
FromSizzleBV (WordN 160) Source # | |
Defined in EVM.Types fromSizzle :: WordN 160 -> FromSizzle (WordN 160) Source # | |
FromSizzleBV (WordN 256) Source # | |
Defined in EVM.Types fromSizzle :: WordN 256 -> FromSizzle (WordN 256) Source # |
litBytes :: ByteString -> [SWord 8] Source #
Operations over buffers (concrete or symbolic)
A buffer is a list of bytes. For concrete execution, this is simply ByteString
.
In symbolic settings, it is a list of symbolic bitvectors of size 8.
Instances
Show Buffer Source # | |
Semigroup Buffer Source # | |
Monoid Buffer Source # | |
EqSymbolic Buffer Source # | |
Defined in EVM.Types | |
SDisplay Buffer Source # | |
Instances
strip0x :: ByteString -> ByteString Source #
newtype ByteStringS Source #
Instances
Eq ByteStringS Source # | |
Defined in EVM.Types (==) :: ByteStringS -> ByteStringS -> Bool # (/=) :: ByteStringS -> ByteStringS -> Bool # | |
Read ByteStringS Source # | |
Defined in EVM.Types readsPrec :: Int -> ReadS ByteStringS # readList :: ReadS [ByteStringS] # readPrec :: ReadPrec ByteStringS # readListPrec :: ReadPrec [ByteStringS] # | |
Show ByteStringS Source # | |
Defined in EVM.Types showsPrec :: Int -> ByteStringS -> ShowS # show :: ByteStringS -> String # showList :: [ByteStringS] -> ShowS # |
hexByteString :: String -> ByteString -> ByteString Source #
hexText :: Text -> ByteString Source #
fromWord512 :: Word512 -> W256 Source #
padLeft :: Int -> ByteString -> ByteString Source #
padRight :: Int -> ByteString -> ByteString Source #
word256 :: ByteString -> Word256 Source #
word :: ByteString -> W256 Source #
fromBE :: Integral a => ByteString -> a Source #
asBE :: Integral a => a -> ByteString Source #
word256Bytes :: W256 -> ByteString Source #
word160Bytes :: Addr -> ByteString Source #
Instances
unpackNibbles :: ByteString -> [Nibble] Source #
packNibbles :: [Nibble] -> ByteString Source #