IO () and IO [()]

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://www.personal.soton.ac.uk/pocm PhD Student @ ECS University of Southampton, UK Sponsor ECS runners - Action against Hunger: http://www.justgiving.com/ecsrunslikethewind

Hi
I would like to know if in fact there's any difference in practice between (), [()], i.e. if in practice the difference matters.
Usually, not so much. A lot of Monad functions have _ variants, i.e. mapM and mapM_. If you don't need the result, use the mapM_ version, as it will run faster and not space/stack leak in some circumstances.
By the way, as a consequence can you possibly get IO (()) or IO ([()]) and are these all different from each other?
Read () as Unit. You can't put anything in a Unit, even if the bracket notation subtly suggests you can. You can have IO Unit and IO [Unit], but not IO Un(Unit)it or IO Un([Unit])it. The two types you gave can't exist. Thanks Neil

On Mon, 10 Mar 2008, Neil Mitchell wrote:
I would like to know if in fact there's any difference in practice between (), [()], i.e. if in practice the difference matters.
Usually, not so much. A lot of Monad functions have _ variants, i.e. mapM and mapM_. If you don't need the result, use the mapM_ version, as it will run faster and not space/stack leak in some circumstances.
In my opinion, mapM_ and sequence_ are in the wrong class, because they do not need much of Monads, or even Functors. They could well live, say, in Data.Monoid class. However, it's hard to integrate that in a hierarchy of type classes. instance Monoid a => Monoid (M a) where mempty = return mempty mappend = liftM2 mappend where M is a monad type.

Henning Thielemann wrote:
On Mon, 10 Mar 2008, Neil Mitchell wrote:
I would like to know if in fact there's any difference in practice between (), [()], i.e. if in practice the difference matters.
Usually, not so much. A lot of Monad functions have _ variants, i.e. mapM and mapM_. If you don't need the result, use the mapM_ version, as it will run faster and not space/stack leak in some circumstances.
In my opinion, mapM_ and sequence_ are in the wrong class, because they do not need much of Monads, or even Functors. They could well live, say, in Data.Monoid class. However, it's hard to integrate that in a hierarchy of type classes.
instance Monoid a => Monoid (M a) where mempty = return mempty mappend = liftM2 mappend
where M is a monad type.
Surely you mean to say: instance Monad m => Monoid (m ()) where mempty = return () mappend = (>>) ? That is the instance which is consistent with your text "don't need much of monads". Then sequence_ becomes mconcat, and mapM_ becomes foldMap (from Data.Foldable), or more directly mconcat $ map ... See also Control.Applicative, for things which can be sequence_'ed or even sequence'd without being Monads. Jules

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
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://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@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

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*
mailto:pocm@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@haskell.org mailto:Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
------------------------------------------------------------------------
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hi
I understand the lack of distinction between a unit type and a 0-tuple, since they are isomorphic.
It's more we pronounce 0-tuple as unit, they are identical.
But it is strange that there is no 1-tuple, since _|_ and the 1-tuple (_|_) would be different things entirely, no?
Yes, it would be useful, but what would the syntax be? (x) already means something else - namely grouping. Yhc defines both Tuple1 and _E, both of which are the 1-tuple. I'd like it if there was a standard definition Box for the 1-tuple, in the base libraries. Thanks Neil

In Python the syntax to create 1-tuple is *(element,)*. Note the ",". It's
not the most beautiful but is acceptable.
Christopher Skrzętnicki
On Tue, Mar 11, 2008 at 12:24 AM, Neil Mitchell
Hi
I understand the lack of distinction between a unit type and a 0-tuple, http://www.haskell.org/pipermail/ since they are isomorphic.
It's more we pronounce 0-tuple as unit, they are identical.
But it is strange that there is no 1-tuple, since _|_ and the 1-tuple (_|_) would be different things entirely, no?
Yes, it would be useful, but what would the syntax be? (x) already means something else - namely grouping. Yhc defines both Tuple1 and _E, both of which are the 1-tuple. I'd like it if there was a standard definition Box for the 1-tuple, in the base libraries.

Hi
In Python the syntax to create 1-tuple is (element,). Note the ",". It's not the most beautiful but is acceptable.
But in Haskell we can write tuples in infix syntax, i.e. (,) is the 2 tuple. Unfortunately, this syntax doesn't suggest anything for the infix 1-tuple, and clashes with the 2-tuple a bit. Thanks Neil

