{- Copyright (C) 2011 Dr. Alistair Ward This program is free software: you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation, either version 3 of the License, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program. If not, see . -} {- | [@AUTHOR@] Dr. Alistair Ward [@DESCRIPTION@] Facilitates representation of 'Integral' values in alternative 'Integral' bases. -} module Factory.Math.Radix( -- * Constants -- decodes, -- digits, -- encodes, -- * Functions digitSum, digitalRoot, fromBase, toBase ) where import Data.Array((!)) import qualified Data.Array import qualified Data.Char import qualified Data.List import qualified Data.Maybe -- | Characters used to represent the digits of numbers in @(-36 <= base <= 36)@. digits :: String digits = ['0' .. '9'] ++ ['a' .. 'z'] -- | Constant random-access lookup for 'digits'. encodes :: (Data.Array.Ix index, Integral index) => Data.Array.Array index Char encodes = Data.Array.listArray (0, fromIntegral $ length digits - 1) digits -- | Constant reverse-lookup for 'digits'. decodes :: Integral i => [(Char, i)] decodes = zip digits [0 ..] {- | * Convert the specified integral decimal quantity, to an alternative base, and represent the result as a 'String'. * Both negative decimals and negative bases are permissible. * The conversion to 'Char' can only succeed where printable and intelligible characters exist to represent all digits in the chosen base; which in practice means @(-36 <= base <= 36)@. -} toBase :: (Integral base, Integral decimal) => base -> decimal -> String toBase 10 decimal = show decimal --Base unchanged. toBase _ 0 = "0" --Zero has the same representation in any base. toBase base decimal | abs base < 2 = error $ "Factory.Math.Radix.toBase:\tan arbitrary integer can't be represented in base " ++ show base | abs base > Data.List.genericLength digits = error $ "Factory.Math.Radix.toBase:\tunable to clearly represent the complete set of digits in base " ++ show base | base > 0 && decimal < 0 = '-' : map (toDigit . fromIntegral) (fromDecimal (negate decimal) []) | otherwise = (toDigit . fromIntegral) `map` fromDecimal decimal [] where fromDecimal 0 = id fromDecimal n | remainder < 0 = fromDecimal (quotient + 1) . ((remainder - fromIntegral base) :) --This can only occur when base is negative; cf. 'divMod'. | otherwise = fromDecimal quotient . (remainder :) where (quotient, remainder) = n `quotRem` fromIntegral base toDigit :: Int -> Char toDigit n | n >&< encodes = encodes ! n | otherwise = error $ "Factory.Math.Radix.toBase.toDigit:\tno suitable character-representation for integer " ++ show n where (>&<) :: Int -> Data.Array.Array Int Char -> Bool index >&< array = ($ index) `all` [(>= lower), (<= upper)] where (lower, upper) = Data.Array.bounds array {- | * Convert the 'String'-representation of a number in the specified base, to a decimal integer. * Both negative numbers and negative bases are permissible. -} fromBase :: (Integral base, Integral decimal, Read decimal) => base -> String -> decimal fromBase 10 s = read s --Base unchanged. fromBase _ "0" = 0 --Zero has the same representation in any base. fromBase base s | abs base < 2 = error $ "Factory.Math.Radix.fromBase:\tan arbitrary integer can't be represented in base " ++ show base | abs base > Data.List.genericLength digits = error $ "Factory.Math.Radix.fromBase:\tunable to clearly represent the complete set of digits in base " ++ show base | base > 0 && head s == '-' = negate . fromBase base $ tail s --Recurse. | otherwise = Data.List.foldl' (\l -> ((l * fromIntegral base) +) . fromIntegral . fromDigit) 0 s where fromDigit :: Char -> Int fromDigit c = case c `lookup` decodes of Just i | i >= abs (fromIntegral base) -> error $ "Factory.Math.Radix.fromBase.fromDigit:\tillegal char " ++ show c ++ ", for base " ++ show base | otherwise -> i _ -> error $ "Factory.Math.Radix.fromBase.fromDigit:\tunrecognised char " ++ show c {- | * . * . -} digitSum :: (Integral base, Integral decimal) => base -> decimal -> decimal digitSum 10 = fromIntegral . foldr ((+) . Data.Char.digitToInt) 0 . show digitSum base = sum . Data.Maybe.mapMaybe (`lookup` decodes) . toBase base -- | . digitalRoot :: Integral decimal => decimal -> decimal digitalRoot = head . dropWhile (> 9) . iterate (digitSum (10 :: Int))