Re: Container type classes

2019-05-30 Thread Clinton Mead
I'm not sure if this is related but the package Map-Classes

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.
> > >>
> > >>
> > >>
> > >> 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, 

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 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.)
> >>
> 

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 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 

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 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 

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 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.
>
> 

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
>>
>> 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 

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]
Sent: 30 May 2019 20:56
To: Andrey Mokhov 
mailto:andrey.mok...@newcastle.ac.uk>>
Cc: 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
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 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
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: Fwd: [hadrian/windows] build broken

2019-05-30 Thread Ben Gamari
Shayne Fletcher via ghc-devs  writes:

> On Thu, May 30, 2019 at 8:32 AM Alp Mestanogullari 
> wrote:
>
>> Heh, it landed less than an hour ago.
>>
>> If the error persists, you'll probably want to do a clean build, by
>> removing at the very least _build/stage1, even though I'd say it can't hurt
>> to remove _build altogether. Along with that patch, I also brought back the
>> Windows CI job and the error did not show up there, so I'm pretty confident
>> you will not run into it again with a fresh, clean build.
>>
>> It's cooking now. Looking promising :) I build fresh every time. Good news
> on the Windows CI!! On that note, how are we doing on the MacOS front ?
> (Let me know if we need resources to make that happen - might be able to
> help if so!).
>
Hi Shayne,

If you think you may be able to help with MacOS resources let's chat.
This is certainly an area where we could use help. Currently we have two
boxes which are generously provided to us by Davean Scies. These tend to
struggle with the load and consequently jobs sometimes timeout before
they are able to get a builder. It would be great to be able to do
better here.

Cheers,

- Ben



signature.asc
Description: PGP signature
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Fwd: [hadrian/windows] build broken

2019-05-30 Thread Shayne Fletcher via ghc-devs
On Thu, May 30, 2019 at 9:18 AM Alp Mestanogullari 
wrote:

> I haven't (yet) worked on making an OS X job for Hadrian. I brought back
> the Windows/Hadrian CI job with that fix, but then tried running the
> testsuite, which didn't go well, see:
>
> https://gitlab.haskell.org/ghc/ghc/merge_requests/1035
>
> https://gitlab.haskell.org/alp/ghc/-/jobs/87467
>
> This seems to have brought back a problem that Ben and I started looking
> into and which led us to disabling that job in the first place... However,
> running the testsuite is one thing, but just making sure we can build GHC
> is another.
>
Exactly. One problem at a time. Preventing changes that break the hadrian
build from landing is what I advocate we concern ourselves with today.

> I guess I can put together a patch to get us an OS X job that just builds
> GHC pretty quickly, and then later get both the Windows and OS X jobs to go
> as far as running the testsuite. That'd at least give us confidence that
> people can build GHC with Hadrian just fine on OS X.
>
Perfect.

