Haskell good for parallelism/concurrency on manycore?

Dear Haskellers, I just got an inquiry from a research department head of a Korean company seriously considering to adopt functional languages because they heard that functional languages can do good at parallel programming on manycore platforms. They want to know what technologies out there implemented in functional languages, such as Erlang or Haskell, that can help them write more maintainable programs that are better at utilizing parallelism and avoiding bugs related to synchronization. They are also very interested in Cilk, as well as Haskell or Erlang. My first thought is that maybe Cilk would work better for them just because it would not be easy to recruit Erlang or Haskell programmers experienced in network, security, or concurrent/parallel programming. I myself can answer basic inquiries such as what libraries to look for to implenent such and so, but not able to give advice on large scale projects such as unified security solution package. So, it wouldn't be practical form them to launch a project without inviting an Erlang or Haskell expert in their domain as a project manager from overseas, which I don't think they are very willing to do. Are there Haskell consultants or Haskell experts on this subject, who believes that Haskell based approach might work better for them, or Haskell can be useful along with other approaches (e.g. DSL, prototyping, formal modeling of policies)? If so, I would like to recommend them trying contact you, and try my best to help communicating with them, if needed. They know English, of course, but may not be familiar with functional programming orlanguage-oriented programming jargons such as DSLs, oops, I mean language middleware :-) For your information: The company is a network security company whose main products are VPN and firewall appliances and their management software. Their research department is in search of better technologies to implement their future UTM (unified threat management) solutions utilizing the manycore platforms. In Korea, there are some research groups and few companies using OCaml, but almost no Erlang or Haskell communities. This company is preferring local researchers or consultants for advice or consulting, but there's no local group using Haskell seriously, as far as I know, even in research yet. That's why this person contacted me, just because I wrote a small tutorial on Haskell Server Programming while ago. P.S. If you happen to be a local Korean expert on this matter, sorry for my ignorance, and I'd be happy to forward their inquiry to you! -- Ahn, Ki Yung

"Ahn" == Ahn, Ki Yung
writes:
Ahn> P.S. If you happen to be a local Korean expert on this matter, Ahn> sorry for my ignorance, and I'd be happy to forward their inquiry Ahn> to you! Probably not Korea-based, but 1st class Haskell hackers: http://www.well-typed.com/ Sincerely, Gour -- Gour | Zagreb, Croatia | GPG key: C6E7162D ----------------------------------------------------------------

When using any of -O, -O1, -O2 with the Debian binary build of GHC 6.6, trace shows that the expression if (lr > ll) then False else True is (at least partially) evaluated, but the value returned is always True, even though trace reports that (lr > ll) is True. When I use only the native code generator (without optimization), the correct value (False) is returned. Further detail and complete code on request. Best, Murray Gross

