hindley-milner-type-check-0.1.1.0: Type inference for Hindley-Milner based languages
Safe HaskellNone
LanguageHaskell2010

Type.Check.HM.Pretty

Description

Pretty printer for types and terms.

Synopsis

Documentation

type PrettyVar a = (Pretty a, PrintCons a, IsVar a) Source #

data FixityCtx var a Source #

Type to querry fixity of infix operations in type variables.

Constructors

FixityCtx 

Fields

Instances

Instances details
(Pretty loc, PrettyVar var) => Pretty (FixityCtx var (TypeError loc var)) Source # 
Instance details

Defined in Type.Check.HM.Pretty

Methods

pretty :: FixityCtx var (TypeError loc var) -> Doc ann #

prettyList :: [FixityCtx var (TypeError loc var)] -> Doc ann #

(PrettyVar v, Pretty prim) => Pretty (FixityCtx v (Term prim loc v)) Source # 
Instance details

Defined in Type.Check.HM.Pretty

Methods

pretty :: FixityCtx v (Term prim loc v) -> Doc ann #

prettyList :: [FixityCtx v (Term prim loc v)] -> Doc ann #

PrettyVar v => Pretty (FixityCtx v (Type loc v)) Source # 
Instance details

Defined in Type.Check.HM.Pretty

Methods

pretty :: FixityCtx v (Type loc v) -> Doc ann #

prettyList :: [FixityCtx v (Type loc v)] -> Doc ann #

PrettyVar v => Pretty (FixityCtx v (Signature loc v)) Source # 
Instance details

Defined in Type.Check.HM.Pretty

Methods

pretty :: FixityCtx v (Signature loc v) -> Doc ann #

prettyList :: [FixityCtx v (Signature loc v)] -> Doc ann #

class PrintCons v where Source #

This class is useful to define the way to print special cases like constructors for tuples or lists.

Methods

printCons :: v -> [Doc ann] -> Doc ann Source #

Instances

Instances details
PrintCons Int Source # 
Instance details

Defined in Type.Check.HM.Pretty

Methods

printCons :: Int -> [Doc ann] -> Doc ann Source #

PrintCons String Source # 
Instance details

Defined in Type.Check.HM.Pretty

Methods

printCons :: String -> [Doc ann] -> Doc ann Source #

PrintCons Text Source # 
Instance details

Defined in Type.Check.HM.Pretty

Methods

printCons :: Text -> [Doc ann] -> Doc ann Source #

data OpFix Source #

Defines fixity type and order of infix operation

Constructors

OpFix 

Fields

data Fixity Source #

Infix operation can be left or right associative or associativity is not known.

Constructors

FixLeft 
FixRight 
FixNone 

Instances

Instances details
Eq Fixity Source # 
Instance details

Defined in Type.Check.HM.Pretty

Methods

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

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

class Pretty a where #

Overloaded conversion to Doc.

Laws:

  1. output should be pretty. :-)

Minimal complete definition

pretty

Methods

pretty :: a -> Doc ann #

>>> pretty 1 <+> pretty "hello" <+> pretty 1.234
1 hello 1.234

prettyList :: [a] -> Doc ann #

prettyList is only used to define the instance Pretty a => Pretty [a]. In normal circumstances only the pretty function is used.

>>> prettyList [1, 23, 456]
[1, 23, 456]

Instances

Instances details
Pretty Bool
>>> pretty True
True
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Bool -> Doc ann #

prettyList :: [Bool] -> Doc ann #

Pretty Char

Instead of (pretty 'n'), consider using line as a more readable alternative.

>>> pretty 'f' <> pretty 'o' <> pretty 'o'
foo
>>> pretty ("string" :: String)
string
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Char -> Doc ann #

prettyList :: [Char] -> Doc ann #

Pretty Double
>>> pretty (exp 1 :: Double)
2.71828182845904...
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Double -> Doc ann #

prettyList :: [Double] -> Doc ann #

Pretty Float
>>> pretty (pi :: Float)
3.1415927
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Float -> Doc ann #

prettyList :: [Float] -> Doc ann #

Pretty Int
>>> pretty (123 :: Int)
123
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Int -> Doc ann #

prettyList :: [Int] -> Doc ann #

Pretty Int8 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Int8 -> Doc ann #

prettyList :: [Int8] -> Doc ann #

Pretty Int16 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Int16 -> Doc ann #

prettyList :: [Int16] -> Doc ann #

Pretty Int32 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Int32 -> Doc ann #

prettyList :: [Int32] -> Doc ann #

Pretty Int64 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Int64 -> Doc ann #

prettyList :: [Int64] -> Doc ann #

Pretty Integer
>>> pretty (2^123 :: Integer)
10633823966279326983230456482242756608
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Integer -> Doc ann #

prettyList :: [Integer] -> Doc ann #

Pretty Natural 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Natural -> Doc ann #

prettyList :: [Natural] -> Doc ann #

Pretty Word 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Word -> Doc ann #

prettyList :: [Word] -> Doc ann #

Pretty Word8 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Word8 -> Doc ann #

prettyList :: [Word8] -> Doc ann #

Pretty Word16 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Word16 -> Doc ann #

prettyList :: [Word16] -> Doc ann #

Pretty Word32 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Word32 -> Doc ann #

prettyList :: [Word32] -> Doc ann #

Pretty Word64 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Word64 -> Doc ann #

prettyList :: [Word64] -> Doc ann #

Pretty ()
>>> pretty ()
()

The argument is not used,

