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

Data.Char.Currency

Description

Unicode has multiple code blocks where it defines currencies. This module aims to expose a data structure that makes it more convenient to work with currency characters.

Synopsis

Defining currencies

data Currency Source #

A datatype to present the currencies that have a unicode character.

Constructors

Dollar

A currency that is rendered as $.

Cent

A currency that is rendered as ¢.

Pound

A currency that is rendered as £.

Currency

A currency that is rendered as ¤.

Yen

A currency that is rendered as ¥.

ArmenianDram

A currency that is rendered as ֏.

Afghani

A currency that is rendered as ؋.

NkoDorome

A currency that is rendered as ߾.

NkoTaman

A currency that is rendered as ߿.

BengaliRupeeMark

A currency that is rendered as .

BengaliRupee

A currency that is rendered as .

BengaliGandaMark

A currency that is rendered as .

GujaratiRupee

A currency that is rendered as .

TamilRupee

A currency that is rendered as .

ThaiSymbolBaht

A currency that is rendered as ฿.

KhmerSymbolRiel

A currency that is rendered as .

EuroCurrency

A currency that is rendered as .

Colon

A currency that is rendered as .

Cruzeiro

A currency that is rendered as .

FrenchFranc

A currency that is rendered as .

Lira

A currency that is rendered as .

Mill

A currency that is rendered as .

Naira

A currency that is rendered as .

Peseta

A currency that is rendered as .

Rupee

A currency that is rendered as .

Won

A currency that is rendered as .

NewSheqel

A currency that is rendered as .

Dong

A currency that is rendered as .

Euro

A currency that is rendered as .

Kip

A currency that is rendered as .

Tugrik

A currency that is rendered as .

Drachma

A currency that is rendered as .

GermanPenny

A currency that is rendered as .

Peso

A currency that is rendered as .

Guarani

A currency that is rendered as .

Austral

A currency that is rendered as .

Hryvnia

A currency that is rendered as .

Cedi

A currency that is rendered as .

LivreTournois

A currency that is rendered as .

Spesmilo

A currency that is rendered as .

Tenge

A currency that is rendered as .

IndianRupee

A currency that is rendered as .

TurkishLira

A currency that is rendered as .

NordicMark

A currency that is rendered as .

Manat

A currency that is rendered as .

Ruble

A currency that is rendered as .

Lari

A currency that is rendered as .

Bitcoin

A currency that is rendered as .

NorthIndicRupeeMark

A currency that is rendered as .

Rial

A currency that is rendered as .

SmallDollar

A currency that is rendered as .

FullwidthDollar

A currency that is rendered as .

FullwidthCent

A currency that is rendered as .

FullwidthPound

A currency that is rendered as .

FullwidthYen

A currency that is rendered as .

FullwidthWon

A currency that is rendered as .

TamilKaacu

A currency that is rendered as 𑿝.

TamilPanam

A currency that is rendered as 𑿞.

TamilPon

A currency that is rendered as 𑿟.

TamilVaraakan

A currency that is rendered as 𑿠.

WanchoNgun

A currency that is rendered as 𞋿.

IndicSiyaqRupeeMark

A currency that is rendered as 𞲰.

Instances

Instances details
Arbitrary Currency Source # 
Instance details

Defined in Data.Char.Currency

Data Currency Source # 
Instance details

Defined in Data.Char.Currency

Methods

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

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

toConstr :: Currency -> Constr #

dataTypeOf :: Currency -> DataType #

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

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

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

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

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

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

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

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

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

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

Bounded Currency Source # 
Instance details

Defined in Data.Char.Currency

Enum Currency Source # 
Instance details

Defined in Data.Char.Currency

Generic Currency Source # 
Instance details

Defined in Data.Char.Currency

Associated Types

type Rep Currency :: Type -> Type #

Methods

from :: Currency -> Rep Currency x #

to :: Rep Currency x -> Currency #

Read Currency Source # 
Instance details

Defined in Data.Char.Currency

Show Currency Source # 
Instance details

Defined in Data.Char.Currency

NFData Currency Source # 
Instance details

Defined in Data.Char.Currency

Methods

rnf :: Currency -> () #

Eq Currency Source # 
Instance details

Defined in Data.Char.Currency

Ord Currency Source # 
Instance details

Defined in Data.Char.Currency

Hashable Currency Source # 
Instance details

Defined in Data.Char.Currency

Methods

hashWithSalt :: Int -> Currency -> Int #

hash :: Currency -> Int #

UnicodeCharacter Currency Source # 
Instance details

Defined in Data.Char.Currency

UnicodeText Currency Source # 
Instance details

Defined in Data.Char.Currency

type Rep Currency Source # 
Instance details

Defined in Data.Char.Currency

