Phil writes:
| Joe writes:
|  
| | Phil Writes:
| |   
| | |  The closest one can come is
| | |
| | |        class G a where
| | |                g :: a -> Bool
| | |                g x = g [x]
| | |
| | |        instance G Int
| | |        instance G [Int]
| | |        instance G [[Int]]
| | |        ...
| | |
| | |which requires an infinite number of instance declarations.
| |   
| | Can't this be written as follows?
| |   
| |     instance G Int
| |     instance (G a) => G [a]
| |   
| | Now, this is still an infinite number of instances, though not
| | declarations, so the point still holds that it can't be monomorphized.
|
| I don't think this works.  The declaration `instance G Int' is valid
| only if `instance G [Int]' holds, and this in turn requires that
| `instance G [[Int]]' holds, and so on.  I haven't tried it in Haskell,
| but it should either be illegal or cause the type-checker to enter an
| infinite loop.  (Hmmm!  Maybe someone should try it ...)  Cheers,  -- P

I forgot to mention that I did try it with hbc:

Silly.hs:
module Silly where

class G a where
        g :: a -> Bool
        g x = g [x]

instance G Int
instance (G a) => G [a]

Welcome to interactive Haskell B. version 0.998.5 SPARC 1992 Aug 27!
Loading prelude... 983 values, 70 types found.
Type "help;" to get help.
> load "Silly";
Loading "Silly.hs"
class G a where {
    g :: a -> Bool
    }
> let f x = g x
# ;
f :: (G a) => a -> Bool


Cheers,
--Joe

Reply via email to