{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE Safe #-}
{-# LANGUAGE TypeApplications #-}
module Data.Char.Number.Mayan
(
MayanLiteral (Zero, One, Two, Three, Four, Five, Six, Seven, Eight, Nine, Ten, Eleven, Twelve, Thirteen, Fourteen, Fifteen, Sixteen, Seventeen, Eighteen, Nineteen),
toMayanVertical,
toMayanVertical',
toMayanVertical'',
toMayan,
toMayan',
toMayan'',
)
where
import Control.DeepSeq (NFData)
import Data.Char.Core (UnicodeCharacter (fromUnicodeChar, fromUnicodeChar', isInCharRange, toUnicodeChar), UnicodeText (isInTextRange), generateIsInTextRange', mapFromEnum, mapToEnum, mapToEnumSafe)
import Data.Data (Data)
import Data.Hashable (Hashable)
import Data.Text (Text, pack)
import GHC.Generics (Generic)
import Test.QuickCheck.Arbitrary (Arbitrary (arbitrary), arbitraryBoundedEnum)
data MayanLiteral
=
Zero
|
One
|
Two
|
Three
|
Four
|
Five
|
Six
|
Seven
|
Eight
|
Nine
|
Ten
|
Eleven
|
Twelve
|
Thirteen
|
Fourteen
|
Fifteen
|
Sixteen
|
Seventeen
|
Eighteen
|
Nineteen
deriving (MayanLiteral
MayanLiteral -> MayanLiteral -> Bounded MayanLiteral
forall a. a -> a -> Bounded a
$cminBound :: MayanLiteral
minBound :: MayanLiteral
$cmaxBound :: MayanLiteral
maxBound :: MayanLiteral
Bounded, Typeable MayanLiteral
Typeable MayanLiteral
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> MayanLiteral -> c MayanLiteral)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c MayanLiteral)
-> (MayanLiteral -> Constr)
-> (MayanLiteral -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c MayanLiteral))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c MayanLiteral))
-> ((forall b. Data b => b -> b) -> MayanLiteral -> MayanLiteral)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> MayanLiteral -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> MayanLiteral -> r)
-> (forall u. (forall d. Data d => d -> u) -> MayanLiteral -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> MayanLiteral -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> MayanLiteral -> m MayanLiteral)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MayanLiteral -> m MayanLiteral)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MayanLiteral -> m MayanLiteral)
-> Data MayanLiteral
MayanLiteral -> Constr
MayanLiteral -> DataType
(forall b. Data b => b -> b) -> MayanLiteral -> MayanLiteral
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) -> MayanLiteral -> u
forall u. (forall d. Data d => d -> u) -> MayanLiteral -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> MayanLiteral -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> MayanLiteral -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> MayanLiteral -> m MayanLiteral
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MayanLiteral -> m MayanLiteral
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c MayanLiteral
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> MayanLiteral -> c MayanLiteral
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c MayanLiteral)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c MayanLiteral)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> MayanLiteral -> c MayanLiteral
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> MayanLiteral -> c MayanLiteral
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c MayanLiteral
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c MayanLiteral
$ctoConstr :: MayanLiteral -> Constr
toConstr :: MayanLiteral -> Constr
$cdataTypeOf :: MayanLiteral -> DataType
dataTypeOf :: MayanLiteral -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c MayanLiteral)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c MayanLiteral)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c MayanLiteral)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c MayanLiteral)
$cgmapT :: (forall b. Data b => b -> b) -> MayanLiteral -> MayanLiteral
gmapT :: (forall b. Data b => b -> b) -> MayanLiteral -> MayanLiteral
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> MayanLiteral -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> MayanLiteral -> r
$cgmapQr :: forall r r'.
(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
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> MayanLiteral -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> MayanLiteral -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> MayanLiteral -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> MayanLiteral -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> MayanLiteral -> m MayanLiteral
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> MayanLiteral -> m MayanLiteral
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MayanLiteral -> m MayanLiteral
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MayanLiteral -> m MayanLiteral
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MayanLiteral -> m MayanLiteral
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> MayanLiteral -> m MayanLiteral
Data, Int -> MayanLiteral
MayanLiteral -> Int
MayanLiteral -> [MayanLiteral]
MayanLiteral -> MayanLiteral
MayanLiteral -> MayanLiteral -> [MayanLiteral]
MayanLiteral -> MayanLiteral -> MayanLiteral -> [MayanLiteral]
(MayanLiteral -> MayanLiteral)
-> (MayanLiteral -> MayanLiteral)
-> (Int -> MayanLiteral)
-> (MayanLiteral -> Int)
-> (MayanLiteral -> [MayanLiteral])
-> (MayanLiteral -> MayanLiteral -> [MayanLiteral])
-> (MayanLiteral -> MayanLiteral -> [MayanLiteral])
-> (MayanLiteral -> MayanLiteral -> MayanLiteral -> [MayanLiteral])
-> Enum MayanLiteral
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: MayanLiteral -> MayanLiteral
succ :: MayanLiteral -> MayanLiteral
$cpred :: MayanLiteral -> MayanLiteral
pred :: MayanLiteral -> MayanLiteral
$ctoEnum :: Int -> MayanLiteral
toEnum :: Int -> MayanLiteral
$cfromEnum :: MayanLiteral -> Int
fromEnum :: MayanLiteral -> Int
$cenumFrom :: MayanLiteral -> [MayanLiteral]
enumFrom :: MayanLiteral -> [MayanLiteral]
$cenumFromThen :: MayanLiteral -> MayanLiteral -> [MayanLiteral]
enumFromThen :: MayanLiteral -> MayanLiteral -> [MayanLiteral]
$cenumFromTo :: MayanLiteral -> MayanLiteral -> [MayanLiteral]
enumFromTo :: MayanLiteral -> MayanLiteral -> [MayanLiteral]
$cenumFromThenTo :: MayanLiteral -> MayanLiteral -> MayanLiteral -> [MayanLiteral]
enumFromThenTo :: MayanLiteral -> MayanLiteral -> MayanLiteral -> [MayanLiteral]
Enum, MayanLiteral -> MayanLiteral -> Bool
(MayanLiteral -> MayanLiteral -> Bool)
-> (MayanLiteral -> MayanLiteral -> Bool) -> Eq MayanLiteral
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: MayanLiteral -> MayanLiteral -> Bool
== :: MayanLiteral -> MayanLiteral -> Bool
$c/= :: MayanLiteral -> MayanLiteral -> Bool
/= :: MayanLiteral -> MayanLiteral -> Bool
Eq, (forall x. MayanLiteral -> Rep MayanLiteral x)
-> (forall x. Rep MayanLiteral x -> MayanLiteral)
-> Generic MayanLiteral
forall x. Rep MayanLiteral x -> MayanLiteral
forall x. MayanLiteral -> Rep MayanLiteral x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. MayanLiteral -> Rep MayanLiteral x
from :: forall x. MayanLiteral -> Rep MayanLiteral x
$cto :: forall x. Rep MayanLiteral x -> MayanLiteral
to :: forall x. Rep MayanLiteral x -> MayanLiteral
Generic, Eq MayanLiteral
Eq MayanLiteral
-> (MayanLiteral -> MayanLiteral -> Ordering)
-> (MayanLiteral -> MayanLiteral -> Bool)
-> (MayanLiteral -> MayanLiteral -> Bool)
-> (MayanLiteral -> MayanLiteral -> Bool)
-> (MayanLiteral -> MayanLiteral -> Bool)
-> (MayanLiteral -> MayanLiteral -> MayanLiteral)
-> (MayanLiteral -> MayanLiteral -> MayanLiteral)
-> Ord MayanLiteral
MayanLiteral -> MayanLiteral -> Bool
MayanLiteral -> MayanLiteral -> Ordering
MayanLiteral -> MayanLiteral -> MayanLiteral
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
$ccompare :: MayanLiteral -> MayanLiteral -> Ordering
compare :: MayanLiteral -> MayanLiteral -> Ordering
$c< :: MayanLiteral -> MayanLiteral -> Bool
< :: MayanLiteral -> MayanLiteral -> Bool
$c<= :: MayanLiteral -> MayanLiteral -> Bool
<= :: MayanLiteral -> MayanLiteral -> Bool
$c> :: MayanLiteral -> MayanLiteral -> Bool
> :: MayanLiteral -> MayanLiteral -> Bool
$c>= :: MayanLiteral -> MayanLiteral -> Bool
>= :: MayanLiteral -> MayanLiteral -> Bool
$cmax :: MayanLiteral -> MayanLiteral -> MayanLiteral
max :: MayanLiteral -> MayanLiteral -> MayanLiteral
$cmin :: MayanLiteral -> MayanLiteral -> MayanLiteral
min :: MayanLiteral -> MayanLiteral -> MayanLiteral
Ord, ReadPrec [MayanLiteral]
ReadPrec MayanLiteral
Int -> ReadS MayanLiteral
ReadS [MayanLiteral]
(Int -> ReadS MayanLiteral)
-> ReadS [MayanLiteral]
-> ReadPrec MayanLiteral
-> ReadPrec [MayanLiteral]
-> Read MayanLiteral
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS MayanLiteral
readsPrec :: Int -> ReadS MayanLiteral
$creadList :: ReadS [MayanLiteral]
readList :: ReadS [MayanLiteral]
$creadPrec :: ReadPrec MayanLiteral
readPrec :: ReadPrec MayanLiteral
$creadListPrec :: ReadPrec [MayanLiteral]
readListPrec :: ReadPrec [MayanLiteral]
Read, Int -> MayanLiteral -> ShowS
[MayanLiteral] -> ShowS
MayanLiteral -> String
(Int -> MayanLiteral -> ShowS)
-> (MayanLiteral -> String)
-> ([MayanLiteral] -> ShowS)
-> Show MayanLiteral
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> MayanLiteral -> ShowS
showsPrec :: Int -> MayanLiteral -> ShowS
$cshow :: MayanLiteral -> String
show :: MayanLiteral -> String
$cshowList :: [MayanLiteral] -> ShowS
showList :: [MayanLiteral] -> ShowS
Show)
instance NFData MayanLiteral
_mayanOffset :: Int
_mayanOffset :: Int
_mayanOffset = Int
0x1d2e0
instance Arbitrary MayanLiteral where
arbitrary :: Gen MayanLiteral
arbitrary = Gen MayanLiteral
forall a. (Bounded a, Enum a) => Gen a
arbitraryBoundedEnum
instance Hashable MayanLiteral
instance UnicodeCharacter MayanLiteral where
toUnicodeChar :: MayanLiteral -> Char
toUnicodeChar = Int -> MayanLiteral -> Char
forall a. Enum a => Int -> a -> Char
mapFromEnum Int
_mayanOffset
fromUnicodeChar :: Char -> Maybe MayanLiteral
fromUnicodeChar = Int -> Char -> Maybe MayanLiteral
forall a. (Bounded a, Enum a) => Int -> Char -> Maybe a
mapToEnumSafe Int
_mayanOffset
fromUnicodeChar' :: Char -> MayanLiteral
fromUnicodeChar' = Int -> Char -> MayanLiteral
forall a. Enum a => Int -> Char -> a
mapToEnum Int
_mayanOffset
isInCharRange :: Char -> Bool
isInCharRange Char
c = Char
'\x1d2e0' Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
<= Char
c Bool -> Bool -> Bool
&& Char
c Char -> Char -> Bool
forall a. Ord a => a -> a -> Bool
<= Char
'\x1d2f3'
instance UnicodeText MayanLiteral where
isInTextRange :: Text -> Bool
isInTextRange = forall a. UnicodeCharacter a => Text -> Bool
generateIsInTextRange' @MayanLiteral
toMayanVertical ::
Integral i =>
i ->
Maybe Text
toMayanVertical :: forall i. Integral i => i -> Maybe Text
toMayanVertical i
n
| i
n i -> i -> Bool
forall a. Ord a => a -> a -> Bool
< i
0 = Maybe Text
forall a. Maybe a
Nothing
| Bool
otherwise = Text -> Maybe Text
forall a. a -> Maybe a
Just (i -> Text
forall i. Integral i => i -> Text
toMayanVertical' i
n)
toMayanVertical' ::
Integral i =>
i ->
Text
toMayanVertical' :: forall i. Integral i => i -> Text
toMayanVertical' = String -> Text
pack (String -> Text) -> (i -> String) -> i -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. i -> String
forall i. Integral i => i -> String
toMayanVertical''
toMayanVertical'' ::
Integral i =>
i ->
String
toMayanVertical'' :: forall i. Integral i => i -> String
toMayanVertical'' = [String] -> String
unlines ([String] -> String) -> (i -> [String]) -> i -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> String) -> String -> [String]
forall a b. (a -> b) -> [a] -> [b]
map Char -> String
forall a. a -> [a]
forall (f :: * -> *) a. Applicative f => a -> f a
pure (String -> [String]) -> (i -> String) -> i -> [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. i -> String
forall i. Integral i => i -> String
toMayan''
toMayan ::
Integral i =>
i ->
Maybe Text
toMayan :: forall i. Integral i => i -> Maybe Text
toMayan i
n
| i
n i -> i -> Bool
forall a. Ord a => a -> a -> Bool
< i
0 = Maybe Text
forall a. Maybe a
Nothing
| Bool
otherwise = Text -> Maybe Text
forall a. a -> Maybe a
Just (i -> Text
forall i. Integral i => i -> Text
toMayan' i
n)
toMayan' ::
Integral i =>
i ->
Text
toMayan' :: forall i. Integral i => i -> Text
toMayan' = String -> Text
pack (String -> Text) -> (i -> String) -> i -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. i -> String
forall i. Integral i => i -> String
toMayan''
toMayan'' ::
Integral i =>
i ->
String
toMayan'' :: forall i. Integral i => i -> String
toMayan'' = String -> i -> String
forall {t}. Integral t => String -> t -> String
go []
where
go :: String -> t -> String
go String
xs t
n
| t
n t -> t -> Bool
forall a. Ord a => a -> a -> Bool
<= t
19 = t -> Char
ch t
n Char -> ShowS
forall a. a -> [a] -> [a]
: String
xs
| Bool
otherwise = String -> t -> String
go (t -> Char
ch t
r Char -> ShowS
forall a. a -> [a] -> [a]
: String
xs) t
q
where
~(t
q, t
r) = t
n t -> t -> (t, t)
forall a. Integral a => a -> a -> (a, a)
`quotRem` t
20
ch :: t -> Char
ch = MayanLiteral -> Char
forall a. UnicodeCharacter a => a -> Char
toUnicodeChar (MayanLiteral -> Char) -> (t -> MayanLiteral) -> t -> Char
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. Enum a => Int -> a
toEnum @MayanLiteral (Int -> MayanLiteral) -> (t -> Int) -> t -> MayanLiteral
forall b c a. (b -> c) -> (a -> b) -> a -> c
. t -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral