Re: [Haskell-cafe] Call for discussion: OverloadedLists extension

2012-11-06 Thread George Giorgidze
I have created a wiki page about the current implementation of the
OverloadedLists extension:

http://hackage.haskell.org/trac/ghc/wiki/OverloadedLists

The link to the GHC branch that provides a preliminary implementation
of the extension is given in the wiki page.

The wiki page documents what works already and how the extension can
be extended/improved further.

We would welcome contributions. If you would like to make a change in
the current design and implementation of the extension, please
document it (e.g., on the wiki page) and/or send us a GHC patch or a
pull request.

Please also comment whether you would like to see this extension
included in GHC.

Cheers, George

On 24 September 2012 18:29, Simon Peyton-Jones simo...@microsoft.com wrote:
 |  Many of us use the OverloadedStrings language extension on a regular
 |  basis. It provides the ability to keep the ease-of-use of string
 |  literal syntax, while getting the performance and correctness
 |  advantages of specialized datatypes like ByteString and Text. I think
 |  we can get the same kind of benefit by allowing another literal syntax
 |  to be overloaded, namely lists.

 Interestingly, Achim Krause, George Giorgidze and Jeroen Weijers have been 
 thinking about this very question.  They have most of an implementation too. 
 I'm ccing them so they can post a status update.

 Your email broadens the topic somewhat; I don't think we'd considered 
 overloading for maps too, though I can see it makes sense.  I'd much prefer 
 the type-family solution (with a single-parameter type class) to the fundep 
 one, if we go that route.

 This topic deserves its own page on the GHC wiki, if someone wants to start 
 one.

 If we can evolve a design consensus, I'm happy to incorporate the result in 
 GHC.

 Simon


 |  -Original Message-
 |  From: haskell-cafe-boun...@haskell.org [mailto:haskell-cafe-
 |  boun...@haskell.org] On Behalf Of Michael Snoyman
 |  Sent: 23 September 2012 05:07
 |  To: Haskell Cafe
 |  Subject: [Haskell-cafe] Call for discussion: OverloadedLists extension
 |
 |  (Prettier formatting available at: https://gist.github.com/3761252)
 |
 |  Many of us use the OverloadedStrings language extension on a regular
 |  basis. It provides the ability to keep the ease-of-use of string
 |  literal syntax, while getting the performance and correctness
 |  advantages of specialized datatypes like ByteString and Text. I think
 |  we can get the same kind of benefit by allowing another literal syntax
 |  to be overloaded, namely lists.
 |
 |  ## Overly simple approach
 |
 |  The simplest example I can think of is allowing easier usage of Vector:
 |
 |  [1, 2, 3] :: Vector Int
 |
 |  In order to allow this, we could use a typeclass approach similar to
 |  how OverloadedStrings works:
 |
 |  class IsList a where
 |  fromList :: [b] - a b
 |  instance IsList Vector where
 |  fromList = V.fromList
 |  foo :: Vector Int
 |  foo = fromList [1, 2, 3]
 |
 |  ## Flaws
 |
 |  However, such a proposal does not allow for constraints, e.g.:
 |
 |  instance IsList Set where
 |  fromList = Set.fromList
 |
 |  No instance for (Ord b)
 |arising from a use of `Set.fromList'
 |  In the expression: Set.fromList
 |  In an equation for `fromList': fromList = Set.fromList
 |  In the instance declaration for `IsList Set'
 |
 |  Additionally, it provides for no means of creating instances for
 |  datatypes like Map, where the contained value is not identical to the
 |  value contained in the original list. In other words, what I'd like to
 |  see is:
 |
 |  [(foo, 1), (bar, 2)] :: Map Text Int
 |
 |  ## A little better: MPTC
 |
 |  A simplistic approach to solve this would be to just use 
 MultiParamTypeClasses:
 |
 |  class IsList input output where
 |  fromList :: [input] - output
 |  instance IsList a (Vector a) where
 |  fromList = V.fromList
 |  foo :: Vector Int
 |  foo = fromList [1, 2, 3]
 |
 |  Unfortunately, this will fail due to too much polymorphism:
 |
 |  No instance for (IsList input0 (Vector Int))
 |arising from a use of `fromList'
 |  Possible fix:
 |add an instance declaration for (IsList input0 (Vector Int))
 |  In the expression: fromList [1, 2, 3]
 |  In an equation for `foo': foo = fromList [1, 2, 3]
 |
 |  This can be worked around by giving an explicit type signature on the
 |  numbers in the list, but that's not a robust solution. In order to
 |  solve this properly, I think we need either functional dependencies or
 |  type families:
 |
 |  ## Functional dependencies
 |
 |  class IsList input output | output - input where
 |  fromList :: [input] - output
 |  instance IsList a (Vector a) where
 |  fromList = V.fromList
 |  instance Ord a = IsList a (Set a) where
 |  fromList = Set.fromList
 |  instance Ord k = IsList (k, v) (Map k v) where
 |  fromList = 

Re: [Haskell-cafe] Call for discussion: OverloadedLists extension

2012-09-29 Thread wren ng thornton

On 9/28/12 2:48 PM, Mario Blažević wrote:

On 12-09-26 08:07 PM, wren ng thornton wrote:

On 9/25/12 1:57 PM, Sjoerd Visscher wrote:

Maybe we could make a literal [a,b,c] turn into
unpack [a,b,c]#
where
[a,b,c]#
is a statically-allocated vector?


I'm kinda surprised this isn't already being done. Just doing this seems
like it'd be a good undertaking, regardless of whether we get overloaded
list literals. Just storing the literal as a C-like array and inflating
it to a list/array/vector at runtime seems like it should be a big win
for code that uses a lot of literals.


Why?

 I'm surprised that this is an issue at all. If list literals you
are talking about are constant, wouldn't GHC apply constant folding and
construct the list only the first time it's needed?


The problem is: if the list is stored naively in the .data segment (as 
apparently it is), then we have to store all the pointer structure as 
well as the data. This hugely bloats the disk footprint for programs.


That is, all the reasons why String=[Char] is bad at runtime are also 
reasons why this representation is bad at objectcode time. For most 
lists, the pointer structure is a considerable portion of the total 
memory cost. During runtime this overhead is (or at least may be) 
unavoidable due to the dynamic nature of program execution; but there's 
no reason to have this overhead in the compiled format of the program 
since it's trivial to generate it from a compact representation (e.g., 
storing lists as C-style arrays + lengths).


The only conceivable benefit of storing lists on disk using their heap 
representation is to allow treating the .data segment as if it were part 
of the heap, i.e., to have zero-cost inflation and to allow GC to ignore 
that part of the heap. However, for lists, I can't imagine this 
actually being beneficial in practice. This sort of thing is more 
beneficial for large structures of static data (e.g., sets, maps,...). 
But then for large static data, we still usually want a non-heap 
representation (e.g., cache-oblivious datastructures), since we're 
liable to only look at the data rather than to change it. It's only when 
we have lots of static mutable data that it makes sense to take heap 
snapshots.


--
Live well,
~wren

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Call for discussion: OverloadedLists extension

2012-09-28 Thread Heinrich Apfelmus

Michael Snoyman wrote:

Heinrich Apfelmus wrote:

Michael Snoyman wrote:


Note that I wasn't necessarily advocating such a pragma. And a lot of
my XML code actually *does* use two IsString instances at the same
time, e.g.:

Element (img :: Name) (singleton (href :: Name) (foo.png ::
Text)) [NodeComment (No content inside an image :: Text)]


In this particular case, would it make sense to use smart constructors
instead?

The idea is that you can put the polymorphism in two places: either make the
output polymorphic, or make the input polymorphic. The latter would
correspond to a type

   element :: (IsString name, IsString s, IsMap map)
   = name - map name s - [Element]
   element name map = Element (toName name) (toMap map)

One benefit would be that the function will accept any list as a map, not
just list literals.


Just to clarify: this would be a *replacement* for OverloadedStrings
usage, right? If used in conjunction with OverloadedStrings, we'd run
into the too-much-polymorphism issue you describe in your initial
email in this thread, since `element foo'` would become `element
(fromString foo)` which would become `Element ((toName . fromString)
foo)`, and `toName . fromString` makes it ambiguous what the
intermediate data type is.


Yes, indeed, it would be an alternative approach.


Assuming this is meant are a replacement, I see two downsides.
Firstly, this would work for construction, but not for deconstruction.
Currently, I can do something like:

handleList :: Element - Element
handleList (Element ul _ _) = ...
handleList e = e


Good point. On the other hand, there is another extension, ViewPatterns, 
which solves the problem of pattern matching on abstract data types in 
full generality, allowing things like


  handleList (viewAsStrings - Element ul _ _) = ...

While more intrusive, the benefit of this extension is that a lot of 
other code could likely become neater as well.



The other is that we've only solved one specific case by providing a
replacement function. In order to keep code just as terse as it is
now, we'd have to provide a whole slew of replacement functions. For
example, consider the code:

handleList (Element ul attrs _) = case Map.lookup class attrs of 

If we get rid of OverloadedStrings, then we need to either provide a
replacement `lookup` function which performs the conversion from
String to Name, or change all lookup calls to explicitly perform that
lookup.


Ah, I see. Since the  Name  type is abstract, I feel it's alright to add 
the polymorphism to functions like  element , but  Map.lookup  is indeed 
a problem.


One option would be to make a new type  NameMap  specifically for  Name 
 as key, but that seems a little overkill. The other option is to bite 
the bullet and add the conversion by hand  Map.lookup (name class) .


In this case, I think I would go with a lightweight first option and 
simply give a new name to the  Map.lookup  combination and use the 
opportunity to sneak in some polymorphism.


   getAttribute name = Map.lookup (toText name)

In my experience, turning all data types into abstractions works quite 
well, but I can see that you can't avoid an annoying conversion if you 
just want to use a quick  Map.lookup .



Best regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Call for discussion: OverloadedLists extension

2012-09-28 Thread Mario Blažević

On 12-09-26 08:07 PM, wren ng thornton wrote:

On 9/25/12 1:57 PM, Sjoerd Visscher wrote:

Maybe we could make a literal [a,b,c] turn into
unpack [a,b,c]#
where
[a,b,c]#
is a statically-allocated vector?


I'm kinda surprised this isn't already being done. Just doing this seems
like it'd be a good undertaking, regardless of whether we get overloaded
list literals. Just storing the literal as a C-like array and inflating
it to a list/array/vector at runtime seems like it should be a big win
for code that uses a lot of literals.


Why?

	I'm surprised that this is an issue at all. If list literals you are 
talking about are constant, wouldn't GHC apply constant folding and 
construct the list only the first time it's needed?



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Call for discussion: OverloadedLists extension

2012-09-26 Thread Michael Snoyman
On Tue, Sep 25, 2012 at 6:21 PM, Heinrich Apfelmus
apfel...@quantentunnel.de wrote:
 Michael Snoyman wrote:


 Note that I wasn't necessarily advocating such a pragma. And a lot of
 my XML code actually *does* use two IsString instances at the same
 time, e.g.:

 Element (img :: Name) (singleton (href :: Name) (foo.png ::
 Text)) [NodeComment (No content inside an image :: Text)]


 In this particular case, would it make sense to use smart constructors
 instead?

 The idea is that you can put the polymorphism in two places: either make the
 output polymorphic, or make the input polymorphic. The latter would
 correspond to a type

element :: (IsString name, IsString s, IsMap map)
= name - map name s - [Element]
element name map = Element (toName name) (toMap map)

 One benefit would be that the function will accept any list as a map, not
 just list literals.

Just to clarify: this would be a *replacement* for OverloadedStrings
usage, right? If used in conjunction with OverloadedStrings, we'd run
into the too-much-polymorphism issue you describe in your initial
email in this thread, since `element foo'` would become `element
(fromString foo)` which would become `Element ((toName . fromString)
foo)`, and `toName . fromString` makes it ambiguous what the
intermediate data type is.

Assuming this is meant are a replacement, I see two downsides.
Firstly, this would work for construction, but not for deconstruction.
Currently, I can do something like:

handleList :: Element - Element
handleList (Element ul _ _) = ...
handleList e = e

The other is that we've only solved one specific case by providing a
replacement function. In order to keep code just as terse as it is
now, we'd have to provide a whole slew of replacement functions. For
example, consider the code:

handleList (Element ul attrs _) = case Map.lookup class attrs of 

If we get rid of OverloadedStrings, then we need to either provide a
replacement `lookup` function which performs the conversion from
String to Name, or change all lookup calls to explicitly perform that
lookup.

Michael

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Call for discussion: OverloadedLists extension

2012-09-26 Thread wren ng thornton

On 9/24/12 8:53 AM, George Giorgidze wrote:

We will release GHC patches for both approaches, meanwhile the
feedback from the community on the approaches that we took would be
very much appreciated. Which one those would you prefer? or would you
suggest a different one.


The first one is much cleaner, and more closely mirrors the other 
overloaded literals. It seems that in most cases the intermediate list 
should be eliminated via build/foldr fusion. Did you do any testing to 
figure out why that fusion wasn't happening? (I.e., *why* is the generic 
approach faster?)


The only other thing I'll mention is that for overloadable strings, part 
of the reason why they're so fast is that string literals are stored a 
la C, and so the conversion to ByteString and Text requires minimal 
work. I wonder if you might be able to leverage a similar technique for 
representing list literals as vectors, which are then inflated to 
lists/vectors/sets/whatever at runtime.


--
Live well,
~wren

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Call for discussion: OverloadedLists extension

2012-09-26 Thread wren ng thornton

On 9/25/12 1:57 PM, Sjoerd Visscher wrote:

Maybe we could make a literal [a,b,c] turn into
unpack [a,b,c]#
where
[a,b,c]#
is a statically-allocated vector?


I'm kinda surprised this isn't already being done. Just doing this seems 
like it'd be a good undertaking, regardless of whether we get overloaded 
list literals. Just storing the literal as a C-like array and inflating 
it to a list/array/vector at runtime seems like it should be a big win 
for code that uses a lot of literals.


--
Live well,
~wren

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Call for discussion: OverloadedLists extension

2012-09-25 Thread Paul Visschers
Would that also work for vectors that have their length in their type? And
while we are at it, how about overloaded tuples?

Paul

On Mon, Sep 24, 2012 at 7:19 PM, Simon Peyton-Jones
simo...@microsoft.comwrote:

 |  I remember a similar discussion a few years ago. The question of whether
 |  or not overloading list literals a good idea notwithstanding, the
 problem
 |  with this is that fromList for vectors is highly inefficient. So if
 |  something like this gets implemented and if vector/array literals are
 one
 |  of the main motivations then I really hope there will be no lists
 |  involved.

 Would you like to remind us why it is so inefficient?  Can't the vector
 construction be a fold over the list?  Ah... you need to know the *length*
 of the list, don't you?  So that you can allocate a suitably-sized vector.
  Which of course we do for literal lists.

 So what if fromList went
 fromList :: Int - [b] - a b
 where the Int is the length of the list?

 Simon


 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Call for discussion: OverloadedLists extension

2012-09-25 Thread Simon Peyton-Jones
| Here at the University of Tübingen, I am co-supervising (together with
| Jeroen Weijers) a student project implementing the OverloadedLists
| extension for GHC. Achim Krause is the student who is working on the
| project. We took into consideration earlier discussions on this topic
| [1,2] before embarking on the project.
| 
| Achim has worked on two approaches.

Your second approach is this:

| [x,y,z] 
| 
| as
| 
| singleton x `mappend` singleton y `mappend` singleton z ;

This approach is not good for long literal lists, because you get tons of 
executable code where the user thought he was just defining a data  structure.  
And long literal lists are an important use-case.

One other possibility is to use a variant of what GHC does for literal strings. 
Currently
foo
turns into  
unpackCString foo#
where foo# is a statically allocate C string, and the unpackCString unpacks 
it lazily.

Maybe we could make a literal [a,b.c] turn into
unpack [a,b,c]#
where 
[a,b,c]#
is a statically-allocated vector?  See 
http://hackage.haskell.org/trac/ghc/ticket/5218, which is stalled awaiting 
brain cycles from someone.

I'm maxed out at the moment.  I'd be very happy if you guys were able to make 
progress; I'm happy to advise.  Open a ticket, start a wiki page, etc!

Simon

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Call for discussion: OverloadedLists extension

2012-09-25 Thread Roman Leshchinskiy
Simon Peyton-Jones wrote:
 |  I remember a similar discussion a few years ago. The question of
 whether
 |  or not overloading list literals a good idea notwithstanding, the
 problem
 |  with this is that fromList for vectors is highly inefficient. So if
 |  something like this gets implemented and if vector/array literals are
 one
 |  of the main motivations then I really hope there will be no lists
 |  involved.

 Would you like to remind us why it is so inefficient?  Can't the vector
 construction be a fold over the list?  Ah... you need to know the *length*
 of the list, don't you?  So that you can allocate a suitably-sized vector.
  Which of course we do for literal lists.

 So what if fromList went
   fromList :: Int - [b] - a b
 where the Int is the length of the list?

That's part of a problem. There are really two aspects to it. Firstly, a
naive list-based implementation would be a loop. But when I write ([x,y]
:: Vector Double) somewhere in an inner loop in my program, I *really*
don't want a loop with two iterations at runtime - I want just an
allocation and two writes. I suppose this could be solved by doing
something like this:

  {-# INLINE fromList #-}
  fromList [] = V.empty
  fromList [x] = V.singleton x
  fromList [x,y] = ...
  -- and so on up to 8? 16? 32?
  fromList xs = fromList_loop xs

But it's ugly and, more importantly, inlines a huge term for every literal.

The other problem is with literals where all values are known at compile
time. Suppose I have ([2.5,1.4] :: Vector Double) in an inner loop. Here,
I don't want a complicated CAF for the constant vector which would have to
be entered on every loop iteration. I'd much rather just have a pointer to
the actual data somewhere in memory and use that. This is more or less
what happens for strings at the moment, even though you have to use
rewrite rules to get at the pointer which, in my opinion, is neither ideal
nor really necessary. IMO, the right design shouldn't rely on rewrite
rules. Also, strings give you an Addr# whereas vector supports ByteArray#,
too.

Since enumerated literals have been mentioned in a different post, I'll
just mention that the Enum class as it is now can't support those
efficiently for arrays because there is no way to determine either the
length or the nth element of [x..y] in constant time. This would have to
be fixed.

Roman




___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Call for discussion: OverloadedLists extension

2012-09-25 Thread Simon Peyton-Jones

| pointer to the actual data somewhere in memory and use that. This is
| more or less what happens for strings at the moment, even though you
| have to use rewrite rules to get at the pointer which, in my opinion, is
| neither ideal nor really necessary. IMO, the right design shouldn't
| rely on rewrite rules. Also, strings give you an Addr# whereas vector
| supports ByteArray#, too.

If it's not necessary, I wonder if you have an idea for the right design?  

I find it a lot easier to see what is wrong with the current situation than to 
think of solutions.

Simon


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Call for discussion: OverloadedLists extension

2012-09-25 Thread Roman Leshchinskiy
Simon Peyton-Jones wrote:

 | pointer to the actual data somewhere in memory and use that. This is
 | more or less what happens for strings at the moment, even though you
 | have to use rewrite rules to get at the pointer which, in my opinion, is
 | neither ideal nor really necessary. IMO, the right design shouldn't
 | rely on rewrite rules. Also, strings give you an Addr# whereas vector
 | supports ByteArray#, too.

 If it's not necessary, I wonder if you have an idea for the right
 design?

For strings, we could have something like this:

data StringPtr

stringFromStringPtr :: StringPtr - Int - String
unsafeStringPtrToPtr :: StringPtr - Ptr CChar

class IsString a where
  fromString :: String - a
  fromStringPtr :: StringPtr - Int - a
  fromStringPtr p n = fromString $ stringFromStringPtr p n

abc would then desugar to fromStringPtr (address of abc) 3. Note that
we couldn't just use Ptr CChar instead of StringPtr because stringFromPtr
would only be safe if the data that the pointer references never changes.

It's much trickier for general-purpose arrays. It's also much trickier to
support both Ptr and ByteArray. I'd have to think about how to do that.

Roman




___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Call for discussion: OverloadedLists extension

2012-09-25 Thread Heinrich Apfelmus

Michael Snoyman wrote:


Note that I wasn't necessarily advocating such a pragma. And a lot of
my XML code actually *does* use two IsString instances at the same
time, e.g.:

Element (img :: Name) (singleton (href :: Name) (foo.png ::
Text)) [NodeComment (No content inside an image :: Text)]


In this particular case, would it make sense to use smart constructors 
instead?


The idea is that you can put the polymorphism in two places: either make 
the output polymorphic, or make the input polymorphic. The latter 
would correspond to a type


   element :: (IsString name, IsString s, IsMap map)
   = name - map name s - [Element]
   element name map = Element (toName name) (toMap map)

One benefit would be that the function will accept any list as a map, 
not just list literals.



Best regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Call for discussion: OverloadedLists extension

2012-09-25 Thread Bryan O'Sullivan
On Mon, Sep 24, 2012 at 5:53 AM, George Giorgidze giorgi...@gmail.comwrote:

 Our second approach to OverloadedLists is to avoid the construction of
 lists altogether. By typechecking and desugaring lists like

 [] ; [x,y,z] ;  ['a' .. 'z'] ;

 as

 mempty ; singleton x `mappend` singleton y `mappend` singleton z ;
 genericEnumFromTo 'a' 'z' ;


This is very interesting.

As Michael mentions later, we already have mechanisms in place to work
around the creation of constant strings for the Text and ByteString types,
and they rely on a combination of GHC rewrite rules and knowledge about the
internal representation of constant strings used by GHC. We are fortunate
that GHC uses a very efficient representation to store constant strings, so
doing the translation is efficient.

Constant lists are another story entirely (for good reason); the generated
object files are bloated and poorly laid out, when for simple types
(integers and whatnot), I'd really like to see a packed array in the .data
section.

I would be interested to see if an approach that avoids list construction
can also aim to achieve a more efficient object file layout, with the
implied goal being to make fast translation to the runtime representation
easily achievable.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Call for discussion: OverloadedLists extension

2012-09-25 Thread Sjoerd Visscher
So, in order not to have to rely on rewrite rules, would it be a good idea to 
add unpackCString to the IsString class?

import GHC.Base (unpackCString#, Addr#)

class IsString a where
fromString :: String - a
unpackCString :: Addr# - a
unpackCString addr = fromString (unpackCString# addr)

For lists something similar could probably be done.

Sjoerd

On Sep 25, 2012, at 10:01 AM, Simon Peyton-Jones simo...@microsoft.com wrote:

 | Here at the University of Tübingen, I am co-supervising (together with
 | Jeroen Weijers) a student project implementing the OverloadedLists
 | extension for GHC. Achim Krause is the student who is working on the
 | project. We took into consideration earlier discussions on this topic
 | [1,2] before embarking on the project.
 | 
 | Achim has worked on two approaches.
 
 Your second approach is this:
 
 | [x,y,z] 
 | 
 | as
 | 
 | singleton x `mappend` singleton y `mappend` singleton z ;
 
 This approach is not good for long literal lists, because you get tons of 
 executable code where the user thought he was just defining a data  
 structure.  And long literal lists are an important use-case.
 
 One other possibility is to use a variant of what GHC does for literal 
 strings. Currently
   foo
 turns into
   unpackCString foo#
 where foo# is a statically allocate C string, and the unpackCString 
 unpacks it lazily.
 
 Maybe we could make a literal [a,b.c] turn into
   unpack [a,b,c]#
 where 
   [a,b,c]#
 is a statically-allocated vector?  See 
 http://hackage.haskell.org/trac/ghc/ticket/5218, which is stalled awaiting 
 brain cycles from someone.
 
 I'm maxed out at the moment.  I'd be very happy if you guys were able to make 
 progress; I'm happy to advise.  Open a ticket, start a wiki page, etc!
 
 Simon
 
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Call for discussion: OverloadedLists extension

2012-09-24 Thread Michael Snoyman
On Mon, Sep 24, 2012 at 2:53 PM, George Giorgidze giorgi...@gmail.com wrote:
 Hi Michael,

 Here at the University of Tübingen, I am co-supervising (together with
 Jeroen Weijers) a student project implementing the OverloadedLists
 extension for GHC. Achim Krause is the student who is working on the
 project. We took into consideration earlier discussions on this topic
 [1,2] before embarking on the project.

 Achim has worked on two approaches.

 The first approach is very simple, both from the user's and the
 extension implementor's perspective (it follows the implementation of
 OverloadedStrings closely) and typechecks and desugars lists like

 [] ; [x,y,z] ;  ['a' .. 'z'] ;

 as

 fromList [] ;  fromList [x,y,z] ; fromList ['a' .. 'z'] ;

 where fromList is whatever is in scope with that name. That said, we
 do provide the FromList type class that can be used to overload
 fromList. In the following I give the definition of the class, as well
 as, example instances:

 class FromList l where
   type Item l
   fromList :: [Item l] - l

 instance FromList [a] where
   type Item [a] = a
   fromList = id

 instance (Ord a) = FromList (Set a) where
   type Item (Set a) = a
   fromList = Set.fromList

 instance (Ord k) = FromList (Map k v) where
   type Item (Map k v) = (k,v)
   fromList = Map.fromList

 instance FromList (IntMap v) where
   type Item (IntMap v) = (Int,v)
   fromList = IntMap.fromList

 instance FromList Text where
   type Item Text = Char
   fromList = Text.pack

 This approach has already been implemented by Achim as patch against GHC head.

 This approach is very simple, but can be inefficient as it may result
 into unnecessary construction of lists at runtime. This can be a
 serious issue when constructing large structures from arithmetic
 sequences (e.g., from the [ .. ] notation) or when using non-literal
 expressions (e.g., variables) inside the square brackets.

 Our second approach to OverloadedLists is to avoid the construction of
 lists altogether. By typechecking and desugaring lists like

 [] ; [x,y,z] ;  ['a' .. 'z'] ;

 as

 mempty ; singleton x `mappend` singleton y `mappend` singleton z ;
 genericEnumFromTo 'a' 'z' ;

 We  provide the Singleton and GenericEnum type classes for overloading
 singleton and genericEnum(..) functions. In the following, I give the
 definitions of the classes, as well as, example instances:

 -- Singleton class

 class Singleton l where
   type SingletonItem l
   singleton :: SingletonItem l - l

 -- Singleton instances

 instance Singleton [a] where
   type SingletonItem [a] = a
   singleton a = [a]

 instance (Ord a) = Singleton (Set a) where
   type SingletonItem (Set a) = a
   singleton = Set.singleton

 instance (Ord k) = Singleton (Map k v) where
   type SingletonItem (Map k v) = (k,v)
   singleton (k,v) = Map.singleton k v

 instance Singleton (IntMap v) where
   type SingletonItem (IntMap v) = (Int,v)
   singleton (k,v) = IntMap.singleton k v

 instance Singleton Text where
   type SingletonItem Text = Char
   singleton = Text.singleton

 -- GenericEnum class

 class GenericEnum l where
   type EnumItem l
   genericEnumFrom:: EnumItem l - l
   genericEnumFromThen:: EnumItem l - EnumItem l - l
   genericEnumFromTo  :: EnumItem l - EnumItem l - l
   genericEnumFromThenTo  :: EnumItem l - EnumItem l - EnumItem l - l

 -- GenericEnum instances

 instance (Enum a) = GenericEnum [a] where
   type EnumItem [a] = a
   genericEnumFrom= enumFrom
   genericEnumFromThen= enumFromThen
   genericEnumFromTo  = enumFromTo
   genericEnumFromThenTo  = enumFromThenTo

 instance (Ord a,Enum a) = GenericEnum (Set a) where
   type EnumItem (Set a) = a
   genericEnumFrom   a = Set.fromList (enumFrom a)
   genericEnumFromThen   a b   = Set.fromList (enumFromThen a b)
   genericEnumFromTo a b   = Set.fromList (enumFromTo a b)
   genericEnumFromThenTo a b c = Set.fromList (enumFromThenTo a b c)

 instance (Ord k,Enum (k,v)) = GenericEnum (Map k v) where
   type EnumItem (Map k v) = (k,v)
   genericEnumFrom   a = Map.fromList (enumFrom a)
   genericEnumFromThen   a b   = Map.fromList (enumFromThen a b)
   genericEnumFromTo a b   = Map.fromList (enumFromTo a b)
   genericEnumFromThenTo a b c = Map.fromList (enumFromThenTo a b c)

 instance (Enum (Int,v)) = GenericEnum (IntMap v) where
   type EnumItem (IntMap v) = (Int,v)
   genericEnumFrom   a = IntMap.fromList (enumFrom a)
   genericEnumFromThen   a b   = IntMap.fromList (enumFromThen a b)
   genericEnumFromTo a b   = IntMap.fromList (enumFromTo a b)
   genericEnumFromThenTo a b c = IntMap.fromList (enumFromThenTo a b c)

 instance GenericEnum Text where
   type EnumItem Text = Char
   genericEnumFrom   a = Text.pack (enumFrom a)
   genericEnumFromThen   a b   = Text.pack (enumFromThen a b)
   genericEnumFromTo a b   = Text.pack (enumFromTo a b)
   genericEnumFromThenTo a b c = Text.pack (enumFromThenTo a b c)

 Note that the GenericEnum 

Re: [Haskell-cafe] Call for discussion: OverloadedLists extension

2012-09-24 Thread Heinrich Apfelmus

Roman Cheplyaka wrote:

* Heinrich Apfelmus apfel...@quantentunnel.de [2012-09-23 10:51:26+0200]

Unfortunately, making literals polymorphic does not always achieve
the desired effect of reducing syntax. In fact, they can instead
increase syntax! In other words, I would like to point out that there
is a trade-off involved: is it worth introducing a small syntactic
reduction at the cost of both a small additional conceptual
complexity and some syntactic enlargement elsewhere?


Can't you just disable the extension when you realise that it
makes your life harder?


I thought so, too, but there is actually a social catch.

Namely, a library/DSL can be designed with that extension in mind and 
advocate its use. The [scotty][] library is an example for this.


In particular, the  RoutePattern  type is made an instance of  IsString 
 and the example code uses it extensively. If I want to disable the 
extension, I have to translate the example code first. When learning a 
library for the first time, this can be rather confusing.


  [scotty]: http://hackage.haskell.org/package/scotty

Best regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Call for discussion: OverloadedLists extension

2012-09-24 Thread Roman Leshchinskiy
Michael Snoyman wrote:

 The simplest example I can think of is allowing easier usage of Vector:

 [1, 2, 3] :: Vector Int

 In order to allow this, we could use a typeclass approach similar to
 how OverloadedStrings works:

 class IsList a where
 fromList :: [b] - a b
 instance IsList Vector where
 fromList = V.fromList
 foo :: Vector Int
 foo = fromList [1, 2, 3]

I remember a similar discussion a few years ago. The question of whether
or not overloading list literals a good idea notwithstanding, the problem
with this is that fromList for vectors is highly inefficient. So if
something like this gets implemented and if vector/array literals are one
of the main motivations then I really hope there will be no lists
involved.

Roman




___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Call for discussion: OverloadedLists extension

2012-09-24 Thread Simon Peyton-Jones
|  Many of us use the OverloadedStrings language extension on a regular
|  basis. It provides the ability to keep the ease-of-use of string
|  literal syntax, while getting the performance and correctness
|  advantages of specialized datatypes like ByteString and Text. I think
|  we can get the same kind of benefit by allowing another literal syntax
|  to be overloaded, namely lists.  

Interestingly, Achim Krause, George Giorgidze and Jeroen Weijers have been 
thinking about this very question.  They have most of an implementation too. 
I'm ccing them so they can post a status update.

Your email broadens the topic somewhat; I don't think we'd considered 
overloading for maps too, though I can see it makes sense.  I'd much prefer the 
type-family solution (with a single-parameter type class) to the fundep one, if 
we go that route.

This topic deserves its own page on the GHC wiki, if someone wants to start one.

If we can evolve a design consensus, I'm happy to incorporate the result in GHC.

Simon


|  -Original Message-
|  From: haskell-cafe-boun...@haskell.org [mailto:haskell-cafe-
|  boun...@haskell.org] On Behalf Of Michael Snoyman
|  Sent: 23 September 2012 05:07
|  To: Haskell Cafe
|  Subject: [Haskell-cafe] Call for discussion: OverloadedLists extension
|  
|  (Prettier formatting available at: https://gist.github.com/3761252)
|  
|  Many of us use the OverloadedStrings language extension on a regular
|  basis. It provides the ability to keep the ease-of-use of string
|  literal syntax, while getting the performance and correctness
|  advantages of specialized datatypes like ByteString and Text. I think
|  we can get the same kind of benefit by allowing another literal syntax
|  to be overloaded, namely lists.  
|  
|  ## Overly simple approach
|  
|  The simplest example I can think of is allowing easier usage of Vector:
|  
|  [1, 2, 3] :: Vector Int
|  
|  In order to allow this, we could use a typeclass approach similar to
|  how OverloadedStrings works:
|  
|  class IsList a where
|  fromList :: [b] - a b
|  instance IsList Vector where
|  fromList = V.fromList
|  foo :: Vector Int
|  foo = fromList [1, 2, 3]
|  
|  ## Flaws
|  
|  However, such a proposal does not allow for constraints, e.g.:
|  
|  instance IsList Set where
|  fromList = Set.fromList
|  
|  No instance for (Ord b)
|arising from a use of `Set.fromList'
|  In the expression: Set.fromList
|  In an equation for `fromList': fromList = Set.fromList
|  In the instance declaration for `IsList Set'
|  
|  Additionally, it provides for no means of creating instances for
|  datatypes like Map, where the contained value is not identical to the
|  value contained in the original list. In other words, what I'd like to
|  see is:
|  
|  [(foo, 1), (bar, 2)] :: Map Text Int
|  
|  ## A little better: MPTC
|  
|  A simplistic approach to solve this would be to just use 
MultiParamTypeClasses:
|  
|  class IsList input output where
|  fromList :: [input] - output
|  instance IsList a (Vector a) where
|  fromList = V.fromList
|  foo :: Vector Int
|  foo = fromList [1, 2, 3]
|  
|  Unfortunately, this will fail due to too much polymorphism:
|  
|  No instance for (IsList input0 (Vector Int))
|arising from a use of `fromList'
|  Possible fix:
|add an instance declaration for (IsList input0 (Vector Int))
|  In the expression: fromList [1, 2, 3]
|  In an equation for `foo': foo = fromList [1, 2, 3]
|  
|  This can be worked around by giving an explicit type signature on the
|  numbers in the list, but that's not a robust solution. In order to
|  solve this properly, I think we need either functional dependencies or
|  type families:
|  
|  ## Functional dependencies
|  
|  class IsList input output | output - input where
|  fromList :: [input] - output
|  instance IsList a (Vector a) where
|  fromList = V.fromList
|  instance Ord a = IsList a (Set a) where
|  fromList = Set.fromList
|  instance Ord k = IsList (k, v) (Map k v) where
|  fromList = Map.fromList
|  
|  foo :: Vector Int
|  foo = fromList [1, 2, 3]
|  
|  bar :: Set Int
|  bar = fromList [1, 2, 3]
|  
|  baz :: Map String Int
|  baz = fromList [(foo, 1), (bar, 2)]
|  
|  ## Type families
|  
|  class IsList a where
|  type IsListInput a
|  fromList :: [IsListInput a] - a
|  instance IsList (Vector a) where
|  type IsListInput (Vector a) = a
|  fromList = V.fromList
|  instance Ord a = IsList (Set a) where
|  type IsListInput (Set a) = a
|  fromList = Set.fromList
|  instance Ord k = IsList (Map k v) where
|  type IsListInput (Map k v) = (k, v)
|  fromList = Map.fromList
|  
|  foo :: Vector Int
|  foo = fromList [1, 2, 3]
|  
|  bar :: Set Int
|  bar = fromList [1, 

Re: [Haskell-cafe] Call for discussion: OverloadedLists extension

2012-09-24 Thread Simon Peyton-Jones
|  I remember a similar discussion a few years ago. The question of whether
|  or not overloading list literals a good idea notwithstanding, the problem
|  with this is that fromList for vectors is highly inefficient. So if
|  something like this gets implemented and if vector/array literals are one
|  of the main motivations then I really hope there will be no lists
|  involved.

Would you like to remind us why it is so inefficient?  Can't the vector 
construction be a fold over the list?  Ah... you need to know the *length* of 
the list, don't you?  So that you can allocate a suitably-sized vector.  Which 
of course we do for literal lists.

So what if fromList went
fromList :: Int - [b] - a b
where the Int is the length of the list?

Simon


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Call for discussion: OverloadedLists extension

2012-09-23 Thread Heinrich Apfelmus

Michael Snoyman wrote:

(Prettier formatting available at: https://gist.github.com/3761252)

Many of us use the OverloadedStrings language extension on a regular
basis. It provides the ability to keep the ease-of-use of string
literal syntax, while getting the performance and correctness
advantages of specialized datatypes like ByteString and Text. I think
we can get the same kind of benefit by allowing another literal syntax
to be overloaded, namely lists.


Actually, I am already somewhat reserved about the  OverloadedStrings 
proposal.


The core point of the OverloadedSomething extensions is that they 
address a syntactic issue, namely that we can write


  example

instead of

  (pack example)

The extension does this by making the literal polymorphic.

Unfortunately, making literals polymorphic does not always achieve the 
desired effect of reducing syntax. In fact, they can instead increase 
syntax! In other words, I would like to point out that there is a 
trade-off involved: is it worth introducing a small syntactic reduction 
at the cost of both a small additional conceptual complexity and some 
syntactic enlargement elsewhere?



The increase in syntax happened to me while using one of the json 
libraries. The thing is that if a receiver function is agnostic in the 
string used, or if it is otherwise polymorphic,


receive1 :: IsString s = s - Foo
receive2 :: JSON s = s - Foo

then I have to specify the type of the overloaded argument (either by a 
type annotation or a monomorphic function call).


In other words, without  OverloadedStrings , I was able to write

receive2 example

but with the extension, I now have to write

receive2 (pack example)


A similar effect can be seen with the good old numeric literals. 
Sometimes, you just have to introduce a type signature (:: Int) to make 
a program unambiguous.



In this light, I don't think that the trade-off made by the 
OverloadedLists extension is big enough.



Best regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Call for discussion: OverloadedLists extension

2012-09-23 Thread Michael Snoyman
On Sun, Sep 23, 2012 at 10:51 AM, Heinrich Apfelmus
apfel...@quantentunnel.de wrote:
 Michael Snoyman wrote:

 (Prettier formatting available at: https://gist.github.com/3761252)

 Many of us use the OverloadedStrings language extension on a regular
 basis. It provides the ability to keep the ease-of-use of string
 literal syntax, while getting the performance and correctness
 advantages of specialized datatypes like ByteString and Text. I think
 we can get the same kind of benefit by allowing another literal syntax
 to be overloaded, namely lists.


 Actually, I am already somewhat reserved about the  OverloadedStrings
 proposal.

 The core point of the OverloadedSomething extensions is that they address a
 syntactic issue, namely that we can write

   example

 instead of

   (pack example)

 The extension does this by making the literal polymorphic.

 Unfortunately, making literals polymorphic does not always achieve the
 desired effect of reducing syntax. In fact, they can instead increase
 syntax! In other words, I would like to point out that there is a trade-off
 involved: is it worth introducing a small syntactic reduction at the cost of
 both a small additional conceptual complexity and some syntactic enlargement
 elsewhere?


 The increase in syntax happened to me while using one of the json libraries.
 The thing is that if a receiver function is agnostic in the string used,
 or if it is otherwise polymorphic,

 receive1 :: IsString s = s - Foo
 receive2 :: JSON s = s - Foo

 then I have to specify the type of the overloaded argument (either by a type
 annotation or a monomorphic function call).

 In other words, without  OverloadedStrings , I was able to write

 receive2 example

 but with the extension, I now have to write

 receive2 (pack example)


 A similar effect can be seen with the good old numeric literals. Sometimes,
 you just have to introduce a type signature (:: Int) to make a program
 unambiguous.


 In this light, I don't think that the trade-off made by the OverloadedLists
 extension is big enough.


 Best regards,
 Heinrich Apfelmus

 --
 http://apfelmus.nfshost.com


 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

I agree with your point. But what you've pointed out is that there's a
trade-off involved, and then elaborated on the downsides of the
trade-off. Let's not forget that there are significant upsides as
well. And based on the large amount of code out there that actually
uses OverloadedStrings, I think many people feel that the upsides
outweigh the downsides in many cases. The nice thing about an
extension like OverloadedStrings or OverloadedLists is that it need
not affect your code in any way: if you don't turn it on, your code
will continue to work. And you'll still be able to use libraries that
themselves use the extensions without any ill effects.

That said, it would be great to come up with ways to mitigate the
downsides of unbounded polymorphism that you bring up. One idea I've
seen mentioned before is to modify these extension so that they target
a specific instance of IsString/IsList, e.g.:

{-# STRING_LITERALS_AS Text #-}

foo == (fromString foo :: Text)

Another might be more intelligent/powerful defaulting rules, similar
to what we have already with numeric literal overloading.

Michael

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Call for discussion: OverloadedLists extension

2012-09-23 Thread Roman Cheplyaka
* Heinrich Apfelmus apfel...@quantentunnel.de [2012-09-23 10:51:26+0200]
 Unfortunately, making literals polymorphic does not always achieve
 the desired effect of reducing syntax. In fact, they can instead
 increase syntax! In other words, I would like to point out that there
 is a trade-off involved: is it worth introducing a small syntactic
 reduction at the cost of both a small additional conceptual
 complexity and some syntactic enlargement elsewhere?

Can't you just disable the extension when you realise that it
makes your life harder?

Roman

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Call for discussion: OverloadedLists extension

2012-09-23 Thread Chris Smith
Michael Snoyman mich...@snoyman.com wrote:
 That said, it would be great to come up with ways to mitigate the
 downsides of unbounded polymorphism that you bring up. One idea I've
 seen mentioned before is to modify these extension so that they target
 a specific instance of IsString/IsList, e.g.:

 {-# STRING_LITERALS_AS Text #-}

 foo == (fromString foo :: Text)

That makes sense for OverloadedStrings, but probably not for
OverloadedLists or overloaded numbers... String literals have the
benefit that there's one type that you probably always really meant.
The cases where you really wanted [Char] or ByteString are rare.  On
the other hand, there really is no sensible I always want this
answer for lists or numbers.  It seems like a kludge to do it
per-module if each module is going to give different answers most of
the time.

-- 
Chris

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Call for discussion: OverloadedLists extension

2012-09-23 Thread Michael Snoyman
On Sun, Sep 23, 2012 at 5:51 PM, Chris Smith cdsm...@gmail.com wrote:
 Michael Snoyman mich...@snoyman.com wrote:
 That said, it would be great to come up with ways to mitigate the
 downsides of unbounded polymorphism that you bring up. One idea I've
 seen mentioned before is to modify these extension so that they target
 a specific instance of IsString/IsList, e.g.:

 {-# STRING_LITERALS_AS Text #-}

 foo == (fromString foo :: Text)

 That makes sense for OverloadedStrings, but probably not for
 OverloadedLists or overloaded numbers... String literals have the
 benefit that there's one type that you probably always really meant.
 The cases where you really wanted [Char] or ByteString are rare.  On
 the other hand, there really is no sensible I always want this
 answer for lists or numbers.  It seems like a kludge to do it
 per-module if each module is going to give different answers most of
 the time.

 --
 Chris

Note that I wasn't necessarily advocating such a pragma. And a lot of
my XML code actually *does* use two IsString instances at the same
time, e.g.:

Element (img :: Name) (singleton (href :: Name) (foo.png ::
Text)) [NodeComment (No content inside an image :: Text)]

(Courtesy of xml-conduit.)

To prove your point even further, with OverloadedLists we could
replace that `singleton` call with `[(href, foo.png)]` and then be
using two `IsList` instances simultaneously as well (`Map` and `[]`).

Also, I use the `ByteString` instance of `IsString` regularly when
using `http-conduit` and `warp` (for all of the header values), and to
an even greater extent when hacking on the internals of any HTTP
library (whether `http-conduit` or something in the `wai` ecosystem).

Michael

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Call for discussion: OverloadedLists extension

2012-09-23 Thread Brandon Allbery
Maybe what's needed is a way to mutate the lexer by adding new kinds of
literals; Unicode offers a number of paired brackets and quote-like
characters.  Although that is likely to get into readability issues
especially if you do have a mixture of [Char], ByteString, and Text for
some reason.  (Map vs. [] is probably easy enough but add another one or
two in and the sam problem rears its head quickly.)

-- 
brandon s allbery  allber...@gmail.com
wandering unix systems administrator (available) (412) 475-9364 vm/sms
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe