Why can't I print an IO Integer?

Here's a small program that replicates the compilation issue I'm seeing: import qualified System.Posix.Files get_size :: String -> IO Integer get_size filename = do file_status <- System.Posix.Files.getFileStatus filename let file_size = System.Posix.Files.fileSize file_status let integer_file_size = fromIntegral file_size return integer_file_size main :: IO () main = do let filenames = ["/etc/services"] let sizes = map get_size filenames mapM_ print sizes The compilation error I get is: ghc -Wall --make -o stat2 stat2.hs [1 of 1] Compiling Main ( stat2.hs, stat2.o ) stat2.hs:15:11: No instance for (Show (IO Integer)) arising from a use of `print' Possible fix: add an instance declaration for (Show (IO Integer)) In the first argument of `mapM_', namely `print' In a stmt of a 'do' block: mapM_ print sizes In the expression: do { let filenames = ...; let sizes = map get_size filenames; mapM_ print sizes } make: *** [stat2] Error 1 I've googled quite a bit, and guessed quite a bit, and added type declarations some, but I'm still not converging on a solution. Why can't I print an IO Integer? Thanks! -- Dan Stromberg

Hello Dan,
`IO Integer` is something that, when executed, returns and `Integer` and
there is no instance of `Show` for `IO Integer` as the compiler says.
You have to run the computations that will return the numbers and then
print them, like so:
main :: IO ()
main = do
let filenames = ["/etc/services"]
let ioSizes = map get_size filenames :: [IO Integer]
sizes <- sequence ioSizes
mapM_ print sizes
-- sequence :: Monad m => [m a] -> m [a]
One important part is the use of sequence which transforms (ioSizes :: [IO
Integer]) to `IO [Integer]` that is run and the result bound to (sizes :
[Integer]).
Hope that's clear enough to get the point :)
Petr
On Tue, Oct 20, 2015 at 5:58 PM, Dan Stromberg
Here's a small program that replicates the compilation issue I'm seeing:
import qualified System.Posix.Files
get_size :: String -> IO Integer get_size filename = do file_status <- System.Posix.Files.getFileStatus filename let file_size = System.Posix.Files.fileSize file_status let integer_file_size = fromIntegral file_size return integer_file_size
main :: IO () main = do let filenames = ["/etc/services"] let sizes = map get_size filenames mapM_ print sizes
The compilation error I get is:
ghc -Wall --make -o stat2 stat2.hs [1 of 1] Compiling Main ( stat2.hs, stat2.o )
stat2.hs:15:11: No instance for (Show (IO Integer)) arising from a use of `print' Possible fix: add an instance declaration for (Show (IO Integer)) In the first argument of `mapM_', namely `print' In a stmt of a 'do' block: mapM_ print sizes In the expression: do { let filenames = ...; let sizes = map get_size filenames; mapM_ print sizes } make: *** [stat2] Error 1
I've googled quite a bit, and guessed quite a bit, and added type declarations some, but I'm still not converging on a solution.
Why can't I print an IO Integer?
Thanks!
-- Dan Stromberg
_______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners

Please correct my inference if I'm wrong:
An IO Integer is not an integer, it's a promise to read an Integer later.
The "sequence" function tells the runtime it's time to make good on that
promise.
Sound about right?
Thanks!
On Tue, Oct 20, 2015 at 9:15 AM, Petr Vápenka
Hello Dan,
`IO Integer` is something that, when executed, returns and `Integer` and there is no instance of `Show` for `IO Integer` as the compiler says.
You have to run the computations that will return the numbers and then print them, like so:
main :: IO () main = do let filenames = ["/etc/services"] let ioSizes = map get_size filenames :: [IO Integer] sizes <- sequence ioSizes mapM_ print sizes
-- sequence :: Monad m => [m a] -> m [a]
One important part is the use of sequence which transforms (ioSizes :: [IO Integer]) to `IO [Integer]` that is run and the result bound to (sizes : [Integer]).
Hope that's clear enough to get the point :)
Petr
On Tue, Oct 20, 2015 at 5:58 PM, Dan Stromberg
wrote: Here's a small program that replicates the compilation issue I'm seeing:
import qualified System.Posix.Files
get_size :: String -> IO Integer get_size filename = do file_status <- System.Posix.Files.getFileStatus filename let file_size = System.Posix.Files.fileSize file_status let integer_file_size = fromIntegral file_size return integer_file_size
main :: IO () main = do let filenames = ["/etc/services"] let sizes = map get_size filenames mapM_ print sizes
The compilation error I get is:
ghc -Wall --make -o stat2 stat2.hs [1 of 1] Compiling Main ( stat2.hs, stat2.o )
stat2.hs:15:11: No instance for (Show (IO Integer)) arising from a use of `print' Possible fix: add an instance declaration for (Show (IO Integer)) In the first argument of `mapM_', namely `print' In a stmt of a 'do' block: mapM_ print sizes In the expression: do { let filenames = ...; let sizes = map get_size filenames; mapM_ print sizes } make: *** [stat2] Error 1
I've googled quite a bit, and guessed quite a bit, and added type declarations some, but I'm still not converging on a solution.
Why can't I print an IO Integer?
Thanks!
-- Dan Stromberg
_______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
-- Dan Stromberg

