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

Morley.Michelson.Printer

Synopsis

Documentation

class RenderDoc a where Source #

Generalize converting a type into a Text.PrettyPrint.Leijen.Text.Doc. Used to pretty print Michelson code and define Fmt.Buildable instances.

Minimal complete definition

renderDoc

Methods

renderDoc :: RenderContext -> a -> Doc Source #

isRenderable :: a -> Bool Source #

Whether a value can be represented in Michelson code. Normally either all values of some type are renderable or not renderable. However, in case of instructions we have extra instructions which should not be rendered. Note: it's not sufficient to just return mempty for such instructions, because sometimes we want to print lists of instructions and we need to ignore them complete (to avoid putting redundant separators).

Instances

Instances details
RenderDoc AnnotationSet Source # 
Instance details

Defined in Morley.Michelson.Untyped.Annotation

RenderDoc InstrCallStack Source # 
Instance details

Defined in Morley.Michelson.ErrorPos

RenderDoc CryptoParseError Source # 
Instance details

Defined in Morley.Tezos.Crypto.Util

RenderDoc T Source # 
Instance details

Defined in Morley.Michelson.Untyped.Type

RenderDoc ParameterType Source # 
Instance details

Defined in Morley.Michelson.Untyped.Type

RenderDoc Ty Source # 
Instance details

Defined in Morley.Michelson.Untyped.Type

RenderDoc T Source # 
Instance details

Defined in Morley.Michelson.Typed.T

RenderDoc BadTypeForScope Source # 
Instance details

Defined in Morley.Michelson.Typed.Scope

RenderDoc EpNameFromRefAnnError Source # 
Instance details

Defined in Morley.Michelson.Untyped.Entrypoints

RenderDoc DeserializationError Source # 
Instance details

Defined in Morley.Tezos.Crypto.BLS12381

RenderDoc ParseContractAddressError Source # 
Instance details

Defined in Morley.Tezos.Address

RenderDoc ParseAddressRawError Source # 
Instance details

Defined in Morley.Tezos.Address

RenderDoc ParseAddressError Source # 
Instance details

Defined in Morley.Tezos.Address

RenderDoc ViewName Source # 
Instance details

Defined in Morley.Michelson.Untyped.View

RenderDoc ExpandedOp Source # 
Instance details

Defined in Morley.Michelson.Untyped.Instr

RenderDoc ParamEpError Source # 
Instance details

Defined in Morley.Michelson.Typed.Entrypoints

RenderDoc ArmCoord Source # 
Instance details

Defined in Morley.Michelson.Typed.Entrypoints

RenderDoc ParseEpAddressError Source # 
Instance details

Defined in Morley.Michelson.Typed.Entrypoints

RenderDoc TypeCheckedOp Source # 
Instance details

Defined in Morley.Michelson.TypeCheck.TypeCheckedOp

RenderDoc TCError Source # 
Instance details

Defined in Morley.Michelson.TypeCheck.Error

RenderDoc TCTypeError Source # 
Instance details

Defined in Morley.Michelson.TypeCheck.Error

RenderDoc TopLevelType Source # 
Instance details

Defined in Morley.Michelson.TypeCheck.Error

RenderDoc TypeContext Source # 
Instance details

Defined in Morley.Michelson.TypeCheck.Error

RenderDoc ParsedOp Source # 
Instance details

Defined in Morley.Michelson.Macro

RenderDoc (Prettier ParameterType) Source # 
Instance details

Defined in Morley.Michelson.Untyped.Type

RenderDoc (Prettier Ty) Source # 
Instance details

Defined in Morley.Michelson.Untyped.Type

RenderDoc (Prettier T) Source # 
Instance details

Defined in Morley.Michelson.Typed.T

RenderDoc (MismatchError [T]) Source # 
Instance details

Defined in Morley.Michelson.Typed.T

RenderDoc a => RenderDoc (MismatchError a) Source # 
Instance details

Defined in Morley.Util.MismatchError

RenderDoc (MismatchError Ty) Source # 
Instance details

Defined in Morley.Michelson.Untyped.Type

RenderDoc (MismatchError T) Source # 
Instance details

Defined in Morley.Michelson.Typed.T

RenderDoc op => RenderDoc (ExtInstrAbstract op) Source # 
Instance details

Defined in Morley.Michelson.Untyped.Ext

RenderDoc (PeanoNatural n) Source # 
Instance details

Defined in Morley.Util.PeanoNatural

RenderDoc op => RenderDoc (Contract' op) Source # 
Instance details

Defined in Morley.Michelson.Untyped.Contract

RenderDoc op => RenderDoc (Elt op) Source # 
Instance details

Defined in Morley.Michelson.Untyped.Value

RenderDoc op => RenderDoc (Value' op) Source # 
Instance details

Defined in Morley.Michelson.Untyped.Value

RenderDoc op => RenderDoc (InstrAbstract op) Source # 
Instance details

Defined in Morley.Michelson.Untyped.Instr

RenderDoc (Notes t) Source # 
Instance details

Defined in Morley.Michelson.Typed.Annotation

(forall (t :: T). cs t => HasNoOp t) => RenderDoc (SomeConstrainedValue cs) Source # 
Instance details

Defined in Morley.Michelson.Typed.Existential

RenderDoc (HST ts) Source # 
Instance details

Defined in Morley.Michelson.TypeCheck.Types

KnownAnnTag tag => RenderDoc (Annotation tag) Source # 
Instance details

Defined in Morley.Michelson.Untyped.Annotation

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

Defined in Morley.Michelson.Typed.Convert

RenderDoc (Instr inp out) Source # 
Instance details

Defined in Morley.Michelson.Typed.Convert

Methods

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

isRenderable :: Instr inp out -> Bool Source #

printDoc :: Bool -> Doc -> Text Source #

Convert Doc to Text with a line width of 80.

printUntypedContract :: RenderDoc op => Bool -> Contract' op -> Text Source #

Convert an untyped contract into a textual representation which will be accepted by the OCaml reference client: tezos-client.

printTypedContractCode :: (SingI p, SingI s) => Bool -> ContractCode p s -> Text Source #

Convert a typed contract into a textual representation which will be accepted by the OCaml reference client: tezos-client.

printTypedContract :: Bool -> Contract p s -> Text Source #

Convert typed contract into a textual representation which will be accepted by the OCaml reference client: tezos-client.

printSomeContract :: Bool -> SomeContract -> Text Source #

Convert SomeContract into a textual representation which will be accepted by the OCaml reference client: tezos-client.

printTypedValue :: forall t. ProperUntypedValBetterErrors t => Bool -> Value t -> Text Source #

Convert typed value into a textual representation which will be accepted by the OCaml reference client: tezos-client.

printUntypedValue :: RenderDoc op => Bool -> Value' op -> Text Source #

Convert untyped value into a textual representation which will be accepted by the OCaml reference client: tezos-client.