n-Tuple maps
Jean-Philippe Bernardy
jeanphilippe.bernardy at gmail.com
Mon Mar 6 16:52:49 EST 2006
Hello Adrian,
On 3/6/06, Adrian Hey <ahey at iee.org> wrote:
> Hello Jean-Philippe,
>
> I haven't had much time to study this, but in the light of recent
> discussions about generalised tries I played about a little last night
> and did have a go at producing n-Tuple maps from instances of your classes.
> e.g. for pairs I ended up trying to define something like this..
>
> instance (MapLike c1 k1 c2, MapLike c2 k2 a) => MapLike (Map2 c1) (k1,k2) a
> where..
Not sure I got what you want to do exactly, but here's what I came up with:
(using Indexed because it's lighter, but the idea is the same for Map.)
module Map2 where
import Data.Collections
newtype Map2 c1 c2 k1 k2 v2 = Map2 c1
instance (Indexed c1 k1 c2, Indexed c2 k2 v2) => Indexed (Map2 c1 c2
k1 k2 v2) (k1,k2) v2 where
(!) (Map2 c1) (k1,k2) = (c1 ! k1) ! k2
> I must admit I found it hard going, but maybe I'm just using it wrong and
> I didn't have much time to play about with alternatives. Perhaps you'd care
> to give it a shot.
You "just" need to witness the types you define Map2 for as
parameters. A bit tricky, I grant you, but nonetheless logical. Once I
got used to it I didn't find it any more difficult than the
constructor-class approach.
Cheers,
JP.
More information about the Libraries
mailing list