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.Number.Mayan

Description

Unicode uses a code block for Mayan numerals. Mayan numerals are written top to bottom, so vertically. This module aims to make it more convenient to write Mayan numerals by offering functions to convert numbers into a Text object for Mayan numbers. Mayan numerals can not present negative numbers.

Synopsis

Define Mayan literals

data MayanLiteral Source #

The Mayan numerals, as defined in the Unicode block.

Constructors

Zero

The unicode character for the Mayan numeral zero: 𝋠.

One

The unicode character for the Mayan numeral one: 𝋡.

Two

The unicode character for the Mayan numeral two: 𝋢.

Three

The unicode character for the Mayan numeral three: 𝋣.

Four

The unicode character for the Mayan numeral four: 𝋤.

Five

The unicode character for the Mayan numeral five: 𝋥.

Six

The unicode character for the Mayan numeral six: 𝋦.

Seven

The unicode character for the Mayan numeral seven: 𝋧.

Eight

The unicode character for the Mayan numeral eight: 𝋨.

Nine

The unicode character for the Mayan numeral nine: 𝋩.

Ten

The unicode character for the Mayan numeral ten: 𝋪.

Eleven

The unicode character for the Mayan numeral eleven: 𝋫.

Twelve

The unicode character for the Mayan numeral twelve: 𝋬.

Thirteen

The unicode character for the Mayan numeral thirteen: 𝋭.

Fourteen

The unicode character for the Mayan numeral fourteen: 𝋮.

Fifteen

The unicode character for the Mayan numeral fifteen: 𝋯.

Sixteen

The unicode character for the Mayan numeral sixteen: 𝋰.

Seventeen

The unicode character for the Mayan numeral seventeen: 𝋱.

Eighteen

The unicode character for the Mayan numeral eighteen: 𝋲.

Nineteen

The unicode character for the Mayan numeral nineteen: 𝋳.

Instances

Instances details
Arbitrary MayanLiteral Source # 
Instance details

Defined in Data.Char.Number.Mayan

Data MayanLiteral Source # 
Instance details

Defined in Data.Char.Number.Mayan

Methods

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

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

toConstr :: MayanLiteral -> Constr #

dataTypeOf :: MayanLiteral -> DataType #

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

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

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

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

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

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

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

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

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

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

Bounded MayanLiteral Source # 
Instance details

Defined in Data.Char.Number.Mayan

Enum MayanLiteral Source # 
Instance details

Defined in Data.Char.Number.Mayan

Generic MayanLiteral Source # 
Instance details

Defined in Data.Char.Number.Mayan

Associated Types

type Rep MayanLiteral :: Type -> Type #

Read MayanLiteral Source # 
Instance details

Defined in Data.Char.Number.Mayan

Show MayanLiteral Source # 
Instance details

Defined in Data.Char.Number.Mayan

NFData MayanLiteral Source # 
Instance details

Defined in Data.Char.Number.Mayan

Methods

rnf :: MayanLiteral -> () #

Eq MayanLiteral Source # 
Instance details

Defined in Data.Char.Number.Mayan

Ord MayanLiteral Source # 
Instance details

Defined in Data.Char.Number.Mayan

Hashable MayanLiteral Source # 
Instance details

Defined in Data.Char.Number.Mayan

UnicodeCharacter MayanLiteral Source # 
Instance details

Defined in Data.Char.Number.Mayan

UnicodeText MayanLiteral Source # 
Instance details

Defined in Data.Char.Number.Mayan

type Rep MayanLiteral Source # 
Instance details

Defined in Data.Char.Number.Mayan

type Rep MayanLiteral = D1 ('MetaData "MayanLiteral" "Data.Char.Number.Mayan" "unicode-tricks-0.14.1.0-EInLeozqGjBL3vIQTNPsAm" 'False) ((((C1 ('MetaCons "Zero" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "One" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Two" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Three" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Four" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Five" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Six" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Seven" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Eight" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Nine" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "Ten" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Eleven" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Twelve" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Thirteen" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Fourteen" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Fifteen" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Sixteen" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Seventeen" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Eighteen" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Nineteen" 'PrefixI 'False) (U1 :: Type -> Type))))))

Converting integers to Mayan numbers.

toMayanVertical Source #

Arguments

:: Integral i 
=> i

The given number to convert to a vertical String object.

-> Maybe Text

A Text that contains the Mayan number wrapped in a Just if we can represent the number; Nothing otherwise.

Convert the given Integral number to a Text object that writes the Mayan number to to bottom. This function will return a Nothing in case the number is negative (since it can not be presented in Mayan).

toMayanVertical' Source #

Arguments

:: Integral i 
=> i

The given number to convert to a vertical String object.

-> Text

A Text that contains the Mayan number.

Convert the given Integral number to a Text object that writes the Mayan number to to bottom.

toMayanVertical'' Source #

Arguments

:: Integral i 
=> i

The given number to convert to a vertical String object.

-> String

A String that contains the Mayan number.

Convert the given Integral number to a String object that writes the Mayan number to to bottom.

toMayan Source #

Arguments

:: Integral i 
=> i

The given number to convert to a horizontal String object.

-> Maybe Text

A Text that contains the Mayan number wrapped in a Just if we can represent the number; Nothing otherwise.

Convert the given Integral number to a Text object that writes the Mayan number from left-to-right. The object is wrapped in a Just data constructor. If the number is negative, and thus can not be represented, Nothing is returned.

toMayan' Source #

Arguments

:: Integral i 
=> i

The given number to convert to a horizontal String object.

-> Text

A Text that contains the Mayan number.

Convert the given Integral number to a Text object that writes the Mayan number from left-to-right.

toMayan'' Source #

Arguments

:: Integral i 
=> i

The given number to convert to a horizontal String object.

-> String

A String that contains the Mayan number.

Convert the given Integral number to a String object that writes the Mayan number from left-to-right.