Copyright | (c) 2013-2016 Galois Inc. |
---|---|
License | BSD3 |
Maintainer | cryptol@galois.com |
Stability | provisional |
Portability | portable |
Safe Haskell | Safe |
Language | Haskell2010 |
Synopsis
- data NameDisp
- = EmptyNameDisp
- | NameDisp (ModName -> Ident -> Maybe NameFormat)
- data NameFormat
- neverQualifyMod :: ModName -> NameDisp
- alwaysQualify :: NameDisp
- neverQualify :: NameDisp
- fmtModName :: ModName -> NameFormat -> Text
- extend :: NameDisp -> NameDisp -> NameDisp
- getNameFormat :: ModName -> Ident -> NameDisp -> NameFormat
- withNameDisp :: (NameDisp -> Doc) -> Doc
- fixNameDisp :: NameDisp -> Doc -> Doc
- newtype Doc = Doc (NameDisp -> Doc)
- runDoc :: NameDisp -> Doc -> Doc
- render :: Doc -> String
- 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 {}
- commaSep :: [Doc] -> Doc
- 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
- liftPJ :: Doc -> Doc
- liftPJ1 :: (Doc -> Doc) -> Doc -> Doc
- liftPJ2 :: (Doc -> Doc -> Doc) -> Doc -> Doc -> Doc
- liftSep :: ([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
- hang :: Doc -> Int -> Doc -> Doc
- nest :: Int -> Doc -> Doc
- parens :: Doc -> Doc
- braces :: Doc -> Doc
- brackets :: Doc -> Doc
- quotes :: Doc -> Doc
- backticks :: Doc -> Doc
- punctuate :: Doc -> [Doc] -> [Doc]
- text :: String -> Doc
- char :: Char -> Doc
- integer :: Integer -> Doc
- int :: Int -> Doc
- comma :: Doc
- empty :: Doc
- colon :: Doc
Documentation
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.
EmptyNameDisp | |
NameDisp (ModName -> Ident -> Maybe NameFormat) |
Instances
Show NameDisp Source # | |
Generic NameDisp Source # | |
Semigroup NameDisp Source # | |
Monoid 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-2.10.0-Bsi6VMfJ6GCFlOdda30jWW" '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 # | |
Defined in Cryptol.Utils.PP showsPrec :: Int -> NameFormat -> ShowS # show :: NameFormat -> String # showList :: [NameFormat] -> ShowS # |
neverQualifyMod :: ModName -> NameDisp Source #
Never qualify names from this module.
fmtModName :: ModName -> NameFormat -> Text Source #
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
.
renderOneLine :: Doc -> String Source #
Instances
class PP a => PPName a where Source #
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.
:: (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)