repr-0.4.1.1: Render overloaded expressions to their textual representation.

MaintainerBas van Dijk <v.dijk.bas@gmail.com>

Text.Repr

Contents

Description

Textual representation of values.

Synopsis

Documentation

data Repr α Source

Repr α is a value of type α 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 α has an instance for most classes in base provided that α has instances for the respected classes. This allows you to write a numeric expression of type Repr α. 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
"1.5 + 2.0 + (3.0 + negate 4.0 * (5.0 - pi / sqrt 6.0))"

Instances

Typeable1 Repr 
Bounded α => Bounded (Repr α) 
Enum α => Enum (Repr α) 
Eq α => Eq (Repr α) 
Floating α => Floating (Repr α) 
Fractional α => Fractional (Repr α) 
Integral α => Integral (Repr α) 
Num α => Num (Repr α) 
Ord α => Ord (Repr α) 
Read α => Read (Repr α) 
Real α => Real (Repr α) 
RealFloat α => RealFloat (Repr α) 
RealFrac α => RealFrac (Repr α) 
Show (Repr α) 
Ix α => Ix (Repr α) 
IsString α => IsString (Repr α) 
HasResolution α => HasResolution (Repr α) 
Monoid α => Monoid (Repr α) 
(Show α, Storable α) => Storable (Repr α) 
Bits α => Bits (Repr α) 
Exception α => Exception (Repr α) 
(Random α, Show α) => Random (Repr α) 

extract :: Repr α -> αSource

Extract the value of the Repr.

renderer :: Repr α -> 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

Non

No fixity information.

L

Left associative operator.

R

Right associative operator.

Instances

(<?>) :: Repr α -> DString -> Repr αSource

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 α => α -> Repr αSource

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]"

repr :: α -> Renderer -> Repr αSource

Construct a Repr from the given value and its renderer.

Utilities

Handy utilities when writing type class instances for Reprs.

constant :: α -> DString -> Repr αSource

For example: pi = constant pi "pi"

to :: (α -> β) -> Repr α -> βSource

For example: toInteger = to toInteger

to2 :: (α -> β -> γ) -> Repr α -> Repr β -> γSource

For example: (<) = to2 (<)

app :: (α -> β) -> DString -> Repr α -> Repr βSource

For example: abs = app abs "abs"

app2 :: (α -> β -> γ) -> DString -> Repr α -> Repr β -> Repr γSource

For example: div = app2 div "div"

infx :: Fixity -> Precedence -> (α -> β -> γ) -> DString -> Repr α -> Repr β -> Repr γSource

For example: (+) = infx L 6 (+) "+"