{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE Safe #-}
{-# LANGUAGE TypeApplications #-}

-- |
-- Module      : Data.Char.Currency
-- Description : The module exposes a type that defines the different currencies for which there is a Unicode equivalent.
-- Maintainer  : hapytexeu+gh@gmail.com
-- Stability   : experimental
-- Portability : POSIX
--
-- 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.
module Data.Char.Currency
  ( -- * Defining currencies
    Currency
      ( Dollar,
        Cent,
        Pound,
        Currency,
        Yen,
        ArmenianDram,
        Afghani,
        NkoDorome,
        NkoTaman,
        BengaliRupeeMark,
        BengaliRupee,
        BengaliGandaMark,
        GujaratiRupee,
        TamilRupee,
        ThaiSymbolBaht,
        KhmerSymbolRiel,
        EuroCurrency,
        Colon,
        Cruzeiro,
        FrenchFranc,
        Lira,
        Mill,
        Naira,
        Peseta,
        Rupee,
        Won,
        NewSheqel,
        Dong,
        Euro,
        Kip,
        Tugrik,
        Drachma,
        GermanPenny,
        Peso,
        Guarani,
        Austral,
        Hryvnia,
        Cedi,
        LivreTournois,
        Spesmilo,
        Tenge,
        IndianRupee,
        TurkishLira,
        NordicMark,
        Manat,
        Ruble,
        Lari,
        Bitcoin,
        NorthIndicRupeeMark,
        Rial,
        SmallDollar,
        FullwidthDollar,
        FullwidthCent,
        FullwidthPound,
        FullwidthYen,
        FullwidthWon,
        TamilKaacu,
        TamilPanam,
        TamilPon,
        TamilVaraakan,
        WanchoNgun,
        IndicSiyaqRupeeMark
      ),

    -- * Currencies as 'Char' objects
    dollar,
    cent,
    pound,
    currency,
    yen,
    armenianDram,
    afghani,
    nkoDorome,
    nkoTaman,
    bengaliRupeeMark,
    bengaliRupee,
    bengaliGandaMark,
    gujaratiRupee,
    tamilRupee,
    thaiSymbolBaht,
    khmerSymbolRiel,
    euroCurrency,
    colon,
    cruzeiro,
    frenchFranc,
    lira,
    mill,
    naira,
    peseta,
    rupee,
    won,
    newSheqel,
    dong,
    euro,
    kip,
    tugrik,
    drachma,
    germanPenny,
    peso,
    guarani,
    austral,
    hryvnia,
    cedi,
    livreTournois,
    spesmilo,
    tenge,
    indianRupee,
    turkishLira,
    nordicMark,
    manat,
    ruble,
    lari,
    bitcoin,
    northIndicRupeeMark,
    rial,
    smallDollar,
    fullwidthDollar,
    fullwidthCent,
    fullwidthPound,
    fullwidthYen,
    fullwidthWon,
    tamilKaacu,
    tamilPanam,
    tamilPon,
    tamilVaraakan,
    wanchoNgun,
    indicSiyaqRupeeMark,

    -- * Check if a character is a currency
    isCurrency,
  )
where

import Control.DeepSeq (NFData)
import Data.Char.Core (UnicodeCharacter (fromUnicodeChar, isInCharRange, toUnicodeChar), UnicodeText (isInTextRange), generateIsInTextRange')
import Data.Data (Data)
import Data.Hashable (Hashable)
import GHC.Generics (Generic)
import Test.QuickCheck.Arbitrary (Arbitrary (arbitrary), arbitraryBoundedEnum)

-- | A datatype to present the currencies that have a unicode character.
data Currency
  = -- | A currency that is rendered as @$@.
    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
  deriving (Currency
forall a. a -> a -> Bounded a
maxBound :: Currency
$cmaxBound :: Currency
minBound :: Currency
$cminBound :: Currency
Bounded, Typeable Currency
Currency -> DataType
Currency -> Constr
(forall b. Data b => b -> b) -> Currency -> Currency
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Currency -> u
forall u. (forall d. Data d => d -> u) -> Currency -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Currency -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Currency -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Currency -> m Currency
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Currency -> m Currency
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Currency
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Currency -> c Currency
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Currency)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Currency)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Currency -> m Currency
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Currency -> m Currency
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Currency -> m Currency
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Currency -> m Currency
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Currency -> m Currency
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Currency -> m Currency
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Currency -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Currency -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Currency -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Currency -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Currency -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Currency -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Currency -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Currency -> r
gmapT :: (forall b. Data b => b -> b) -> Currency -> Currency
$cgmapT :: (forall b. Data b => b -> b) -> Currency -> Currency
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Currency)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Currency)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Currency)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Currency)
dataTypeOf :: Currency -> DataType
$cdataTypeOf :: Currency -> DataType
toConstr :: Currency -> Constr
$ctoConstr :: Currency -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Currency
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Currency
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Currency -> c Currency
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Currency -> c Currency
Data, Int -> Currency
Currency -> Int
Currency -> [Currency]
Currency -> Currency
Currency -> Currency -> [Currency]
Currency -> Currency -> Currency -> [Currency]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: Currency -> Currency -> Currency -> [Currency]
$cenumFromThenTo :: Currency -> Currency -> Currency -> [Currency]
enumFromTo :: Currency -> Currency -> [Currency]
$cenumFromTo :: Currency -> Currency -> [Currency]
enumFromThen :: Currency -> Currency -> [Currency]
$cenumFromThen :: Currency -> Currency -> [Currency]
enumFrom :: Currency -> [Currency]
$cenumFrom :: Currency -> [Currency]
fromEnum :: Currency -> Int
$cfromEnum :: Currency -> Int
toEnum :: Int -> Currency
$ctoEnum :: Int -> Currency
pred :: Currency -> Currency
$cpred :: Currency -> Currency
succ :: Currency -> Currency
$csucc :: Currency -> Currency
Enum, Currency -> Currency -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Currency -> Currency -> Bool
$c/= :: Currency -> Currency -> Bool
== :: Currency -> Currency -> Bool
$c== :: Currency -> Currency -> Bool
Eq, forall x. Rep Currency x -> Currency
forall x. Currency -> Rep Currency x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Currency x -> Currency
$cfrom :: forall x. Currency -> Rep Currency x
Generic, Eq Currency
Currency -> Currency -> Bool
Currency -> Currency -> Ordering
Currency -> Currency -> Currency
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Currency -> Currency -> Currency
$cmin :: Currency -> Currency -> Currency
max :: Currency -> Currency -> Currency
$cmax :: Currency -> Currency -> Currency
>= :: Currency -> Currency -> Bool
$c>= :: Currency -> Currency -> Bool
> :: Currency -> Currency -> Bool
$c> :: Currency -> Currency -> Bool
<= :: Currency -> Currency -> Bool
$c<= :: Currency -> Currency -> Bool
< :: Currency -> Currency -> Bool
$c< :: Currency -> Currency -> Bool
compare :: Currency -> Currency -> Ordering
$ccompare :: Currency -> Currency -> Ordering
Ord, ReadPrec [Currency]
ReadPrec Currency
Int -> ReadS Currency
ReadS [Currency]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Currency]
$creadListPrec :: ReadPrec [Currency]
readPrec :: ReadPrec Currency
$creadPrec :: ReadPrec Currency
readList :: ReadS [Currency]
$creadList :: ReadS [Currency]
readsPrec :: Int -> ReadS Currency
$creadsPrec :: Int -> ReadS Currency
Read, Int -> Currency -> ShowS
[Currency] -> ShowS
Currency -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Currency] -> ShowS
$cshowList :: [Currency] -> ShowS
show :: Currency -> String
$cshow :: Currency -> String
showsPrec :: Int -> Currency -> ShowS
$cshowsPrec :: Int -> Currency -> ShowS
Show)

