morley-0.3.0.1: Developer tools for the Michelson Language

Safe HaskellNone
LanguageHaskell2010

Michelson.TypeCheck.Helpers

Synopsis

Documentation

onLeft :: Either a c -> (a -> b) -> Either b c Source #

deriveSpecialVN :: VarAnn -> FieldAnn -> VarAnn -> VarAnn Source #

Function which derives special annotations for CDR / CAR instructions.

deriveSpecialFNs :: FieldAnn -> FieldAnn -> VarAnn -> VarAnn -> (VarAnn, FieldAnn, FieldAnn) Source #

Function which derives special annotations for PAIR instruction.

Namely, it does following transformation: PAIR % % [ p.a int : p.b int : .. ] ~ [ p (pair (int %a) (int %b) : .. ]

All relevant cases (e.g. PAIR %myf % ) are handled as they should be according to spec.

deriveVN :: VarAnn -> VarAnn -> VarAnn Source #

Append suffix to variable annotation (if it's not empty)

deriveNsOr :: Notes (TOr a b) -> VarAnn -> (Notes a, Notes b, VarAnn, VarAnn) Source #

Function which extracts annotations for or type (for left and right parts).

It extracts field/type annotations and also auto-generates variable annotations if variable annotation is not provided as second argument.

deriveNsOption :: Notes (TOption a) -> VarAnn -> (Notes a, VarAnn) Source #

Function which extracts annotations for option t type.

It extracts field/type annotations and also auto-generates variable annotation for Some case if it is not provided as second argument.

convergeHST :: HST ts -> HST ts -> Either AnnConvergeError (HST ts) Source #

Combine annotations from two given stack types

hstToTs :: HST st -> [T] Source #

Extract singleton for each single type of the given stack.

eqHST :: forall as bs. (Typeable as, Typeable bs) => HST as -> HST bs -> Either TCTypeError (as :~: bs) Source #

Check whether the given stack types are equal.

eqHST1 :: forall t st. (Typeable st, Typeable t, SingI t) => HST st -> Either TCTypeError (st :~: '[t]) Source #

Check whether the given stack has size 1 and its only element matches the given type. This function is a specialized version of eqHST.

ensureDistinctAsc :: (Ord b, Show a) => (a -> b) -> [a] -> Either Text [a] Source #

Check whether elements go in strictly ascending order and return the original list (to keep only one pass on the original list).

eqType :: forall (a :: T) (b :: T). Each [Typeable, SingI] [a, b] => Either TCTypeError (a :~: b) Source #

Function eqType is a simple wrapper around Data.Typeable.eqT suited for use within Either TCTypeError a applicative.

checkEqT :: forall (a :: T) (b :: T) ts m. (Each [Typeable, SingI] [a, b], Typeable ts, MonadReader InstrCallStack m, MonadError TCError m) => ExpandedInstr -> HST ts -> Text -> m (a :~: b) Source #

checkEqHST :: forall (a :: [T]) (b :: [T]) ts m. (Typeable a, Typeable b, Typeable ts, MonadReader InstrCallStack m, MonadError TCError m) => HST a -> HST b -> ExpandedInstr -> HST ts -> Text -> m (a :~: b) Source #

compareTypes :: forall t. (Typeable t, SingI t) => (Sing t, Notes t) -> Type -> Either TCTypeError () Source #

Check whether typed and untyped types converge

memImpl :: forall (q :: CT) (c :: T) ts inp m. (MonadReader InstrCallStack m, MonadError TCError m, Typeable ts, Typeable (MemOpKey c), SingI (MemOpKey c), MemOp c, inp ~ (Tc q ': (c ': ts))) => ExpandedInstr -> HST inp -> VarAnn -> m (SomeInstr inp) Source #

Generic implementation for MEMeration

getImpl :: forall c getKey rs inp m. (GetOp c, Typeable (GetOpKey c), Typeable (GetOpVal c), SingI (GetOpVal c), SingI (GetOpKey c), inp ~ (getKey ': (c ': rs)), MonadReader InstrCallStack m, MonadError TCError m) => ExpandedInstr -> HST (getKey ': (c ': rs)) -> Sing (GetOpVal c) -> Notes (GetOpVal c) -> VarAnn -> m (SomeInstr inp) Source #

updImpl :: forall c updKey updParams rs inp m. (UpdOp c, Typeable (UpdOpKey c), SingI (UpdOpKey c), Typeable (UpdOpParams c), SingI (UpdOpParams c), inp ~ (updKey ': (updParams ': (c ': rs))), MonadReader InstrCallStack m, MonadError TCError m) => ExpandedInstr -> HST (updKey ': (updParams ': (c ': rs))) -> m (SomeInstr inp) Source #

sliceImpl :: (SliceOp c, Typeable c, inp ~ (Tc CNat ': (Tc CNat ': (c ': rs))), Monad m) => HST inp -> VarAnn -> m (SomeInstr inp) Source #

concatImpl :: (ConcatOp c, Typeable c, inp ~ (c ': (c ': rs)), MonadReader InstrCallStack m, MonadError TCError m) => HST inp -> VarAnn -> m (SomeInstr inp) Source #

concatImpl' :: (ConcatOp c, Typeable c, inp ~ (TList c ': rs), Monad m) => HST inp -> VarAnn -> m (SomeInstr inp) Source #

sizeImpl :: (SizeOp c, inp ~ (c ': rs), Monad m) => HST inp -> VarAnn -> m (SomeInstr inp) Source #

arithImpl :: (Typeable (ArithRes aop n m), SingI (ArithRes aop n m), Typeable (Tc (ArithRes aop n m) ': s), inp ~ (Tc n ': (Tc m ': s)), Monad t) => Instr inp (Tc (ArithRes aop n m) ': s) -> HST inp -> VarAnn -> t (SomeInstr inp) Source #

Helper function to construct instructions for binary arithmetic operations.

addImpl :: forall a b inp rs m. (Typeable rs, Each [Typeable, SingI] [a, b], inp ~ (Tc a ': (Tc b ': rs)), MonadReader InstrCallStack m, MonadError TCError m) => Sing a -> Sing b -> HST inp -> VarAnn -> m (SomeInstr inp) Source #

subImpl :: forall a b inp rs m. (Typeable rs, Each [Typeable, SingI] [a, b], inp ~ (Tc a ': (Tc b ': rs)), MonadReader InstrCallStack m, MonadError TCError m) => Sing a -> Sing b -> HST inp -> VarAnn -> m (SomeInstr inp) Source #

mulImpl :: forall a b inp rs m. (Typeable rs, Each [Typeable, SingI] [a, b], inp ~ (Tc a ': (Tc b ': rs)), MonadReader InstrCallStack m, MonadError TCError m) => Sing a -> Sing b -> HST inp -> VarAnn -> m (SomeInstr inp) Source #

edivImpl :: forall a b inp rs m. (Typeable rs, Each [Typeable, SingI] [a, b], inp ~ (Tc a ': (Tc b ': rs)), MonadReader InstrCallStack m, MonadError TCError m) => Sing a -> Sing b -> HST inp -> VarAnn -> m (SomeInstr inp) Source #

compareImpl :: forall a b inp rs m. (Typeable rs, Each [Typeable, SingI] [a, b], inp ~ (Tc a ': (Tc b ': rs)), MonadReader InstrCallStack m, MonadError TCError m) => Sing a -> Sing b -> HST inp -> VarAnn -> m (SomeInstr inp) Source #

unaryArithImpl :: (Typeable (UnaryArithRes aop n), SingI (UnaryArithRes aop n), Typeable (Tc (UnaryArithRes aop n) ': s), inp ~ (Tc n ': s), Monad t) => Instr inp (Tc (UnaryArithRes aop n) ': s) -> HST inp -> VarAnn -> t (SomeInstr inp) Source #

Helper function to construct instructions for binary arithmetic operations.