Re: the MPTC Dilemma (please solve)

2006-03-20 Thread Claus Reinke

welcome to the discussion!-)


(A) It's not as if every interesting program (or even the majority of
interesting programs) use(s) MPTCs.


well, I express my opinions and experience, and you express your's:-)

let's hope that Haskell' will accomodate both of us, and all the other
possible views and applications of Haskellers in general, to the extent 
that they are represented here.



(B) I don't think the time for which an extension has been around is
particularly relevant. 


oh yes, it is. don't get me wrong, we have ample proof that having 
been around for long does not imply good, necessary or even just 
well-understood. but it is certainly relevant, as it demonstrates

continued use.

haskell prime is an attempt to standardize current Haskell practice, 
and MPTCs and FDs have been part of that for a long time, so haskell
prime has to take a stand about them. Haskell98 could get away with 
closed eyes, claiming that those features were new then, just as GADTs 
and ATS are new today. haskell prime does not have that choice

any more.

so I see two choices:

- define current practice in MPTCs and FDs, then mark those then
   well-defined extensions as deprecated, to be removed in Haskell''.

   to do this, you'd need to provide a clear alternative to migrate to,
   with a simple and complete definition both of the feature set you
   are advocating, and its interactions with other features, and its
   relation to the features it is meant to replace.

- define current practice in MPTCs and FDs, find the simple story
   behind these features and their interactions with other features
   (as simple as we can make it, without the scaremongering), and 
   add that to Haskell'. 

   also define the initial versions of your alternative feature sets 
   and their interactions. leave it to Haskell'' to decide which of 
   the two to deprecate, if any.


either option needs a definition of both feature sets (I assume you're
arguing for associated type synonyms). we do have fairly simple
definitions of MPTCs and FDs, although I still think (and have been
trying to demonstrate) that the restrictions are too conservative. 

