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

2005-03-31 Thread Keean Schupke
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@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


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

2005-03-31 Thread Keean Schupke
Not at all... You can have Datasource s k v | s k -> v ... but I have't 
time to do it now...

By the way that wasn't the change I was talking about!
class Datasource' z l r k v | z l r k -> v
The 'z' was missing from your fundep.
   Keean.
Robert van Herk wrote:

See change above!
Also note type of fundep for Datasource should now be:
class Datasource s k v | s -> k v where ...

I see But the cool thing was, that my datasources were generic, in 
the sence that they could store multiple k's and v's. Now, they would 
be unique for the actual storage mechanism used, meaning, for example, 
that I could only read values from 1 table, if I'd instantiate the 
datasource for a database coupling.

Currently, I use the Boilerplate approach to make it possible to store 
multiple types in one datasource, for example:

data MyKeyVal = IntXString Int String
| FloatXInt  Float Int
deriving (Eq, Ord, Show)
Furthermore, I generate an instance of KeyHasValue, to tell my 
framework which keys are valid for a datasource, for example:

instance KeyHasValue MyKeyVal Int String where
constructor = IntXString
instance KeyHasValue MyKeyVal Float Int where
constructor = FloatXInt
I have an instance
instance (..., KeyHasValue a k v) =>
Datasource [a] k v where ...
This way, I can read Ints from a [MyKeyVal], and get a String, and 
read Floats, and get an Int. If I would have a fundep
class Datasource s k v | s -> k v where ...

this wouldn't be possible anymore, I guess?
Regards,
Robert
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


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

2005-03-31 Thread Keean Schupke
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@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


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

2005-03-31 Thread Robert van Herk

See change above!
Also note type of fundep for Datasource should now be:
class Datasource s k v | s -> k v where ...

I see But the cool thing was, that my datasources were generic, in 
the sence that they could store multiple k's and v's. Now, they would be 
unique for the actual storage mechanism used, meaning, for example, that 
I could only read values from 1 table, if I'd instantiate the datasource 
for a database coupling.

Currently, I use the Boilerplate approach to make it possible to store 
multiple types in one datasource, for example:

data MyKeyVal = IntXString Int String
| FloatXInt  Float Int
deriving (Eq, Ord, Show)
Furthermore, I generate an instance of KeyHasValue, to tell my framework 
which keys are valid for a datasource, for example:

instance KeyHasValue MyKeyVal Int String where
constructor = IntXString
instance KeyHasValue MyKeyVal Float Int where
constructor = FloatXInt
I have an instance
instance (..., KeyHasValue a k v) =>
Datasource [a] k v where ...
This way, I can read Ints from a [MyKeyVal], and get a String, and read 
Floats, and get an Int. If I would have a fundep
class Datasource s k v | s -> k v where ...

this wouldn't be possible anymore, I guess?
Regards,
Robert
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


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

2005-03-31 Thread Robert van Herk
Sorry, oops again:
The problem is that it complains that it cannot find an instance for
 Datasource' z [MyKeyVal] [MyKeyVal] Float Int
Whilst I have an instance
 Datasource [MyKeyVal] Float Int
Thus, it seems that it needs an explicit type for the z here.
Both datasources stored in the joined datasource are of type [MyKeyVal], 
so I would expect this to compile correctly, and then take the left 
datasource.

