Copyright | Aleksandr Krupenkin 2016-2024 |
---|---|
License | Apache-2.0 |
Maintainer | mail@akru.me |
Stability | experimental |
Portability | noportable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Data.Solidity.Prim
Description
Solidity primitive data types.
Documentation
Ethereum account address
Instances
FromJSON Address Source # | |
ToJSON Address Source # | |
Defined in Data.Solidity.Prim.Address | |
IsString Address Source # | |
Defined in Data.Solidity.Prim.Address Methods fromString :: String -> Address # | |
Generic Address Source # | |
Show Address Source # | |
Default Address Source # | |
Defined in Data.Solidity.Prim.Address | |
Generic Address Source # | |
Eq Address Source # | |
Ord Address Source # | |
Defined in Data.Solidity.Prim.Address | |
AbiGet Address Source # | |
AbiPut Address Source # | |
AbiType Address Source # | |
type Rep Address Source # | |
Defined in Data.Solidity.Prim.Address | |
type Code Address Source # | |
Defined in Data.Solidity.Prim.Address |
Simplest Byte Array
Instances
FromJSON Bytes Source # | |
ToJSON Bytes Source # | |
Defined in Data.Solidity.Prim.Bytes | |
IsString Bytes Source # | |
Defined in Data.Solidity.Prim.Bytes Methods fromString :: String -> Bytes # | |
Monoid Bytes | |
Semigroup Bytes | |
Show Bytes | |
NormalForm Bytes | |
Defined in Data.ByteArray.Bytes Methods toNormalForm :: Bytes -> () # | |
NFData Bytes | |
Defined in Data.ByteArray.Bytes | |
Eq Bytes | |
Ord Bytes | |
ByteArray Bytes | |
ByteArrayAccess Bytes | |
AbiGet Bytes Source # | |
AbiPut Bytes Source # | |
AbiType Bytes Source # | |
KnownNat n => FromJSON (BytesN n) Source # | |
KnownNat n => ToJSON (BytesN n) Source # | |
Defined in Data.Solidity.Prim.Bytes | |
KnownNat n => IsString (BytesN n) Source # | |
Defined in Data.Solidity.Prim.Bytes Methods fromString :: String -> BytesN n # | |
(KnownNat n, n <= 32) => AbiGet (BytesN n) Source # | |
KnownNat n => AbiPut (BytesN n) Source # | |
KnownNat n => AbiType (BytesN n) Source # | |
type BytesN n = SizedByteArray n Bytes Source #
Sized byte array with fixed length in bytes
Signed integer with fixed length in bits.
Instances
data UIntN (n :: Nat) Source #
Unsigned integer with fixed length in bits.
Instances
A Typed-level sized List equivalent to [a]
Instances
Generic (ListN n a) | |
(NatWithinBound Int n, KnownNat n) => IsList (ListN n a) Source # | |
Show a => Show (ListN n a) | |
NormalForm a => NormalForm (ListN n a) | |
Defined in Basement.Sized.List Methods toNormalForm :: ListN n a -> () # | |
Eq a => Eq (ListN n a) | |
Ord a => Ord (ListN n a) | |
(NatWithinBound Int n, KnownNat n, AbiGet a) => AbiGet (ListN n a) Source # | |
(AbiPut a, KnownNat n, 1 <= (n + 1)) => AbiPut (ListN n a) Source # | |
(AbiType a, KnownNat n) => AbiType (ListN n a) Source # | |
type Rep (ListN n a) | |
Defined in Basement.Sized.List | |
type Item (ListN n a) Source # | |
Defined in Data.Solidity.Prim.List |