instance Arbitrary Currency where
  arbitrary :: Gen Currency
arbitrary = forall a. (Bounded a, Enum a) => Gen a
arbitraryBoundedEnum

instance Hashable Currency

instance NFData Currency

instance UnicodeCharacter Currency where
  toUnicodeChar :: Currency -> Char
toUnicodeChar Currency
Dollar = Char
dollar
  toUnicodeChar Currency
Cent = Char
cent
  toUnicodeChar Currency
Pound = Char
pound
  toUnicodeChar Currency
Currency = Char
currency
  toUnicodeChar Currency
Yen = Char
yen
  toUnicodeChar Currency
ArmenianDram = Char
armenianDram
  toUnicodeChar Currency
Afghani = Char
afghani
  toUnicodeChar Currency
NkoDorome = Char
nkoDorome
  toUnicodeChar Currency
NkoTaman = Char
nkoTaman
  toUnicodeChar Currency
BengaliRupeeMark = Char
bengaliRupeeMark
  toUnicodeChar Currency
BengaliRupee = Char
bengaliRupee
  toUnicodeChar Currency
BengaliGandaMark = Char
bengaliGandaMark
  toUnicodeChar Currency
GujaratiRupee = Char
gujaratiRupee
  toUnicodeChar Currency
TamilRupee = Char
tamilRupee
  toUnicodeChar Currency
