Re: Container type classes

2019-06-03 Thread Carter Schonwald
http://hackage.haskell.org/package/EdisonCore

the Edison packages come to mind as a previous effort in this space

On Wed, May 29, 2019 at 4:08 PM Simon Peyton Jones via ghc-devs <
ghc-devs@haskell.org> wrote:

> | having a common pattern for naming the operations certainly seems
> | nice.   I am ambivalent if we do this with a class, or just name the
> | operations the same way, and use the module system.
>
> This was my reaction too.  Consistent naming, yes.  Using a type class,
> when every invocation is at a statically known type (i.e. not leveraging
> the type class) seems less good.
>
> For example, eqType :: Type -> Type -> Bool, and I can search for every
> invocation of eqType.  That can be very useful.  Searching for every use of
> (==) and figuring out which of those zillions of calls are for equality of
> Type, is much less attractive.
>
> But I'm not going to die in the trenches for this.  You are doing us a
> service by making everything systematic.  The code that is finally executed
> will, I hope and believe, be the same either way.
>
> Simon
>
>
>  The type hackery I
> | was referring to was the type family for the set elements and map
> | keys you were referring to.It looks like the maps we have are
> | uniform enough that one type family per class does the job, so I think
> the
> | class you came with looks nice.
> |
> | -Iavor
> | PS: the type hacker I was referring to was  having to add more type
> | families, for example if we had a map that can only store one type of
> | elements, but it looks like this is not the case here.
> |
> |
> | On Wed, May 29, 2019 at 3:48 AM Andreas Klebinger
> |  wrote:
> | >
> | > ghc-devs-requ...@haskell.org schrieb:
> | > > Hello,
> | > >
> | > > I think refactoring to use consistent naming is a good idea, but I
> | > > am not sure about the class idea.
> | > >
> | > > To see if it is viable, we should list the types in question and the
> | > > operations we'd like to overload.
> | > >
> | > > I find that with containers there tend to be two cases: either the
> | > > operations are similar but not exactly the same and you have to do
> | > > type hackery to make things fit, or you realize that you can just
> | > > use the same type in multiple places.
> | > >
> | > > Iavor
> | > The function prototype are already part of the merge request. See here:
> | > https://nam06.safelinks.protection.outlook.com/?url=https%3A%2F%2Fgitl
> | > ab.haskell.org%2Fghc%2Fghc%2Fblob%2Fa0781d746c223636a90a0837fe678aab5b
> | > 70e4b6%2Fcompiler%2Fstructures%2FCollections.hsdata=02%7C01%7Csim
> | > onpj%40microsoft.com%7C4fe7780126ff475c3c7308d6e45e8586%7C72f988bf86f1
> | > 41af91ab2d7cd011db47%7C1%7C0%7C636947491952787823sdata=lgu4jc9g3x
> | > H%2B9nDorkvPZjts9L1RpVLpexed1uJnyXA%3Dreserved=0
> | >
> | > As for the data structures in question these are:
> | > * EnumSet
> | > * Data.IntSet
> | > * Data.Set
> | > * UniqSet
> | > * UniqDSet
> | >
> | > * Data.IntMap
> | > * Data.Map
> | > * LabelMap
> | > * UniqFM
> | > * UniqDFM
> | > * UniqMap
> | >
> | > * Maybe the TrieMap Variants
> | >
> | > Maybe I missed some but these are all I can think of currently. But
> | > they are already plenty.
> | >
> | > Imo using type classes IS a kind of type hackery required "to make
> | > things fit".
> | > ___
> | > ghc-devs mailing list
> | > ghc-devs@haskell.org
> | > https://nam06.safelinks.protection.outlook.com/?url=http%3A%2F%2Fmail.
> | > haskell.org%2Fcgi-bin%2Fmailman%2Flistinfo%2Fghc-devsdata=02%7C01
> | > %7Csimonpj%40microsoft.com%7C4fe7780126ff475c3c7308d6e45e8586%7C72f988
> | > bf86f141af91ab2d7cd011db47%7C1%7C0%7C636947491952787823sdata=fjw2
> | > XfNXANsWXsCb4mfQV0UFvyNNW%2BjqUhhCbOcr%2FhQ%3Dreserved=0
> | ___
> | ghc-devs mailing list
> | ghc-devs@haskell.org
> |
> https://nam06.safelinks.protection.outlook.com/?url=http%3A%2F%2Fmail.hask
> | ell.org%2Fcgi-bin%2Fmailman%2Flistinfo%2Fghc-
> | devsdata=02%7C01%7Csimonpj%40microsoft.com
> %7C4fe7780126ff475c3c7308d6
> |
> e45e8586%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C636947491952787823
> |
> mp;sdata=fjw2XfNXANsWXsCb4mfQV0UFvyNNW%2BjqUhhCbOcr%2FhQ%3Dreserved=0
> ___
> 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


