On Dec 25, 2007 4:27 PM, Henning Thielemann
<[EMAIL PROTECTED]> wrote:
> test :: (Integral a, RealFrac a) => a
> test =
>    let c = undefined
>    in  asTypeOf (round c) c
>
>
> When compiling I get:
>
> Compiling StorableInstance ( src/StorableInstance.hs, interpreted )
>
> src/StorableInstance.hs:38:17:
>     Warning: Defaulting the following constraint(s) to type `Double'
>              `RealFrac a' arising from use of `round' at 
> src/StorableInstance.hs:38:17-21
>              In the first argument of `asTypeOf', namely `(round c)'
>              In the definition of `test1': test1 = let c = undefined in 
> asTypeOf (round c) c

Interesting, I don't see this behaviour at all.

$ cat t.hs
module Main where

instance Integral Double

test :: (Integral a, RealFrac a) => a
test =
  let c = undefined
  in  asTypeOf (round c) c

main = print (test :: Double)

$ ghc --make t.hs
[1 of 1] Compiling Main             ( t.hs, t.o )

t.hs:3:0:
    Warning: No explicit method nor default method for `quotRem'
             In the instance declaration for `Integral Double'

t.hs:3:0:
    Warning: No explicit method nor default method for `toInteger'
             In the instance declaration for `Integral Double'
Linking t ...

$ ./t
t: Prelude.undefined

$ ghc --version
The Glorious Glasgow Haskell Compilation System, version 6.6.1


-- 
Felipe.
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to