Hi Luke,
You're right. My code had a typo. Unfortunately, I still get the same error whichever way I do it.
For example:
> {-# LANGUAGE DisambiguateRecordFields #-}
> import A
> import B
>
> main = do
> let xx = getA
> print (x xx)
and:
#!/usr/bin/env runhaskell
> {-# LANGUAGE DisambiguateRecordFields #-}
> import A
> import B
>
> main = do
> let xx = getA
> putStrLn $ show (x xx)
both give me:
test.lhs:8:22:
Ambiguous occurrence `x'
It could refer to either `A.x', imported from A at test.lhs:3:2-9
(defined at A.hs:5:5)
or `B.x', imported from B at test.lhs:4:2-9
(defined at B.hs:5:5)
Any ideas?
$ ghc --version
The Glorious Glasgow Haskell Compilation System, version 6.10.3
Thanks,
-John
On Sat, Jun 6, 2009 at 1:48 AM, John Ky <newhoggy@gmail.com> wrote:Hi Haskell Cafe,
In the following code, I get an error saying Ambiguous occurrence `x'. Why can't Haskell work out which x to call based on the type of getA?
Thanks
-John
#!/usr/bin/env runhaskell
> {-# LANGUAGE DisambiguateRecordFields #-}
> import A
> import B
>
> main = do
> let xx = getA
> putStrLn $ show x xx
This is parsed as two arguments passed to the show function (which only takes one argument).
putStrLn $ show (x xx)
Or because putStrLn . show = print;
print $ x xx
----------------------
module A where
data TypeA = TypeA
{ a :: Int
, x :: Int
}
getA = TypeA { a = 1, x = 2 }
-------------------------
module B where
data TypeB = TypeB
{ b :: Int
, x :: Int
}
getB = TypeB { b = 1, x = 3 }
--------------------------
./test.lhs:8:21:
Ambiguous occurrence `x'
It could refer to either `A.x', imported from A at ./test.lhs:3:2-9
(defined at A.hs:5:5)
or `B.x', imported from B at ./test.lhs:4:2-9
(defined at B.hs:5:5)
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe