portray-0.2.0: A pseudo-Haskell syntax type and typeclass producing it.
Safe HaskellNone
LanguageHaskell2010

Data.Portray

Description

Provides a compatibility layer of Haskell-like terms for pretty-printers.

Synopsis

Syntax Tree

newtype Portrayal Source #

The portrayal of a Haskell runtime value as a pseudo-Haskell syntax tree.

This can be rendered to various pretty-printing libraries' document types relatively easily; as such, it provides a lingua franca for integrating with pretty-printers, without incurring heavyweight dependencies.

Constructors

Portrayal 

Bundled Patterns

pattern Name :: Ident -> Portrayal

An identifier, including variable, constructor, and operator names.

The IdentKind distinguishes constructors, operators, etc. to enable backends to do things like syntax highlighting, without needing to engage in text manipulation to figure out syntax classes.

pattern LitInt :: Integer -> Portrayal

An integral literal.

pattern LitRat :: Rational -> Portrayal

A rational / floating-point literal.

pattern LitStr :: Text -> Portrayal

A string literal.

Some backends may be capable of flowing these onto multiple lines automatically, which they wouldn't be able to do with opaque text.

pattern LitChar :: Char -> Portrayal

A character literal.

pattern Opaque :: Text -> Portrayal

An opaque chunk of text included directly in the pretty-printed output.

This is used by things like strAtom that don't understand their contents, and will miss out on any syntax-aware features provided by backends.

pattern Apply :: Portrayal -> [Portrayal] -> Portrayal

A function or constructor application of arbitrary arity.

Although we could have just unary function application, this gives backends a hint about how to format the result: for example, the "pretty" backend prints the function (parenthesized if non-atomic) followed by the arguments indented by two spaces; a chain of unary applications would be needlessly parenthesized.

Given:

Apply (Name "These") [LitInt 2, LitInt 4]

We render something like These 2 4, or if line-wrapped:

These
  2
  4
pattern Binop :: Ident -> Infixity -> Portrayal -> Portrayal -> Portrayal

A binary operator application.

The fixity is used to avoid unnecessary parentheses, even in chains of operators of the same precedence.

Given:

Binop (Name "+") (infixl_ 6)
  [ Binop (Name "+") (infixl_ 6) [LitInt 2, LitInt 4]
  , "6"
  ]

We render something like: 2 + 4 + 6

pattern Tuple :: [Portrayal] -> Portrayal

A tuple.

Given Tuple [LitInt 2, LitInt 4], we render something like (2, 4)

pattern List :: [Portrayal] -> Portrayal

A list literal.

Given:

List
  [ Apply (Name "These") [LitInt 2, LitInt 4]
  , Apply (Name "That") [LitInt 6]
  ]

We render something like:

[ These 2 4
, That 6
]
pattern LambdaCase :: [(Portrayal, Portrayal)] -> Portrayal

A lambda-case.

Given LambdaCase [(LitInt 0, LitStr "hi"), (LitInt 1, LitStr "hello")], we render something like \case 0 -> "hi"; 1 -> "hello".

This can be useful in cases where meaningful values effectively appear in negative position in a type, like in a total map or table with non-integral indices.

pattern Record :: Portrayal -> [FactorPortrayal Portrayal] -> Portrayal

A record literal.

Given:

Record
  (Name "Identity")
  [FactorPortrayal (Name "runIdentity") (LitInt 2)]

We render something like:

Identity
  { runIdentity = 2
  }
pattern TyApp :: Portrayal -> Portrayal -> Portrayal

A type application.

Given TyApp (Name "Proxy") (Name "Int"), we render Proxy @Int

pattern TySig :: Portrayal -> Portrayal -> Portrayal

An explicit type signature.

Given TySig (Name "Proxy") [Apply (Name "Proxy") [Name "Int"]], we render Proxy :: Proxy Int

pattern Quot :: Text -> Portrayal -> Portrayal

A quasiquoter expression.

Given:

