cryptol-2.9.0: Cryptol: The Language of Cryptography

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

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 display has no opinion on how this name should be displayed, and some other display should be tried out.

Instances
Show NameDisp Source # 
Instance details

Defined in Cryptol.Utils.PP

Generic NameDisp Source # 
Instance details

Defined in Cryptol.Utils.PP

Associated Types

type Rep NameDisp :: Type -> Type #

Methods

from :: NameDisp -> Rep NameDisp x #

to :: Rep NameDisp x -> NameDisp #

Semigroup NameDisp Source # 
Instance details

Defined in Cryptol.Utils.PP

Monoid NameDisp Source # 
Instance details

Defined in Cryptol.Utils.PP

NFData NameDisp Source # 
Instance details

Defined in Cryptol.Utils.PP

Methods

rnf :: NameDisp -> () #

type Rep NameDisp Source # 
Instance details

Defined in Cryptol.Utils.PP

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

data NameFormat Source #

Instances
Show NameFormat Source # 
Instance details

Defined in Cryptol.Utils.PP

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 # 
Instance details

Defined in Cryptol.Utils.PP

Methods

showsPrec :: Int -> Doc -> ShowS #

show :: Doc -> String #

showList :: [Doc] -> ShowS #

IsString Doc Source # 
Instance details

Defined in Cryptol.Utils.PP

Methods

fromString :: String -> Doc #

Generic Doc Source # 
Instance details

Defined in Cryptol.Utils.PP

Associated Types

type Rep Doc :: Type -> Type #

Methods

from :: Doc -> Rep Doc x #

to :: Rep Doc x -> Doc #

Semigroup Doc Source # 
Instance details

Defined in Cryptol.Utils.PP

Methods

(<>) :: Doc -> Doc -> Doc #

sconcat :: NonEmpty Doc -> Doc #

stimes :: Integral b => b -> Doc -> Doc #

Monoid Doc Source # 
Instance details

Defined in Cryptol.Utils.PP

Methods

mempty :: Doc #

mappend :: Doc -> Doc -> Doc #

mconcat :: [Doc] -> Doc #

NFData Doc Source # 
Instance details

Defined in Cryptol.Utils.PP

Methods

rnf :: Doc -> () #

type Rep Doc Source # 
Instance details

Defined in Cryptol.Utils.PP

type Rep Doc = D1 (MetaData "Doc" "Cryptol.Utils.PP" "cryptol-2.9.0-4aSi1YZNBynFQwh9aOpllR" True) (C1 (MetaCons "Doc" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (NameDisp -> Doc))))

class PP a where Source #

Methods

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

Instances
PP Text Source # 
Instance details

Defined in Cryptol.Utils.PP

Methods

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

PP Fixity Source # 
Instance details

Defined in Cryptol.Utils.PP

Methods

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

PP Assoc Source # 
Instance details

Defined in Cryptol.Utils.PP

Methods

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

PP Ident Source # 
Instance details

Defined in Cryptol.Utils.PP

Methods

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

PP ModName Source # 
Instance details

Defined in Cryptol.Utils.PP

Methods

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

PP Selector Source # 
Instance details

Defined in Cryptol.Parser.Selector

Methods

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

PP Range Source # 
Instance details

Defined in Cryptol.Parser.Position

Methods

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

PP Position Source # 
Instance details

Defined in Cryptol.Parser.Position

Methods

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

PP PName Source # 
Instance details

Defined in Cryptol.Parser.Name

Methods

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

PP Token Source # 
Instance details

Defined in Cryptol.Parser.LexerUtils

Methods

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

PP Name Source # 
Instance details

Defined in Cryptol.ModuleSystem.Name

Methods

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

PP TFun Source # 
Instance details

Defined in Cryptol.TypeCheck.TCon

Methods

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

PP TCErrorMessage Source # 
Instance details

Defined in Cryptol.TypeCheck.TCon

PP UserTC Source # 
Instance details

Defined in Cryptol.TypeCheck.TCon

Methods

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

PP TC Source # 
Instance details

Defined in Cryptol.TypeCheck.TCon

Methods

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

PP PC Source # 
Instance details

Defined in Cryptol.TypeCheck.TCon

Methods

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

PP TCon Source # 
Instance details

Defined in Cryptol.TypeCheck.TCon

Methods

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

PP Kind Source # 
Instance details

Defined in Cryptol.TypeCheck.TCon

Methods

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

PP Newtype Source # 
Instance details

Defined in Cryptol.TypeCheck.Type

Methods

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

PP TySyn Source # 
Instance details

Defined in Cryptol.TypeCheck.Type

Methods

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

PP TVarSource Source # 
Instance details

Defined in Cryptol.TypeCheck.Type

Methods

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

PP TVarInfo Source # 
Instance details

Defined in Cryptol.TypeCheck.Type

Methods

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

PP TVar Source # 
Instance details

Defined in Cryptol.TypeCheck.Type

Methods

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

PP Type Source # 
Instance details

Defined in Cryptol.TypeCheck.Type

Methods

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

PP TParam Source # 
Instance details

Defined in Cryptol.TypeCheck.Type

Methods

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

PP Schema Source # 
Instance details

Defined in Cryptol.TypeCheck.Type

Methods

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

PP Kind Source # 
Instance details

Defined in Cryptol.Parser.AST

Methods

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

PP UpdHow Source # 
Instance details

Defined in Cryptol.Parser.AST

Methods

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

PP Literal Source # 
Instance details

Defined in Cryptol.Parser.AST

Methods

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

PP Pragma Source # 
Instance details

Defined in Cryptol.Parser.AST

Methods

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

PP ImportSpec Source # 
Instance details

Defined in Cryptol.Parser.AST

Methods

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

PP Import Source # 
Instance details

Defined in Cryptol.Parser.AST

Methods

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

PP Error Source # 
Instance details

Defined in Cryptol.Parser.NoPat

Methods

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

PP Decl Source # 
Instance details

Defined in Cryptol.TypeCheck.AST

Methods

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

PP DeclGroup Source # 
Instance details

Defined in Cryptol.TypeCheck.AST

Methods

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

PP Match Source # 
Instance details

Defined in Cryptol.TypeCheck.AST

Methods

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

PP Expr Source # 
Instance details

Defined in Cryptol.TypeCheck.AST

Methods

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

PP Module Source # 
Instance details

Defined in Cryptol.TypeCheck.AST

Methods

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

PP Solved Source # 
Instance details

Defined in Cryptol.TypeCheck.Solver.Types

Methods

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

PP Subst Source # 
Instance details

Defined in Cryptol.TypeCheck.Subst

Methods

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

PP ConstraintSource Source # 
Instance details

Defined in Cryptol.TypeCheck.InferTypes

PP Error Source # 
Instance details

Defined in Cryptol.TypeCheck.Error

Methods

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

PP Warning Source # 
Instance details

Defined in Cryptol.TypeCheck.Error

Methods

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

PP Unsupported Source # 
Instance details

Defined in Cryptol.Eval.Monad

Methods

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

PP EvalError Source # 
Instance details

Defined in Cryptol.Eval.Monad

Methods

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

PP RenamerWarning Source # 
Instance details

Defined in Cryptol.ModuleSystem.Renamer

PP RenamerError Source # 
Instance details

Defined in Cryptol.ModuleSystem.Renamer

Methods

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

PP ModulePath Source # 
Instance details

Defined in Cryptol.ModuleSystem.Env

Methods

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

PP ModuleWarning Source # 
Instance details

Defined in Cryptol.ModuleSystem.Monad

PP ModuleError Source # 
Instance details

Defined in Cryptol.ModuleSystem.Monad

Methods

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

PP ImportSource Source # 
Instance details

Defined in Cryptol.ModuleSystem.Monad

Methods

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

PP Smoke Source # 
Instance details

Defined in Cryptol.REPL.Monad

Methods

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

PP REPLException Source # 
Instance details

Defined in Cryptol.REPL.Monad

PP (WithNames Newtype) Source # 
Instance details

Defined in Cryptol.TypeCheck.Type

PP (WithNames TySyn) Source # 
Instance details

Defined in Cryptol.TypeCheck.Type

Methods

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

PP (WithNames TVar) Source # 
Instance details

Defined in Cryptol.TypeCheck.Type

Methods

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

PP (WithNames Type) Source #