type Rep Currency = D1 ('MetaData "Currency" "Data.Char.Currency" "unicode-tricks-0.14.1.0-EInLeozqGjBL3vIQTNPsAm" 'False) (((((C1 ('MetaCons "Dollar" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Cent" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Pound" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Currency" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Yen" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ArmenianDram" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Afghani" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "NkoDorome" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NkoTaman" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "BengaliRupeeMark" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "BengaliRupee" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "BengaliGandaMark" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "GujaratiRupee" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "TamilRupee" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ThaiSymbolBaht" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: ((((C1 ('MetaCons "KhmerSymbolRiel" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "EuroCurrency" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Colon" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Cruzeiro" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "FrenchFranc" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Lira" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Mill" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Naira" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "Peseta" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Rupee" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Won" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NewSheqel" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Dong" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Euro" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Kip" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Tugrik" 'PrefixI 'False) (U1 :: Type -> Type)))))) :+: ((((C1 ('MetaCons "Drachma" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "GermanPenny" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Peso" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Guarani" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Austral" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Hryvnia" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Cedi" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "LivreTournois" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Spesmilo" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Tenge" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "IndianRupee" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "TurkishLira" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NordicMark" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Manat" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Ruble" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: ((((C1 ('MetaCons "Lari" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Bitcoin" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "NorthIndicRupeeMark" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Rial" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "SmallDollar" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FullwidthDollar" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "FullwidthCent" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FullwidthPound" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "FullwidthYen" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FullwidthWon" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "TamilKaacu" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TamilPanam" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "TamilPon" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TamilVaraakan" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "WanchoNgun" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "IndicSiyaqRupeeMark" 'PrefixI 'False) (U1 :: Type -> Type)))))))

Currencies as Char objects

dollar Source #

Arguments

:: Char

A character that corresponds with the dollar sign.

The character used to render a dollar sign presented as $.

cent Source #

Arguments

:: Char

A character that corresponds with the cent sign.

The character used to render a cent sign presented as ¢.

pound Source #

Arguments

:: Char

A character that corresponds with the pound sign.

The character used to render a pound sign presented as £.

currency Source #

Arguments

:: Char

A character that corresponds with the currency sign.

The character used to render a currency sign presented as ¤.

yen Source #

Arguments

:: Char

A character that corresponds with the yen sign.

The character used to render a yen sign presented as ¥.

armenianDram Source #

Arguments

:: Char

A character that corresponds with the armenian dram sign.

The character used to render a armenian dram sign presented as ֏.

afghani Source #

Arguments

:: Char

A character that corresponds with the afghani sign.

The character used to render a afghani sign presented as ؋.

nkoDorome Source #

Arguments

:: Char

A character that corresponds with the nko dorome sign.

The character used to render a nko dorome sign presented as ߾.

nkoTaman Source #

Arguments

:: Char

A character that corresponds with the nko taman sign.

The character used to render a nko taman sign presented as ߿.

bengaliRupeeMark Source #

Arguments

:: Char

A character that corresponds with the bengali rupee mark.

The character used to render a bengali rupee mark presented as .

bengaliRupee Source #

Arguments

:: Char

A character that corresponds with the bengali rupee sign.

The character used to render a bengali rupee sign presented as .

bengaliGandaMark Source #

Arguments

:: Char

A character that corresponds with the bengali ganda mark.

The character used to render a bengali ganda mark presented as .

gujaratiRupee Source #

Arguments

:: Char

A character that corresponds with the gujarati rupee sign.

The character used to render a gujarati rupee sign presented as .

tamilRupee Source #

Arguments

:: Char

A character that corresponds with the tamil rupee sign.

The character used to render a tamil rupee sign presented as .

thaiSymbolBaht Source #

Arguments

:: Char

A character that corresponds with the thai currency symbol baht.

The character used to render a thai currency symbol baht presented as ฿.

khmerSymbolRiel Source #

Arguments

:: Char

A character that corresponds with the khmer currency symbol riel.

The character used to render a khmer currency symbol riel presented as .

euroCurrency Source #

Arguments

:: Char

A character that corresponds with the euro-currency sign.

The character used to render a euro-currency sign presented as .

colon Source #

Arguments

:: Char

A character that corresponds with the colon sign.

The character used to render a colon sign presented as .

cruzeiro Source #

Arguments

:: Char

A character that corresponds with the cruzeiro sign.

The character used to render a cruzeiro sign presented as .

frenchFranc Source #

Arguments

:: Char

A character that corresponds with the french franc sign.

The character used to render a french franc sign presented as .

lira Source #

Arguments

:: Char

A character that corresponds with the lira sign.

The character used to render a lira sign presented as .

mill Source #

Arguments

:: Char

A character that corresponds with the mill sign.

The character used to render a mill sign presented as .

naira Source #

Arguments

:: Char

A character that corresponds with the naira sign.

The character used to render a naira sign presented as .

peseta Source #

Arguments

:: Char

A character that corresponds with the peseta sign.

The character used to render a peseta sign presented as .

rupee Source #

Arguments

:: Char

A character that corresponds with the rupee sign.

The character used to render a rupee sign presented as .

won Source #

Arguments

:: Char

A character that corresponds with the won sign.

The character used to render a won sign presented as .

newSheqel Source #

Arguments

:: Char

A character that corresponds with the new sheqel sign.

The character used to render a new sheqel sign presented as .

dong Source #

Arguments

:: Char

A character that corresponds with the dong sign.

The character used to render a dong sign presented as .

euro Source #

Arguments

:: Char

A character that corresponds with the euro sign.

The character used to render a euro sign presented as .

kip Source #

Arguments

:: Char

A character that corresponds with the kip sign.

The character used to render a kip sign presented as .

tugrik Source #

Arguments

:: Char

A character that corresponds with the tugrik sign.

The character used to render a tugrik sign presented as .

drachma Source #

Arguments

:: Char

A character that corresponds with the drachma sign.

The character used to render a drachma sign presented as .

germanPenny Source #

Arguments

:: Char

A character that corresponds with the german penny sign.

The character used to render a german penny sign presented as .

peso Source #

Arguments

:: Char

A character that corresponds with the peso sign.

The character used to render a peso sign presented as .

guarani Source #

Arguments

:: Char

A character that corresponds with the guarani sign.

The character used to render a guarani sign presented as .

austral Source #

Arguments

:: Char

A character that corresponds with the austral sign.

The character used to render a austral sign presented as .

hryvnia Source #

Arguments

:: Char

A character that corresponds with the hryvnia sign.

The character used to render a hryvnia sign presented as .

cedi Source #

Arguments

:: Char

A character that corresponds with the cedi sign.

The character used to render a cedi sign presented as .

livreTournois Source #

Arguments

:: Char

A character that corresponds with the livre tournois sign.

The character used to render a livre tournois sign presented as .

spesmilo Source #

Arguments

:: Char

A character that corresponds with the spesmilo sign.

The character used to render a spesmilo sign presented as .

tenge Source #

Arguments

:: Char

A character that corresponds with the tenge sign.

The character used to render a tenge sign presented as .

indianRupee Source #

Arguments

:: Char

A character that corresponds with the indian rupee sign.

The character used to render a indian rupee sign presented as .

turkishLira Source #

Arguments

:: Char

A character that corresponds with the turkish lira sign.

The character used to render a turkish lira sign presented as .

nordicMark Source #

Arguments

:: Char

A character that corresponds with the nordic mark sign.

The character used to render a nordic mark sign presented as .

manat Source #

Arguments

:: Char

A character that corresponds with the manat sign.

The character used to render a manat sign presented as .

ruble Source #

Arguments

:: Char

A character that corresponds with the ruble sign.

The character used to render a ruble sign presented as .

lari Source #

Arguments

:: Char

A character that corresponds with the lari sign.

The character used to render a lari sign presented as .

bitcoin Source #

Arguments

:: Char

A character that corresponds with the bitcoin sign.

The character used to render a bitcoin sign presented as .

northIndicRupeeMark Source #

Arguments

:: Char

A character that corresponds with the north indic rupee mark.

The character used to render a north indic rupee mark presented as .

rial Source #

Arguments

:: Char

A character that corresponds with the rial sign.

The character used to render a rial sign presented as .

smallDollar Source #

Arguments

:: Char

A character that corresponds with the small dollar sign.

The character used to render a small dollar sign presented as .

fullwidthDollar Source #

Arguments

:: Char

A character that corresponds with the fullwidth dollar sign.

The character used to render a fullwidth dollar sign presented as .

fullwidthCent Source #

Arguments

:: Char

A character that corresponds with the fullwidth cent sign.

The character used to render a fullwidth cent sign presented as .

fullwidthPound Source #

Arguments

:: Char

A character that corresponds with the fullwidth pound sign.

The character used to render a fullwidth pound sign presented as .

fullwidthYen Source #

Arguments

:: Char

A character that corresponds with the fullwidth yen sign.

The character used to render a fullwidth yen sign presented as .

fullwidthWon Source #

Arguments

:: Char

A character that corresponds with the fullwidth won sign.

The character used to render a fullwidth won sign presented as .

tamilKaacu Source #

Arguments

:: Char

A character that corresponds with the tamil sign kaacu.

The character used to render a tamil sign kaacu presented as 𑿝.

tamilPanam Source #

Arguments

:: Char

A character that corresponds with the tamil sign panam.

The character used to render a tamil sign panam presented as 𑿞.

tamilPon Source #

Arguments

:: Char

A character that corresponds with the tamil sign pon.

The character used to render a tamil sign pon presented as 𑿟.

tamilVaraakan Source #

Arguments

:: Char

A character that corresponds with the tamil sign varaakan.

The character used to render a tamil sign varaakan presented as 𑿠.

wanchoNgun Source #

Arguments

:: Char

A character that corresponds with the wancho ngun sign.

The character used to render a wancho ngun sign presented as 𞋿.

indicSiyaqRupeeMark Source #

Arguments

:: Char

A character that corresponds with the indic siyaq rupee mark.

The character used to render a indic siyaq rupee mark presented as 𞲰.

Check if a character is a currency

isCurrency Source #

Arguments

:: Char

The given character to test.

-> Bool

True if the given character is a currency character; False otherwise.

Check if the given Character is a currency character.