I really don't understand this

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

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.

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.

Hi, On 01/23/2018 02:39 PM, Jean-Marc Alliot wrote:
Thank you very much for your answer, but I still don't get it (I might be not bright enough :-))
Not at all! This is definitely not an obvious problem.
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...).
You can erase (acc :: IO Bool) only if acc is in fact pure (i.e., acc = return b), but how would GHC deduce such a fact? - inlining could take care of it on a case-by-case basis at each call site, but ins is recursive, which prevents inlining; - a more general solution for recursive definitions might be some kind of static analysis, that GHC doesn't do; - using Identity instead of IO, then all computations must be pure, and in fact the optimization would apply automatically as a consequence of the lazy (>>=) for Identity.
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.
I don't have any good pointers unfortunately. But it may help to expand the folds. ins {1,2,3} acc = do acc ins {1+2,3} (ins {1+3,2} (ins {2+1,3} (... (ins {3+2, 1} acc)))) For the first recursive call to ins... ins {1+2,3} acc1 = do acc1 ins {1+2+3} (ins {3+1+2} acc1) ... substitute that in the former (acc1 = ins {1+3,2} (ins {2+1,3} (... acc))) ins {1,2,3} acc = do acc (ins {1+3,2} (... acc)) ins {1+2+3} (ins {3+1+2} (ins {1+3,2} (... acc))) etc. Li-yao

First thanks again for the answer, I really appreciate. However, I am still a little bit in doubt, so I decided to write an ocaml search2 function which is almost an exact copy/paste of the Haskell function, including an IO monad implemented in ocaml (included below; I am much more fluent in caml that I have been using for 20 years than I am in Haskell, as you might have guessed). In ocaml, there is no problem at all and everything is running as I expect it to run. I can access and even print the value of acc without modifying the behaviour of the program. The main difference I am aware of is that Haskell is lazy while ocaml is not. So is my interpretation correct if I say that Hakell lazyness is the reason why the Haskell program behaves "oddly" (according to my standards of course, there is no judgement value here)? And if it is so, is it possible to force the evaluation in order to have a program which doesn't run forever just because I am accessing an object? I presume I am still confused and I might be wrong, so thanks again for helping. module IOMonad = struct type 'a t = IO of 'a;; let return x = IO x;; let (>>=) (IO m) (f : ('a -> 'b t)) = (f m);; end;; open IOMonad;; module IMS = CCMultiSet.Make(struct type t = int let compare = compare end);; let delete x s = IMS.remove s x;; let insert x s = IMS.add s x;; let fold f b s = let f2 b n t = f t b in IMS.fold s b f2;; let fromlist = IMS.of_list ;; let search2 mynumbers nb = let rec ins numbers acc = (>>=) acc (fun v -> (* Printf.printf "%b\n" v; *) fold (fun x acc1 -> let numbers2 = delete x numbers in fold (fun y acc2 -> let numbers3 = delete y numbers2 and res = x + y in if res = nb then (return true) else ins (insert res numbers3) acc2) acc1 numbers2) acc numbers) in ins mynumbers (return false);; let b = fromlist [1;2;3;4];; let main = (>>=) (search2 b 99999999) (fun v -> return (if v then Printf.printf "True\n" else Printf.printf "False\n"));; Le 23/01/2018 à 22:08, Li-yao Xia a écrit :
Hi,
On 01/23/2018 02:39 PM, Jean-Marc Alliot wrote:
Thank you very much for your answer, but I still don't get it (I might be not bright enough :-))
Not at all! This is definitely not an obvious problem.
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...).
You can erase (acc :: IO Bool) only if acc is in fact pure (i.e., acc = return b), but how would GHC deduce such a fact?
- inlining could take care of it on a case-by-case basis at each call site, but ins is recursive, which prevents inlining;
- a more general solution for recursive definitions might be some kind of static analysis, that GHC doesn't do;
- using Identity instead of IO, then all computations must be pure, and in fact the optimization would apply automatically as a consequence of the lazy (>>=) for Identity.
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.
I don't have any good pointers unfortunately.
But it may help to expand the folds.
ins {1,2,3} acc = do acc ins {1+2,3} (ins {1+3,2} (ins {2+1,3} (... (ins {3+2, 1} acc))))
For the first recursive call to ins...
ins {1+2,3} acc1 = do acc1 ins {1+2+3} (ins {3+1+2} acc1)
... substitute that in the former (acc1 = ins {1+3,2} (ins {2+1,3} (... acc)))
ins {1,2,3} acc = do acc (ins {1+3,2} (... acc)) ins {1+2+3} (ins {3+1+2} (ins {1+3,2} (... acc)))
etc.
Li-yao

Hi, On 01/24/2018 12:02 PM, Jean-Marc Alliot wrote:
First thanks again for the answer, I really appreciate.
You're welcome, I'm happy to help!
module IOMonad = struct type 'a t = IO of 'a;; let return x = IO x;; let (>>=) (IO m) (f : ('a -> 'b t)) = (f m);; end;; open IOMonad;;
The closest thing to Haskell's (IO a) in OCaml is (unit -> 'a). module IOMonad = struct type 'a t = unit -> 'a let return x = fun () -> x let (>>=) m f = fun () -> f (m ()) () end I believe that definition will result in the same looping behavior as with the original Haskell program. It's not really a matter of laziness, but more of (im)purity. In OCaml, functions can have side effects. In Haskell, we must write pure functions that return an effectful computation as a value. In particular, we have the following property in Haskell: let a = print 1 in a >> a -- a :: IO () is equivalent to print 1 >> print 1 because "a" stands for the computation that prints 1 and returns (). Whereas in OCaml: let a = print_int 1 in a; a is not equivalent to print_int 1; print_int 1 here "a" just stands for (), and the effect is performed before it is evaluated. But we can define (print : int -> IO.t ()) as (let print n () = print_int n) in OCaml, with compositional properties similar to Haskell's print. Li-yao
participants (2)
-
Jean-Marc Alliot
-
Li-yao Xia