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

Morley.Michelson.Printer.Util

Description

Utilities for rendering Michelson code in a format compatible with Octez software (e.g octez-client)

Synopsis

Documentation

class RenderDoc a where Source #

Generalize converting a type into a Doc. Used to pretty print Michelson code and define 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 ViewName Source # 
Instance details

Defined in Morley.Michelson.Internal.ViewName

RenderDoc ParsedOp Source # 
Instance details

Defined in Morley.Michelson.Macro

RenderDoc T Source # 
Instance details

Defined in Morley.Michelson.Typed.T

RenderDoc AnnotationSet Source # 
Instance details

Defined in Morley.Michelson.Untyped.Annotation

RenderDoc AnyAnn Source # 
Instance details

Defined in Morley.Michelson.Untyped.Annotation

RenderDoc ExpandedOp Source # 
Instance details

Defined in Morley.Michelson.Untyped.Instr

RenderDoc ParameterType Source # 
Instance details

Defined in Morley.Michelson.Untyped.Type

RenderDoc T Source # 
Instance details

Defined in Morley.Michelson.Untyped.Type

RenderDoc Ty Source # 
Instance details

Defined in Morley.Michelson.Untyped.Type

RenderDoc Doc Source # 
Instance details

Defined in Morley.Michelson.Printer.Util

Methods

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

isRenderable :: Doc -> Bool Source #

RenderDoc Text Source # 
Instance details

Defined in Morley.Michelson.Printer.Util

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

Defined in Morley.Michelson.Printer.Util

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

Defined in Morley.Michelson.TypeCheck.Error

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

Defined in Morley.Michelson.TypeCheck.TypeCheckedOp

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

Defined in Morley.Michelson.TypeCheck.TypeCheckedOp

RenderDoc (Notes t) Source # 
Instance details

Defined in Morley.Michelson.Typed.Annotation

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

Defined in Morley.Michelson.Typed.Existential

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

Defined in Morley.Michelson.Untyped.Contract

RenderDoc (PeanoNatural n) Source # 
Instance details

Defined in Morley.Util.PeanoNatural

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 #

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

Defined in Morley.Michelson.Typed.Convert

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

Defined in Morley.Michelson.Untyped.Annotation

RenderDoc (ExtInstrAbstract f op) Source # 
Instance details

Defined in Morley.Michelson.Untyped.Ext

(RenderDoc op, Foldable f) => RenderDoc (InstrAbstract f op) Source # 
Instance details

Defined in Morley.Michelson.Untyped.Instr

(Foldable f, RenderDoc op) => RenderDoc (Elt f op) Source # 
Instance details

Defined in Morley.Michelson.Untyped.Value

Methods

renderDoc :: RenderContext -> Elt f op -> Doc Source #

isRenderable :: Elt f op -> Bool Source #

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

Defined in Morley.Michelson.Untyped.Value

Methods

renderDoc :: RenderContext -> Value' f op -> Doc Source #

isRenderable :: Value' f op -> Bool Source #

newtype Prettier a Source #

Deprecated: This has no actual effect nowadays

A new type that can wrap values so that the RenderDoc instances of the combined value can have a different behavior for the pretty printer.

Constructors

Prettier a

Deprecated: This has no actual effect nowadays

Instances

Instances details
Functor Prettier Source # 
Instance details

Defined in Morley.Michelson.Printer.Util

Methods

fmap :: (a -> b) -> Prettier a -> Prettier b #

(<$) :: a -> Prettier b -> Prettier a #

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

Defined in Morley.Michelson.Printer.Util

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

Deprecated: Use printRenderDoc instead

Convert Doc to LText with a line width of 80.

printDocB :: Bool -> Doc -> Builder Source #

Deprecated: Use printRenderDoc instead

Convert Doc to Builder in the same manner as printDoc.

printDocS :: Bool -> Doc -> String Source #

Deprecated: Use printRenderDoc instead

Convert Doc to String in the same manner as printDoc.

printRenderDoc :: (RenderDoc a, FromSimpleDoc b) => Bool -> a -> b Source #

Convert anything renderable to some text format with line width of 80.

renderOps :: RenderDoc op => Bool -> NonEmpty op -> Doc Source #

Deprecated: Use renderOpsList instead

Generic way to render the different op types that get passed to a contract.

renderOpsList :: (RenderDoc op, Foldable f) => Bool -> f op -> Doc Source #

Render a comma-separated list of items in braces

renderOpsListNoBraces :: (RenderDoc op, Foldable f) => Bool -> f op -> Doc Source #

Render a semi-colon-separated list of items without braces

renderAnyBuildable :: Buildable a => a -> Doc Source #

Deprecated: Use build instead

wrapInParens :: RenderContext -> NonEmpty Doc -> Doc Source #

Wrap documents in parentheses if there are two or more in the list.

buildRenderDoc :: RenderDoc a => a -> Doc Source #

Deprecated: RenderDoc already implies Buildable, use build if you can

renderDoc, then group and align. Generally, this is the same as build.

buildRenderDocExtended :: RenderDoc a => a -> Doc Source #

Deprecated: RenderDoc already implies Buildable, use build if you can

Works as buildRenderDoc above, but doesn't group.

renderDocList :: RenderDoc a => RenderContext -> [a] -> Doc Source #

Renders a list of RenderDoc elements surrounded with square brackets, separated by a comma and a space.

Smart parentheses

data RenderContext Source #

Environment carried during recursive rendering.

addParens :: RenderContext -> Doc -> Doc Source #

Add parentheses if needed.

addParensMultiline :: RenderContext -> Doc -> Doc Source #

Add parentheses if needed, multiline if necessary.

assertParensNotNeeded :: RenderContext -> a -> a Source #

Ensure parentheses are not required, for case when you cannot sensibly wrap your expression into them.

Orphan instances

RenderDoc a => Buildable a Source # 
Instance details

Methods

build :: a -> Doc

buildList :: [a] -> Doc