
I found a strange behavior in my code Here a (very) simplified version of my code: {-# LANGUAGE PArr #-} {-# OPTIONS -fdph-seq #-} module Main where import Control.Parallel import GHC.PArr parArr :: [:String:] parArr = [: "1", "2", "3", "4" :] isElement :: String -> Bool isElement x = x `elemP` parArr main :: IO () main = do putStrLn $ (show . isElement) "5" The aspected result is "False" ("5" isn't a member of parArr), but the result I get is "True". I've compiled this code with the command: ghc --make -Odph -threaded Test.hs -rtsopts -o test and launched with: test +RTS -N2 My system is MacOS X 10.7.1 with Xcode 4.1 and GHC 7.0.4 (I've found the same behavior on Windows). Its obvious I'm missing something. Could someone help me? Thanks. Luca.

Yes, I'm interested too in this problem.
Is any body able to answer to the Luca's question?
Alba
2011/8/25 Luca Ciciriello
I found a strange behavior in my code
Here a (very) simplified version of my code:
{-# LANGUAGE PArr #-} {-# OPTIONS -fdph-seq #-}
module Main where
import Control.Parallel import GHC.PArr
parArr :: [:String:] parArr = [: "1", "2", "3", "4" :]
isElement :: String -> Bool isElement x = x `elemP` parArr
main :: IO () main = do putStrLn $ (show . isElement) "5"
The aspected result is "False" ("5" isn't a member of parArr), but the result I get is "True".
I've compiled this code with the command: ghc --make -Odph -threaded Test.hs -rtsopts -o test
and launched with: test +RTS -N2
My system is MacOS X 10.7.1 with Xcode 4.1 and GHC 7.0.4 (I've found the same behavior on Windows).
Its obvious I'm missing something. Could someone help me?
Thanks.
Luca. _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Hi Alba. Since I've got no answer to my question I think that my strange behavior is a very deep problem. I let you know when I have news. Bye. Luca. On Aug 29, 2011, at 8:35 AM, Alba Marchisio wrote:
Yes, I'm interested too in this problem. Is any body able to answer to the Luca's question?
Alba
2011/8/25 Luca Ciciriello
I found a strange behavior in my code Here a (very) simplified version of my code:
{-# LANGUAGE PArr #-} {-# OPTIONS -fdph-seq #-}
module Main where
import Control.Parallel import GHC.PArr
parArr :: [:String:] parArr = [: "1", "2", "3", "4" :]
isElement :: String -> Bool isElement x = x `elemP` parArr
main :: IO () main = do putStrLn $ (show . isElement) "5"
The aspected result is "False" ("5" isn't a member of parArr), but the result I get is "True".
I've compiled this code with the command: ghc --make -Odph -threaded Test.hs -rtsopts -o test
and launched with: test +RTS -N2
My system is MacOS X 10.7.1 with Xcode 4.1 and GHC 7.0.4 (I've found the same behavior on Windows).
Its obvious I'm missing something. Could someone help me?
Thanks.
Luca. _______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

On Monday 29 August 2011, 08:41:35, Luca Ciciriello wrote:
Hi Alba. Since I've got no answer to my question I think that my strange behavior is a very deep problem.
Well, perhaps it's not very deep, just not enough people on this list are familiar with dph. In such cases, ask on haskell-cafe or #haskell to reach a wider audience. Anyway, I'm pretty sure it's a bug in dph. If you change your code to avoid elemP: isElement :: String -> Bool isElement x = x `elemP1` parArr where elemP1 :: Eq a => a -> [:a:] -> Bool elemP1 v ar = lengthP (filterP (== v) ar) /= 0 you get the expected result(s) [but not with HEAD]. I've opened a ticket: http://hackage.haskell.org/trac/ghc/ticket/5438
I let you know when I have news.
Bye.
Luca.
Cheers, Daniel

Ok, Thanks. This works fine. I found out that also mapP and sumP are working as expected, but elemP and foldP do not behave correctly. Luca. On Aug 29, 2011, at 11:14 AM, Daniel Fischer wrote:
On Monday 29 August 2011, 08:41:35, Luca Ciciriello wrote:
Hi Alba. Since I've got no answer to my question I think that my strange behavior is a very deep problem.
Well, perhaps it's not very deep, just not enough people on this list are familiar with dph. In such cases, ask on haskell-cafe or #haskell to reach a wider audience.
Anyway, I'm pretty sure it's a bug in dph. If you change your code to avoid elemP:
isElement :: String -> Bool isElement x = x `elemP1` parArr where elemP1 :: Eq a => a -> [:a:] -> Bool elemP1 v ar = lengthP (filterP (== v) ar) /= 0
you get the expected result(s) [but not with HEAD].
I've opened a ticket: http://hackage.haskell.org/trac/ghc/ticket/5438
I let you know when I have news.
Bye.
Luca.
Cheers, Daniel
participants (3)
-
Alba Marchisio
-
Daniel Fischer
-
Luca Ciciriello