ThaiSymbolBaht = Char
thaiSymbolBaht
  toUnicodeChar Currency
KhmerSymbolRiel = Char
khmerSymbolRiel
  toUnicodeChar Currency
EuroCurrency = Char
euroCurrency
  toUnicodeChar Currency
Colon = Char
colon
  toUnicodeChar Currency
Cruzeiro = Char
cruzeiro
  toUnicodeChar Currency
FrenchFranc = Char
frenchFranc
  toUnicodeChar Currency
Lira = Char
lira
  toUnicodeChar Currency
Mill = Char
mill
  toUnicodeChar Currency
Naira = Char
naira
  toUnicodeChar Currency
Peseta = Char
peseta
  toUnicodeChar Currency
Rupee = Char
rupee
  toUnicodeChar Currency
Won = Char
won
  toUnicodeChar Currency
NewSheqel = Char
newSheqel
  toUnicodeChar Currency
Dong = Char
dong
  toUnicodeChar Currency
Euro = Char
euro
  toUnicodeChar Currency
Kip = Char
kip
  toUnicodeChar Currency
Tugrik = Char
tugrik
  toUnicodeChar Currency
Drachma = Char
drachma
  toUnicodeChar Currency
GermanPenny = Char
germanPenny
  toUnicodeChar Currency
Peso = Char
peso
  toUnicodeChar Currency
Guarani = Char
guarani
  toUnicodeChar Currency
Austral = Char
austral
  toUnicodeChar Currency
Hryvnia = Char
hryvnia
  toUnicodeChar Currency
Cedi = Char
cedi
  toUnicodeChar Currency
LivreTournois = Char
livreTournois
  toUnicodeChar Currency
Spesmilo = Char
spesmilo
  toUnicodeChar Currency
Tenge = Char
tenge
  toUnicodeChar Currency
IndianRupee = Char
indianRupee
  toUnicodeChar Currency
TurkishLira = Char
turkishLira
  toUnicodeChar Currency
NordicMark = Char
nordicMark
  toUnicodeChar Currency
Manat = Char
manat
  toUnicodeChar Currency
Ruble = Char
ruble
  toUnicodeChar Currency
Lari = Char
lari
  toUnicodeChar Currency
Bitcoin = Char
bitcoin
  toUnicodeChar Currency
NorthIndicRupeeMark = Char
northIndicRupeeMark
  toUnicodeChar Currency
Rial = Char
rial
  toUnicodeChar Currency
SmallDollar = Char
smallDollar
  toUnicodeChar Currency
FullwidthDollar = Char
fullwidthDollar
  toUnicodeChar Currency
FullwidthCent = Char
fullwidthCent
  toUnicodeChar Currency
FullwidthPound = Char
fullwidthPound
  toUnicodeChar Currency
FullwidthYen = Char
fullwidthYen
  toUnicodeChar Currency
FullwidthWon = Char
fullwidthWon
  toUnicodeChar Currency
TamilKaacu = Char
tamilKaacu
  toUnicodeChar Currency
TamilPanam = Char
tamilPanam
  toUnicodeChar Currency
TamilPon = Char
tamilPon
  toUnicodeChar Currency
TamilVaraakan = Char
tamilVaraakan
  toUnicodeChar Currency
WanchoNgun = Char
wanchoNgun
  toUnicodeChar Currency
IndicSiyaqRupeeMark = Char
indicSiyaqRupeeMark
  fromUnicodeChar :: Char -> Maybe Currency
fromUnicodeChar Char
'\x24' = forall a. a -> Maybe a
Just Currency
Dollar
  fromUnicodeChar Char
'\xa2' = forall a. a -> Maybe a
Just Currency
Cent
  fromUnicodeChar Char
'\xa3' = forall a. a -> Maybe a
Just Currency
Pound
  fromUnicodeChar Char
'\xa4' = forall a. a -> Maybe a
Just Currency
Currency
  fromUnicodeChar Char
'\xa5' = forall a. a -> Maybe a
Just Currency
Yen
  fromUnicodeChar Char
'\x58f' = forall a. a -> Maybe a
Just Currency
ArmenianDram
  fromUnicodeChar Char
'\x60b' = forall a. a -> Maybe a
Just Currency
Afghani
  fromUnicodeChar Char
'\x7fe' = forall a. a -> Maybe a
Just Currency
NkoDorome
  fromUnicodeChar Char
'\x7ff' = forall a. a -> Maybe a
Just Currency
NkoTaman
  fromUnicodeChar Char
'\x9f2' = forall a. a -> Maybe a
Just Currency
BengaliRupeeMark
  fromUnicodeChar Char
