Thanks to all for pointing out my mistake, which was that I needed to use a
from- function to generalize the signature.  I thought I might add that,
although most people suggested using fromInteger, it's necessary to use
fromIntegral in this case (unless your implementation has a fromInt function).

  Since I have learned that others have had similar problems, I would just like
to clarify the problem as I understand it.  If I may take the liberty of
posting a response I got in a personal communication (from John Peterson):

   You're missing a `fromInteger'.  

   >    properFraction n@(Exact x) = (fromInteger n, 1)
   >    properFraction (Inexact x) = (fromInteger i, Inexact f)
   >                                 where (i,f) = properFraction x

   The type of the instance has to match the class signature exactly.
   Yours didn't include the Integral b.  You cannot use a type that is
   more specific than that declared in the class declaration.

  According to this, then, my function had the signature Number -> (Number,
Number) but the signature needed was Integral b => Number -> (b,Number).  The
error message I got from GHC, though, does not mention the context at all:

  "Domains.lhs", line 238: Type signature mismatch:
      Signature for class method `properFraction' doesn't match its inferred type.
      Signature: Number -> (b._401, Number)
      Inferred type: Number -> (Number, Number)

  This is quite misleading, because it looks as though the contexts have simply 
been omitted because they are common to both signatures.

  Another person, who tried the example out on HBC reported the following error 
message:

  "numtest.hs", line 28, [59] Bad restriction
      (Integral a) => Number -> (a, Number)
  ...

  which mentions the context but is perhaps even more puzzling.

  In any case, since this appears to have been a point of some difficulty for
people, I am going to forward a copy of this message to Glasgow in hope that
there is a way to produce a better error message.

  Here is the original message:

    I have a numeric type Number for use in a dynamically typed language where
  Exact numbers are considered a subset of Inexact numbers.  For this reason, it
  makes sense to call functions like truncate, round, etc. on Exact numbers.  To
  implement this, I made Number an instance of RealFrac, whose methods include
  the above functions; note that all the methods are defined by default in terms
  of one method, properFraction.  properFraction has the following type:

  >   properFraction :: (Integral b) => a -> (b,a)

    Here is the Number type I am using:

  > data  Number          = Exact         Int
  >                       | Inexact       Double
  >                       deriving (Eq)

    Here is the RealFrac instance:

  > instance RealFrac Number where
  >       properFraction n@(Exact x) = (n, 1)
  >       properFraction (Inexact x) = (Exact (fst pf), Inexact (snd pf))
  >                                    where pf = properFraction x

    I also have instances for the superclasses of RealFrac and an instance for
  Integral (and Text).  When I compile the module, I get this error from
  GHC-0.26:

    "Domains.lhs", line 212: Type signature mismatch:
        Signature for class method `properFraction' doesn't match its inferred type.
        Signature: Number -> (b._370, Number)
        Inferred type: Number -> (Number, Number)

    Now if b._370 is free, then I ought to be able to instantiate it with
  Number, yet GHC considers this a type mismatch.  Why?  My type appears to be
  too specific but as far as I can tell it is not inconsistent; if it were an
  ambiguity, I would think to use an explicit signature in the function body or
  use the function asTypeOf, but clearly there is no way to make a type more
  general.

    I have also looked through the Report a few times, checking for relevant
  restrictions on classes and overloading instances, and although there is a lot
  of stuff about ambiguities, nothing seems to apply to this problem.  Also, as
  far as I can see, this does not appear to be an instance of the monomorphism
  restriction.

    Has anyone encountered this problem before?  Is it a compiler bug, an
  oversight in the language or am I just doing something wrong?  Comments and
  workarounds would be appreciated.

Frank Christoph <[EMAIL PROTECTED]>



Reply via email to