module Michelson.Let
( LetType (..)
, LetValue (..)
) where
import Data.Aeson.TH (deriveJSON)
import qualified Data.Text as T
import Michelson.Macro (ParsedOp)
import Michelson.Untyped (Type, Value')
import Util.Aeson
data LetValue = LetValue
{ LetValue -> Text
lvName :: T.Text
, LetValue -> Type
lvSig :: Type
, LetValue -> Value' ParsedOp
lvVal :: (Value' ParsedOp)
} deriving stock (LetValue -> LetValue -> Bool
(LetValue -> LetValue -> Bool)
-> (LetValue -> LetValue -> Bool) -> Eq LetValue
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LetValue -> LetValue -> Bool
$c/= :: LetValue -> LetValue -> Bool
== :: LetValue -> LetValue -> Bool
$c== :: LetValue -> LetValue -> Bool
Eq, Int -> LetValue -> ShowS
[LetValue] -> ShowS
LetValue -> String
(Int -> LetValue -> ShowS)
-> (LetValue -> String) -> ([LetValue] -> ShowS) -> Show LetValue
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LetValue] -> ShowS
$cshowList :: [LetValue] -> ShowS
show :: LetValue -> String
$cshow :: LetValue -> String
showsPrec :: Int -> LetValue -> ShowS
$cshowsPrec :: Int -> LetValue -> ShowS
Show)
data LetType = LetType
{ LetType -> Text
ltName :: T.Text
, LetType -> Type
ltSig :: Type
} deriving stock (LetType -> LetType -> Bool
(LetType -> LetType -> Bool)
-> (LetType -> LetType -> Bool) -> Eq LetType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: LetType -> LetType -> Bool
$c/= :: LetType -> LetType -> Bool
== :: LetType -> LetType -> Bool
$c== :: LetType -> LetType -> Bool
Eq, Int -> LetType -> ShowS
[LetType] -> ShowS
LetType -> String
(Int -> LetType -> ShowS)
-> (LetType -> String) -> ([LetType] -> ShowS) -> Show LetType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [LetType] -> ShowS
$cshowList :: [LetType] -> ShowS
show :: LetType -> String
$cshow :: LetType -> String
showsPrec :: Int -> LetType -> ShowS
$cshowsPrec :: Int -> LetType -> ShowS
Show)
deriveJSON morleyAesonOptions ''LetValue
deriveJSON morleyAesonOptions ''LetType