'\x9f3' = forall a. a -> Maybe a
Just Currency
BengaliRupee
  fromUnicodeChar Char
'\x9fb' = forall a. a -> Maybe a
Just Currency
BengaliGandaMark
  fromUnicodeChar Char
'\xaf1' = forall a. a -> Maybe a
Just Currency
GujaratiRupee
  fromUnicodeChar Char
'\xbf9' = forall a. a -> Maybe a
Just Currency
TamilRupee
  fromUnicodeChar Char
'\xe3f' = forall a. a -> Maybe a
Just Currency
ThaiSymbolBaht
  fromUnicodeChar Char
'\x17db' = forall a. a -> Maybe a
Just Currency
KhmerSymbolRiel
  fromUnicodeChar Char
'\x20a0' = forall a. a -> Maybe a
Just Currency
EuroCurrency
  fromUnicodeChar Char
'\x20a1' = forall a. a -> Maybe a
Just Currency
Colon
  fromUnicodeChar Char
'\x20a2' = forall a. a -> Maybe a
Just Currency
Cruzeiro
  fromUnicodeChar Char
'\x20a3' = forall a. a -> Maybe a
Just Currency
FrenchFranc
  fromUnicodeChar Char
'\x20a4' = forall a. a -> Maybe a
Just Currency
Lira
  fromUnicodeChar Char
'\x20a5' = forall a. a -> Maybe a
Just Currency
Mill
  fromUnicodeChar Char
'\x20a6' = forall a. a -> Maybe a
Just Currency
Naira
  fromUnicodeChar Char
'\x20a7' = forall a. a -> Maybe a
Just Currency
Peseta
  fromUnicodeChar Char
'\x20a8' = forall a. a -> Maybe a
Just Currency
Rupee
  fromUnicodeChar Char
'\x20a9' = forall a. a -> Maybe a
Just Currency
Won
  fromUnicodeChar Char
'\x20aa' = forall a. a -> Maybe a
Just Currency
NewSheqel
  fromUnicodeChar Char
'\x20ab' = forall a. a -> Maybe a
Just Currency
Dong
  fromUnicodeChar Char
'\x20ac' = forall a. a -> Maybe a
Just Currency
Euro
  fromUnicodeChar Char
'\x20ad' = forall a. a -> Maybe a
Just Currency
Kip
  fromUnicodeChar Char
'\x20ae' = forall a. a -> Maybe a
Just Currency
Tugrik
  fromUnicodeChar Char
'\x20af' = forall a. a -> Maybe a
Just Currency
Drachma
  fromUnicodeChar Char
'\x20b0' = forall a. a -> Maybe a
Just Currency
GermanPenny
  fromUnicodeChar Char
'\x20b1' = forall a. a -> Maybe a
Just Currency
Peso
  fromUnicodeChar Char
'\x20b2' = forall a. a -> Maybe a
Just Currency
Guarani
  fromUnicodeChar Char
'\x20b3' = forall a. a -> Maybe a
Just Currency
Austral
  fromUnicodeChar Char
'\x20b4' = forall a. a -> Maybe a
Just Currency
Hryvnia
  fromUnicodeChar Char
'\x20b5' = forall a. a -> Maybe a
Just Currency
Cedi
  fromUnicodeChar Char
'\x20b6' = forall a. a -> Maybe a
Just Currency
LivreTournois
  fromUnicodeChar Char
'\x20b7' = forall a. a -> Maybe a
Just Currency
Spesmilo
  fromUnicodeChar Char
'\x20b8' = forall a. a -> Maybe a
Just Currency
Tenge
  fromUnicodeChar Char
'\x20b9' = forall a. a -> Maybe a
Just Currency
IndianRupee
  fromUnicodeChar Char
'\x20ba' = forall a. a -> Maybe a
Just Currency
TurkishLira
  fromUnicodeChar Char
'\x20bb' = forall a. a -> Maybe a
Just Currency
NordicMark
  fromUnicodeChar Char
'\x20bc' = forall a. a -> Maybe a
Just Currency
Manat
  fromUnicodeChar Char
'\x20bd' = forall a. a -> Maybe a
Just Currency
Ruble
  fromUnicodeChar Char
'\x20be' = forall a. a -> Maybe a
Just Currency
Lari
  fromUnicodeChar Char
'\x20bf' = forall a. a -> Maybe a
Just Currency
Bitcoin
  fromUnicodeChar Char
'\xa838' = forall a. a -> Maybe a
Just Currency
NorthIndicRupeeMark
  fromUnicodeChar Char
'\xfdfc' = forall a. a -> Maybe a
Just Currency
Rial
  fromUnicodeChar Char
