morley-1.16.1: Developer tools for the Michelson Language
Safe HaskellNone
LanguageHaskell2010

Morley.Michelson.TypeCheck.TypeCheck

Synopsis

Documentation

data TypeCheckEnv Source #

The typechecking state

data TypeCheckOptions Source #

Constructors

TypeCheckOptions 

Fields

  • tcVerbose :: Bool

    Whether to add stack type comments after every instruction a la tezos-client.

  • tcStrict :: Bool

    Whether should we behave like in test run or real run (real run is more strict).

    tezos-client run's behaviour can slightly differ from the behaviour of tezos-client originate and tezos-client transfer. For instance, some values can be "forged" in test run, but not in a real one, see: Note [Tickets forging].

    Set this to True when need to match the behaviour in the network, and to False if you prefer providing the user with some convenient features.

Instances

Instances details
Default TypeCheckOptions Source # 
Instance details

Defined in Morley.Michelson.TypeCheck.TypeCheck

type TypeCheckNoExcept = ReaderT TypeCheckOptions (State TypeCheckEnv) Source #

A non-throwing alternative for TypeCheck. Mainly meant to be used for construction of a partially typed tree (see TypeCheckedSeq).

type TypeCheckResult = ReaderT TypeCheckOptions (Except TCError) Source #

Monad for performing some typechecking operations with the same options.

Unlike TypeCheck monad, this does not carry the context of intra-contract or intra-value typechecking. TODO [this MR]: probably come up with a better name? IntraTypeCheck?

runTypeCheckIsolated :: TypeCheck a -> TypeCheckResult a Source #

Run type checker as if it worked isolated from other world - no access to environment of the current contract is allowed.

Use this function for test purposes only or for some utilities when environment does not matter. In particular, it is assumed that whatever we typecheck does not depend on the parameter type of the contract which is being typechecked (because there is no contract that we are typechecking).

preserving Source #

Arguments

:: TypeCheckInstrNoExcept (TypeCheckedSeq inp)

Acquiring computation

-> ([TypeCheckedOp] -> TypeCheckedInstr)

The parent instruction constructor

-> (SomeInstr inp -> TypeCheckInstr (SomeInstr inp'))

The throwing action

-> TypeCheckInstrNoExcept (TypeCheckedSeq inp') 

Perform a throwing action on an acquired instruction. Preserve the acquired result by embedding it into a type checking tree with a specified parent instruction.

preserving' Source #

Arguments

:: TypeCheckInstrNoExcept (TypeCheckedSeq inp)

Acquiring computation

-> ([TypeCheckedOp] -> TypeCheckedInstr)

The parent instruction constructor

-> (SomeInstr inp -> TypeCheckInstrNoExcept (TypeCheckedSeq inp'))

The action

-> TypeCheckInstrNoExcept (TypeCheckedSeq inp') 

Perform a non-throwing action on an acquired instruction. Preserve the acquired result even if the action does not succeed. Embed the result into a type checking tree with a specified parent instruction.

guarding Source #

Arguments

:: ExpandedInstr

Untyped instruction

-> TypeCheckInstr a

Acquiring computation

-> (a -> TypeCheckInstrNoExcept (TypeCheckedSeq inp))

Follow-up action

-> TypeCheckInstrNoExcept (TypeCheckedSeq inp) 

Acquire a resource. If successfully, call a follow-up action on it, otherwise embed the error into a type checking tree along with a specified untyped instruction.

guarding_ :: ExpandedInstr -> TypeCheckInstr a -> TypeCheckInstrNoExcept (TypeCheckedSeq inp) -> TypeCheckInstrNoExcept (TypeCheckedSeq inp) Source #

Same as guarding but doesn't pass an acquired result to a follow-up action.

tcEither Source #

Arguments

:: (TCError -> TypeCheckInstrNoExcept a)

Call this if the action throws

-> (b -> TypeCheckInstrNoExcept a)

Call this if it doesn't

-> TypeCheckInstr b

The action to perform

-> TypeCheckInstrNoExcept a

A non-throwing action

data TypeCheckMode Source #

Typechecking mode that tells the type checker whether it is typechecking contract code in actual contract, lambda, or test.

data SomeParamType Source #

Constructors

forall t.ParameterScope t => SomeParamType (Sing t) (ParamNotes t) 

Instances

Instances details
Eq SomeParamType Source #

Eq instance of SomeParamType, mainly used in test.

Instance details

Defined in Morley.Michelson.TypeCheck.TypeCheck

Show SomeParamType Source #

Show instance of SomeParamType, mainly used in test.

Instance details

Defined in Morley.Michelson.TypeCheck.TypeCheck

Buildable SomeParamType Source #

Buildable instance of SomeParamType, mainly used in test.

Instance details

Defined in Morley.Michelson.TypeCheck.TypeCheck

unsafeMkSomeParamType :: HasCallStack => ParameterType -> SomeParamType Source #

Construct SomeParamType from ParameterType, mainly used in test.