Copyright | (c) 2013-2016 Galois Inc. |
---|---|
License | BSD3 |
Maintainer | cryptol@galois.com |
Stability | provisional |
Portability | portable |
Safe Haskell | Safe |
Language | Haskell2010 |
Cryptol.Utils.PP
Description
Synopsis
- data PPOpts = PPOpts {
- useAscii :: Bool
- useBase :: Int
- useInfLength :: Int
- useFPBase :: Int
- useFPFormat :: PPFloatFormat
- useFieldOrder :: FieldOrder
- asciiMode :: PPOpts -> Integer -> Bool
- data PPFloatFormat
- data PPFloatExp
- data FieldOrder
- defaultPPOpts :: PPOpts
- data NameDisp
- = EmptyNameDisp
- | NameDisp (OrigName -> Maybe NameFormat)
- data NameFormat
- neverQualifyMod :: ModPath -> NameDisp
- neverQualify :: NameDisp
- extend :: NameDisp -> NameDisp -> NameDisp
- getNameFormat :: OrigName -> NameDisp -> NameFormat
- withNameDisp :: (NameDisp -> Doc) -> Doc
- withPPCfg :: (PPCfg -> Doc) -> Doc
- fixNameDisp :: NameDisp -> Doc -> Doc
- fixPPCfg :: PPCfg -> Doc -> Doc
- updPPCfg :: (PPCfg -> PPCfg) -> Doc -> Doc
- debugShowUniques :: Doc -> Doc
- data PPCfg = PPCfg {}
- defaultPPCfg :: PPCfg
- newtype Doc = Doc (PPCfg -> Doc Void)
- runDocWith :: PPCfg -> Doc -> Doc Void
- runDoc :: NameDisp -> Doc -> Doc Void
- renderOneLine :: Doc -> String
- class PP a where
- class PP a => PPName a where
- ppNameFixity :: a -> Maybe Fixity
- ppPrefixName :: a -> Doc
- ppInfixName :: a -> Doc
- pp :: PP a => a -> Doc
- pretty :: PP a => a -> String
- optParens :: Bool -> Doc -> Doc
- data Infix op thing = Infix {}
- ppInfix :: (PP thing, PP op) => Int -> (thing -> Maybe (Infix op thing)) -> Infix op thing -> Doc
- ordinal :: (Integral a, Show a, Eq a) => a -> Doc
- ordSuffix :: (Integral a, Eq a) => a -> String
- liftPP :: Doc Void -> Doc
- liftPP1 :: (Doc Void -> Doc Void) -> Doc -> Doc
- liftPP2 :: (Doc Void -> Doc Void -> Doc Void) -> Doc -> Doc -> Doc
- liftSep :: ([Doc Void] -> Doc Void) -> [Doc] -> Doc
- reflow :: Text -> Doc
- (<.>) :: Doc -> Doc -> Doc
- (<+>) :: Doc -> Doc -> Doc
- (</>) :: Doc -> Doc -> Doc
- ($$) :: Doc -> Doc -> Doc
- sep :: [Doc] -> Doc
- fsep :: [Doc] -> Doc
- hsep :: [Doc] -> Doc
- hcat :: [Doc] -> Doc
- vcat :: [Doc] -> Doc
- vsep :: [Doc] -> Doc
- group :: Doc -> Doc
- hang :: Doc -> Int -> Doc -> Doc
- nest :: Int -> Doc -> Doc
- indent :: Int -> Doc -> Doc
- align :: Doc -> Doc
- parens :: Doc -> Doc
- braces :: Doc -> Doc
- brackets :: Doc -> Doc
- quotes :: Doc -> Doc
- commaSep :: [Doc] -> Doc
- commaSepFill :: [Doc] -> Doc
- ppList :: [Doc] -> Doc
- ppTuple :: [Doc] -> Doc
- ppRecord :: [Doc] -> Doc
- backticks :: Doc -> Doc
- text :: String -> Doc
- char :: Char -> Doc
- integer :: Integer -> Doc
- int :: Int -> Doc
- comma :: Doc
- colon :: Doc
- pipe :: Doc
Documentation
How to pretty print things when evaluating
Constructors
PPOpts | |
Fields
|
data PPFloatFormat Source #
Constructors
FloatFixed Int PPFloatExp | Use this many significant digis |
FloatFrac Int | Show this many digits after floating point |
FloatFree PPFloatExp | Use the correct number of digits |
Instances
Show PPFloatFormat Source # | |
Defined in Cryptol.Utils.PP Methods showsPrec :: Int -> PPFloatFormat -> ShowS # show :: PPFloatFormat -> String # showList :: [PPFloatFormat] -> ShowS # |
data PPFloatExp Source #
Constructors
ForceExponent | Always show an exponent |
AutoExponent | Only show exponent when needed |
Instances
Show PPFloatExp Source # | |
Defined in Cryptol.Utils.PP Methods showsPrec :: Int -> PPFloatExp -> ShowS # show :: PPFloatExp -> String # showList :: [PPFloatExp] -> ShowS # |
data FieldOrder Source #
Constructors
DisplayOrder | |
CanonicalOrder |
Instances
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.
Constructors
EmptyNameDisp | |
NameDisp (OrigName -> Maybe NameFormat) |
Instances
Monoid NameDisp Source # | |
Semigroup NameDisp Source # | |
Generic NameDisp Source # | |
Show NameDisp Source # | |
NFData NameDisp Source # | |
Defined in Cryptol.Utils.PP | |
type Rep NameDisp Source # | |
Defined in Cryptol.Utils.PP type Rep NameDisp = D1 ('MetaData "NameDisp" "Cryptol.Utils.PP" "cryptol-3.3.0-7OIQa8lMv7L2xoAlM9JEI6" 'False) (C1 ('MetaCons "EmptyNameDisp" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NameDisp" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (OrigName -> Maybe NameFormat)))) |
data NameFormat Source #
Constructors
UnQualified | |
Qualified !ModName | |
NotInScope |
Instances
Show NameFormat Source # | |
Defined in Cryptol.Utils.PP Methods showsPrec :: Int -> NameFormat -> ShowS # show :: NameFormat -> String # showList :: [NameFormat] -> ShowS # |
neverQualifyMod :: ModPath -> NameDisp Source #
Never qualify names from this module.
extend :: NameDisp -> NameDisp -> NameDisp Source #
Compose two naming environments, preferring names from the left environment.
getNameFormat :: OrigName -> NameDisp -> NameFormat Source #
Get the format for a name.
withNameDisp :: (NameDisp -> Doc) -> Doc Source #
Produce a document in the context of the current NameDisp
.
withPPCfg :: (PPCfg -> Doc) -> Doc Source #
Produce a document in the context of the current configuration.
debugShowUniques :: Doc -> Doc Source #
Constructors
PPCfg | |
Fields |
defaultPPCfg :: PPCfg Source #
renderOneLine :: Doc -> String Source #
Instances
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
Information about an infix expression of some sort.
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
commaSepFill :: [Doc] -> Doc Source #
Print a comma-separated list. Lay out each item on a single line if it will fit. If an item requires multiple lines, then start it on its own line.