clash-lib-1.2.5: CAES Language for Synchronous Hardware - As a Library
Copyright(C) 2012-2016 University of Twente
2016 Myrtle Software Ltd
LicenseBSD2 (see the file LICENSE)
MaintainerChristiaan Baaij <christiaan.baaij@gmail.com>
Safe HaskellNone
LanguageHaskell2010

Clash.Core.Pretty

Description

PrettyPrec printing class and instances for CoreHW

Synopsis

Documentation

class PrettyPrec p where Source #

PrettyPrec printing Show-like typeclass

Minimal complete definition

pprPrec

Methods

pprPrec :: Monad m => Rational -> p -> m ClashDoc Source #

pprPrec' :: Monad m => PrettyOptions -> Rational -> p -> m ClashDoc Source #

Instances

Instances details
PrettyPrec Text Source # 
Instance details

Defined in Clash.Core.Pretty

PrettyPrec SrcSpan Source # 
Instance details

Defined in Clash.Core.Pretty

PrettyPrec TyCon Source # 
Instance details

Defined in Clash.Core.Pretty

PrettyPrec Type Source # 
Instance details

Defined in Clash.Core.Pretty

PrettyPrec Term Source # 
Instance details

Defined in Clash.Core.Pretty

PrettyPrec DataCon Source # 
Instance details

Defined in Clash.Core.Pretty

PrettyPrec Literal Source # 
Instance details

Defined in Clash.Core.Pretty

PrettyPrec LitTy Source # 
Instance details

Defined in Clash.Core.Pretty

PrettyPrec Pat Source # 
Instance details

Defined in Clash.Core.Pretty

PrettyPrec TickInfo Source # 
Instance details

Defined in Clash.Core.Pretty

PrettyPrec a => PrettyPrec [a] Source # 
Instance details

Defined in Clash.Core.Pretty

Methods

pprPrec :: Monad m => Rational -> [a] -> m ClashDoc Source #

pprPrec' :: Monad m => PrettyOptions -> Rational -> [a] -> m ClashDoc Source #

PrettyPrec (Name a) Source # 
Instance details

Defined in Clash.Core.Pretty

PrettyPrec (Var a) Source # 
Instance details

Defined in Clash.Core.Pretty

PrettyPrec (Id, Term) Source # 
Instance details

Defined in Clash.Core.Pretty

data PrettyOptions Source #

Options for the pretty-printer, controlling which elements to hide.

Constructors

PrettyOptions 

Fields

Instances

Instances details
Default PrettyOptions Source # 
Instance details

Defined in Clash.Core.Pretty

Methods

def :: PrettyOptions #

type ClashDoc = Doc ClashAnnotation Source #

Clash's specialized Doc type holds metadata of type ClashAnnotation.

data ClashAnnotation Source #

Annotations carried on pretty-printed code.

Constructors

AnnContext CoreContext

marking navigation to a different context

AnnSyntax SyntaxElement

marking a specific sort of syntax

Instances

Instances details
Eq ClashAnnotation Source # 
Instance details

Defined in Clash.Core.Pretty

data SyntaxElement Source #

Specific places in the program syntax.

Constructors

Keyword 
LitS 
Type 
Unique 
Qualifier 

Instances

Instances details
Eq SyntaxElement Source # 
Instance details

Defined in Clash.Core.Pretty

Show SyntaxElement Source # 
Instance details

Defined in Clash.Core.Pretty

showPpr :: PrettyPrec p => p -> String Source #

Print a PrettyPrec thing to a String

tracePprId :: PrettyPrec p => p -> p Source #

tracePpr :: PrettyPrec p => p -> a -> a Source #

fromPpr :: PrettyPrec a => a -> Doc () Source #

Orphan instances

Pretty LitTy Source # 
Instance details

Methods

pretty :: LitTy -> Doc ann #

prettyList :: [LitTy] -> Doc ann #

ClashPretty Type Source # 
Instance details

Methods

clashPretty :: Type -> Doc () Source #

ClashPretty Term Source # 
Instance details

Methods

clashPretty :: Term -> Doc () Source #

ClashPretty (Name a) Source # 
Instance details

Methods

clashPretty :: Name a -> Doc () Source #

ClashPretty (Var a) Source # 
Instance details

Methods

clashPretty :: Var a -> Doc () Source #