Sorry that my explanation is all so confusing
Robert
--- Begin Message ---
Sorry, this is the compiler error I get:
No instances for (KeyHasValue MyKeyVal k' v',
 Datasource.Tools.FakePrelude.TypeEq Float k' z,
 Datasource' z [MyKeyVal] [MyKeyVal] Float Int)
When I am trying to do
 do { createJoinedDS' x x;
 (joined,(v::Maybe Int)) <- _dsread joined (2.0::Float);
  }
Robert
--- Begin Message ---
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@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
--- End Message ---
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
--- End Message ---
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


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

2005-03-31 Thread Keean Schupke
Robert van Herk wrote:
Sorry, this is the compiler error I get:
No instances for (KeyHasValue MyKeyVal k' v',
 Datasource.Tools.FakePrelude.TypeEq Float k' z,
 Datasource' z [MyKeyVal] [MyKeyVal] Float Int)
When I am trying to do
 do { createJoinedDS' x x;
 (joined,(v::Maybe Int)) <- _dsread joined (2.0::Float);
  }
Robert
----
Subject:
Re: Allowing duplicate instances in GHC 6.4
From:
Robert van Herk <[EMAIL PROTECTED]>
Date:
Thu, 31 Mar 2005 16:49:07 +0200
To:
glasgow-haskell-users@haskell.org
To:
glasgow-haskell-users@haskell.org
Return-Path:
<[EMAIL PROTECTED]>
X-Original-To:
[EMAIL PROTECTED]
Delivered-To:
[EMAIL PROTECTED]
Received:
from mail.students.cs.uu.nl (localhost.localdomain [127.0.0.1]) by 
mail.students.cs.uu.nl (Postfix) with ESMTP id 85339225D8C for 
<[EMAIL PROTECTED]>; Thu, 31 Mar 2005 16:54:12 +0200 (CEST)
Received:
from mail.cs.uu.nl (dusk.cs.uu.nl [131.211.80.10]) by 
mail.students.cs.uu.nl (Postfix) with ESMTP id 68C95225D84 for 
<[EMAIL PROTECTED]>; Thu, 31 Mar 2005 16:54:12 +0200 (CEST)
Received:
by mail.cs.uu.nl (Postfix) id EF0D9A35E2; Thu, 31 Mar 2005 16:54:11 
+0200 (CEST)
Delivered-To:
[EMAIL PROTECTED]
Received:
from mail.cs.uu.nl (localhost.localdomain [127.0.0.1]) by 
mail.cs.uu.nl (Postfix) with ESMTP id D9C06A35F7; Thu, 31 Mar 2005 
16:54:11 +0200 (CEST)
Received:
from www.haskell.org (bugs.haskell.org [128.36.229.215]) by 
mail.cs.uu.nl (Postfix) with ESMTP id 99FA2A35E2; Thu, 31 Mar 2005 
16:54:11 +0200 (CEST)
Received:
from haskell.cs.yale.edu (localhost.localdomain [127.0.0.1]) by 
www.haskell.org (Postfix) with ESMTP id 666A436825E; Thu, 31 Mar 2005 
09:36:48 -0500 (EST)
X-Original-To:
glasgow-haskell-users@haskell.org
Delivered-To:
glasgow-haskell-users@haskell.org
Received:
from mail.cs.uu.nl (dusk.cs.uu.nl [131.211.80.10]) by www.haskell.org 
(Postfix) with ESMTP id 3A87D368106 for 
; Thu, 31 Mar 2005 09:36:45 -0500 
(EST)
Received:
from mail.cs.uu.nl (localhost.localdomain [127.0.0.1]) by 
mail.cs.uu.nl (Postfix) with ESMTP id 16C67A35F7; Thu, 31 Mar 2005 
16:54:05 +0200 (CEST)
Received:
from [131.211.84.110] (mckroket.labs.cs.uu.nl [131.211.84.110]) by 
mail.cs.uu.nl (Postfix) with ESMTP id 0635AA35E2; Thu, 31 Mar 2005 
16:54:05 +0200 (CEST)
Message-ID:
<[EMAIL PROTECTED]>
User-Agent:
Mozilla Thunderbird 1.0 (Macintosh/20041206)
X-Accept-Language:
en-us, en
MIME-Version:
1.0
References:
<[EMAIL PROTECTED]> <[EMAIL PROTECTED]> 
<[EMAIL PROTECTED]> <[EMAIL PROTECTED]> 
<[EMAIL PROTECTED]> <[EMAIL PROTECTED]>
In-Reply-To:
<[EMAIL PROTECTED]>
Content-Type:
text/plain; charset=ISO-8859-1; format=flowed
Content-Transfer-Encoding:
7bit
X-AV-Checked:
ClamAV using ClamSMTP at cs.uu.nl
X-BeenThere:
glasgow-haskell-users@haskell.org
X-Mailman-Version:
2.1.5
Precedence:
list
List-Id:
The Glasgow Haskell Users Mailing List 

List-Unsubscribe:
<http://www.haskell.org/mailman/listinfo/glasgow-haskell-users>, 
<mailto:[EMAIL PROTECTED]>
List-Archive:
<http://www.haskell.org//pipermail/glasgow-haskell-users>
List-Post:
<mailto:glasgow-haskell-users@haskell.org>
List-Help:
<mailto:[EMAIL PROTECTED]>
List-Subscribe:
<http://www.haskell.org/mailman/listinfo/glasgow-haskell-users>, 
<mailto:[EMAIL PROTECTED]>
Sender:
[EMAIL PROTECTED]
Errors-To:
[EMAIL PROTECTED]
X-AV-Checked:
ClamAV using ClamSMTP at cs.uu.nl
X-AV-Checked:
ClamAV using ClamSMTP at students.cs.uu.nl
X-Spam-Checker-Version:
SpamAssassin 3.0.2-hvl (2004-11-16) on dawn.students.cs.uu.nl
X-Spam-Status:
No, score=-0.7 required=7.0 tests=AWL autolearn=ham version=3.0.2-hvl

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
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);
   }
instance Datasource r k v => Datasource' HFalse l r k v where
 _dsread'

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

2005-03-31 Thread Robert van Herk
Sorry, this is the compiler error I get:
No instances for (KeyHasValue MyKeyVal k' v',
 Datasource.Tools.FakePrelude.TypeEq Float k' z,
 Datasource' z [MyKeyVal] [MyKeyVal] Float Int)
When I am trying to do
 do { createJoinedDS' x x;
 (joined,(v::Maybe Int)) <- _dsread joined (2.0::Float);
  }
Robert
--- Begin Message ---
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@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
--- End Message ---
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Allowing duplicate instances in GHC 6.4

2005-03-31 Thread Robert van Herk
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@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Allowing duplicate instances in GHC 6.4

2005-03-25 Thread Keean Schupke
Robert van Herk wrote:
Keean Schupke wrote:
Just thought I ought to point out that all this is only necessary if 
the datasources may return different types... If you want them to 
return the same type you only need:

instance (Datasource l k v,Datasource r k v) => Datasource (JoinedDS 
l r) k v ...

As both datasources have the same key and value types, you then 
choose which 'v' to return at the value level.

Nono, the datasources I have implemented are a type safe means to 
extract (key,value) pairs from a data store. The idea is that this 
way, in a type safe fashion, e.g. database access can be abstract.

I use HaskellDB as the database access layer, and then define a 
datasource instance for any given database, so that the user does not 
need to think about the details of the actual database access: he can 
just read and write from the datasource, and the datasource will make 
sure the actual queries will be executed.

My idea now was that if I have 2 databases, and I construct 
datasources for them, it would be really cool if I was able to unite 
them, so that the programmer in the end could talk two 1 datasource, 
that allowed for accessing the 2 databases at one entry point. This 
was what I was making the JoinedDS for.

So, suppose I have 2 datasources for two different databases. One may 
have keys:
data KeysOfDS1 = KDB1_Table1 Int
   |  KDB1_Table2 Int

and values
data ValuesOfDS1 = VDB1_Table1 (Int,Int,String)
   | VDB2_Table2 (Int,Int,String)
and the other one:
data KeysOfDS2 = KDB2_Table1 String
   |  KDB2_Table2 String
data ValuesOfDS2 = VDB2_Table1 (String, Float)
   | VDB2_Table2 (String, Float, Int)
Now, these datastructures correspond to the actual tables in the 
database. My toolset will generate datasources for these types, thus 
we have instances:

instance Datasource Database1 KeysOfDS1 ValuesOfDS1
instance Datasource Database2 KeysOfDS2 ValuesOfDS2
and the cool thing would be, to combine these two datasources at a 
higher level in my datasources graph, so that I would have 1 
datasource that found out by itself which actual datasource to use, thus:

x::JoinedDS
x = JoinedDS  db1 db2 -- where dbx is a datasource Databasex KeysOfDSx 
ValuesOfDSx

Now, I would want the user to be able to read both KeysOfDS1 (which 
would yield a ValuesOfDS1) as well as KeysOfDS2 (which would yield a 
ValuesOfDS2) from x.

Herefore, I need the instances mentioned before:
instance (Datasource l k v) => Datasource (JoinedDS l r) k v where
dsread (JoinedDS l r) k = let (l, v) = dsread l k in (JoinedDS l r, v)
instance (Datasource r k v) => Datasource (JoinedDS l r) k v where
dsread (JoinedDS l r) k = let (r, v) = dsread r k in (JoinedDS l r, v)
But this, thus, yields duplicate instance errors, which I don't like :-).
Robert
P.S. Sorry for any typos, I am enjoying a rather nice bottle of wine :-).
Thats because they overlap in 'k'. However you can change the fundep:
>class Datasource s k v | s -> k v
>instance Datasource DB1 K1 V1
>instance Datasource DB2 K2 V2
>instance (Datasource l k' v',TypeEq k k' z,Datasource' z l r k v) => 
Datasource (JoinedDS l r) k v where
>
>class Datasource' z l r k v | z l r -> k v
>instance Datasource l k v => Datasource' TTrue l r k v
>instance Datasource r k v => Datasource' TFalse l r k v

