module Math.Dozenal ( decimalToDozenal
, dozenalToDecimal
, Dozenal(..)
) where
import Numeric (showIntAtBase, readInt)
import Data.Char (intToDigit, digitToInt)
import Data.Maybe (listToMaybe, fromJust)
newtype Dozenal = Dozenal { number ∷ String } deriving (Show, Eq)
dozenalBase ∷ Int
dozenalBase = 12
dozenalCharacters ∷ String
dozenalCharacters = "0123456789ab"
changeConvention ∷ String → String
changeConvention = map changeCharacters
where changeCharacters 'X' = 'a'
changeCharacters 'E' = 'b'
changeCharacters 'a' = 'X'
changeCharacters 'b' = 'E'
changeCharacters x = x
decimalToDozenal ∷ Int → Dozenal
decimalToDozenal decimal = Dozenal
$ changeConvention
$ showIntAtBase dozenalBase intToDigit decimal ""
dozenalToDecimal ∷ String → Maybe Int
dozenalToDecimal = fmap fst
. listToMaybe
. readInt dozenalBase (`elem` dozenalCharacters) digitToInt
. changeConvention
operand = fromJust . dozenalToDecimal
instance Num Dozenal where
Dozenal a + Dozenal b = decimalToDozenal $ operand a + operand b
Dozenal a ★ Dozenal b = decimalToDozenal $ operand a ★ operand b
Dozenal a Dozenal b = decimalToDozenal $ operand a operand b
abs (Dozenal a) = decimalToDozenal $ operand a
signum (Dozenal a) = decimalToDozenal $ signum $ operand a
fromInteger i = fromInteger i