The precedence levels used by this pretty-printing instance correspond with parser non-terminals as follows:

  • 0-1: type
  • 2: infix_type
  • 3: app_type
  • 4: atype
Instance details

Defined in Cryptol.TypeCheck.Type

Methods

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

PP (WithNames TParam) Source # 
Instance details

Defined in Cryptol.TypeCheck.Type

PP (WithNames Schema) Source # 
Instance details

Defined in Cryptol.TypeCheck.Type

PP (WithNames DeclDef) Source # 
Instance details

Defined in Cryptol.TypeCheck.AST

PP (WithNames Decl) Source # 
Instance details

Defined in Cryptol.TypeCheck.AST

Methods

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

PP (WithNames DeclGroup) Source # 
Instance details

Defined in Cryptol.TypeCheck.AST

PP (WithNames Match) Source # 
Instance details

Defined in Cryptol.TypeCheck.AST

Methods

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

PP (WithNames Expr) Source # 
Instance details

Defined in Cryptol.TypeCheck.AST

Methods

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

PP (WithNames Module) Source # 
Instance details

Defined in Cryptol.TypeCheck.AST

PP (WithNames Subst) Source # 
Instance details

Defined in Cryptol.TypeCheck.Subst

Methods

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

PP (WithNames DelayedCt) Source # 
Instance details

Defined in Cryptol.TypeCheck.InferTypes

PP (WithNames Goal) Source # 
Instance details

Defined in Cryptol.TypeCheck.InferTypes

Methods

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

PP (WithNames Error) Source # 
Instance details

Defined in Cryptol.TypeCheck.Error

Methods

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

PP (WithNames Warning) Source # 
Instance details

Defined in Cryptol.TypeCheck.Error

PP a => PP (Located a) Source # 
Instance details

Defined in Cryptol.Parser.Position

Methods

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

PPName name => PP (Prop name) Source # 
Instance details

Defined in Cryptol.Parser.AST

Methods

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

PPName name => PP (Type name) Source # 
Instance details

Defined in Cryptol.Parser.AST

Methods

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

PPName name => PP (TParam name) Source # 
Instance details

Defined in Cryptol.Parser.AST

Methods

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

PPName name => PP (Schema name) Source # 
Instance details

Defined in Cryptol.Parser.AST

Methods

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

PPName name => PP (Pattern name) Source # 
Instance details

Defined in Cryptol.Parser.AST

Methods

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

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

Defined in Cryptol.Parser.AST

Methods

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

PPName name => PP (TypeInst name) Source # 
Instance details

Defined in Cryptol.Parser.AST

Methods

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

(Show name, PPName name) => PP (UpdField name) Source # 
Instance details

Defined in Cryptol.Parser.AST

Methods

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

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

Defined in Cryptol.Parser.AST

Methods

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

PP a => PP (TopLevel a) Source # 
Instance details

Defined in Cryptol.Parser.AST

Methods

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

(Show name, PPName name) => PP (PrimType name) Source # 
Instance details

Defined in Cryptol.Parser.AST

Methods

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

PPName name => PP (Newtype name) Source # 
Instance details

Defined in Cryptol.Parser.AST

Methods

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

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

Defined in Cryptol.Parser.AST

Methods

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

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

Defined in Cryptol.Parser.AST

Methods

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

PPName name => PP (PropSyn name) Source # 
Instance details

Defined in Cryptol.Parser.AST

Methods

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

PPName name => PP (TySyn name) Source # 
Instance details

Defined in Cryptol.Parser.AST

Methods

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

(Show name, PPName name) => PP (ParameterFun name) Source # 
Instance details

Defined in Cryptol.Parser.AST

Methods

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

(Show name, PPName name) => PP (ParameterType name) Source # 
Instance details

Defined in Cryptol.Parser.AST

Methods

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

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

Defined in Cryptol.Parser.AST

Methods

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

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

Defined in Cryptol.Parser.AST

Methods

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

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

Defined in Cryptol.Parser.AST

Methods

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

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

Defined in Cryptol.Parser.AST

Methods

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

class PP a => PPName a where Source #

Methods

ppNameFixity :: a -> Maybe Fixity 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 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 value as an ordinal (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 #