{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE Safe #-}
{-# LANGUAGE TypeApplications #-}
module Data.Char.Number.Roman
(
RomanLiteral (I, II, III, IV, V, VI, VII, VIII, IX, X, XI, XII, L, C, D, M),
RomanStyle (Additive, Subtractive),
toLiterals,
romanLiteral,
romanLiteral',
romanNumeral,
romanNumeral',
romanNumeralCase,
romanNumber,
romanNumber',
romanNumberCase,
)
where
import Control.DeepSeq (NFData)
import Data.Bits ((.|.))
import Data.Char (chr)
import Data.Char.Core (LetterCase, Ligate, UnicodeCharacter (fromUnicodeChar, fromUnicodeChar', isInCharRange, toUnicodeChar), UnicodeText (isInTextRange), generateIsInTextRange', ligateF, mapFromEnum, mapToEnum, mapToEnumSafe, splitLetterCase)
import Data.Data (Data)
import Data.Default.Class (Default (def))
import Data.Hashable (Hashable)
import Data.Text (Text, cons, empty)
import GHC.Generics (Generic)
import Test.QuickCheck.Arbitrary (Arbitrary (arbitrary), arbitraryBoundedEnum)
data RomanStyle
=
Additive
|
Subtractive
deriving (RomanStyle
RomanStyle -> RomanStyle -> Bounded RomanStyle
forall a. a -> a -> Bounded a
$cminBound :: RomanStyle
minBound :: RomanStyle
$cmaxBound :: RomanStyle
maxBound :: RomanStyle
Bounded, Typeable RomanStyle
Typeable RomanStyle
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RomanStyle -> c RomanStyle)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RomanStyle)
-> (RomanStyle -> Constr)
-> (RomanStyle -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RomanStyle))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c RomanStyle))
-> ((forall b. Data b => b -> b) -> RomanStyle -> RomanStyle)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RomanStyle -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RomanStyle -> r)
-> (forall u. (forall d. Data d => d -> u) -> RomanStyle -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> RomanStyle -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> RomanStyle -> m RomanStyle)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RomanStyle -> m RomanStyle)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RomanStyle -> m RomanStyle)
-> Data RomanStyle
RomanStyle -> Constr
RomanStyle -> DataType
(forall b. Data b => b -> b) -> RomanStyle -> RomanStyle
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) -> RomanStyle -> u
forall u. (forall d. Data d => d -> u) -> RomanStyle -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RomanStyle -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RomanStyle -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> RomanStyle -> m RomanStyle
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RomanStyle -> m RomanStyle
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RomanStyle
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RomanStyle -> c RomanStyle
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RomanStyle)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RomanStyle)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RomanStyle -> c RomanStyle
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RomanStyle -> c RomanStyle
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RomanStyle
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RomanStyle
$ctoConstr :: RomanStyle -> Constr
toConstr :: RomanStyle -> Constr
$cdataTypeOf :: RomanStyle -> DataType
dataTypeOf :: RomanStyle -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RomanStyle)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RomanStyle)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RomanStyle)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RomanStyle)
$cgmapT :: (forall b. Data b => b -> b) -> RomanStyle -> RomanStyle
gmapT :: (forall b. Data b => b -> b) -> RomanStyle -> RomanStyle
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RomanStyle -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RomanStyle -> r
$cgmapQr :: forall r r'.
(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
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> RomanStyle -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> RomanStyle -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> RomanStyle -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> RomanStyle -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> RomanStyle -> m RomanStyle
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> RomanStyle -> m RomanStyle
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RomanStyle -> m RomanStyle
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RomanStyle -> m RomanStyle
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RomanStyle -> m RomanStyle
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RomanStyle -> m RomanStyle
Data, Int -> RomanStyle
RomanStyle -> Int
RomanStyle -> [RomanStyle]
RomanStyle -> RomanStyle
RomanStyle -> RomanStyle -> [RomanStyle]
RomanStyle -> RomanStyle -> RomanStyle -> [RomanStyle]
(RomanStyle -> RomanStyle)
-> (RomanStyle -> RomanStyle)
-> (Int -> RomanStyle)
-> (RomanStyle -> Int)
-> (RomanStyle -> [RomanStyle])
-> (RomanStyle -> RomanStyle -> [RomanStyle])
-> (RomanStyle -> RomanStyle -> [RomanStyle])
-> (RomanStyle -> RomanStyle -> RomanStyle -> [RomanStyle])
-> Enum RomanStyle
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 :: RomanStyle -> RomanStyle
succ :: RomanStyle -> RomanStyle
$cpred :: RomanStyle -> RomanStyle
pred :: RomanStyle -> RomanStyle
$ctoEnum :: Int -> RomanStyle
toEnum :: Int -> RomanStyle
$cfromEnum :: RomanStyle -> Int
fromEnum :: RomanStyle -> Int
$cenumFrom :: RomanStyle -> [RomanStyle]
enumFrom :: RomanStyle -> [RomanStyle]
$cenumFromThen :: RomanStyle -> RomanStyle -> [RomanStyle]
enumFromThen :: RomanStyle -> RomanStyle -> [RomanStyle]
$cenumFromTo :: RomanStyle -> RomanStyle -> [RomanStyle]
enumFromTo :: RomanStyle -> RomanStyle -> [RomanStyle]
$cenumFromThenTo :: RomanStyle -> RomanStyle -> RomanStyle -> [RomanStyle]
enumFromThenTo :: RomanStyle -> RomanStyle -> RomanStyle -> [RomanStyle]
Enum, RomanStyle -> RomanStyle -> Bool
(RomanStyle -> RomanStyle -> Bool)
-> (RomanStyle -> RomanStyle -> Bool) -> Eq RomanStyle
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RomanStyle -> RomanStyle -> Bool
== :: RomanStyle -> RomanStyle -> Bool
$c/= :: RomanStyle -> RomanStyle -> Bool
/= :: RomanStyle -> RomanStyle -> Bool
Eq, (forall x. RomanStyle -> Rep RomanStyle x)
-> (forall x. Rep RomanStyle x -> RomanStyle) -> Generic RomanStyle
forall x. Rep RomanStyle x -> RomanStyle
forall x. RomanStyle -> Rep RomanStyle x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. RomanStyle -> Rep RomanStyle x
from :: forall x. RomanStyle -> Rep RomanStyle x
$cto :: forall x. Rep RomanStyle x -> RomanStyle
to :: forall x. Rep RomanStyle x -> RomanStyle
Generic, Eq RomanStyle
Eq RomanStyle
-> (RomanStyle -> RomanStyle -> Ordering)
-> (RomanStyle -> RomanStyle -> Bool)
-> (RomanStyle -> RomanStyle -> Bool)
-> (RomanStyle -> RomanStyle -> Bool)
-> (RomanStyle -> RomanStyle -> Bool)
-> (RomanStyle -> RomanStyle -> RomanStyle)
-> (RomanStyle -> RomanStyle -> RomanStyle)
-> Ord RomanStyle
RomanStyle -> RomanStyle -> Bool
RomanStyle -> RomanStyle -> Ordering
RomanStyle -> RomanStyle -> RomanStyle
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 :: RomanStyle -> RomanStyle -> Ordering
compare :: RomanStyle -> RomanStyle -> Ordering
$c< :: RomanStyle -> RomanStyle -> Bool
< :: RomanStyle -> RomanStyle -> Bool
$c<= :: RomanStyle -> RomanStyle -> Bool
<= :: RomanStyle -> RomanStyle -> Bool
$c> :: RomanStyle -> RomanStyle -> Bool
> :: RomanStyle -> RomanStyle -> Bool
$c>= :: RomanStyle -> RomanStyle -> Bool
>= :: RomanStyle -> RomanStyle -> Bool
$cmax :: RomanStyle -> RomanStyle -> RomanStyle
max :: RomanStyle -> RomanStyle -> RomanStyle
$cmin :: RomanStyle -> RomanStyle -> RomanStyle
min :: RomanStyle -> RomanStyle -> RomanStyle
Ord, ReadPrec [RomanStyle]
ReadPrec RomanStyle
Int -> ReadS RomanStyle
ReadS [RomanStyle]
(Int -> ReadS RomanStyle)
-> ReadS [RomanStyle]
-> ReadPrec RomanStyle
-> ReadPrec [RomanStyle]
-> Read RomanStyle
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS RomanStyle
readsPrec :: Int -> ReadS RomanStyle
$creadList :: ReadS [RomanStyle]
readList :: ReadS [RomanStyle]
$creadPrec :: ReadPrec RomanStyle
readPrec :: ReadPrec RomanStyle
$creadListPrec :: ReadPrec [RomanStyle]
readListPrec :: ReadPrec [RomanStyle]
Read, Int -> RomanStyle -> ShowS
[RomanStyle] -> ShowS
RomanStyle -> String
(Int -> RomanStyle -> ShowS)
-> (RomanStyle -> String)
-> ([RomanStyle] -> ShowS)
-> Show RomanStyle
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RomanStyle -> ShowS
showsPrec :: Int -> RomanStyle -> ShowS
$cshow :: RomanStyle -> String
show :: RomanStyle -> String
$cshowList :: [RomanStyle] -> ShowS
showList :: [RomanStyle] -> ShowS
Show)
instance Arbitrary RomanStyle where
arbitrary :: Gen RomanStyle
arbitrary = Gen RomanStyle
forall a. (Bounded a, Enum a) => Gen a
arbitraryBoundedEnum
instance Arbitrary RomanLiteral where
arbitrary :: Gen RomanLiteral
arbitrary = Gen RomanLiteral
forall a. (Bounded a, Enum a) => Gen a
arbitraryBoundedEnum
instance Default RomanStyle where
def :: RomanStyle
def = RomanStyle
Subtractive
instance Hashable RomanStyle
instance NFData RomanStyle
instance UnicodeCharacter RomanLiteral where
toUnicodeChar :: RomanLiteral -> Char
toUnicodeChar = Int -> RomanLiteral -> Char
forall a. Enum a => Int -> a -> Char
mapFromEnum Int
_romanUppercaseOffset
fromUnicodeChar :: Char -> Maybe RomanLiteral
fromUnicodeChar = Int -> Char -> Maybe RomanLiteral
forall a. (Bounded a, Enum a) => Int -> Char -> Maybe a
mapToEnumSafe Int
_romanUppercaseOffset
fromUnicodeChar' :: Char -> RomanLiteral
fromUnicodeChar' = Int -> Char -> RomanLiteral
forall a. Enum a => Int -> Char -> a
mapToEnum Int
_romanUppercaseOffset
isInCharRange :: Char -> Bool
isInCharRange Char
c = Char
'\x2160' 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
'\x216f'
instance UnicodeText RomanLiteral where
isInTextRange :: Text -> Bool
isInTextRange = forall a. UnicodeCharacter a => Text -> Bool
generateIsInTextRange' @RomanLiteral
data RomanLiteral
=
I
|
II
|
III
|
IV
|
V
|
VI
|
VII
|
VIII
|
IX
|
X
|
XI
|
XII
|
L
|
C
|
D
|
M
deriving (RomanLiteral
RomanLiteral -> RomanLiteral -> Bounded RomanLiteral
forall a. a -> a -> Bounded a
$cminBound :: RomanLiteral
minBound :: RomanLiteral
$cmaxBound :: RomanLiteral
maxBound :: RomanLiteral
Bounded, Typeable RomanLiteral
Typeable RomanLiteral
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RomanLiteral -> c RomanLiteral)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RomanLiteral)
-> (RomanLiteral -> Constr)
-> (RomanLiteral -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RomanLiteral))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c RomanLiteral))
-> ((forall b. Data b => b -> b) -> RomanLiteral -> RomanLiteral)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RomanLiteral -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RomanLiteral -> r)
-> (forall u. (forall d. Data d => d -> u) -> RomanLiteral -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> RomanLiteral -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> RomanLiteral -> m RomanLiteral)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RomanLiteral -> m RomanLiteral)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RomanLiteral -> m RomanLiteral)
-> Data RomanLiteral
RomanLiteral -> Constr
RomanLiteral -> DataType
(forall b. Data b => b -> b) -> RomanLiteral -> RomanLiteral
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) -> RomanLiteral -> u
forall u. (forall d. Data d => d -> u) -> RomanLiteral -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RomanLiteral -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> RomanLiteral -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> RomanLiteral -> m RomanLiteral
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RomanLiteral -> m RomanLiteral
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RomanLiteral
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RomanLiteral -> c RomanLiteral
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RomanLiteral)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c RomanLiteral)
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RomanLiteral -> c RomanLiteral
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> RomanLiteral -> c RomanLiteral
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RomanLiteral
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c RomanLiteral
$ctoConstr :: RomanLiteral -> Constr
toConstr :: RomanLiteral -> Constr
$cdataTypeOf :: RomanLiteral -> DataType
dataTypeOf :: RomanLiteral -> DataType
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RomanLiteral)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c RomanLiteral)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c RomanLiteral)
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c RomanLiteral)
$cgmapT :: (forall b. Data b => b -> b) -> RomanLiteral -> RomanLiteral
gmapT :: (forall b. Data b => b -> b) -> RomanLiteral -> RomanLiteral
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RomanLiteral -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> RomanLiteral -> r
$cgmapQr :: forall r r'.
(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
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> RomanLiteral -> [u]
gmapQ :: forall u. (forall d. Data d => d -> u) -> RomanLiteral -> [u]
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> RomanLiteral -> u
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> RomanLiteral -> u
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> RomanLiteral -> m RomanLiteral
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> RomanLiteral -> m RomanLiteral
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RomanLiteral -> m RomanLiteral
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RomanLiteral -> m RomanLiteral
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RomanLiteral -> m RomanLiteral
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> RomanLiteral -> m RomanLiteral
Data, Int -> RomanLiteral
RomanLiteral -> Int
RomanLiteral -> [RomanLiteral]
RomanLiteral -> RomanLiteral
RomanLiteral -> RomanLiteral -> [RomanLiteral]
RomanLiteral -> RomanLiteral -> RomanLiteral -> [RomanLiteral]
(RomanLiteral -> RomanLiteral)
-> (RomanLiteral -> RomanLiteral)
-> (Int -> RomanLiteral)
-> (RomanLiteral -> Int)
-> (RomanLiteral -> [RomanLiteral])
-> (RomanLiteral -> RomanLiteral -> [RomanLiteral])
-> (RomanLiteral -> RomanLiteral -> [RomanLiteral])
-> (RomanLiteral -> RomanLiteral -> RomanLiteral -> [RomanLiteral])
-> Enum RomanLiteral
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 :: RomanLiteral -> RomanLiteral
succ :: RomanLiteral -> RomanLiteral
$cpred :: RomanLiteral -> RomanLiteral
pred :: RomanLiteral -> RomanLiteral
$ctoEnum :: Int -> RomanLiteral
toEnum :: Int -> RomanLiteral
$cfromEnum :: RomanLiteral -> Int
fromEnum :: RomanLiteral -> Int
$cenumFrom :: RomanLiteral -> [RomanLiteral]
enumFrom :: RomanLiteral -> [RomanLiteral]
$cenumFromThen :: RomanLiteral -> RomanLiteral -> [RomanLiteral]
enumFromThen :: RomanLiteral -> RomanLiteral -> [RomanLiteral]
$cenumFromTo :: RomanLiteral -> RomanLiteral -> [RomanLiteral]
enumFromTo :: RomanLiteral -> RomanLiteral -> [RomanLiteral]
$cenumFromThenTo :: RomanLiteral -> RomanLiteral -> RomanLiteral -> [RomanLiteral]
enumFromThenTo :: RomanLiteral -> RomanLiteral -> RomanLiteral -> [RomanLiteral]
Enum, RomanLiteral -> RomanLiteral -> Bool
(RomanLiteral -> RomanLiteral -> Bool)
-> (RomanLiteral -> RomanLiteral -> Bool) -> Eq RomanLiteral
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RomanLiteral -> RomanLiteral -> Bool
== :: RomanLiteral -> RomanLiteral -> Bool
$c/= :: RomanLiteral -> RomanLiteral -> Bool
/= :: RomanLiteral -> RomanLiteral -> Bool
Eq, (forall x. RomanLiteral -> Rep RomanLiteral x)
-> (forall x. Rep RomanLiteral x -> RomanLiteral)
-> Generic RomanLiteral
forall x. Rep RomanLiteral x -> RomanLiteral
forall x. RomanLiteral -> Rep RomanLiteral x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. RomanLiteral -> Rep RomanLiteral x
from :: forall x. RomanLiteral -> Rep RomanLiteral x
$cto :: forall x. Rep RomanLiteral x -> RomanLiteral
to :: forall x. Rep RomanLiteral x -> RomanLiteral
Generic, Int -> RomanLiteral -> ShowS
[RomanLiteral] -> ShowS
RomanLiteral -> String
(Int -> RomanLiteral -> ShowS)
-> (RomanLiteral -> String)
-> ([RomanLiteral] -> ShowS)
-> Show RomanLiteral
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RomanLiteral -> ShowS
showsPrec :: Int -> RomanLiteral -> ShowS
$cshow :: RomanLiteral -> String
show :: RomanLiteral -> String
$cshowList :: [RomanLiteral] -> ShowS
showList :: [RomanLiteral] -> ShowS
Show, ReadPrec [RomanLiteral]
ReadPrec RomanLiteral
Int -> ReadS RomanLiteral
ReadS [RomanLiteral]
(Int -> ReadS RomanLiteral)
-> ReadS [RomanLiteral]
-> ReadPrec RomanLiteral
-> ReadPrec [RomanLiteral]
-> Read RomanLiteral
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS RomanLiteral
readsPrec :: Int -> ReadS RomanLiteral
$creadList :: ReadS [RomanLiteral]
readList :: ReadS [RomanLiteral]
$creadPrec :: ReadPrec RomanLiteral
readPrec :: ReadPrec RomanLiteral
$creadListPrec :: ReadPrec [RomanLiteral]
readListPrec :: ReadPrec [RomanLiteral]
Read)
instance Hashable RomanLiteral
instance NFData RomanLiteral
_literals :: Integral i => RomanStyle -> [(i, [RomanLiteral] -> [RomanLiteral])]
_literals :: forall i.
Integral i =>
RomanStyle -> [(i, [RomanLiteral] -> [RomanLiteral])]
_literals RomanStyle
Additive =
[ (i
1000, (RomanLiteral
M RomanLiteral -> [RomanLiteral] -> [RomanLiteral]
forall a. a -> [a] -> [a]
:)),
(i
500, (RomanLiteral
D RomanLiteral -> [RomanLiteral] -> [RomanLiteral]
forall a. a -> [a] -> [a]
:)),
(i
100, (RomanLiteral
C RomanLiteral -> [RomanLiteral] -> [RomanLiteral]
forall a. a -> [a] -> [a]
:)),
(i
50, (RomanLiteral
L RomanLiteral -> [RomanLiteral] -> [RomanLiteral]
forall a. a -> [a] -> [a]
:)),
(i
10, (RomanLiteral
X RomanLiteral -> [RomanLiteral] -> [RomanLiteral]
forall a. a -> [a] -> [a]
:)),
(i
5, (RomanLiteral
V RomanLiteral -> [RomanLiteral] -> [RomanLiteral]
forall a. a -> [a] -> [a]
:)),
(i
1, (RomanLiteral
I RomanLiteral -> [RomanLiteral] -> [RomanLiteral]
forall a. a -> [a] -> [a]
:))
]
_literals RomanStyle
Subtractive =
[ (i
1000, (RomanLiteral
M RomanLiteral -> [RomanLiteral] -> [RomanLiteral]
forall a. a -> [a] -> [a]
:)),
(i
900, ([RomanLiteral
C, RomanLiteral
M] [RomanLiteral] -> [RomanLiteral] -> [RomanLiteral]
forall a. [a] -> [a] -> [a]
++)),
(i
500, (RomanLiteral
D RomanLiteral -> [RomanLiteral] -> [RomanLiteral]
forall a. a -> [a] -> [a]
:)),
(i
400, ([RomanLiteral
C, RomanLiteral
D] [RomanLiteral] -> [RomanLiteral] -> [RomanLiteral]
forall a. [a] -> [a] -> [a]
++)),
(i
100, (RomanLiteral
C RomanLiteral -> [RomanLiteral] -> [RomanLiteral]
forall a. a -> [a] -> [a]
:)),
(i
90, ([RomanLiteral
X, RomanLiteral
C] [RomanLiteral] -> [RomanLiteral] -> [RomanLiteral]
forall a. [a] -> [a] -> [a]
++)),
(i
50, (RomanLiteral
L RomanLiteral -> [RomanLiteral] -> [RomanLiteral]
forall a. a -> [a] -> [a]
:)),
(i
40, ([RomanLiteral
X, RomanLiteral
L] [RomanLiteral] -> [RomanLiteral] -> [RomanLiteral]
forall a. [a] -> [a] -> [a]
++)),
(i
10, (RomanLiteral
X RomanLiteral -> [RomanLiteral] -> [RomanLiteral]
forall a. a -> [a] -> [a]
:)),
(i
9, ([RomanLiteral
I, RomanLiteral
X] [RomanLiteral] -> [RomanLiteral] -> [RomanLiteral]
forall a. [a] -> [a] -> [a]
++)),
(i
5, (RomanLiteral
V RomanLiteral -> [RomanLiteral] -> [RomanLiteral]
forall a. a -> [a] -> [a]
:)),
(i
4, ([RomanLiteral
I, RomanLiteral
V] [RomanLiteral] -> [RomanLiteral] -> [RomanLiteral]
forall a. [a] -> [a] -> [a]
++)),
(i
1, (RomanLiteral
I RomanLiteral -> [RomanLiteral] -> [RomanLiteral]
forall a. a -> [a] -> [a]
:))
]
_ligate :: [RomanLiteral] -> [RomanLiteral]
_ligate :: [RomanLiteral] -> [RomanLiteral]
_ligate [] = []
_ligate (RomanLiteral
r : [RomanLiteral]
rs) = RomanLiteral -> [RomanLiteral] -> [RomanLiteral]
go RomanLiteral
r [RomanLiteral]
rs
where
go :: RomanLiteral -> [RomanLiteral] -> [RomanLiteral]
go RomanLiteral
x [] = [RomanLiteral
x]
go RomanLiteral
x (RomanLiteral
y : [RomanLiteral]
ys) = RomanLiteral -> RomanLiteral -> [RomanLiteral] -> [RomanLiteral]
f RomanLiteral
x RomanLiteral
y [RomanLiteral]
ys
f :: RomanLiteral -> RomanLiteral -> [RomanLiteral] -> [RomanLiteral]
f RomanLiteral
I RomanLiteral
I = RomanLiteral -> [RomanLiteral] -> [RomanLiteral]
go RomanLiteral
II
f RomanLiteral
II RomanLiteral
I = RomanLiteral -> [RomanLiteral] -> [RomanLiteral]
skip RomanLiteral
III
f RomanLiteral
I RomanLiteral
V = RomanLiteral -> [RomanLiteral] -> [RomanLiteral]
skip RomanLiteral
IV
f RomanLiteral
V RomanLiteral
I = RomanLiteral -> [RomanLiteral] -> [RomanLiteral]
go RomanLiteral
VI
f RomanLiteral
VI RomanLiteral
I = RomanLiteral -> [RomanLiteral] -> [RomanLiteral]
go RomanLiteral
VII
f RomanLiteral
VII RomanLiteral
I = RomanLiteral -> [RomanLiteral] -> [RomanLiteral]
skip RomanLiteral
VIII
f RomanLiteral
X RomanLiteral
I = RomanLiteral -> [RomanLiteral] -> [RomanLiteral]
go RomanLiteral
XI
f RomanLiteral
I RomanLiteral
X = RomanLiteral -> [RomanLiteral] -> [RomanLiteral]
skip RomanLiteral
IX
f RomanLiteral
XI RomanLiteral
I = RomanLiteral -> [RomanLiteral] -> [RomanLiteral]
go RomanLiteral
XII
f RomanLiteral
x RomanLiteral
y = (RomanLiteral
x RomanLiteral -> [RomanLiteral] -> [RomanLiteral]
forall a. a -> [a] -> [a]
:) ([RomanLiteral] -> [RomanLiteral])
-> ([RomanLiteral] -> [RomanLiteral])
-> [RomanLiteral]
-> [RomanLiteral]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RomanLiteral -> [RomanLiteral] -> [RomanLiteral]
go RomanLiteral
y
skip :: RomanLiteral -> [RomanLiteral] -> [RomanLiteral]
skip = (([RomanLiteral] -> [RomanLiteral])
-> ([RomanLiteral] -> [RomanLiteral])
-> [RomanLiteral]
-> [RomanLiteral]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [RomanLiteral] -> [RomanLiteral]
_ligate) (([RomanLiteral] -> [RomanLiteral])
-> [RomanLiteral] -> [RomanLiteral])
-> (RomanLiteral -> [RomanLiteral] -> [RomanLiteral])
-> RomanLiteral
-> [RomanLiteral]
-> [RomanLiteral]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (:)
toLiterals ::
Integral i =>
RomanStyle ->
Ligate ->
i ->
Maybe [RomanLiteral]
toLiterals :: forall i.
Integral i =>
RomanStyle -> Ligate -> i -> Maybe [RomanLiteral]
toLiterals RomanStyle
s Ligate
c i
k
| i
k i -> i -> Bool
forall a. Ord a => a -> a -> Bool
> i
0 = ([RomanLiteral] -> [RomanLiteral])
-> Ligate -> Maybe [RomanLiteral] -> Maybe [RomanLiteral]
forall (f :: * -> *) a.
Functor f =>
(a -> a) -> Ligate -> f a -> f a
ligateF [RomanLiteral] -> [RomanLiteral]
_ligate Ligate
c (i
-> [(i, [RomanLiteral] -> [RomanLiteral])] -> Maybe [RomanLiteral]
forall {t} {a}.
(Num t, Ord t) =>
t -> [(t, [a] -> [a])] -> Maybe [a]
go i
k (RomanStyle -> [(i, [RomanLiteral] -> [RomanLiteral])]
forall i.
Integral i =>
RomanStyle -> [(i, [RomanLiteral] -> [RomanLiteral])]
_literals RomanStyle
s))
| Bool
otherwise = Maybe [RomanLiteral]
forall a. Maybe a
Nothing
where
go :: t -> [(t, [a] -> [a])] -> Maybe [a]
go t
0 [(t, [a] -> [a])]
_ = [a] -> Maybe [a]
forall a. a -> Maybe a
Just []
go t
_ [] = Maybe [a]
forall a. Maybe a
Nothing
go t
n va :: [(t, [a] -> [a])]
va@((t
m, [a] -> [a]
l) : [(t, [a] -> [a])]
vs)
| t
n t -> t -> Bool
forall a. Ord a => a -> a -> Bool
>= t
m = [a] -> [a]
l ([a] -> [a]) -> Maybe [a] -> Maybe [a]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> t -> [(t, [a] -> [a])] -> Maybe [a]
go (t
n t -> t -> t
forall a. Num a => a -> a -> a
- t
m) [(t, [a] -> [a])]
va
| Bool
otherwise = t -> [(t, [a] -> [a])] -> Maybe [a]
go t
n [(t, [a] -> [a])]
vs
_romanUppercaseOffset :: Int
_romanUppercaseOffset :: Int
_romanUppercaseOffset = Int
0x2160
_romanLowercaseOffset :: Int
_romanLowercaseOffset :: Int
_romanLowercaseOffset = Int
0x2170
_romanLiteral :: Int -> RomanLiteral -> Char
_romanLiteral :: Int -> RomanLiteral -> Char
_romanLiteral = (Int -> Char
chr (Int -> Char) -> (RomanLiteral -> Int) -> RomanLiteral -> Char
forall b c a. (b -> c) -> (a -> b) -> a -> c
.) ((RomanLiteral -> Int) -> RomanLiteral -> Char)
-> (Int -> RomanLiteral -> Int) -> Int -> RomanLiteral -> Char
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Int -> Int) -> (RomanLiteral -> Int) -> RomanLiteral -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RomanLiteral -> Int
forall a. Enum a => a -> Int
fromEnum) ((Int -> Int) -> RomanLiteral -> Int)
-> (Int -> Int -> Int) -> Int -> RomanLiteral -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int -> Int
forall a. Bits a => a -> a -> a
(.|.)
romanLiteral ::
RomanLiteral ->
Char
romanLiteral :: RomanLiteral -> Char
romanLiteral = Int -> RomanLiteral -> Char
_romanLiteral Int
_romanUppercaseOffset
romanLiteral' ::
RomanLiteral ->
Char
romanLiteral' :: RomanLiteral -> Char
romanLiteral' = Int -> RomanLiteral -> Char
_romanLiteral Int
_romanLowercaseOffset
_romanNumeral :: (RomanLiteral -> Char) -> [RomanLiteral] -> Text
_romanNumeral :: (RomanLiteral -> Char) -> [RomanLiteral] -> Text
_romanNumeral = ((RomanLiteral -> Text -> Text) -> Text -> [RomanLiteral] -> Text
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
`foldr` Text
empty) ((RomanLiteral -> Text -> Text) -> [RomanLiteral] -> Text)
-> ((RomanLiteral -> Char) -> RomanLiteral -> Text -> Text)
-> (RomanLiteral -> Char)
-> [RomanLiteral]
-> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Char -> Text -> Text
cons (Char -> Text -> Text)
-> (RomanLiteral -> Char) -> RomanLiteral -> Text -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
.)
romanNumeral ::
[RomanLiteral] ->
Text
romanNumeral :: [RomanLiteral] -> Text
romanNumeral = (RomanLiteral -> Char) -> [RomanLiteral] -> Text
_romanNumeral RomanLiteral -> Char
romanLiteral
romanNumeral' ::
[RomanLiteral] ->
Text
romanNumeral' :: [RomanLiteral] -> Text
romanNumeral' = (RomanLiteral -> Char) -> [RomanLiteral] -> Text
_romanNumeral RomanLiteral -> Char
romanLiteral'
romanNumeralCase ::
LetterCase ->
[RomanLiteral] ->
Text
romanNumeralCase :: LetterCase -> [RomanLiteral] -> Text
romanNumeralCase = ([RomanLiteral] -> Text)
-> ([RomanLiteral] -> Text) -> LetterCase -> [RomanLiteral] -> Text
forall a. a -> a -> LetterCase -> a
splitLetterCase [RomanLiteral] -> Text
romanNumeral [RomanLiteral] -> Text
romanNumeral'
_romanNumber :: Integral i => ([RomanLiteral] -> a) -> RomanStyle -> Ligate -> i -> Maybe a
_romanNumber :: forall i a.
Integral i =>
([RomanLiteral] -> a) -> RomanStyle -> Ligate -> i -> Maybe a
_romanNumber [RomanLiteral] -> a
f RomanStyle
r Ligate
c = ([RomanLiteral] -> a) -> Maybe [RomanLiteral] -> Maybe a
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap [RomanLiteral] -> a
f (Maybe [RomanLiteral] -> Maybe a)
-> (i -> Maybe [RomanLiteral]) -> i -> Maybe a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RomanStyle -> Ligate -> i -> Maybe [RomanLiteral]
forall i.
Integral i =>
RomanStyle -> Ligate -> i -> Maybe [RomanLiteral]
toLiterals RomanStyle
r Ligate
c
romanNumber ::
Integral i =>
RomanStyle ->
Ligate ->
i ->
Maybe Text
romanNumber :: forall i. Integral i => RomanStyle -> Ligate -> i -> Maybe Text
romanNumber = ([RomanLiteral] -> Text) -> RomanStyle -> Ligate -> i -> Maybe Text
forall i a.
Integral i =>
([RomanLiteral] -> a) -> RomanStyle -> Ligate -> i -> Maybe a
_romanNumber [RomanLiteral] -> Text
romanNumeral
romanNumber' ::
Integral i =>
RomanStyle ->
Ligate ->
i ->
Maybe Text
romanNumber' :: forall i. Integral i => RomanStyle -> Ligate -> i -> Maybe Text
romanNumber' = ([RomanLiteral] -> Text) -> RomanStyle -> Ligate -> i -> Maybe Text
forall i a.
Integral i =>
([RomanLiteral] -> a) -> RomanStyle -> Ligate -> i -> Maybe a
_romanNumber [RomanLiteral] -> Text
romanNumeral'
romanNumberCase ::
Integral i =>
LetterCase ->
RomanStyle ->
Ligate ->
i ->
Maybe Text
romanNumberCase :: forall i.
Integral i =>
LetterCase -> RomanStyle -> Ligate -> i -> Maybe Text
romanNumberCase = (RomanStyle -> Ligate -> i -> Maybe Text)
-> (RomanStyle -> Ligate -> i -> Maybe Text)
-> LetterCase
-> RomanStyle
-> Ligate
-> i
-> Maybe Text
forall a. a -> a -> LetterCase -> a
splitLetterCase RomanStyle -> Ligate -> i -> Maybe Text
forall i. Integral i => RomanStyle -> Ligate -> i -> Maybe Text
romanNumber RomanStyle -> Ligate -> i -> Maybe Text
forall i. Integral i => RomanStyle -> Ligate -> i -> Maybe Text
romanNumber'