Re: Pattern guards

2006-09-30 Thread Sebastian Sylvan

On 10/1/06, Yitzchak Gale [EMAIL PROTECTED] wrote:

Conor McBride wrote:

 Claus Reinke wrote:

 ...the results of the translation are rather
 more awkward but -and this is the important
 point- pattern guards do not add new
 functionality.

 Well, neither do Boolean guards nor even basic
 pattern matching...  one simply should not need
 to clutter a program with do, return, mplus and
 fromJust (ugh!), spelling out the semantics of
 pattern matching in minute detail. For at least
 36 years, we've been able to hide all that junk
 behind a highly readable equational notation.
 This is one monad we don't need to see.

Some complex things are happening: selections and
bindings are happening at the same time.  The
monad spells it out clearly and concisely, without
adding very much weight at all.


I would argue that most Haskell programmers would *never* write the
various snippets of code demonstrated in this thread in your way, on
the other hand pattern guards are convenient and easy enough to
understand (i.e. you don't have to know very much about monads), and
probably would get used. I certainly use them (and I *do* understand
monads enough to switch to your style of coding if I wanted to)!
Your way is nice and elegant if you happen to know enough to
understand it, pattern guards are nice and elegant to people who
don't.


There has to be a really, really compelling reason
to add new syntax to a language. Every bit of new
syntax makes a language harder to learn, and less
usable for the general user.


I disagree.
Adding syntactic sugar is cheap, as long as the core concepts are
small and elegant. I believe Haskell has taken this approach so far
(or do you want to get rid of e.g. list comprehensions as well? They
too are expressible quite elegantly with monads.), and I think pattern
guards are an excellent candidate in line with this.

It's a natural (in terms of feel, fuzzy I know) generalisation of
guards, and simply won't affect anyone who think they are difficult in
any way. They are and intuitive and nice. They don't change the
behaviour of the core language, all they do is add a tiny bit of
syntactic sugar to make programmer's lives a little bit easier - and
they're not even adding anything completely new, just extending
existing features.

/S
--
Sebastian Sylvan
+46(0)736-818655
UIN: 44640862
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-prime


Re: Strict tuples

2006-03-20 Thread Sebastian Sylvan
On 3/20/06, Sebastian Sylvan [EMAIL PROTECTED] wrote:
 On 3/19/06, Manuel M T Chakravarty [EMAIL PROTECTED] wrote:
  Loosely related to Ticket #76 (Bang Patterns) is the question of whether
  we want the language to include strict tuples.  It is related to bang
  patterns, because its sole motivation is to simplify enforcing
  strictness for some computations.  Its about empowering the programmer
  to choose between laziness and strictness where they deem that necessary
  without forcing them to completely re-arrange sub-expressions (as seq
  does).
 
  So what are strict tupples?  If a lazy pair is defined in pseudo code as
 
data (a, b) = (a, b)
 
  a strict pair would be defined as
 
data (!a, b!) = ( !a, !b )
 
  Ie, a strict tuple is enclosed by bang parenthesis (! ... !).  The use
  of the ! on the rhs are just the already standard strict data type
  fields.
 

 Maybe I've missed something here. But is there really any reasonable
 usage cases for something like:

 f !(a,b) = a + b

 in the current bang patterns proposal?

 I mean, would anyone really ever want an explicitly strict (i.e. using
 extra syntax) tuple with lazy elements?

 Couldn't the syntax for strict tuples be just what I wrote above
 (instead of adding weird-looking exclamation parenthesis).

 I'm pretty sure that most programmers who would write f !(a,b) = ...
 would expect the tuple's elements to be forced (they wouldn't expect
 it to do nothing, at least).. In fact !(x:xs) should mean (intuitively
 to me, at least) force x, and xs, meaning that the element x is
 forced, and the list xs is forced (but not the elements of the xs).

 Couldn't this be generalised? A pattern match on any constructor with
 a bang in front of it will force all the parts of the constructor
 (with seq)?

 So:
 f !xs = b   -- gives  f xs = xs `seq` b, like the current proposal
 f !(x:xs) = b -- gives f (x:xs) = x `seq` xs `seq` b, unlike the
 current proposal?

 The latter would then be equal to

 f (!x:xs) = b

I mean

f (!x:!xs) = b


/S
--
Sebastian Sylvan
+46(0)736-818655
UIN: 44640862
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Strict tuples

