numerals-0.4: Convert numbers to number words

Safe HaskellNone

Text.Numeral.Render

Contents

Synopsis

Rendering numerals

renderSource

Arguments

:: Repr i

Representation.

-> i

Initial inflection.

-> Exp i

The expression to render.

-> Maybe Text 

Renders an expression to a Text value according to a certain representation and inflection.

Representation of numerals

data Repr i Source

A representation for numerals.

A Repr contains all the information on how to render an Expression to a Text value.

Constructors

Repr 

Fields

reprUnknown :: Maybe Text

Representation for unknown values.

reprValue :: i -> -> Maybe (Ctx (Exp i) -> Text)

Renders a literal value. Not necessarily defined for every value.

reprNeg :: Maybe (Exp i -> Ctx (Exp i) -> Text)

Renders a negation. This concerns the negation itself, not the thing being negated.

reprAdd :: Maybe (Exp i -> Exp i -> Ctx (Exp i) -> Text)

Renders an addition. This concerns the addition itself, not the things being added. For example: In "one hundred and eighty" this function would be responsible for rendering the "and".

reprMul :: Maybe (Exp i -> Exp i -> Ctx (Exp i) -> Text)

Renders a multiplication. This concerns the multiplication itself, not the things being multiplied.

reprSub :: Maybe (Exp i -> Exp i -> Ctx (Exp i) -> Text)

Renders a subtraction. This concerns the subtraction itself, not the things being subtracted.

reprFrac :: Maybe (Exp i -> Exp i -> Ctx (Exp i) -> Text)

Renders a fraction. This concerns the fraction itself, not the numerator or the denominator.

reprScale :: ScaleRepr i

Renders a step in a scale of large values.

reprNegCombine :: Maybe (Text -> Text -> Exp i -> Text)

Combines a negation and the thing being negated. For example: this would combine "minus" and "three" into "minus three".

reprAddCombine :: Maybe (Text -> Text -> Exp i -> Text -> Exp i -> Text)

Combines an addition and the things being added.

reprMulCombine :: Maybe (Text -> Text -> Exp i -> Text -> Exp i -> Text)

Combines a multiplication and the things being multiplied.

reprSubCombine :: Maybe (Text -> Text -> Exp i -> Text -> Exp i -> Text)

Combines a subtraction and the things being subtracted.

reprFracCombine :: Maybe (Text -> Text -> Exp i -> Text -> Exp i -> Text)

Combines a fraction and the numerator and denominator.

type ScaleRepr iSource

Arguments

 = i 
->

Base.

->

Offset.

-> Exp i

Rank.

-> Ctx (Exp i)

Rank context.

-> Maybe Text 

Function that renders the representation of a step in a scale of large values. The value represented by the step is 10 ^ (rank * base + offset).

defaultRepr :: Repr infSource

The default representation.

Only the combining functions are defined. The rest are either Nothing or always produce Nothing.

Context of expressions

data Ctx α Source

A context in which an Expression appears.

Constructors

CtxEmpty

The empty context. Used for top level expressions.

CtxNeg (Ctx α)

Negation context.

CtxAdd Side α (Ctx α)

Addition context.

CtxMul Side α (Ctx α)

Multiplication context.

CtxSub Side α (Ctx α)

Subtraction context.

CtxFrac Side α (Ctx α)

Fraction context.

CtxScale (Ctx α)

Scale context.

CtxDual (Ctx α)

Dual context.

CtxPlural (Ctx α)

Plural context.

Instances

Eq α => Eq (Ctx α) 
Show α => Show (Ctx α) 

isOutside :: Side -> Ctx α -> BoolSource

Checks whether a context is completely on the outside of an expression, either left or right.

Given the following expression:

 Add (Lit 1000) (Add (Mul (Lit 2) (Lit 100)) (Add (Lit 4) (Mul (Lit 3) (Lit 10))))

On the left we have Lit 1000 and on the right Lit 10.