Oops [Fwd: Re: Allowing duplicate instances in GHC 6.4]

Keean Schupke k.schupke at imperial.ac.uk
Thu Mar 31 10:31:36 EST 2005


Some more fixes...

Keean Schupke wrote:

>>
>> Hi Keean,
>>
>> First of all, thank you for your answers. I have tried your solution 
>> using TypeEq.
>>
>> instance (Datasource l k' v', TypeEq k k' z, Datasource' z l r k v) =>
>>  Datasource (JoinedDS l r) k v where
>>  _dsread (JoinedDS refl refr) k = do { l <- readIORef refl;
>>                                        r <- readIORef 
>> refr;                                     
>>                                        (z,l,r,v) <- _dsread' (l,r) k;
>>                                        writeIORef refl l;
>>                                        writeIORef refr r;
>>                                        return (JoinedDS refl refr, v);
>>                                      }
>
    _dsread (JoinedDS l r) k = _dsread' (typeEq (undefined::k') k) l r k

>>
>> class Datasource' z l r k v | l r k -> v where
>
>
> class Datasource' z l r k v | z l r k -> v where
>
>>  _dsread'  :: (l,r) -> k -> IO (z,l,r,Maybe v)
>>  _dswrite' :: (l,r) -> k -> v -> IO (z,l,r)
>> instance Datasource l k v => Datasource' HTrue  l r k v where
>>  _dsread' (l,r) k = do { (l,v) <- _dsread l k;
>>                          return (hTrue, l, r, v);
>
The type says the return type of Datasource' is v where v is the type 
resturned from _dsread so:

   _dsread' _ (l,r) k = _dsread l k

The types are determined by the instance... (I don't understand why you 
are trying to return
hTrue????

    _dsread :: s -> k -> v

and for Datasource'

    _dsread :: z -> l -> r -> k -> v

>>                        }
>> instance Datasource r k v => Datasource' HFalse l r k v where
>>  _dsread' (l,r) k = do { (r,v) <- _dsread r k;
>>                          return (hFalse, l, r, v);
>>                        }
>>
>> This compiles.
>>
>> I cannot, however, include type z in the fundep of Datasource', since 
>> this conflicts with Datasource ds k v | ds k -> v. Furthermore, I do 
>> not understand how the key and value types of my right datasource (r 
>> k v) is bound to the instance of Datasource (JoinedDS l r) k v, since 
>> in the premisse (Datasource l k' v', TypeEq k k' z, Datasource' z l r 
>> k v), nothing is said about Datasource r k'' v''. However, I could be 
>> wrong in this, since Datasource r k v is in the premisse of instance 
>> Datasource r k v => Datsource' HFalse l r k v.
>>
>> However, my problem is, that when I use this code:
>>
>> do {joined <- createJoinedDS' x y;
>>      (joined,(v::Maybe Int)) <- _dsread joined (2.0::Float);
>>     }
>>
>> {- | Easy constructor -}
>> createJoinedDS :: (IORef left) -> (IORef right) -> JoinedDS left right
>> createJoinedDS left right = JoinedDS left right
>> createJoinedDS' :: left -> right -> IO (JoinedDS left right)
>> createJoinedDS' l r = do { left <- newIORef l;
>>                           right <- newIORef r;
>>                           return (createJoinedDS left right);
>>                         }
>>
>> the compiler will complain:
>>
>>  Could not deduce (Datasource' z1 l r k v)
>>      from the context (Datasource (JoinedDS l r) k v,
>>                        Datasource l k' v',
>>                        TypeEq k k' z,
>>                        Datasource' z l r k v)
>>      arising from use of `_dsread''
>>
>> It seems to be the case that it cannot decide on the type of z.
>>
> See change above!
>
> Also note type of fundep for Datasource should now be:
>
> class Datasource s k v | s -> k v where ...
>
>    Keean.
>
> _______________________________________________
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users at haskell.org
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users




More information about the Glasgow-haskell-users mailing list