On Mon, Jan 5, 2009 at 4:34 PM, Murray Gross
When using any of -O, -O1, -O2 with the Debian binary build of GHC 6.6, trace shows that the expression
if (lr > ll) then False else True
is (at least partially) evaluated, but the value returned is always True, even though trace reports that (lr > ll) is True. When I use only the native code generator (without optimization), the correct value (False) is returned.
Further detail and complete code on request.
Of course! This is obviously incorrect behavior. Are you doing any unsafePerformIO? Please, complete code (minimal test case if possible, but don't let that stop you). Luke
Best,
Murray Gross _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

No unsafe perform (except what may be hidden in trace), nothing, fancy, no gimmicks (very pedestrian, even heavy-handed) code. Complete code is attached (I don't have smaller snippets, because I just discovered the problem). Best, Murray Gross On Mon, 5 Jan 2009, Luke Palmer wrote:
On Mon, Jan 5, 2009 at 4:34 PM, Murray Gross
wrote: When using any of -O, -O1, -O2 with the Debian binary build of GHC 6.6, trace shows that the expression
if (lr > ll) then False else True
is (at least partially) evaluated, but the value returned is always True, even though trace reports that (lr > ll) is True. When I use only the native code generator (without optimization), the correct value (False) is returned.
Further detail and complete code on request.
Of course! This is obviously incorrect behavior. Are you doing any unsafePerformIO? Please, complete code (minimal test case if possible, but don't let that stop you).
Luke
Best,
Murray Gross _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Specifically for this code:
gTst3 right left = if (lr > ll) then False else True
where lr = length (right ! 2)
ll = length (left ! 2)
why don't you just negate the condition, like:
gTst3 right left = (lr <= ll)
where lr = length (right ! 2)
ll = length (left ! 2)
2009/1/5 Murray Gross
No unsafe perform (except what may be hidden in trace), nothing, fancy, no gimmicks (very pedestrian, even heavy-handed) code. Complete code is attached (I don't have smaller snippets, because I just discovered the problem).
Best,
Murray Gross
On Mon, 5 Jan 2009, Luke Palmer wrote:
On Mon, Jan 5, 2009 at 4:34 PM, Murray Gross
wrote:
When using any of -O, -O1, -O2 with the Debian binary build of GHC 6.6, trace shows that the expression
if (lr > ll) then False else True
is (at least partially) evaluated, but the value returned is always True, even though trace reports that (lr > ll) is True. When I use only the native code generator (without optimization), the correct value (False) is returned.
Further detail and complete code on request.
Of course! This is obviously incorrect behavior. Are you doing any unsafePerformIO? Please, complete code (minimal test case if possible, but don't let that stop you).
Luke
Best,
Murray Gross _______________________________________________ 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
-- Rafael Gustavo da Cunha Pereira Pinto Electronic Engineer, MSc.

Hi
gTst3 right left = if (lr > ll) then False else True where lr = length (right ! 2) ll = length (left ! 2)
Running this code over HLint (http://www.cs.york.ac.uk/~ndm/hlint) says: Example.hs:8:1: Error: Redundant if Found: if (lr > ll) then False else True Why not: not (lr > ll) Making that change and running it again gives: Example.hs:8:1: Error: Use <= Found: not (lr > ll) Why not: lr <= ll Which ends up with something similar to what you came up with. However, if we take your final answer:
gTst3 right left = (lr <= ll) where lr = length (right ! 2) ll = length (left ! 2)
We get: Example.hs:8:1: Warning: Redundant brackets Found: (lr <= ll) Why not: lr <= ll Leaving us with the HLint 1.0 compliant (TM) : gTst3 right left = lr <= ll where lr = length (right ! 2) ll = length (left ! 2) Thanks Neil

The issue here is not whether or not the code is pretty or elegant, but whether or not I get correct execution of what I have, which is a correct statement of what I want (even if not the prettiest or most lint free), and I don't. There are lots of ways to work around the problem, but that doesn't, unfortunately, make the problem go away, and it is sure to appear elsewhere as the program is extended, which it will be. It would appear that the real issue here is that someone with resources I don't have needs to dig into the compilers--it should not be necessary to use trial and error to find an alternate writing of code that is legal and correct (regardless of the aesthetics) but is incorrectly compiled. For the time being, I will use native compilation and hope that someone can find and fix the error so that I can use the speed advantage of optimization. Best, Murray Gross On Tue, 6 Jan 2009, Neil Mitchell wrote:
Hi
gTst3 right left = if (lr > ll) then False else True where lr = length (right ! 2) ll = length (left ! 2)
Running this code over HLint (http://www.cs.york.ac.uk/~ndm/hlint) says:
Example.hs:8:1: Error: Redundant if Found: if (lr > ll) then False else True Why not: not (lr > ll)
Making that change and running it again gives:
Example.hs:8:1: Error: Use <= Found: not (lr > ll) Why not: lr <= ll
Which ends up with something similar to what you came up with. However, if we take your final answer:
gTst3 right left = (lr <= ll) where lr = length (right ! 2) ll = length (left ! 2)
We get:
Example.hs:8:1: Warning: Redundant brackets Found: (lr <= ll) Why not: lr <= ll
Leaving us with the HLint 1.0 compliant (TM) :
gTst3 right left = lr <= ll where lr = length (right ! 2) ll = length (left ! 2)
Thanks
Neil _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Exactly. The best you can do is try to reduce your code to a tiny
fragment that still exposes the problem, and report it as a bug.
On Tue, Jan 6, 2009 at 4:52 PM, Murray Gross
The issue here is not whether or not the code is pretty or elegant, but whether or not I get correct execution of what I have, which is a correct statement of what I want (even if not the prettiest or most lint free), and I don't. There are lots of ways to work around the problem, but that doesn't, unfortunately, make the problem go away, and it is sure to appear elsewhere as the program is extended, which it will be.
It would appear that the real issue here is that someone with resources I don't have needs to dig into the compilers--it should not be necessary to use trial and error to find an alternate writing of code that is legal and correct (regardless of the aesthetics) but is incorrectly compiled. For the time being, I will use native compilation and hope that someone can find and fix the error so that I can use the speed advantage of optimization.
Best,
Murray Gross
On Tue, 6 Jan 2009, Neil Mitchell wrote:
Hi
gTst3 right left = if (lr > ll) then False else True where lr = length (right ! 2) ll = length (left ! 2)
Running this code over HLint (http://www.cs.york.ac.uk/~ndm/hlint) says:
Example.hs:8:1: Error: Redundant if Found: if (lr > ll) then False else True Why not: not (lr > ll)
Making that change and running it again gives:
Example.hs:8:1: Error: Use <= Found: not (lr > ll) Why not: lr <= ll
Which ends up with something similar to what you came up with. However, if we take your final answer:
gTst3 right left = (lr <= ll) where lr = length (right ! 2) ll = length (left ! 2)
We get:
Example.hs:8:1: Warning: Redundant brackets Found: (lr <= ll) Why not: lr <= ll
Leaving us with the HLint 1.0 compliant (TM) :
gTst3 right left = lr <= ll where lr = length (right ! 2) ll = length (left ! 2)
Thanks
Neil _______________________________________________ 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

Hi Murray,
The issue here is not whether or not the code is pretty or elegant, but whether or not I get correct execution of what I have, which is a correct statement of what I want (even if not the prettiest or most lint free), and I don't.
Sorry, I was merely responding to someone else suggesting ways to improve your code. Of course you are right - if the code goes wrong when written in an inelegant way that is the fault of the compiler, not the fault or the author! Trying your code I get 69 of output on stdout, then the message "fail" repeatedly on stderr. This happens whether I compile the code with -fasm or -fvia-c, using GHC 6.10. What are you expecting the code to output in each case, what command lines do you use, and which do you believe is correct? Please make sure you clean all the .hi and .o files between each build, so they don't have any confusing effects. As soon as someone else can reproduce the problem, they will probably be able to snip it down to a more manageable example. Thanks Neil

My last note had an error in it, and the code originally sent to the list should be ignored. I have attached the current version of the code, and here is some further information (the behavior is different, by the way, but still apparently wrong). I have attached the current version of the program, which behaves slightly differently from the version originally sent. I am running ghc 6.6, gcc 4.1.2, g++ 4.1.1, on Debian Linux. The compile lines are ghc -threaded solve.hs or ghc -threaded -O2 solve.hs. The execution line is ./a.out, which should give me single-threaded execution. Ignore the output on stdout; it is the same for both versions. On stderr, the unoptimized version of the attached code gives me both "fail" and "goOn" (see lines #150 and #153). The optimized version gives me only "goOn." I think that both should give me both "fail" and "goOn." Were circumstances different, I might suspect that laziness and optimization had something to do with this. However, earlier tests showed inconsistency between the result of the test in gTst3 and the code where the value of gTst3 is used. A copy of the current version of solve.hs is attached. Best, Murray Gross P.S.: For anyone who has actually looked at the logic, I am aware that the test in gTst3 can be sharpened. That will come later. The current version is adequate for the time being.

If you believe this is a compiler bug, please report it: http://hackage.haskell.org/trac/ghc/newticket?type=bug mgross21:
My last note had an error in it, and the code originally sent to the list should be ignored. I have attached the current version of the code, and here is some further information (the behavior is different, by the way, but still apparently wrong).
I have attached the current version of the program, which behaves slightly differently from the version originally sent.
I am running ghc 6.6, gcc 4.1.2, g++ 4.1.1, on Debian Linux. The compile lines are ghc -threaded solve.hs or ghc -threaded -O2 solve.hs. The execution line is ./a.out, which should give me single-threaded execution.
Ignore the output on stdout; it is the same for both versions.
On stderr, the unoptimized version of the attached code gives me both "fail" and "goOn" (see lines #150 and #153). The optimized version gives me only "goOn." I think that both should give me both "fail" and "goOn."
Were circumstances different, I might suspect that laziness and optimization had something to do with this. However, earlier tests showed inconsistency between the result of the test in gTst3 and the code where the value of gTst3 is used.
A copy of the current version of solve.hs is attached.
Best,
Murray Gross
P.S.: For anyone who has actually looked at the logic, I am aware that the test in gTst3 can be sharpened. That will come later. The current version is adequate for the time being.
Content-Description: Current version of solve.hs
-- ********************************************************************* -- * * -- * Eternity II puzzle. Each puzzle piece is represented by a * -- * 5-tuple, in which the first 4 entries represent the four * -- * edge colors in the order left, top, right, bottom, and the * -- * fifth member is the (numerical) identifier for the piece. * -- * * -- *********************************************************************
-- module Solve where
import Data.Array.IArray import Control.Parallel import Control.Parallel.Strategies import List import Debug.Trace
main = putStrLn (show corns) >> putStrLn (corpic) >> putStrLn "Left sides\n">>
putStrLn (pArrayPic (pArray pSides)) >> putStrLn "Right sides\n">> putStrLn (pArrayPic (rightArray ))>> putStrLn (show (length (perims (pArray pSides) corTemp))) >> putStrLn (show (perims (pArray pSides) corTemp))>> putStrLn "done"
-- ********************************************************************* -- * * -- * Make a list of all possible perimeters. Run the operation in * -- * parallel over the list of possible corner configurations. * -- * * -- *********************************************************************
perims:: Array (Int) [Int]-> [(Int,Int,Int,Int)]->[[Int]] perims pArray corTemp = concat $ parMap rwhnf (\oneCor->makPerim oneCor pArray ) corTemp
-- ********************************************************************* -- * * -- * We build a list of perimeters by constructing each backward * -- * from position 59. However, position 59 needs special handling * -- * because it must match position 0 as well as 58. Each of the * -- * other corners will also need special handling, which is done * -- * by a case statement. * -- * * -- * Note that pArray is organized by the left sides of the pieces, * -- * while in makePerim we need to check the right side of a * -- * against the bottom of the first corner. This results in the * -- * need for rightArray, and some tricky indexing. * -- * * -- *********************************************************************
makPerim :: (Int,Int,Int,Int) -> Array (Int) [Int] -> [[Int]] makPerim oneCor pArray = [a:b | a <- ((rightArray) ! startCol), b <- (restPerim a (pArray // [(left(refPerim!a), (pArray!(left(refPerim!a)))\\[a])])
(rightArray //[(startCol, (rightArray ! startCol) \\ [a])]) oneCor 58), trace (show b) b /=[] ] where startCol = bot (corns !! (fst4 oneCor))
-- ********************************************************************* -- * * -- * Once past the first piece in a perimeter, move to next. * -- * Check for a corner piece, which needs special handling. * -- * If there are no candidates left to match last, terminate * -- * the recursion, indicating there is no way to continue. * -- * Otherwise, construct the list of possible continuations of * -- * the perimeter. * -- * * -- ********************************************************************* --
restPerim last leftRay rightRay oneCor iAm | -- trace ((show iAm)++" "++ (show last)) elem iAm [0,15,30,45] = corner last leftRay rightRay oneCor iAm
| useRow /= [] = extend
| otherwise = []
where useRow = rightRay ! (left (refPerim ! last)) extend = [b:c | b <- (rightRay ! (left (refPerim ! last))), c <- restPerim b (newLeft b) (newRight b) oneCor (iAm - 1), --trace (show c) c/=[]] newLeft b = leftRay // [((left (refPerim ! b)), (leftRay ! (left (refPerim ! b))) \\ [b])] newRight b = rightRay // [((right (refPerim ! b)), (rightRay ! (right (refPerim ! b))) \\ [b])]
-- ********************************************************************* -- * * -- * Corners get special handling. The corner in the upper left is * -- * always piece 1, because of rotational symmetry. * -- * * -- ********************************************************************* --
corner last leftRay rightRay oneCor iAm
| -- trace ((show last)++" "++(show iAm)) iAm == 15 = if (gTst3 leftRay rightRay) then (trace "goOn") goOn (snd4 oneCor) else trace "fail" [] | -- trace "goo" iAm == 30 = goOn (thd4 oneCor) | -- trace "gah" iAm == 45 = goOn (fth4 oneCor) | -- trace "gii" iAm == 0 = if (lastLeft == rightCor 1) then [[1]] else [] | otherwise = error ("\n\n *** You can't get here"++ " *** \n\n")
where lastLeft = left (refPerim ! last) rightCor b = right (refPerim ! b) botCor b = bot (refPerim ! b) nLeft b = left (refPerim ! b)
goOn q = if (lastLeft /= rightCor q) then [] else [q:c:d | c <- (leftRay ! (botCor q)), d <- -- trace ((show q)++" "++ -- (show c)++"xx ")
restPerim c (newleft c) (newright c) oneCor (iAm - 2) ] newleft c = leftRay // [((nLeft c), leftRay!(nLeft c)\\[c])] newright c = rightRay // [((rightCor c), rightRay!(rightCor c)\\ [c])]
-- ********************************************************************* -- * * -- * agTst is a simple heuristic test to determine whether it is * -- * possible for a perimeter to be built with the remaining * -- * pieces: it tests to find out whether there are an equal no. of * -- * pieces whose right side matches the left sides of available * -- * pieces, except, perhaps for 1, which will fit a corner piece. * -- * * -- * And it doesn't work, at least at the beginning of the solution.* -- * In the first 10,000,000 passages through corner 15, there is * -- * only 1 fail. * -- * * -- *********************************************************************
gTst :: Array Int [Int] -> Array Int [Int] -> Bool gTst right left = and $ map tryme (indices right)
where iList = indices right tryme x | (length (right ! x)) == (length (left ! x)) = True
| abs ((length (right ! x))- (length (left ! x))) == 1 = True | otherwise = False
gTst1:: Array Int [Int] -> Array Int [Int] -> Bool gTst1 right left = if (sum $ map tryme (indices right)) > 2 then False else True where tryme x = abs ((length (right ! x)) - (length (left ! x))) gTst2 right left = if (length (left ! 2)) > 0 then True else False
gTst3 right left = if ((lr > ll+2)||(lr < ll-2)) then False else True where lr = length (right ! 2) ll = length (left ! 2)
-- ********************************************************************* -- * * -- * Here we make up a list of the 6 possible corner configurations * -- * There are only 6 such because the remaining permutations of * -- * corner pieces are merely rotations of the six used here. * -- * * -- *********************************************************************
corTemp :: [(Int,Int,Int,Int)] corTemp = [(1,2,3,4),(1,2,4,3),(1,3,2,4),(1,3,4,2),(1,4,2,3),(1,4,3,2)]
corns = [(0,0,0,0,0), (0,0,2,1,1),(0,0,2,3,2),(0,0,4,1,3),(0,0,1,4,4)]
-- ********************************************************************* -- * * -- * Construct an array in which each entry is a list of pieces * -- * that have the same color on the left side. This array will be * -- * used to construct the perimeters of the puzzle. * -- * * -- * We use pArray as an array of available pieces, and refPerim * -- * in order to find the matching colors; since it changes a lot, * -- * the reduced item count will reduce overhead from building new * -- * pArray's. * -- * * -- *********************************************************************
pSides:: [(Int,Int,Int,Int,Int)] pSides = [(2,0,2,5,5),(4,0,2,6,6),(2,0,2,7,7),(8,0,2,7,8),(1,0,2,9,9), (3,0,2,10,10),(4,0,2,11,11),(3,0,2,12,12),(8,0,2,12,13), (3,0,2,13,14),(2,0,4,6,15),(1,0,4,14,16),(8,0,4,15,17), (8,0,4,16,18),(4,0,4,10,19),(4,0,4,11,20),(3,0,4,17,21), (2,0,4,18,22),(8,0,4,18,23),(2,0,4,19,24),(2,0,4,13,25), (4,0,1,5,26),(1,0,1,5,27),(1,0,1,6,28),(1,0,1,14,29), (8,0,1,10,30),(4,0,1,11,31),(1,0,1,19,32),(4,0,1,12,33),
(3,0,1,12,34),(8,0,1,20,35),(3,0,1,21,36),(2,0,3,14,37), (8,0,3,22,38),(8,0,3,9,39),(4,0,3,16,40),(1,0,3,16,41), (2,0,3,11,42),(4,0,3,11,43),(1,0,3,11,44),(2,0,3,17,45), (3,0,3,19,46),(3,0,3,12,47),(3,0,3,20,48),(8,0,8,5,49),
(2,0,8,6,50),(4,0,8,6,51),(2,0,8,7,52),(3,0,8,10,53), (3,0,8,17,54),(8,0,8,17,55),(1,0,8,12,56),(2,0,8,20,57), (8,0,8,20,58),(4,0,8,13,59),(1,0,8,21,60)]
pArray:: [(Int,Int,Int,Int,Int)] -> Array (Int) [Int] pArray pSides = accumArray (++) [] (1,8) accumPlist
rightArray:: Array (Int) [Int] rightArray = accumArray (++) [] (1,8) rightAccum rightAccum = map (\item ->((right item),[piece item])) pSides
accumPlist = map (\item ->((left item),[piece item])) pSides
refPerim:: Array (Int) (Int,Int,Int,Int,Int)
refPerim = listArray (1,60) (trace "don't get here"(drop 1 corns)++pSides)
-- ********************************************************************* -- * * -- * Pretty-printer for corner configurations. * -- * * -- * * -- *********************************************************************
corpic = concat $ map oneSq corTemp
oneSq (a,b,c,d) = show (corns !! a) ++ " " ++ show (corns !! b) ++ "\n\n" ++ show (corns !! c)++" "++show (corns !! d) ++ "\n\n\n"
-- ********************************************************************* -- * * -- * Ugly-printer for pArray, the array of pieces for the * -- * perimeter. * -- * * -- * * -- *********************************************************************
pArrayPic myray = concatMap (\x-> (show x)++"\n\n") (elems myray)
-- ********************************************************************* -- * * -- * Convenience functions. * -- * * -- *********************************************************************
left:: (Int,Int,Int,Int,Int) -> Int left (a,b,c,d,e) = a fst4 (a,b,c,d) = a
top (a,b,c,d,e) = b snd4 (a,b,c,d) =b
right (a,b,c,d,e) = c thd4 (a,b,c,d) = c
bot (a,b,c,d,e) = d fth4 (a,b,c,d) = d
piece (a,b,c,d,e) = e
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Am Dienstag, 6. Januar 2009 18:32 schrieb Murray Gross:
My last note had an error in it, and the code originally sent to the list should be ignored. I have attached the current version of the code, and here is some further information (the behavior is different, by the way, but still apparently wrong).
I have attached the current version of the program, which behaves slightly differently from the version originally sent.
I am running ghc 6.6, gcc 4.1.2, g++ 4.1.1, on Debian Linux. The compile lines are ghc -threaded solve.hs or ghc -threaded -O2 solve.hs. The execution line is ./a.out, which should give me single-threaded execution.
Ignore the output on stdout; it is the same for both versions.
On stderr, the unoptimized version of the attached code gives me both "fail" and "goOn" (see lines #150 and #153). The optimized version gives me only "goOn." I think that both should give me both "fail" and "goOn."
I get one "fail" and many "goOn" with optimisation using both, ghc-6.6 and ghc-6.8.3. That should indeed be so, because with optimisation, the branch else trace "fail" [] is only evaluated once, the result ([]) being reused. Without optimisation, that branch is re-evaluated every time it is hit, so many "fail" are printed.
Were circumstances different, I might suspect that laziness and optimization had something to do with this. However, earlier tests showed inconsistency between the result of the test in gTst3 and the code where the value of gTst3 is used.
Could you elaborate? I couldn't find an inconsistency using your previous code, it behaved as it should (until I ^C-ed it). HTH, Daniel

On Tue, 6 Jan 2009, Daniel Fischer wrote:
Could you elaborate? I couldn't find an inconsistency using your previous code, it behaved as it should (until I ^C-ed it).
In several versions of the code, now unfortunately lost because of a crash on a power failure (which is extremely rare where I live), I did not get any "goOn" despite the value of gTst3 indicating I should, or where, according to your analysis, I should have gotten a single "fail," I didn't. If I can prod myself into recreating now lost code (unfortunate, sending out the wrong version of the code and losing the right one, only to replace it with one that seems to work now [yes, I'm careful about deleting .o and .hi files]), I'll do so, and report it as a bug according to the instructions in another post. Since I have workarounds and I am using a back-dated version of GHC, it probably isn't worth too much more attention, although I'll keep a wary eye open. Thanks to all for attention. Best, Murray Gross
participants (9)
-
Ahn, Ki Yung
-
Daniel Fischer
-
Don Stewart
-
Gour
-
Luke Palmer
-
Murray Gross
-
Neil Mitchell
-
Peter Verswyvelen
-
Rafael Gustavo da Cunha Pereira Pinto