what we don't have are definitions of the interactions with other 
features (and the restrictions really get in the way here), such as 
overlap resolution, or termination proofs, but we are making 
progress there. what we also don't have is a simple definition 
of ATS, its interactions with other features, and a comparison 
of well-understood ATS with well-understood FDs (I only just 
printed the associated FD paper, perhaps that'll help), which 
could form the basis for a decision between the two.


so, imho, haskell prime can only define the current state, hopefully
with a better form of MPTCs/FDs and at least some preliminary 
form of ATS, and let practice over the next years decide whether 
haskellers will move from MPTCs/FDs to ATS. just as practice

seems to have decided that other features, eg, implicit parameters,
in spite of their initial popularity, have not recommended themselves
for any but the most careful and sparing use, and not as part of
the standard.


One of the big selling points of Haskell is that
it's quite well defined, and hence, its semantics is fairly well
understood and sane - sure, there are dark corners, but compared to
other languages of the same size, we are in good shape.  If we include
half-baked features, we weaken the standard.


we are not in a good shape. Haskell 98 doesn't even have a semantics.

current Haskell is so full of dark corners, odd restrictions and unexpected
feature interactions that I've been tempted to refer to it as the C++ of
functional languages. the question on the table is not wether to include
half-baked features of current Haskell in Haskell', but how to make sure
that we understand those features well enough to make an informed
decision. nothing I've seen so far indicates that it is impossible to come
up with a well-defined form of some of those features, including their 
interactions with other features. that doesn't come without some 
further work, so the haskell prime effort cannot just pick and choose,

but there's no reason to give up just yet.

and to keep what is good about Haskell, we need to think about
simplifying the features we have as our understanding of them improves,
in particular, we need to get rid of unnecessary restrictions (they
complicate the language), and we need to investigate feature interactions.
we weaken the standard if it has nothing to say about the problems
in current practice.


In fact, it's quite worrying that FDs have been around for so long and
still resisted a thorough understanding.


they don't resist. but as long as progress is example-driven and scary
stories about FDs supposedly being tricky and inherently non-under-
standable are more popular than investigations of the issues, there 
won't be much progress. please don't contribute to that hype.


you reply to a message that is about a month 

RE: Strict tuples

2006-03-20 Thread Simon Marlow
On 19 March 2006 02:35, Manuel M T Chakravarty 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.
 
 Why strict tuples, but not strict lists and strict Maybe and so on?
 Tuples are the Haskell choice of returning more than one result from a
 function.  So, if I write
 
   add x y = x + y
 
 the caller gets an evaluated result.  However, if I write
 
   addmul x y = (x + y, x * y)
 
 the caller gets a pair of two unevaluated results.  Even with bang
 patterns, I still have to write
 
   addmul x y = let !s = x + y; !p = x * y in (s, p)
 
 to have both results evaluated.  With strict tuples
 
   addmul x y = (!x + y, x * y!)
 
 suffices.
 
 Of course, the caller could invoke addmul using a bang patterns, as in
 
   let ( !s, !p ) = addmul x y
   in ...
 
 but that's quite different to statically knowing (from the type) that
 the two results of addmul will already be evaluated.  The latter
 leaves room for more optimisations.
 
 Syntax issues
 ~
 * In Haskell (,) is the pair constructor.  What should be use for
   strict tuples?  (!,!) ?
 * With strict tuples (! and !) would become some sort of
   reserved/special symbol.  That interferes with bang patterns, as
   (!x, y!) would be tokenized as (! x , y !).  We could use ( ... !)
   for strict tuples to avoid that conflict, or just requires that the
   user write ( !x, !y ) when they want a bang pattern.  (Just like you
   cannot write `Just.x' to mean `Just . x' as the former will always
   be read as a qualified name and not the application of function
   composition.

Not to mention overlap with sections:  (!i).  Even with just bang
patterns, we have some interesting parsing problems due to the overlap
with infix '!'.  eg., now 

  arr ! x = indexArray arr x

will probably parse as

  arr (!x) = indexArray arr x

which means that in order to define (!) you have to use the prefix form:
(!) arr x = ...

GHC's implementation of bang pattern parsing has some ugliness to deal
with this.  In the report, we will have to be very careful to make sure
the syntax doesn't have any ambiguities in this area, which will
probably mean adding special cases to the grammar.

My suggestion is to avoid these problems by removing infix '!' from the
syntax:

http://haskell.galois.com/cgi-bin/haskell-prime/trac.cgi/wiki/ArrayIndex
ing

I realise this is a code-breaking change, but I consider the special
cases introduced to the syntax by bang patterns to be rather warty.
Also, since I think many of us envisage Haskell moving towards having
more strictness annotations in the future, it makes sense to
consistently use the '!' operator to mean strict.

Cheers,
Simon
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: the MPTC Dilemma (please solve)

2006-03-20 Thread Ross Paterson
On Mon, Mar 20, 2006 at 10:50:32AM -, Claus Reinke wrote:
 you reply to a message that is about a month old. since then, every
 single example of FD trickyness presented here has been resolved
 (or have we missed some example?), and as far as I'm concerned, 
 the remaining problems are due to feature interactions, and need a 
 more systematic approach.

As understand it, you've proposed changes in context reduction to
restore confluence:

http://www.haskell.org//pipermail/haskell-prime/2006-March/000880.html
(with subsequent minor corrections)

What is your plan to deal with non-termination (e.g. examples 6 and 16
of the FD-CHR paper)?

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re[2]: Strict tuples

2006-03-20 Thread Bulat Ziganshin
Hello Simon,

Monday, March 20, 2006, 1:47:52 PM, you wrote:

 i've proposed to allow adding strict mark to any type constructors and
 type constructor parameters so that finally we can define any data
 structure that can be defined in strict languages. in particular:
 
 type StrictPair a b = !(,) a b
 type StrictElements a b = (,) !a !b
 type StrictBoth a b = !(,) !a !b
 type StrictFunction a b = !(-) !a !b
 
 strictMap :: StrictFunction a b - ![!a] - ![!b]
 
 where ![!a] is a strict list with strict elements

SM Bulat, this doesn't constitute a proposal.  It leaves too many questions
SM unanswered.  If it is supposed to be just syntactic sugar, and I believe
SM that is your intention, then can you show me how the above definitions
SM translate into Haskell 98?  

i'm not sure that i can make complete proposal, but i can say what i
mean in more details:

one of the differences between Haskell and most other languages is what
even when we don't need laziness we are forced to buy it. so i want to
see the language where laziness is optional at any place.

shebang patterns allow to specify that concrete IMPLEMENTATION of some
function is strict in its using of parameters. but this can't help us
if we want to carry strict function in data structure, pass it as
function argument, has is as a class member. i was bitten by this
when i wrote Streams library - although Char encoding transformers are
simple strict computations that just read several bytes and then return
one Char, and byte reading operation by itself is very fast - they
cannot be combined to fast Char-reading function.

another problem is what while we can specify strictness of fields in
ADTs, we cannot redefine strictness of fields in existing ADT, such
as list.

my solutions to these problems:

1) make a strictness annotation part of function type declaration,
i.e. when function type can include strictness annotation on each of
its arguments and on result:

fac :: !Int - !Int - !Int

strictness annotation on argument means that function is strict in
this argument - if its value diverges then entire function diverges.
informally, strict argument can be evaluated before evaluation of
function body, as in the strict languages - what opens up possibility
to unbox such values and to omit checking of argument evaluation in
function body, moving this evaluation to the caller side

strictness annotation on result means that function DON'T DIVERGE if
all arguments are don't diverge. this allows to unbox result and to
skip checking that result was evaluated on callee side by moving real
computation inside the function. informally, this means that a
function is inexpensive enough and therefore can be computed non-lazily


2) to allow changing of strictness inside existing ADTs, i propose
to copy strictness annotations on type arguments to the type
declaration bodies:

data List a = Nil | Cons (List a) a
type StrictElements a = List !a

is equal to the:

data StrictElements a = Nil | Cons (List a) !a

i.e. it's the same list but each element is strict. using strictness
annotation on type constructor itself should mean strictifying of all
other (non-type-variable) fields:

type StrictList a = !List a
=
data StrictList a = !Nil | !Cons !(List a) a

of course, i don't mean introducing new incompatible types - that is a
compiler responsibility (sorry, Simon :) ) to convert between variants
of types with different strictness. That we should fix at the language
definition level is what on strict types te user don't expects lazy
evaluation of list/it's elements and compiler is free to use program
transformations what non-lazily computes these data. for example, if
putStr function accepts strict list, then it can be implemented
without evaluated? checks on each step and the callers would ensure
that all strings passed to this function are fully evaluated

these two changes together should make it possible to implement
strictly strict algorithms in Haskell

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


RE: Re[2]: Strict tuples

2006-03-20 Thread Simon Marlow
On 20 March 2006 12:26, Bulat Ziganshin wrote:

 2) to allow changing of strictness inside existing ADTs, i propose
 to copy strictness annotations on type arguments to the type
 declaration bodies:

 data List a = Nil | Cons (List a) a
 type StrictElements a = List !a
 
 is equal to the:
 
 data StrictElements a = Nil | Cons (List a) !a

So, in fact StrictElements is not compatible with the List type at all
(that is, you can't pass a value of type (StrictElements Int) to a
function expecting (List Int)).  I can envisage that this might be a
sound extension, and imlementable, but is it what you mean?  I don't
think so.

I imagine you want a lot of automatic conversion back and forth bewteen
strict and lazy types.  This is where it gets a *lot* trickier, starting
with the type system.

 i.e. it's the same list but each element is strict. using strictness
 annotation on type constructor itself should mean strictifying of all
 other (non-type-variable) fields:
 
 type StrictList a = !List a
 =
 data StrictList a = !Nil | !Cons !(List a) a

I don't know what !Nil or !Cons mean.

 of course, i don't mean introducing new incompatible types - that is a
 compiler responsibility (sorry, Simon :)

Well, you haven't told me what type system I need to implement, so it's
not just an implementation issue.  And it seems to me that you *are*
introducing incompatible types.

Cheers,
Simon
___
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, 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 Manuel M T Chakravarty
Simon Marlow:
 Not to mention overlap with sections:  (!i).  Even with just bang
 patterns, we have some interesting parsing problems due to the overlap
 with infix '!'.  eg., now 
 
   arr ! x = indexArray arr x
 
 will probably parse as
 
   arr (!x) = indexArray arr x
 
 which means that in order to define (!) you have to use the prefix form:
 (!) arr x = ...
 
 GHC's implementation of bang pattern parsing has some ugliness to deal
 with this.  In the report, we will have to be very careful to make sure
 the syntax doesn't have any ambiguities in this area, which will
 probably mean adding special cases to the grammar.
 
 My suggestion is to avoid these problems by removing infix '!' from the
 syntax:
 
 http://haskell.galois.com/cgi-bin/haskell-prime/trac.cgi/wiki/ArrayIndex
 ing
 
 I realise this is a code-breaking change, but I consider the special
 cases introduced to the syntax by bang patterns to be rather warty.
 Also, since I think many of us envisage Haskell moving towards having
 more strictness annotations in the future, it makes sense to
 consistently use the '!' operator to mean strict.

I agree that the use of ! for indexing is a bad choice, actually a very
bad choice.  As arrays are not used that much and (!) isn't even
exported from the Prelude, I like the idea of changing the indexing
syntax.  I am less convinced that it is wise to change the syntax of
function composition, as this will break a huge set of programs.  I
actually also don't see that this affects the array proposal.  (.#)
would be a valid and free operator anyway, wouldn't it?  What about list
indexing? Use (.##)?  (Doesn't look very nice, but transfers the (!) for
arrays and (!!) for lists idea.)  A change to list indexing will
probably break more programs than a change to array indexing.

Apart from the syntactic issues, does anybody else support the idea of
strict tuples as proposed?  I just want to know whether I am alone on
this before putting it on the wiki.

Manuel

 On 19 March 2006 02:35, Manuel M T Chakravarty 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.
  
  Why strict tuples, but not strict lists and strict Maybe and so on?
  Tuples are the Haskell choice of returning more than one result from a
  function.  So, if I write
  
add x y = x + y
  
  the caller gets an evaluated result.  However, if I write
  
addmul x y = (x + y, x * y)
  
  the caller gets a pair of two unevaluated results.  Even with bang
  patterns, I still have to write
  
addmul x y = let !s = x + y; !p = x * y in (s, p)
  
  to have both results evaluated.  With strict tuples
  
addmul x y = (!x + y, x * y!)
  
  suffices.
  
  Of course, the caller could invoke addmul using a bang patterns, as in
  
let ( !s, !p ) = addmul x y
in ...
  
  but that's quite different to statically knowing (from the type) that
  the two results of addmul will already be evaluated.  The latter
  leaves room for more optimisations.
  
  Syntax issues
  ~
  * In Haskell (,) is the pair constructor.  What should be use for
strict tuples?  (!,!) ?
  * With strict tuples (! and !) would become some sort of
reserved/special symbol.  That interferes with bang patterns, as
(!x, y!) would be tokenized as (! x , y !).  We could use ( ... !)
for strict tuples to avoid that conflict, or just requires that the
user write ( !x, !y ) when they want a bang pattern.  (Just like you
cannot write `Just.x' to mean `Just . x' as the former will always
be read as a qualified name and not the application of function
composition.
 

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: the MPTC Dilemma (please solve)

2006-03-20 Thread Claus Reinke

As understand it, you've proposed changes in context reduction to
restore confluence:


yes.


What is your plan to deal with non-termination (e.g. examples 6 and 16
of the FD-CHR paper)?


I haven't read all the suggestions that Martin, you, and others have 
made in that area yet (still busy with overlaps), including those in the 
revised FD-CHR paper, so I can't make concrete suggestions yet, 
beyond those I've already posted here:


1 we all want terminating instance inference, but trying to assure that
   via restrictions is bound to be limiting (does GHC still have to build
   part of the hierarchical libs with -fallow-undecidable-instances?).

   I'm not opposed to it, but I'd like Haskell' to document current
   practice, in that we have the option to switch of termination checks
   whenever they are not able to see that our programs are terminating
   (available in Hugs and GHC, and all too often necessary).

2 that said, termination checks can do a lot, and it is certainly useful
   know various methods of checking terminations, as well as terminating
   examples beyond current termination checks.

   the old FD-CHR draft already discussed relaxed FD conditions,
   but was somewhat hampered because confluence checks seemed
   entangled with termination. with confluence problems out of the
   way, the restrictions can focus on termination. was there any other
   reason not to go for the relaxed FD conditions as a start?

3 in http://www.haskell.org//pipermail/haskell-prime/2006-February/000825.html

   I gave two examples that are terminating, but for which the
   current conditions are too restrictive. the first could be cured
   by taking smaller predicates into account, in addition to smaller
   types and smaller variable sets, and the second turned out to be 
   a special case of the relaxed coverage condition, I think. I run 
   into both problems all the time (the first is especially annoying as 
   it prevents calling out to simpler helper predicates..).


4 example 6, FD-CHR, is vector multiplication Mul. I argued that 
   it is wrong to call the declarations faulty and invalid just because

   there are some invalid calls. I also suggested one way in which
   the declarations can be permitted, while ruling out the faulty call:

   http://www.haskell.org//pipermail/haskell-prime/2006-March/000847.html

   basically, the idea is that FDs specify type-level functions, so
   unless we can demonstrate that those functions are non-strict, we
   need to rule out cyclic type-level programs that feed the range of
   an FD into one of its domain parameters, by a generalized occurs
   check.

   simply looking at the intersection of variables is easy to implement;
   that method is still too conservative (eg, if the range is simly a
   copy of the domain), but adding it to our repertoire of termination 
   checks definitely improves the situation, and is sufficient to permit

   the declarations in example 6, while ruling out the offending call.

5 example 16, CHR, defines an instance that hides an increasing
   type behind an FD. my intuition on that one tells me that we are
   again ignoring the functional character of FDs (as we did in 4). 
   
   instead of ruling out types determined entirely by FDs via the 
   bound variable restriction, as the paper suggests, we could 
   extend the termination check to collect information about 
   FDs. just think of type constructors as simple FDs and try 
   to treat real FDs similarly: 

   adding a constructor around a type variable in the context 
   means we cannot guarantee termination by reasoning about 
   shrinking types. determining a type variable in the context by

   putting it in the range of an FD means we cannot guarantee
   termination by reasoning about shrinking types, unless we
   have some conservative approximation of the relation 
   between domain and range of the FD to tell us so.


   the example case:

   class F a b | a- b
   instance F [a] [[a]]

   clearly shows the range to be more complex than the domain,
   so we can account for that increase in complexity when we 
   see F t x in an instance context.


   if instead, we only had:

   class F a b | a-b
   instance F [[a]] [a]

   the range would be less complex than the domain, so we could
   permit use of this, even though the bound variable condition
   would treat it the same way - forbid it.

there are whole yearly workshops dedicated to termination.
we shouldn't assume that we can reach any satisfactory solution
by a mere handful of restrictions. which means that we need to
add to our repertoire of termination checks, and to keep open 
the option of switching of those checks.


cheers,
claus

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: the MPTC Dilemma (please solve)

2006-03-20 Thread Manuel M T Chakravarty
Claus Reinke:
  In fact, it's quite worrying that FDs have been around for so long and
  still resisted a thorough understanding.
 
 they don't resist. but as long as progress is example-driven and scary
 stories about FDs supposedly being tricky and inherently non-under-
 standable are more popular than investigations of the issues, there 
 won't be much progress. please don't contribute to that hype.

When I say hard to understand, I mean difficult to formalise.  Maybe I
have missed something, but AFAIK the recent Sulzmann et al. paper is the
first to thoroughly investigate this.  And even this paper doesn't
really capture the interaction with all features of H98.  For example,
AFAIK the CHR formalisation doesn't consider higher kinds (ie, no
constructor classes).

 it is okay to advertize for your favourite features. in fact, I might 
 agree with you that a functional type-class replacement would be 
 more consistent, and would be a sensible aim for the future. 
 
 but current Haskell has type classes, and current practice does use 
 MPTCs and FDs; and you don't do your own case any favours by 
 trying to argue against others advertizing and investigating their's. 

