module Data.Solidity.Prim.Bool () where
import Data.Solidity.Abi (AbiGet (..), AbiPut (..), AbiType (..))
import Data.Solidity.Prim.Int (getWord256, putWord256)
instance AbiType Bool where
isDynamic :: Proxy Bool -> Bool
isDynamic Proxy Bool
_ = Bool
False
instance AbiGet Bool where
abiGet :: Get Bool
abiGet = Int -> Bool
forall a. Enum a => Int -> a
toEnum (Int -> Bool) -> (Word256 -> Int) -> Word256 -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word256 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word256 -> Bool) -> Get Word256 -> Get Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Get Word256
getWord256
instance AbiPut Bool where
abiPut :: Putter Bool
abiPut = Putter Word256
putWord256 Putter Word256 -> (Bool -> Word256) -> Putter Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Word256
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word256) -> (Bool -> Int) -> Bool -> Word256
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Bool -> Int
forall a. Enum a => a -> Int
fromEnum