[Haskell-cafe] overloaded overloading?

Daniel Fischer daniel.is.fischer at web.de
Tue Jan 12 19:33:12 EST 2010


Am Mittwoch 13 Januar 2010 01:17:17 schrieb Alberto G. Corona:
> Hi,
>
> I sometimes strumble on the same quiestion that forces me to insert
> functions that process objects of a certain class inside their class
> definition.  This occurs when a computation uses the object internally,
> neiter as parameter or as a return value or in the case of existential
> types. An example of the first:
>
>
> class Example a where
>     irec ::  IO a
>     pr :: a →  IO String
>     sample2 ::  a  →   IO ()
>     sample2 _  =   do
>       x ←  irec :: IO a
>       pr x
>       return ()
>
> sample :: Example a ⇒ a  →   IO ()
> sample _  =   do
>   x ←  irec :: IO a
>   pr x
>   return ()
>
>
> With the flag -fglasgow-exts, the following error below appears in
> sample. without the flag, the error appears in both sample and sample2.
> I´m too lazy to find what concrete extension is involved and why,

{-# LANGUAGE ScopedTypeVariables #-}

sample :: forall a. Example a => a -> IO ()
sample _ = do
    x <- irec :: IO a
    pr x
   return ()

Unless you bring the type variable a into scope, the 'a' in the signature 
of irec within sample is a fresh type variable, so it looks to the compiler 
like

sample :: Example a => a -> IO ()
sample _ = do
    x <- irec :: IO b
    pr x
    return ()

You can make it without language extensions:

sample :: Example a => a -> IO ()
sample dummy = do
    x <- irec
    pr (x `asTypeOf` dummy)
    return ()

> anyhow, in the case of sample, the compiler must generate a new type a1
> with no context.
>
>     Could not deduce (Example a1) from the context ()
>       arising from a use of `irec' at Control\Workflow\Users.hs:73:7-10
>     Possible fix:
>       add (Example a1) to the context of an expression type signature
>     In a stmt of a 'do' expression: x <- irec :: IO a
>     In the expression:
>         do x <- irec :: IO a
>            pr x
>            return ()



More information about the Haskell-Cafe mailing list