cryptol-2.3.0: Cryptol: The Language of Cryptography

Copyright(c) 2013-2016 Galois, Inc.
LicenseBSD3
Maintainercryptol@galois.com
Stabilityprovisional
Portabilityportable
Safe HaskellSafe
LanguageHaskell98

Cryptol.Utils.PP

Description

 

Synopsis

Documentation

data NameDisp Source

How to display names, inspired by the GHC Outputable module. Getting a value of Nothing from the NameDisp function indicates that the name is not in scope.

neverQualifyMod :: ModName -> NameDisp Source

Never qualify names from this module.

extend :: NameDisp -> NameDisp -> NameDisp Source

Compose two naming environments, preferring names from the left environment.

getNameFormat :: ModName -> Ident -> NameDisp -> NameFormat Source

Get the format for a name. When Nothing is returned, the name is not currently in scope.

withNameDisp :: (NameDisp -> Doc) -> Doc Source

Produce a document in the context of the current NameDisp.

fixNameDisp :: NameDisp -> Doc -> Doc Source

Fix the way that names are displayed inside of a doc.

class PP a where Source

Methods

ppPrec :: Int -> a -> Doc Source

Instances

PP Text Source 
PP Ident Source 
PP Range Source 
PP Position Source 
PP Token Source 
PP Name Source 
PP PName Source 
PP TFun Source 
PP Kind Source 
PP Selector Source 
PP Literal Source 
PP Pragma Source 
PP ImportSpec Source 
PP Import Source 
PP Decl Source 
PP DeclGroup Source 
PP Match Source 
PP Expr Source 
PP UserTC Source 
PP TC Source 
PP PC Source 
PP TCon Source 
PP TVar Source 
PP Type Source 
PP TParam Source 
PP TySyn Source 
PP Schema Source 
PP Kind Source 
PP Module Source 
PP EvalError Source 
PP Subst Source 
PP Error Source 
PP TyFunName Source 
PP ConstraintSource Source 
PP Error Source 
PP Warning Source 
PP Solved Source 
PP ParseError Source 
PP RenamerWarning Source 
PP RenamerError Source 
PP ModuleWarning Source 
PP ModuleError Source 
PP ImportSource Source 
PP Smoke Source 
PP REPLException Source 
PP a => PP (Located a) Source 
PP (WithNames DeclDef) Source 
PP (WithNames Decl) Source 
PP (WithNames DeclGroup) Source 
PP (WithNames Match) Source 
PP (WithNames Expr) Source 
PP (WithNames TVar) Source 
PP (WithNames Type) Source 
PP (WithNames TParam) Source 
PP (WithNames TySyn) Source 
PP (WithNames Schema) Source 
PP (WithNames Module) Source 
PP (WithNames Subst) Source 
PP (WithNames Error) Source 
PP (WithNames Warning) Source 
PP (WithNames DelayedCt) Source 
PP (WithNames Goal) Source 
PPName name => PP (Prop name) Source 
PPName name => PP (Type name) Source 
PPName name => PP (TParam name) Source 
PPName name => PP (Schema name) Source 
PPName name => PP (Pattern name) Source 
(Show name, PPName name) => PP (Match name) Source 
PPName name => PP (TypeInst name) Source 
(Show name, PPName name) => PP (Expr name) Source 
PP a => PP (TopLevel a) Source 
PPName name => PP (Newtype name) Source 
(Show name, PPName name) => PP (BindDef name) Source 
(Show name, PPName name) => PP (Bind name) Source 
PPName name => PP (TySyn name) Source 
(Show name, PPName name) => PP (Decl name) Source 
(Show name, PPName name) => PP (TopDecl name) Source 
(Show name, PPName name) => PP (Module name) Source 
(Show name, PPName name) => PP (Program name) Source 
PP (WithBase Value) Source 
PP (WithBase EvalEnv) Source 

class PP a => PPName a where Source

Methods

ppPrefixName :: a -> Doc Source

Print a name in prefix: f a b or (+) a b)

ppInfixName :: a -> Doc Source

Print a name as an infix operator: a + b

pp :: PP a => a -> Doc Source

pretty :: PP a => a -> String Source

data Assoc Source

Information about associativity.

Constructors

LeftAssoc 
RightAssoc 
NonAssoc 

data Infix op thing Source

Information about an infix expression of some sort.

Constructors

Infix 

Fields

ieOp :: op

operator

ieLeft :: thing

left argument

ieRight :: thing

right argumrnt

iePrec :: Int

operator precedence

ieAssoc :: Assoc

operator associativity

ppInfix Source

Arguments

:: (PP thing, PP op) 
=> Int

Non-infix leaves are printed with this precedence

-> (thing -> Maybe (Infix op thing))

pattern to check if sub-thing is also infix

-> Infix op thing

Pretty print this infix expression

-> Doc 

Pretty print an infix expression of some sort.

ordinal :: (Integral a, Show a, Eq a) => a -> Doc Source

Display a numeric values as an ordinar (e.g., 2nd)

ordSuffix :: (Integral a, Eq a) => a -> String Source

The suffix to use when displaying a number as an oridinal

liftPJ1 :: (Doc -> Doc) -> Doc -> Doc Source

liftPJ2 :: (Doc -> Doc -> Doc) -> Doc -> Doc -> Doc Source

liftSep :: ([Doc] -> Doc) -> [Doc] -> Doc Source

(<>) :: Doc -> Doc -> Doc infixl 6 Source

(<+>) :: Doc -> Doc -> Doc infixl 6 Source

($$) :: Doc -> Doc -> Doc infixl 5 Source

sep :: [Doc] -> Doc Source

fsep :: [Doc] -> Doc Source

hsep :: [Doc] -> Doc Source

hcat :: [Doc] -> Doc Source

vcat :: [Doc] -> Doc Source

hang :: Doc -> Int -> Doc -> Doc Source

nest :: Int -> Doc -> Doc Source

punctuate :: Doc -> [Doc] -> [Doc] Source