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

Morley.Michelson.Typed.Convert

Synopsis

Documentation

convertParamNotes :: ParamNotes cp -> ParameterType Source #

Convert typed parameter annotations to an untyped ParameterType.

convertView :: forall arg store ret. View arg store ret -> View Source #

convertContractCode :: forall param store. (SingI param, SingI store) => ContractCode param store -> Contract Source #

Convert typed ContractCode to an untyped Contract.

convertContract :: Contract param store -> Contract Source #

Convert typed Contract to an untyped Contract.

instrToOps :: HasCallStack => Instr inp out -> [ExpandedOp] Source #

Convert Haskell-typed Instr to a list of human-readable untyped operations

instrToOpsOptimized :: HasCallStack => Instr inp out -> [ExpandedOp] Source #

Convert Haskell-typed Instr to a list of optimized untyped operations

untypeDemoteT :: forall (t :: T). SingI t => Ty Source #

Convert a Haskell type-level type tag into an untyped value representation.

This function is intended to be used with TypeApplications.

untypeValue :: HasNoOp t => Value' Instr t -> Value Source #

Convert a typed value to an untyped human-readable representation

untypeValueHashable :: HasNoOp t => Value' Instr t -> Value Source #

Like untypeValueOptimized, but without list notation for pairs.

Created to match tezos-client hash data behaviour for typed values.

untypeValueOptimized :: HasNoOp t => Value' Instr t -> Value Source #

Convert a typed value to an untyped optimized representation

sampleTypedValue :: forall t. Sing t -> Maybe (Value t) Source #

Generate a value used for generating examples in documentation.

Since not for all types it is possible to produce a sensible example, the result is optional. E.g. for operations, never, not proper types like contract operation we return Nothing.

Misc

flattenEntrypoints :: ParamNotes t -> Map EpName Ty Source #

Flatten a provided list of notes to a map of its entrypoints and its corresponding utype. Please refer to mkEntrypointsMap in regards to how duplicate entrypoints are handled.

eqInstrExt :: Instr i1 o1 -> Instr i2 o2 -> Bool Source #

Extended equality of Instr - this behaves like (==) but does not require the compared instructions to be of strictly the same type.

Orphan instances

SingI s => Eq (TestAssert s) Source # 
Instance details

Methods

(==) :: TestAssert s -> TestAssert s -> Bool #

(/=) :: TestAssert s -> TestAssert s -> Bool #

Buildable (Instr inp out) Source # 
Instance details

Methods

build :: Instr inp out -> Builder #

Buildable (Value' Instr t) Source # 
Instance details

Methods

build :: Value' Instr t -> Builder #

Eq (Instr inp out) Source # 
Instance details

Methods

(==) :: Instr inp out -> Instr inp out -> Bool #

(/=) :: Instr inp out -> Instr inp out -> Bool #

RenderDoc (Instr inp out) Source # 
Instance details

Methods

renderDoc :: RenderContext -> Instr inp out -> Doc Source #

isRenderable :: Instr inp out -> Bool Source #

HasNoOp t => RenderDoc (Value' Instr t) Source # 
Instance details