Here I have used TypeEq from the HList library to determine if the type 
parameter k is the same type as the k' from datasource l. This lets k 
determine which instance from the other class gets used.

   Keean.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Allowing duplicate instances in GHC 6.4

2005-03-25 Thread Robert van Herk
Keean Schupke wrote:
Just thought I ought to point out that all this is only necessary if 
the datasources may return different types... If you want them to 
return the same type you only need:

instance (Datasource l k v,Datasource r k v) => Datasource (JoinedDS l 
r) k v ...

As both datasources have the same key and value types, you then choose 
which 'v' to return at the value level.
Nono, the datasources I have implemented are a type safe means to 
extract (key,value) pairs from a data store. The idea is that this way, 
in a type safe fashion, e.g. database access can be abstract.

I use HaskellDB as the database access layer, and then define a 
datasource instance for any given database, so that the user does not 
need to think about the details of the actual database access: he can 
just read and write from the datasource, and the datasource will make 
sure the actual queries will be executed.

My idea now was that if I have 2 databases, and I construct datasources 
for them, it would be really cool if I was able to unite them, so that 
the programmer in the end could talk two 1 datasource, that allowed for 
accessing the 2 databases at one entry point. This was what I was making 
the JoinedDS for.

So, suppose I have 2 datasources for two different databases. One may 
have keys:
data KeysOfDS1 = KDB1_Table1 Int
   |  KDB1_Table2 Int

and values
data ValuesOfDS1 = VDB1_Table1 (Int,Int,String)
   | VDB2_Table2 (Int,Int,String)
and the other one:
data KeysOfDS2 = KDB2_Table1 String
   |  KDB2_Table2 String
data ValuesOfDS2 = VDB2_Table1 (String, Float)
   | VDB2_Table2 (String, Float, Int)
Now, these datastructures correspond to the actual tables in the 
database. My toolset will generate datasources for these types, thus we 
have instances:

instance Datasource Database1 KeysOfDS1 ValuesOfDS1
instance Datasource Database2 KeysOfDS2 ValuesOfDS2
and the cool thing would be, to combine these two datasources at a 
higher level in my datasources graph, so that I would have 1 datasource 
that found out by itself which actual datasource to use, thus:

x::JoinedDS
x = JoinedDS  db1 db2 -- where dbx is a datasource Databasex KeysOfDSx 
ValuesOfDSx

Now, I would want the user to be able to read both KeysOfDS1 (which 
would yield a ValuesOfDS1) as well as KeysOfDS2 (which would yield a 
ValuesOfDS2) from x.

Herefore, I need the instances mentioned before:
instance (Datasource l k v) => Datasource (JoinedDS l r) k v where
dsread (JoinedDS l r) k = let (l, v) = dsread l k in (JoinedDS l r, v)
instance (Datasource r k v) => Datasource (JoinedDS l r) k v where
dsread (JoinedDS l r) k = let (r, v) = dsread r k in (JoinedDS l r, v)
But this, thus, yields duplicate instance errors, which I don't like :-).
Robert
P.S. Sorry for any typos, I am enjoying a rather nice bottle of wine :-).
I am not sure whether you intended Datasources to contain 
heterogeneous key or value types, and whether the loolup is supposed 
to be value or type driven. My original answer assumed a single 
Datasource contains values of different types, selected by the type of 
the key...

   Keean.

