Many thanks Iavor,

This looks very promising! I played with your encoding a little, but quickly 
came across type inference issues. The following doesn't compile:

add3 :: (Fun s s, Elem s ~ Int) => s -> s
add3 = colMap (+1) . colMap (+2)

I'm getting:

    * Could not deduce: Elem a0 ~ Int
      from the context: (Fun s s, Elem s ~ Int)
        bound by the type signature for:
                   add3 :: forall s. (Fun s s, Elem s ~ Int) => s -> s
      Expected type: Elem a0 -> Elem s
        Actual type: Int -> Int
      The type variable `a0' is ambiguous

Fun s s is supposed to say that the intermediate type is `s` too, but I guess 
this is not how type class resolution works.

Cheers,
Andrey

-----Original Message-----
From: Iavor Diatchki [mailto:iavor.diatc...@gmail.com] 
Sent: 30 May 2019 22:38
To: Brandon Allbery <allber...@gmail.com>
Cc: Andrey Mokhov <andrey.mok...@newcastle.ac.uk>; Andreas Klebinger 
<klebinger.andr...@gmx.at>; ghc-devs@haskell.org
Subject: Re: Container type classes

This is how you could define `map`.  This is just for fun, and to
discuss Haskell idioms---I am not suggesting we should do it.  Of
course, it might be a bit more general than what you'd like---for
example it allows defining instances like `Fun IntSet (Set Int)` that,
perhaps?, you'd like to disallow:

{-# LANGUAGE MultiParamTypeClasses, TypeFamilies #-}

import Data.Set (Set)
import qualified Data.Set as Set
import Data.IntSet (IntSet)
import qualified Data.IntSet as ISet

class Col t where
  type Elem t
  -- ... As in Andreas's example

class (Col a, Col b) => Fun a b where
  colMap :: (Elem a -> Elem b) -> a -> b

instance Col (Set a) where
  type Elem (Set a) = a

instance Col IntSet where
  type Elem IntSet = Int

instance Fun IntSet IntSet where
  colMap = ISet.map

instance Ord b => Fun (Set a) (Set b) where
  colMap = Set.map

On Thu, May 30, 2019 at 2:32 PM Brandon Allbery <allber...@gmail.com> wrote:
>
> They can, with more work. You want indexed monads, so you can describe types 
> that have e.g. an ordering constraint as well as the Monad constraint.
>
> On Thu, May 30, 2019 at 5:26 PM Andrey Mokhov <andrey.mok...@newcastle.ac.uk> 
> wrote:
>>
>> Hi Artem,
>>
>>
>>
>> Thanks for the pointer, but this doesn’t seem to be a solution to my 
>> challenge: they simply give up on overloading `map` for both Set and IntSet. 
>> As a result, we can’t write polymorphic functions over Set and IntSet if 
>> they involve any mapping.
>>
>>
>>
>> I looked at the prototype by Andreas Klebinger, and it doesn’t include the 
>> method `setMap` either.
>>
>>
>>
>> Perhaps, Haskell’s type classes just can’t cope with this problem.
>>
>>
>>
>> *ducks for cover*
>>
>>
>>
>> Cheers,
>>
>> Andrey
>>
>>
>>
>> From: Artem Pelenitsyn [mailto:a.pelenit...@gmail.com]
>> Sent: 30 May 2019 20:56
>> To: Andrey Mokhov <andrey.mok...@newcastle.ac.uk>
>> Cc: ghc-devs@haskell.org; Andreas Klebinger <klebinger.andr...@gmx.at>
>> Subject: Re: Container type classes
>>
>>
>>
>> Hi Andrey,
>>
>>
>>
>> FWIW, mono-traversable (http://hackage.haskell.org/package/mono-traversable) 
>> suggests decoupling IsSet and Funtor-like.
>>
>>
>>
>> In a nutshell, they define the IsSet class (in Data.Containers) with typical 
>> set operations like member and singleton, union and intersection. And then 
>> they tackle a (seemingly) independent problem of mapping monomorphic 
>> containers (like IntSet, ByteString, etc.) with a separate class MonoFunctor 
>> (in Data.MonoTraversable):
>>
>>
>>
>> class MonoFunctor mono where
>>     omap :: (Element mono -> Element mono) -> mono -> mono
>>
>>
>>
>> And gazillion of instances for both polymorphic containers with a fixed type 
>> parameter and monomorphic ones.
>>
>>
>>
>> --
>>
>> Best wishes,
>>
>> Artem
>>
>>
>>
>> On Thu, 30 May 2019 at 20:11, Andrey Mokhov <andrey.mok...@newcastle.ac.uk> 
>> wrote:
>>
>> Hi all,
>>
>> I tried to use type classes for unifying APIs of several similar data 
>> structures and it didn't work well. (In my case I was working with graphs, 
>> instead of sets or maps.)
>>
>> First, you rarely want to be polymorphic over the set representation, 
>> because you care about performance. You really want to use that 
>> Very.Special.Set.insert because it has the right performance characteristics 
>> for your task at hand. I found only *one* use-case for writing polymorphic 
>> functions operating on something like IsSet: the testsuite. Of course, it is 
>> very nice to write a single property test like
>>
>> memberInsertProperty x set = (member x (insert x set) == True)
>>
>> and then use it for testing all set data structures that implement `member` 
>> and `insert`. Here you don't care about performance, only about correctness!
>>
>> However, this approach leads to problems with type inference, confusing 
>> error messages, and complexity. I found that it is much nicer to use 
>> explicit dictionary passing and write something like this instead:
>>
>> memberInsertProperty SetAPI{..} x set = (member x (insert x set) == True)
>>
>> where `member` and `insert` come from the SetAPI record via RecordWildCards.
>>
>> Finally, I'm not even sure how to create a type class covering Set and 
>> IntSet with the following two methods:
>>
>> singleton :: a -> Set a
>> map :: Ord b => (a -> b) -> Set a -> Set b
>>
>> singleton :: Int -> IntSet
>> map :: (Int -> Int) -> IntSet -> IntSet
>>
>> Could anyone please enlighten me about the right way to abstract over this 
>> using type classes?
>>
>> I tried a few approaches, for example:
>>
>> class IsSet s where
>>     type Elem s
>>     singleton :: Elem s -> s
>>     map :: Ord (Elem t) => (Elem s -> Elem t) -> s -> t
>>
>> Looks nice, but I can't define the IntSet instance:
>>
>> instance IsSet IntSet where
>>     type Elem IntSet = Int
>>     singleton = IntSet.singleton
>>     map = IntSet.map
>>
>> This fails with: Couldn't match type `t' with `IntSet' -- and indeed, how do 
>> I tell the compiler that in the IntSet case s ~ t in the map signature? 
>> Shall I add more associated types, or "associated constraints" using 
>> ConstraintKinds? I tried and failed, at various stages, repeatedly.
>>
>> ...And then you discover that there is Set.cartesianProduct :: Set a -> Set 
>> b -> Set (a, b), but no equivalent in IntSet and things get even more grim.
>>
>> Cheers,
>> Andrey
>>
>> _______________________________________________
>> ghc-devs mailing list
>> ghc-devs@haskell.org
>> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>>
>> _______________________________________________
>> ghc-devs mailing list
>> ghc-devs@haskell.org
>> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
>
>
>
> --
> brandon s allbery kf8nh
> allber...@gmail.com
> _______________________________________________
> ghc-devs mailing list
> ghc-devs@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
_______________________________________________
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs

Reply via email to