-- SPDX-FileCopyrightText: 2021 Oxhead Alpha -- SPDX-License-Identifier: LicenseRef-MIT-OA -- TODO [#712]: Remove this next major release {-# OPTIONS_GHC -Wno-deprecations #-} module Hedgehog.Gen.Michelson.Untyped ( genInternalByteString , genVar , genTyVar , genExpandedOp , genExtInstrAbstract , genPrintComment , genStackRef , genTestAssert , genStackFn , genStackTypePattern , genInstrAbstract , genContract , genContract' , genEntriesOrder , genValue , genValue' , genElt , genParameterType , genType , genValidType , genEpName , genAnnotation , genT ) where import Prelude hiding (EQ, GT, LT) import Data.Text qualified as T import Hedgehog (MonadGen(GenBase), Range) import Hedgehog.Gen qualified as Gen import Hedgehog.Range qualified as Range import Morley.Michelson.Untyped import Hedgehog.Gen.Michelson (genInstrCallStack, genMText) genInternalByteString :: MonadGen m => m InternalByteString genInternalByteString = InternalByteString <$> Gen.bytes (Range.linear 0 100) genVar :: MonadGen m => m Var genVar = Var <$> genSmallText genTyVar :: (MonadGen m, GenBase m ~ Identity) => m TyVar genTyVar = Gen.choice [VarID <$> genVar, TyCon <$> genValidType] genExpandedOp :: (MonadGen m, GenBase m ~ Identity) => m ExpandedOp genExpandedOp = Gen.recursive Gen.choice -- non-recursive constructors [ -- NB: When used together, genExpandedOp & genInstrAbstract are mutually recursive. -- So we use a generator of InstrAbstract that does not contain any ops as an escape hatch. PrimEx <$> Gen.choice instrAbstractWithoutOp ] -- recursive constructors [ PrimEx <$> genInstrAbstract genExpandedOp , SeqEx <$> genSmallList genExpandedOp , Gen.subtermM genExpandedOp $ \expandedOp -> WithSrcEx <$> genInstrCallStack <*> pure expandedOp ] genExtInstrAbstract :: (MonadGen m, GenBase m ~ Identity) => m op -> m (ExtInstrAbstract op) genExtInstrAbstract genOp = Gen.choice [ STACKTYPE <$> genStackTypePattern , FN <$> genSmallText <*> genStackFn <*> genSmallList genOp , UTEST_ASSERT <$> genTestAssert genOp , UPRINT <$> genPrintComment , UCOMMENT <$> genSmallText ] genPrintComment :: MonadGen m => m PrintComment genPrintComment = PrintComment <$> Gen.list (Range.linear 0 5) (Gen.either genSmallText genStackRef) genStackRef :: MonadGen m => m StackRef genStackRef = StackRef <$> Gen.integral (Range.linear 0 (fromIntegral $ maxBound @Word64)) genTestAssert :: MonadGen m => m op -> m (TestAssert op) genTestAssert genOp = TestAssert <$> genSmallText <*> genPrintComment <*> genSmallList genOp genStackFn :: (MonadGen m, GenBase m ~ Identity) => m StackFn genStackFn = StackFn <$> Gen.maybe (Gen.set smallCollectionRange genVar) <*> genStackTypePattern <*> genStackTypePattern genStackTypePattern :: (MonadGen m, GenBase m ~ Identity) => m StackTypePattern genStackTypePattern = Gen.recursive Gen.choice [ pure StkEmpty, pure StkRest ] [ Gen.subtermM genStackTypePattern $ \stp -> StkCons <$> genTyVar <*> pure stp ] genInstrAbstract :: (MonadGen m, GenBase m ~ Identity) => m op -> m (InstrAbstract op) genInstrAbstract genOp = Gen.choice $ instrAbstractWithOp genOp <> instrAbstractWithoutOp instrAbstractWithOp :: (MonadGen m, GenBase m ~ Identity) => m op -> [m (InstrAbstract op)] instrAbstractWithOp genOp = [ EXT <$> genExtInstrAbstract genOp , PUSH <$> genAnnotation <*> genValidType <*> genValue' genOp , IF_NONE <$> genSmallList genOp <*> genSmallList genOp , IF_LEFT <$> genSmallList genOp <*> genSmallList genOp , IF_CONS <$> genSmallList genOp <*> genSmallList genOp , MAP <$> genAnnotation <*> genSmallList genOp , ITER <$> genSmallList genOp , IF <$> genSmallList genOp <*> genSmallList genOp , LOOP <$> genSmallList genOp , LOOP_LEFT <$> genSmallList genOp , LAMBDA <$> genAnnotation <*> genValidType <*> genValidType <*> genSmallList genOp , DIP <$> genSmallList genOp , DIPN <$> Gen.word Range.linearBounded <*> genSmallList genOp , CREATE_CONTRACT <$> genAnnotation <*> genAnnotation <*> genContract' genOp ] instrAbstractWithoutOp :: (MonadGen m, GenBase m ~ Identity) => [m (InstrAbstract op)] instrAbstractWithoutOp = [ DROPN <$> Gen.word Range.linearBounded , pure DROP , DUP <$> genAnnotation , DUPN <$> genAnnotation <*> Gen.word Range.linearBounded , pure SWAP , DIG <$> Gen.word Range.linearBounded , DUG <$> Gen.word Range.linearBounded , SOME <$> genAnnotation <*> genAnnotation , NONE <$> genAnnotation <*> genAnnotation <*> genValidType , UNIT <$> genAnnotation <*> genAnnotation , PAIR <$> genAnnotation <*> genAnnotation <*> genAnnotation <*> genAnnotation , PAIRN <$> genAnnotation <*> Gen.word Range.linearBounded , UNPAIRN <$> Gen.word Range.linearBounded , CAR <$> genAnnotation <*> genAnnotation , CDR <$> genAnnotation <*> genAnnotation , LEFT <$> genAnnotation <*> genAnnotation <*> genAnnotation <*> genAnnotation <*> genValidType , RIGHT <$> genAnnotation <*> genAnnotation <*> genAnnotation <*> genAnnotation <*> genValidType , NIL <$> genAnnotation <*> genAnnotation <*> genValidType , CONS <$> genAnnotation , SIZE <$> genAnnotation , EMPTY_SET <$> genAnnotation <*> genAnnotation <*> genValidType , EMPTY_MAP <$> genAnnotation <*> genAnnotation <*> genValidType <*> genValidType , EMPTY_BIG_MAP <$> genAnnotation <*> genAnnotation <*> genValidType <*> genValidType , MEM <$> genAnnotation , GET <$> genAnnotation , GETN <$> genAnnotation <*> Gen.word Range.linearBounded , UPDATE <$> genAnnotation , EXEC <$> genAnnotation , APPLY <$> genAnnotation , pure FAILWITH , CAST <$> genAnnotation <*> genValidType , RENAME <$> genAnnotation , PACK <$> genAnnotation , UNPACK <$> genAnnotation <*> genAnnotation <*> genValidType , CONCAT <$> genAnnotation , SLICE <$> genAnnotation , ISNAT <$> genAnnotation , ADD <$> genAnnotation , SUB <$> genAnnotation , SUB_MUTEZ <$> genAnnotation , MUL <$> genAnnotation , EDIV <$> genAnnotation , ABS <$> genAnnotation , NEG <$> genAnnotation , LSL <$> genAnnotation , LSR <$> genAnnotation , OR <$> genAnnotation , AND <$> genAnnotation , XOR <$> genAnnotation , NOT <$> genAnnotation , COMPARE <$> genAnnotation , EQ <$> genAnnotation , NEQ <$> genAnnotation , LT <$> genAnnotation , GT <$> genAnnotation , LE <$> genAnnotation , GE <$> genAnnotation , INT <$> genAnnotation , SELF <$> genAnnotation <*> genAnnotation , CONTRACT <$> genAnnotation <*> genAnnotation <*> genValidType , TRANSFER_TOKENS <$> genAnnotation , SET_DELEGATE <$> genAnnotation , IMPLICIT_ACCOUNT <$> genAnnotation , NOW <$> genAnnotation , AMOUNT <$> genAnnotation , BALANCE <$> genAnnotation , CHECK_SIGNATURE <$> genAnnotation , SHA256 <$> genAnnotation , SHA512 <$> genAnnotation , BLAKE2B <$> genAnnotation , SHA3 <$> genAnnotation , KECCAK <$> genAnnotation , HASH_KEY <$> genAnnotation , SOURCE <$> genAnnotation , SENDER <$> genAnnotation , ADDRESS <$> genAnnotation , CHAIN_ID <$> genAnnotation , LEVEL <$> genAnnotation , SELF_ADDRESS <$> genAnnotation ] genContract :: (MonadGen m, GenBase m ~ Identity) => m Contract genContract = genContract' genExpandedOp genContract' :: (MonadGen m, GenBase m ~ Identity) => m op -> m (Contract' op) genContract' genOp = Contract <$> genParameterType True <*> genValidType <*> genSmallList genOp <*> genEntriesOrder <*> Gen.list (Range.exponential 0 2) (genSomeView genOp) genEntriesOrder :: (MonadGen m) => m EntriesOrder genEntriesOrder = Gen.enumBounded genViewName :: (MonadGen m, GenBase m ~ Identity) => m ViewName genViewName = unsafe . mkViewName <$> Gen.text (Range.linear 0 viewNameMaxLength) (Gen.filter isValidViewNameChar Gen.ascii) genSomeView :: (MonadGen m, GenBase m ~ Identity) => m op -> m (View' op) genSomeView genOp = View <$> genViewName <*> genValidType <*> genValidType <*> genSmallList genOp genValue :: (MonadGen m, GenBase m ~ Identity) => m Value genValue = genValue' genExpandedOp genValue' :: MonadGen m => m op -> m (Value' op) genValue' genOp = Gen.recursive Gen.choice -- non-recursive constructors [ ValueInt <$> Gen.integral (Range.linearFrom 0 (fromIntegral $ minBound @Int64) (fromIntegral $ maxBound @Word64)) , ValueString <$> genMText , ValueBytes <$> genInternalByteString , pure ValueUnit , pure ValueTrue , pure ValueFalse , pure ValueNone , pure ValueNil ] -- recursive constructors [ Gen.subterm2 (genValue' genOp) (genValue' genOp) ValuePair , Gen.subterm (genValue' genOp) ValueLeft , Gen.subterm (genValue' genOp) ValueRight , Gen.subterm (genValue' genOp) ValueSome , ValueSeq <$> genSmallNonEmpty (genValue' genOp) , ValueMap <$> genSmallNonEmpty (genElt genOp) , ValueLambda <$> genSmallNonEmpty genOp ] genElt :: MonadGen m => m op -> m (Elt op) genElt genOp = Elt <$> genValue' genOp <*> genValue' genOp genParameterType :: (MonadGen m, GenBase m ~ Identity) => Bool -> m ParameterType genParameterType mustBeValid = ParameterType <$> genType mustBeValid <*> genAnnotation -- | Generate a 'Ty'. Note that 'Ty' may store invalid types by -- construction if you put a non-comparable type to a place where a -- comparable type is expected. The caller may request that generated -- value is guaranteed to be valid or can be invalid. genType :: (MonadGen m, GenBase m ~ Identity) => Bool -> m Ty genType mustBeValid = Ty <$> genT mustBeValid <*> genAnnotation -- | Generate a 'Ty' that is guaranteed to be valid. genValidType :: (MonadGen m, GenBase m ~ Identity) => m Ty genValidType = genType True genComparableType :: (MonadGen m, GenBase m ~ Identity) => m Ty genComparableType = Ty <$> genComparableT <*> genAnnotation genEpName :: (MonadGen m, GenBase m ~ Identity) => m EpName genEpName = Gen.mapMaybe (rightToMaybe . epNameFromRefAnn) genAnnotation genAnnotation :: forall m a. (MonadGen m, GenBase m ~ Identity) => m (Annotation a) genAnnotation = Gen.mapMaybe (rightToMaybe . mkAnnotation) genAnnotationText where genAnnotationText :: m Text genAnnotationText = Gen.frequency [ (1, pure "") , (17, T.cons <$> annStart <*> Gen.text (Range.linear 0 100) annBodyChar) , (1, pure specialFieldAnn) , (1, Gen.element specialVarAnns) ] annStart :: m Char annStart = Gen.choice [ pure '_', Gen.alphaNum ] annBodyChar :: m Char annBodyChar = Gen.choice [ annStart, Gen.element (".%@" :: String) ] -- | Generate a 'T'. Note that 'T' may store invalid types by -- construction if you put a non-comparable type to a place where a -- comparable type is expected. The caller may request that generated -- value is guaranteed to be valid or can be invalid. genT :: (MonadGen m, GenBase m ~ Identity) => Bool -> m T genT mustBeValid = Gen.recursive Gen.choice -- non-recursive constructors [ pure TKey , pure TUnit , pure TSignature , pure TChainId , pure TOperation , pure TInt , pure TNat , pure TString , pure TBytes , pure TMutez , pure TBool , pure TKeyHash , pure TTimestamp , pure TAddress , pure TChest , pure TChestKey ] -- recursive constructors [ TOption <$> genType' , TList <$> genType' , TSet <$> genComparableType , TContract <$> genType' , TPair <$> genAnnotation <*> genAnnotation <*> genAnnotation <*> genAnnotation <*> genType' <*> genType' , TOr <$> genAnnotation <*> genAnnotation <*> genType' <*> genType' , TLambda <$> genType' <*> genType' , TMap <$> genComparableType <*> genType' , TBigMap <$> genComparableType <*> genType' ] where genType' = genType mustBeValid -- We don't need to pass @mustBeValid@ here because comparable types are always valid. genComparableT :: (MonadGen m, GenBase m ~ Identity) => m T genComparableT = Gen.recursive Gen.choice [ pure TInt , pure TNat , pure TString , pure TBytes , pure TMutez , pure TBool , pure TKeyHash , pure TTimestamp , pure TAddress ] [ TPair <$> genAnnotation <*> genAnnotation <*> genAnnotation <*> genAnnotation <*> genComparableType <*> genComparableType ] smallCollectionRange :: Range Int smallCollectionRange = Range.linear 0 3 genSmallList :: MonadGen m => m a -> m [a] genSmallList = Gen.list smallCollectionRange genSmallNonEmpty :: MonadGen m => m a -> m (NonEmpty a) genSmallNonEmpty = Gen.nonEmpty smallCollectionRange genSmallText :: MonadGen m => m Text genSmallText = Gen.text (Range.linear 0 10) Gen.unicodeAll