> Regarding the resources, that certainly sounds like something that would
> help if we are to double the number of OS X builds, indeed. I'm sure Ben
> (cc'd), who handles those matters, would be happy to talk about this with
> you!
>
Excellent. @Ben, let's talk!

> In the meantime, I will prepare a patch to add an OSX/Hadrian job.
>
Thanks Alp!

-- 
Shayne Fletcher
Language Engineer
c: +1 917 699 7763
e: shayne.fletc...@daml.com
Digital Asset Holdings, LLC
4 World Trade Center150 Greenwich
Street, 47th Floor

New York, NY 10007, USA

digitalasset.com 

-- 
This message, and any attachments, is for the intended recipient(s) only, 
may contain information that is privileged, confidential and/or proprietary 
and subject to important terms and conditions available at 
http://www.digitalasset.com/emaildisclaimer.html 
. If you are not the 
intended recipient, please delete this message.
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Fwd: [hadrian/windows] build broken

2019-05-30 Thread Alp Mestanogullari
I haven't (yet) worked on making an OS X job for Hadrian. I brought back 
the Windows/Hadrian CI job with that fix, but then tried running the 
testsuite, which didn't go well, see:


https://gitlab.haskell.org/ghc/ghc/merge_requests/1035

https://gitlab.haskell.org/alp/ghc/-/jobs/87467

This seems to have brought back a problem that Ben and I started looking 
into and which led us to disabling that job in the first place... 
However, running the testsuite is one thing, but just making sure we can 
build GHC is another. I guess I can put together a patch to get us an OS 
X job that just builds GHC pretty quickly, and then later get both the 
Windows and OS X jobs to go as far as running the testsuite. That'd at 
least give us confidence that people can build GHC with Hadrian just 
fine on OS X.


Regarding the resources, that certainly sounds like something that would 
help if we are to double the number of OS X builds, indeed. I'm sure Ben 
(cc'd), who handles those matters, would be happy to talk about this 
with you!


In the meantime, I will prepare a patch to add an OSX/Hadrian job.

On 30/05/2019 15:04, Shayne Fletcher wrote:



On Thu, May 30, 2019 at 8:32 AM Alp Mestanogullari > wrote:


Heh, it landed less than an hour ago.

If the error persists, you'll probably want to do a clean build,
by removing at the very least _build/stage1, even though I'd say
it can't hurt to remove _build altogether. Along with that patch,
I also brought back the Windows CI job and the error did not show
up there, so I'm pretty confident you will not run into it again
with a fresh, clean build.

It's cooking now. Looking promising :) I build fresh every time. Good 
news on the Windows CI!! On that note, how are we doing on the MacOS 
front ? (Let me know if we need resources to make that happen - might 
be able to help if so!).


Do feel free to contact me or open a ticket if somehow the error
still shows up, even against a clean tree.

You bet. Thanks for your hard work!

--
Shayne Fletcher
Language Engineer
c: +1 917 699 7763
e: shayne.fletc...@daml.com 
Digital Asset Holdings, LLC
4 World Trade Center 150 Greenwich Street, 47th Floor 

New York, NY 10007, USA 


digitalasset.com 


This message, and any attachments, is for the intended recipient(s) 
only, may contain information that is privileged, confidential and/or 
proprietary and subject to important terms and conditions available at 
http://www.digitalasset.com/emaildisclaimer.html 
. If you are not the 
intended recipient, please delete this message. 


--
Alp Mestanogullari, Haskell Consultant
Well-Typed LLP, https://www.well-typed.com/

Registered in England and Wales, OC335890
118 Wymering Mansions, Wymering Road, London, W9 2NF, England

___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Fwd: [hadrian/windows] build broken

2019-05-30 Thread Shayne Fletcher via ghc-devs
On Thu, May 30, 2019 at 8:32 AM Alp Mestanogullari 
wrote:

> Heh, it landed less than an hour ago.
>
> If the error persists, you'll probably want to do a clean build, by
> removing at the very least _build/stage1, even though I'd say it can't hurt
> to remove _build altogether. Along with that patch, I also brought back the
> Windows CI job and the error did not show up there, so I'm pretty confident
> you will not run into it again with a fresh, clean build.
>
> It's cooking now. Looking promising :) I build fresh every time. Good news
on the Windows CI!! On that note, how are we doing on the MacOS front ?
(Let me know if we need resources to make that happen - might be able to
help if so!).

> Do feel free to contact me or open a ticket if somehow the error still
> shows up, even against a clean tree.
>
You bet. Thanks for your hard work!

-- 
Shayne Fletcher
Language Engineer
c: +1 917 699 7763
e: shayne.fletc...@daml.com
Digital Asset Holdings, LLC
4 World Trade Center150 Greenwich
Street, 47th Floor

New York, NY 10007, USA

digitalasset.com 

-- 
This message, and any attachments, is for the intended recipient(s) only, 
may contain information that is privileged, confidential and/or proprietary 
and subject to important terms and conditions available at 
http://www.digitalasset.com/emaildisclaimer.html 
. If you are not the 
intended recipient, please delete this message.
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Fwd: [hadrian/windows] build broken

2019-05-30 Thread Alp Mestanogullari

Heh, it landed less than an hour ago.

If the error persists, you'll probably want to do a clean build, by 
removing at the very least _build/stage1, even though I'd say it can't 
hurt to remove _build altogether. Along with that patch, I also brought 
back the Windows CI job and the error did not show up there, so I'm 
pretty confident you will not run into it again with a fresh, clean build.


Do feel free to contact me or open a ticket if somehow the error still 
shows up, even against a clean tree.


On 30/05/2019 13:01, Shayne Fletcher wrote:



On Thu, May 30, 2019 at 6:55 AM Shayne Fletcher 
mailto:shayne.fletc...@daml.com>> wrote:


Hi Alp,

On Fri, May 24, 2019 at 11:34 AM Shayne Fletcher
mailto:shayne.fletc...@daml.com>> wrote:


On Fri, May 24, 2019 at 7:33 AM Alp Mestanogullari
mailto:a...@well-typed.com>> wrote:

Hello Shayne,

David and I figured out the cause of that problem, I am
working on a patch, will put it up as a (WIP) MR as soon
as it's ready.



Awesome!

Confused. I see 382dc918 ("Hadrian: always generate the libffi
dynlibs manifest with globbing") has landed but I'm still getting,
```
2019-05-30T10:47:57.5002328Z Error, file does not exist and no
rule available:
2019-05-30T10:47:57.5002606Z
_build/stage1/libffi/build/inst/bin/libffi-6.dll
```
What am I missing?


Golden rule of programming : when your program doesn't work and you've 
checked everything and are sure everything is right and your program 
still doesn't work then, one of the things you are sure of is wrong :)


My front-running guess is that the patch hasn't landed. So many 
confusing notifications!! Sorry for the noise and fingers crossed for 
its progress in the merge queue!


--
Shayne Fletcher
Language Engineer
c: +1 917 699 7763
e: shayne.fletc...@daml.com 
Digital Asset Holdings, LLC
4 World Trade Center 150 Greenwich Street, 47th Floor 

New York, NY 10007, USA 


digitalasset.com 


This message, and any attachments, is for the intended recipient(s) 
only, may contain information that is privileged, confidential and/or 
proprietary and subject to important terms and conditions available at 
http://www.digitalasset.com/emaildisclaimer.html 
. If you are not the 
intended recipient, please delete this message. 


--
Alp Mestanogullari, Haskell Consultant
Well-Typed LLP, https://www.well-typed.com/

Registered in England and Wales, OC335890
118 Wymering Mansions, Wymering Road, London, W9 2NF, England

___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Fwd: [hadrian/windows] build broken

2019-05-30 Thread Shayne Fletcher via ghc-devs
On Thu, May 30, 2019 at 6:55 AM Shayne Fletcher 
wrote:

> Hi Alp,
>
> On Fri, May 24, 2019 at 11:34 AM Shayne Fletcher 
> wrote:
>
>>
>> On Fri, May 24, 2019 at 7:33 AM Alp Mestanogullari 
>> wrote:
>>
>>> Hello Shayne,
>>>
>>> David and I figured out the cause of that problem, I am working on a
>>> patch, will put it up as a (WIP) MR as soon as it's ready.
>>>
>>>
>> Awesome!
>>
> Confused. I see 382dc918 ("Hadrian: always generate the libffi dynlibs
> manifest with globbing") has landed but I'm still getting,
> ```
> 2019-05-30T10:47:57.5002328Z Error, file does not exist and no rule
> available:
> 2019-05-30T10:47:57.5002606Z
> _build/stage1/libffi/build/inst/bin/libffi-6.dll
> ```
> What am I missing?
>

Golden rule of programming : when your program doesn't work and you've
checked everything and are sure everything is right and your program still
doesn't work then, one of the things you are sure of is wrong :)

My front-running guess is that the patch hasn't landed. So many confusing
notifications!! Sorry for the noise and fingers crossed for its progress in
the merge queue!

-- 
Shayne Fletcher
Language Engineer
c: +1 917 699 7763
e: shayne.fletc...@daml.com
Digital Asset Holdings, LLC
4 World Trade Center150 Greenwich
Street, 47th Floor

New York, NY 10007, USA

digitalasset.com 

-- 
This message, and any attachments, is for the intended recipient(s) only, 
may contain information that is privileged, confidential and/or proprietary 
and subject to important terms and conditions available at 
http://www.digitalasset.com/emaildisclaimer.html 
. If you are not the 
intended recipient, please delete this message.
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs


Re: Fwd: [hadrian/windows] build broken

2019-05-30 Thread Shayne Fletcher via ghc-devs
Hi Alp,

On Fri, May 24, 2019 at 11:34 AM Shayne Fletcher 
wrote:

>
> On Fri, May 24, 2019 at 7:33 AM Alp Mestanogullari 
> wrote:
>
>> Hello Shayne,
>>
>> David and I figured out the cause of that problem, I am working on a
>> patch, will put it up as a (WIP) MR as soon as it's ready.
>>
>>
> Awesome!
>
Confused. I see 382dc918 ("Hadrian: always generate the libffi dynlibs
manifest with globbing") has landed but I'm still getting,
```
2019-05-30T10:47:57.5002328Z Error, file does not exist and no rule
available:
2019-05-30T10:47:57.5002606Z
_build/stage1/libffi/build/inst/bin/libffi-6.dll
```
What am I missing?

--
Shayne Fletcher
Language Engineer
c: +1 917 699 7763
e: shayne.fletc...@daml.com
Digital Asset Holdings, LLC
4 World Trade Center150 Greenwich
Street, 47th Floor

New York, NY 10007, USA

digitalasset.com 

-- 
This message, and any attachments, is for the intended recipient(s) only, 
may contain information that is privileged, confidential and/or proprietary 
and subject to important terms and conditions available at 
http://www.digitalasset.com/emaildisclaimer.html 
. If you are not the 
intended recipient, please delete this message.
___
ghc-devs mailing list
ghc-devs@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/ghc-devs