Quot (Opaque "expr") (Binop (Opaque "+") _ [Opaque "x", Opaque "!y"])

We render something like [expr| x + !y |]

pattern Unlines :: [Portrayal] -> Portrayal

A series of lines arranged vertically, if supported.

This is meant for use inside Quot, where it makes sense to use non-Haskell syntax.

pattern Nest :: Int -> Portrayal -> Portrayal

Indent a sub-expression by the given number of spaces.

This is meant for use inside Quot, where it makes sense to use non-Haskell syntax.

Instances

Instances details
Eq Portrayal Source # 
Instance details

Defined in Data.Portray

Read Portrayal Source # 
Instance details

Defined in Data.Portray

Show Portrayal Source # 
Instance details

Defined in Data.Portray

Generic Portrayal Source # 
Instance details

Defined in Data.Portray

Associated Types

type Rep Portrayal :: Type -> Type #

Portray Portrayal Source # 
Instance details

Defined in Data.Portray

type Rep Portrayal Source # 
Instance details

Defined in Data.Portray

type Rep Portrayal = D1 ('MetaData "Portrayal" "Data.Portray" "portray-0.2.0-inplace" 'True) (C1 ('MetaCons "Portrayal" 'PrefixI 'True) (S1 ('MetaSel ('Just "unPortrayal") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Fix PortrayalF))))

data FactorPortrayal a Source #

A Portrayal along with a field name; one piece of a record literal.

Constructors

FactorPortrayal 

Fields

Instances

Instances details
Functor FactorPortrayal Source # 
Instance details

Defined in Data.Portray

Methods

fmap :: (a -> b) -> FactorPortrayal a -> FactorPortrayal b #

(<$) :: a -> FactorPortrayal b -> FactorPortrayal a #

Foldable FactorPortrayal Source # 
Instance details

Defined in Data.Portray

Methods

fold :: Monoid m => FactorPortrayal m -> m #

foldMap :: Monoid m => (a -> m) -> FactorPortrayal a -> m #

foldMap' :: Monoid m => (a -> m) -> FactorPortrayal a -> m #

foldr :: (a -> b -> b) -> b -> FactorPortrayal a -> b #

foldr' :: (a -> b -> b) -> b -> FactorPortrayal a -> b #

foldl :: (b -> a -> b) -> b -> FactorPortrayal a -> b #

foldl' :: (b -> a -> b) -> b -> FactorPortrayal a -> b #

foldr1 :: (a -> a -> a) -> FactorPortrayal a -> a #

foldl1 :: (a -> a -> a) -> FactorPortrayal a -> a #

toList :: FactorPortrayal a -> [a] #

null :: FactorPortrayal a -> Bool #

length :: FactorPortrayal a -> Int #

elem :: Eq a => a -> FactorPortrayal a -> Bool #

maximum :: Ord a => FactorPortrayal a -> a #

minimum :: Ord a => FactorPortrayal a -> a #

sum :: Num a => FactorPortrayal a -> a #

product :: Num a => FactorPortrayal a -> a #

Traversable FactorPortrayal Source # 
Instance details

Defined in Data.Portray

Methods

traverse :: Applicative f => (a -> f b) -> FactorPortrayal a -> f (FactorPortrayal b) #

sequenceA :: Applicative f => FactorPortrayal (f a) -> f (FactorPortrayal a) #

mapM :: Monad m => (a -> m b) -> FactorPortrayal a -> m (FactorPortrayal b) #

sequence :: Monad m => FactorPortrayal (m a) -> m (FactorPortrayal a) #

Eq a => Eq (FactorPortrayal a) Source # 
Instance details

Defined in Data.Portray

Ord a => Ord (FactorPortrayal a) Source # 
Instance details

Defined in Data.Portray

Read a => Read (FactorPortrayal a) Source # 
Instance details

Defined in Data.Portray

Show a => Show (FactorPortrayal a) Source # 
Instance details

Defined in Data.Portray

Generic (FactorPortrayal a) Source # 
Instance details

Defined in Data.Portray

Associated Types

type Rep (FactorPortrayal a) :: Type -> Type #

Portray a => Portray (FactorPortrayal a) Source # 
Instance details

Defined in Data.Portray

type Rep (FactorPortrayal a) Source # 
Instance details

Defined in Data.Portray

type Rep (FactorPortrayal a) = D1 ('MetaData "FactorPortrayal" "Data.Portray" "portray-0.2.0-inplace" 'False) (C1 ('MetaCons "FactorPortrayal" 'PrefixI 'True) (S1 ('MetaSel ('Just "_fpFieldName") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Ident) :*: S1 ('MetaSel ('Just "_fpPortrayal") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a)))

data IdentKind Source #

The kind of identifier a particular Ident represents.

Instances

Instances details
Eq IdentKind Source # 
Instance details

Defined in Data.Portray

Ord IdentKind Source # 
Instance details

Defined in Data.Portray

Read IdentKind Source # 
Instance details

Defined in Data.Portray

Show IdentKind Source # 
Instance details

Defined in Data.Portray

Generic IdentKind Source # 
Instance details

Defined in Data.Portray

Associated Types

type Rep IdentKind :: Type -> Type #

Portray IdentKind Source # 
Instance details

Defined in Data.Portray

type Rep IdentKind Source # 
Instance details

Defined in Data.Portray

type Rep IdentKind = D1 ('MetaData "IdentKind" "Data.Portray" "portray-0.2.0-inplace" 'False) ((C1 ('MetaCons "VarIdent" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ConIdent" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "OpIdent" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "OpConIdent" 'PrefixI 'False) (U1 :: Type -> Type)))

data Ident Source #

An identifier or operator name.

Constructors

Ident !IdentKind !Text 

Instances

Instances details
Eq Ident Source # 
Instance details

Defined in Data.Portray

Methods

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

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

Ord Ident Source # 
Instance details

Defined in Data.Portray

Methods

compare :: Ident -> Ident -> Ordering #

(<) :: Ident -> Ident -> Bool #

(<=) :: Ident -> Ident -> Bool #

(>) :: Ident -> Ident -> Bool #

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

max :: Ident -> Ident -> Ident #

min :: Ident -> Ident -> Ident #

Read Ident Source # 
Instance details

Defined in Data.Portray

Show Ident Source # 
Instance details

Defined in Data.Portray

Methods

showsPrec :: Int -> Ident -> ShowS #

show :: Ident -> String #

showList :: [Ident] -> ShowS #

IsString Ident Source # 
Instance details

Defined in Data.Portray

Methods

fromString :: String -> Ident #

Generic Ident Source # 
Instance details

Defined in Data.Portray

Associated Types

type Rep Ident :: Type -> Type #

Methods

from :: Ident -> Rep Ident x #

to :: Rep Ident x -> Ident #

Portray Ident Source # 
Instance details

Defined in Data.Portray

type Rep Ident Source # 
Instance details

Defined in Data.Portray

Operator Fixity

data Assoc Source #

Associativity of an infix operator.

Constructors

AssocL 
AssocR 
AssocNope 

Instances

Instances details
Eq Assoc Source # 
Instance details

Defined in Data.Portray

Methods

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

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

Ord Assoc Source # 
Instance details

Defined in Data.Portray

Methods

compare :: Assoc -> Assoc -> Ordering #

(<) :: Assoc -> Assoc -> Bool #

(<=) :: Assoc -> Assoc -> Bool #

(>) :: Assoc -> Assoc -> Bool #

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

max :: Assoc -> Assoc -> Assoc #

min :: Assoc -> Assoc -> Assoc #

Read Assoc Source # 
Instance details

Defined in Data.Portray

Show Assoc Source # 
Instance details

Defined in Data.Portray

Methods

showsPrec :: Int -> Assoc -> ShowS #

show :: Assoc -> String #

showList :: [Assoc] -> ShowS #

Generic Assoc Source # 
Instance details

Defined in Data.Portray

Associated Types

type Rep Assoc :: Type -> Type #

Methods

from :: Assoc -> Rep Assoc x #

to :: Rep Assoc x -> Assoc #

Portray Assoc Source # 
Instance details

Defined in Data.Portray

type Rep Assoc Source # 
Instance details

Defined in Data.Portray

type Rep Assoc = D1 ('MetaData "Assoc" "Data.Portray" "portray-0.2.0-inplace" 'False) (C1 ('MetaCons "AssocL" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "AssocR" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AssocNope" 'PrefixI 'False) (U1 :: Type -> Type)))

data Infixity Source #

Associativity and binding precedence of an infix operator.

Constructors

Infixity !Assoc !Rational 

Instances

Instances details
Eq Infixity Source # 
Instance details

Defined in Data.Portray

Ord Infixity Source # 
Instance details

Defined in Data.Portray

Read Infixity Source # 
Instance details

Defined in Data.Portray

Show Infixity Source # 
Instance details

Defined in Data.Portray

Generic Infixity Source # 
Instance details

Defined in Data.Portray

Associated Types

type Rep Infixity :: Type -> Type #

Methods

from :: Infixity -> Rep Infixity x #

to :: Rep Infixity x -> Infixity #

Portray Infixity Source # 
Instance details

Defined in Data.Portray

type Rep Infixity Source # 
Instance details

Defined in Data.Portray

infix_ :: Rational -> Infixity Source #

Construct the Infixity corresponding to e.g. infix 6 +&&+*

infixl_ :: Rational -> Infixity Source #

Construct the Infixity corresponding to e.g. infixl 6 +&&+*

infixr_ :: Rational -> Infixity Source #

Construct the Infixity corresponding to e.g. infixr 6 +&&+*

Base Functor

data PortrayalF a Source #

A single level of pseudo-Haskell expression; used to define Portrayal.

Constructors

NameF !Ident

An identifier, including variable, constructor and operator names.

LitIntF !Integer

An integral literal. e.g. 42

LitRatF !Rational

A rational / floating-point literal. e.g. 42.002

LitStrF !Text

A string literal, stored without escaping or quotes. e.g. "hi"

LitCharF !Char

A character literal. e.g. 'a'

OpaqueF !Text

A chunk of opaque text. e.g. abc"]def

ApplyF !a [a]

A function application to several arguments.

BinopF !Ident !Infixity !a !a

A binary infix operator application to two arguments.

TupleF [a]

A tuple of sub-values.

ListF [a]

A list of sub-values.

LambdaCaseF [(a, a)]

A lambda-case expression.

RecordF !a [FactorPortrayal a]

A record construction/update syntax.

TyAppF !a !a

A TypeApplication.

TySigF !a !a

A term with explicit type signature.

QuotF !Text !a

A quasiquoter term with the given name.

UnlinesF [a]

A collection of vertically-aligned lines

NestF !Int !a

A subdocument indented by the given number of columns.

Instances

Instances details
Functor PortrayalF Source # 
Instance details

Defined in Data.Portray

Methods

fmap :: (a -> b) -> PortrayalF a -> PortrayalF b #

(<$) :: a -> PortrayalF b -> PortrayalF a #

Foldable PortrayalF Source # 
Instance details

Defined in Data.Portray

Methods

fold :: Monoid m => PortrayalF m -> m #

foldMap :: Monoid m => (a -> m) -> PortrayalF a -> m #

foldMap' :: Monoid m => (a -> m) -> PortrayalF a -> m #

foldr :: (a -> b -> b) -> b -> PortrayalF a -> b #

foldr' :: (a -> b -> b) -> b -> PortrayalF a -> b #

foldl :: (b -> a -> b) -> b -> PortrayalF a -> b #

foldl' :: (b -> a -> b) -> b -> PortrayalF a -> b #

foldr1 :: (a -> a -> a) -> PortrayalF a -> a #

foldl1 :: (a -> a -> a) -> PortrayalF a -> a #

toList :: PortrayalF a -> [a] #

null :: PortrayalF a -> Bool #

length :: PortrayalF a -> Int #

elem :: Eq a => a -> PortrayalF a -> Bool #

maximum :: Ord a => PortrayalF a -> a #

minimum :: Ord a => PortrayalF a -> a #

sum :: Num a => PortrayalF a -> a #

product :: Num a => PortrayalF a -> a #

Traversable PortrayalF Source # 
Instance details

Defined in Data.Portray

Methods

traverse :: Applicative f => (a -> f b) -> PortrayalF a -> f (PortrayalF b) #

sequenceA :: Applicative f => PortrayalF (f a) -> f (PortrayalF a) #

mapM :: Monad m => (a -> m b) -> PortrayalF a -> m (PortrayalF b) #

sequence :: Monad m => PortrayalF (m a) -> m (PortrayalF a) #

Eq a => Eq (PortrayalF a) Source # 
Instance details

Defined in Data.Portray

Methods

(==) :: PortrayalF a -> PortrayalF a -> Bool #

(/=) :: PortrayalF a -> PortrayalF a -> Bool #

Ord a => Ord (PortrayalF a) Source # 
Instance details

Defined in Data.Portray

Read a => Read (PortrayalF a) Source # 
Instance details

Defined in Data.Portray

Show a => Show (PortrayalF a) Source # 
Instance details

Defined in Data.Portray

Generic (PortrayalF a) Source # 
Instance details

Defined in Data.Portray

Associated Types

type Rep (PortrayalF a) :: Type -> Type #

Methods

from :: PortrayalF a -> Rep (PortrayalF a) x #

to :: Rep (PortrayalF a) x -> PortrayalF a #

Portray a => Portray (PortrayalF a) Source # 
Instance details

Defined in Data.Portray

type Rep (PortrayalF a) Source # 
Instance details

Defined in Data.Portray

type Rep (PortrayalF a) = D1 ('MetaData "PortrayalF" "Data.Portray" "portray-0.2.0-inplace" 'False) ((((C1 ('MetaCons "NameF" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Ident)) :+: C1 ('MetaCons "LitIntF" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Integer))) :+: (C1 ('MetaCons "LitRatF" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Rational)) :+: C1 ('MetaCons "LitStrF" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)))) :+: ((C1 ('MetaCons "LitCharF" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Char)) :+: C1 ('MetaCons "OpaqueF" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text))) :+: (C1 ('MetaCons "ApplyF" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [a])) :+: C1 ('MetaCons "BinopF" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Ident) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Infixity)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a)))))) :+: (((C1 ('MetaCons "TupleF" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [a])) :+: C1 ('MetaCons "ListF" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [a]))) :+: (C1 ('MetaCons "LambdaCaseF" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(a, a)])) :+: C1 ('MetaCons "RecordF" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [FactorPortrayal a])))) :+: ((C1 ('MetaCons "TyAppF" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a)) :+: C1 ('MetaCons "TySigF" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a))) :+: (C1 ('MetaCons "QuotF" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a)) :+: (C1 ('MetaCons "UnlinesF" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [a])) :+: C1 ('MetaCons "NestF" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 a)))))))

Class

class Portray a where Source #

A class providing rendering to pseudo-Haskell syntax.

Instances should guarantee that they produce output that could, in principle, be parsed as Haskell source that evaluates to a value equal to the one being printed, provided the right functions, quasiquoters, plugins, extensions, etc. are available. Note this doesn't require you to /actually implement/ these functions, quasiquoters, etc; just that it would be feasible to do so.

Most of the time, this requirement is dispatched simply by portraying the datum as its actual tree of data constructors. However, since this can sometimes be unwieldy, you might wish to have more stylized portrayals.

The most basic form of stylized portrayal is to retract the datum through a function, e.g. portraying 4 :| [2] :: NonEmpty a as fromList [4, 2].

For cases where you actually want to escape the Haskell syntax, you can use (or pretend to use) quasiquoter syntax, e.g. portray EAdd (ELit 2) (EVar a) as [expr| 2 + a |].

Minimal complete definition

portray

Methods

portray :: a -> Portrayal Source #

portrayList :: [a] -> Portrayal Source #

Portray a list of the given element type

This is part of a Haskell98 mechanism for special-casing String to print differently from other lists; clients of the library can largely ignore it.

Instances

Instances details
Portray Bool Source # 
Instance details

Defined in Data.Portray

Portray Char Source # 
Instance details

Defined in Data.Portray

Portray Double Source # 
Instance details

Defined in Data.Portray

Portray Float Source # 
Instance details

Defined in Data.Portray

Portray Int Source # 
Instance details

Defined in Data.Portray

Portray Int8 Source # 
Instance details

Defined in Data.Portray

Portray Int16 Source # 
Instance details

Defined in Data.Portray

Portray Int32 Source # 
Instance details

Defined in Data.Portray

Portray Int64 Source # 
Instance details

Defined in Data.Portray

Portray Integer Source # 
Instance details

Defined in Data.Portray

Portray Natural Source # 
Instance details

Defined in Data.Portray

Portray Word Source # 
Instance details

Defined in Data.Portray

Portray Word8 Source # 
Instance details

Defined in Data.Portray

Portray Word16 Source # 
Instance details

Defined in Data.Portray

Portray Word32 Source # 
Instance details

Defined in Data.Portray

Portray Word64 Source # 
Instance details

Defined in Data.Portray

Portray CallStack Source # 
Instance details

Defined in Data.Portray

Portray SomeTypeRep Source # 
Instance details

Defined in Data.Portray

Portray () Source # 
Instance details

Defined in Data.Portray

Portray TyCon Source # 
Instance details

Defined in Data.Portray

Portray Void Source # 
Instance details

Defined in Data.Portray

Portray Text Source # 
Instance details

Defined in Data.Portray

Portray Portrayal Source # 
Instance details

Defined in Data.Portray

Portray Ident Source # 
Instance details

Defined in Data.Portray

Portray IdentKind Source # 
Instance details

Defined in Data.Portray

Portray Infixity Source # 
Instance details

Defined in Data.Portray

Portray Assoc Source # 
Instance details

Defined in Data.Portray

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

Defined in Data.Portray

Methods

portray :: [a] -> Portrayal Source #

portrayList :: [[a]] -> Portrayal Source #

Portray a => Portray (Maybe a) Source # 
Instance details

Defined in Data.Portray

Portray a => Portray (Ratio a) Source # 
Instance details

Defined in Data.Portray

Portray a => Portray (Identity a) Source # 
Instance details

Defined in Data.Portray

Portray a => Portray (NonEmpty a) Source # 
Instance details

Defined in Data.Portray

Portray a => Portray (IntMap a) Source # 
Instance details

Defined in Data.Portray

Portray a => Portray (Seq a) Source # 
Instance details

Defined in Data.Portray

(Ord a, Portray a) => Portray (Set a) Source # 
Instance details

Defined in Data.Portray

Show a => Portray (ShowAtom a) Source # 
Instance details

Defined in Data.Portray

Real a => Portray (PortrayRatLit a) Source # 
Instance details

Defined in Data.Portray

Integral a => Portray (PortrayIntLit a) Source # 
Instance details

Defined in Data.Portray

(forall a. Portray a => Portray (f a)) => Portray (Fix f) Source # 
Instance details

Defined in Data.Portray

Portray a => Portray (FactorPortrayal a) Source # 
Instance details

Defined in Data.Portray

Portray a => Portray (PortrayalF a) Source # 
Instance details

Defined in Data.Portray

(Portray a, Portray b) => Portray (Either a b) Source # 
Instance details

Defined in Data.Portray

Portray (TypeRep a) Source # 
Instance details

Defined in Data.Portray

(Portray a, Portray b) => Portray (a, b) Source # 
Instance details

Defined in Data.Portray

Methods

portray :: (a, b) -> Portrayal Source #

portrayList :: [(a, b)] -> Portrayal Source #

Portray (Proxy a) Source # 
Instance details

Defined in Data.Portray

(Ord k, Portray k, Portray a) => Portray (Map k a) Source # 
Instance details

Defined in Data.Portray

(IsList a, Portray (Item a)) => Portray (Wrapped IsList a) Source #

Portray a list-like type as "fromList [...]".

Instance details

Defined in Data.Portray

(Generic a, GPortray (Rep a)) => Portray (Wrapped Generic a) Source # 
Instance details

Defined in Data.Portray

(Portray a, Portray b, Portray c) => Portray (a, b, c) Source # 
Instance details

Defined in Data.Portray

Methods

portray :: (a, b, c) -> Portrayal Source #

portrayList :: [(a, b, c)] -> Portrayal Source #

Portray a => Portray (Const a b) Source # 
Instance details

Defined in Data.Portray

Portray (Coercion a b) Source # 
Instance details

Defined in Data.Portray

Portray (a :~: b) Source # 
Instance details

Defined in Data.Portray

Methods

portray :: (a :~: b) -> Portrayal Source #

portrayList :: [a :~: b] -> Portrayal Source #

(Portray a, Portray b, Portray c, Portray d) => Portray (a, b, c, d) Source # 
Instance details

Defined in Data.Portray

Methods

portray :: (a, b, c, d) -> Portrayal Source #

portrayList :: [(a, b, c, d)] -> Portrayal Source #

(Portray a, Portray b, Portray c, Portray d, Portray e) => Portray (a, b, c, d, e) Source # 
Instance details

Defined in Data.Portray

Methods

portray :: (a, b, c, d, e) -> Portrayal Source #

portrayList :: [(a, b, c, d, e)] -> Portrayal Source #

Via Generic

class GPortray f where Source #

Generics-based deriving of Portray.

Exported mostly to give Haddock something to link to; use deriving Portray via Wrapped Generic MyType.

Methods

gportray :: f a -> Portrayal Source #

Instances

Instances details
GPortray (V1 :: k -> Type) Source # 
Instance details

Defined in Data.Portray

Methods

gportray :: forall (a :: k0). V1 a -> Portrayal Source #

(Constructor ('MetaCons n fx 'False), GPortrayProduct f) => GPortray (C1 ('MetaCons n fx 'False) f :: k -> Type) Source # 
Instance details

Defined in Data.Portray

Methods

gportray :: forall (a :: k0). C1 ('MetaCons n fx 'False) f a -> Portrayal Source #

(KnownSymbol n, GPortrayProduct f) => GPortray (C1 ('MetaCons n fx 'True) f :: k -> Type) Source # 
Instance details

Defined in Data.Portray

Methods

gportray :: forall (a :: k0). C1 ('MetaCons n fx 'True) f a -> Portrayal Source #

(GPortray f, GPortray g) => GPortray (f :+: g :: k -> Type) Source # 
Instance details

Defined in Data.Portray

Methods

gportray :: forall (a :: k0). (f :+: g) a -> Portrayal Source #

GPortray f => GPortray (D1 d f :: k -> Type) Source # 
Instance details

Defined in Data.Portray

Methods

gportray :: forall (a :: k0). D1 d f a -> Portrayal Source #

class GPortrayProduct f where Source #

Generics-based deriving of Portray for product types.

Exported mostly to give Haddock something to link to; use deriving Portray via Wrapped Generic MyType.

Instances

Instances details
GPortrayProduct (U1 :: k -> Type) Source # 
Instance details

Defined in Data.Portray

(GPortrayProduct f, GPortrayProduct g) => GPortrayProduct (f :*: g :: k -> Type) Source # 
Instance details

Defined in Data.Portray

Methods

gportrayProduct :: forall (a :: k0). (f :*: g) a -> [FactorPortrayal Portrayal] -> [FactorPortrayal Portrayal] Source #

(Selector s, Portray a) => GPortrayProduct (S1 s (K1 i a :: k -> Type) :: k -> Type) Source # 
Instance details

Defined in Data.Portray

Methods

gportrayProduct :: forall (a0 :: k0). S1 s (K1 i a) a0 -> [FactorPortrayal Portrayal] -> [FactorPortrayal Portrayal] Source #

Via Show, Integral, and Real

newtype PortrayIntLit a Source #

A newtype wrapper providing a Portray instance via Integral.

Constructors

PortrayIntLit a 

Instances

Instances details
Integral a => Portray (PortrayIntLit a) Source # 
Instance details

Defined in Data.Portray

newtype PortrayRatLit a Source #

A newtype wrapper providing a Portray instance via Real.

Constructors

PortrayRatLit a 

Instances

Instances details
Real a => Portray (PortrayRatLit a) Source # 
Instance details

Defined in Data.Portray

newtype ShowAtom a Source #

A newtype wrapper providing a Portray instance via showAtom.

Beware that instances made this way will not be subject to syntax highlighting or layout, and will be shown as plain text all on one line. It's recommended to derive instances via Wrapped Generic or hand-write more detailed instances instead.

Constructors

ShowAtom 

Fields

Instances

Instances details
Show a => Portray (ShowAtom a) Source # 
Instance details

Defined in Data.Portray

Convenience

showAtom :: Show a => a -> Portrayal Source #

Convenience for using show and wrapping the result in Opaque.

Note this will be excluded from syntax highlighting and layout; see the cautionary text on ShowAtom.

strAtom :: String -> Portrayal Source #

Convenience for building an Opaque from a String.

Note this will be excluded from syntax highlighting for lack of semantic information; consider using Name instead.

strQuot :: String -> Portrayal -> Portrayal Source #

Convenience for building a Quot from a String.

strBinop :: IdentKind -> String -> Infixity -> Portrayal -> Portrayal -> Portrayal Source #

Convenience for building a Binop with a String operator name.

Miscellaneous

newtype Fix f Source #

Fixed-point of a functor.

There are many packages that provide equivalent things, but we need almost nothing but the type itself, so we may as well just define one locally.

Constructors

Fix (f (Fix f)) 

Instances

Instances details
(forall a. Eq a => Eq (f a)) => Eq (Fix f) Source # 
Instance details

Defined in Data.Portray

Methods

(==) :: Fix f -> Fix f -> Bool #

(/=) :: Fix f -> Fix f -> Bool #

(forall a. Read a => Read (f a)) => Read (Fix f) Source # 
Instance details

Defined in Data.Portray

(forall a. Show a => Show (f a)) => Show (Fix f) Source # 
Instance details

Defined in Data.Portray

Methods

showsPrec :: Int -> Fix f -> ShowS #

show :: Fix f -> String #

showList :: [Fix f] -> ShowS #

Generic (Fix f) Source # 
Instance details

Defined in Data.Portray

Associated Types

type Rep (Fix f) :: Type -> Type #

Methods

from :: Fix f -> Rep (Fix f) x #

to :: Rep (Fix f) x -> Fix f #

(forall a. Portray a => Portray (f a)) => Portray (Fix f) Source # 
Instance details

Defined in Data.Portray

type Rep (Fix f) Source # 
Instance details

Defined in Data.Portray

type Rep (Fix f) = D1 ('MetaData "Fix" "Data.Portray" "portray-0.2.0-inplace" 'True) (C1 ('MetaCons "Fix" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f (Fix f)))))

cata :: Functor f => (f a -> a) -> Fix f -> a Source #

Fold a Fix f to a given a function to collapse each layer.

portrayCallStack :: [(String, SrcLoc)] -> Portrayal Source #

Construct a Portrayal of a CallStack without the "callStack" prefix.

portrayType :: TypeRep a -> Portrayal Source #

Portray the type described by the given TypeRep.

This gives the type-level syntax for the type, as opposed to value-level syntax that would construct the TypeRep.