Johan Nordlander and I have been looking at these interesting examples,
and would like to offer another entertaining variation to the collection:
class C t where op :: t -> Bool
instance C [t] where op x = True
p y = (let f :: c -> Bool; f x = op (y >> return x) in f, y ++ [])
q y = (y +
A prototype of this tool is shown here:
www.numeric-quest.com/haskell/explorer/browser.html
Jan
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe
Christian Lescher writes:
> [...]
>
> Let's say we restrict it to the types Int and Double. Is an
> automatic conversion at least in this case possible?
You could try wheeling out Haskell's Least Used Keyword:
module Defs where
default(Double, Int)
n = 3 -- This is defau
> One complication is that some Integer values exceed the greatest
> Double value. In such cases, it's not clear which implementation of
> (/) should be used.
>
> It would certainly be nice to have an automatic conversion if, for
> example, n were an Int and x were a Float, because those types ar
Christian Lescher writes:
> When defining expressions with arithmetic operations on a mixture of
> Integers and Floats (except literals), an explicit conversion by
> "fromIntegral" for the Integers is necessary, for example: ceiling
> (fromIntegral n / x)
>
> Is it possible to do the "fromI
When defining expressions with arithmetic operations on a mixture of
Integers and Floats (except literals), an explicit conversion by
"fromIntegral" for the Integers is necessary, for example: ceiling
(fromIntegral n / x)
Is it possible to do the "fromInteger" conversion automatically? What's
the
| reported the bug several months ago.)
Sorry! The bug has been fixed, but our nhc98 installation hasn't
been rebuilt.
| If your nhc98 compiler
| was built by gcc, hbc, or nhc98 itself, then it gives a proper error
| message here, viz:
|
| Couldn't simplify the context ((_180#) _171).
|
> Both GHC and Hugs reject this module if the type signature for
> test is omitted. NHC (v1.00, 2000-09-15) falls over completely, with
> Fail: Prelude.chr: bad argument
Rushing to the defence of nhc98 (as always!), I should point out
that nhc98 actually falls over here because of a bug in