futhark-0.19.2: An optimising compiler for a functional, array-oriented language.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Futhark.IR.Pretty

Description

Futhark prettyprinter. This module defines Pretty instances for the AST defined in Futhark.IR.Syntax, but also a number of convenience functions if you don't want to use the interface from Pretty.

Synopsis

Documentation

prettyTuple :: Pretty a => [a] -> String Source #

Prettyprint a list enclosed in curly braces.

pretty :: Pretty a => a -> String Source #

Prettyprint a value, wrapped to 80 characters.

class (Decorations lore, Pretty (RetType lore), Pretty (BranchType lore), Pretty (FParamInfo lore), Pretty (LParamInfo lore), Pretty (LetDec lore), Pretty (Op lore)) => PrettyLore lore where Source #

The class of lores whose annotations can be prettyprinted.

Minimal complete definition

Nothing

Methods

ppExpLore :: ExpDec lore -> Exp lore -> Maybe Doc Source #

Instances

Instances details
PrettyLore Seq Source # 
Instance details

Defined in Futhark.IR.Seq

PrettyLore SOACS Source # 
Instance details

Defined in Futhark.IR.SOACS

PrettyLore MCMem Source # 
Instance details

Defined in Futhark.IR.MCMem

PrettyLore MC Source # 
Instance details

Defined in Futhark.IR.MC

PrettyLore SeqMem Source # 
Instance details

Defined in Futhark.IR.SeqMem

PrettyLore Kernels Source # 
Instance details

Defined in Futhark.IR.Kernels

PrettyLore KernelsMem Source # 
Instance details

Defined in Futhark.IR.KernelsMem

(ASTLore lore, CanBeAliased (Op lore)) => PrettyLore (Aliases lore) Source # 
Instance details

Defined in Futhark.IR.Aliases

Methods

ppExpLore :: ExpDec (Aliases lore) -> Exp (Aliases lore) -> Maybe Doc Source #

(PrettyLore lore, CanBeWise (Op lore)) => PrettyLore (Wise lore) Source # 
Instance details

Defined in Futhark.Optimise.Simplify.Lore

Methods

ppExpLore :: ExpDec (Wise lore) -> Exp (Wise lore) -> Maybe Doc Source #

ppTuple' :: Pretty a => [a] -> Doc Source #

Like prettyTuple, but produces a Doc.

Orphan instances

Pretty VName Source # 
Instance details

Methods

ppr :: VName -> Doc #

pprPrec :: Int -> VName -> Doc #

pprList :: [VName] -> Doc #

Pretty Commutativity Source # 
Instance details

Pretty SubExp Source # 
Instance details

Methods

ppr :: SubExp -> Doc #

pprPrec :: Int -> SubExp -> Doc #

pprList :: [SubExp] -> Doc #

Pretty Certificates Source # 
Instance details

Pretty Ident Source # 
Instance details

Methods

ppr :: Ident -> Doc #

pprPrec :: Int -> Ident -> Doc #

pprList :: [Ident] -> Doc #

Pretty NoUniqueness Source # 
Instance details

Pretty Space Source # 
Instance details

Methods

ppr :: Space -> Doc #

pprPrec :: Int -> Space -> Doc #

pprList :: [Space] -> Doc #

Pretty ExtShape Source # 
Instance details

Methods

ppr :: ExtShape -> Doc #

pprPrec :: Int -> ExtShape -> Doc #

pprList :: [ExtShape] -> Doc #

Pretty Shape Source # 
Instance details

Methods

ppr :: Shape -> Doc #

pprPrec :: Int -> Shape -> Doc #

pprList :: [Shape] -> Doc #

Pretty EntryPointType Source # 
Instance details

Pretty BasicOp Source # 
Instance details

Methods

ppr :: BasicOp -> Doc #

pprPrec :: Int -> BasicOp -> Doc #

pprList :: [BasicOp] -> Doc #

Pretty Attr Source # 
Instance details

