unicode-tricks-0.14.1.0: Functions to work with unicode blocks more convenient.
Maintainer[email protected]
Stabilityexperimental
PortabilityPOSIX
Safe HaskellSafe
LanguageHaskell2010

Data.Char.Number.Tally

Description

This module aims to convert numbers to (Western) tally marks and vice versa.

Synopsis

Data types to represent tally marks

data TallyLiteral Source #

A tally literal that is either a one (𝍷), or five grouped together (𝍸).

Constructors

I

The unicode character for the tally numeral one: 𝍷.

V

The unicode character for the tally numeral five: 𝍸.

Instances

Instances details
Arbitrary TallyLiteral Source # 
Instance details

Defined in Data.Char.Number.Tally

Data TallyLiteral Source # 
Instance details

Defined in Data.Char.Number.Tally

Methods

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

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

toConstr :: TallyLiteral -> Constr #

dataTypeOf :: TallyLiteral -> DataType #

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

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

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

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

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

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

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

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

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

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

Bounded TallyLiteral Source # 
Instance details

Defined in Data.Char.Number.Tally

Enum TallyLiteral Source # 
Instance details

Defined in Data.Char.Number.Tally

Generic TallyLiteral Source # 
Instance details

Defined in Data.Char.Number.Tally

Associated Types

type Rep TallyLiteral :: Type -> Type #

Read TallyLiteral Source # 
Instance details

Defined in Data.Char.Number.Tally

Show TallyLiteral Source # 
Instance details

Defined in Data.Char.Number.Tally

NFData TallyLiteral Source # 
Instance details

Defined in Data.Char.Number.Tally

Methods

rnf :: TallyLiteral -> () #

Eq TallyLiteral Source # 
Instance details

Defined in Data.Char.Number.Tally

Hashable TallyLiteral Source # 
Instance details

Defined in Data.Char.Number.Tally

UnicodeCharacter TallyLiteral Source # 
Instance details

Defined in Data.Char.Number.Tally

UnicodeText TallyLiteral Source # 
Instance details

Defined in Data.Char.Number.Tally

type Rep TallyLiteral Source # 
Instance details

Defined in Data.Char.Number.Tally

type Rep TallyLiteral = D1 ('MetaData "TallyLiteral" "Data.Char.Number.Tally" "unicode-tricks-0.14.1.0-EInLeozqGjBL3vIQTNPsAm" 'False) (C1 ('MetaCons "I" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "V" 'PrefixI 'False) (U1 :: Type -> Type))

Convert a number to TallyLiterals

toLiterals Source #

Arguments

:: Integral i 
=> i

The given number to convert.

-> Maybe [TallyLiteral]

A list of TallyLiterals if the given number can be specified with tally marks, Nothing otherwise.

Convert a given positive natural number to a sequence of TallyLiterals.

toLiterals' Source #

Arguments

:: Integral i 
=> i

The given number to convert.

-> [TallyLiteral]

A list of TallyLiterals that denotes the given number.

Convert a given number to a sequence of TallyLiterals, for negative numbers or zero, the behavior is unspecified.

tallyNumber Source #

Arguments

:: Integral i 
=> i

The given number to convert.

-> Maybe Text

A Text with the tally marks wrapped in a Just if the number can be represented with tally marks; Nothing otherwise.

Convert a given positive natural number to a Text object with the tally marks for that number.

tallyNumber' Source #

Arguments

:: Integral i 
=> i

The given number to convert.

-> Text

The corresponding Text that contains the number as tally marks.

Convert a given number to a Text object with the tally marks for that number, for negative numbers or zero, the behavior is unspecified.