On Sun, Oct 9, 2011 at 10:33 PM, George Giorgidze <giorgi...@gmail.com> wrote:
> Thanks to all of you for providing feedback on my proposal and for providing 
> alternatives.
>
> In this email, I will try to collect all proposals and give pros and cons for 
> each of those (although I will try to provide a good argumentation, some of 
> them might be subjective).
>
> Inspired by Simon's and Roman's suggestions I will introduce one more 
> proposal, I am afraid.
>
> Proposal (1): my original proposal
>
> Pros:
> * Simple and straightforward generalisation similar to fromInteger and 
> fromString.
>
> * Works with arithmetic sequences as well (i.e., for sequences like [1 .. 
> 10], [x .. z], ['a' .. 'z']). Sequences will be desugared as defined in the 
> Haskell standard and the proposed extension would just add the fromList 
> function.
>
> Cons:
> * Performance. I share Roman's concerns. What we are overloading here is 
> somewhat different from integer and string literals. Namely, what I was 
> referring as list literals may feature expressions (e.g., a variable bound 
> elsewhere as in f x = [x,x]) and hence may not be evaluated only once. Maybe 
> I should have called it "list notation" and not "list literals". This 
> proposal would result into runtime overheads associated with conversion of 
> lists.
>
> * Programmers may provide partial instances failing at runtime.
>
> (BTW. I agree that FromList is much better name than IsList).
>
>
> Proposal (2) by Yitz (with improvements suggested by Gábor)
> Pros:
> * Allows partial instances to fail at compile time
> * Allows writing of instances that convert lists at compile time
>
> Cons:
> * Consensus is emerging that people do not want to unnecessarily tie the 
> lightweight extension of the list notation overloading to the heavyweight 
> extension of Template Haskell.
> * Not clear how to implement this and what would be the impact on quality of 
> error messages.
>
> (The first point is subjective, the second point can be addressed but at this 
> stage I do not know how).
>
>
> Proposal (3) by Roman: the Cons class
>
> Pros:
> * Addresses the runtime conversion issue
>
> Cons:
> * Does not support arithmetic sequences (this can be addressed, see below)
>
>
> Proposal (4) by Simon: avoid classes and desugar to return and mappend
> Pros:
> * Addresses the runtime conversion issue
> * Does not introduce new type classes (at least for the list notation)
>
> Cons:
> * Unnecessarily ties the list notation to the concept of monad.
> * Does not support arithmetic sequences (this can be addressed, see below)
>
>
> Proposal (5): one more proposal from me (I am afraid) addressing shortcomings 
> of Proposal (3) and Proposal (4).
>
> Here is the first attempt to generalise Proposal (4):
>
> class Functor f => Pointed f where
>  point :: a -> f a
>
> with the following (free) pointed law guaranteed by parametricity:
>
> fmap f . point = point . f
>
> Now the list notation can be desugared as follows:
>
> [] = mempty
> [x,y,z] = point x `mappend` point y `mappend` point z
>
> Now this will work for any pointed function that is also a monoid (much 
> larger class of structures than monads that are also monoids). However, Map 
> and Text examples from my original proposal are still ruled out.
>
> The following two classes provide as much flexibility as Proposal (1) but 
> avoid going through lists at runtime.
>
> class Singleton l where
>  type Elem l
>  singleton :: Elem l -> l
>
> Now the list notation can be desugarred as follows:
>
> [] = mempty
> [x,y,z] = singleton x `mappend` singleton y `mappend` singleton z
>
> Also the following class can be used to desugar arithmetic sequences:
>
> class Enum a => GenericEnum f a where
>  genericEnumFrom        :: a -> f a
>  genericEnumFromThen    :: a -> a -> f a
>  genericEnumFromTo      :: a -> a -> f a
>  genericEnumFromThenTo  :: a -> a -> a -> f a
>
> as follows:
>
> [ x.. ] =       genericEnumFrom x
> [ x,y.. ]       =       genericEnumFromThen x y
> [ x..y ]        =       genericEnumFromTo x y
> [ x,y..z ]      =       genericEnumFromThenTo x y z
>
> To summarise:
> * Proposal (5) is slightly more involved one compared to Proposal (1).
> * Proposal (5) avoids going through lists at runtime and is as flexible as 
> Proposal (1).
>
> For me both options are acceptable. But it seems Proposal (5) should be more 
> suitable for DPH folks and other applications (other parallel arrays, e.g., 
> GPU and distributed arrays) where going through lists at runtime is not an 
> option for performance reasons.
>
> OK, any thoughts on Proposal (1) vs. Proposal (5)?

Is it worth the extra effort to reuse the Monoid instance? It feels a
bit contorted to introduce a not-really-generally-useful Singleton
class just for the purpose, and then to mappend single-element
containers. (I'm not even sure if every type will always have the
'right' Monoid instance, though at the moment I can't think of any
counterexamples.) What I think you'd truly want is a class which
expresses the thought "can have elements added to it" (rather than
"can be combined with others"). That's basically what Roman's Cons
class is. It's barely more complicated than Singleton, and if you have
to introduce a new class either way I think you may as well go with
it. (I don't know whether there's an equivalent version already in a
library somewhere...)

I'd rather have GenericEnum use an associated type as well, so as not
to restrict it to fully parametric types.

Maybe:

class FromListSyntax l where
    type Elem l
    empty :: l
    addElem :: Elem l -> l -> l

class FromListSyntax l => FromEnumSyntax l where
    enumFrom        :: Elem l -> l
    enumFromThen    :: Elem l -> Elem l -> l
    enumFromTo      :: Elem l -> Elem l -> l
    enumFromThenTo  :: Elem l -> Elem l -> Elem l -> l

That name-clashes with both Alternative and Enum but I don't know what
else to call them.

All of that being said, I'm perfectly fine with any solution which
uses type families rather than requiring a parametric type (which is 4
out of 5).

P.S. If you want to make these generally useful for things other than
their main purpose, you could split them up to make the rudimentary
beginnings of a container classes library, and call them something
like class Container c where type Element c, class Container c =>
Empty c where empty :: c, class Container c => AddElement c where
addElement :: Element c -> c -> c, ...

>
> Of course if no consensus is reached we should not implement any of those. 
> Having said that, the reason I like this extension is that it has a potential 
> to subsume and potentially displace two GHC extensions (list literal 
> overloading and the DPH array notation) in future. This rarely happens these 
> days :).
>
> Cheers, George
>
> P.S. Lennart, asked about defaulting rules and backwards compatibility. Let 
> us keep this in mind and comeback to it after we decide on how to overload 
> the list notation and arithmetic sequences in the first place.
> _______________________________________________
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users@haskell.org
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
>



-- 
Work is punishment for failing to procrastinate effectively.

_______________________________________________
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Reply via email to