I don't care whether I do my case a favour.  I am not a politician.
There is only one reason that ATs exist: FDs have serious problems.

Two serious problems have little to do with type theory.  They are more
like software engineering problems:

 I. One is nicely documented in

http://www.osl.iu.edu/publications/prints/2003/comparing_generic_programming03.pdf
II. The other one is that if you use FDs to define type-indexed
types, you cannot make these abstract (ie, the representations
leak into user code).  For details, please see the Lack of
abstraction. subsubsection in Section 5 of
http://www.cse.unsw.edu.au/~chak/papers/#assoc

 you reply to a message that is about a month old.

That's what re-locating around half of the planet does to your email
responsiveness...but the topic is still of interest and I got the
impression that your position is still the same.

 for instance, ATS should just be special syntax for a limited, but 
 possibly sufficient and more tractable form of MPTCs/FDs, and 
 as long as that isn't the case in practice because of limitations in
 current implementations or theory, we don't understand either 
 feature set sufficiently well to make any decisions.

ATs are not about special syntax.  Type checking with ATs doesn't not
use improvement, but rather a rewrite system on type terms interleaved
with unification.  This leads to similar effects, but seems to have
slightly different properties.

Actually, I think, much of our disagreement is due to a different idea
of the purpose of a language standard.  You appear to be happy to
standardise a feature that may be replaced in the next standard.  (At
least, both of the choices you propose in your email include
deprecating a feature in Haskell''.)  I don't see that as an acceptable
solution.  A standard is about something that stays.  That people can
rely on.  IMHO if we consider deprecating a feature in Haskell'' again,
we should not include it in Haskell', but leave it as an optional extra
that some systems may experimentally implement and some may not.

Manuel


___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Re[2]: the MPTC Dilemma (please solve)

2006-03-20 Thread Manuel M T Chakravarty
Ross Paterson:
 On Sun, Mar 19, 2006 at 11:25:44AM -0500, Manuel M T Chakravarty wrote:
  My statement remains:  Why use a relational notation if you can have a
  functional one?
 
 I agree that functions on static data are more attractive than logic
 programming at the type level.  But with associated type synonyms,
 the type level is not a functional language but a functional-logic one.

Your are right, of course.  

Hand-waving-alert
However, the evaluation model is what is known as residuation
in the FL community, which is essentially functional programming
with logic variables and lenient evaluation (a la Id).  As long
as we only have strongly normalising functions, lenient
evaluation and lazy evaluation coincide.  So, for Haskell
programmers, we are on familiar ground.
/Hand-waving-alert

Manuel


___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Strict tuples

2006-03-20 Thread Manuel M T Chakravarty
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.  So, yes, I can just define my own

  data MyStrictPair a b = MyStrictPair !a !b

and use that.  My point is simply that strict tuples are a particularly
useful form of strict data types, so

  * they should be pre-defined in the Prelude and
  * they should inherit the special syntax of tuples.

So, this is not so much a language feature as a library issue.

Manuel


___
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: the MPTC Dilemma (please solve)

2006-03-20 Thread Aaron Denney
On 2006-03-20, Manuel M T Chakravarty [EMAIL PROTECTED] wrote:
 IMHO if we consider deprecating a feature in Haskell'' again,
 we should not include it in Haskell', but leave it as an optional extra
 that some systems may experimentally implement and some may not.

Possibly true, but it still needs to be standardized so that it will
work the same on different implementations.

-- 
Aaron Denney
--

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: the MPTC Dilemma (please solve)

2006-03-20 Thread Claus Reinke
For example, AFAIK the CHR formalisation doesn't consider higher 
kinds (ie, no constructor classes).


you're right about interactions in general. but do you think constructor 
classes specifically would pose any interaction problems with FDs?



I don't care whether I do my case a favour.  I am not a politician.
There is only one reason that ATs exist: FDs have serious problems.


you don't solve problems by creating new features from scratch,
with a different theory/formalization to boot. you try to pinpoint the
perceived problems in the old feature, then either transform it to
avoid those problems, or demonstrate that such transformation is
not possible. otherwise, you have the nasty problem of relating 
your new feature/theory to the old one to demonstrate that you've

really improved matters.


Two serious problems have little to do with type theory.  They are more
like software engineering problems:

I. One is nicely documented in
   
http://www.osl.iu.edu/publications/prints/2003/comparing_generic_programming03.pdf


that paper isn't bad as far as language comparisons go, but it focusses
on a rather restricted problem, so I'm surprised that this was part of the
motivation to launch ATS: to reduce the number of parameters in 
combined concepts, we might as well associate types with each

other, instead of types with instances.

variant A: I never understood why parameters of a class declaration
   are limited to variables. the instance parameters just have
   to match the class parameters, so let's assume we didn't
   have that variables-only restriction.

   class Graph (g e v) where
   src :: e - g e v - v
   tgt :: e - g e v - v

   we associate edge and node types with a graph type by
   making them parameters, and extract them by matching.

variant B: I've often wanted type destructors as well as constructors.
   would there be any problem with that?

   type Edge (g e v) = e
   type Vertex (g e v) = v

   class Graph g where
   src :: Edge g - g - Vertex g
   tgt :: Edge g  - g - Vertex g

variant C: the point the paper makes is not so much about the number
   of class parameters, but that the associations for concepts
   should not need to be repeated for every combined concept.
   and, indeed, they need not be

   class Edge g e | g - e
   instance Edge (g e v) e
   class Vertex g v | g - v
   instance Vertex (g e v) v

   class (Edge g e,Vertex g v) = Graph g where
   src :: e - g - v
   tgt :: e - g - v

   (this assumes scoped type variables; also, current GHC,
contrary to its documentation, does not permit entirely 
FD-determined variables in superclass contexts)


all three seem to offer possible solutions to the problem posed in 
that paper, don't they?



   II. The other one is that if you use FDs to define type-indexed
   types, you cannot make these abstract (ie, the representations
   leak into user code).  For details, please see the Lack of
   abstraction. subsubsection in Section 5 of
   http://www.cse.unsw.edu.au/~chak/papers/#assoc


do they have to? if variant C above would not run into limitations
of current implementations, it would seem to extend to cover ATS:

   class C a where
   type CT a

   instance C t0 where
   type CT t0 = t1

would translate to something like:

   class CT a t | a - t
   instance CT t0 t1

   class CT a t = CT a
   instance CT t0 t1 = C t0

as Martin pointed out when I first suggested this on haskell-cafe,
this might lead to parallel recursions for classes C and their type
associations CT, so perhaps one might only want to use this to
hide the extra parameter from user code (similar to calling auxiliary
functions with an initial value for an accumulator).


you reply to a message that is about a month old.


That's what re-locating around half of the planet does to your email
responsiveness...but the topic is still of interest and I got the
impression that your position is still the same.


definitely. I was just unsure how to react - if you really hadn't seen
the messages of the last month, it would be better to let you catch up
(perhaps via the mailing list archive). if you just took that message as
the natural place to attach your contribution to, there's no need to wait.


ATs are not about special syntax.  Type checking with ATs doesn't not
use improvement, but rather a rewrite system on type terms interleaved
with unification.  This leads to similar effects, but seems to have
slightly different properties.


that's what I'm complaining about. if ATs were identified as a subset of
FDs with better properties and nicer syntax, it would be easy to compare.

Re: Ranges and the Enum class

2006-03-20 Thread Wolfgang Jeltsch
Am Freitag, 17. März 2006 18:49 schrieb Ross Paterson:
 [...]

 Also, toEnum and fromEnum would make more sense mapping from and to
 Integer.

Why do we need toEnum and fromEnum at all?  As far as I know, they are merely 
there to help people implement things like enumFrom.  It's often not clear 
how toEnum and fromEnum should look like.  How should they be implemented for 
Time.Day, for example?  Should the days corresponds to the integers 0 to 6 or 
1 to 7?

 It seems that succ and pred are unused. 