'\xfe69' = forall a. a -> Maybe a
Just Currency
SmallDollar
  fromUnicodeChar Char
'\xff04' = forall a. a -> Maybe a
Just Currency
FullwidthDollar
  fromUnicodeChar Char
'\xffe0' = forall a. a -> Maybe a
Just Currency
FullwidthCent
  fromUnicodeChar Char
'\xffe1' = forall a. a -> Maybe a
Just Currency
FullwidthPound
  fromUnicodeChar Char
'\xffe5' = forall a. a -> Maybe a
Just Currency
FullwidthYen
  fromUnicodeChar Char
'\xffe6' = forall a. a -> Maybe a
Just Currency
FullwidthWon
  fromUnicodeChar Char
'\x11fdd' = forall a. a -> Maybe a
Just Currency
TamilKaacu
  fromUnicodeChar Char
'\x11fde' = forall a. a -> Maybe a
Just Currency
TamilPanam
  fromUnicodeChar Char
'\x11fdf' = forall a. a -> Maybe a
Just Currency
TamilPon
  fromUnicodeChar Char
'\x11fe0' = forall a. a -> Maybe a
Just Currency
TamilVaraakan
  fromUnicodeChar Char
'\x1e2ff' = forall a. a -> Maybe a
Just Currency
WanchoNgun
  fromUnicodeChar Char
'\x1ecb0' = forall a. a -> Maybe a
Just Currency
IndicSiyaqRupeeMark
  fromUnicodeChar Char
_ = forall a. Maybe a
Nothing
  isInCharRange :: Char -> Bool
isInCharRange = Char -> Bool
isCurrency

instance UnicodeText Currency where
  isInTextRange :: Text -> Bool
isInTextRange = forall a. UnicodeCharacter a => Text -> Bool
generateIsInTextRange' @Currency

-- | Check if the given 'Char'acter is a currency character.
isCurrency ::
  -- | The given character to test.
  Char ->
  -- | 'True' if the given character is a currency character; 'False' otherwise.
  Bool
isCurrency :: Char -> Bool
isCurrency Char
x
  | Char
'\x20a0' forall a. Ord a => a -> a -> Bool
<= Char
x Bool -> Bool -> Bool
&& Char
x forall a. Ord a => a -> a -> Bool
<= Char
'\x20bf' = Bool
True
  | Char
'\xa2' forall a. Ord a => a -> a -> Bool
<= Char
x Bool -> Bool -> Bool
&& Char
x forall a. Ord a => a -> a -> Bool
<= Char
'\xa5' = Bool
True
  | Char
'\x11fdd' forall a. Ord a => a -> a -> Bool
<= Char
x Bool -> Bool -> Bool
&& Char
x forall a. Ord a => a -> a -> Bool
<= Char
'\x11fe0' = Bool
True
  | Char
'\x7fe' forall a. Ord a => a -> a -> Bool
<= Char
x Bool -> Bool -> Bool
&& Char
x forall a. Ord a => a -> a -> Bool
<= Char
'\x7ff' = Bool
True
  | Char
'\x9f2' forall a. Ord a => a -> a -> Bool
<= Char
x Bool -> Bool -> Bool
&& Char
x forall a. Ord a => a -> a -> Bool
<= Char
'\x9f3' = Bool
True
  | Char
'\xffe0' forall a. Ord a => a -> a -> Bool
<= Char
x Bool -> Bool -> Bool
&& Char
x forall a. Ord a => a -> a -> Bool
<= Char
'\xffe1' = Bool
True
  | Char
'\xffe5' forall a. Ord a => a -> a -> Bool
<= Char
x Bool -> Bool -> Bool
&& Char
x forall a. Ord a => a -> a -> Bool
<= Char
'\xffe6' = Bool
True
isCurrency Char
'\x24' = Bool
True
isCurrency Char
'\x58f' = Bool
True
isCurrency Char
'\x60b' = Bool
True
isCurrency Char
'\x9fb' = Bool
True
isCurrency Char
'\xaf1' = Bool
True
isCurrency Char
'\xbf9' = Bool
True
isCurrency Char
'\xe3f' = Bool
True
isCurrency Char
'\x17db' = Bool
True
isCurrency Char
'\xa838' = Bool
True
isCurrency Char
'\xfdfc' = Bool
True
isCurrency Char
'\xfe69' = Bool
True
isCurrency Char
'\xff04' = Bool
True
isCurrency Char
'\x1e2ff' = Bool
True
isCurrency Char
_ = Bool
False

-- | The character used to render a /dollar sign/ presented as @$@.
dollar ::
  -- | A character that corresponds with the /dollar sign/.
  Char
dollar :: Char
dollar = Char
'\x24'

-- | The character used to render a /cent sign/ presented as @¢@.
cent ::
  -- | A character that corresponds with the /cent sign/.
  Char
cent :: Char
cent = Char
'\xa2'

-- | The character used to render a /pound sign/ presented as @£@.
pound ::
  -- | A character that corresponds with the /pound sign/.
  Char
pound :: Char
pound = Char
'\xa3'

-- | The character used to render a /currency sign/ presented as @¤@.
currency ::
  -- | A character that corresponds with the /currency sign/.
  Char
currency :: Char
currency = Char
'\xa4'

-- | The character used to render a /yen sign/ presented as @¥@.
yen ::
  -- | A character that corresponds with the /yen sign/.
  Char
yen :: Char
yen = Char
'\xa5'

-- | The character used to render a /armenian dram sign/ presented as @֏@.
armenianDram ::
  -- | A character that corresponds with the /armenian dram sign/.
  Char
armenianDram :: Char
armenianDram = Char
'\x58f'

-- | The character used to render a /afghani sign/ presented as @؋@.
afghani ::
  -- | A character that corresponds with the /afghani sign/.
  Char
afghani :: Char
afghani = Char
'\x60b'

-- | The character used to render a /nko dorome sign/ presented as @߾@.
nkoDorome ::
  -- | A character that corresponds with the /nko dorome sign/.
  Char
nkoDorome :: Char
nkoDorome = Char
'\x7fe'

-- | The character used to render a /nko taman sign/ presented as @߿@.
nkoTaman ::
  -- | A character that corresponds with the /nko taman sign/.
  Char
nkoTaman :: Char
nkoTaman = Char
'\x7ff'

-- | The character used to render a /bengali rupee mark/ presented as @৲@.
bengaliRupeeMark ::
  -- | A character that corresponds with the /bengali rupee mark/.
  Char
bengaliRupeeMark :: Char
bengaliRupeeMark = Char
'\x9f2'

-- | The character used to render a /bengali rupee sign/ presented as @৳@.
bengaliRupee ::
  -- | A character that corresponds with the /bengali rupee sign/.
  Char
bengaliRupee :: Char
bengaliRupee = Char
'\x9f3'

-- | The character used to render a /bengali ganda mark/ presented as @৻@.
bengaliGandaMark ::
  -- | A character that corresponds with the /bengali ganda mark/.
  Char
bengaliGandaMark :: Char
bengaliGandaMark = Char
'\x9fb'

-- | The character used to render a /gujarati rupee sign/ presented as @૱@.
gujaratiRupee ::
  -- | A character that corresponds with the /gujarati rupee sign/.
  Char
gujaratiRupee :: Char
gujaratiRupee = Char
'\xaf1'

-- | The character used to render a /tamil rupee sign/ presented as @௹@.
tamilRupee ::
  -- | A character that corresponds with the /tamil rupee sign/.
  Char
tamilRupee :: Char
tamilRupee = Char
'\xbf9'

-- | The character used to render a /thai currency symbol baht/ presented as @฿@.
thaiSymbolBaht ::
  -- | A character that corresponds with the /thai currency symbol baht/.
  Char
thaiSymbolBaht :: Char
thaiSymbolBaht = Char
'\xe3f'

-- | The character used to render a /khmer currency symbol riel/ presented as @៛@.
khmerSymbolRiel ::
  -- | A character that corresponds with the /khmer currency symbol riel/.
  Char
khmerSymbolRiel :: Char
khmerSymbolRiel = Char
'\x17db'

-- | The character used to render a /euro-currency sign/ presented as @₠@.
euroCurrency ::
  -- | A character that corresponds with the /euro-currency sign/.
  Char
euroCurrency :: Char
euroCurrency = Char
'\x20a0'

-- | The character used to render a /colon sign/ presented as @₡@.
colon ::
  -- | A character that corresponds with the /colon sign/.
  Char
colon :: Char
colon = Char
'\x20a1'

-- | The character used to render a /cruzeiro sign/ presented as @₢@.
cruzeiro ::
  -- | A character that corresponds with the /cruzeiro sign/.
  Char
cruzeiro :: Char
cruzeiro = Char
'\x20a2'

-- | The character used to render a /french franc sign/ presented as @₣@.
frenchFranc ::
  -- | A character that corresponds with the /french franc sign/.
  Char
frenchFranc :: Char
frenchFranc = Char
'\x20a3'

-- | The character used to render a /lira sign/ presented as @₤@.
lira ::
  -- | A character that corresponds with the /lira sign/.
  Char
lira :: Char
lira = Char
'\x20a4'

-- | The character used to render a /mill sign/ presented as @₥@.
mill ::
  -- | A character that corresponds with the /mill sign/.
  Char
mill :: Char
mill = Char
'\x20a5'

-- | The character used to render a /naira sign/ presented as @₦@.
naira ::
  -- | A character that corresponds with the /naira sign/.
  Char
naira :: Char
naira = Char
'\x20a6'

-- | The character used to render a /peseta sign/ presented as @₧@.
peseta ::
  -- | A character that corresponds with the /peseta sign/.
  Char
peseta :: Char
peseta = Char
'\x20a7'

-- | The character used to render a /rupee sign/ presented as @₨@.
rupee ::
  -- | A character that corresponds with the /rupee sign/.
  Char
rupee :: Char
rupee = Char
'\x20a8'

-- | The character used to render a /won sign/ presented as @₩@.
won ::
  -- | A character that corresponds with the /won sign/.
  Char
won :: Char
won = Char
'\x20a9'

-- | The character used to render a /new sheqel sign/ presented as @₪@.
newSheqel ::
  -- | A character that corresponds with the /new sheqel sign/.
  Char
newSheqel :: Char
newSheqel = Char
'\x20aa'

-- | The character used to render a /dong sign/ presented as @₫@.
dong ::
  -- | A character that corresponds with the /dong sign/.
  Char
dong :: Char
dong = Char
'\x20ab'

-- | The character used to render a /euro sign/ presented as @€@.
euro ::
  -- | A character that corresponds with the /euro sign/.
  Char
euro :: Char
euro = Char
'\x20ac'

-- | The character used to render a /kip sign/ presented as @₭@.
kip ::
  -- | A character that corresponds with the /kip sign/.
  Char
kip :: Char
kip = Char
'\x20ad'

-- | The character used to render a /tugrik sign/ presented as @₮@.
tugrik ::
  -- | A character that corresponds with the /tugrik sign/.
  Char
tugrik :: Char
tugrik = Char
'\x20ae'

-- | The character used to render a /drachma sign/ presented as @₯@.
drachma ::
  -- | A character that corresponds with the /drachma sign/.
  Char
drachma :: Char
drachma = Char
'\x20af'

-- | The character used to render a /german penny sign/ presented as @₰@.
germanPenny ::
  -- | A character that corresponds with the /german penny sign/.
  Char
germanPenny :: Char
germanPenny = Char
'\x20b0'

-- | The character used to render a /peso sign/ presented as @₱@.
peso ::
  -- | A character that corresponds with the /peso sign/.
  Char
peso :: Char
peso = Char
'\x20b1'

-- | The character used to render a /guarani sign/ presented as @₲@.
guarani ::
  -- | A character that corresponds with the /guarani sign/.
  Char
guarani :: Char
guarani = Char
'\x20b2'

-- | The character used to render a /austral sign/ presented as @₳@.
austral ::
  -- | A character that corresponds with the /austral sign/.
  Char
austral :: Char
austral = Char
'\x20b3'

-- | The character used to render a /hryvnia sign/ presented as @₴@.
hryvnia ::
  -- | A character that corresponds with the /hryvnia sign/.
  Char
hryvnia :: Char
hryvnia = Char
'\x20b4'

-- | The character used to render a /cedi sign/ presented as @₵@.
cedi ::
  -- | A character that corresponds with the /cedi sign/.
  Char
cedi :: Char
cedi = Char
'\x20b5'

-- | The character used to render a /livre tournois sign/ presented as @₶@.
livreTournois ::
  -- | A character that corresponds with the /livre tournois sign/.
  Char
livreTournois :: Char
livreTournois = Char
'\x20b6'

-- | The character used to render a /spesmilo sign/ presented as @₷@.
spesmilo ::
  -- | A character that corresponds with the /spesmilo sign/.
  Char
spesmilo :: Char
spesmilo = Char
'\x20b7'

-- | The character used to render a /tenge sign/ presented as @₸@.
tenge ::
  -- | A character that corresponds with the /tenge sign/.
  Char
tenge :: Char
tenge = Char
'\x20b8'

-- | The character used to render a /indian rupee sign/ presented as @₹@.
indianRupee ::
  -- | A character that corresponds with the /indian rupee sign/.
  Char
indianRupee :: Char
indianRupee = Char
'\x20b9'

-- | The character used to render a /turkish lira sign/ presented as @₺@.
turkishLira ::
  -- | A character that corresponds with the /turkish lira sign/.
  Char
turkishLira :: Char
turkishLira = Char
'\x20ba'

