gf-3.11: Grammatical Framework
Safe HaskellSafe-Inferred
LanguageHaskell2010

GF.Text.Pretty

Description

Pretty printing with class

Synopsis

Documentation

class Pretty a where Source #

Minimal complete definition

pp

Methods

pp :: a -> Doc Source #

ppList :: [a] -> Doc Source #

Instances

Instances details
Pretty Char Source # 
Instance details

Defined in GF.Text.Pretty

Methods

pp :: Char -> Doc Source #

ppList :: [Char] -> Doc Source #

Pretty Double Source # 
Instance details

Defined in GF.Text.Pretty

Methods

pp :: Double -> Doc Source #

ppList :: [Double] -> Doc Source #

Pretty Float Source # 
Instance details

Defined in GF.Text.Pretty

Methods

pp :: Float -> Doc Source #

ppList :: [Float] -> Doc Source #

Pretty Int Source # 
Instance details

Defined in GF.Text.Pretty

Methods

pp :: Int -> Doc Source #

ppList :: [Int] -> Doc Source #

Pretty Integer Source # 
Instance details

Defined in GF.Text.Pretty

Methods

pp :: Integer -> Doc Source #

ppList :: [Integer] -> Doc Source #

Pretty Doc Source # 
Instance details

Defined in GF.Text.Pretty

Methods

pp :: Doc -> Doc Source #

ppList :: [Doc] -> Doc Source #

Pretty Location Source # 
Instance details

Defined in GF.Infra.Location

Pretty RawIdent Source # 
Instance details

Defined in GF.Infra.Ident

Pretty Ident Source # 
Instance details

Defined in GF.Infra.Ident

Methods

pp :: Ident -> Doc Source #

ppList :: [Ident] -> Doc Source #

Pretty ModuleName Source # 
Instance details

Defined in GF.Infra.Ident

Pretty QualId Source # 
Instance details

Defined in GF.Grammar.Canonical

Methods

pp :: QualId -> Doc Source #

ppList :: [QualId] -> Doc Source #

Pretty FlagValue Source # 
Instance details

Defined in GF.Grammar.Canonical

Pretty Flags Source # 
Instance details

Defined in GF.Grammar.Canonical

Methods

pp :: Flags -> Doc Source #

ppList :: [Flags] -> Doc Source #

Pretty VarId Source # 
Instance details

Defined in GF.Grammar.Canonical

Methods

pp :: VarId -> Doc Source #

ppList :: [VarId] -> Doc Source #

Pretty FunId Source # 
Instance details

Defined in GF.Grammar.Canonical

Methods

pp :: FunId -> Doc Source #

ppList :: [FunId] -> Doc Source #

Pretty CatId Source # 
Instance details

Defined in GF.Grammar.Canonical

Methods

pp :: CatId -> Doc Source #

ppList :: [CatId] -> Doc Source #

Pretty ModId Source # 
Instance details

Defined in GF.Grammar.Canonical

Methods

pp :: ModId -> Doc Source #

ppList :: [ModId] -> Doc Source #

Pretty ParamId Source # 
Instance details

Defined in GF.Grammar.Canonical

Methods

pp :: ParamId -> Doc Source #

ppList :: [ParamId] -> Doc Source #

Pretty VarValueId Source # 
Instance details

Defined in GF.Grammar.Canonical

Pretty LabelId Source # 
Instance details

Defined in GF.Grammar.Canonical

Methods

pp :: LabelId -> Doc Source #

ppList :: [LabelId] -> Doc Source #

Pretty PredefId Source # 
Instance details

Defined in GF.Grammar.Canonical

Pretty LinPattern Source # 
Instance details

Defined in GF.Grammar.Canonical

Pretty LinLiteral Source # 
Instance details

Defined in GF.Grammar.Canonical

Pretty LinValue Source # 
Instance details

Defined in GF.Grammar.Canonical

Pretty ParamType Source # 
Instance details

Defined in GF.Grammar.Canonical

Pretty LinType Source # 
Instance details

Defined in GF.Grammar.Canonical

Methods

pp :: LinType -> Doc Source #

ppList :: [LinType] -> Doc Source #

Pretty LinDef Source # 
Instance details

Defined in GF.Grammar.Canonical

Methods

pp :: LinDef -> Doc Source #

ppList :: [LinDef] -> Doc Source #

Pretty LincatDef Source # 
Instance details

Defined in GF.Grammar.Canonical

Pretty ParamDef Source # 
Instance details

Defined in GF.Grammar.Canonical

Pretty Concrete Source # 
Instance details

