ordinal-0.5.0.0: Convert numbers to words in different languages.
Maintainerhapytexeu+gh@gmail.com
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

Text.Numerals.Algorithm

Description

A module that contains data types and functions to automatically convert a number to words. It has tooling for a NumeralsAlgorithm as well as a HighNumberAlgorithm that is used to generate a ShortScale or LongScale.

Synopsis

Data types for number algorithms

data NumeralsAlgorithm Source #

A data type for algorithmic number to word conversions. Most western languages likely can work with this data type.

numeralsAlgorithm :: (Foldable f, Foldable g) => Text -> Text -> Text -> f Text -> g (Integer, Text) -> FreeValueSplitter -> FreeMergerFunction -> (Text -> Text) -> FreeNumberToWords -> ClockText -> NumeralsAlgorithm Source #

A smart constructor for the NumeralsAlgorithm type. This constructor allows one to use an arbitrary Foldable type for the low words and mid words. It will also order the midwords accordingly.

Large number algorithms

data HighNumberAlgorithm Source #

A data type used for to map larger numbers to words. This data type supports the short scale and long scale with Latin prefixes, and custom suffixes. The Default value is the short scale with illion as suffix. This is used in English for large numbers.

Instances

Instances details
Eq HighNumberAlgorithm Source # 
Instance details

Defined in Text.Numerals.Algorithm

Data HighNumberAlgorithm Source # 
Instance details

Defined in Text.Numerals.Algorithm

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> HighNumberAlgorithm -> c HighNumberAlgorithm #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c HighNumberAlgorithm #

toConstr :: HighNumberAlgorithm -> Constr #

dataTypeOf :: HighNumberAlgorithm -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c HighNumberAlgorithm) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c HighNumberAlgorithm) #

gmapT :: (forall b. Data b => b -> b) -> HighNumberAlgorithm -> HighNumberAlgorithm #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> HighNumberAlgorithm -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> HighNumberAlgorithm -> r #

gmapQ :: (forall d. Data d => d -> u) -> HighNumberAlgorithm -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> HighNumberAlgorithm -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> HighNumberAlgorithm -> m HighNumberAlgorithm #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> HighNumberAlgorithm -> m HighNumberAlgorithm #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> HighNumberAlgorithm -> m HighNumberAlgorithm #

Ord HighNumberAlgorithm Source # 
Instance details

Defined in Text.Numerals.Algorithm

Read HighNumberAlgorithm Source # 
Instance details

Defined in Text.Numerals.Algorithm

Show HighNumberAlgorithm Source # 
Instance details

Defined in Text.Numerals.Algorithm

Generic HighNumberAlgorithm Source # 
Instance details

Defined in Text.Numerals.Algorithm

Associated Types

type Rep HighNumberAlgorithm :: Type -> Type #

Arbitrary HighNumberAlgorithm Source # 
Instance details

Defined in Text.Numerals.Algorithm

Default HighNumberAlgorithm Source # 
Instance details

Defined in Text.Numerals.Algorithm

NFData HighNumberAlgorithm Source # 
Instance details

Defined in Text.Numerals.Algorithm

Methods

rnf :: HighNumberAlgorithm -> () #

ValueSplit HighNumberAlgorithm Source # 
Instance details

Defined in Text.Numerals.Algorithm

type Rep HighNumberAlgorithm Source # 
Instance details

Defined in Text.Numerals.Algorithm

type Rep HighNumberAlgorithm = D1 ('MetaData "HighNumberAlgorithm" "Text.Numerals.Algorithm" "ordinal-0.5.0.0-EO9ST13hFnV3ZkeDBMRak1" 'False) (C1 ('MetaCons "ShortScale" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: C1 ('MetaCons "LongScale" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

shortScale :: Text -> FreeValueSplitter Source #

Construct a FreeValueSplitter function for the given suffix for a short scale.

longScale :: Text -> Text -> FreeValueSplitter Source #

Construct a FreeValueSplitter function for the given suffixes for a long scale.

shortScaleTitle :: Text -> FreeValueSplitter Source #

Construct a FreeValueSplitter function for the given suffix for a short scale, the names are written in title case.

longScaleTitle :: Text -> Text -> FreeValueSplitter Source #

Construct a FreeValueSplitter function for the given suffixes for a long scale, the names are written in title case.

valueSplit' Source #

Arguments

:: (Text -> Text)

The post-processing function.

-> HighNumberAlgorithm

The HighNumberAlgorithm that is used.

-> FreeValueSplitter

The FreeValueSplitter result.

Generate a value splitter for a HighNumberAlgorithm but where the result is post-processed by a function.

Conversion to a NumberSegment

toSegments Source #

Arguments

:: Integral i 
=> Vector Text

A Vector of low words.

-> [(Integer, Text)]

The list of name and the names of these numbers in descending order for the mid words.

-> ValueSplitter i

The ValueSplitter used for large numbers, likely a splitter from a short scale or long scale.

-> NumberSegmenting i

The function that maps the number to the NumberSegment.

Convert the given number to a NumberSegment with the given Vector of low numbers, the sorted list of mid numbers, and a FreeValueSplitter for large numbers.

toSegmentLow Source #

Arguments

:: Integral i 
=> Vector Text

A Vector of low words.

-> NumberSegmenting i

The function that maps the number to the NumberSegment.

Convert the given number to a NumberSegment with the given Vector of low numbers. Mid words and large numbers are not taken into account. This is often the next step after the toSegmentMid.

toSegmentMid Source #

Arguments

:: Integral i 
=> Vector Text

A Vector of low words.

-> [(Integer, Text)]

The list of name and the names of these numbers in descending order for the mid words.

-> NumberSegmenting i

The function that maps the number to the NumberSegment.

Convert the given number to a NumberSegment with the given Vector of low numbers, and the sorted list of mid numbers. Large numbers are not taken into account. This is often the next step after the toSegmentHigh.

toSegmentHigh Source #

Arguments

:: Integral i 
=> Vector Text

A Vector of low words.

-> [(Integer, Text)]

The list of name and the names of these numbers in descending order for the mid words.

-> ValueSplitter i

The ValueSplitter used for large numbers, likely a splitter from a short scale or long scale.

-> NumberSegmenting i

The function that maps the number to the NumberSegment.

Convert the given number to a NumberSegment with the given Vector of low numbers, the sorted list of mid numbers, and a FreeValueSplitter for large numbers.

Segment compression

compressSegments Source #

Arguments

:: Integral i 
=> Text

The value used for one in the specific language.

-> MergerFunction i

The MergerFunction for the specific language that implements the grammar rules how to merge values.

-> NumberSegment i

The given NumberSegment value to turn into a Text object.

-> Text

The Text object that contains the name of the number stored in the NumberSegment.

Use the given MergerFunction to compress the NumberSegment to a single Text object that represents the given number.