Methods

ppr :: Attr -> Doc #

pprPrec :: Int -> Attr -> Doc #

pprList :: [Attr] -> Doc #

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

Methods

ppr :: ErrorMsg a -> Doc #

pprPrec :: Int -> ErrorMsg a -> Doc #

pprList :: [ErrorMsg a] -> Doc #

Pretty t => Pretty (PatElemT t) Source # 
Instance details

Methods

ppr :: PatElemT t -> Doc #

pprPrec :: Int -> PatElemT t -> Doc #

pprList :: [PatElemT t] -> Doc #

Pretty d => Pretty (DimIndex d) Source # 
Instance details

Methods

ppr :: DimIndex d -> Doc #

pprPrec :: Int -> DimIndex d -> Doc #

pprList :: [DimIndex d] -> Doc #

Pretty t => Pretty (Param t) Source # 
Instance details

Methods

ppr :: Param t -> Doc #

pprPrec :: Int -> Param t -> Doc #

pprList :: [Param t] -> Doc #

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

Methods

ppr :: Ext a -> Doc #

pprPrec :: Int -> Ext a -> Doc #

pprList :: [Ext a] -> Doc #

PrettyLore lore => Pretty (Prog lore) Source # 
Instance details

Methods

ppr :: Prog lore -> Doc #

pprPrec :: Int -> Prog lore -> Doc #

pprList :: [Prog lore] -> Doc #

PrettyLore lore => Pretty (FunDef lore) Source # 
Instance details

Methods

ppr :: FunDef lore -> Doc #

pprPrec :: Int -> FunDef lore -> Doc #

pprList :: [FunDef lore] -> Doc #

PrettyLore lore => Pretty (Lambda lore) Source # 
Instance details

Methods

ppr :: Lambda lore -> Doc #

pprPrec :: Int -> Lambda lore -> Doc #

pprList :: [Lambda lore] -> Doc #

PrettyLore lore => Pretty (Exp lore) Source # 
Instance details

Methods

ppr :: Exp lore -> Doc #

pprPrec :: Int -> Exp lore -> Doc #

pprList :: [Exp lore] -> Doc #

Pretty d => Pretty (DimChange d) Source # 
Instance details

Methods

ppr :: DimChange d -> Doc #

pprPrec :: Int -> DimChange d -> Doc #

pprList :: [DimChange d] -> Doc #

PrettyLore lore => Pretty (Body lore) Source # 
Instance details

Methods

ppr :: Body lore -> Doc #

pprPrec :: Int -> Body lore -> Doc #

pprList :: [Body lore] -> Doc #

PrettyLore lore => Pretty (Stms lore) Source # 
Instance details

Methods

ppr :: Stms lore -> Doc #

pprPrec :: Int -> Stms lore -> Doc #

pprList :: [Stms lore] -> Doc #

PrettyLore lore => Pretty (Stm lore) Source # 
Instance details

Methods

ppr :: Stm lore -> Doc #

pprPrec :: Int -> Stm lore -> Doc #

pprList :: [Stm lore] -> Doc #

Pretty (PatElemT dec) => Pretty (PatternT dec) Source # 
Instance details

Methods

ppr :: PatternT dec -> Doc #

pprPrec :: Int -> PatternT dec -> Doc #

pprList :: [PatternT dec] -> Doc #

Pretty u => Pretty (TypeBase Rank u) Source # 
Instance details

Methods

ppr :: TypeBase Rank u -> Doc #

pprPrec :: Int -> TypeBase Rank u -> Doc #

pprList :: [TypeBase Rank u] -> Doc #

Pretty u => Pretty (TypeBase ExtShape u) Source # 
Instance details

Pretty u => Pretty (TypeBase Shape u) Source # 
Instance details

Methods

ppr :: TypeBase Shape u -> Doc #

pprPrec :: Int -> TypeBase Shape u -> Doc #

pprList :: [TypeBase Shape u] -> Doc #