Simon Peyton-Jones wrote:
Hmm. I'm not sure you are done yet! What happens if you say
map ((#,#) True) xs
?
You'll probably end up with a link error, because there is no curried function
(#,#). With a regular data type, we inject the (rather odd-looking) function
(,) = \a \b. (a,b)
and similarly for all data type declarations, just so that there is a current
(,) function defined.
looks like a good point. Although many examples such as yours fail to be
kind-correct. However, I cannot reproduce when I found a compilable
example that seems similar:
]cat Main.hs
{-# LANGUAGE UnboxedTuples #-}
main = case curried True of
(# n, b #) -> print (n,b)
{-# NOINLINE curried #-}
curried :: Bool -> (# Int, Bool #)
curried = (#,#) 3
]../compiler/ghc-inplace --make -O0 Main.hs
]./Main
(3,True)
]#edit, edit...
]cat Main.hs
{-# LANGUAGE UnboxedTuples #-}
map_ :: (a -> (# b, c #)) -> [a] -> [(b,c)]
map_ f [] = []
map_ f (a:as) = case f a of
(# b, c #) -> (b, c) : map_ f as
main = print $ map_ ((#,#) True) ['a','b','c']
]../compiler/ghc-inplace --make -O0 Main.hs
]./Main
[(True,'a'),(True,'b'),(True,'c')]
The same happens even if I put the definition of "map_" into a separate
module.
I'll certainly add a testcase for currying, but do you have any idea why
this isn't breaking?
Do you want to tackle (2) on #1509. I can explain what's needed...
maybe someday; if it's not too hard/time-consuming, maybe now (you could
put your explanation of what's needed as a response to that ticket, i.e.
in Trac?)
would implementing that make it harder or easier for ghci to support
unboxed tuples?
Isaac
_______________________________________________
Cvs-ghc mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-ghc