cryptol-2.4.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.

Instances

Show NameDisp Source # 
Generic NameDisp Source # 

Associated Types

type Rep NameDisp :: * -> * #

Methods

from :: NameDisp -> Rep NameDisp x #

to :: Rep NameDisp x -> NameDisp #

Monoid NameDisp Source # 
NFData NameDisp Source # 

Methods

rnf :: NameDisp -> () #

type Rep NameDisp Source # 
type Rep NameDisp = D1 (MetaData "NameDisp" "Cryptol.Utils.PP" "cryptol-2.4.0-AtabUoGsZJn8kSvO8P84NP" False) ((:+:) (C1 (MetaCons "EmptyNameDisp" PrefixI False) U1) (C1 (MetaCons "NameDisp" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (ModName -> Ident -> Maybe NameFormat)))))

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.

newtype Doc Source #

Constructors

Doc (NameDisp -> Doc) 

Instances

Show Doc Source # 

Methods

showsPrec :: Int -> Doc -> ShowS #

show :: Doc -> String #

showList :: [Doc] -> ShowS #

IsString Doc Source # 

Methods

fromString :: String -> Doc #

Generic Doc Source # 

Associated Types

type Rep Doc :: * -> * #

Methods

from :: Doc -> Rep Doc x #

to :: Rep Doc x -> Doc #

Monoid Doc Source # 

Methods

mempty :: Doc #

mappend :: Doc -> Doc -> Doc #

mconcat :: [Doc] -> Doc #

NFData Doc Source # 

Methods

rnf :: Doc -> () #

DebugLog Doc Source # 

Methods

debugLog :: Solver -> Doc -> IO () Source #

debugLogList :: Solver -> [Doc] -> IO () Source #

type Rep Doc Source # 
type Rep Doc = D1 (MetaData "Doc" "Cryptol.Utils.PP" "cryptol-2.4.0-AtabUoGsZJn8kSvO8P84NP" True) (C1 (MetaCons "Doc" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NameDisp -> Doc))))

class PP a where Source #

Minimal complete definition

ppPrec

Methods

ppPrec :: Int -> a -> Doc Source #

Instances

PP Text Source # 

Methods

ppPrec :: Int -> Text -> Doc Source #

PP Ident Source # 

Methods

ppPrec :: Int -> Ident -> Doc Source #

PP Range Source # 

Methods

ppPrec :: Int -> Range -> Doc Source #

PP Position Source # 

Methods

ppPrec :: Int -> Position -> Doc Source #

PP Token Source # 

Methods

ppPrec :: Int -> Token -> Doc Source #

PP PName Source # 

Methods

ppPrec :: Int -> PName -> Doc Source #

PP TFun Source # 

Methods

ppPrec :: Int -> TFun -> Doc Source #

PP Kind Source # 

Methods

ppPrec :: Int -> Kind -> Doc Source #

PP Selector Source # 

Methods

ppPrec :: Int -> Selector -> Doc Source #

PP Literal Source # 

Methods

ppPrec :: Int -> Literal -> Doc Source #

PP Pragma Source # 

Methods

ppPrec :: Int -> Pragma -> Doc Source #

PP ImportSpec Source # 

Methods

ppPrec :: Int -> ImportSpec -> Doc Source #

PP Import Source # 

Methods

ppPrec :: Int -> Import -> Doc Source #

PP Name Source # 

Methods

ppPrec :: Int -> Name -> Doc Source #

PP Decl Source # 

Methods

ppPrec :: Int -> Decl -> Doc Source #

PP DeclGroup Source # 

Methods

ppPrec :: Int -> DeclGroup -> Doc Source #

PP Match Source # 

Methods

ppPrec :: Int -> Match -> Doc Source #

PP Expr Source # 

Methods

ppPrec :: Int -> Expr -> Doc Source #

PP UserTC Source # 

Methods

ppPrec :: Int -> UserTC -> Doc Source #

PP TC Source # 

Methods

ppPrec :: Int -> TC -> Doc Source #

PP PC Source # 

Methods

ppPrec :: Int -> PC -> Doc Source #

PP TCon Source # 

Methods

ppPrec :: Int -> TCon -> Doc Source #

PP TVar Source # 

Methods

ppPrec :: Int -> TVar -> Doc Source #

PP Type Source # 

Methods

ppPrec :: Int -> Type -> Doc Source #

PP TParam Source # 

Methods

ppPrec :: Int -> TParam -> Doc Source #

PP TySyn Source # 

Methods

ppPrec :: Int -> TySyn -> Doc Source #

PP Schema Source # 

Methods

ppPrec :: Int -> Schema -> Doc Source #

PP Kind Source # 

Methods

ppPrec :: Int -> Kind -> Doc Source #

PP Module Source # 

Methods

ppPrec :: Int -> Module -> Doc Source #

PP EvalError Source # 

Methods

ppPrec :: Int -> EvalError -> Doc Source #

PP Subst Source # 

Methods

ppPrec :: Int -> Subst -> Doc Source #

PP Error Source # 

Methods

ppPrec :: Int -> Error -> Doc Source #

PP TyFunName Source # 

Methods

ppPrec :: Int -> TyFunName -> Doc Source #

PP ConstraintSource Source # 
PP Error Source # 

Methods

ppPrec :: Int -> Error -> Doc Source #

PP Warning Source # 

Methods

ppPrec :: Int -> Warning -> Doc Source #

PP Solved Source # 

Methods

ppPrec :: Int -> Solved -> Doc Source #

PP ParseError Source # 

Methods

ppPrec :: Int -> ParseError -> Doc Source #

PP RenamerWarning Source # 
PP RenamerError Source # 

Methods

ppPrec :: Int -> RenamerError -> Doc Source #

PP ModuleWarning Source # 
PP ModuleError Source # 

Methods

ppPrec :: Int -> ModuleError -> Doc Source #

PP ImportSource Source # 

Methods

ppPrec :: Int -> ImportSource -> Doc Source #

PP Smoke Source # 

Methods

ppPrec :: Int -> Smoke -> Doc Source #

PP REPLException Source # 
PP a => PP (Located a) Source # 

Methods

ppPrec :: Int -> Located a -> Doc Source #

PP (WithNames DeclDef) Source # 
PP (WithNames Decl) Source # 

Methods

ppPrec :: Int -> WithNames Decl -> Doc Source #

PP (WithNames DeclGroup) Source # 
PP (WithNames Match) Source # 

Methods

ppPrec :: Int -> WithNames Match -> Doc Source #

PP (WithNames Expr) Source # 

Methods

ppPrec :: Int -> WithNames Expr -> Doc Source #

PP (WithNames TVar) Source # 

Methods

ppPrec :: Int -> WithNames TVar -> Doc Source #

PP (WithNames Type) Source # 

Methods

ppPrec :: Int -> WithNames Type -> Doc Source #

PP (WithNames TParam) Source # 
PP (WithNames TySyn) Source # 

Methods

ppPrec :: Int -> WithNames TySyn -> Doc Source #

PP (WithNames Schema) Source # 
PP (WithNames Module) Source # 
PP (WithNames Subst) Source # 

Methods

ppPrec :: Int -> WithNames Subst -> Doc Source #

PP (WithNames Error) Source # 

Methods

ppPrec :: Int -> WithNames Error -> Doc Source #

PP (WithNames Warning) Source # 
PP (WithNames DelayedCt) Source # 
PP (WithNames Goal) Source # 

Methods

ppPrec :: Int -> WithNames Goal -> Doc Source #

PPName name => PP (Prop name) Source # 

Methods

ppPrec :: Int -> Prop name -> Doc Source #

PPName name => PP (Type name) Source # 

Methods

ppPrec :: Int -> Type name -> Doc Source #

PPName name => PP (TParam name) Source # 

Methods

ppPrec :: Int -> TParam name -> Doc Source #

PPName name => PP (Schema name) Source # 

Methods

ppPrec :: Int -> Schema name -> Doc Source #

PPName name => PP (Pattern name) Source # 

Methods

ppPrec :: Int -> Pattern name -> Doc Source #

(Show name, PPName name) => PP (Match name) Source # 

Methods

ppPrec :: Int -> Match name -> Doc Source #

PPName name => PP (TypeInst name) Source # 

Methods

ppPrec :: Int -> TypeInst name -> Doc Source #

(Show name, PPName name) => PP (Expr name) Source # 

Methods

ppPrec :: Int -> Expr name -> Doc Source #

PP a => PP (TopLevel a) Source # 

Methods

ppPrec :: Int -> TopLevel a -> Doc Source #

PPName name => PP (Newtype name) Source # 

Methods

ppPrec :: Int -> Newtype name -> Doc Source #

(Show name, PPName name) => PP (BindDef name) Source # 

Methods

ppPrec :: Int -> BindDef name -> Doc Source #

(Show name, PPName name) => PP (Bind name) Source # 

Methods

ppPrec :: Int -> Bind name -> Doc Source #

PPName name => PP (TySyn name) Source # 

Methods

ppPrec :: Int -> TySyn name -> Doc Source #

(Show name, PPName name) => PP (Decl name) Source # 

Methods

ppPrec :: Int -> Decl name -> Doc Source #

(Show name, PPName name) => PP (TopDecl name) Source # 

Methods

ppPrec :: Int -> TopDecl name -> Doc Source #

(Show name, PPName name) => PP (Module name) Source # 

Methods

ppPrec :: Int -> Module name -> Doc Source #

(Show name, PPName name) => PP (Program name) Source # 

Methods

ppPrec :: Int -> Program name -> Doc Source #

PP (WithBase Value) Source # 

Methods

ppPrec :: Int -> WithBase Value -> Doc Source #

PP (WithBase EvalEnv) Source # 

class PP a => PPName a where Source #

Minimal complete definition

ppNameFixity, ppPrefixName, ppInfixName

Methods

ppNameFixity :: a -> Maybe (Assoc, Int) Source #

Fixity information for infix operators

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 

Instances

Eq Assoc Source # 

Methods

(==) :: Assoc -> Assoc -> Bool #

(/=) :: Assoc -> Assoc -> Bool #

Show Assoc Source # 

Methods

showsPrec :: Int -> Assoc -> ShowS #

show :: Assoc -> String #

showList :: [Assoc] -> ShowS #

Generic Assoc Source # 

Associated Types

type Rep Assoc :: * -> * #

Methods

from :: Assoc -> Rep Assoc x #

to :: Rep Assoc x -> Assoc #

NFData Assoc Source # 

Methods

rnf :: Assoc -> () #

type Rep Assoc Source # 
type Rep Assoc = D1 (MetaData "Assoc" "Cryptol.Utils.PP" "cryptol-2.4.0-AtabUoGsZJn8kSvO8P84NP" False) ((:+:) (C1 (MetaCons "LeftAssoc" PrefixI False) U1) ((:+:) (C1 (MetaCons "RightAssoc" PrefixI False) U1) (C1 (MetaCons "NonAssoc" PrefixI False) U1)))

data Infix op thing Source #

Information about an infix expression of some sort.

Constructors

Infix 

Fields

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 #