
I am trying to write a function that will covert either an integer or an int into a list containing its digits. ex. toIntegralList 123 -> [1,2,3] I have written the following definition that tries to use read to generically cast a string value to an Integral type that is the same as the Integral passed in: toIntegralList :: (Integral a) => a -> [a] toIntegralList x = map (\c -> read [c] :: a) (show x) I understand it would be very simple to just create two functions, one that converts an Int and one that converts an Integer, however I was wondering if there were any way to accomplish what I am trying to do here. Thanks In Advance, Bryan

I assume the problem is that the function doesn't compile. This should work:
toIntegralList :: (Read a, Show a) => a -> [a] toIntegralList x = map (\c -> read [c]) (show x) This adds the required Read and Show instances, which are necessary because of the read and show functions, respectively. Also note that I have omitted your extra type annotation, which also causes an compile error.
The problem with this functions is that you can use it on a lot of stuff that isn't a number, and you'll get a runtime read error, to remedy this, just reinsert the Integral type class requirement:
toIntegralList :: (Integral a, Read a, Show a) => a -> [a] toIntegralList x = map (\c -> read [c]) (show x)
Hope this helps, Paul William Gilbert wrote:
I am trying to write a function that will covert either an integer or an int into a list containing its digits.
ex. toIntegralList 123 -> [1,2,3]
I have written the following definition that tries to use read to generically cast a string value to an Integral type that is the same as the Integral passed in:
toIntegralList :: (Integral a) => a -> [a] toIntegralList x = map (\c -> read [c] :: a) (show x)
I understand it would be very simple to just create two functions, one that converts an Int and one that converts an Integer, however I was wondering if there were any way to accomplish what I am trying to do here.
Thanks In Advance, Bryan _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

William Gilbert
I am trying to write a function that will covert either an integer or an int into a list containing its digits.
ex. toIntegralList 123 -> [1,2,3]
I have written the following definition that tries to use read to generically cast a string value to an Integral type that is the same as the Integral passed in:
toIntegralList :: (Integral a) => a -> [a] toIntegralList x = map (\c -> read [c] :: a) (show x)
I understand it would be very simple to just create two functions, one that converts an Int and one that converts an Integer, however I was wondering if there were any way to accomplish what I am trying to do here.
Of course you can use read and show for that, but personally I find it more appropriate to write the algorithm yourself. It will be faster and give you a much more useful digit ordering, namely starting with the least significant digit: toDigits :: Integral i => i -> i -> [i] toDigits base = takeWhile (>0) . map (`rem` base) . iterate (`div` base) toDecimalDigits :: Integral i => i -> [i] toDecimalDigits = toDigits 10 fromDigits :: Num a => a -> [a] -> a fromDigits base = foldr (\d c -> base*c + d) 0 fromDecimalDigits :: Num a => [a] -> a fromDecimalDigits = fromDigits 10 Greets, Ertugrul. -- nightmare = unsafePerformIO (getWrongWife >>= sex) http://blog.ertes.de/

Hi Bryan, I think that it isn't a very good idea to use `read/show` to do some numeric computations. You can use standard functions `div` and `mod` which work with any Integrals. digits :: (Integral a) => a -> [a] digits 0 = [] digits n = digits (n `div` 10) ++ [n `mod` 10] This code behaves differently on 0 then your one (also on negative numbers). You can fix it easily, and moreover, you may want to use `divMod` and some accumulator to improve efficiency: digits2 :: (Integral a) => a -> [a] digits2 0 = [0] digits2 n = digits2' n [] where digits2' 0 acc = acc digits2' n acc = let (r,d) = divMod n 10 in digits2' r (d:acc) I hope I understood well what you were asking about ;-) Btw, to make your code working I needed to write it as: toIntegralList :: (Read a, Integral a) => a -> [a] toIntegralList (x :: a) = map (\c -> read [c] :: a) (show x) Sincerely, Jan. On Thu, May 28, 2009 at 11:50:36AM -0400, William Gilbert wrote:
I am trying to write a function that will covert either an integer or an int into a list containing its digits.
ex. toIntegralList 123 -> [1,2,3]
I have written the following definition that tries to use read to generically cast a string value to an Integral type that is the same as the Integral passed in:
toIntegralList :: (Integral a) => a -> [a] toIntegralList x = map (\c -> read [c] :: a) (show x)
I understand it would be very simple to just create two functions, one that converts an Int and one that converts an Integer, however I was wondering if there were any way to accomplish what I am trying to do here.
Thanks In Advance, Bryan _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
-- Heriot-Watt University is a Scottish charity registered under charity number SC000278.

Hi William, I would also strongly success not to make the detour using read and show. Keep things simple. Here is my suggestion: toDigit x = case f x of (0,b) -> [b] (a,b) -> toDigit a ++ [b] f = \x -> (x `quot` 10, x `mod` 10) Best, Thomas William Gilbert wrote:
I am trying to write a function that will covert either an integer or an int into a list containing its digits.
ex. toIntegralList 123 -> [1,2,3]
I have written the following definition that tries to use read to generically cast a string value to an Integral type that is the same as the Integral passed in:
toIntegralList :: (Integral a) => a -> [a] toIntegralList x = map (\c -> read [c] :: a) (show x)
I understand it would be very simple to just create two functions, one that converts an Int and one that converts an Integer, however I was wondering if there were any way to accomplish what I am trying to do here.
Thanks In Advance, Bryan _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

On Thu, 2009-05-28 at 13:05 -0400, Thomas Friedrich wrote:
toDigit x = case f x of (0,b) -> [b] (a,b) -> toDigit a ++ [b]
f = \x -> (x `quot` 10, x `mod` 10)
Your function f is almost the same as divMod in Prelude. Also, using a lambda function seems odd; this is simpler:
f x = (x `quot` 10, x `mod` 10)
Anyways, because that's essentially just divMod, toDigit can be simplified thusly:
toDigit x = case x `divMod` 10 of (0, b) -> [b] (a, b) -> toDigit a ++ [b]
Jeff Wheeler

Jeff Wheeler
f = \x -> (x `quot` 10, x `mod` 10)
Your function f is almost the same as divMod in Prelude. Also, using a lambda function seems odd; this is simpler:
f x = (x `quot` 10, x `mod` 10)
Hmm, simplicity. f = (`quot` 10) &&& (`mod` 10) SCNR. Greets, Ertugrul. -- nightmare = unsafePerformIO (getWrongWife >>= sex) http://blog.ertes.de/
participants (6)
-
Ertugrul Soeylemez
-
Jan Jakubuv
-
Jeff Wheeler
-
Paul Visschers
-
Thomas Friedrich
-
William Gilbert