Defined in GF.Grammar.Canonical

Pretty TypeBinding Source # 
Instance details

Defined in GF.Grammar.Canonical

Pretty TypeApp Source # 
Instance details

Defined in GF.Grammar.Canonical

Methods

pp :: TypeApp -> Doc Source #

ppList :: [TypeApp] -> Doc Source #

Pretty Type Source # 
Instance details

Defined in GF.Grammar.Canonical

Methods

pp :: Type -> Doc Source #

ppList :: [Type] -> Doc Source #

Pretty FunDef Source # 
Instance details

Defined in GF.Grammar.Canonical

Methods

pp :: FunDef -> Doc Source #

ppList :: [FunDef] -> Doc Source #

Pretty CatDef Source # 
Instance details

Defined in GF.Grammar.Canonical

Methods

pp :: CatDef -> Doc Source #

ppList :: [CatDef] -> Doc Source #

Pretty Abstract Source # 
Instance details

Defined in GF.Grammar.Canonical

Pretty Grammar Source # 
Instance details

Defined in GF.Grammar.Canonical

Methods

pp :: Grammar -> Doc Source #

ppList :: [Grammar] -> Doc Source #

Pretty Label Source # 
Instance details

Defined in GF.Grammar.Printer

Methods

pp :: Label -> Doc Source #

ppList :: [Label] -> Doc Source #

Pretty Patt Source # 
Instance details

Defined in GF.Grammar.Printer

Methods

pp :: Patt -> Doc Source #

ppList :: [Patt] -> Doc Source #

Pretty Term Source # 
Instance details

Defined in GF.Grammar.Printer

Methods

pp :: Term -> Doc Source #

ppList :: [Term] -> Doc Source #

Pretty Grammar Source # 
Instance details

Defined in GF.Grammar.Printer

Methods

pp :: Grammar -> Doc Source #

ppList :: [Grammar] -> Doc Source #

Pretty a => Pretty [a] Source # 
Instance details

Defined in GF.Text.Pretty

Methods

pp :: [a] -> Doc Source #

ppList :: [[a]] -> Doc Source #

Pretty a => Pretty (L a) Source # 
Instance details

Defined in GF.Infra.Location

Methods

pp :: L a -> Doc Source #

ppList :: [L a] -> Doc Source #

Pretty rhs => Pretty (TableRow rhs) Source # 
Instance details

Defined in GF.Grammar.Canonical

Methods

pp :: TableRow rhs -> Doc Source #

ppList :: [TableRow rhs] -> Doc Source #

RhsSeparator rhs => Pretty (RecordRow rhs) Source # 
Instance details

Defined in GF.Grammar.Canonical

Methods

pp :: RecordRow rhs -> Doc Source #

ppList :: [RecordRow rhs] -> Doc Source #

PPA arg => Pretty (Param arg) Source # 
Instance details

Defined in GF.Grammar.Canonical

Methods

pp :: Param arg -> Doc Source #

ppList :: [Param arg] -> Doc Source #

render :: Pretty a => a -> String Source #

($$) :: (Pretty a1, Pretty a2) => a1 -> a2 -> Doc infixl 5 Source #

($+$) :: (Pretty a1, Pretty a2) => a1 -> a2 -> Doc infixl 5 Source #

(<+>) :: (Pretty a1, Pretty a2) => a1 -> a2 -> Doc infixl 6 Source #

(<>) :: (Pretty a1, Pretty a2) => a1 -> a2 -> Doc infixl 6 Source #

braces :: Pretty a => a -> Doc Source #

brackets :: Pretty a => a -> Doc Source #

cat :: Pretty a => [a] -> Doc Source #

fcat :: Pretty a => [a] -> Doc Source #

fsep :: Pretty a => [a] -> Doc Source #

hang :: (Pretty a1, Pretty a2) => a1 -> Int -> a2 -> Doc Source #

hcat :: Pretty a => [a] -> Doc Source #

hsep :: Pretty a => [a] -> Doc Source #

nest :: Pretty a => Int -> a -> Doc Source #

parens :: Pretty a => a -> Doc Source #

punctuate :: (Pretty a1, Pretty a2) => a1 -> [a2] -> [Doc] Source #

quotes :: Pretty a => a -> Doc Source #

sep :: Pretty a => [a] -> Doc Source #

vcat :: Pretty a => [a] -> Doc Source #

data Mode #

Rendering mode.

Constructors

PageMode

