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

Keean Schupke k.schupke at imperial.ac.uk
Thu Mar 31 13:14:20 EST 2005


In the case where a datasource is determined by 's' and 'k', we need to 
return a different
type depending on sucess or failure:

 >data TJust t = TJust t
 >data TNothing = TNothing
 >
 >class Datasource s k v | s k -> v where
 >    dsread :: s -> k -> v
 >instance (Datasource l k v',Datasource r k v'',Datasource' v' v'' v)
 >    => Datasource (JoinedDS l r) k v where
 >    dsread (JoinedDS l r) k =  dsread' (dsread l k) (dsread r k)
 >
 >class Datasource' l r v | l r -> v where
 >    dsread' :: l -> r -> v
 >instance Datasource' TNothing TNothing TNothing where
 >    dsread' _ _ = TNothing
 >instance Datasource' (TJust l) TNothing (TJust l) where
 >    dsread' t _ = t
 >instance Datasource' TNothing (TJust r) (TJust r) where
 >    dsread' _ t = t
 >instance Datasource' (TJust l) (TJust r) TNothing where
 >    dsread' _ _ = TNothing

Now all you need to do is arrange for individual datasources to
return (TJust v) if that combination of source and key exist and
TNothing if they dont. Something like:

 >instance Datasource Source1 Key1 (TJust Value1)
 >instance Datasource Source1 Key2 TNothing
 >
 >instance Datasource Source2 Key1 TNothing
 >instance Datasource Source2 Key2 (TJust Value2)

This is a simple implementation, using TypeEq, you can generically
reject with TNothing all datasource instances not specifically defined.

    Keean.

>
> 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);
>                                      }
>
> class Datasource' z l r k v | 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);
>                        }
> 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.
>
> Would you know how to solve this?
>
> Regards,
>
> Robert
>
> _______________________________________________
> 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