{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-}
module Text.Numeral.Roman
(
NumeralConfig
, mkNumConfig
, convertTo
, convertFrom
, modernRoman
, toRoman
, fromRoman
) where
import Control.Monad (mzero)
import Data.Function (on)
import Data.List (sortBy)
import qualified Data.Text as T (Text, null, stripPrefix)
import Data.Text.Internal.Builder
import qualified Data.Text.Lazy as TL (toStrict)
data NumeralConfig n = NC
{
forall n. NumeralConfig n -> Text
ncZero :: T.Text
, forall n. NumeralConfig n -> [(Text, n)]
ncTable :: [(T.Text, n)]
}
mkNumConfig :: (Ord n, Num n)
=> T.Text
-> T.Text
-> [(T.Text, n)]
-> NumeralConfig n
mkNumConfig :: forall n.
(Ord n, Num n) =>
Text -> Text -> [(Text, n)] -> NumeralConfig n
mkNumConfig Text
z Text
o [(Text, n)]
tab =
NC { ncZero :: Text
ncZero = Text
z, ncTable :: [(Text, n)]
ncTable = forall a. (a -> a -> Ordering) -> [a] -> [a]
sortBy (forall a b c. (a -> b -> c) -> b -> a -> c
flip forall a. Ord a => a -> a -> Ordering
compare forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` forall a b. (a, b) -> b
snd) ((Text
o, n
1) forall a. a -> [a] -> [a]
: [(Text, n)]
tab) }
convertTo :: (Ord n, Num n) => NumeralConfig n -> n -> T.Text
convertTo :: forall n. (Ord n, Num n) => NumeralConfig n -> n -> Text
convertTo NumeralConfig n
nc n
n | n
n forall a. Eq a => a -> a -> Bool
== n
0 = forall n. NumeralConfig n -> Text
ncZero NumeralConfig n
nc
| Bool
otherwise = Text -> Text
TL.toStrict forall a b. (a -> b) -> a -> b
$ Builder -> Text
toLazyText forall a b. (a -> b) -> a -> b
$ forall {t}. (Ord t, Num t) => t -> [(Text, t)] -> Builder
go n
n forall a b. (a -> b) -> a -> b
$ forall n. NumeralConfig n -> [(Text, n)]
ncTable NumeralConfig n
nc
where
go :: t -> [(Text, t)] -> Builder
go t
_ [] = forall a. HasCallStack => [Char] -> a
error [Char]
"Roman.convertTo: out of symbols (BUG)"
go t
i tab :: [(Text, t)]
tab@(~(Text
sym, t
val) : [(Text, t)]
ts) | t
i forall a. Ord a => a -> a -> Bool
<= t
0 = forall a. Monoid a => a
mempty
| t
i forall a. Ord a => a -> a -> Bool
>= t
val = Text -> Builder
fromText Text
sym forall a. Semigroup a => a -> a -> a
<> t -> [(Text, t)] -> Builder
go (t
i forall a. Num a => a -> a -> a
- t
val) [(Text, t)]
tab
| Bool
otherwise = t -> [(Text, t)] -> Builder
go t
i [(Text, t)]
ts
convertFrom :: (Ord n, Num n) => NumeralConfig n -> T.Text -> Maybe n
convertFrom :: forall n. (Ord n, Num n) => NumeralConfig n -> Text -> Maybe n
convertFrom NumeralConfig n
nc Text
s
| forall n. NumeralConfig n -> Text
ncZero NumeralConfig n
nc forall a. Eq a => a -> a -> Bool
== Text
s = forall (m :: * -> *) a. Monad m => a -> m a
return n
0
| Bool
otherwise = do
n
n <- forall {m :: * -> *} {t}.
(MonadPlus m, Num t) =>
t -> [(Text, t)] -> Text -> m t
go n
0 (forall n. NumeralConfig n -> [(Text, n)]
ncTable NumeralConfig n
nc) Text
s
if Text
s forall a. Eq a => a -> a -> Bool
== forall n. (Ord n, Num n) => NumeralConfig n -> n -> Text
convertTo NumeralConfig n
nc n
n then forall (m :: * -> *) a. Monad m => a -> m a
return n
n else forall (m :: * -> *) a. MonadPlus m => m a
mzero
where
go :: t -> [(Text, t)] -> Text -> m t
go t
n [(Text, t)]
_ Text
x | Text -> Bool
T.null Text
x = forall (m :: * -> *) a. Monad m => a -> m a
return t
n
go t
_ [] Text
_ = forall (m :: * -> *) a. MonadPlus m => m a
mzero
go t
n tab :: [(Text, t)]
tab@((Text
sym, t
val) : [(Text, t)]
ts) Text
x =
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (t -> [(Text, t)] -> Text -> m t
go t
n [(Text, t)]
ts Text
x) (t -> [(Text, t)] -> Text -> m t
go (t
n forall a. Num a => a -> a -> a
+ t
val) [(Text, t)]
tab) forall a b. (a -> b) -> a -> b
$ Text -> Text -> Maybe Text
T.stripPrefix Text
sym Text
x
modernRoman :: (Ord n, Num n) => NumeralConfig n
modernRoman :: forall n. (Ord n, Num n) => NumeralConfig n
modernRoman = forall n.
(Ord n, Num n) =>
Text -> Text -> [(Text, n)] -> NumeralConfig n
mkNumConfig
Text
""
Text
"I"
[ (Text
"IV", n
4)
, (Text
"V" , n
5)
, (Text
"IX", n
9)
, (Text
"X" , n
10)
, (Text
"XL", n
40)
, (Text
"L" , n
50)
, (Text
"XC", n
90)
, (Text
"C" , n
100)
, (Text
"CD", n
400)
, (Text
"D" , n
500)
, (Text
"CM", n
900)
, (Text
"M" , n
1000)
]
toRoman :: (Ord n, Num n) => n -> T.Text
toRoman :: forall n. (Ord n, Num n) => n -> Text
toRoman = forall n. (Ord n, Num n) => NumeralConfig n -> n -> Text
convertTo forall n. (Ord n, Num n) => NumeralConfig n
modernRoman
fromRoman :: (Ord n, Num n) => T.Text -> Maybe n
fromRoman :: forall n. (Ord n, Num n) => Text -> Maybe n
fromRoman = forall n. (Ord n, Num n) => NumeralConfig n -> Text -> Maybe n
convertFrom forall n. (Ord n, Num n) => NumeralConfig n
modernRoman