Robert van Herk wrote:
Yes, but this is not what I want. I want to be able to give a key 
that either the left or the right data source would take, and then 
return the appropriate value. Thus: if I pass it a key that would 
normally go into l, I want the value l returns me to be returned, and 
if I pass it the key that would normally go into r, I want to return 
the value r returns me.

The datasource class has a function dsread :: ds -> k -> (ds, v) -- 
read may have a side effect
Thus I want want to do something like:
instance (Datasource l k v) => Datasource (JoinedDS l r) k v where
 dsread (JoinedDS l r) k = let (l, v) = dsread l k in (JoinedDS l r, v)
instance (Datasource r k v) => Datasource (JoinedDS l r) k v where
 dsread (JoinedDS l r) k = let (r, v) = dsread r k in (JoinedDS l r, v)

It would be perfectly okay to me when the compiler would complain if 
the key and value that go into l and r are the same, but for any 
useful purpose I can think of (e.g. glueing two database couplings 
together, since I also made a Datasource instance for database 
access), this will not happen and the duplicate instances should not 
really occur, since the context of the instances makes sure only 1 
will be possible.

However, GHC only looks at the RHS (thus: Datasource (JoinedDS l r) k 
v) and then decides that both instances are the same.

So, my question was: how to overcome this.
Thanks,
Robert


___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Allowing duplicate instances in GHC 6.4

2005-03-25 Thread Keean Schupke
Just thought I ought to point out that all this is only necessary if the 
datasources may return different types... If you want them to return the 
same type you only need:

instance (Datasource l k v,Datasource r k v) => Datasource (JoinedDS l 
r) k v ...

As both datasources have the same key and value types, you then choose 
which 'v' to return at the value level.

I am not sure whether you intended Datasources to contain heterogeneous 
key or value types, and whether the loolup is supposed to be value or 
type driven. My original answer assumed a single Datasource contains 
values of different types, selected by the type of the key...

   Keean.

Robert van Herk wrote:
Yes, but this is not what I want. I want to be able to give a key that 
either the left or the right data source would take, and then return 
the appropriate value. Thus: if I pass it a key that would normally go 
into l, I want the value l returns me to be returned, and if I pass it 
the key that would normally go into r, I want to return the value r 
returns me.

The datasource class has a function dsread :: ds -> k -> (ds, v) -- 
read may have a side effect
Thus I want want to do something like:
instance (Datasource l k v) => Datasource (JoinedDS l r) k v where
 dsread (JoinedDS l r) k = let (l, v) = dsread l k in (JoinedDS l r, v)
instance (Datasource r k v) => Datasource (JoinedDS l r) k v where
 dsread (JoinedDS l r) k = let (r, v) = dsread r k in (JoinedDS l r, v)

It would be perfectly okay to me when the compiler would complain if 
the key and value that go into l and r are the same, but for any 
useful purpose I can think of (e.g. glueing two database couplings 
together, since I also made a Datasource instance for database 
access), this will not happen and the duplicate instances should not 
really occur, since the context of the instances makes sure only 1 
will be possible.

However, GHC only looks at the RHS (thus: Datasource (JoinedDS l r) k 
v) and then decides that both instances are the same.

So, my question was: how to overcome this.
Thanks,
Robert

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Allowing duplicate instances in GHC 6.4

2005-03-25 Thread Keean Schupke
There was a typo in the code I posted:
>
>class Fail
>data This_should_never_happen
>
should read:
>
>class Fail x
>data This_should_never_happen
>
Keean.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Allowing duplicate instances in GHC 6.4

2005-03-25 Thread Robert van Herk
Keean Schupke wrote:
Robert van Herk wrote:
Hi all,
I need to use duplicate instances. I read in the documentation on GHC 
6.4, that overlapping class instances checks are lazy instead of 
gready in 6.4. However, my code still gives duplicate instance errors 
when compiling in GHC 6.4.

