unicode-tricks-0.12.1.0: Functions to work with unicode blocks more convenient.
Maintainerhapytexeu+gh@gmail.com
Stabilityexperimental
PortabilityPOSIX
Safe HaskellSafe
LanguageHaskell2010

Data.Char.Number.Roman

Description

This module aims to convert Roman numerals to a String of unicode characters that represent the corresponding Roman number.

One can convert numbers to Roman numerals in upper case and lower case, and in Additive and Subtractive style.

Synopsis

Data types to represent Roman numerals

data RomanLiteral Source #

Roman numerals for which a unicode character exists.

Constructors

I

The unicode character for the Roman numeral one: Ⅰ.

II

The unicode character for the Roman numeral two: Ⅱ.

III

The unicode character for the Roman numeral three: Ⅲ.

IV

The unicode character for the Roman numeral four: Ⅳ.

V

The unicode character for the Roman numeral five: Ⅴ.

VI

The unicode character for the Roman numeral six: Ⅵ.

VII

The unicode character for the Roman numeral seven: Ⅶ.

VIII

The unicode character for the Roman numeral eight: Ⅷ.

IX

The unicode character for the Roman numeral nine: Ⅸ.

X

The unicode character for the Roman numeral ten: Ⅹ.

XI

The unicode character for the Roman numeral eleven: Ⅺ.

XII

The unicode character for the Roman numeral twelve: Ⅻ.

L

The unicode character for the Roman numeral fifty: Ⅼ.

C

The unicode character for the Roman numeral hundred: Ⅽ.

D

The unicode character for the Roman numeral five hundred: Ⅾ.

M

The unicode character for the Roman numeral thousand: Ⅿ.

Instances

Instances details
Arbitrary RomanLiteral Source # 
Instance details

Defined in Data.Char.Number.Roman

Data RomanLiteral Source # 
Instance details

Defined in Data.Char.Number.Roman

Methods

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

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

toConstr :: RomanLiteral -> Constr #

dataTypeOf :: RomanLiteral -> DataType #

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

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

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

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

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

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

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

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

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

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

Bounded RomanLiteral Source # 
Instance details

Defined in Data.Char.Number.Roman

Enum RomanLiteral Source # 
Instance details

Defined in Data.Char.Number.Roman

Generic RomanLiteral Source # 
Instance details

Defined in Data.Char.Number.Roman

Associated Types

type Rep RomanLiteral :: Type -> Type #

Read RomanLiteral Source # 
Instance details

Defined in Data.Char.Number.Roman

Show RomanLiteral Source # 
Instance details

Defined in Data.Char.Number.Roman

NFData RomanLiteral Source # 
Instance details

Defined in Data.Char.Number.Roman

Methods

rnf :: RomanLiteral -> () #

Eq RomanLiteral Source # 
Instance details

Defined in Data.Char.Number.Roman

Hashable RomanLiteral Source # 
Instance details

Defined in Data.Char.Number.Roman

UnicodeCharacter RomanLiteral Source # 
Instance details

Defined in Data.Char.Number.Roman

UnicodeText RomanLiteral Source # 
Instance details

Defined in Data.Char.Number.Roman

type Rep RomanLiteral Source # 
Instance details

Defined in Data.Char.Number.Roman

