{-# LANGUAGE UnicodeSyntax #-} -- | -- Module : Math.Dozenal -- Copyright : (C) 2014 Siddhanathan Shanmugam -- License : LGPL (see LICENSE) -- Maintainer : siddhanathan@gmail.com -- Portability : very -- -- Dozenal (Duodecimal) number system, promoting the use of base 12. -- -- The dozenal number system is superior to the decimal number system -- which is widely in use today. -- -- For information on why you should bother, see -- -- -- Example usage: -- -- @ -- module Main where -- import Math.Dozenal -- main = print $ (Dozenal "4")^2 -- @ -- -- module Math.Dozenal ( decimalToDozenal , dozenalToDecimal , Dozenal(..) ) where import Numeric (showIntAtBase, readInt) import Data.Char (intToDigit, digitToInt) import Data.Maybe (listToMaybe, fromJust) -- | Dozenal numbers need to be represented as strings since they contain more -- than 9 digits 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 -- | Convert a decimal int to a dozenal string decimalToDozenal ∷ Int → Dozenal decimalToDozenal decimal = Dozenal $ changeConvention $ showIntAtBase dozenalBase intToDigit decimal "" -- | Convert a dozenal string to a decimal integer if base conversions allow it 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