[Haskell-cafe] I really don't understand this

Jean-Marc Alliot jm at alliot.org
Tue Jan 23 19:39:40 UTC 2018


Thank you very much for your answer, but I still don't get it (I might 
be not bright enough :-))

I rewrote the program to suppress all syntactic sugar; for me, the value 
of the first argument of >>= is never used, so I can't see why it 
changes anything to put acc as the first argument or anything else (such 
as return false for example...).

I would really appreciate a pointer to a chapter of any manual or 
introduction to Haskell which would be able to explain why with acc as 
first argument of (>==) the program runs at least 2 hours (I stopped it 
after 2 hours) and with (return False) it takes less than one second, 
while the actual value of the first argument of (>>=) is meaningless.

Thanks again for answering

import qualified Data.IntMultiSet as IMS

b :: IMS.IntMultiSet
b = IMS.fromList ([1, 2, 3, 4])

search2 :: IMS.IntMultiSet -> Int -> IO Bool
search2 mynumbers nb = ins mynumbers (return False)
   where
     ins numbers acc =
       (>>=)
         acc
         (\_ ->
            IMS.fold
              (\x acc1 ->
                 let numbers2 = IMS.delete x numbers
                  in IMS.fold
                       (\y acc2 ->
                          let numbers3 = IMS.delete y numbers2
                              res = x + y
                           in if res == nb
                                then (return True)
                                else ins (IMS.insert res numbers3) acc2)
                       acc1
                       numbers2)
              acc
              numbers)

main = do
   v <- search2 b 999999999
   print v


Le 23/01/2018 à 16:03, Li-yao Xia a écrit :
> Bonjour Jean-Marc,
>
> "acc" contains the computation of the whole search up to a point. 
> Calling it once (as part of the fold) makes it grow linearly in the 
> size of the search space, but calling it twice (once more as "v <- 
> acc") makes it grow exponentially.
>
> Cordialement,
> Li-yao
>
> On 01/23/2018 08:35 AM, Jean-Marc Alliot wrote:
>> I apologize if my question is stupid, but here is a simple Haskell 
>> program which never stops.
>>
>> However, if I comment the line (which is apparently useless):
>> v<-acc
>> The program works like a charm...
>>
>> I am using GHC 8.0.2 (debian sid) and multiset 0.3.3. If anyone has 
>> an idea,  I would gladly hear it.
>>
>> Thanks in advance
>>
>> PS: don't try to understand what the program is doing; it is just the 
>> reduction to a few lines of a much larger code; I have tried to find 
>> a smaller subset which is not working "properly".
>>   PPS: The program can also be downloaded from:
>> http://www.alliot.fr/tmp/example.hs
>>
>> import qualified Data.IntMultiSet as IMS
>>
>> b :: IMS.IntMultiSet
>> b = IMS.fromList ([1, 2, 3, 4])
>>
>> search :: IMS.IntMultiSet -> Int -> IO Bool
>> search mynumbers nb = ins mynumbers (return False)
>>    where
>>      ins numbers acc = do
>>        v <- acc
>>        IMS.fold
>>          (\x acc1 ->
>>             let numbers2 = IMS.delete x numbers
>>              in IMS.fold
>>                   (\y acc2 ->
>>                      let numbers3 = IMS.delete y numbers2
>>                          res = x + y
>>                       in if res == nb
>>                            then (return True)
>>                            else ins (IMS.insert res numbers3) acc2)
>>                   acc1
>>                   numbers2)
>>          acc
>>          numbers
>>
>> main = do
>>    v <- search b 999999999
>>    print v
>> _______________________________________________
>> 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.



More information about the Haskell-Cafe mailing list