-- SPDX-FileCopyrightText: 2020 Tocqueville Group -- -- SPDX-License-Identifier: LicenseRef-MIT-TQ -- | Michelson types represented in untyped model. module Michelson.Untyped.Type ( Type (..) , T (..) , ParameterType (..) , toption , tpair , tor , tyint , tynat , tyunit , tybool , typair , tyor , tyImplicitAccountParam , isAtomicType , isKey , isSignature , isComparable , isMutez , isKeyHash , isBool , isString , isInteger , isTimestamp , isNat , isInt , isBytes , renderType , unwrapT ) where import Data.Aeson.TH (deriveJSON) import Data.Data (Data(..)) import Fmt (Buildable(build)) import Language.Haskell.TH.Lift (deriveLift) import Prelude hiding ((<$>)) import Text.PrettyPrint.Leijen.Text (Doc, align, softbreak, (<$>), (<+>)) import Michelson.Printer.Util (Prettier(..), RenderContext, RenderDoc(..), addParens, buildRenderDoc, doesntNeedParens, needsParens, wrapInParens) import Michelson.Untyped.Annotation (AnnotationSet, FieldAnn, RootAnn, TypeAnn, emptyAnnSet, fullAnnSet, noAnn, singleAnnSet) import Util.Aeson -- Annotated type data Type = Type ~T TypeAnn deriving stock (Eq, Show, Data, Generic) unwrapT :: Type -> T unwrapT (Type t _) = t instance NFData Type instance RenderDoc (Prettier Type) where renderDoc pn (Prettier w) = case w of (Type t ta) -> renderType t False pn (singleAnnSet ta) instance RenderDoc Type where renderDoc pn (Type t ta) = renderType t True pn (singleAnnSet ta) instance RenderDoc T where renderDoc pn t = renderType t True pn emptyAnnSet -- | Since Babylon parameter type can have special root annotation. data ParameterType = ParameterType Type RootAnn deriving stock (Eq, Show, Data, Generic) instance NFData ParameterType instance RenderDoc (Prettier ParameterType) where renderDoc pn (Prettier w) = case w of ParameterType (Type t ta) ra -> renderType t False pn (fullAnnSet [ta] [ra] []) instance RenderDoc ParameterType where renderDoc pn (ParameterType (Type t ta) ra) = renderType t True pn (fullAnnSet [ta] [ra] []) -- Ordering between different kinds of annotations is not significant, -- but ordering among annotations of the same kind is. Annotations -- of a same kind must be grouped together. -- (prim @v :t %x arg1 arg2 ...) -- these are equivalent -- PAIR :t @my_pair %x %y -- PAIR %x %y :t @my_pair renderType :: T -> Bool -> RenderContext -> AnnotationSet -> Doc renderType t forceSingleLine pn annSet = let annDoc = renderDoc doesntNeedParens annSet recRenderer t' annSet' = renderType t' forceSingleLine needsParens annSet' renderBranches d1 d2 = if forceSingleLine then (d1 <+> d2) else align $ softbreak <> (d1 <$> d2) in case t of TInt -> wrapInParens pn $ "int" :| [annDoc] TNat -> wrapInParens pn $ "nat" :| [annDoc] TString -> wrapInParens pn $ "string" :| [annDoc] TMutez -> wrapInParens pn $ "mutez" :| [annDoc] TBool -> wrapInParens pn $ "bool" :| [annDoc] TKeyHash -> wrapInParens pn $ "key_hash" :| [annDoc] TTimestamp -> wrapInParens pn $ "timestamp" :| [annDoc] TBytes -> wrapInParens pn $ "bytes" :| [annDoc] TAddress -> wrapInParens pn $ "address" :| [annDoc] TKey -> wrapInParens pn $ "key" :| [annDoc] TUnit -> wrapInParens pn $ "unit" :| [annDoc] TSignature -> wrapInParens pn $ "signature" :| [annDoc] TChainId -> wrapInParens pn $ "chain_id" :| [annDoc] TOperation -> wrapInParens pn $ "operation" :| [annDoc] TOption (Type t1 ta1) -> addParens pn $ "option" <+> annDoc <+> recRenderer t1 (singleAnnSet ta1) TList (Type t1 ta1) -> addParens pn $ "list" <+> annDoc <+> recRenderer t1 (singleAnnSet ta1) TSet (Type t1 ta1) -> addParens pn $ "set" <+> annDoc <+> recRenderer t1 (singleAnnSet ta1) TContract (Type t1 ta1) -> addParens pn $ "contract" <+> annDoc <+> recRenderer t1 (singleAnnSet ta1) TPair fa1 fa2 (Type t1 ta1) (Type t2 ta2) -> addParens pn $ "pair" <+> annDoc <+> renderBranches (recRenderer t1 $ fullAnnSet [ta1] [fa1] []) (recRenderer t2 $ fullAnnSet [ta2] [fa2] []) TOr fa1 fa2 (Type t1 ta1) (Type t2 ta2) -> addParens pn $ "or" <+> annDoc <+> renderBranches (recRenderer t1 $ fullAnnSet [ta1] [fa1] []) (recRenderer t2 $ fullAnnSet [ta2] [fa2] []) TLambda (Type t1 ta1) (Type t2 ta2) -> addParens pn $ "lambda" <+> annDoc <+> renderBranches (recRenderer t1 $ singleAnnSet ta1) (recRenderer t2 $ singleAnnSet ta2) TMap (Type t1 ta1) (Type t2 ta2) -> addParens pn $ "map" <+> annDoc <+> renderBranches (recRenderer t1 $ singleAnnSet ta1) (recRenderer t2 $ singleAnnSet ta2) TBigMap (Type t1 ta1) (Type t2 ta2) -> addParens pn $ "big_map" <+> annDoc <+> renderBranches (recRenderer t1 $ singleAnnSet ta1) (recRenderer t2 $ singleAnnSet ta2) instance Buildable Type where build = buildRenderDoc instance Buildable ParameterType where build = buildRenderDoc -- Michelson Type data T = TKey | TUnit | TSignature | TChainId | TOption Type | TList Type | TSet Type | TOperation | TContract Type | TPair FieldAnn FieldAnn Type Type | TOr FieldAnn FieldAnn Type Type | TLambda Type Type | TMap Type Type | TBigMap Type Type | TInt | TNat | TString | TBytes | TMutez | TBool | TKeyHash | TTimestamp | TAddress deriving stock (Eq, Show, Data, Generic) instance Buildable T where build = buildRenderDoc instance NFData T toption :: Type -> T toption t = TOption t tpair :: Type -> Type -> T tpair l r = TPair noAnn noAnn l r tor :: Type -> Type -> T tor l r = TOr noAnn noAnn l r tyint :: Type tyint = Type TInt noAnn tynat :: Type tynat = Type TNat noAnn tyunit :: Type tyunit = Type TUnit noAnn tybool :: Type tybool = Type TBool noAnn typair :: Type -> Type -> Type typair l r = Type (tpair l r) noAnn tyor :: Type -> Type -> Type tyor l r = Type (tor l r) noAnn -- | For implicit account, which type its parameter seems to have -- from outside. tyImplicitAccountParam :: Type tyImplicitAccountParam = Type TUnit noAnn isAtomicType :: Type -> Bool isAtomicType t@(Type _ tAnn) | tAnn == noAnn = isComparable t || isKey t || isUnit t || isSignature t || isOperation t isAtomicType _ = False isKey :: Type -> Bool isKey (Type TKey _) = True isKey _ = False isUnit :: Type -> Bool isUnit (Type TUnit _) = True isUnit _ = False isSignature :: Type -> Bool isSignature (Type TSignature _) = True isSignature _ = False isOperation :: Type -> Bool isOperation (Type TOperation _) = True isOperation _ = False isComparable :: Type -> Bool isComparable (Type t _) = case t of TInt -> True TNat -> True TString -> True TBytes -> True TMutez -> True TBool -> True TKeyHash -> True TTimestamp -> True TAddress -> True _ -> False isMutez :: Type -> Bool isMutez (Type TMutez _) = True isMutez _ = False isTimestamp :: Type -> Bool isTimestamp (Type TTimestamp _) = True isTimestamp _ = False isKeyHash :: Type -> Bool isKeyHash (Type TKeyHash _) = True isKeyHash _ = False isBool :: Type -> Bool isBool (Type TBool _) = True isBool _ = False isString :: Type -> Bool isString (Type TString _) = True isString _ = False isInteger :: Type -> Bool isInteger a = isNat a || isInt a || isMutez a || isTimestamp a isNat :: Type -> Bool isNat (Type TNat _) = True isNat _ = False isInt :: Type -> Bool isInt (Type TInt _) = True isInt _ = False isBytes :: Type -> Bool isBytes (Type TBytes _) = True isBytes _ = False ---------------------------------------------------------------------------- -- TH derivations ---------------------------------------------------------------------------- deriveJSON morleyAesonOptions ''Type deriveJSON morleyAesonOptions ''T deriveJSON morleyAesonOptions ''ParameterType deriveLift ''Type deriveLift ''T deriveLift ''ParameterType