Re: Container type classes

2019-05-30 Thread Clinton Mead
I'm not sure if this is related but the package Map-Classes
<http://hackage.haskell.org/package/map-classes-0.1.0.0/docs/Control-Class-Impl-Map.html>
provides
about 50 functions on around a dozen key/value like datatypes e.g. Arrays,
Maps, Sets (value is ()) etc. Even ByteStrings are included (Int -> Word8
mapping).

You should be able to fairly easily add new types and even new functions to
the instances if you give them default implementations.

On Fri, May 31, 2019 at 9:23 AM Andrey Mokhov 
wrote:

> Thanks again Iavor,
>
> Despite the type inference issue, and the fact that this requires a
> separate type class, this is the best solution I've seen so far.
>
> Cheers,
> Andrey
>
> -Original Message-
> From: Iavor Diatchki [mailto:iavor.diatc...@gmail.com]
> Sent: 30 May 2019 23:16
> To: Andrey Mokhov 
> Cc: Brandon Allbery ; Andreas Klebinger <
> klebinger.andr...@gmx.at>; ghc-devs@haskell.org
> Subject: Re: Container type classes
>
> Yeah, there is really no relation between the two parameters of `Fun`,
> so you'd have to specify the intermediate type manually. For example:
>
> add3 :: forall s. (Fun s s, Elem s ~ Int) => s -> s
> add3 = colMap @s (+1) . colMap (+2)
>
> I wouldn't say that it's a particularly convenient interface to work
> with, unless you are working in a setting where most of the containers
> have known types.
>
>
> On Thu, May 30, 2019 at 2:58 PM Andrey Mokhov
>  wrote:
> >
> > 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 
> > Cc: Andrey Mokhov ; 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 
> 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.
> > >>
> > >>
> > >>

RE: Container type classes

2019-05-30 Thread Andrey Mokhov
Thanks again Iavor,

Despite the type inference issue, and the fact that this requires a separate 
type class, this is the best solution I've seen so far.

Cheers,
Andrey

-Original Message-
From: Iavor Diatchki [mailto:iavor.diatc...@gmail.com] 
Sent: 30 May 2019 23:16
To: Andrey Mokhov 
Cc: Brandon Allbery ; Andreas Klebinger 
; ghc-devs@haskell.org
Subject: Re: Container type classes

Yeah, there is really no relation between the two parameters of `Fun`,
so you'd have to specify the intermediate type manually. For example:

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

I wouldn't say that it's a particularly convenient interface to work
with, unless you are working in a setting where most of the containers
have known types.


On Thu, May 30, 2019 at 2:58 PM Andrey Mokhov
 wrote:
>
> 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 
> Cc: Andrey Mokhov ; Andreas Klebinger 
> ; 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  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 
> >  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 
> >> Cc: ghc-devs@haskell.org; Andreas Klebinger 
> >> 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 pr

Re: Container type classes

2019-05-30 Thread Iavor Diatchki
Yeah, there is really no relation between the two parameters of `Fun`,
so you'd have to specify the intermediate type manually. For example:

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

I wouldn't say that it's a particularly convenient interface to work
with, unless you are working in a setting where most of the containers
have known types.


On Thu, May 30, 2019 at 2:58 PM Andrey Mokhov
 wrote:
>
> 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 
> Cc: Andrey Mokhov ; Andreas Klebinger 
> ; 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  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 
> >  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 
> >> Cc: ghc-devs@haskell.org; Andreas Klebinger 
> >> 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 gazillio

RE: Container type classes

