morley-1.18.0: Developer tools for the Michelson Language
Safe HaskellSafe-Inferred
LanguageHaskell2010

Morley.Michelson.Typed.Polymorphic

Description

Module, containing type classes for operating with Michelson values in the context of polymorphic stack type operations.

Synopsis

Documentation

class EDivOp (n :: T) (m :: T) where Source #

Associated Types

type EDivOpRes n m :: T Source #

type EModOpRes n m :: T Source #

Methods

evalEDivOp :: Value' instr n -> Value' instr m -> Value' instr ('TOption ('TPair (EDivOpRes n m) (EModOpRes n m))) Source #

Instances

Instances details
EDivOp 'TInt 'TInt Source # 
Instance details

Defined in Morley.Michelson.Typed.Polymorphic

Associated Types

type EDivOpRes 'TInt 'TInt :: T Source #

type EModOpRes 'TInt 'TInt :: T Source #

Methods

evalEDivOp :: forall (instr :: [T] -> [T] -> Type). Value' instr 'TInt -> Value' instr 'TInt -> Value' instr ('TOption ('TPair (EDivOpRes 'TInt 'TInt) (EModOpRes 'TInt 'TInt))) Source #

EDivOp 'TInt 'TNat Source # 
Instance details

Defined in Morley.Michelson.Typed.Polymorphic

Associated Types

type EDivOpRes 'TInt 'TNat :: T Source #

type EModOpRes 'TInt 'TNat :: T Source #

Methods

evalEDivOp :: forall (instr :: [T] -> [T] -> Type). Value' instr 'TInt -> Value' instr 'TNat -> Value' instr ('TOption ('TPair (EDivOpRes 'TInt 'TNat) (EModOpRes 'TInt 'TNat))) Source #

EDivOp 'TMutez 'TMutez Source # 
Instance details

Defined in Morley.Michelson.Typed.Polymorphic

Associated Types

type EDivOpRes 'TMutez 'TMutez :: T Source #

type EModOpRes 'TMutez 'TMutez :: T Source #

Methods

evalEDivOp :: forall (instr :: [T] -> [T] -> Type). Value' instr 'TMutez -> Value' instr 'TMutez -> Value' instr ('TOption ('TPair (EDivOpRes 'TMutez 'TMutez) (EModOpRes 'TMutez 'TMutez))) Source #

EDivOp 'TMutez 'TNat Source # 
Instance details

Defined in Morley.Michelson.Typed.Polymorphic

Associated Types

type EDivOpRes 'TMutez 'TNat :: T Source #

type EModOpRes 'TMutez 'TNat :: T Source #

Methods

evalEDivOp :: forall (instr :: [T] -> [T] -> Type). Value' instr 'TMutez -> Value' instr 'TNat -> Value' instr ('TOption ('TPair (EDivOpRes 'TMutez 'TNat) (EModOpRes 'TMutez 'TNat))) Source #

EDivOp 'TNat 'TInt Source # 
Instance details

Defined in Morley.Michelson.Typed.Polymorphic

Associated Types

type EDivOpRes 'TNat 'TInt :: T Source #

type EModOpRes 'TNat 'TInt :: T Source #

Methods

evalEDivOp :: forall (instr :: [T] -> [T] -> Type). Value' instr 'TNat -> Value' instr 'TInt -> Value' instr ('TOption ('TPair (EDivOpRes 'TNat 'TInt) (EModOpRes 'TNat 'TInt))) Source #

EDivOp 'TNat 'TNat Source # 
Instance details

Defined in Morley.Michelson.Typed.Polymorphic

Associated Types

type EDivOpRes 'TNat 'TNat :: T Source #

type EModOpRes 'TNat 'TNat :: T Source #

Methods

evalEDivOp :: forall (instr :: [T] -> [T] -> Type). Value' instr 'TNat -> Value' instr 'TNat -> Value' instr ('TOption ('TPair (EDivOpRes 'TNat 'TNat) (EModOpRes 'TNat 'TNat))) Source #

class MemOp (c :: T) where Source #

Associated Types

type MemOpKey c :: T Source #

Methods

evalMem :: Value' instr (MemOpKey c) -> Value' instr c -> Bool Source #

Instances

Instances details
MemOp ('TSet e) Source # 
Instance details

Defined in Morley.Michelson.Typed.Polymorphic

Associated Types

type MemOpKey ('TSet e) :: T Source #

Methods

evalMem :: forall (instr :: [T] -> [T] -> Type). Value' instr (MemOpKey ('TSet e)) -> Value' instr ('TSet e) -> Bool Source #

MemOp ('TBigMap k v) Source # 
Instance details

Defined in Morley.Michelson.Typed.Polymorphic

Associated Types

type MemOpKey ('TBigMap k v) :: T Source #

Methods

evalMem :: forall (instr :: [T] -> [T] -> Type). Value' instr (MemOpKey ('TBigMap k v)) -> Value' instr ('TBigMap k v) -> Bool Source #

MemOp ('TMap k v) Source # 
Instance details

Defined in Morley.Michelson.Typed.Polymorphic

Associated Types

type MemOpKey ('TMap k v) :: T Source #

Methods

evalMem :: forall (instr :: [T] -> [T] -> Type). Value' instr (MemOpKey ('TMap k v)) -> Value' instr ('TMap k v) -> Bool Source #

class MapOp (c :: T) where Source #

Associated Types

type MapOpInp c :: T Source #

type MapOpRes c :: T -> T Source #

Methods

mapOpToList :: Value' instr c -> [Value' instr (MapOpInp c)] Source #

mapOpFromList :: SingI b => Value' instr c -> [Value' instr b] -> Value' instr (MapOpRes c b) Source #

mapOpNotes :: Notes c -> Notes (MapOpInp c) Source #

Instances

Instances details
MapOp ('TList e) Source # 
Instance details

Defined in Morley.Michelson.Typed.Polymorphic

Associated Types

type MapOpInp ('TList e) :: T Source #

type MapOpRes ('TList e) :: T -> T Source #

Methods

mapOpToList :: forall (instr :: [T] -> [T] -> Type). Value' instr ('TList e) -> [Value' instr (MapOpInp ('TList e))] Source #

mapOpFromList :: forall (b :: T) (instr :: [T] -> [T] -> Type). SingI b => Value' instr ('TList e) -> [Value' instr b] -> Value' instr (MapOpRes ('TList e) b) Source #

mapOpNotes :: Notes ('TList e) -> Notes (MapOpInp ('TList e)) Source #

MapOp ('TOption e) Source # 
Instance details

Defined in Morley.Michelson.Typed.Polymorphic

Associated Types

type MapOpInp ('TOption e) :: T Source #

type MapOpRes ('TOption e) :: T -> T Source #

Methods

mapOpToList :: forall (instr :: [T] -> [T] -> Type). Value' instr ('TOption e) -> [Value' instr (MapOpInp ('TOption e))] Source #

mapOpFromList :: forall (b :: T) (instr :: [T] -> [T] -> Type). SingI b => Value' instr ('TOption e) -> [Value' instr b] -> Value' instr (MapOpRes ('TOption e) b) Source #

mapOpNotes :: Notes ('TOption e) -> Notes (MapOpInp ('TOption e)) Source #

MapOp ('TMap k v) Source # 
Instance details

Defined in Morley.Michelson.Typed.Polymorphic

Associated Types

type MapOpInp ('TMap k v) :: T Source #

type MapOpRes ('TMap k v) :: T -> T Source #

Methods

mapOpToList :: forall (instr :: [T] -> [T] -> Type). Value' instr ('TMap k v) -> [Value' instr (MapOpInp ('TMap k v))] Source #

mapOpFromList :: forall (b :: T) (instr :: [T] -> [T] -> Type). SingI b => Value' instr ('TMap k v) -> [Value' instr b] -> Value' instr (MapOpRes ('TMap k v) b) Source #

mapOpNotes :: Notes ('TMap k v) -> Notes (MapOpInp ('TMap k v)) Source #

class IterOp (c :: T) where Source #

Associated Types

type IterOpEl c :: T Source #

Methods

iterOpDetachOne :: Value' instr c -> (Maybe (Value' instr (IterOpEl c)), Value' instr c) Source #

iterOpNotes :: Notes c -> Notes (IterOpEl c) Source #

Instances

Instances details
IterOp ('TList e) Source # 
Instance details

Defined in Morley.Michelson.Typed.Polymorphic

Associated Types

type IterOpEl ('TList e) :: T Source #

Methods

iterOpDetachOne :: forall (instr :: [T] -> [T] -> Type). Value' instr ('TList e) -> (Maybe (Value' instr (IterOpEl ('TList e))), Value' instr ('TList e)) Source #

iterOpNotes :: Notes ('TList e) -> Notes (IterOpEl ('TList e)) Source #

IterOp ('TSet e) Source # 
Instance details

Defined in Morley.Michelson.Typed.Polymorphic

Associated Types

type IterOpEl ('TSet e) :: T Source #

Methods

iterOpDetachOne :: forall (instr :: [T] -> [T] -> Type). Value' instr ('TSet e) -> (Maybe (Value' instr (IterOpEl ('TSet e))), Value' instr ('TSet e)) Source #