Is the duplicate instance check still gready? Is there a way to 
overwrite that behaviour?

Right now, I have two instance of a class Datasource. Datasource 
allows the user to read (key,value) pairs.

class Datasource ds k v where
...
Now, I wanted to make a special datasource that combines two 
datasources, namely

data JoinedDS left right = JoinedDS left right
instance (Datasource left k v) => Datasource (JoinedDS left right) k 
v where
...

instance (Datasource right k v) => Datasource (JoinedDS left right) k 
v where
...

The idea is that when you combine 2 datasources in one JoinedDS, the 
user can read both types from the JoinedDS. I do not need to allow to 
combine 2 different datasources that have the same types of 
(key,value) pairs, so the duplicate instances will not occur and when 
they do, this will be by mistake. Hence, the two premisses in the 
instance declaration will never be fulfilled both at the same time 
and I do not want a duplicate instance error here.

Is there a  solution to this problem?
To resolve overlap the HEAD of the instance must be different... Might 
I suggest:

-- as value depends on source and key, requires functional dependancy
class Datasource s k v | s k -> v ...
Yes, I already had that, forgot to mention it though...
data JoinedDS l r = JoinedDS l r
instance (Datasource l k v1,Datasource r k v2) => Datasource (JoinedDS 
l r) k (v1,v2) ...

Now a joined datasource resturns a pair of values instead of a single 
value.
Yes, but this is not what I want. I want to be able to give a key that 
either the left or the right data source would take, and then return the 
appropriate value. Thus: if I pass it a key that would normally go into 
l, I want the value l returns me to be returned, and if I pass it the 
key that would normally go into r, I want to return the value r returns me.

The datasource class has a function dsread :: ds -> k -> (ds, v) -- read 
may have a side effect
Thus I want want to do something like:
instance (Datasource l k v) => Datasource (JoinedDS l r) k v where
 dsread (JoinedDS l r) k = let (l, v) = dsread l k in (JoinedDS l r, v)
instance (Datasource r k v) => Datasource (JoinedDS l r) k v where
 dsread (JoinedDS l r) k = let (r, v) = dsread r k in (JoinedDS l r, v)

It would be perfectly okay to me when the compiler would complain if the 
key and value that go into l and r are the same, but for any useful 
purpose I can think of (e.g. glueing two database couplings together, 
since I also made a Datasource instance for database access), this will 
not happen and the duplicate instances should not really occur, since 
the context of the instances makes sure only 1 will be possible.

However, GHC only looks at the RHS (thus: Datasource (JoinedDS l r) k v) 
and then decides that both instances are the same.

So, my question was: how to overcome this.
Thanks,
Robert
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Allowing duplicate instances in GHC 6.4

2005-03-25 Thread Keean Schupke
Keean Schupke wrote:
Robert van Herk wrote:
Hi all,
I need to use duplicate instances. I read in the documentation on GHC 
6.4, that overlapping class instances checks are lazy instead of 
gready in 6.4. However, my code still gives duplicate instance errors 
when compiling in GHC 6.4.

Is the duplicate instance check still gready? Is there a way to 
overwrite that behaviour?

Right now, I have two instance of a class Datasource. Datasource 
allows the user to read (key,value) pairs.

class Datasource ds k v where
...
Now, I wanted to make a special datasource that combines two 
datasources, namely

data JoinedDS left right = JoinedDS left right
instance (Datasource left k v) => Datasource (JoinedDS left right) k 
v where
...

instance (Datasource right k v) => Datasource (JoinedDS left right) k 
v where
...

The idea is that when you combine 2 datasources in one JoinedDS, the 
user can read both types from the JoinedDS. I do not need to allow to 
combine 2 different datasources that have the same types of 
(key,value) pairs, so the duplicate instances will not occur and when 
they do, this will be by mistake. Hence, the two premisses in the 
instance declaration will never be fulfilled both at the same time 
and I do not want a duplicate instance error here.

Is there a  solution to this problem?
To resolve overlap the HEAD of the instance must be different... Might 
I suggest:

