defaulting vs instance declarations

Robert Dockins robdockins at fastmail.fm
Tue Jul 20 09:24:01 EDT 2004


Hello all,

Is is possible to apply numeric defaulting while looking for matching
instance declarations?  For example, I'd like the following code to work
without having to explicitly specify the type of "7":

module Main where

class Stuff a b c | a b -> c
  where hi :: a -> b -> c

instance Stuff Integer Bool Bool where
  hi a b = if b then True else a == 0 

instance Stuff Float Bool Bool where
  hi a b = if b then False else a < 12.0

main = do
  --putStrLn $ show $ hi 7 True     -- doesn't work
  putStrLn $ show $ hi (7::Integer) True -- works


Under normal circumstances, the value of 7 would default to 7::Integer,
but this doesn't occur when type classes are involved this way.  Instead
GHC complains of 'No instance for (Stuff a Bool c)'

Obviously, I can just insert '::Integer' everywhere, but that is the
problem defaulting was designed to solve, and besides, its really
irritating and ugly.

BTW I already tried using Data.Typeable to determine the correct types
and cast at runtime, but GHC won't default over the constraint:

(Typeable a, Num a)

because, I suppose, Typeable is not a standard type class (Haskell
Report section 4.3.4)

Any ideas?

Thanks,
Robert


-------------- next part --------------
A non-text attachment was scrubbed...
Name: not available
Type: application/pgp-signature
Size: 189 bytes
Desc: This is a digitally signed message part
Url : http://www.haskell.org//pipermail/glasgow-haskell-users/attachments/20040720/cf9aa447/attachment.bin


More information about the Glasgow-haskell-users mailing list