repr-0.3.1: Render overloaded expressions to their textual representation.Source codeContentsIndex
Text.Repr
Synopsis
data Repr a
extract :: Repr a -> a
renderer :: Repr a -> Renderer
type Renderer = Precedence -> Fixity -> DString
type Precedence = Int
data Fixity
= Non
| L
| R
(<?>) :: Repr a -> DString -> Repr a
pure :: Show a => a -> Repr a
Documentation
data Repr a Source

Repr a is a value of type a paired with a way to render that value to its textual representation.

Reprs follow the property that given a Repr r if you evaluate the textual representation of r you should get the value or r.

Note that Repr a has an instance for most classes in base provided that a has instances for the respected classes. This allows you to write a numeric expression of type Repr a. For example:

*Repr> let r = 1.5 + 2 + (3 + (-4) * (5 - pi / sqrt 6)) :: Repr Double

You can extract the value of r:

*Repr> extract r
17.281195923884734

And you can render r to its textual representation using show:

*Repr> show r
"fromRational (3 % 2) + fromInteger 2 + (fromInteger 3 + negate (fromInteger 4) * (fromInteger 5 - pi / sqrt (fromInteger 6)))"
show/hide Instances
Bounded a => Bounded (Repr a)
Enum a => Enum (Repr a)
Eq a => Eq (Repr a)
Floating a => Floating (Repr a)
Fractional a => Fractional (Repr a)
Integral a => Integral (Repr a)
Num a => Num (Repr a)
Ord a => Ord (Repr a)
Read a => Read (Repr a)
Real a => Real (Repr a)
RealFloat a => RealFloat (Repr a)
RealFrac a => RealFrac (Repr a)
Show (Repr a)
Ix a => Ix (Repr a)
Typeable a => Typeable (Repr a)
IsString a => IsString (Repr a)
Monoid a => Monoid (Repr a)
HasResolution a => HasResolution (Repr a)
(Show a, Storable a) => Storable (Repr a)
Exception a => Exception (Repr a)
Bits a => Bits (Repr a)
(Random a, Show a) => Random (Repr a)
ToString a => ToString (Repr a)
extract :: Repr a -> aSource
Extract the value of the Repr.
renderer :: Repr a -> RendererSource
Extract the renderer of the Repr.
type Renderer = Precedence -> Fixity -> DStringSource

To render you need to supply the precedence and fixity of the enclosing context.

For more documentation about precedence and fixity see:

http://haskell.org/onlinereport/decls.html#sect4.4.2

The reason the renderer returns a DString, instead of for example a String has to do with efficiency. The rendering of expressions involves lots of left-factored appends i.e.: ((a ++ b) ++ c) ++ d. A DString, which is equivalent to a ShowS, has a O(1) append operation while a String has a O(n) append.

type Precedence = IntSource

The precedence of operators and function application.

  • Operators usually have a precedence in the range of 0 to 9.
  • Function application always has precedence 10.
data Fixity Source
Fixity of operators.
Constructors
NonNo fixity information.
LLeft associative operator.
RRight associative operator.
show/hide Instances
(<?>) :: Repr a -> DString -> Repr aSource

x <?> s annotates the rendering with the given string.

The rendering wil look like: "({- s -} ...)" where ... is the rendering of x.

This combinator is handy when you want to render the ouput of a function and you want to see how the parameters of the function contribute to the result. For example, suppose you defined the following function f:

f p0 p1 p2 = p0 ^ 2 + sqrt p1 * ([p2..] !! 10)

You can then apply f to some parameters annotated with some descriptive strings (the name of the parameter is usally a good idea):

f (1 <?> "p0") (2 <?> "p1") (3 <?> "p2")

The rendering will then look like:

"({- p0 -} fromInteger 1) * ({- p0 -} fromInteger 1) + sqrt ({- p1 -} (fromInteger 2)) * enumFrom ({- p2 -} (fromInteger 3)) !! 10"
pure :: Show a => a -> Repr aSource

pure x constructs a Repr which has x as value and the showed x as rendering. For example:

*Repr> let r = pure [1,2,3]
*Repr> extract r
[1,2,3]
*Repr> show r
"[1,2,3]"
Produced by Haddock version 2.4.2