2006-03-20 Thread Sebastian Sylvan
On 3/20/06, Manuel M T Chakravarty [EMAIL PROTECTED] wrote:
 Sebastian Sylvan:
  On 3/19/06, Manuel M T Chakravarty [EMAIL PROTECTED] wrote:
   Loosely related to Ticket #76 (Bang Patterns) is the question of whether
   we want the language to include strict tuples.  It is related to bang
   patterns, because its sole motivation is to simplify enforcing
   strictness for some computations.  Its about empowering the programmer
   to choose between laziness and strictness where they deem that necessary
   without forcing them to completely re-arrange sub-expressions (as seq
   does).
  
   So what are strict tupples?  If a lazy pair is defined in pseudo code as
  
 data (a, b) = (a, b)
  
   a strict pair would be defined as
  
 data (!a, b!) = ( !a, !b )
  
   Ie, a strict tuple is enclosed by bang parenthesis (! ... !).  The use
   of the ! on the rhs are just the already standard strict data type
   fields.
  
 
  Maybe I've missed something here. But is there really any reasonable
  usage cases for something like:
 
  f !(a,b) = a + b
 
  in the current bang patterns proposal?
 
  I mean, would anyone really ever want an explicitly strict (i.e. using
  extra syntax) tuple with lazy elements?
 
  Couldn't the syntax for strict tuples be just what I wrote above
  (instead of adding weird-looking exclamation parenthesis).
 
  I'm pretty sure that most programmers who would write f !(a,b) = ...
  would expect the tuple's elements to be forced (they wouldn't expect
  it to do nothing, at least).. In fact !(x:xs) should mean (intuitively
  to me, at least) force x, and xs, meaning that the element x is
  forced, and the list xs is forced (but not the elements of the xs).
 
  Couldn't this be generalised? A pattern match on any constructor with
  a bang in front of it will force all the parts of the constructor
  (with seq)?

 The point about strict tuples is not that the components are forced on
 pattern matching (that's indeed what bang patterns are for).  The point
 about strict tuples is that the components are forced *before* the tuple
 is *constructed*.  It's really exactly the same as with strict fields in
 data type declarations today.

Ah yes, I get it now.

What I wrote was more related to Bang patterns then (so it's a bit
OT). The more I think about bang patterns, though, the more it seems
reasonable that f !(a,b) shouldn't be equivalent to f (a,b). If
one thinks about ! as removing one layer of laziness (e.g. !xs will
force a list, but not its elements) then it should make sense that
applying ! to a pattern where one (or more) layer of laziness has
already been removed (via pattern matching) would result in forcing
the next layer (e.g. ![a,b] would evaluate a and b, since the list
itself has already been forced via pattern matching).
It makes sense to me to at least. More sense than having ! do nothing
in circumstances like the above, anyway.

/S

--
Sebastian Sylvan
+46(0)736-818655
UIN: 44640862
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Haskell-prime Digest, Vol 2, Issue 58

2006-02-24 Thread Sebastian Sylvan
On 2/24/06, John Hughes [EMAIL PROTECTED] wrote:
 From: Claus Reinke [EMAIL PROTECTED]

 let's go through 5.2 Export Lists to see what would be missing
 if we tried to replace the export list with a separation of a module
 into a public (exported) and a private (local) part:
 ...
 any other issues I missed here?

 I feel unkeen.

 One of the nice things about Haskell is that definitions can appear in any 
 order. That makes it possible to gather a group of logically related 
 definitions together, within a module. With your proposal, exported 
 definitions and non-exported ones would have to be separated.

 What would that mean in practice? Suppose I have a few exported functions and 
 a collection of auxiliary functions that are used to implement them. I have 
 two choices: either I put the exported definitions in the public section, and 
 the remaining ones elsewhere in the private section, or I put everything in 
 the private section with appropriate redeclarations in the public part -- 
 exportedName = localExportedName or whatever. The first alternative has the 
 disadvantages that logically related code is separated, and that the public 
 section of the module may itself become quite large (since it contains full 
 function definitions), making it hard to see at a glance what the exported 
 names are. The second alternative has the disadvantage of introducing an 
 indirection---finding the actual definition of an exported function becomes 
 more difficult, because one must both scan the module for it, and first look 
 up the public section to see what the private version is called. Neither 
 alternative feels really attractive to me.

 Today's export lists at least have the advantage that it is easy to see what 
 is exported, even if changing the status of a definition from private to 
 public is a little awkward (with edits in two places). With a tool like 
 Haddock installed too, once gets a pretty good view of the 
 interface---arguably better than one can get from a public module section. 
 Perhaps, given that Haddock is available, a public modifier makes more sense 
 than an explicit export list---although code browsing would then require 
 running Haddock during development much more often than today, and 
 potentially on syntactically incorrect or ill-typed modules.

 Incidentally, the Erlang equivalent of Haddock, edoc, is distributed with the 
 compiler, so that all Erlang installations include the tool, no matter what 
 platform they're running on. Surely that's a prerequisite for adapting the 
 language design on the assumption that tools of various kinds are available?

 John




Just a quick thought. How about having separating the code in two
sections, public and local, BUT allowing you to export local names by
simply mentioning them in the public section. So the equivalent of
what we have now would be to write all your code in the private/local
section, and then put the names of the functions you want exported in
the public section.
These exported locals could be in a separate list like it is now (in
addition to the public section) or it could be enough to just put them
in the public top level like so

--
public:
foo = blah + bar

bar -- this re-exports a local bar defined in the private section

A(B,D) -- re-exports data type A with constructors B and D (but keeps C hidden)

baz = blahglah

private:
bar = blahblah
data A = B  | C | D
--

Maybe some keyword to re-export local definitions is a good idea. Like
export bar or something...

This means you can still group locally related functions together, but
you're allowed to write defintions in the public part of the module as
well. So you get all your public stuff in the same place (good), while
the definitions for some of those items may be in the local area if
that makes sense (good). And there's no extra indirection since the
public name isn't different from the priveate one (good). You do have
to type the name twice, but that's no different from what we have now
(and better, since it's pay as you go - you only need to retype
names if you choose to put the definition in the local part).

A likely coding practice would be to put short and simply defitions in
the public interface, but using the exporting feature for larger
functions (which need a significant amount of local helper functions
etc.).

/S

--
Sebastian Sylvan
+46(0)736-818655
UIN: 44640862
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: public/private module sections (was: Haskell-prime Digest, Vol 2, Issue 58)

2006-02-24 Thread Sebastian Sylvan
On 2/24/06, Benjamin Franksen [EMAIL PROTECTED] wrote:
 On Friday 24 February 2006 16:38, Bulat Ziganshin wrote:
  i personally prefer to have
  public/private modifiers on each function and gather interface
  documentation by tools like haddock

 Me too.


Maybe if you only had to specify which functions where public (whereas
private is implied -- or maybe not even allowing it to save a
keyword). But having to type one of public or private at each
function site would get really tedious...

/S
--
Sebastian Sylvan
+46(0)736-818655
UIN: 44640862
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: The dreaded M-R

2006-01-30 Thread Sebastian Sylvan
On 1/30/06, Simon Marlow [EMAIL PROTECTED] wrote:
 I've put a wiki page with a summary of this discussion here:

 http://hackage.haskell.org/cgi-bin/haskell-prime/trac.cgi/wiki/Monomorph
 ismRestriction

 Hopefully I've captured most of the important points, please let me know
 if there's anything I missed, or misrepresented.  I'll add a ticket
 shortly.

 Given the new evidence that it's actually rather hard to demonstrate any
 performance loss in the absence of the M-R with GHC, I'm attracted to
 the option of removing it in favour of a warning.

Given that the discussion has focused a lot on how beginners would
feel about this, I'll chime in with my two cents. I may not be a
beginner in the strictest sense of the word, but I'm probably a lot
closer to it than the rest of the participants in this discussion :-)