iterOpNotes :: Notes ('TSet e) -> Notes (IterOpEl ('TSet e)) Source #

IterOp ('TMap k v) Source # 
Instance details

Defined in Morley.Michelson.Typed.Polymorphic

Associated Types

type IterOpEl ('TMap k v) :: T Source #

Methods

iterOpDetachOne :: forall (instr :: [T] -> [T] -> Type). Value' instr ('TMap k v) -> (Maybe (Value' instr (IterOpEl ('TMap k v))), Value' instr ('TMap k v)) Source #

iterOpNotes :: Notes ('TMap k v) -> Notes (IterOpEl ('TMap k v)) Source #

class SizeOp (c :: T) where Source #

Methods

evalSize :: Value' instr c -> Int Source #

Instances

Instances details
SizeOp 'TBytes Source # 
Instance details

Defined in Morley.Michelson.Typed.Polymorphic

Methods

evalSize :: forall (instr :: [T] -> [T] -> Type). Value' instr 'TBytes -> Int Source #

SizeOp 'TString Source # 
Instance details

Defined in Morley.Michelson.Typed.Polymorphic

Methods

evalSize :: forall (instr :: [T] -> [T] -> Type). Value' instr 'TString -> Int Source #

SizeOp ('TList a) Source # 
Instance details

Defined in Morley.Michelson.Typed.Polymorphic

Methods

evalSize :: forall (instr :: [T] -> [T] -> Type). Value' instr ('TList a) -> Int Source #

SizeOp ('TSet a) Source # 
Instance details

Defined in Morley.Michelson.Typed.Polymorphic

Methods

evalSize :: forall (instr :: [T] -> [T] -> Type). Value' instr ('TSet a) -> Int Source #

SizeOp ('TMap k v) Source # 
Instance details

Defined in Morley.Michelson.Typed.Polymorphic

Methods

evalSize :: forall (instr :: [T] -> [T] -> Type). Value' instr ('TMap k v) -> Int Source #

class GetOp (c :: T) where Source #

Associated Types

type GetOpKey c :: T Source #

type GetOpVal c :: T Source #

Methods

evalGet :: Value' instr (GetOpKey c) -> Value' instr c -> Maybe (Value' instr (GetOpVal c)) Source #

Instances

Instances details
GetOp ('TBigMap k v) Source # 
Instance details

Defined in Morley.Michelson.Typed.Polymorphic

Associated Types

type GetOpKey ('TBigMap k v) :: T Source #

type GetOpVal ('TBigMap k v) :: T Source #

Methods

evalGet :: forall (instr :: [T] -> [T] -> Type). Value' instr (GetOpKey ('TBigMap k v)) -> Value' instr ('TBigMap k v) -> Maybe (Value' instr (GetOpVal ('TBigMap k v))) Source #

GetOp ('TMap k v) Source # 
Instance details

Defined in Morley.Michelson.Typed.Polymorphic

Associated Types

type GetOpKey ('TMap k v) :: T Source #

type GetOpVal ('TMap k v) :: T Source #

Methods

evalGet :: forall (instr :: [T] -> [T] -> Type). Value' instr (GetOpKey ('TMap k v)) -> Value' instr ('TMap k v) -> Maybe (Value' instr (GetOpVal ('TMap k v))) Source #

class UpdOp (c :: T) where Source #

Associated Types

type UpdOpKey c :: T Source #

type UpdOpParams c :: T Source #

Methods

evalUpd :: Value' instr (UpdOpKey c) -> Value' instr (UpdOpParams c) -> Value' instr c -> Value' instr c Source #

Instances

Instances details
UpdOp ('TSet a) Source # 
Instance details

Defined in Morley.Michelson.Typed.Polymorphic

Associated Types

type UpdOpKey ('TSet a) :: T Source #

type UpdOpParams ('TSet a) :: T Source #

Methods

evalUpd :: forall (instr :: [T] -> [T] -> Type). Value' instr (UpdOpKey ('TSet a)) -> Value' instr (UpdOpParams ('TSet a)) -> Value' instr ('TSet a) -> Value' instr ('TSet a) Source #

UpdOp ('TBigMap k v) Source # 
Instance details

Defined in Morley.Michelson.Typed.Polymorphic

Associated Types

type UpdOpKey ('TBigMap k v) :: T Source #

type UpdOpParams ('TBigMap k v) :: T Source #

Methods

evalUpd :: forall (instr :: [T] -> [T] -> Type). Value' instr (UpdOpKey ('TBigMap k v)) -> Value' instr (UpdOpParams ('TBigMap k v)) -> Value' instr ('TBigMap k v) -> Value' instr ('TBigMap k v) Source #

UpdOp ('TMap k v) Source # 
Instance details

Defined in Morley.Michelson.Typed.Polymorphic

Associated Types

type UpdOpKey ('TMap k v) :: T Source #

type UpdOpParams ('TMap k v) :: T Source #

Methods

evalUpd :: forall (instr :: [T] -> [T] -> Type). Value' instr (UpdOpKey ('TMap k v)) -> Value' instr (UpdOpParams ('TMap k v)) -> Value' instr ('TMap k v) -> Value' instr ('TMap k v) Source #

class SliceOp (c :: T) where Source #

Methods

evalSlice :: Natural -> Natural -> Value' instr c -> Maybe (Value' instr c) Source #

Instances

Instances details
SliceOp 'TBytes Source # 
Instance details

Defined in Morley.Michelson.Typed.Polymorphic

Methods

evalSlice :: forall (instr :: [T] -> [T] -> Type). Natural -> Natural -> Value' instr 'TBytes -> Maybe (Value' instr 'TBytes) Source #

SliceOp 'TString Source # 
Instance details

Defined in Morley.Michelson.Typed.Polymorphic

Methods

evalSlice :: forall (instr :: [T] -> [T] -> Type). Natural -> Natural -> Value' instr 'TString -> Maybe (Value' instr 'TString) Source #

class ConcatOp (c :: T) where Source #

Methods

evalConcat :: Value' instr c -> Value' instr c -> Value' instr c Source #

evalConcat' :: [Value' instr c] -> Value' instr c Source #

Instances

Instances details
ConcatOp 'TBytes Source # 
Instance details

Defined in Morley.Michelson.Typed.Polymorphic

Methods

evalConcat :: forall (instr :: [T] -> [T] -> Type). Value' instr 'TBytes -> Value' instr 'TBytes -> Value' instr 'TBytes Source #

evalConcat' :: forall (instr :: [T] -> [T] -> Type). [Value' instr 'TBytes] -> Value' instr 'TBytes Source #

ConcatOp 'TString Source # 
Instance details

Defined in Morley.Michelson.Typed.Polymorphic

Methods

evalConcat :: forall (instr :: [T] -> [T] -> Type). Value' instr 'TString -> Value' instr 'TString -> Value' instr 'TString Source #

evalConcat' :: forall (instr :: [T] -> [T] -> Type). [Value' instr 'TString] -> Value' instr 'TString Source #

divMich :: Integral a => a -> a -> a Source #

Computing div function in Michelson style. When divisor is negative, Haskell gives x as integer part, while Michelson gives x+1.

modMich :: Integral a => a -> a -> a Source #

Computing mod function in Michelson style. When divisor is negative, Haskell gives a negative modulo, while there is a positive modulo in Michelson.