Manuel M T Chakravarty wrote:
Peter Gavin:
> instance ( NaturalT n
> , zero ~ (n :==: D0)
> , zero ~ True )
> => TestIter n True where
> testIter _ _ = ""
I am wondering why you are writing (zero ~ (n :==: D0), zero ~ True)
instead os just (True ~ (n :==: D0)) - after all zero appears nowhere else.
[..]
Well, it's not happening in this instance, but I had some other code that would
give me compilation warnings unless I flattened everything out like that. I
don't recall what the message exactly was anymore, but I'd never seen it before.
I guess I just got into the habit of doing that without really thinking about it.
In any case, I'm getting a different error now. I unflattened the code, and
added a call to the testIter function:
> class TestIter n zero where
> testIter :: n -> zero -> Prelude.String
>
> instance ( NaturalT n
> , (n :==: D0) ~ True )
> => TestIter n True where
> testIter _ _ = ""
>
> instance ( NaturalT n
> , (n :==: D0) ~ False
> , TestIter (Pred n) ((Pred n) :==: D0) )
> => TestIter n False where
> testIter n _ =
> intToDigit (fromIntegerT n) : testIter (_T :: (Pred n))
> (_T :: ((Pred n) :==: D0))
>
> test9 :: Prelude.String
> test9 = testIter d9 (_T :: False)
which gives me the message:
Test.hs:220:38:
Could not deduce (TestIter
(Pred n) (IsEQ (Compare (Pred n) (Dec DecN))))
from the context (n :==: D0 ~ False,
TestIter n False,
NaturalT n,
TestIter (Pred n) (Pred n :==: D0))
arising from a use of `testIter' at Test.hs:220:38-89
Possible fix:
add (TestIter
(Pred n) (IsEQ (Compare (Pred n) (Dec DecN)))) to the context of
the instance declaration
or add an instance declaration for
(TestIter (Pred n) (IsEQ (Compare (Pred n) (Dec DecN))))
In the second argument of `(:)', namely
`testIter (_T :: Pred n) (_T :: (Pred n) :==: D0)'
In the expression:
intToDigit (fromIntegerT n)
: testIter (_T :: Pred n) (_T :: (Pred n) :==: D0)
In the definition of `testIter':
testIter n _
= intToDigit (fromIntegerT n)
: testIter (_T :: Pred n) (_T :: (Pred n) :==: D0)
Test.hs:223:8:
No instance for (TestIter
(Pred (Dec (DecN :. Dec9))) (Pred (Dec (DecN :. Dec9))
:==: D0))
arising from a use of `testIter' at Test.hs:223:8-32
Possible fix:
add an instance declaration for
(TestIter
(Pred (Dec (DecN :. Dec9))) (Pred (Dec (DecN :. Dec9)) :==: D0))
In the expression: testIter d9 (_T :: False)
In the definition of `test9': test9 = testIter d9 (_T :: False)
The first message corresponds to the instance definition for
(TestIter n False). The second corresponds to the definition for test9.
Any ideas why I should get this? I'm using ghc-6.10.0.20081007 (but I'm
currently building the latest HEAD, which should be done shortly).
Pete
_______________________________________________
Cvs-ghc mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-ghc