Function hanging in infinite input

Hello all, I was trying to implement >>= (tBind) on my "Temporal" data type and found that it hangs on an operation like takeInitialPart $ infiniteTemporal >>= (\x -> finiteTemporal) I am pretty sure the result is well defined and by no means infinite. Also the code works on finite Temporals. How does one address such problems? I attach the relevant pieces of code, in case someone would be so kind and inspect or run it. Feel free to point out any flaws as I might be completely off-track. If you call ex10 in GHCI, you get no result. The line marked with "< here" is executed over and over, but apparently without contributing to the result. The debugger shows, that "hd" does have a correct, finite value each time and that "tpr" is consumed as expected. -- -- -- -- -- -- -- -- -- examples -- -- -- -- -- -- -- ex1 = Temporal [(DPast, 1), (T 3,3), (T 7, 7)] :: Temporal Int ex10 = tUntil (T 5) $ outer `tBind` \_ -> ex1 :: Temporal Int where outer = Temporal $ (DPast,0):[(T (fromIntegral t), t)| t <- [5,10 ..]] -- -- -- -- -- -- -- -- -- tBind -- -- -- -- -- -- -- -- -- Changed (Temporal a) to (Temporal Int) for debugging tBind :: (Temporal Int) -> (Int -> Temporal Int) -> Temporal Int tBind tpr f -- tpr is infinite in this example, let's forget these cases -- | tNull tpr = error "empty Temporal" -- | tNull (tTail tpr) = laties | otherwise = let hd = (tUntil (tTt tpr) laties) in hd `tAppend` (tTail tpr `tBind` f) -- < here where laties = switchAt (tTh tpr) ( f (tVh tpr)) tTail (Temporal xs) = Temporal (tail xs) tAppend (Temporal as) (Temporal bs) = Temporal (as ++ bs) switchAt t tpx | tNull (tTail tpx) = Temporal (tot tpx) | between t (tTh tpx) (tTt tpx) = Temporal (tot tpx) | otherwise = switchAt t (tTail tpx) where tot (Temporal ((ty,vy):xs)) = ((max t ty, vy):xs) between t x y = t >= x && t < y -- -- -- -- -- -- -- -- -- helpers -- -- -- -- -- -- -- -- data Time = DPast | T Integer deriving (Eq, Show) -- DPast is "distant past" instance Ord Time where compare DPast DPast = EQ compare DPast _ = LT compare _ DPast = GT compare (T t1) (T t2) = compare t1 t2 -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- data Temporal a = Temporal [(Time, a)] deriving (Eq, Show) tVh :: Temporal a -> a tVh = snd . head . toList -- value head tTt, tTh :: Temporal a -> Time tTt = fst . head . tail . toList -- time tail tTh = fst . head . toList -- time head tNull = null . toList tUntil :: Time -> Temporal a -> Temporal a tUntil t (Temporal xs) = Temporal $ (takeWhile (\(tx, vx) -> tx > t)) xs toList :: Temporal a -> [(Time, a)] toList (Temporal xs) = xs

Le 26/04/2015 15:20, martin a écrit :
I was trying to implement >>= (tBind) on my "Temporal" data type and found that it hangs on an operation like
takeInitialPart $ infiniteTemporal >>= (\x -> finiteTemporal)
I am pretty sure the result is well defined and by no means infinite./*Also the code works on finite Temporals.*/ I am not sure about this... I replaced [5,10 ..] by [5,10 .. 100], so outer becomes
Temporal [(DPast,0),(T 5,5),(T 10,10),(T 15,15),(T 20,20),(T 25,25),(T 30,30),(T 35,35),(T 40,40),(T 45,45),(T 50,50),(T 55,55),(T 60,60),(T 65,65),(T 70,70),(T 75,75),(T 80,80),(T 85,85),(T 90,90),(T 95,95),(T 100,100)] and GHCi says: *Main> ex10 *** Exception: Prelude.head: empty list == Jerzy Karczmarczuk

Am 04/26/2015 um 05:28 PM schrieb Jerzy Karczmarczuk:
Le 26/04/2015 15:20, martin a écrit :
I was trying to implement >>= (tBind) on my "Temporal" data type and found that it hangs on an operation like
takeInitialPart $ infiniteTemporal >>= (\x -> finiteTemporal)
I am pretty sure the result is well defined and by no means infinite. /*Also the code works on finite Temporals.*/ I am not sure about this... I replaced [5,10 ..] by [5,10 .. 100], so outer becomes
Temporal [(DPast,0),(T 5,5),(T 10,10),(T 15,15),(T 20,20),(T 25,25),(T 30,30),(T 35,35),(T 40,40),(T 45,45),(T 50,50),(T 55,55),(T 60,60),(T 65,65),(T 70,70),(T 75,75),(T 80,80),(T 85,85),(T 90,90),(T 95,95),(T 100,100)]
and GHCi says:
*Main> ex10 *** Exception: Prelude.head: empty list
This is because I have commented out two corner cases in tBind, to make sure it's not them. Remove the comments and it'll work

