module Tests.Src.Test_Getallen where import Data.List import Data.Maybe import Control.Monad import Control.Arrow unfoldl :: (t -> Maybe (a, t)) -> t -> [a] unfoldl f x = case f x of Nothing -> [] Just (u,v) -> unfoldl f v ++ [u] -- we miss you wli -- @@ Export -- | This is a reverse of the original divMod function, it's useful with unfoldl modDiv :: Integer -> Integer -> (Integer, Integer) modDiv = \a -> (snd &&& fst).(divMod a) -- @@ Export -- | calculate the decimal representation of a number from it's components -- . -- e.g. fromDec [1,2,3] = 123 -- . -- The inverse of toDec fromDec :: [Integer] -- ^ The list of decimal numbers to combine -> Integer -- ^ The combined representation of the input fromDec = foldl' ((+).(*10)) 0 -- @@ Export -- | calculate from a decimal number it's components -- . -- e.g. toDec 123 = [1,2,3] -- . -- The inverse of fromDec toDec :: Integer -- ^ The decimal number to break into it's sub components -> [Integer] -- ^ The result from decomposing the input toDec 0 = [0] -- toDec x = (reverse.(unfoldr (\a-> let b = a `mod` 10 -- in if a == 0 then Nothing -- else Just (b,(a-b) `div` 10)))) x toDec x = unfoldl (\x -> guard (x /= 0) >> return (x `modDiv` 10)) x -- @@ Export -- | Calculate from a list of binary digits the corresponding decimal number -- . -- e.g. fromBin [1,0,1] = 5 -- . -- The inverse of toBin fromBin :: [Integer] -- ^ The list of bits to convert -> Integer -- ^ The resulting nnumber converted from binary fromBin x = fromBin' (length x - 1) x where fromBin' _ [] = 0 fromBin' c (x:xs) = x*2^c + fromBin' (c-1) xs -- @@ Export -- | Calculate from a decimal number the corresponding binary digit components -- . -- e.g. toBin 5 = [1,0,1] -- . -- The inverse of fromBin toBin :: Integer -- ^ The input number to convert to binary -> [Integer] -- ^ The list consisting of the bits of the computation toBin 0 = [0] toBin x = (unfoldl (\a -> guard (a /= 0) >> return (a `modDiv` 2))) x -- toBin = reverse.(unfoldr (\a -> if a == 0 then Nothing -- else let b = a `mod` 2 -- in Just (b,a `div` 2))) -- @@ Export = fromBaseMaybe -- | Calculate given the base and the input string with the number to encode -- the corresponding encoding. -- . -- e.g. fromBase2 2 "101" = Just 5 -- . -- This can ofcourse fail, to encode this there's a Maybe in the return type. -- . -- e.g. fromBase2 1 "101" = Nothing fromBase2 :: Int -- ^ The numerical base -> String -- ^ The input string to convert -> Maybe Int -- ^ The result of the conversion, which may have failed fromBase2 b i = fromBase' (take b $ ['0'..'9']++['a'..'z']) (length i-1) i where fromBase' _ _ [] = Just 0 fromBase' a i (x:xs) = let val = (elemIndex x a) rec_ = fromBase' a (i-1) xs in liftM2 (+) (fmap (*b^i) val) rec_ -- @@ Export -- | A version of fromBase2 (fromBaseMaybe) where failure is not encoded. -- If it fails it'll produce a crash. -- . -- see fromBase2 (fromBaseMaybe) -- . -- The inverse of toBase fromBase :: Int -- ^ The numerical base to use -> String -- ^ The number to convert -> Int -- ^ The converted number to the destination base fromBase a b= fromJust (fromBase2 a b) -- @@ Export -- | A encode a number using the given base. The result is encoded into a string. -- . -- e.g. toBase 2 5 = "101" -- . -- . The inverse of fromBase toBase :: Int -- ^ The numerical base to use -> Int -- ^ The number to convert -> String -- ^ The converted number to the destination base toBase b = toBase' (take b $ ['0'..'9']++['a'..'z']) where toBase' d i = case i of 0 -> "0" _ -> (unfoldl (\a -> guard (a /= 0) >> return ( d !! (a `mod` b),a `div` b))) i -- @@ Export -- | Calculate the result of converting the list of strings using the given base into a tuple -- . -- which contains the (input, representation) -- . -- this is done using fromBase2. Encodings that fail will simple not be included in the resulting list. -- . -- numbers 2 ["101010","10101"] = [("101010",42),("10101",21)] -- . -- numbers 2 ["12345" ,"10101"] = [("10101",21)] numbers :: Int -- ^ The numerical base -> [String] -- ^ The list of number to convert to the given base. -> [(String,Int)] -- ^ The result of the conversion, the first part of the tuple is the original input and the second part the converted number numbers b i = mapMaybe (uncurry (fmap . (,))) $ zip i (fmap (fromBase2 b) i) grayCode :: Int -> (String -> Int, Int -> String) grayCode base = (fromBase base,toBase base) lookAndSay :: Int -> [String] lookAndSay x = look (show x) where look :: String -> [String] look y = let lst = group y res = concatMap (\x->show (length x) ++ [head x]) lst in y:look res keithGetallen :: [Integer] keithGetallen = [x | x <- [10..], genNumberSec x] -- @@ Export -- | Checks to see if a number is a valid keith number. genNumberSec :: Integer -- ^ The number to check whether it's a keith number or not -> Bool -- ^ The answer to whether the number given as input is a keith number genNumberSec xo = gen no where gen x = let res = sum (drop (length x-n) x) in case compare res xo of GT -> False EQ -> True LT -> gen (x++[res]) no = toDec xo n = length no