I'm against it. People will want to *understand* the difference
between := and =, and I don't think beginners will really grok
something like that without significant difficulties. And it does add
a significant extra clutter to the language, IMO. That symbols feels
heavy, somehow, even if it's meaning is subtle (at least from a
beginners POV).

Also, since it's only a problem very rarely, it could be noted in an
optimization faq somewhere. Plus, don't we already tell people to
add type signatures when something is too slow? Isn't that the first
thing you would try when something is surprisingly slow?

/S

--
Sebastian Sylvan
+46(0)736-818655
UIN: 44640862
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Existential types: want better syntactic support (autoboxing?)

2006-01-30 Thread Sebastian Sylvan
Seems like a convenient feature to me.

Also, you may want to have a function which works on a list of any
values which are both readable and showable.
Say (mockup syntax):

foo :: Show a, Read a = [a]
foo = [ 1, True, myRocketLauncher ]

Which would create a newtype called ShowReadAble or something with
extistential types and also instantiate that type in both Show and
Read.

I do agree that this is something I'd like in a lot of cases, and it
probably would be used quite a bit more if it were convenient (and
standardised!).

I leave it to someone else to figure out how to make this play nice
with e.g. type inference.

/S

--
Sebastian Sylvan
+46(0)736-818655
UIN: 44640862
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime