| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Michelson.TypeCheck.TypeCheck
Synopsis
- type TcInstrHandler = forall inp. (Typeable inp, HasCallStack) => ExpandedInstr -> HST inp -> TypeCheckInstr (SomeInstr inp)
- type TcOriginatedContracts = Map ContractHash SomeParamType
- type TcResult inp = Either TCError (SomeInstr inp)
- data TypeCheckEnv = TypeCheckEnv {}
- type TypeCheck = ExceptT TCError (State TypeCheckEnv)
- runTypeCheck :: TypeCheckMode -> TypeCheck a -> Either TCError a
- type TypeCheckInstr = ReaderT InstrCallStack TypeCheck
- runTypeCheckIsolated :: TypeCheck a -> Either TCError a
- runTypeCheckInstrIsolated :: TypeCheckInstr a -> Either TCError a
- mapTCError :: (TCError -> TCError) -> TypeCheckInstr a -> TypeCheckInstr a
- tcExtFramesL :: Lens' TypeCheckEnv TcExtFrames
- tcModeL :: Lens' TypeCheckEnv TypeCheckMode
- data TypeCheckMode
- data SomeParamType = forall t.ParameterScope t => SomeParamType (Sing t) (ParamNotes t)
- mkSomeParamType :: ParameterType -> Either TCError SomeParamType
- mkSomeParamTypeUnsafe :: HasCallStack => ParameterType -> SomeParamType
Documentation
type TcInstrHandler = forall inp. (Typeable inp, HasCallStack) => ExpandedInstr -> HST inp -> TypeCheckInstr (SomeInstr inp) Source #
data TypeCheckEnv Source #
The typechecking state
Constructors
| TypeCheckEnv | |
| Fields 
 | |
runTypeCheck :: TypeCheckMode -> TypeCheck a -> Either TCError a Source #
runTypeCheckIsolated :: TypeCheck a -> Either TCError 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).
runTypeCheckInstrIsolated :: TypeCheckInstr a -> Either TCError a Source #
Similar to runTypeCheckIsolated, but for 'TypeCheckInstr.'
mapTCError :: (TCError -> TCError) -> TypeCheckInstr a -> TypeCheckInstr a Source #
Run TypeCheckInstr and modify thrown errors using given functions.
data TypeCheckMode Source #
Typechecking mode that tells the type checker whether it is typechecking contract code in actual contract, lambda, or test.
Constructors
| TypeCheckValue (Value, T) | |
| TypeCheckContract SomeParamType | |
| TypeCheckTest | |
| TypeCheckPack | 
data SomeParamType Source #
Constructors
| forall t.ParameterScope t => SomeParamType (Sing t) (ParamNotes t) | 
Instances
| Eq SomeParamType Source # | 
 | 
| Defined in Michelson.TypeCheck.TypeCheck Methods (==) :: SomeParamType -> SomeParamType -> Bool # (/=) :: SomeParamType -> SomeParamType -> Bool # | |
| Show SomeParamType Source # | 
 | 
| Defined in Michelson.TypeCheck.TypeCheck Methods showsPrec :: Int -> SomeParamType -> ShowS # show :: SomeParamType -> String # showList :: [SomeParamType] -> ShowS # | |
| Buildable SomeParamType Source # | 
 | 
| Defined in Michelson.TypeCheck.TypeCheck Methods build :: SomeParamType -> Builder # | |
mkSomeParamTypeUnsafe :: HasCallStack => ParameterType -> SomeParamType Source #
Construct SomeParamType from ParameterType, mainly used in test.