Normal rendering (lineLength and ribbonsPerLine respected').

ZigZagMode

With zig-zag cuts.

LeftMode

No indentation, infinitely long lines (lineLength ignored), but explicit new lines, i.e., text "one" $$ text "two", are respected.

OneLineMode

All on one line, lineLength ignored and explicit new lines ($$) are turned into spaces.

Instances

Instances details
Eq Mode 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Methods

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

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

Show Mode 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Methods

showsPrec :: Int -> Mode -> ShowS #

show :: Mode -> String #

showList :: [Mode] -> ShowS #

Generic Mode 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Associated Types

type Rep Mode :: Type -> Type #

Methods

from :: Mode -> Rep Mode x #

to :: Rep Mode x -> Mode #

type Rep Mode 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

type Rep Mode = D1 ('MetaData "Mode" "Text.PrettyPrint.Annotated.HughesPJ" "pretty-1.1.3.6" 'False) ((C1 ('MetaCons "PageMode" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ZigZagMode" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "LeftMode" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OneLineMode" 'PrefixI 'False) (U1 :: Type -> Type)))

data Style #

A rendering style. Allows us to specify constraints to choose among the many different rendering options.

Constructors

Style 

Fields

  • mode :: Mode

    The rendering mode.

  • lineLength :: Int

    Maximum length of a line, in characters.

  • ribbonsPerLine :: Float

    Ratio of line length to ribbon length. A ribbon refers to the characters on a line excluding indentation. So a lineLength of 100, with a ribbonsPerLine of 2.0 would only allow up to 50 characters of ribbon to be displayed on a line, while allowing it to be indented up to 50 characters.

Instances

Instances details
Eq Style 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Methods

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

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

Show Style 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Methods

showsPrec :: Int -> Style -> ShowS #

show :: Style -> String #

showList :: [Style] -> ShowS #

Generic Style 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

Associated Types

type Rep Style :: Type -> Type #

Methods

from :: Style -> Rep Style x #

to :: Rep Style x -> Style #

type Rep Style 
Instance details

Defined in Text.PrettyPrint.Annotated.HughesPJ

type Rep Style = D1 ('MetaData "Style" "Text.PrettyPrint.Annotated.HughesPJ" "pretty-1.1.3.6" 'False) (C1 ('MetaCons "Style" 'PrefixI 'True) (S1 ('MetaSel ('Just "mode") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Mode) :*: (S1 ('MetaSel ('Just "lineLength") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "ribbonsPerLine") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Float))))

style :: Style #

The default style (mode=PageMode, lineLength=100, ribbonsPerLine=1.5).

data Doc #

The abstract type of documents. A Doc represents a set of layouts. A Doc with no occurrences of Union or NoDoc represents just one layout.

Instances

Instances details
Eq Doc 
Instance details

Defined in Text.PrettyPrint.HughesPJ

Methods

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

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

Show Doc 
Instance details

Defined in Text.PrettyPrint.HughesPJ

Methods

showsPrec :: Int -> Doc -> ShowS #

show :: Doc -> String #

showList :: [Doc] -> ShowS #

IsString Doc 
Instance details

Defined in Text.PrettyPrint.HughesPJ

Methods

fromString :: String -> Doc #

Generic Doc 
Instance details

Defined in Text.PrettyPrint.HughesPJ

Associated Types

type Rep Doc :: Type -> Type #

Methods

from :: Doc -> Rep Doc x #

to :: Rep Doc x -> Doc #

Semigroup Doc 
Instance details

Defined in Text.PrettyPrint.HughesPJ

Methods

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

sconcat :: NonEmpty Doc -> Doc #

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

Monoid Doc 
Instance details

Defined in Text.PrettyPrint.HughesPJ

Methods

mempty :: Doc #

mappend :: Doc -> Doc -> Doc #

mconcat :: [Doc] -> Doc #

NFData Doc 
Instance details

Defined in Text.PrettyPrint.HughesPJ

Methods

rnf :: Doc -> () #

Pretty Doc Source # 
Instance details

Defined in GF.Text.Pretty

Methods

pp :: Doc -> Doc Source #

ppList :: [Doc] -> Doc Source #

type Rep Doc 
Instance details

Defined in Text.PrettyPrint.HughesPJ

type Rep Doc = D1 ('MetaData "Doc" "Text.PrettyPrint.HughesPJ" "pretty-1.1.3.6" 'True) (C1 ('MetaCons "Doc" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Doc ()))))

empty :: Doc #

The empty document, with no height and no width. empty is the identity for <>, <+>, $$ and $+$, and anywhere in the argument list for sep, hcat, hsep, vcat, fcat etc.

isEmpty :: Doc -> Bool #

Returns True if the document is empty