-- | The character used to render a /nordic mark sign/ presented as @₻@.
nordicMark ::
  -- | A character that corresponds with the /nordic mark sign/.
  Char
nordicMark :: Char
nordicMark = Char
'\x20bb'

-- | The character used to render a /manat sign/ presented as @₼@.
manat ::
  -- | A character that corresponds with the /manat sign/.
  Char
manat :: Char
manat = Char
'\x20bc'

-- | The character used to render a /ruble sign/ presented as @₽@.
ruble ::
  -- | A character that corresponds with the /ruble sign/.
  Char
ruble :: Char
ruble = Char
'\x20bd'

-- | The character used to render a /lari sign/ presented as @₾@.
lari ::
  -- | A character that corresponds with the /lari sign/.
  Char
lari :: Char
lari = Char
'\x20be'

-- | The character used to render a /bitcoin sign/ presented as @₿@.
bitcoin ::
  -- | A character that corresponds with the /bitcoin sign/.
  Char
bitcoin :: Char
bitcoin = Char
'\x20bf'

-- | The character used to render a /north indic rupee mark/ presented as @꠸@.
northIndicRupeeMark ::
  -- | A character that corresponds with the /north indic rupee mark/.
  Char
northIndicRupeeMark :: Char
northIndicRupeeMark = Char
'\xa838'

-- | The character used to render a /rial sign/ presented as @﷼@.
rial ::
  -- | A character that corresponds with the /rial sign/.
  Char
rial :: Char
rial = Char
'\xfdfc'

-- | The character used to render a /small dollar sign/ presented as @﹩@.
smallDollar ::
  -- | A character that corresponds with the /small dollar sign/.
  Char
smallDollar :: Char
smallDollar = Char
'\xfe69'

-- | The character used to render a /fullwidth dollar sign/ presented as @$@.
fullwidthDollar ::
  -- | A character that corresponds with the /fullwidth dollar sign/.
  Char
fullwidthDollar :: Char
fullwidthDollar = Char
'\xff04'

-- | The character used to render a /fullwidth cent sign/ presented as @¢@.
fullwidthCent ::
  -- | A character that corresponds with the /fullwidth cent sign/.
  Char
fullwidthCent :: Char
fullwidthCent = Char
'\xffe0'

-- | The character used to render a /fullwidth pound sign/ presented as @£@.
fullwidthPound ::
  -- | A character that corresponds with the /fullwidth pound sign/.
  Char
fullwidthPound :: Char
fullwidthPound = Char
'\xffe1'

-- | The character used to render a /fullwidth yen sign/ presented as @¥@.
fullwidthYen ::
  -- | A character that corresponds with the /fullwidth yen sign/.
  Char
fullwidthYen :: Char
fullwidthYen = Char
'\xffe5'

-- | The character used to render a /fullwidth won sign/ presented as @₩@.
fullwidthWon ::
  -- | A character that corresponds with the /fullwidth won sign/.
  Char
fullwidthWon :: Char
fullwidthWon = Char
'\xffe6'

-- | The character used to render a /tamil sign kaacu/ presented as @𑿝@.
tamilKaacu ::
  -- | A character that corresponds with the /tamil sign kaacu/.
  Char
tamilKaacu :: Char
tamilKaacu = Char
'\x11fdd'

-- | The character used to render a /tamil sign panam/ presented as @𑿞@.
tamilPanam ::
  -- | A character that corresponds with the /tamil sign panam/.
  Char
tamilPanam :: Char
tamilPanam = Char
'\x11fde'

-- | The character used to render a /tamil sign pon/ presented as @𑿟@.
tamilPon ::
  -- | A character that corresponds with the /tamil sign pon/.
  Char
tamilPon :: Char
tamilPon = Char
'\x11fdf'

-- | The character used to render a /tamil sign varaakan/ presented as @𑿠@.
tamilVaraakan ::
  -- | A character that corresponds with the /tamil sign varaakan/.
  Char
tamilVaraakan :: Char
tamilVaraakan = Char
'\x11fe0'

-- | The character used to render a /wancho ngun sign/ presented as @𞋿@.
wanchoNgun ::
  -- | A character that corresponds with the /wancho ngun sign/.
  Char
wanchoNgun :: Char
wanchoNgun = Char
'\x1e2ff'

-- | The character used to render a /indic siyaq rupee mark/ presented as @𞲰@.
indicSiyaqRupeeMark ::
  -- | A character that corresponds with the /indic siyaq rupee mark/.
  Char
indicSiyaqRupeeMark :: Char
indicSiyaqRupeeMark = Char
'\x1ecb0'