type Rep RomanLiteral = D1 ('MetaData "RomanLiteral" "Data.Char.Number.Roman" "unicode-tricks-0.12.1.0-xfS7pllWdNI2gUc6R0rNH" 'False) ((((C1 ('MetaCons "I" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "II" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "III" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "IV" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "V" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "VI" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "VII" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "VIII" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "IX" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "X" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "XI" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "XII" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "L" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "C" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "D" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "M" 'PrefixI 'False) (U1 :: Type -> Type)))))

data RomanStyle Source #

The style to convert a number to a Roman numeral. The UnicodeCharacter instance maps on the uppercase Roman literals.

Constructors

Additive

The additive style converts four to ⅠⅠⅠⅠ.

Subtractive

The subtractive style converts four to ⅠⅤ.

Instances

Instances details
Arbitrary RomanStyle Source # 
Instance details

Defined in Data.Char.Number.Roman

Data RomanStyle Source # 
Instance details

Defined in Data.Char.Number.Roman

Methods

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

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

toConstr :: RomanStyle -> Constr #

dataTypeOf :: RomanStyle -> DataType #

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

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

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

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

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

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

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

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

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

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

Bounded RomanStyle Source # 
Instance details

Defined in Data.Char.Number.Roman

Enum RomanStyle Source # 
Instance details

Defined in Data.Char.Number.Roman

Generic RomanStyle Source # 
Instance details

Defined in Data.Char.Number.Roman

Associated Types

type Rep RomanStyle :: Type -> Type #

Read RomanStyle Source # 
Instance details

Defined in Data.Char.Number.Roman

Show RomanStyle Source # 
Instance details

Defined in Data.Char.Number.Roman

Default RomanStyle Source # 
Instance details

Defined in Data.Char.Number.Roman

Methods

def :: RomanStyle #

NFData RomanStyle Source # 
Instance details

Defined in Data.Char.Number.Roman

Methods

rnf :: RomanStyle -> () #

Eq RomanStyle Source # 
Instance details

Defined in Data.Char.Number.Roman

Ord RomanStyle Source # 
Instance details

Defined in Data.Char.Number.Roman

Hashable RomanStyle Source # 
Instance details

Defined in Data.Char.Number.Roman

type Rep RomanStyle Source # 
Instance details

Defined in Data.Char.Number.Roman

type Rep RomanStyle = D1 ('MetaData "RomanStyle" "Data.Char.Number.Roman" "unicode-tricks-0.12.1.0-xfS7pllWdNI2gUc6R0rNH" 'False) (C1 ('MetaCons "Additive" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Subtractive" 'PrefixI 'False) (U1 :: Type -> Type))

Convert a number to Roman literals

toLiterals Source #

Arguments

:: Integral i 
=> RomanStyle

Specifies if the Numeral is Additive or Subtractive style.

-> Ligate

Specifies if characters like ⅠⅤ are joined to .

-> i

The given number to convert.

-> Maybe [RomanLiteral]

A list of RomanLiterals if the given number can be specified with Roman numerals, Nothing otherwise.

Convert the given number with the given RomanStyle and Ligate style to a sequence of RomanLiterals, given the number can be represented with Roman numerals (is strictly larger than zero).

romanLiteral Source #

Arguments

:: RomanLiteral

The given RomanLiteral to convert.

-> Char

A unicode character that represents the given RomanLiteral.

Convert the given RomanLiteral object to a unicode character in upper case.

romanLiteral' Source #

Arguments

:: RomanLiteral

The given RomanLiteral to convert.

-> Char

A unicode character that represents the given RomanLiteral.

Convert the given RomanLiteral object to a unicode character in lower case.

Convert a number to text

romanNumeral Source #

Arguments

:: [RomanLiteral]

The given list of RomanLiteral objects to convert to a Unicode equivalent.

-> Text

A Text object that contains a sequence of unicode characters that represents the RomanLiterals.

Convert a sequence of RomanLiteral objects to a Text object that contains a sequence of corresponding Unicode characters which are Roman numberals in upper case.

romanNumeral' Source #

Arguments

:: [RomanLiteral]

The given list of RomanLiteral objects to convert to a Unicode equivalent.

-> Text

A Text object that contains a sequence of unicode characters that represents the RomanLiterals.

Convert a sequence of RomanLiteral objects to a Text object that contains a sequence of corresponding Unicode characters which are Roman numberals in lower case.

romanNumeralCase Source #

Arguments

:: LetterCase

The given LetterCase to apply.

-> [RomanLiteral]

The given list of RomanLiteral objects to convert to a Unicode equivalent.

-> Text

A Text object that contains a sequence of unicode characters that represents the RomanLiterals.

Convert a sequence of RomanLiteral objects to a Text object that contains a sequence of corresponding Unicode characters which are Roman numberals in upper case or lower case depending on the LetterCase value.

romanNumber Source #

Arguments

:: Integral i 
=> RomanStyle

Specifies if the Numeral is Additive or Subtractive style.

-> Ligate

Specifies if characters like ⅠⅤ are joined to .

-> i

The given number to convert.

-> Maybe Text

A Text if the given number can be specified with Roman numerals wrapped in a Just, Nothing otherwise.

Convert a given number to a Text wrapped in a Just data constructor, given the number, given it can be represented. Nothing in case it can not be represented. The number is written in Roman numerals in upper case.

romanNumber' Source #

Arguments

:: Integral i 
=> RomanStyle

Specifies if the Numeral is Additive or Subtractive style.

-> Ligate

Specifies if characters like ⅠⅤ are joined to .

-> i

The given number to convert.

-> Maybe Text

A Text if the given number can be specified with Roman numerals wrapped in a Just, Nothing otherwise.

Convert a given number to a Text wrapped in a Just data constructor, given the number, given it can be represented. Nothing in case it can not be represented. The number is written in Roman numerals in lower case.

romanNumberCase :: Integral i => LetterCase -> RomanStyle -> Ligate -> i -> Maybe Text Source #

Convert a given number to a Text wrapped in a Just data constructor, given the number, given it can be represented. Nothing in case it can not be represented. The number is written in Roman numerals in upper case or lower case depending on the LetterCase value.