>>> pretty (error "Strict?" :: ())
()
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: () -> Doc ann #

prettyList :: [()] -> Doc ann #

Pretty Void

Finding a good example for printing something that does not exist is hard, so here is an example of printing a list full of nothing.

>>> pretty ([] :: [Void])
[]
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Void -> Doc ann #

prettyList :: [Void] -> Doc ann #

Pretty Text

(lazy Text instance, identical to the strict version)

Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Text -> Doc ann #

prettyList :: [Text] -> Doc ann #

Pretty Text

Automatically converts all newlines to line.

>>> pretty ("hello\nworld" :: Text)
hello
world

Note that line can be undone by group:

>>> group (pretty ("hello\nworld" :: Text))
hello world

Manually use hardline if you definitely want newlines.

Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Text -> Doc ann #

prettyList :: [Text] -> Doc ann #

Pretty a => Pretty [a]
>>> pretty [1,2,3]
[1, 2, 3]
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: [a] -> Doc ann #

prettyList :: [[a]] -> Doc ann #

Pretty a => Pretty (Maybe a)

Ignore Nothings, print Just contents.

>>> pretty (Just True)
True
>>> braces (pretty (Nothing :: Maybe Bool))
{}
>>> pretty [Just 1, Nothing, Just 3, Nothing]
[1, 3]
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Maybe a -> Doc ann #

prettyList :: [Maybe a] -> Doc ann #

Pretty a => Pretty (Identity a)
>>> pretty (Identity 1)
1
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Identity a -> Doc ann #

prettyList :: [Identity a] -> Doc ann #

Pretty a => Pretty (NonEmpty a) 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: NonEmpty a -> Doc ann #

prettyList :: [NonEmpty a] -> Doc ann #

(Pretty a1, Pretty a2) => Pretty (a1, a2)
>>> pretty (123, "hello")
(123, hello)
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: (a1, a2) -> Doc ann #

prettyList :: [(a1, a2)] -> Doc ann #

PrettyVar v => Pretty (Type loc v) Source # 
Instance details

Defined in Type.Check.HM.Pretty

Methods

pretty :: Type loc v -> Doc ann #

prettyList :: [Type loc v] -> Doc ann #

PrettyVar v => Pretty (Signature loc v) Source # 
Instance details

Defined in Type.Check.HM.Pretty

Methods

pretty :: Signature loc v -> Doc ann #

prettyList :: [Signature loc v] -> Doc ann #

(Pretty loc, PrettyVar var) => Pretty (TypeError loc var) Source # 
Instance details

Defined in Type.Check.HM.Pretty

Methods

pretty :: TypeError loc var -> Doc ann #

prettyList :: [TypeError loc var] -> Doc ann #

(Pretty loc, PrettyVar var) => Pretty (FixityCtx var (TypeError loc var)) Source # 
Instance details

Defined in Type.Check.HM.Pretty

Methods

pretty :: FixityCtx var (TypeError loc var) -> Doc ann #

prettyList :: [FixityCtx var (TypeError loc var)] -> Doc ann #

(PrettyVar v, Pretty prim) => Pretty (FixityCtx v (Term prim loc v)) Source # 
Instance details

Defined in Type.Check.HM.Pretty

Methods

pretty :: FixityCtx v (Term prim loc v) -> Doc ann #

prettyList :: [FixityCtx v (Term prim loc v)] -> Doc ann #

PrettyVar v => Pretty (FixityCtx v (Type loc v)) Source # 
Instance details

Defined in Type.Check.HM.Pretty

Methods

pretty :: FixityCtx v (Type loc v) -> Doc ann #

prettyList :: [FixityCtx v (Type loc v)] -> Doc ann #

PrettyVar v => Pretty (FixityCtx v (Signature loc v)) Source # 
Instance details

Defined in Type.Check.HM.Pretty

Methods

pretty :: FixityCtx v (Signature loc v) -> Doc ann #

prettyList :: [FixityCtx v (Signature loc v)] -> Doc ann #

(Pretty a1, Pretty a2, Pretty a3) => Pretty (a1, a2, a3)
>>> pretty (123, "hello", False)
(123, hello, False)
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: (a1, a2, a3) -> Doc ann #

prettyList :: [(a1, a2, a3)] -> Doc ann #

Pretty a => Pretty (Const a b) 
Instance details

Defined in Prettyprinter.Internal

Methods

pretty :: Const a b -> Doc ann #

prettyList :: [Const a b] -> Doc ann #

(PrettyVar v, Pretty prim) => Pretty (Term prim loc v) Source # 
Instance details

Defined in Type.Check.HM.Pretty

Methods

pretty :: Term prim loc v -> Doc ann #

prettyList :: [Term prim loc v] -> Doc ann #

Orphan instances

PrettyVar v => Pretty (Type loc v) Source # 
Instance details

Methods

pretty :: Type loc v -> Doc ann #

prettyList :: [Type loc v] -> Doc ann #

PrettyVar v => Pretty (Signature loc v) Source # 
Instance details

Methods

pretty :: Signature loc v -> Doc ann #

prettyList :: [Signature loc v] -> Doc ann #

(Pretty loc, PrettyVar var) => Pretty (TypeError loc var) Source # 
Instance details

Methods

pretty :: TypeError loc var -> Doc ann #

prettyList :: [TypeError loc var] -> Doc ann #

(PrettyVar v, Pretty prim) => Pretty (Term prim loc v) Source # 
Instance details

Methods

pretty :: Term prim loc v -> Doc ann #

prettyList :: [Term prim loc v] -> Doc ann #