plutus-core-1.0.0.1: Language library for Plutus Core
Safe Haskell None
Language Haskell2010

PlutusCore.Pretty

Synopsis

Basic types and functions

data Doc ann Source #

The abstract data type Doc ann represents pretty documents that have been annotated with data of type ann .

More specifically, a value of type Doc represents a non-empty set of possible layouts of a document. The layout functions select one of these possibilities, taking into account things like the width of the output document.

The annotation is an arbitrary piece of data associated with (part of) a document. Annotations may be used by the rendering backends in order to display output differently, such as

  • color information (e.g. when rendering to the terminal)
  • mouseover text (e.g. when rendering to rich HTML)
  • whether to show something or not (to allow simple or detailed versions)

The simplest way to display a Doc is via the Show class.

>>> putStrLn (show (vsep ["hello", "world"]))
hello
world

Instances

Instances details
Functor Doc

Alter the document’s annotations.

This instance makes Doc more flexible (because it can be used in Functor -polymorphic values), but fmap is much less readable compared to using reAnnotate in code that only works for Doc anyway. Consider using the latter when the type does not matter.

Instance details

Defined in Prettyprinter.Internal

Methods

fmap :: (a -> b) -> Doc a -> Doc b Source #

(<$) :: a -> Doc b -> Doc a Source #

Show ( Doc ann)

( show doc) prettyprints document doc with defaultLayoutOptions , ignoring all annotations.

Instance details

Defined in Prettyprinter.Internal

IsString ( Doc ann)
>>> pretty ("hello\nworld")
hello
world

This instance uses the Pretty Text instance, and uses the same newline to line conversion.

Instance details

Defined in Prettyprinter.Internal

Generic ( Doc ann)
Instance details

Defined in Prettyprinter.Internal

Associated Types

type Rep ( Doc ann) :: Type -> Type Source #

Semigroup ( Doc ann)
x <> y = hcat [x, y]
>>> "hello" <> "world" :: Doc ann
helloworld
Instance details

Defined in Prettyprinter.Internal

Monoid ( Doc ann)
mempty = emptyDoc
mconcat = hcat
>>> mappend "hello" "world" :: Doc ann
helloworld
Instance details

Defined in Prettyprinter.Internal

type Rep ( Doc ann)
Instance details

Defined in Prettyprinter.Internal

type Rep ( Doc ann) = D1 (' MetaData "Doc" "Prettyprinter.Internal" "prettyprinter-1.7.1-4IgD8s5wquO6FIO1jHqEQF" ' False ) ((( C1 (' MetaCons "Fail" ' PrefixI ' False ) ( U1 :: Type -> Type ) :+: ( C1 (' MetaCons "Empty" ' PrefixI ' False ) ( U1 :: Type -> Type ) :+: C1 (' MetaCons "Char" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' SourceStrict ' DecidedUnpack ) ( Rec0 Char )))) :+: ( C1 (' MetaCons "Text" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' SourceStrict ' DecidedUnpack ) ( Rec0 Int ) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' SourceStrict ' DecidedStrict ) ( Rec0 Text )) :+: ( C1 (' MetaCons "Line" ' PrefixI ' False ) ( U1 :: Type -> Type ) :+: C1 (' MetaCons "FlatAlt" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Doc ann)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Doc ann)))))) :+: (( C1 (' MetaCons "Cat" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Doc ann)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Doc ann))) :+: ( C1 (' MetaCons "Nest" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' SourceStrict ' DecidedUnpack ) ( Rec0 Int ) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Doc ann))) :+: C1 (' MetaCons "Union" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Doc ann)) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Doc ann))))) :+: (( C1 (' MetaCons "Column" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Int -> Doc ann))) :+: C1 (' MetaCons "WithPageWidth" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( PageWidth -> Doc ann)))) :+: ( C1 (' MetaCons "Nesting" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Int -> Doc ann))) :+: C1 (' MetaCons "Annotated" ' PrefixI ' False ) ( S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ann) :*: S1 (' MetaSel (' Nothing :: Maybe Symbol ) ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 ( Doc ann)))))))

class Pretty a where Source #

Overloaded conversion to Doc .

Laws:

  1. output should be pretty. :-)

Minimal complete definition

pretty

Methods

pretty :: a -> Doc ann Source #

>>> pretty 1 <+> pretty "hello" <+> pretty 1.234
1 hello 1.234

prettyList :: [a] -> Doc ann Source #

prettyList is only used to define the instance Pretty a => Pretty [a] . In normal circumstances only the pretty function is used.

>>> prettyList [1, 23, 456]
[1, 23, 456]

Instances

Instances details
Pretty Bool
>>> pretty True
True
Instance details

Defined in Prettyprinter.Internal

Pretty Char

Instead of ( pretty 'n') , consider using line as a more readable alternative.

>>> pretty 'f' <> pretty 'o' <> pretty 'o'
foo
>>> pretty ("string" :: String)
string
Instance details

Defined in Prettyprinter.Internal

Pretty Double
>>> pretty (exp 1 :: Double)
2.71828182845904...
Instance details

Defined in Prettyprinter.Internal

Pretty Float
>>> pretty (pi :: Float)
3.1415927
Instance details

Defined in Prettyprinter.Internal

Pretty Int
>>> pretty (123 :: Int)
123
Instance details

Defined in Prettyprinter.Internal

Pretty Int8
Instance details

Defined in Prettyprinter.Internal

Pretty Int16
Instance details

Defined in Prettyprinter.Internal

Pretty Int32
Instance details

Defined in Prettyprinter.Internal

Pretty Int64
Instance details

Defined in Prettyprinter.Internal

Pretty Integer
>>> pretty (2^123 :: Integer)
10633823966279326983230456482242756608
Instance details

Defined in Prettyprinter.Internal

Pretty Natural
Instance details

Defined in Prettyprinter.Internal

Pretty Word
Instance details

Defined in Prettyprinter.Internal

Pretty Word8
Instance details

Defined in Prettyprinter.Internal

Pretty Word16
Instance details

Defined in Prettyprinter.Internal

Pretty Word32
Instance details

Defined in Prettyprinter.Internal

Pretty Word64
Instance details

Defined in Prettyprinter.Internal

Pretty ()
>>> pretty ()
()

The argument is not used:

>>> pretty (error "Strict?" :: ())
()
Instance details

Defined in Prettyprinter.Internal

Pretty Text

Automatically converts all newlines to line .

>>> pretty ("hello\nworld" :: Text)
hello
world

Note that line can be undone by group :

>>> group (pretty ("hello\nworld" :: Text))
hello world

Manually use hardline if you definitely want newlines.

Instance details

Defined in Prettyprinter.Internal

Pretty Text

(lazy Text instance, identical to the strict version)

Instance details

Defined in Prettyprinter.Internal

Pretty Void

Finding a good example for printing something that does not exist is hard, so here is an example of printing a list full of nothing.

>>> pretty ([] :: [Void])
[]
Instance details

Defined in Prettyprinter.Internal

Pretty SourcePos Source #
Instance details

Defined in PlutusCore.Error

Pretty ErrorCode Source #
Instance details

Defined in ErrorCode

Pretty Data Source #
Instance details

Defined in PlutusCore.Data

Pretty Unique Source #
Instance details

Defined in PlutusCore.Name

Pretty FreeVariableError Source #
Instance details

Defined in PlutusCore.DeBruijn.Internal

Pretty Index Source #
Instance details

Defined in PlutusCore.DeBruijn.Internal

Pretty ExCPU Source #
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

Pretty ExMemory Source #
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

Pretty ExRestrictingBudget Source #
Instance details

Defined in PlutusCore.Evaluation.Machine.ExBudget

Pretty ExBudget Source #
Instance details

Defined in PlutusCore.Evaluation.Machine.ExBudget

Pretty UnliftingError Source #
Instance details

Defined in PlutusCore.Evaluation.Machine.Exception

Pretty Size Source #
Instance details

Defined in PlutusCore.Size

Pretty ParseError Source #
Instance details

Defined in PlutusCore.Error

Pretty DefaultFun Source #
Instance details

Defined in PlutusCore.Default.Builtins

Pretty CostModelApplyError Source #
Instance details

Defined in PlutusCore.Evaluation.Machine.CostModelInterface

Pretty CekUserError Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.Internal

Pretty RestrictingSt Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.ExBudgetMode

Pretty CountingSt Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.ExBudgetMode

Pretty DatatypeComponent Source #
Instance details

Defined in PlutusIR.Compiler.Provenance

Pretty RetainedSize Source #
Instance details

Defined in PlutusIR.Analysis.RetainedSize

Pretty ExtensionFun Source #
Instance details

Defined in PlutusCore.Examples.Builtins

Pretty a => Pretty [a]
>>> pretty [1,2,3]
[1, 2, 3]
Instance details

Defined in Prettyprinter.Internal

Pretty a => Pretty ( Maybe a)

Ignore Nothing s, print Just contents.

>>> pretty (Just True)
True
>>> braces (pretty (Nothing :: Maybe Bool))
{}
>>> pretty [Just 1, Nothing, Just 3, Nothing]
[1, 3]
Instance details

Defined in Prettyprinter.Internal

Pretty a => Pretty ( Identity a)
>>> pretty (Identity 1)
1
Instance details

Defined in Prettyprinter.Internal

Pretty a => Pretty ( NonEmpty a)
Instance details

Defined in Prettyprinter.Internal

GShow uni => Pretty ( SomeTypeIn uni) Source #
Instance details

Defined in PlutusCore.Pretty.PrettyConst

PrettyClassic a => Pretty ( EvaluationResult a) Source #
Instance details

Defined in PlutusCore.Evaluation.Result

Pretty ( Version ann) Source #
Instance details

Defined in PlutusCore.Core.Instance.Pretty.Common

Pretty ann => Pretty ( Kind ann) Source #
Instance details

Defined in PlutusCore.Core.Instance.Pretty.Default

Pretty a => Pretty ( Normalized a) Source #
Instance details

Defined in PlutusCore.Core.Type

Pretty ann => Pretty ( UniqueError ann) Source #
Instance details

Defined in PlutusCore.Error

Show fun => Pretty ( ExBudgetCategory fun) Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.Internal

( Show fun, Ord fun) => Pretty ( TallyingSt fun) Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.ExBudgetMode

( Show fun, Ord fun) => Pretty ( CekExTally fun) Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.ExBudgetMode

Pretty a => Pretty ( Provenance a) Source #
Instance details

Defined in PlutusIR.Compiler.Provenance

( Pretty a, Pretty b) => Pretty ( Either a b) Source #
Instance details

Defined in PlutusPrelude

( Pretty a1, Pretty a2) => Pretty (a1, a2)
>>> pretty (123, "hello")
(123, hello)
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: (a1, a2) -> Doc ann Source #

prettyList :: [(a1, a2)] -> Doc ann Source #

PrettyBy config a => Pretty ( AttachPrettyConfig config a)
>>> data Cfg = Cfg
>>> data D = D
>>> instance PrettyBy Cfg D where prettyBy Cfg D = "D"
>>> pretty $ AttachPrettyConfig Cfg D
D
Instance details

Defined in Text.PrettyBy.Internal

DefaultPrettyBy config a => Pretty ( AttachDefaultPrettyConfig config a)
Instance details

Defined in Text.PrettyBy.Internal

( Closed uni, Everywhere uni PrettyConst ) => Pretty ( Some ( ValueOf uni)) Source #
Instance details

Defined in PlutusCore.Pretty.PrettyConst

( Closed uni, Everywhere uni PrettyConst ) => Pretty ( ValueOf uni a) Source #

Special treatment for built-in constants: see the Note in PlutusCore.Pretty.PrettyConst.

Instance details

Defined in PlutusCore.Pretty.PrettyConst

( PrettyClassic tyname, Pretty ann) => Pretty ( TyVarDecl tyname ann) Source #
Instance details

Defined in PlutusIR.Core.Instance.Pretty

( Pretty err, Pretty cause) => Pretty ( ErrorWithCause err cause) Source #
Instance details

Defined in PlutusCore.Evaluation.Machine.Exception

Pretty val => Pretty ( Opaque val rep) Source #
Instance details

Defined in PlutusCore.Builtin.Polymorphism

( Pretty a1, Pretty a2, Pretty a3) => Pretty (a1, a2, a3)
>>> pretty (123, "hello", False)
(123, hello, False)
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: (a1, a2, a3) -> Doc ann Source #

prettyList :: [(a1, a2, a3)] -> Doc ann Source #

Pretty a => Pretty ( Const a b)
Instance details

Defined in Prettyprinter.Internal

( PrettyClassic tyname, GShow uni, Pretty ann) => Pretty ( Type tyname uni ann) Source #
Instance details

Defined in PlutusCore.Core.Instance.Pretty.Default

Methods

pretty :: Type tyname uni ann -> Doc ann0 Source #

prettyList :: [ Type tyname uni ann] -> Doc ann0 Source #

( Pretty ann, Pretty fun, GShow uni, Closed uni, Everywhere uni PrettyConst ) => Pretty ( Error uni fun ann) Source #
Instance details

Defined in PlutusIR.Error

Methods

pretty :: Error uni fun ann -> Doc ann0 Source #

prettyList :: [ Error uni fun ann] -> Doc ann0 Source #

( PrettyClassic name, GShow uni, Closed uni, Everywhere uni PrettyConst , Pretty fun, Pretty ann) => Pretty ( Program name uni fun ann) Source #
Instance details

Defined in UntypedPlutusCore.Core.Instance.Pretty.Default

Methods

pretty :: Program name uni fun ann -> Doc ann0 Source #

prettyList :: [ Program name uni fun ann] -> Doc ann0 Source #

( PrettyClassic name, GShow uni, Closed uni, Everywhere uni PrettyConst , Pretty fun, Pretty ann) => Pretty ( Term name uni fun ann) Source #
Instance details

Defined in UntypedPlutusCore.Core.Instance.Pretty.Default

Methods

pretty :: Term name uni fun ann -> Doc ann0 Source #

prettyList :: [ Term name uni fun ann] -> Doc ann0 Source #

( PrettyClassic tyname, PrettyClassic name, GShow uni, Closed uni, Everywhere uni PrettyConst , Pretty fun, Pretty ann) => Pretty ( Program tyname name uni fun ann) Source #
Instance details

Defined in PlutusCore.Core.Instance.Pretty.Default

Methods

pretty :: Program tyname name uni fun ann -> Doc ann0 Source #

prettyList :: [ Program tyname name uni fun ann] -> Doc ann0 Source #

( PrettyClassic tyname, PrettyClassic name, GShow uni, Closed uni, Everywhere uni PrettyConst , Pretty fun, Pretty ann) => Pretty ( Term tyname name uni fun ann) Source #
Instance details

Defined in PlutusCore.Core.Instance.Pretty.Default

Methods

pretty :: Term tyname name uni fun ann -> Doc ann0 Source #

prettyList :: [ Term tyname name uni fun ann] -> Doc ann0 Source #

( PrettyClassic tyname, PrettyClassic name, GShow uni, Closed uni, Everywhere uni PrettyConst , Pretty fun, Pretty ann) => Pretty ( Program tyname name uni fun ann) Source #
Instance details

Defined in PlutusIR.Core.Instance.Pretty

Methods

pretty :: Program tyname name uni fun ann -> Doc ann0 Source #

prettyList :: [ Program tyname name uni fun ann] -> Doc ann0 Source #

( PrettyClassic tyname, PrettyClassic name, GShow uni, Closed uni, Everywhere uni PrettyConst , Pretty fun, Pretty ann) => Pretty ( Term tyname name uni fun ann) Source #
Instance details

Defined in PlutusIR.Core.Instance.Pretty

Methods

pretty :: Term tyname name uni fun ann -> Doc ann0 Source #

prettyList :: [ Term tyname name uni fun ann] -> Doc ann0 Source #

( PrettyClassic tyname, PrettyClassic name, GShow uni, Closed uni, Everywhere uni PrettyConst , Pretty fun, Pretty ann) => Pretty ( Binding tyname name uni fun ann) Source #
Instance details

Defined in PlutusIR.Core.Instance.Pretty

Methods

pretty :: Binding tyname name uni fun ann -> Doc ann0 Source #

prettyList :: [ Binding tyname name uni fun ann] -> Doc ann0 Source #

( PrettyClassic tyname, PrettyClassic name, GShow uni, Everywhere uni PrettyConst , Pretty ann) => Pretty ( Datatype tyname name uni fun ann) Source #
Instance details

Defined in PlutusIR.Core.Instance.Pretty

Methods

pretty :: Datatype tyname name uni fun ann -> Doc ann0 Source #

prettyList :: [ Datatype tyname name uni fun ann] -> Doc ann0 Source #

( PrettyClassic tyname, PrettyClassic name, GShow uni, Everywhere uni PrettyConst , Pretty ann) => Pretty ( VarDecl tyname name uni fun ann) Source #
Instance details

Defined in PlutusIR.Core.Instance.Pretty

Methods

pretty :: VarDecl tyname name uni fun ann -> Doc ann0 Source #

prettyList :: [ VarDecl tyname name uni fun ann] -> Doc ann0 Source #

class PrettyBy config a where Source #

A class for pretty-printing values in a configurable manner.

A basic example:

>>> data Case = UpperCase | LowerCase
>>> data D = D
>>> instance PrettyBy Case D where prettyBy UpperCase D = "D"; prettyBy LowerCase D = "d"
>>> prettyBy UpperCase D
D
>>> prettyBy LowerCase D
d

The library provides instances for common types like Integer or Bool , so you can't define your own PrettyBy SomeConfig Integer instance. And for the same reason you should not define instances like PrettyBy SomeAnotherConfig a for universally quantified a , because such an instance would overlap with the existing ones. Take for example

>>> data ViaShow = ViaShow
>>> instance Show a => PrettyBy ViaShow a where prettyBy ViaShow = pretty . show

with such an instance prettyBy ViaShow (1 :: Int) throws an error about overlapping instances:

• Overlapping instances for PrettyBy ViaShow Int
    arising from a use of ‘prettyBy’
  Matching instances:
    instance PrettyDefaultBy config Int => PrettyBy config Int
    instance [safe] Show a => PrettyBy ViaShow a

There's a newtype provided specifically for the purpose of defining a PrettyBy instance for any a : PrettyAny . Read its docs for details on when you might want to use it.

The PrettyBy instance for common types is defined in a way that allows to override default pretty-printing behaviour, read the docs of HasPrettyDefaults for details.

Minimal complete definition

Nothing

Methods

prettyBy :: config -> a -> Doc ann Source #

Pretty-print a value of type a the way a config specifies it. The default implementation of prettyBy is in terms of pretty , defaultPrettyFunctorBy or defaultPrettyBifunctorBy depending on the kind of the data type that you're providing an instance for. For example, the default implementation of prettyBy for a monomorphic type is going to be "ignore the config and call pretty over the value":

>>> newtype N = N Int deriving newtype (Pretty)
>>> instance PrettyBy () N
>>> prettyBy () (N 42)
42

The default implementation of prettyBy for a Functor is going to be in terms of defaultPrettyFunctorBy :

>>> newtype N a = N a deriving stock (Functor) deriving newtype (Pretty)
>>> instance PrettyBy () a => PrettyBy () (N a)
>>> prettyBy () (N (42 :: Int))
42

It's fine for the data type to have a phantom parameter as long as the data type is still a Functor (i.e. the parameter has to be of kind Type ). Then defaultPrettyFunctorBy is used again:

>>> newtype N a = N Int deriving stock (Functor) deriving newtype (Pretty)
>>> instance PrettyBy () (N b)
>>> prettyBy () (N 42)
42

If the data type has a single parameter of any other kind, then it's not a functor and so like in the monomorphic case pretty is used:

>>> newtype N (b :: Bool) = N Int deriving newtype (Pretty)
>>> instance PrettyBy () (N b)
>>> prettyBy () (N 42)
42

Same applies to a data type with two parameters: if both the parameters are of kind Type , then the data type is assumed to be a Bifunctor and hence defaultPrettyBifunctorBy is used. If the right parameter is of kind Type and the left parameter is of any other kind, then we fallback to assuming the data type is a Functor and defining prettyBy as defaultPrettyFunctorBy . If both the parameters are not of kind Type , we fallback to implementing prettyBy in terms of pretty like in the monomorphic case.

Note that in all those cases a Pretty instance for the data type has to already exist, so that we can derive a PrettyBy one in terms of it. If it doesn't exist or if your data type is not supported (for example, if it has three or more parameters of kind Type ), then you'll need to provide the implementation manually.

prettyListBy :: config -> [a] -> Doc ann Source #

prettyListBy is used to define the default PrettyBy instance for [a] and NonEmpty a . In normal circumstances only the prettyBy function is used. The default implementation of prettyListBy is in terms of defaultPrettyFunctorBy .

Instances

Instances details
PrettyDefaultBy config Word8 => PrettyBy config Word8
Instance details

Defined in Text.PrettyBy.Internal

PrettyDefaultBy config Word64 => PrettyBy config Word64
Instance details

Defined in Text.PrettyBy.Internal

PrettyDefaultBy config Word32 => PrettyBy config Word32
Instance details

Defined in Text.PrettyBy.Internal

PrettyDefaultBy config Word16 => PrettyBy config Word16
Instance details

Defined in Text.PrettyBy.Internal

PrettyDefaultBy config Word => PrettyBy config Word
Instance details

Defined in Text.PrettyBy.Internal

PrettyDefaultBy config Void => PrettyBy config Void
>>> prettyBy () ([] :: [Void])
[]
Instance details

Defined in Text.PrettyBy.Internal

PrettyDefaultBy config Text => PrettyBy config Text

Automatically converts all newlines to line .

>>> prettyBy () ("hello\nworld" :: Strict.Text)
hello
world
Instance details

Defined in Text.PrettyBy.Internal

PrettyDefaultBy config Text => PrettyBy config Text

An instance for lazy Text . Identitical to the strict one.

Instance details

Defined in Text.PrettyBy.Internal

PrettyDefaultBy config Natural => PrettyBy config Natural
>>> prettyBy () (123 :: Natural)
123
Instance details

Defined in Text.PrettyBy.Internal

PrettyDefaultBy config Integer => PrettyBy config Integer
>>> prettyBy () (2^(123 :: Int) :: Integer)
10633823966279326983230456482242756608
Instance details

Defined in Text.PrettyBy.Internal

PrettyDefaultBy config Int8 => PrettyBy config Int8
Instance details

Defined in Text.PrettyBy.Internal

PrettyDefaultBy config Int64 => PrettyBy config Int64
Instance details

Defined in Text.PrettyBy.Internal

PrettyDefaultBy config Int32 => PrettyBy config Int32
Instance details

Defined in Text.PrettyBy.Internal

PrettyDefaultBy config Int16 => PrettyBy config Int16
Instance details

Defined in Text.PrettyBy.Internal

PrettyDefaultBy config Int => PrettyBy config Int
>>> prettyBy () (123 :: Int)
123
Instance details

Defined in Text.PrettyBy.Internal

PrettyDefaultBy config Float => PrettyBy config Float
>>> prettyBy () (pi :: Float)
3.1415927
Instance details

Defined in Text.PrettyBy.Internal

PrettyDefaultBy config Double => PrettyBy config Double
>>> prettyBy () (pi :: Double)
3.141592653589793
Instance details

Defined in Text.PrettyBy.Internal

PrettyDefaultBy config Char => PrettyBy config Char

By default a String (i.e. [Char] ) is converted to a Text first and then pretty-printed. So make sure that if you have any non-default pretty-printing for Char or Text , they're in sync.

>>> prettyBy () 'a'
a
>>> prettyBy () "abc"
abc
Instance details

Defined in Text.PrettyBy.Internal

PrettyDefaultBy config Bool => PrettyBy config Bool
>>> prettyBy () True
True
Instance details

Defined in Text.PrettyBy.Internal

PrettyDefaultBy config () => PrettyBy config ()
>>> prettyBy () ()
()

The argument is not used:

>>> prettyBy () (error "Strict?" :: ())
()
Instance details

Defined in Text.PrettyBy.Internal

Methods

prettyBy :: config -> () -> Doc ann Source #

prettyListBy :: config -> [()] -> Doc ann Source #

HasPrettyConfigName config => PrettyBy config TyName Source #
Instance details

Defined in PlutusCore.Name

HasPrettyConfigName config => PrettyBy config Name Source #
Instance details

Defined in PlutusCore.Name

HasPrettyConfigName config => PrettyBy config TyDeBruijn Source #
Instance details

Defined in PlutusCore.DeBruijn.Internal

HasPrettyConfigName config => PrettyBy config NamedTyDeBruijn Source #
Instance details

Defined in PlutusCore.DeBruijn.Internal

HasPrettyConfigName config => PrettyBy config FakeNamedDeBruijn Source #
Instance details

Defined in PlutusCore.DeBruijn.Internal

HasPrettyConfigName config => PrettyBy config DeBruijn Source #
Instance details

Defined in PlutusCore.DeBruijn.Internal

HasPrettyConfigName config => PrettyBy config NamedDeBruijn Source #
Instance details

Defined in PlutusCore.DeBruijn.Internal

PrettyBy config ExCPU Source #
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

PrettyBy config ExMemory Source #
Instance details

Defined in PlutusCore.Evaluation.Machine.ExMemory

PrettyBy config ExRestrictingBudget Source #
Instance details

Defined in PlutusCore.Evaluation.Machine.ExBudget

PrettyBy config ExBudget Source #
Instance details

Defined in PlutusCore.Evaluation.Machine.ExBudget

PrettyBy config RestrictingSt Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.ExBudgetMode

PrettyBy config CountingSt Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.ExBudgetMode

PrettyBy PrettyConfigPlc DefaultFun Source #
Instance details

Defined in PlutusCore.Default.Builtins

PrettyBy ConstConfig ByteString Source #
Instance details

Defined in PlutusCore.Pretty.PrettyConst

PrettyBy ConstConfig Data Source #
Instance details

Defined in PlutusCore.Pretty.PrettyConst

PrettyDefaultBy config a => PrettyBy config ( PrettyCommon a)
Instance details

Defined in Text.PrettyBy.Internal

PrettyDefaultBy config [a] => PrettyBy config [a]

prettyBy for [a] is defined in terms of prettyListBy by default.

>>> prettyBy () [True, False]
[True, False]
>>> prettyBy () "abc"
abc
>>> prettyBy () [Just False, Nothing, Just True]
[False, True]
Instance details

Defined in Text.PrettyBy.Internal

Methods

prettyBy :: config -> [a] -> Doc ann Source #

prettyListBy :: config -> [[a]] -> Doc ann Source #

PrettyDefaultBy config ( NonEmpty a) => PrettyBy config ( NonEmpty a)

prettyBy for NonEmpty a is defined in terms of prettyListBy by default.

>>> prettyBy () (True :| [False])
[True, False]
>>> prettyBy () ('a' :| "bc")
abc
>>> prettyBy () (Just False :| [Nothing, Just True])
[False, True]
Instance details

Defined in Text.PrettyBy.Internal

PrettyDefaultBy config ( Maybe a) => PrettyBy config ( Maybe a)

By default a [Maybe a] is converted to [a] first and only then pretty-printed.

>>> braces $ prettyBy () (Just True)
{True}
>>> braces $ prettyBy () (Nothing :: Maybe Bool)
{}
>>> prettyBy () [Just False, Nothing, Just True]
[False, True]
>>> prettyBy () [Nothing, Just 'a', Just 'b', Nothing, Just 'c']
abc
Instance details

Defined in Text.PrettyBy.Internal

Pretty a => PrettyBy config ( IgnorePrettyConfig a)
>>> data Cfg = Cfg
>>> data D = D
>>> instance Pretty D where pretty D = "D"
>>> prettyBy Cfg $ IgnorePrettyConfig D
D
Instance details

Defined in Text.PrettyBy.Internal

PrettyDefaultBy config ( Identity a) => PrettyBy config ( Identity a)
>>> prettyBy () (Identity True)
True
Instance details

Defined in Text.PrettyBy.Internal

PrettyBy config a => PrettyBy config ( EvaluationResult a) Source #
Instance details

Defined in PlutusCore.Evaluation.Result

PrettyBy config a => PrettyBy config ( Normalized a) Source #
Instance details

Defined in PlutusCore.Core.Type

( HasPrettyDefaults config ~ ' True , Pretty fun) => PrettyBy config ( MachineError fun) Source #
Instance details

Defined in PlutusCore.Evaluation.Machine.Exception

( Show fun, Ord fun) => PrettyBy config ( TallyingSt fun) Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.ExBudgetMode

( Show fun, Ord fun) => PrettyBy config ( CekExTally fun) Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.ExBudgetMode

DefaultPrettyPlcStrategy a => PrettyBy PrettyConfigPlc ( PrettyAny a) Source #
Instance details

Defined in PlutusCore.Pretty.Plc

DefaultPrettyPlcStrategy ( Kind ann) => PrettyBy PrettyConfigPlc ( Kind ann) Source #
Instance details

Defined in PlutusCore.Core.Instance.Pretty.Plc

DefaultPrettyPlcStrategy a => PrettyBy PrettyConfigPlcStrategy ( PrettyAny a) Source #
Instance details

Defined in PlutusCore.Pretty.Plc

DefaultPrettyBy ConstConfig ( PrettyAny a) => PrettyBy ConstConfig ( PrettyAny a) Source #
Instance details

Defined in PlutusCore.Pretty.PrettyConst

PrettyDefaultBy config ( Either a b) => PrettyBy config ( Either a b) Source #

An instance extending the set of types supporting default pretty-printing with Either .

Instance details

Defined in PlutusPrelude

Methods

prettyBy :: config -> Either a b -> Doc ann Source #

prettyListBy :: config -> [ Either a b] -> Doc ann Source #

PrettyDefaultBy config (a, b) => PrettyBy config (a, b)
>>> prettyBy () (False, "abc")
(False, abc)
Instance details

Defined in Text.PrettyBy.Internal

Methods

prettyBy :: config -> (a, b) -> Doc ann Source #

prettyListBy :: config -> [(a, b)] -> Doc ann Source #

( PrettyBy config cause, PrettyBy config err) => PrettyBy config ( ErrorWithCause err cause) Source #
Instance details

Defined in PlutusCore.Evaluation.Machine.Exception

Methods

prettyBy :: config -> ErrorWithCause err cause -> Doc ann Source #

prettyListBy :: config -> [ ErrorWithCause err cause] -> Doc ann Source #

( HasPrettyDefaults config ~ ' True , PrettyBy config internal, Pretty user) => PrettyBy config ( EvaluationError user internal) Source #
Instance details

Defined in PlutusCore.Evaluation.Machine.Exception

Methods

prettyBy :: config -> EvaluationError user internal -> Doc ann Source #

prettyListBy :: config -> [ EvaluationError user internal] -> Doc ann Source #

( Closed uni, GShow uni, Everywhere uni PrettyConst , Pretty fun) => PrettyBy PrettyConfigPlc ( CkValue uni fun) Source #
Instance details

Defined in PlutusCore.Evaluation.Machine.Ck

( Closed uni, GShow uni, Everywhere uni PrettyConst , Pretty fun) => PrettyBy PrettyConfigPlc ( CekValue uni fun) Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.Internal

PrettyUni uni ann => PrettyBy PrettyConfigPlc ( TypeErrorExt uni ann) Source #
Instance details

Defined in PlutusIR.Error

PrettyDefaultBy config ( Const a b) => PrettyBy config ( Const a b)

Non-polykinded, because Pretty (Const a b) is not polykinded either.

>>> prettyBy () (Const 1 :: Const Integer Bool)
1
Instance details

Defined in Text.PrettyBy.Internal

Methods

prettyBy :: config -> Const a b -> Doc ann Source #

prettyListBy :: config -> [ Const a b] -> Doc ann Source #

PrettyDefaultBy config (a, b, c) => PrettyBy config (a, b, c)
>>> prettyBy () ('a', "bcd", True)
(a, bcd, True)
Instance details

Defined in Text.PrettyBy.Internal

Methods

prettyBy :: config -> (a, b, c) -> Doc ann Source #

prettyListBy :: config -> [(a, b, c)] -> Doc ann Source #

DefaultPrettyPlcStrategy ( Type tyname uni ann) => PrettyBy PrettyConfigPlc ( Type tyname uni ann) Source #
Instance details

Defined in PlutusCore.Core.Instance.Pretty.Plc

( GShow uni, Closed uni, Everywhere uni PrettyConst , Pretty fun, Pretty ann) => PrettyBy PrettyConfigPlc ( Error uni fun ann) Source #
Instance details

Defined in PlutusCore.Error

( GShow uni, Closed uni, Everywhere uni PrettyConst , Pretty fun, Pretty ann) => PrettyBy PrettyConfigPlc ( Error uni fun ann) Source #
Instance details

Defined in PlutusIR.Error

( GShow uni, Closed uni, Everywhere uni PrettyConst , Pretty ann, Pretty fun, Pretty term) => PrettyBy PrettyConfigPlc ( TypeError term uni fun ann) Source #
Instance details

Defined in PlutusCore.Error

DefaultPrettyPlcStrategy ( Program name uni fun ann) => PrettyBy PrettyConfigPlc ( Program name uni fun ann) Source #
Instance details

Defined in UntypedPlutusCore.Core.Instance.Pretty.Plc

DefaultPrettyPlcStrategy ( Term name uni fun ann) => PrettyBy PrettyConfigPlc ( Term name uni fun ann) Source #
Instance details

Defined in UntypedPlutusCore.Core.Instance.Pretty.Plc

( Pretty ann, PrettyBy config ( Type tyname uni ann), PrettyBy config ( Term tyname name uni fun ann)) => PrettyBy config ( NormCheckError tyname name uni fun ann) Source #
Instance details

Defined in PlutusCore.Error

Methods

prettyBy :: config -> NormCheckError tyname name uni fun ann -> Doc ann0 Source #

prettyListBy :: config -> [ NormCheckError tyname name uni fun ann] -> Doc ann0 Source #

DefaultPrettyPlcStrategy ( Program tyname name uni fun ann) => PrettyBy PrettyConfigPlc ( Program tyname name uni fun ann) Source #
Instance details

Defined in PlutusCore.Core.Instance.Pretty.Plc

Methods

prettyBy :: PrettyConfigPlc -> Program tyname name uni fun ann -> Doc ann0 Source #

prettyListBy :: PrettyConfigPlc -> [ Program tyname name uni fun ann] -> Doc ann0 Source #

DefaultPrettyPlcStrategy ( Term tyname name uni fun ann) => PrettyBy PrettyConfigPlc ( Term tyname name uni fun ann) Source #
Instance details

Defined in PlutusCore.Core.Instance.Pretty.Plc

Methods

prettyBy :: PrettyConfigPlc -> Term tyname name uni fun ann -> Doc ann0 Source #

prettyListBy :: PrettyConfigPlc -> [ Term tyname name uni fun ann] -> Doc ann0 Source #

PrettyBy ( PrettyConfigClassic configName) Strictness Source #
Instance details

Defined in PlutusIR.Core.Instance.Pretty

PrettyBy ( PrettyConfigClassic configName) Recursivity Source #
Instance details

Defined in PlutusIR.Core.Instance.Pretty

PrettyBy ( PrettyConfigReadable configName) ( Kind a) Source #
Instance details

Defined in PlutusCore.Core.Instance.Pretty.Readable

Pretty ann => PrettyBy ( PrettyConfigClassic configName) ( Kind ann) Source #
Instance details

Defined in PlutusCore.Core.Instance.Pretty.Classic

( PrettyClassicBy configName tyname, Pretty ann) => PrettyBy ( PrettyConfigClassic configName) ( TyVarDecl tyname ann) Source #
Instance details

Defined in PlutusIR.Core.Instance.Pretty

( PrettyReadableBy configName tyname, GShow uni) => PrettyBy ( PrettyConfigReadable configName) ( Type tyname uni a) Source #
Instance details

Defined in PlutusCore.Core.Instance.Pretty.Readable

( PrettyClassicBy configName tyname, GShow uni, Pretty ann) => PrettyBy ( PrettyConfigClassic configName) ( Type tyname uni ann) Source #
Instance details

Defined in PlutusCore.Core.Instance.Pretty.Classic

Methods

prettyBy :: PrettyConfigClassic configName -> Type tyname uni ann -> Doc ann0 Source #

prettyListBy :: PrettyConfigClassic configName -> [ Type tyname uni ann] -> Doc ann0 Source #

PrettyReadableBy configName ( Term name uni fun a) => PrettyBy ( PrettyConfigReadable configName) ( Program name uni fun a) Source #
Instance details

Defined in UntypedPlutusCore.Core.Instance.Pretty.Readable

( PrettyReadableBy configName name, GShow uni, Closed uni, Everywhere uni PrettyConst , Pretty fun) => PrettyBy ( PrettyConfigReadable configName) ( Term name uni fun a) Source #
Instance details

Defined in UntypedPlutusCore.Core.Instance.Pretty.Readable

Methods

prettyBy :: PrettyConfigReadable configName -> Term name uni fun a -> Doc ann Source #

prettyListBy :: PrettyConfigReadable configName -> [ Term name uni fun a] -> Doc ann Source #

( PrettyClassicBy configName ( Term name uni fun ann), Pretty ann) => PrettyBy ( PrettyConfigClassic configName) ( Program name uni fun ann) Source #
Instance details

Defined in UntypedPlutusCore.Core.Instance.Pretty.Classic

Methods

prettyBy :: PrettyConfigClassic configName -> Program name uni fun ann -> Doc ann0 Source #

prettyListBy :: PrettyConfigClassic configName -> [ Program name uni fun ann] -> Doc ann0 Source #

( PrettyClassicBy configName name, GShow uni, Closed uni, Everywhere uni PrettyConst , Pretty fun, Pretty ann) => PrettyBy ( PrettyConfigClassic configName) ( Term name uni fun ann) Source #
Instance details

Defined in UntypedPlutusCore.Core.Instance.Pretty.Classic

Methods

prettyBy :: PrettyConfigClassic configName -> Term name uni fun ann -> Doc ann0 Source #

prettyListBy :: PrettyConfigClassic configName -> [ Term name uni fun ann] -> Doc ann0 Source #

PrettyReadableBy configName ( Term tyname name uni fun a) => PrettyBy ( PrettyConfigReadable configName) ( Program tyname name uni fun a) Source #
Instance details

Defined in PlutusCore.Core.Instance.Pretty.Readable

Methods

prettyBy :: PrettyConfigReadable configName -> Program tyname name uni fun a -> Doc ann Source #

prettyListBy :: PrettyConfigReadable configName -> [ Program tyname name uni fun a] -> Doc ann Source #

( PrettyReadableBy configName tyname, PrettyReadableBy configName name, GShow uni, Closed uni, Everywhere uni PrettyConst , Pretty fun) => PrettyBy ( PrettyConfigReadable configName) ( Term tyname name uni fun a) Source #
Instance details

Defined in PlutusCore.Core.Instance.Pretty.Readable

Methods

prettyBy :: PrettyConfigReadable configName -> Term tyname name uni fun a -> Doc ann Source #

prettyListBy :: PrettyConfigReadable configName -> [ Term tyname name uni fun a] -> Doc ann Source #

( PrettyClassicBy configName ( Term tyname name uni fun ann), Pretty ann) => PrettyBy ( PrettyConfigClassic configName) ( Program tyname name uni fun ann) Source #
Instance details

Defined in PlutusCore.Core.Instance.Pretty.Classic

Methods

prettyBy :: PrettyConfigClassic configName -> Program tyname name uni fun ann -> Doc ann0 Source #

prettyListBy :: PrettyConfigClassic configName -> [ Program tyname name uni fun ann] -> Doc ann0 Source #

( PrettyClassicBy configName tyname, PrettyClassicBy configName name, GShow uni, Closed uni, Everywhere uni PrettyConst , Pretty fun, Pretty ann) => PrettyBy ( PrettyConfigClassic configName) ( Term tyname name uni fun ann) Source #
Instance details

Defined in PlutusCore.Core.Instance.Pretty.Classic

Methods

prettyBy :: PrettyConfigClassic configName -> Term tyname name uni fun ann -> Doc ann0 Source #

prettyListBy :: PrettyConfigClassic configName -> [ Term tyname name uni fun ann] -> Doc ann0 Source #

( PrettyClassicBy configName tyname, PrettyClassicBy configName name, GShow uni, Closed uni, Everywhere uni PrettyConst , Pretty fun, Pretty ann) => PrettyBy ( PrettyConfigClassic configName) ( Program tyname name uni fun ann) Source #
Instance details

Defined in PlutusIR.Core.Instance.Pretty

Methods

prettyBy :: PrettyConfigClassic configName -> Program tyname name uni fun ann -> Doc ann0 Source #

prettyListBy :: PrettyConfigClassic configName -> [ Program tyname name uni fun ann] -> Doc ann0 Source #

( PrettyClassicBy configName tyname, PrettyClassicBy configName name, GShow uni, Closed uni, Everywhere uni PrettyConst , Pretty fun, Pretty ann) => PrettyBy ( PrettyConfigClassic configName) ( Term tyname name uni fun ann) Source #
Instance details

Defined in PlutusIR.Core.Instance.Pretty

Methods

prettyBy :: PrettyConfigClassic configName -> Term tyname name uni fun ann -> Doc ann0 Source #

prettyListBy :: PrettyConfigClassic configName -> [ Term tyname name uni fun ann] -> Doc ann0 Source #

( PrettyClassicBy configName tyname, PrettyClassicBy configName name, GShow uni, Closed uni, Everywhere uni PrettyConst , Pretty fun, Pretty ann) => PrettyBy ( PrettyConfigClassic configName) ( Binding tyname name uni fun ann) Source #
Instance details

Defined in PlutusIR.Core.Instance.Pretty

Methods

prettyBy :: PrettyConfigClassic configName -> Binding tyname name uni fun ann -> Doc ann0 Source #

prettyListBy :: PrettyConfigClassic configName -> [ Binding tyname name uni fun ann] -> Doc ann0 Source #

( PrettyClassicBy configName tyname, PrettyClassicBy configName name, GShow uni, Everywhere uni PrettyConst , Pretty ann) => PrettyBy ( PrettyConfigClassic configName) ( Datatype tyname name uni fun ann) Source #
Instance details

Defined in PlutusIR.Core.Instance.Pretty

Methods

prettyBy :: PrettyConfigClassic configName -> Datatype tyname name uni fun ann -> Doc ann0 Source #

prettyListBy :: PrettyConfigClassic configName -> [ Datatype tyname name uni fun ann] -> Doc ann0 Source #

( PrettyClassicBy configName tyname, PrettyClassicBy configName name, GShow uni, Everywhere uni PrettyConst , Pretty ann) => PrettyBy ( PrettyConfigClassic configName) ( VarDecl tyname name uni fun ann) Source #
Instance details

Defined in PlutusIR.Core.Instance.Pretty

Methods

prettyBy :: PrettyConfigClassic configName -> VarDecl tyname name uni fun ann -> Doc ann0 Source #

prettyListBy :: PrettyConfigClassic configName -> [ VarDecl tyname name uni fun ann] -> Doc ann0 Source #

newtype IgnorePrettyConfig a Source #

A newtype wrapper around a whose point is to provide a PrettyBy config instance for anything that has a Pretty instance.

Instances

Instances details
Pretty a => PrettyBy config ( IgnorePrettyConfig a)
>>> data Cfg = Cfg
>>> data D = D
>>> instance Pretty D where pretty D = "D"
>>> prettyBy Cfg $ IgnorePrettyConfig D
D
Instance details

Defined in Text.PrettyBy.Internal

data AttachPrettyConfig config a Source #

A config together with some value. The point is to provide a Pretty instance for anything that has a PrettyBy config instance.

Constructors

AttachPrettyConfig !config !a

Instances

Instances details
PrettyBy config a => Pretty ( AttachPrettyConfig config a)
>>> data Cfg = Cfg
>>> data D = D
>>> instance PrettyBy Cfg D where prettyBy Cfg D = "D"
>>> pretty $ AttachPrettyConfig Cfg D
D
Instance details

Defined in Text.PrettyBy.Internal

class Render str where Source #

A class for rendering Doc s as string types.

Methods

render :: Doc ann -> str Source #

Render a Doc as a string type.

Instances

Instances details
Render Text
Instance details

Defined in Text.PrettyBy.Default

Render Text
Instance details

Defined in Text.PrettyBy.Default

a ~ Char => Render [a]
Instance details

Defined in Text.PrettyBy.Default

Methods

render :: Doc ann -> [a] Source #

display :: forall str a. ( Pretty a, Render str) => a -> str Source #

Pretty-print and render a value as a string type.

displayBy :: forall str a config. ( PrettyBy config a, Render str) => config -> a -> str Source #

Pretty-print and render a value as a string type in a configurable way.

Defaults

prettyPlcDef :: PrettyPlc a => a -> Doc ann Source #

Pretty-print a value in the default mode using the classic view.

displayPlcDef :: ( PrettyPlc a, Render str) => a -> str Source #

Render a value to String in the default mode using the classic view.

prettyPlcDebug :: PrettyPlc a => a -> Doc ann Source #

Pretty-print a value in the debug mode using the classic view.

displayPlcDebug :: ( PrettyPlc a, Render str) => a -> str Source #

Render a value to String in the debug mode using the classic view.

Global configuration

newtype PrettyConfigPlcOptions Source #

Options for pretty-printing PLC entities.

data PrettyConfigPlc Source #

Global configuration used for pretty-printing PLC entities.

Instances

Instances details
HasPrettyConfigName PrettyConfigPlc Source #
Instance details

Defined in PlutusCore.Pretty.Plc

PrettyBy PrettyConfigPlc DefaultFun Source #
Instance details

Defined in PlutusCore.Default.Builtins

DefaultPrettyPlcStrategy a => PrettyBy PrettyConfigPlc ( PrettyAny a) Source #
Instance details

Defined in PlutusCore.Pretty.Plc

DefaultPrettyPlcStrategy ( Kind ann) => PrettyBy PrettyConfigPlc ( Kind ann) Source #
Instance details

Defined in PlutusCore.Core.Instance.Pretty.Plc

( Closed uni, GShow uni, Everywhere uni PrettyConst , Pretty fun) => PrettyBy PrettyConfigPlc ( CkValue uni fun) Source #
Instance details

Defined in PlutusCore.Evaluation.Machine.Ck

( Closed uni, GShow uni, Everywhere uni PrettyConst , Pretty fun) => PrettyBy PrettyConfigPlc ( CekValue uni fun) Source #
Instance details

Defined in UntypedPlutusCore.Evaluation.Machine.Cek.Internal

PrettyUni uni ann => PrettyBy PrettyConfigPlc ( TypeErrorExt uni ann) Source #
Instance details

Defined in PlutusIR.Error

DefaultPrettyPlcStrategy ( Type tyname uni ann) => PrettyBy PrettyConfigPlc ( Type tyname uni ann) Source #
Instance details

Defined in PlutusCore.Core.Instance.Pretty.Plc

( GShow uni, Closed uni, Everywhere uni PrettyConst , Pretty fun, Pretty ann) => PrettyBy PrettyConfigPlc ( Error uni fun ann) Source #
Instance details

Defined in PlutusCore.Error

( GShow uni, Closed uni, Everywhere uni PrettyConst , Pretty fun, Pretty ann) => PrettyBy PrettyConfigPlc ( Error uni fun ann) Source #
Instance details

Defined in PlutusIR.Error

( GShow uni, Closed uni, Everywhere uni PrettyConst , Pretty ann, Pretty fun, Pretty term) => PrettyBy PrettyConfigPlc ( TypeError term uni fun ann) Source #
Instance details

Defined in PlutusCore.Error

DefaultPrettyPlcStrategy ( Program name uni fun ann) => PrettyBy PrettyConfigPlc ( Program name uni fun ann) Source #
Instance details

Defined in UntypedPlutusCore.Core.Instance.Pretty.Plc

DefaultPrettyPlcStrategy ( Term name uni fun ann) => PrettyBy PrettyConfigPlc ( Term name uni fun ann) Source #
Instance details

Defined in UntypedPlutusCore.Core.Instance.Pretty.Plc

DefaultPrettyPlcStrategy ( Program tyname name uni fun ann) => PrettyBy PrettyConfigPlc ( Program tyname name uni fun ann) Source #
Instance details

Defined in PlutusCore.Core.Instance.Pretty.Plc

Methods

prettyBy :: PrettyConfigPlc -> Program tyname name uni fun ann -> Doc ann0 Source #

prettyListBy :: PrettyConfigPlc -> [ Program tyname name uni fun ann] -> Doc ann0 Source #

DefaultPrettyPlcStrategy ( Term tyname name uni fun ann) => PrettyBy PrettyConfigPlc ( Term tyname name uni fun ann) Source #
Instance details

Defined in PlutusCore.Core.Instance.Pretty.Plc

Methods

prettyBy :: PrettyConfigPlc -> Term tyname name uni fun ann -> Doc ann0 Source #

prettyListBy :: PrettyConfigPlc -> [ Term tyname name uni fun ann] -> Doc ann0 Source #

type HasPrettyDefaults PrettyConfigPlc Source #
Instance details

Defined in PlutusCore.Pretty.Plc

type PrettyPlc = PrettyBy PrettyConfigPlc Source #

The "pretty-printable PLC entity" constraint.

defPrettyConfigPlcClassic :: PrettyConfigPlcOptions -> PrettyConfigPlc Source #

The PrettyConfigPlc used by default: use the classic view and print neither Unique s, nor name attachments.

debugPrettyConfigPlcClassic :: PrettyConfigPlcOptions -> PrettyConfigPlc Source #

The PrettyConfigPlc used for debugging: use the classic view and print Unique s, but not name attachments.

defPrettyConfigPlcReadable :: PrettyConfigPlcOptions -> PrettyConfigPlc Source #

The PrettyConfigPlc used by default and for readability: use the refined view and print neither Unique s, nor name attachments.

debugPrettyConfigPlcReadable :: PrettyConfigPlcOptions -> PrettyConfigPlc Source #

The PrettyConfigPlc used for debugging and readability: use the refined view and print Unique s, but not name attachments.

Custom functions for PLC types.

prettyPlcClassicDef :: PrettyPlc a => a -> Doc ann Source #

Pretty-print a PLC value in the default mode using the classic view.

prettyPlcClassicDebug :: PrettyPlc a => a -> Doc ann Source #

Pretty-print a PLC value in the debug mode using the classic view.

prettyPlcReadableDef :: PrettyPlc a => a -> Doc ann Source #

Pretty-print a PLC value in the default mode using the readable view.

prettyPlcReadableDebug :: PrettyPlc a => a -> Doc ann Source #

Pretty-print a PLC value in the debug mode using the readable view.

prettyPlcCondensedErrorBy :: PrettyPlc a => ( PrettyConfigPlcOptions -> PrettyConfigPlc ) -> a -> Doc ann Source #

Pretty-print a PLC value using the condensed way (see CondensedErrors ) of pretty-printing PLC errors (in case there are any).

displayPlcCondensedErrorClassic :: ( PrettyPlc a, Render str) => a -> str Source #

Render an error to String in the condensed manner using the classic view.

Names

newtype PrettyConfigName Source #

A config that determines how to pretty-print a PLC name.

Constructors

PrettyConfigName

Fields

defPrettyConfigName :: PrettyConfigName Source #

The PrettyConfigName used by default: print neither Unique s, nor name attachments.

debugPrettyConfigName :: PrettyConfigName Source #

The PrettyConfigName used for debugging: print Unique s, but not name attachments.

Classic view

data PrettyConfigClassic configName Source #

Configuration for the classic pretty-printing.

Constructors

PrettyConfigClassic

Fields

Instances

Instances details
configName ~ PrettyConfigName => HasPrettyConfigName ( PrettyConfigClassic configName) Source #
Instance details

Defined in PlutusCore.Pretty.Classic

PrettyBy ( PrettyConfigClassic configName) Strictness Source #
Instance details

Defined in PlutusIR.Core.Instance.Pretty

PrettyBy ( PrettyConfigClassic configName) Recursivity Source #
Instance details

Defined in PlutusIR.Core.Instance.Pretty

Pretty ann => PrettyBy ( PrettyConfigClassic configName) ( Kind ann) Source #
Instance details

Defined in PlutusCore.Core.Instance.Pretty.Classic

( PrettyClassicBy configName tyname, Pretty ann) => PrettyBy ( PrettyConfigClassic configName) ( TyVarDecl tyname ann) Source #
Instance details

Defined in PlutusIR.Core.Instance.Pretty

( PrettyClassicBy configName tyname, GShow uni, Pretty ann) => PrettyBy ( PrettyConfigClassic configName) ( Type tyname uni ann) Source #
Instance details

Defined in PlutusCore.Core.Instance.Pretty.Classic

Methods

prettyBy :: PrettyConfigClassic configName -> Type tyname uni ann -> Doc ann0 Source #

prettyListBy :: PrettyConfigClassic configName -> [ Type tyname uni ann] -> Doc ann0 Source #

( PrettyClassicBy configName ( Term name uni fun ann), Pretty ann) => PrettyBy ( PrettyConfigClassic configName) ( Program name uni fun ann) Source #
Instance details

Defined in UntypedPlutusCore.Core.Instance.Pretty.Classic

Methods

prettyBy :: PrettyConfigClassic configName -> Program name uni fun ann -> Doc ann0 Source #

prettyListBy :: PrettyConfigClassic configName -> [ Program name uni fun ann] -> Doc ann0 Source #

( PrettyClassicBy configName name, GShow uni, Closed uni, Everywhere uni PrettyConst , Pretty fun, Pretty ann) => PrettyBy ( PrettyConfigClassic configName) ( Term name uni fun ann) Source #
Instance details

Defined in UntypedPlutusCore.Core.Instance.Pretty.Classic

Methods

prettyBy :: PrettyConfigClassic configName -> Term name uni fun ann -> Doc ann0 Source #

prettyListBy :: PrettyConfigClassic configName -> [ Term name uni fun ann] -> Doc ann0 Source #

( PrettyClassicBy configName ( Term tyname name uni fun ann), Pretty ann) => PrettyBy ( PrettyConfigClassic configName) ( Program tyname name uni fun ann) Source #
Instance details

Defined in PlutusCore.Core.Instance.Pretty.Classic

Methods

prettyBy :: PrettyConfigClassic configName -> Program tyname name uni fun ann -> Doc ann0 Source #

prettyListBy :: PrettyConfigClassic configName -> [ Program tyname name uni fun ann] -> Doc ann0 Source #

( PrettyClassicBy configName tyname, PrettyClassicBy configName name, GShow uni, Closed uni, Everywhere uni PrettyConst , Pretty fun, Pretty ann) => PrettyBy ( PrettyConfigClassic configName) ( Term tyname name uni fun ann) Source #
Instance details

Defined in PlutusCore.Core.Instance.Pretty.Classic

Methods

prettyBy :: PrettyConfigClassic configName -> Term tyname name uni fun ann -> Doc ann0 Source #

prettyListBy :: PrettyConfigClassic configName -> [ Term tyname name uni fun ann] -> Doc ann0 Source #

( PrettyClassicBy configName tyname, PrettyClassicBy configName name, GShow uni, Closed uni, Everywhere uni PrettyConst , Pretty fun, Pretty ann) => PrettyBy ( PrettyConfigClassic configName) ( Program tyname name uni fun ann) Source #
Instance details

Defined in PlutusIR.Core.Instance.Pretty

Methods

prettyBy :: PrettyConfigClassic configName -> Program tyname name uni fun ann -> Doc ann0 Source #

prettyListBy :: PrettyConfigClassic configName -> [ Program tyname name uni fun ann] -> Doc ann0 Source #

( PrettyClassicBy configName tyname, PrettyClassicBy configName name, GShow uni, Closed uni, Everywhere uni PrettyConst , Pretty fun, Pretty ann) => PrettyBy ( PrettyConfigClassic configName) ( Term tyname name uni fun ann) Source #
Instance details

Defined in PlutusIR.Core.Instance.Pretty

Methods

prettyBy :: PrettyConfigClassic configName -> Term tyname name uni fun ann -> Doc ann0 Source #

prettyListBy :: PrettyConfigClassic configName -> [ Term tyname name uni fun ann] -> Doc ann0 Source #

( PrettyClassicBy configName tyname, PrettyClassicBy configName name, GShow uni, Closed uni, Everywhere uni PrettyConst , Pretty fun, Pretty ann) => PrettyBy ( PrettyConfigClassic configName) ( Binding tyname name uni fun ann) Source #
Instance details

Defined in PlutusIR.Core.Instance.Pretty

Methods

prettyBy :: PrettyConfigClassic configName -> Binding tyname name uni fun ann -> Doc ann0 Source #

prettyListBy :: PrettyConfigClassic configName -> [ Binding tyname name uni fun ann] -> Doc ann0 Source #

( PrettyClassicBy configName tyname, PrettyClassicBy configName name, GShow uni, Everywhere uni PrettyConst , Pretty ann) => PrettyBy ( PrettyConfigClassic configName) ( Datatype tyname name uni fun ann) Source #
Instance details

Defined in PlutusIR.Core.Instance.Pretty

Methods

prettyBy :: PrettyConfigClassic configName -> Datatype tyname name uni fun ann -> Doc ann0 Source #

prettyListBy :: PrettyConfigClassic configName -> [ Datatype tyname name uni fun ann] -> Doc ann0 Source #

( PrettyClassicBy configName tyname, PrettyClassicBy configName name, GShow uni, Everywhere uni PrettyConst , Pretty ann) => PrettyBy ( PrettyConfigClassic configName) ( VarDecl tyname name uni fun ann) Source #
Instance details

Defined in PlutusIR.Core.Instance.Pretty

Methods

prettyBy :: PrettyConfigClassic configName -> VarDecl tyname name uni fun ann -> Doc ann0 Source #

prettyListBy :: PrettyConfigClassic configName -> [ VarDecl tyname name uni fun ann] -> Doc ann0 Source #

type HasPrettyDefaults ( PrettyConfigClassic _1) Source #
Instance details

Defined in PlutusCore.Pretty.Classic

type PrettyClassicBy configName = PrettyBy ( PrettyConfigClassic configName) Source #

The "classically pretty-printable" constraint.

consAnnIf :: Pretty ann => PrettyConfigClassic configName -> ann -> [ Doc dann] -> [ Doc dann] Source #

Add a pretty-printed annotation to a list of Doc s if the given config enables pretty-printing of annotations.

prettyClassicDef :: PrettyClassic a => a -> Doc ann Source #

Pretty-print a value in the default mode using the classic view.

prettyClassicDebug :: PrettyClassic a => a -> Doc ann Source #

Pretty-print a value in the debug mode using the classic view.

Readable view

data PrettyConfigReadable configName Source #

Configuration for the readable pretty-printing.

Instances

Instances details
HasRenderContext ( PrettyConfigReadable configName) Source #
Instance details

Defined in PlutusCore.Pretty.Readable

configName ~ PrettyConfigName => HasPrettyConfigName ( PrettyConfigReadable configName) Source #
Instance details

Defined in PlutusCore.Pretty.Readable

PrettyBy ( PrettyConfigReadable configName) ( Kind a) Source #
Instance details

Defined in PlutusCore.Core.Instance.Pretty.Readable

( PrettyReadableBy configName tyname, GShow uni) => PrettyBy ( PrettyConfigReadable configName) ( Type tyname uni a) Source #
Instance details

Defined in PlutusCore.Core.Instance.Pretty.Readable

PrettyReadableBy configName ( Term name uni fun a) => PrettyBy ( PrettyConfigReadable configName) ( Program name uni fun a) Source #
Instance details

Defined in UntypedPlutusCore.Core.Instance.Pretty.Readable

( PrettyReadableBy configName name, GShow uni, Closed uni, Everywhere uni PrettyConst , Pretty fun) => PrettyBy ( PrettyConfigReadable configName) ( Term name uni fun a) Source #
Instance details

Defined in UntypedPlutusCore.Core.Instance.Pretty.Readable

Methods

prettyBy :: PrettyConfigReadable configName -> Term name uni fun a -> Doc ann Source #

prettyListBy :: PrettyConfigReadable configName -> [ Term name uni fun a] -> Doc ann Source #

PrettyReadableBy configName ( Term tyname name uni fun a) => PrettyBy ( PrettyConfigReadable configName) ( Program tyname name uni fun a) Source #
Instance details

Defined in PlutusCore.Core.Instance.Pretty.Readable

Methods

prettyBy :: PrettyConfigReadable configName -> Program tyname name uni fun a -> Doc ann Source #

prettyListBy :: PrettyConfigReadable configName -> [ Program tyname name uni fun a] -> Doc ann Source #

( PrettyReadableBy configName tyname, PrettyReadableBy configName name, GShow uni, Closed uni, Everywhere uni PrettyConst , Pretty fun) => PrettyBy ( PrettyConfigReadable configName) ( Term tyname name uni fun a) Source #
Instance details

Defined in PlutusCore.Core.Instance.Pretty.Readable

Methods

prettyBy :: PrettyConfigReadable configName -> Term tyname name uni fun a -> Doc ann Source #

prettyListBy :: PrettyConfigReadable configName -> [ Term tyname name uni fun a] -> Doc ann Source #

type HasPrettyDefaults ( PrettyConfigReadable _1) Source #
Instance details

Defined in PlutusCore.Pretty.Readable

type PrettyReadableBy configName = PrettyBy ( PrettyConfigReadable configName) Source #

The "readably pretty-printable" constraint.

Utils

data ConstConfig Source #

Constructors

ConstConfig

Instances

Instances details
PrettyBy ConstConfig ByteString Source #
Instance details

Defined in PlutusCore.Pretty.PrettyConst

PrettyBy ConstConfig Data Source #
Instance details

Defined in PlutusCore.Pretty.PrettyConst

NonDefaultPrettyBy ConstConfig Bool Source #
Instance details

Defined in PlutusCore.Pretty.PrettyConst

NonDefaultPrettyBy ConstConfig Integer Source #
Instance details

Defined in PlutusCore.Pretty.PrettyConst

NonDefaultPrettyBy ConstConfig () Source #
Instance details

Defined in PlutusCore.Pretty.PrettyConst

NonDefaultPrettyBy ConstConfig Text Source #
Instance details

Defined in PlutusCore.Pretty.PrettyConst

DefaultPrettyBy ConstConfig ( PrettyAny a) => PrettyBy ConstConfig ( PrettyAny a) Source #
Instance details

Defined in PlutusCore.Pretty.PrettyConst

Show a => DefaultPrettyBy ConstConfig ( PrettyAny a) Source #
Instance details

Defined in PlutusCore.Pretty.PrettyConst

PrettyConst a => NonDefaultPrettyBy ConstConfig [a] Source #
Instance details

Defined in PlutusCore.Pretty.PrettyConst

DefaultPrettyBy ConstConfig ( PrettyAny a) => NonDefaultPrettyBy ConstConfig ( PrettyAny a) Source #
Instance details

Defined in PlutusCore.Pretty.PrettyConst

( PrettyConst a, PrettyConst b) => NonDefaultPrettyBy ConstConfig (a, b) Source #
Instance details

Defined in PlutusCore.Pretty.PrettyConst

type HasPrettyDefaults ConstConfig Source #
Instance details

Defined in PlutusCore.Pretty.PrettyConst