cleveland-0.3.0: Testing framework for Morley.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Hedgehog.Gen.Michelson.Typed

Synopsis

Documentation

genBigMap :: forall k v m. (MonadGen m, Ord k, WellTypedToT k, WellTypedToT v, Comparable (ToT k)) => Range Length -> m k -> m v -> m (BigMap k v) Source #

genEpAddress :: (MonadGen m, GenBase m ~ Identity) => m EpAddress Source #

genValueBigMap :: forall (k :: T) (v :: T) m instr. (MonadGen m, WellTyped k, WellTyped v, HasNoBigMap v, Comparable k) => Range Length -> m (Value' instr k) -> m (Value' instr v) -> m (Value' instr ('TBigMap k v)) Source #

genValueChestAndKey :: MonadGen m => m (Value' instr 'TChest, Value' instr 'TChestKey) Source #

genValueInt :: MonadGen m => Range (Value' instr 'TInt) -> m (Value' instr 'TInt) Source #

genValueKeyHash :: MonadGen m => m (Value' instr 'TKeyHash) Source #

genValueList :: (MonadGen m, SingI a) => Range Length -> m (Value' instr a) -> m (Value' instr ('TList a)) Source #

genValueMap :: forall (k :: T) (v :: T) m instr. (MonadGen m, WellTyped k, WellTyped v, Comparable k) => Range Length -> m (Value' instr k) -> m (Value' instr v) -> m (Value' instr ('TMap k v)) Source #

genValueMutez :: MonadGen m => Range Mutez -> m (Value' instr 'TMutez) Source #

genValueNat :: MonadGen m => Range (Value' instr 'TNat) -> m (Value' instr 'TNat) Source #

genValuePair :: MonadGen m => m (Value' instr a) -> m (Value' instr b) -> m (Value' instr ('TPair a b)) Source #

genValueSet :: (MonadGen m, Comparable a, SingI a) => Range Length -> m (Value' instr a) -> m (Value' instr ('TSet a)) Source #

genValueString :: MonadGen f => Range Length -> f (Value' instr 'TString) Source #

genValueTimestamp :: MonadGen m => Range Timestamp -> m (Value' instr 'TTimestamp) Source #

genValueUnit :: Applicative m => m (Value' instr 'TUnit) Source #

genValue :: forall t m. (MonadGen m, GenBase m ~ Identity, HasNoOp t, WellTyped t) => m (Value' Instr t) Source #

genValue' :: (MonadGen m, GenBase m ~ Identity, HasNoOp t, WellTyped t) => Sing t -> m (Value' Instr t) Source #

genSimpleInstr :: (MonadGen m, inp ~ (x ': xs), SingI x) => m (Instr inp inp) Source #

Generate a simple instruction. Ideally instruction generator should produce instructions containing all possible primitive instructions. In our case we consider only a few primitive instructions and pick one from a hardcoded list. Hence we call it "simple". Another limitation is that input stack and output stack types must be identical and non-empty.