instance Functor Set, was: Re: Export lists in modules

Jim Apple jbapple+haskell-prime at gmail.com
Tue Feb 28 16:43:22 EST 2006


On 2/28/06, Johannes Waldmann <waldmann at imn.htwk-leipzig.de> wrote:
> Malcolm Wallace wrote:
>
> > But if contexts-on-datatypes worked correctly,
> >
> >     data Set a = Ord a => ....
> >
> > then even the "real" map from Data.Set:
> >
> >     map :: (Ord a, Ord b) => (a -> b) -> Set a -> Set b
> >
> > could be an instance method of Functor.
>
> I'd love that. But I don't quite understand:
> do you think this is/should be possible with:
> current Haskell? Haskell-Prime? Current ghc (what extensions)?

as Oleg:

{-# OPTIONS -fglasgow-exts #-}
{-# OPTIONS -fallow-undecidable-instances  #-}

module Map where

import qualified Data.Set

class MyMap f a b where
    myMap :: (a -> b) -> f a -> f b
instance (Functor f) => MyMap f a b where
    myMap = fmap
instance (Ord a, Ord b) => MyMap Data.Set.Set a b where
    myMap = Data.Set.map

Jim


More information about the Haskell-prime mailing list