Martin reacts to my non-answer:
Am 04/26/2015 um 05:28 PM schrieb Jerzy Karczmarczuk:
... and GHCi says:
*Main> ex10 *** Exception: Prelude.head: empty list This is because I have commented out two corner cases in tBind, to make sure it's not them. Remove the comments and it'll work Martin I sent you a private follow-up. I repeat it here.
I uncommented those lines. Your program goes until the end of the list, and returns the /*last*/ element (modified). The form *tBind tpr f ... (tTail tpr `tBind` f) * loops until ... Now, I know about laziness... It seems that it doesn't help. Most probably your hd is simply empty, and the tail gets stuck in an idle loop. Jerzy Karczmarczuk

Am 04/26/2015 um 07:05 PM schrieb Jerzy Karczmarczuk:
Martin reacts to my non-answer:
Martin I sent you a private follow-up. I repeat it here.
I uncommented those lines. Your program goes until the end of the list, and returns the /*last*/ element (modified). The form
*tBind tpr f ... (tTail tpr `tBind` f) *
loops until ...
Now, I know about laziness... It seems that it doesn't help. Most probably your hd is simply empty, and the tail gets stuck in an idle loop.
Thanks a lot for taking the time to look into my code. I had made a mistake when I stripped down my code. In tUntil the inequality is wrong. I updated the example and put it here: https://www.dropbox.com/s/836hykwhhsb0n55/Function_hanging_in_infinite_input... The strange thing is: I can set an upper limit to "outer" and I get the result Temporal [(DPast,1),(T 3,3)] When I push the upper limit to later times, the result doesn't change. This is as expected, because I am only taking everything until (T 5). It looks like Haskell doesn't know that and believes that later recursions might contribute to the result. But I don't see why. tUntil is basically an innocent takeWhile.

The problem is that tAppend is too strict; it evaluates both its arguments
before producing anything. This is because you are pattern matching on
those arguments. You could use lazy patterns or make Temporal a newtype to
avoid that. Or you could rewrite to something like
tAppend as bs = Temporal $ toList as ++ toList bs
On Sun, Apr 26, 2015 at 11:22 AM, martin
Am 04/26/2015 um 07:05 PM schrieb Jerzy Karczmarczuk:
Martin reacts to my non-answer:
Martin I sent you a private follow-up. I repeat it here.
I uncommented those lines. Your program goes until the end of the list, and returns the /*last*/ element (modified). The form
*tBind tpr f ... (tTail tpr `tBind` f) *
loops until ...
Now, I know about laziness... It seems that it doesn't help. Most probably your hd is simply empty, and the tail gets stuck in an idle loop.
Thanks a lot for taking the time to look into my code.
I had made a mistake when I stripped down my code. In tUntil the inequality is wrong. I updated the example and put it here:
https://www.dropbox.com/s/836hykwhhsb0n55/Function_hanging_in_infinite_input...
The strange thing is: I can set an upper limit to "outer" and I get the result
Temporal [(DPast,1),(T 3,3)]
When I push the upper limit to later times, the result doesn't change. This is as expected, because I am only taking everything until (T 5). It looks like Haskell doesn't know that and believes that later recursions might contribute to the result. But I don't see why. tUntil is basically an innocent takeWhile.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
-- Matthew Korson mjkorson@gmail.com

Am 04/26/2015 um 08:38 PM schrieb Matthew Korson:
The problem is that tAppend is too strict; it evaluates both its arguments before producing anything. This is because you are pattern matching on those arguments. You could use lazy patterns or make Temporal a newtype to avoid that. Or you could rewrite to something like
tAppend as bs = Temporal $ toList as ++ toList bs
Mathew, you made my day! At least things work now as expected. But could you please elaborate on the difference between tAppend (Temporal as) (Temporal bs) = Temporal (as ++ bs) vs tAppend as bs = Temporal $ (toList as) ++ (toList bs) toList (Temporal xs) = xs Why is the first one more strict than the second?

Am 04/26/2015 um 08:38 PM schrieb Matthew Korson:
The problem is that tAppend is too strict; it evaluates both its arguments before producing anything.
That's it. Define *tAppend (Temporal as) ~(Temporal bs) = Temporal (as ++ bs)* No need (I think) to pass through the toList, which is a redundant ping-pong. Jerzy K.

On Sun, Apr 26, 2015 at 3:23 PM, martin
At least things work now as expected. But could you please elaborate on the difference between
tAppend (Temporal as) (Temporal bs) = Temporal (as ++ bs)
vs
tAppend as bs = Temporal $ (toList as) ++ (toList bs) toList (Temporal xs) = xs
Why is the first one more strict than the second?
Because the first one pattern matches both parameters immediately to ensure that the constructor is the one named (Temporal). The second defers it, since the toList call is not forced and therefore won't be invoked (along with its strict pattern match) until its value is needed. -- brandon s allbery kf8nh sine nomine associates allbery.b@gmail.com ballbery@sinenomine.net unix, openafs, kerberos, infrastructure, xmonad http://sinenomine.net
participants (4)
-
Brandon Allbery
-
Jerzy Karczmarczuk
-
martin
-
Matthew Korson