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

Michelson.Printer.Util

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 suficcient 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 Michelson.Untyped.Annotation

RenderDoc T Source # 
Instance details

Defined in Michelson.Untyped.Type

RenderDoc ParameterType Source # 
Instance details

Defined in Michelson.Untyped.Type

RenderDoc Type Source # 
Instance details

Defined in Michelson.Untyped.Type

RenderDoc ExpandedOp Source # 
Instance details

Defined in Michelson.Untyped.Instr

RenderDoc ParsedOp Source # 
Instance details

Defined in Michelson.Macro

RenderDoc (Prettier ParameterType) Source # 
Instance details

Defined in Michelson.Untyped.Type

RenderDoc (Prettier Type) Source # 
Instance details

Defined in Michelson.Untyped.Type

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

Defined in Michelson.Untyped.Ext

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

Defined in Michelson.Untyped.Contract

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

Defined in Michelson.Untyped.Value

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

Defined in Michelson.Untyped.Value

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

Defined in Michelson.Untyped.Instr

RenderDoc (Notes t) Source # 
Instance details

Defined in Michelson.Typed.Annotation

RenderDoc (PackedNotes a) Source # 
Instance details

Defined in Michelson.Typed.Instr

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

Defined in Michelson.Untyped.Annotation

newtype Prettier a Source #

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 

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

Convert Doc to Text with a line width of 80.

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

Convert Doc to Builder in the same maner as printDoc.

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

Convert Doc to String in the same maner as printDoc.

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

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

renderOpsList :: RenderDoc op => Bool -> [op] -> Doc Source #

spaces :: Int -> Doc Source #

Create a specific number of spaces.

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

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

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

Turn something that is instance of RenderDoc into a Builder. It's formatted the same way as printDoc formats docs.

Smart parentheses

data RenderContext Source #

Environment carried during recursive rendering.

needsParens :: RenderContext Source #

ParensNeeded constant.

doesntNeedParens :: RenderContext Source #

ParensNeeded constant.

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

Add parentheses if needed.

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

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