[Haskell-cafe] IO () and IO [()]

Dan Weston westondan at imageworks.com
Mon Mar 10 19:17:04 EDT 2008


I understand the lack of distinction between a unit type and a 0-tuple, 
since they are isomorphic. But it is strange that there is no 1-tuple, 
since _|_ and the 1-tuple (_|_) would be different things entirely, no?

Dan

Rodrigo Queiro wrote:
> You're looking for mapM_
> mapM_ :: (Monad m) => (a -> m b) -> [a] -> m ()
> (see also sequence_ :: (Monad m) => [m a] -> m () )
> 
> I don't think that it is possible to have a 1-tuples, just 2 and up. () 
> is a unit rather than a 0-tuple, apparently:
> http://www.haskell.org/onlinereport/basic.html#sect6.1.4
> 
> On 10/03/2008, *Paulo J. Matos* <pocm at soton.ac.uk 
> <mailto:pocm at soton.ac.uk>> wrote:
> 
>     Hello all,
> 
>     I find it funny that IO () is different from IO [()].
>     For example, if I define a function to output some lines with mapT,
>     I would do:
>     outputLines :: Int -> IO ()
>     outputLines i = mapM (putStrLn . show) (take i $ iterate ((+) 1) 1)
> 
>     However, this is in fact
>     outputLines :: Int -> IO [()]
> 
>     I would like to know if in fact there's any difference in practice
>     between (), [()], i.e. if in practice the difference matters.
>     My first guess is that this is just a consequence of the Haskell type
>     system and so that everything fits this really needs to be like this.
>     Because
>     mapM :: (Monad m) => (a -> m b) -> [a] -> m [b]
> 
>     So I guess that it makes sense that you get IO [()] instead of IO (),
>     and adding an exception just to say that [()] == () isn't good.
>     By the way, as a consequence can you possibly get IO (()) or IO ([()])
>     and are these all different from each other?
> 
>     Cheers,
> 
>     --
>     Paulo Jorge Matos - pocm at soton.ac.uk <http://soton.ac.uk>
>     http://www.personal.soton.ac.uk/pocm
>     PhD Student @ ECS
>     University of Southampton, UK
>     Sponsor ECS runners - Action against Hunger:
>     http://www.justgiving.com/ecsrunslikethewind
>     _______________________________________________
>     Haskell-Cafe mailing list
>     Haskell-Cafe at haskell.org <mailto:Haskell-Cafe at haskell.org>
>     http://www.haskell.org/mailman/listinfo/haskell-cafe
> 
> 
> 
> ------------------------------------------------------------------------
> 
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe




More information about the Haskell-Cafe mailing list