2019-05-30 Thread Andrey Mokhov
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 
Cc: Andrey Mokhov ; Andreas Klebinger 
; 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  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  
> 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 
>> Cc: ghc-devs@haskell.org; Andreas Klebinger 
>> 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  
>> 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 us

Re: Container type classes

2019-05-30 Thread Brandon Allbery
I was talking in general about why you don't find instances of Monad, etc.
for Set or Map which require an additional constraint on the key.

On Thu, May 30, 2019 at 5:36 PM Andrey Mokhov 
wrote:

> Hi Brandon,
>
>
>
> Could you show the code?
>
>
>
> I have no idea how indexed monads could possibly be related here. All I
> want is to have a type class that unifies these two methods:
>
>
>
> singleton :: a -> Set a
>
> map :: Ord b => (a -> b) -> Set a -> Set b
>
>
>
> singleton :: Int -> IntSet
>
> map :: (Int -> Int) -> IntSet -> IntSet
>
>
>
> Cheers,
>
> Andrey
>
>
>
> *From:* Brandon Allbery [mailto:allber...@gmail.com]
> *Sent:* 30 May 2019 22:32
> *To:* Andrey Mokhov 
> *Cc:* Artem Pelenitsyn ; Andreas Klebinger <
> klebinger.andr...@gmx.at>; ghc-devs@haskell.org
> *Subject:* Re: Container type classes
>
>
>
> 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 
> *Cc:* ghc-devs@haskell.org; Andreas Klebinger 
> *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 
> 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 defi

Re: Container type classes

2019-05-30 Thread Iavor Diatchki
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  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  
> 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 
>> Cc: ghc-devs@haskell.org; Andreas Klebinger 
>> 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  
>> 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
>>
>>

RE: Container type classes

2019-05-30 Thread Andrey Mokhov
Hi Brandon,

Could you show the code?

I have no idea how indexed monads could possibly be related here. All I want is 
to have a type class that unifies these two methods:

singleton :: a -> Set a
map :: Ord b => (a -> b) -> Set a -> Set b

singleton :: Int -> IntSet
map :: (Int -> Int) -> IntSet -> IntSet

Cheers,
Andrey

From: Brandon Allbery [mailto:allber...@gmail.com]
Sent: 30 May 2019 22:32
To: Andrey Mokhov 
Cc: Artem Pelenitsyn ; Andreas Klebinger 
; ghc-devs@haskell.org
Subject: Re: Container type classes

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 
mailto: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<mailto:a.pelenit...@gmail.com>]
Sent: 30 May 2019 20:56
To: Andrey Mokhov 
mailto:andrey.mok...@newcastle.ac.uk>>
Cc: ghc-devs@haskell.org<mailto:ghc-devs@haskell.org>; Andreas Klebinger 
mailto: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 
mailto: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<mailto:ghc-devs@haskell.org>
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs
_

Re: Container type classes

2019-05-30 Thread Brandon Allbery
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 
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 
> *Cc:* ghc-devs@haskell.org; Andreas Klebinger 
> *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 
> 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


RE: Container type classes

2019-05-30 Thread Andrey Mokhov
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 
Cc: ghc-devs@haskell.org; Andreas Klebinger 
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 
mailto: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<mailto: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


Re: Container type classes

2019-05-30 Thread Artem Pelenitsyn
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 
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


RE: Container type classes

2019-05-30 Thread Andrey Mokhov
> If you care about performance then explicit dictionary passing is
> going to be worse than using type classes.