-- as value depends on source and key, requires functional dependancy
class Datasource s k v | s k -> v ...
data JoinedDS l r = JoinedDS l r
instance (Datasource l k v1,Datasource r k v2) => Datasource (JoinedDS 
l r) k (v1,v2) ...

Now a joined datasource resturns a pair of values instead of a single 
value.

 
Further to this to get the exact behaviour you want, if a datasource can 
return the result using a type lifted maybe on a lookup failure then:

>class Datasource s k v | s k -> v ...
>data JoinedDS l r = JoinedDS l r
>instance (Datasource l k v1,
>Datasource r k v2,
>JoinDS v1 v2 v) => Datasource (JoinedDS l r) k v
>
>class Fail
>data This_should_never_happen
>
>data TNothing = TNothing
>data TJust a = TJust a
>
>class JoinDS l r t | l r -> t
>instance JoinDS TNothing TNothing TNothing
>instance JoinDS TNothing (TJust v) (TJust v)
>instance JoinDS (TJust u) TNothing (TJust u)
>instance Fail This_should_never_happen => JoinDS (TJust u) (TJust v) 
TNothing

Now you datasources just need to return the type "TJust v" on success 
and TNothing on failure.

   Keean.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Allowing duplicate instances in GHC 6.4

2005-03-25 Thread Keean Schupke
Robert van Herk wrote:
Hi all,
I need to use duplicate instances. I read in the documentation on GHC 
6.4, that overlapping class instances checks are lazy instead of 
gready in 6.4. However, my code still gives duplicate instance errors 
when compiling in GHC 6.4.

Is the duplicate instance check still gready? Is there a way to 
overwrite that behaviour?

Right now, I have two instance of a class Datasource. Datasource 
allows the user to read (key,value) pairs.

class Datasource ds k v where
...
Now, I wanted to make a special datasource that combines two 
datasources, namely

data JoinedDS left right = JoinedDS left right
instance (Datasource left k v) => Datasource (JoinedDS left right) k v 
where
...

instance (Datasource right k v) => Datasource (JoinedDS left right) k 
v where
...

The idea is that when you combine 2 datasources in one JoinedDS, the 
user can read both types from the JoinedDS. I do not need to allow to 
combine 2 different datasources that have the same types of 
(key,value) pairs, so the duplicate instances will not occur and when 
they do, this will be by mistake. Hence, the two premisses in the 
instance declaration will never be fulfilled both at the same time and 
I do not want a duplicate instance error here.

Is there a  solution to this problem?
To resolve overlap the HEAD of the instance must be different... Might I 
suggest:

-- as value depends on source and key, requires functional dependancy
class Datasource s k v | s k -> v ...
data JoinedDS l r = JoinedDS l r
instance (Datasource l k v1,Datasource r k v2) => Datasource (JoinedDS l 
r) k (v1,v2) ...

Now a joined datasource resturns a pair of values instead of a single value.
   Keean.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Allowing duplicate instances in GHC 6.4

2005-03-25 Thread Robert van Herk
Hi all,
I need to use duplicate instances. I read in the documentation on GHC 
6.4, that overlapping class instances checks are lazy instead of gready 
in 6.4. However, my code still gives duplicate instance errors when 
compiling in GHC 6.4.

Is the duplicate instance check still gready? Is there a way to 
overwrite that behaviour?

Right now, I have two instance of a class Datasource. Datasource allows 
the user to read (key,value) pairs.

class Datasource ds k v where
...
Now, I wanted to make a special datasource that combines two 
datasources, namely

data JoinedDS left right = JoinedDS left right
instance (Datasource left k v) => Datasource (JoinedDS left right) k v 
where
...

instance (Datasource right k v) => Datasource (JoinedDS left right) k v 
where
...

The idea is that when you combine 2 datasources in one JoinedDS, the 
user can read both types from the JoinedDS. I do not need to allow to 
combine 2 different datasources that have the same types of (key,value) 
pairs, so the duplicate instances will not occur and when they do, this 
will be by mistake. Hence, the two premisses in the instance declaration 
will never be fulfilled both at the same time and I do not want a 
duplicate instance error here.

Is there a  solution to this problem?
Thanks,
Robert
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users