An IO Integer is not an integer, it's a promise to read an Integer later. The "sequence" function tells the runtime it's time to make good on that promise.
Not exactly. You don't need "sequence" for a plain (IO Int), only for a list of IO actions. "sequence" just changes a "list of promises" into a "promise of a list": sequence :: (Traversable t, Monad m) => t (m a) -> m (t a) When specialized to IO and a list, the function becomes: sequence :: [IO a] -> IO [a] Also, for any f: sequence . map f === mapM f It is when you bind its result to your "main" (with "do" notation or (>>) and (>>=) operators) when it can interact with the rest of your program. You can bind it more than once, and it will be executed more than one time, like any other "IO something". Best regards, Marcin Mrotek

Using your wording, sequence makes from a `list of promises of integer` a
`promise of list of integers`.
You can get the value out of a promise using bind, ie using `<-` in do
notation as written below.
ioA :: IO Int
ioA = return 1
main :: IO ()
main = do
a <- ioA
print a
This may help: http://learnyouahaskell.com/input-and-output
On Tue, Oct 20, 2015 at 9:28 PM, Dan Stromberg
Please correct my inference if I'm wrong:
An IO Integer is not an integer, it's a promise to read an Integer later. The "sequence" function tells the runtime it's time to make good on that promise.
Sound about right?
Thanks!
On Tue, Oct 20, 2015 at 9:15 AM, Petr Vápenka
wrote: Hello Dan,
`IO Integer` is something that, when executed, returns and `Integer` and there is no instance of `Show` for `IO Integer` as the compiler says.
You have to run the computations that will return the numbers and then print them, like so:
main :: IO () main = do let filenames = ["/etc/services"] let ioSizes = map get_size filenames :: [IO Integer] sizes <- sequence ioSizes mapM_ print sizes
-- sequence :: Monad m => [m a] -> m [a]
One important part is the use of sequence which transforms (ioSizes :: [IO Integer]) to `IO [Integer]` that is run and the result bound to (sizes : [Integer]).
Hope that's clear enough to get the point :)
Petr
On Tue, Oct 20, 2015 at 5:58 PM, Dan Stromberg
wrote: Here's a small program that replicates the compilation issue I'm seeing:
import qualified System.Posix.Files
get_size :: String -> IO Integer get_size filename = do file_status <- System.Posix.Files.getFileStatus filename let file_size = System.Posix.Files.fileSize file_status let integer_file_size = fromIntegral file_size return integer_file_size
main :: IO () main = do let filenames = ["/etc/services"] let sizes = map get_size filenames mapM_ print sizes
The compilation error I get is:
ghc -Wall --make -o stat2 stat2.hs [1 of 1] Compiling Main ( stat2.hs, stat2.o )
stat2.hs:15:11: No instance for (Show (IO Integer)) arising from a use of `print' Possible fix: add an instance declaration for (Show (IO Integer)) In the first argument of `mapM_', namely `print' In a stmt of a 'do' block: mapM_ print sizes In the expression: do { let filenames = ...; let sizes = map get_size filenames; mapM_ print sizes } make: *** [stat2] Error 1
I've googled quite a bit, and guessed quite a bit, and added type declarations some, but I'm still not converging on a solution.
Why can't I print an IO Integer?
Thanks!
-- Dan Stromberg
_______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
-- Dan Stromberg
_______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners

Hello, Function "print" has type "Show a => a -> IO ()". To use it with a value of type "IO Int", you need to use (>>=), which, specialized to IO, has type "IO a -> (a -> IO b) -> IO b". "print =<< foo", if foo :: IO Int, will have type IO () and is going to print the integer from foo. In your code, though, you can use mapM instead of map: sizes <- mapM get_size filenames mapM_ print sizes Best regards, Marcin Mrotek
participants (3)
-
Dan Stromberg
-
Marcin Mrotek
-
Petr Vápenka