Of course! But explicit dictionary passing works great for tests: the code size 
is reduced from O(#modules * #tests) when using the module system to O(#modules 
+ #tests) when using dictionaries.

For example, in the algebraic-graphs library, I have 500+ generic tests and 
around 10 modules. I don't want to write 5000 tests! Here is an example generic 
test which uses explicit dictionary passing: 
https://github.com/snowleopard/alga/blob/master/test/Algebra/Graph/Test/Generic.hs#L303-L319.
 I don't think it would be possible to reuse this test for different graph data 
types by using the module system instead of dictionaries. (Perhaps, Backpack 
could help? I don't know it very well.)

Cheers,
Andrey

-Original Message-
From: Matthew Pickering [mailto:matthewtpicker...@gmail.com] 
Sent: 30 May 2019 18:26
To: Andrey Mokhov 
Cc: ghc-devs@haskell.org; Andreas Klebinger 
Subject: Re: Container type classes

If you care about performance then explicit dictionary passing is
going to be worse than using type classes.

At that point though, what do you gain from using the module system as
you are just going to pass the same dictionaries into every function
and never change them.

So, for me, keep using modules but make the APIs of each module more
consistent if you think it's worthwhile.

On Thu, May 30, 2019 at 6:11 PM Andrey Mokhov
 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


Re: Container type classes

2019-05-30 Thread Matthew Pickering
If you care about performance then explicit dictionary passing is
going to be worse than using type classes.

At that point though, what do you gain from using the module system as
you are just going to pass the same dictionaries into every function
and never change them.

So, for me, keep using modules but make the APIs of each module more
consistent if you think it's worthwhile.

On Thu, May 30, 2019 at 6:11 PM Andrey Mokhov
 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


RE: Container type classes

2019-05-30 Thread Andrey Mokhov
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


RE: Container type classes

2019-05-29 Thread Simon Peyton Jones via ghc-devs
| having a common pattern for naming the operations certainly seems
| nice.   I am ambivalent if we do this with a class, or just name the
| operations the same way, and use the module system. 

This was my reaction too.  Consistent naming, yes.  Using a type class, when 
every invocation is at a statically known type (i.e. not leveraging the type 
class) seems less good.

For example, eqType :: Type -> Type -> Bool, and I can search for every 
invocation of eqType.  That can be very useful.  Searching for every use of 
(==) and figuring out which of those zillions of calls are for equality of 
Type, is much less attractive.

But I'm not going to die in the trenches for this.  You are doing us a service 
by making everything systematic.  The code that is finally executed will, I 
hope and believe, be the same either way.

Simon


 The type hackery I
| was referring to was the type family for the set elements and map
| keys you were referring to.It looks like the maps we have are
| uniform enough that one type family per class does the job, so I think the
| class you came with looks nice.
| 
| -Iavor
| PS: the type hacker I was referring to was  having to add more type
| families, for example if we had a map that can only store one type of
| elements, but it looks like this is not the case here.
| 
| 
| On Wed, May 29, 2019 at 3:48 AM Andreas Klebinger
|  wrote:
| >
| > ghc-devs-requ...@haskell.org schrieb:
| > > Hello,
| > >
| > > I think refactoring to use consistent naming is a good idea, but I
| > > am not sure about the class idea.
| > >
| > > To see if it is viable, we should list the types in question and the
| > > operations we'd like to overload.
| > >
| > > I find that with containers there tend to be two cases: either the
| > > operations are similar but not exactly the same and you have to do
| > > type hackery to make things fit, or you realize that you can just
| > > use the same type in multiple places.
| > >
| > > Iavor
| > The function prototype are already part of the merge request. See here:
| > https://nam06.safelinks.protection.outlook.com/?url=https%3A%2F%2Fgitl
| > ab.haskell.org%2Fghc%2Fghc%2Fblob%2Fa0781d746c223636a90a0837fe678aab5b
| > 70e4b6%2Fcompiler%2Fstructures%2FCollections.hsdata=02%7C01%7Csim
| > onpj%40microsoft.com%7C4fe7780126ff475c3c7308d6e45e8586%7C72f988bf86f1
| > 41af91ab2d7cd011db47%7C1%7C0%7C636947491952787823sdata=lgu4jc9g3x
| > H%2B9nDorkvPZjts9L1RpVLpexed1uJnyXA%3Dreserved=0
| >
| > As for the data structures in question these are:
| > * EnumSet
| > * Data.IntSet
| > * Data.Set
| > * UniqSet
| > * UniqDSet
| >
| > * Data.IntMap
| > * Data.Map
| > * LabelMap
| > * UniqFM
| > * UniqDFM
| > * UniqMap
| >
| > * Maybe the TrieMap Variants
| >
| > Maybe I missed some but these are all I can think of currently. But
| > they are already plenty.
| >
| > Imo using type classes IS a kind of type hackery required "to make
| > things fit".
| > ___
| > ghc-devs mailing list
| > ghc-devs@haskell.org
| > https://nam06.safelinks.protection.outlook.com/?url=http%3A%2F%2Fmail.
| > haskell.org%2Fcgi-bin%2Fmailman%2Flistinfo%2Fghc-devsdata=02%7C01
| > %7Csimonpj%40microsoft.com%7C4fe7780126ff475c3c7308d6e45e8586%7C72f988
| > bf86f141af91ab2d7cd011db47%7C1%7C0%7C636947491952787823sdata=fjw2
| > XfNXANsWXsCb4mfQV0UFvyNNW%2BjqUhhCbOcr%2FhQ%3Dreserved=0
| ___
| ghc-devs mailing list
| ghc-devs@haskell.org
| https://nam06.safelinks.protection.outlook.com/?url=http%3A%2F%2Fmail.hask
| ell.org%2Fcgi-bin%2Fmailman%2Flistinfo%2Fghc-
| devsdata=02%7C01%7Csimonpj%40microsoft.com%7C4fe7780126ff475c3c7308d6
| e45e8586%7C72f988bf86f141af91ab2d7cd011db47%7C1%7C0%7C636947491952787823
| mp;sdata=fjw2XfNXANsWXsCb4mfQV0UFvyNNW%2BjqUhhCbOcr%2FhQ%3Dreserved=0
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Container type classes

2019-05-29 Thread Iavor Diatchki
Hi,

having a common pattern for naming the operations certainly seems
nice.   I am ambivalent if we do this with a class, or just name the
operations the same way, and use the module system.  The type hackery
I was referring to was the type family for the set elements and map
keys you were referring to.It looks like the maps we have are
uniform enough that one type family per class does the job, so I think
the class you came with looks nice.

-Iavor
PS: the type hacker I was referring to was  having to add more type
families, for example if we had a map that can only store one type of
elements, but it looks like this is not the case here.


On Wed, May 29, 2019 at 3:48 AM Andreas Klebinger
 wrote:
>
> ghc-devs-requ...@haskell.org schrieb:
> > Hello,
> >
> > I think refactoring to use consistent naming is a good idea, but I am
> > not sure about the class idea.
> >
> > To see if it is viable, we should list the types in question and the
> > operations we'd like to overload.
> >
> > I find that with containers there tend to be two cases: either the
> > operations are similar but not exactly the same and you have to do
> > type hackery to make things fit, or you realize that you can just use
> > the same type in multiple places.
> >
> > Iavor
> The function prototype are already part of the merge request. See here:
> https://gitlab.haskell.org/ghc/ghc/blob/a0781d746c223636a90a0837fe678aab5b70e4b6/compiler/structures/Collections.hs
>
> As for the data structures in question these are:
> * EnumSet
> * Data.IntSet
> * Data.Set
> * UniqSet
> * UniqDSet
>
> * Data.IntMap
> * Data.Map
> * LabelMap
> * UniqFM
> * UniqDFM
> * UniqMap
>
> * Maybe the TrieMap Variants
>
> Maybe I missed some but these are all I can think of currently. But they
> are already plenty.
>
> Imo using type classes IS a kind of type hackery required "to make
> things fit".
> ___
> 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


Re: Container type classes

2019-05-29 Thread Andreas Klebinger

ghc-devs-requ...@haskell.org schrieb:

Hello,

I think refactoring to use consistent naming is a good idea, but I am
not sure about the class idea.

To see if it is viable, we should list the types in question and the
operations we'd like to overload.

I find that with containers there tend to be two cases: either the
operations are similar but not exactly the same and you have to do
type hackery to make things fit, or you realize that you can just use
the same type in multiple places.

Iavor

The function prototype are already part of the merge request. See here:
https://gitlab.haskell.org/ghc/ghc/blob/a0781d746c223636a90a0837fe678aab5b70e4b6/compiler/structures/Collections.hs

As for the data structures in question these are:
* EnumSet
* Data.IntSet
* Data.Set
* UniqSet
* UniqDSet

* Data.IntMap
* Data.Map
* LabelMap
* UniqFM
* UniqDFM
* UniqMap

* Maybe the TrieMap Variants

Maybe I missed some but these are all I can think of currently. But they
are already plenty.

Imo using type classes IS a kind of type hackery required "to make
things fit".
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs