Alternative: you can fool many people some time, and some people many time, but...

Hi guys, I'm playing with the mysterious "some" and "many" from Control.Applicative. If I try: many $ Just 1 It just loops, I understand why: http://stackoverflow.com/questions/18108608/what-are-alterna tives-some-and-many-useful-for It seems that some and many are usually used in a context where something is consumed, and can be depleted, so the loop ends. But why doesn't this terminates? take 3 $ many $ Just 1 It's a recursive call, but the construction of the result should be lazy...

take 3 $ many $ Just 1
doesn't type check. Did you mean this?
take 3 <$> (many $ Just 1)
I think this may have something to do with the default definition of
many in the definition of Alternative
http://hackage.haskell.org/package/base-4.9.0.0/docs/src/GHC.Base.html#Alter...:
many :: f http://hackage.haskell.org/package/base-4.9.0.0/docs/src/GHC.Base.html#local...
a http://hackage.haskell.org/package/base-4.9.0.0/docs/src/GHC.Base.html#local...
-> f http://hackage.haskell.org/package/base-4.9.0.0/docs/src/GHC.Base.html#local...
[a http://hackage.haskell.org/package/base-4.9.0.0/docs/src/GHC.Base.html#local...]many
http://hackage.haskell.org/package/base-4.9.0.0/docs/src/GHC.Base.html#many
v http://hackage.haskell.org/package/base-4.9.0.0/docs/src/GHC.Base.html#local...
= many_v http://hackage.haskell.org/package/base-4.9.0.0/docs/src/GHC.Base.html#local...
where many_v
http://hackage.haskell.org/package/base-4.9.0.0/docs/src/GHC.Base.html#local...
= some_v http://hackage.haskell.org/package/base-4.9.0.0/docs/src/GHC.Base.html#local...
<|> http://hackage.haskell.org/package/base-4.9.0.0/docs/src/GHC.Base.html#%3C%7...
pure http://hackage.haskell.org/package/base-4.9.0.0/docs/src/GHC.Base.html#pure
[] some_v http://hackage.haskell.org/package/base-4.9.0.0/docs/src/GHC.Base.html#local...
= (fmap http://hackage.haskell.org/package/base-4.9.0.0/docs/src/GHC.Base.html#fmap
(:) v http://hackage.haskell.org/package/base-4.9.0.0/docs/src/GHC.Base.html#local...)
<*> http://hackage.haskell.org/package/base-4.9.0.0/docs/src/GHC.Base.html#%3C%2...
many_v http://hackage.haskell.org/package/base-4.9.0.0/docs/src/GHC.Base.html#local...
many_v and some_v are mutually recursive functions, and it may be that this
prevents the thunks from being made available to take in some way. I'm
really not sure though, this is just an idea about why this is not quite
the same as (take $ repeat 1)
On Thu, Sep 29, 2016 at 3:51 PM Corentin Dupont
Hi guys, I'm playing with the mysterious "some" and "many" from Control.Applicative. If I try:
many $ Just 1
It just loops, I understand why:
http://stackoverflow.com/questions/18108608/what-are-alternatives-some-and-m... It seems that some and many are usually used in a context where something is consumed, and can be depleted, so the loop ends.
But why doesn't this terminates?
take 3 $ many $ Just 1
It's a recursive call, but the construction of the result should be lazy...
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

On Thu, Sep 29, 2016 at 4:28 PM, Jake
I think this may have something to do with the default definition of many in the definition of Alternative http://hackage.haskell.org/package/base-4.9.0.0/docs/src/GHC.Base.html#Alter...:
many :: f http://hackage.haskell.org/package/base-4.9.0.0/docs/src/GHC.Base.html#local... a http://hackage.haskell.org/package/base-4.9.0.0/docs/src/GHC.Base.html#local... -> f http://hackage.haskell.org/package/base-4.9.0.0/docs/src/GHC.Base.html#local... [a http://hackage.haskell.org/package/base-4.9.0.0/docs/src/GHC.Base.html#local...]many http://hackage.haskell.org/package/base-4.9.0.0/docs/src/GHC.Base.html#many v http://hackage.haskell.org/package/base-4.9.0.0/docs/src/GHC.Base.html#local... = many_v http://hackage.haskell.org/package/base-4.9.0.0/docs/src/GHC.Base.html#local... where many_v http://hackage.haskell.org/package/base-4.9.0.0/docs/src/GHC.Base.html#local... = some_v http://hackage.haskell.org/package/base-4.9.0.0/docs/src/GHC.Base.html#local... <|> http://hackage.haskell.org/package/base-4.9.0.0/docs/src/GHC.Base.html#%3C%7... pure http://hackage.haskell.org/package/base-4.9.0.0/docs/src/GHC.Base.html#pure [] some_v http://hackage.haskell.org/package/base-4.9.0.0/docs/src/GHC.Base.html#local... = (fmap http://hackage.haskell.org/package/base-4.9.0.0/docs/src/GHC.Base.html#fmap (:) v http://hackage.haskell.org/package/base-4.9.0.0/docs/src/GHC.Base.html#local...) <*> http://hackage.haskell.org/package/base-4.9.0.0/docs/src/GHC.Base.html#%3C%2... many_v http://hackage.haskell.org/package/base-4.9.0.0/docs/src/GHC.Base.html#local...
many_v and some_v are mutually recursive functions, and it may be that this prevents the thunks from being made available to take in some way. I'm really not sure though, this is just an idea about why this is not quite the same as (take $ repeat 1)
The problem is that many is creating an infinite sum that’s nested to the
left. So you’re trying to compute
(((… <|> Just [1,1,1]) <|> Just [1,1]) <|> Just [1]) <|> Just 1
which will never terminate because Maybe is strict in the first argument to
<|>.
As a practical matter, the Alternative instance for Maybe should probably
be changed to either call error or return Just (repeat v).
Similarly, we should probably flip the order for many in the instance for
[].
--
Dave Menendez

The type of the last part of the expression is: many $ Just 1 :: Num a => Maybe [a] So in order to be able to return the “Just” constructor which inspected by the application of (take 3 <$>) we have somehow to know for sure that all the <*> executions will indeed see a “Just” in both of their arguments. This forces more and more evaluations. Doaitse
Op 29 sep. 2016, om 22:28 heeft Jake
het volgende geschreven: take 3 $ many $ Just 1
doesn't type check. Did you mean this?
take 3 <$> (many $ Just 1) I think this may have something to do with the default definition of many in the definition of Alternative http://hackage.haskell.org/package/base-4.9.0.0/docs/src/GHC.Base.html#Alter...: many :: f http://hackage.haskell.org/package/base-4.9.0.0/docs/src/GHC.Base.html#local... a http://hackage.haskell.org/package/base-4.9.0.0/docs/src/GHC.Base.html#local... -> f http://hackage.haskell.org/package/base-4.9.0.0/docs/src/GHC.Base.html#local... [a http://hackage.haskell.org/package/base-4.9.0.0/docs/src/GHC.Base.html#local...] many http://hackage.haskell.org/package/base-4.9.0.0/docs/src/GHC.Base.html#many <>v http://hackage.haskell.org/package/base-4.9.0.0/docs/src/GHC.Base.html#local... = many_v http://hackage.haskell.org/package/base-4.9.0.0/docs/src/GHC.Base.html#local... <> where <> many_v http://hackage.haskell.org/package/base-4.9.0.0/docs/src/GHC.Base.html#local... = some_v http://hackage.haskell.org/package/base-4.9.0.0/docs/src/GHC.Base.html#local... <|> http://hackage.haskell.org/package/base-4.9.0.0/docs/src/GHC.Base.html#%3C%7... pure http://hackage.haskell.org/package/base-4.9.0.0/docs/src/GHC.Base.html#pure [] <> some_v http://hackage.haskell.org/package/base-4.9.0.0/docs/src/GHC.Base.html#local... = (fmap http://hackage.haskell.org/package/base-4.9.0.0/docs/src/GHC.Base.html#fmap (:) v http://hackage.haskell.org/package/base-4.9.0.0/docs/src/GHC.Base.html#local...) <*> http://hackage.haskell.org/package/base-4.9.0.0/docs/src/GHC.Base.html#%3C%2... many_v http://hackage.haskell.org/package/base-4.9.0.0/docs/src/GHC.Base.html#local... many_v and some_v are mutually recursive functions, and it may be that this prevents the thunks from being made available to take in some way. I'm really not sure though, this is just an idea about why this is not quite the same as (take $ repeat 1)
On Thu, Sep 29, 2016 at 3:51 PM Corentin Dupont
mailto:corentin.dupont@gmail.com> wrote: Hi guys, I'm playing with the mysterious "some" and "many" from Control.Applicative. If I try: many $ Just 1
It just loops, I understand why: http://stackoverflow.com/questions/18108608/what-are-alternatives-some-and-m... http://stackoverflow.com/questions/18108608/what-are-alternatives-some-and-m... It seems that some and many are usually used in a context where something is consumed, and can be depleted, so the loop ends.
But why doesn't this terminates?
take 3 $ many $ Just 1
It's a recursive call, but the construction of the result should be lazy...
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post. _______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

Thanks for the replies... What I'm trying to do is a simple input system: query :: IO (Maybe String) query = do putStrLn "Enter text or press q:" r <- getLine return $ if r == "q" then Nothing else Just r This will ask an input to the user which is returned, unless "q" is pressed. I want to repeat this query "some" or "many" times: main = do qs <- some $ query -- qs <- many $ query putStrLn qs This should ask the query multiple times until "q" is pressed. The type of qs is Maybe [String]. The expected result is that with "some", returning zero results will not be permitted, while with "many" it is. Probably I should defined a newtype for IO Maybe: data IOMaybe a = IOMaybe {getIOMaybe :: IO (Maybe a)} And define all the instances. Or use Data.Fucntor.Compose: type IOMaybe = Compose IO Maybe On Thu, Sep 29, 2016 at 11:15 PM, Doaitse Swierstra < doaitse.swierstra@gmail.com> wrote:
The type of the last part of the expression is:
many $ Just 1 :: Num a => Maybe [a]
So in order to be able to return the “Just” constructor which inspected by the application of (take 3 <$>) we have somehow to know for sure that all the <*> executions will indeed see a “Just” in both of their arguments. This forces more and more evaluations.
Doaitse
Op 29 sep. 2016, om 22:28 heeft Jake
het volgende geschreven: take 3 $ many $ Just 1
doesn't type check. Did you mean this?
take 3 <$> (many $ Just 1)
I think this may have something to do with the default definition of many in the definition of Alternative http://hackage.haskell.org/package/base-4.9.0.0/docs/src/GHC.Base.html#Alter...:
many :: f http://hackage.haskell.org/package/base-4.9.0.0/docs/src/GHC.Base.html#local... a http://hackage.haskell.org/package/base-4.9.0.0/docs/src/GHC.Base.html#local... -> f http://hackage.haskell.org/package/base-4.9.0.0/docs/src/GHC.Base.html#local... [a http://hackage.haskell.org/package/base-4.9.0.0/docs/src/GHC.Base.html#local...]many http://hackage.haskell.org/package/base-4.9.0.0/docs/src/GHC.Base.html#many v http://hackage.haskell.org/package/base-4.9.0.0/docs/src/GHC.Base.html#local... = many_v http://hackage.haskell.org/package/base-4.9.0.0/docs/src/GHC.Base.html#local... where many_v http://hackage.haskell.org/package/base-4.9.0.0/docs/src/GHC.Base.html#local... = some_v http://hackage.haskell.org/package/base-4.9.0.0/docs/src/GHC.Base.html#local... <|> http://hackage.haskell.org/package/base-4.9.0.0/docs/src/GHC.Base.html#%3C%7... pure http://hackage.haskell.org/package/base-4.9.0.0/docs/src/GHC.Base.html#pure [] some_v http://hackage.haskell.org/package/base-4.9.0.0/docs/src/GHC.Base.html#local... = (fmap http://hackage.haskell.org/package/base-4.9.0.0/docs/src/GHC.Base.html#fmap (:) v http://hackage.haskell.org/package/base-4.9.0.0/docs/src/GHC.Base.html#local...) <*> http://hackage.haskell.org/package/base-4.9.0.0/docs/src/GHC.Base.html#%3C%2... many_v http://hackage.haskell.org/package/base-4.9.0.0/docs/src/GHC.Base.html#local...
many_v and some_v are mutually recursive functions, and it may be that this prevents the thunks from being made available to take in some way. I'm really not sure though, this is just an idea about why this is not quite the same as (take $ repeat 1)
On Thu, Sep 29, 2016 at 3:51 PM Corentin Dupont
wrote: Hi guys, I'm playing with the mysterious "some" and "many" from Control.Applicative. If I try:
many $ Just 1
It just loops, I understand why: http://stackoverflow.com/questions/18108608/what-are- alternatives-some-and-many-useful-for It seems that some and many are usually used in a context where something is consumed, and can be depleted, so the loop ends.
But why doesn't this terminates?
take 3 $ many $ Just 1
It's a recursive call, but the construction of the result should be lazy...
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
participants (4)
-
Corentin Dupont
-
David Menendez
-
Doaitse Swierstra
-
Jake