2008/3/10 Krzysztof Skrzętnicki
In Python the syntax to create 1-tuple is (element,). Note the ",". It's not the most beautiful but is acceptable.
But that syntax ought to be for tuple sections. Is there a good reason that Haskell doesn't have tuple sections? ("hello", "world") :: (String,String) (,) :: a -> b -> (a,b) ("hello",) :: a -> (String,a) -- I want this (,"hello") :: a -> (a, String) -- this too On an unrelated note, the only time I can recall where I wanted a "Box" data type was when I was doing evil with the garbage collector. Can someone show me an example of when they would use a Box? Not that it's hard to make yourself... data Box a = Box a Luke

Yes, I wish Haskell had a 1-tuple. The obvious syntax is already taken, but
I could accept something different, like 'One a'.
On Mon, Mar 10, 2008 at 11:17 PM, Dan Weston
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
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*
mailto:pocm@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
Rodrigo Queiro wrote: 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@haskell.org mailto:Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
------------------------------------------------------------------------
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Lennart Augustsson wrote:
Yes, I wish Haskell had a 1-tuple. The obvious syntax is already taken, but I could accept something different, like 'One a'.
Python's one-tuple syntax is (1,). The obvious difficulty with adapting this notation to Haskell lies in how one might write the constructor as a section.

I don't think writing (1,) is an option for Haskell, it looks like a section
(and should be one).
On Wed, Mar 12, 2008 at 9:13 PM, Bryan O'Sullivan
Lennart Augustsson wrote:
Yes, I wish Haskell had a 1-tuple. The obvious syntax is already taken, but I could accept something different, like 'One a'.
Python's one-tuple syntax is (1,). The obvious difficulty with adapting this notation to Haskell lies in how one might write the constructor as a section.

On Mon, Mar 10, 2008 at 10:11:33PM +0000, Paulo J. Matos wrote:
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?
Note that there exists mapM_ which discards the return values. mapM_ :: (Monad m) => (a -> m b) -> [a] -> m () -- Lars Viklund | zao@acc.umu.se

On Mon, Mar 10, 2008 at 11:11 PM, Paulo J. Matos
outputLines i = mapM (putStrLn . show) (take i $ iterate ((+) 1) 1)
However, this is in fact outputLines :: Int -> IO [()]
As others suggested you can use mapM_ Furthermore, you can simplify it a bit with some syntactic sugar outputLines i = mapM_ (putStrLn . show) [1..i] BTW, considering how often is (putStrLn.show) used, it is surprising that there is no Ln variant for print (just like it happens with putStr and putStrLn)

On Mon, Mar 10, 2008 at 7:34 PM, Alfonso Acosta
BTW, considering how often is (putStrLn.show) used, it is surprising that there is no Ln variant for print (just like it happens with putStr and putStrLn)
Actually,
print = putStrLn . show
so
outputLines i = mapM_ print [1..i]
-- Felipe.

Am Montag, 10. März 2008 23:34 schrieb Alfonso Acosta:
On Mon, Mar 10, 2008 at 11:11 PM, Paulo J. Matos
wrote: outputLines i = mapM (putStrLn . show) (take i $ iterate ((+) 1) 1)
However, this is in fact outputLines :: Int -> IO [()]
As others suggested you can use mapM_
Furthermore, you can simplify it a bit with some syntactic sugar
outputLines i = mapM_ (putStrLn . show) [1..i]
BTW, considering how often is (putStrLn.show) used, it is surprising that there is no Ln variant for print (just like it happens with putStr and putStrLn)
But print is (putStrLn . show), so what may be missing is (putStr . show).

On Mon, Mar 10, 2008 at 3:11 PM, Paulo J. Matos
I would like to know if in fact there's any difference in practice between (), [()], i.e. if in practice the difference matters.
The type [()] is very similar to the type Integer and it's quite different from () because you can count with it. For example: main = do count <- mapM print ["Hello","World"] print $ "You printed " ++ show (length count) ++ " lines" You can't do that with a IO (). Not that I actually recommend doing this. -- Dan

At Mon, 10 Mar 2008 22:11:33 +0000, Paulo J. Matos wrote:
I would like to know if in fact there's any difference in practice between (), [()], i.e. if in practice the difference matters.
Well, you could do something like this: outputLines :: Int -> IO [()] outputLines i = mapM (putStrLn . show) (take (i*2) $ iterate ((+) 1) 1) main = do l <- outputLines 10 putStrLn $ "I putted " ++ show (length l) ++ " lines." which is not very exciting in this case. But I think I may have done something similar in real code. j.
participants (16)
-
Alfonso Acosta
-
Bryan O'Sullivan
-
Dan Piponi
-
Dan Weston
-
Daniel Fischer
-
Felipe Lessa
-
Henning Thielemann
-
Jeremy Shaw
-
Jules Bean
-
Krzysztof Skrzętnicki
-
Lars Viklund
-
Lennart Augustsson
-
Luke Palmer
-
Neil Mitchell
-
Paulo J. Matos
-
Rodrigo Queiro