No, I use them.  In my opinion, it makes much more sense to write succ n than 
n + 1.

Best wishes,
Wolfgang
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Strict tuples

2006-03-20 Thread Wolfgang Jeltsch
Am Sonntag, 19. März 2006 15:53 schrieb Bulat Ziganshin:
 Hello Manuel,

 Sunday, March 19, 2006, 5:35:12 AM, you wrote:

 MMTC PS: IIRC Clean supports strict tuples.

 i've proposed to allow adding strict mark to any type constructors and
 type constructor parameters so that finally we can define any data
 structure that can be defined in strict languages. in particular:

 type StrictPair a b = !(,) a b
 type StrictElements a b = (,) !a !b
 type StrictBoth a b = !(,) !a !b
 type StrictFunction a b = !(-) !a !b

 strictMap :: StrictFunction a b - ![!a] - ![!b]

 where ![!a] is a strict list with strict elements

Strictness has to refer to attributes (the things you apply a data constructor 
to).  In you approach, strictness is connected to type arguments.  This 
causes problems.  For example, if you have

data T a = C a a,

what would T !a mean?  Would both attributes be strict?  But how would you 
force only one attribute to be strict then?

These thinkings make me believe that assigning strictness flags to type 
arguments is just not sensible.

Best wishes,
Wolfgang
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Ranges and the Enum class

2006-03-20 Thread Aaron Denney
On 2006-03-20, Wolfgang Jeltsch [EMAIL PROTECTED] wrote:
 Am Freitag, 17. März 2006 18:49 schrieb Ross Paterson:
 [...]

 Also, toEnum and fromEnum would make more sense mapping from and to
 Integer.

 Why do we need toEnum and fromEnum at all?  As far as I know, they are merely 
 there to help people implement things like enumFrom.

Which could still be useful.

 It's often not clear 
 how toEnum and fromEnum should look like.  How should they be implemented for 
 Time.Day, for example?  Should the days corresponds to the integers 0 to 6 or 
 1 to 7?

I believe that 0 to n-1 is the standard representation that deriving Enum 
currently
uses.

 It seems that succ and pred are unused. 

 No, I use them.  In my opinion, it makes much more sense to write succ n than 
 n + 1.

Agreed, for non-arithmetical types.

-- 
Aaron Denney
--

___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime


Re: Strict tuples

2006-03-20 Thread John Meacham
On Mon, Mar 20, 2006 at 09:39:41AM -0500, Manuel M T Chakravarty wrote:
 Apart from the syntactic issues, does anybody else support the idea of
 strict tuples as proposed?  I just want to know whether I am alone on
 this before putting it on the wiki.

I have a few issues though, not entirely easy to articulate.

I worry about all the (! .. !) types that will appear in interfaces,
making things like (map fst) not work. It has been my experience that a
lot of things that should be strict that are obvious to the user, are
often obvious to the compiler as well. having the user place redundant
strictness annotations in can ofsucate where the actual performance
fixes are. As in, are lazy tuples actually a source of problems or are
we just guessing? ghc's strictness analyzer is pretty darn good, If
something is subtle enough for the compiler not to catch it, then the
programmer probably won't right off the bat either. it usually takes
profiling to determine where the human-fixable problems are.

strictness does not belong in the type system in general. strictness
annotations are attached to the data components and not type components
in data declarations because they only affect the desugaring of the
constructor, but not the run-time representation or the types in
general. attaching strictness info to types is just the wrong thing to
do in general I think.

however, strict tuples I think would have use in function returns,
no need to declare them as a separate type, just have

(! a,b !) desugar exactly to a `seq` b `seq` (a,b)

this avoids any type issues and the only time the strictness of a
constructor comes into play is in the constructor desugaring anyway, it
makes sense that strict tuples would be a simple desugaring to normal
tuples as well.

hope this makes sense...

John


-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-prime mailing list
Haskell-prime@haskell.org
http://haskell.org/mailman/listinfo/haskell-prime