perl6-language@perl.org

2005-09-07 Thread Luke Palmer
On 9/8/05, Damian Conway <[EMAIL PROTECTED]> wrote:
> Luke wrote:
> 
>  > Okay, fair enough.  The reason that I thought it was surprising is
>  > because 1 and 2 are usually orthogonal patterns.
> 
> It depends what they're doing. Matched against a regex like /[12]/ they're
> not orthogonal either.

Well, then they're not patterns; they're the things being matched
against a pattern.  But then you could think of junctions in the same
way.  In fact, the proposal was to do precisely that.  But I think
you've knocked me off of that one (with your "multiple junctions in
the same expression" examples).

>  > that was a logical statement explaining that junctions are not logical.
> 
> Right. So "Luke's statement is a logical travesty" isn't an
> unsubstantiated emotive assertion either? ;-)

Hey. I backed up my claim with a proof!  Let's settle on "It doesn't
matter!" :-)

>  >> if ! defined one(@inputs) {...}
>  >
>  > I don't get how this could possibly be useful.
> 
> That doesn't mean it's not. ;-)

You don't need to sell me on these, by the way.  You already did. 
That was just a comment on this particular example.

>  > So my original point was that, as cool as junctions are, they must not
>  > be values, lest logical assumptions that code makes be violated.  I
>  > can tell you one thing: an ordered set class assumes that < is
>  > transitive.  You had better not make an ordered set of junctions!
> 
> You can rest assured that I won't try to make one. Because it doesn't
> makes *sense* to even talk about an ordered set of junctions. Any more
> than it makes sense to talk about an ordered set of vectors, or lists,
> or regexes. Will you also be recommending that lists and regexes not be
> values???

Well, none of those things define a < operator.  I suppose one could
say that lists do, but he'd be wrong.  They coerce to numbers, which
in turn have a < operator, so you'd end up with a set of numbers...

I think I see where you're coming from though.  If we go with
Haskell's type classes, then I could see how this would work. 
Junction simply wouldn't do Eq or Ord (equality or ordering), since it
doesn't meet the prerequisites for doing those type classes
(transitivity and antisymmetry).  Then the Junctive > would be about
as similar to numeric > as IO::All's > is, at least from Perl's
perspective.

> More seriously, since the ordered set's methods presumably *won't* use
> (Item(+)Junction) type arguments, why will this be a problem? The
> ordered set will never *see* junctions.

Set of Junction?  If the methods are declared with parameters ::T (the
parameterization type of Set), then it certainly would accept
junctions.

Admittedly, that should just fail since it doesn't make any sense. 
Admittedly, it would probably end up succeeding and giving you an
infinite loop, and then comp.lang.perl.misc or #perl would give you a
belated compile-time error.  Or Set could say "No junctions!", but
then we're getting into special cases.

Hmm, incidentally, if we have:

theory Value[::T] {
# in order to do Value, eqv must be transitive:
# $a eqv $b and $b eqv $c implies $a eqv $c
multi infix: (::T, ::T --> Bool) {...}
# ... some useful methods
}

(For those of you following along at home, don't worry if you don't
know what a "theory" is, I haven't proposed it yet.  For those of you
lambdacamels following along at home, a "theory" is basically a type
class.)

Then Junction shouldn't do Value, since it doesn't meet one of the
implicit requirements.  Since Sets only operate on Values (no
reference types allowed: they can change under your feet), then a Set
would reject a Junction as a valid parameterization.  Oh, I guess
Junction's absence of the Ordered class already did that.

Alright, this seems to be working out mathematically if we get type
classes.  It's really not a solution I like much, as it's basically
saying "yeah, junctions exist, but they really don't participate in
the algebra of your program".  Actually, since they don't do Value,
you can't make any aggregate of Junctions whether you declare it or
not (sub parameters are still okay when declared though; they don't
have to be Values).

Okay, with that, my position changes.  I no longer see anything wrong
with Junctions from a pure perspective.  I still think it's wrong to
Humans to have something that looks ordered but in fact isn't, and I
still think that if Junctions are values, you ought to be able to
metaprogram with them.  But I don't really have any ideas other than
the ones I've proposed in this thread and the one involving Haskell's
"M" word.

Luke


perl6-language@perl.org

2005-09-07 Thread Damian Conway

Luke wrote:

> Okay, fair enough.  The reason that I thought it was surprising is
> because 1 and 2 are usually orthogonal patterns.

It depends what they're doing. Matched against a regex like /[12]/ they're
not orthogonal either.


>> > Junctions are logical travesty,
>>
>>Well, that's very emotive, but I don't believe it's either a useful or
>>an accurate characterization. I would agree that junctions can be
>>logically *sophisticated*, but then I'd argue that *all* programming
>>constructs are that.
>
> No, that wasn't emotive,

"Travesty" is not an emotive word???


> that was a logical statement explaining that junctions are not logical.

Right. So "Luke's statement is a logical travesty" isn't an
unsubstantiated emotive assertion either? ;-)



> Have you ever heard of generic programming?
>
> How can any *ever* write a sensible generic Set class when you are
> required to know what kind of thing you have in the set?

By restricting the implementation to behaviours that are universal (see
below). Or by restricting the set of contained values to values for
which the implemented behaviours work correctly. That is: just like any
other kind of programming.


>>Otherwise hard things that junctions make a lot easier:
>>
>> if 0 <= @coefficients < 1 {...}
>
> Ummm... that's an array in numeric context...

Yes. A mistake. I (fairly obviously) meant:

   if 0 <= all @coefficients < 1 {...}


>> if ! defined one(@inputs) {...}
>
> I don't get how this could possibly be useful.

That doesn't mean it's not. ;-)

You might use exactly that test to initiate autocomputation of the one
missing value. For example, if you're given volume, pressure, and
temperature values of a gas, but one is undefined, then you might
want to compute it from the others. That test would tell you that you need to 
(and that you have enough information to do so).




> In particular, testing whether all
> elements in a list are equal goes from an O(n) operation to an O(n^2)
> operation, since I can't make the assumption that equality is
> transitive.

That's simply not true. It is perfectly possible to write an O(n) list
equality test on a list that may include junctions. You simply need an
elementwise equality test that handles junctions correctly. Let's call it
C:

# Junctions same if same type, same number of values, and same values...
multi sub same(Junction $j1, Junction $j2) {
return 0 if $j1.type != $j2.type || $j1.values != $j2.values;
return [&&] same<<($j1.values, $j2.values);
}

# Junctions and non-junctions never the same...
multi sub same(Junction $j, Item $i) is reversible {
return 0;
}

# Non-junctions same if == (or whatever base-case test you prefer)
multi sub same(Item $i1, Item $i2) {
return $i1 == $i2;
}

# List elems equal if each pair of adjacent elements is the same...
sub all_equal(@list) {
return [&&] same<<(@[EMAIL PROTECTED], @list[1...]);
}



> So my original point was that, as cool as junctions are, they must not
> be values, lest logical assumptions that code makes be violated.  I
> can tell you one thing: an ordered set class assumes that < is
> transitive.  You had better not make an ordered set of junctions!

You can rest assured that I won't try to make one. Because it doesn't
makes *sense* to even talk about an ordered set of junctions. Any more
than it makes sense to talk about an ordered set of vectors, or lists,
or regexes. Will you also be recommending that lists and regexes not be
values???

More seriously, since the ordered set's methods presumably *won't* use
(Item(+)Junction) type arguments, why will this be a problem? The
ordered set will never *see* junctions.

Damian


perl6-language@perl.org

2005-09-07 Thread Thomas Sandlass
HaloO,

Luke wrote:
> I just proved that < is not transitive.
>
> I can do that for every boolean operator that Perl has.  They no
> longer have any general properties, so you can't write code based on
> assumptions that they do.   In particular, testing whether all
> elements in a list are equal goes from an O(n) operation to an O(n^2)
> operation, since I can't make the assumption that equality is
> transitive.

I fully second this. I guess the axiom of excluded middle simply doesn't
hold for the four junction types, nor are they ordered.
(Sidenode as non-native: is the last usage of 'nor' incorrect?)
But so will be many other types.

Could someone point me to a mathematical paper or general material what
axiom system applies to junctions?


> So my original point was that, as cool as junctions are, they must not
> be values, lest logical assumptions that code makes be violated.  I
> can tell you one thing: an ordered set class assumes that < is
> transitive.  You had better not make an ordered set of junctions!

With a certain stricture on defining the meaning of tokens like < I
think Perl6 shouldn't join poor C++ with its fixed set of operators
to overload ops arbitrarily with unrelated meaning. Unicode has enough
to offer. But back to the point that Luke made: all comparison ops don't
apply to junctions which spoils a big advantage and deminishes junctions
to a nice form to avoid chained boolean connectives like || with an any().

To me junctions always felt more code like than value like. They
are even some kind of meta ops that consume boolean comparison ops
in terms of another boolean connective (any => or, all => and, etc.)
Why not reflect that in the syntax and make them like for, map,
grep etc? I mean with the junction name in front:

   if all( @new_coefficients < @prev_coefficients ) {...}

or Brent's example

   if any( $active eq ['all', keys %to] ) {...}

The desugared forms would be simple ternary calls:

  if any( &infix:{'<'}, $active, ['all', keys %to] ) {...}

The return value would need to be lists of tuples to allow
combining junctions:

  if any($x < all(@values > 0))

That latter property also gives

  for all(@values > 0) -> $x { say sqrt $x }

And as all other code types junctions are subject to currying
and later usage like other code refs

  &x_in = any.assuming( lhs => $x, op => &infix:<==> );

  if &x_in( @array ) {...}

With (curried) junctions travelling in & vars I guess people
have less problems with the auto-threading behaviour as well.

Hmm, and we win back the three single character infix ops |, &
and ^. The simple example

  if $x == 1|2|3 {...}

then reads

  if any($x == [1,2,3]) {...}

I admit though, that the any might be optically attached to the
$x and not to the implicitly hyperated ==. Thus the idiom needs
to be spelled

  if any([1,2,3] == $x) {...}

TSa.



Re: Packages, Modules and Classes

2005-09-07 Thread Stevan Little

Larry,

On Sep 7, 2005, at 12:45 PM, Larry Wall wrote:
: >All sigils and twigils are part of the key to the symbol table, so 
it's

: >now just
: >
: >Foo<$.baz>
:
: What would Foo<$.baz> return though (assuming Foo is a class)? It
: cannot return a value since it is an instance specific value.

Foo<@baz> is not a value either, but a container.  I would say that
Foo<$.baz> returns a generic container that happens not to work
without an extra instance argument to say which chunk of data to map
the container metainfo onto.

: Should it return some kind of meta-object?

Yes.


If methods and subs are in the same namespace, and both have the & 
sigil, what about instance attributes and class attributes? Is this 
legal?


class Foo {
my $.bar;
has $.bar;
}

Part of me thinks that it should be since my $.bar is an attribute of 
the Foo class, and has $.bar is an attribute of instances of Foo.


Also, is there anyway to iterate over the keys in the namespace? The 
old way would be to do something like keys(%Foo::). Is something like 
this possible with the new way?


Thanks,

Stevan



perl6-language@perl.org

2005-09-07 Thread Luke Palmer
On 9/7/05, Brent 'Dax' Royal-Gordon <[EMAIL PROTECTED]> wrote:
> Here's a Real Live Perl 6 module I wrote recently.  I've omitted a few
> magic portions of the code for clarity.

Thanks for real live perl 6 code.  It's always nice to have real examples.

However, I'm arguing for logical stability without losing expressive
power.  The case that convinces me is the one where something becomes
a lot harder without lexical junctions.  This one doesn't:

> module Trace-0.01-BRENTDAX;
> 
> my $active;
> ...
> 
> sub activate(*%newtags) {
> $active |= any(keys %newtags);
   @active.push(keys %newtags);
> }
> 
> sub trace([EMAIL PROTECTED] is copy, *%to is copy) is export {
> ...
> if $active eq any('all', keys %to) {
  if any(@active) eq any('all', keys %to) {
> ...
> print $ERR: @msg;
> return [EMAIL PROTECTED] #but true;
> }
> return;
> }

And that is clearer to me at least.  You can tell the nature of the
comparison: that you're checking a list of pattern against a list of
active objects, rather than a list of patterns against a single
object, which is what it looked like before.  YMMV on that angle,
though.

The reason I think that this approach won't lose expressive power is
mostly because of our new Set class.  The one remaining thing is when
you build up a nested junction in terms of ors and ands and check
that, as was given in one of Damian's old examples.  I really haven't
come up with a reason you'd want to do that yet, but I *am* looking. 
I'm not on a mission to destroy junctions, really. I'm just on a
mission to make things make sense. :-/

Luke


perl6-language@perl.org

2005-09-07 Thread Brent 'Dax' Royal-Gordon
On 9/7/05, Luke Palmer <[EMAIL PROTECTED]> wrote:
> And this is based on lexical expansion.  Which is cool.  In fact, once
> upon a time I was going to propose that junctions are a purely lexical
> entity, expanded into greps and whatnot by the compiler; that you
> can't ever stick them in variables.  Your examples above are just more
> attestment to that, since there is not one of them that I can't write
> confining all junctions to lexical areas.

Here's a Real Live Perl 6 module I wrote recently.  I've omitted a few
magic portions of the code for clarity.

module Trace-0.01-BRENTDAX;

my $active;
...

sub activate(*%newtags) {
$active |= any(keys %newtags);
}

sub trace([EMAIL PROTECTED] is copy, *%to is copy) is export {
...
if $active eq any('all', keys %to) {
...
print $ERR: @msg;
return [EMAIL PROTECTED] #but true;
}
return;
}

I rather like that non-lexical use of junctions.

-- 
Brent 'Dax' Royal-Gordon <[EMAIL PROTECTED]>
Perl and Parrot hacker


Re: \(...)?

2005-09-07 Thread Juerd
Ingo Blechschmidt skribis 2005-09-06 21:24 (+0200):
> > \(@array,) is [ @array ], NOT map { \$_ } @array
> I'm not sure of the []s, remember &postcirumfix:<[ ]> creates *new*
> containers:

That was the point.

> [EMAIL PROTECTED] = $bar;
> (@array,)[0] = $bar;

AFAIK, these are the same thing, because the left side of [0] is in
Array context, which is a scalar context, in which comma creates a new
anonymous array ref.


Juerd
-- 
http://convolution.nl/maak_juerd_blij.html
http://convolution.nl/make_juerd_happy.html 
http://convolution.nl/gajigu_juerd_n.html


Re: Proposal: split ternary ?? :: into binary ?? and //

2005-09-07 Thread Juerd
Larry Wall skribis 2005-09-07  8:32 (-0700):
> I think that's a powerful argument even if we don't have an infix:<::>.
> Plus I hate all infix "nor" operators due to my English-speaking bias
> that requires a "neither" on the front.  So let's go ahead and make
> it ??!!.  (At least this week...)

I was going to object based on !!foo being ! ! foo, but that !! is
spelled ? now, so nevermind.


Juerd
-- 
http://convolution.nl/maak_juerd_blij.html
http://convolution.nl/make_juerd_happy.html 
http://convolution.nl/gajigu_juerd_n.html


Re: Packages, Modules and Classes

2005-09-07 Thread Larry Wall
On Wed, Sep 07, 2005 at 12:27:20PM -0400, Stevan Little wrote:
: How do I differentiate a method from a sub? Wouldn't they both have the 
: & sigil?

Yes, as it currently stands, you can only tell that by introspection.

: >:   class Foo;
: >:   has $.baz;
: >:   method bar { ... }
: >:
: >: Can I get to $.baz? If I can, what will I get?
: >
: >All sigils and twigils are part of the key to the symbol table, so it's
: >now just
: >
: >Foo<$.baz>
: 
: What would Foo<$.baz> return though (assuming Foo is a class)? It 
: cannot return a value since it is an instance specific value.

Foo<@baz> is not a value either, but a container.  I would say that
Foo<$.baz> returns a generic container that happens not to work
without an extra instance argument to say which chunk of data to map
the container metainfo onto.

: Should it return some kind of meta-object?

Yes.

:Or possibly the default value specified (if one is specified)?

No, symbol tables don't hold values.  (We once thought about making
the attribute return the default value within class methods (in fact
the Apocalypse espouses that, if I recall) but we eventually decided
that it was a confusing idea.)

: Can this value be written too?

Only via introspection.

: If so, how does that affect things?

Doesn't, since you can't.

: Also would/should this work:
: 
: $iFoo<$.baz>

Yes, but...

: As a means of breaking the opaque instance data structure. (I for one, 
: vote no on that).

It would still get you the metacontainer, which these days still
represents an virtual call and thus doesn't break encapsulation.
The name of the non-virtual storage for $.baz is currently $._baz
(with a private ._baz() accessor akin to the old .:baz() accessor),
and we presumably take steps to prevent people from breaking any "_"
encapsulation trivially.  (The debugger needs to get at the info,
of course, which basically means anyone can if they pretend to be
the debugger, but we don't have to make it easy...)

Larry


Re: Packages, Modules and Classes

2005-09-07 Thread Stevan Little

Larry,

On Sep 7, 2005, at 11:46 AM, Larry Wall wrote:

: I base this off the AUTO* hooks described in
: S10. I assume too that the METH slot is only valid for Classes, and 
not

: appropriate for Packages and Modules.

All those entries are based on the notion of intuiting from the first
character of the variable name within the symbol table, not from having
separate typeglobbish slots within each symbol.


How do I differentiate a method from a sub? Wouldn't they both have the 
& sigil?



:   class Foo;
:   has $.baz;
:   method bar { ... }
:
: Can I get to $.baz? If I can, what will I get?

All sigils and twigils are part of the key to the symbol table, so it's
now just

Foo<$.baz>


What would Foo<$.baz> return though (assuming Foo is a class)? It 
cannot return a value since it is an instance specific value. Should it 
return some kind of meta-object? Or possibly the default value 
specified (if one is specified)? Can this value be written too? If so, 
how does that affect things?


Also would/should this work:

$iFoo<$.baz>

As a means of breaking the opaque instance data structure. (I for one, 
vote no on that).


- Stevan



Re: Packages, Modules and Classes

2005-09-07 Thread Larry Wall
On Wed, Sep 07, 2005 at 08:46:24AM -0700, Larry Wall wrote:
: No special {FOO} subscripts, so the question doesn't arise.  To the
: symbol table all blocks are stored as Foo<&bar>, presumably with
: extra canonicalized key info for "long" names.

Actually, we might well omit the '&' on Code objects for better
interoperability with other languages, unless we name mangle it.
(Might need to name-mangle the key of Foo<::Bar> in any event,
so maybe Foo<&bar> isn't any different in that respect when other
languages want to look up the .bar method.  Come to think of it,
Perl 6 usually wants to look it up without the & too.  :-)

If for some reason we decided to allow a sub and a method of the same
name, I suppose we could make them Foo<&bar> and Foo<.bar>.  But for now
we've got subs and/or methods in the same namespace.

Larry


Re: Proposal: split ternary ?? :: into binary ?? and //

2005-09-07 Thread Patrick R. Michaud
On Wed, Sep 07, 2005 at 08:32:39AM -0700, Larry Wall wrote:
> 
> I think that's a powerful argument even if we don't have an infix:<::>.
> Plus I hate all infix "nor" operators due to my English-speaking bias
> that requires a "neither" on the front.  So let's go ahead and make
> it ??!!.  (At least this week...)

Yay !!

Pm


Re: \(...)?

2005-09-07 Thread Larry Wall
We can do whatever we like with \ since it's really a *macro* that
imposes lvalue context (or at least, indirection in the abstract, if
we were ever to allow it in an outer lvalue context).  In the case of
\($a,$b) it is also distributing that context over the items in the
list without copying.

The only questions in my mind are whether Perl 5's \($a,$b) is
what people expect (it's arguably counterintuitive to newbies),
and whether there's some other construct that would more naturally
construct a list of references.  It's not just \« though, since it
has to *parse* as a list of lvalues.  Maybe a siglet can degenerate to
that, but there are problems with that approach too.  Unless someone
can come up with a better proposal, \($a,$b) is the default winner
on the basis of prior Perl 5 art.

Larry


Re: Packages, Modules and Classes

2005-09-07 Thread Larry Wall
On Tue, Sep 06, 2005 at 02:04:00PM -0400, Stevan Little wrote:
: I assume that each symbol table entry has the following slots; SCALAR, 
: ARRAY, HASH, SUB, METH.

Nope, typeglobs are dead, dead, dead, dead, and dead, not necessariy in
that order.

: I base this off the AUTO* hooks described in 
: S10. I assume too that the METH slot is only valid for Classes, and not 
: appropriate for Packages and Modules.

All those entries are based on the notion of intuiting from the first
character of the variable name within the symbol table, not from having
separate typeglobbish slots within each symbol.

: This would mean that given this code:
: 
:   package Foo;
:   our $baz;
:   sub bar { ... }
: 
: %Foo::{'bar'}{SUB} is a ref to the &bar sub, and %Foo::{'baz'}{SCALAR} 
: is a ref to the scalar $baz.

That syntax is also dead, including the %Foo:: part of it.
If you'll look at the most recent S2 from 
http://svn.perl.org/perl6/doc/trunk/design/syn/S02.pod (the dev.perl.org web 
pages
are out of date), you'll find:

To do direct lookup in a package's symbol table without scanning, treat
the package name as a hash:

Foo::Bar{'&baz'}# same as &Foo::Bar::baz
GLOBAL<$IN> # Same as $*IN
Foo<::Bar><::Baz>   # same as Foo::Bar::Baz

Unlike C<::()> symbolic references, this does not parse the argument
for C<::>, nor does it initiate a namespace scan from that initial point.

: The same, I would assume, would apply for 
: Modules, so that:
: 
:   module Foo;
:   our $baz;
:   sub bar { ... }
: 
: is pretty much interchangable with the first example. But I think it's 
: a little trickier when we get to Classes. Given this code:
: 
:   class Foo;
:   our $baz;
:   sub bar { ... }
: 
: I would expect it to behave just as it does for a Package or Module. 
: But when we start to introduce methods and attributes, I am unsure of 
: how things will work.
: 
:   class Foo;
:   has $.baz;
:   method bar { ... }
: 
: Can I get to $.baz? If I can, what will I get?

All sigils and twigils are part of the key to the symbol table, so it's
now just

Foo<$.baz>

: I expect that %Foo::{'bar'}{METH} will give me a method ref, but what 
: happens when I try to store something in it? Does that perform some 
: kind of meta-model actions (Foo.meta.change_method(...) or somesuch)? 
: What if I delete the symbol table entry, what happens then (more 
: meta-trickery)?

No special {FOO} subscripts, so the question doesn't arise.  To the
symbol table all blocks are stored as Foo<&bar>, presumably with
extra canonicalized key info for "long" names.

Larry


Re: Proposal: split ternary ?? :: into binary ?? and //

2005-09-07 Thread Larry Wall
On Tue, Sep 06, 2005 at 04:57:30PM +0200, Thomas Sandlass wrote:
: HaloO,
: 
: Luke wrote:
: > Okay, now why don't you tell us about this new binary :: you're proposing.
: 
: Well, not a new one. Just plain old foo::bar::blahh and 'my ::blubb $x'
: with relaxed whitespace rules. The ternary ?? :: is a splinter in my
: mind's eye because it is not a compile time or symbol lookup construct.
: 
: The driving idea is to let tokens always mean the same or at least very
: similar things in different contexts. And I thought that is your rating
: as well. For :: that should be 'symbol table management'. E.g. ::= fits
: that notion perfectly while the alternative separation of the ternary
: doesn't.

I think that's a powerful argument even if we don't have an infix:<::>.
Plus I hate all infix "nor" operators due to my English-speaking bias
that requires a "neither" on the front.  So let's go ahead and make
it ??!!.  (At least this week...)

Larry


perl6-language@perl.org

2005-09-07 Thread Luke Palmer
On 9/7/05, Damian Conway <[EMAIL PROTECTED]> wrote:
> Luke wrote:
>  > In that last case though, this is not equivalent to the above:
>  >
>  > given &code.arity {
>  > when 2 { code(1,2) }
>  > when 1 { code(1) }
>  > }
>  >
>  > That may be a little... surprising.  Still, it's fixed to succeed
>  > either way, so that's probably okay, right?
> 
> It's not surprising at all. The order of C tests (usually) matters,
> because a series of C statements (usually) short-circuits.

Okay, fair enough.  The reason that I thought it was surprising is
because 1 and 2 are usually orthogonal patterns.  But, I guess in the
presence of junctions I'm not able to assume that (as I'll explain in
my conclusion later, junctions make it impossible for me to assume
just about anything).

>  > Junctions are logical travesty,
> 
> Well, that's very emotive, but I don't believe it's either a useful or an
> accurate characterization. I would agree that junctions can be logically
> *sophisticated*, but then I'd argue that *all* programming constructs are 
> that.

No, that wasn't emotive, that was a logical statement explaining that
junctions are not logical.  Maybe that's what I should have said
before.  See below.

>  > and it seems to me that they cease to be useful in all but the
>  > situations where the coder knows *everything*.
> 
> What does that mean, exactly? How can anyone *ever* write sensible code
> without knowing what kind of values they're processing?

Have you ever heard of generic programming?

How can any *ever* write a sensible generic Set class when you are
required to know what kind of thing you have in the set?

> Otherwise hard things that junctions make a lot easier:
> 
>  if 0 <= @coefficients < 1 {...}

Ummm... that's an array in numeric context...

>  if 0 <= all(@new_coefficients) < all(@prev_coefficients) < 1 {...}

I'll give you this one.  This takes twice the amount of code.

if 0 <= min(@new_coefficients) && 
max(@new_coeffficients) < min(@prev_coefficients) &&
max(@prev_coefficients) < 1   {...}

>  if 0 <= all(@new_coefficients) != all(@prev_coefficients) < 1 {...}
> 
>  if 0 <= any(@new_coefficients) != all(@prev_coefficients) < 1 {...}

Okay, you may be convincing me here.  Until I find a good way to do
these.  The fact that I have to look is already junctions++.

>  if ! defined one(@inputs) {...}

I don't get how this could possibly be useful.

>  > $a <= any($a, $b).
>  > any($a, $b) <= $b.
>  > Therefore, $a <= $b.

...

>  Luke is no smarter than Luke or Luke is no smarter than a rock.
>  Luke is no smarter than a rock or a rock is no smarter than a rock.
> 
> Remove the false assertions (since nothing correct can ever be deduced
> from a false assertion):

Sure, everything correct can be deduced from a false premise.  Just...
um... everything incorrect can too.  :-)

>  Luke is no smarter than Luke
>a rock is no smarter than a rock.
> 
> But now the remaining assertions support *no* new conclusion.

And this is based on lexical expansion.  Which is cool.  In fact, once
upon a time I was going to propose that junctions are a purely lexical
entity, expanded into greps and whatnot by the compiler; that you
can't ever stick them in variables.  Your examples above are just more
attestment to that, since there is not one of them that I can't write
confining all junctions to lexical areas.

I think you missed my original point.  Here is a similar proof:

Assume for the sake of contradiction that:
  For all $a,$b,$c:
$a < $b && $b < $c implies $a < $c;

let $a = 3, $b = any(1,4), and $c = 2

Substituting:
3 < any(1,4) && any(1,4) < 2 implies 3 < 2
   True  implies False
Contradiction!

I just proved that < is not transitive.

I can do that for every boolean operator that Perl has.  They no
longer have any general properties, so you can't write code based on
assumptions that they do.   In particular, testing whether all
elements in a list are equal goes from an O(n) operation to an O(n^2)
operation, since I can't make the assumption that equality is
transitive.

So my original point was that, as cool as junctions are, they must not
be values, lest logical assumptions that code makes be violated.  I
can tell you one thing: an ordered set class assumes that < is
transitive.  You had better not make an ordered set of junctions!

Luke


perl6-language@perl.org

2005-09-07 Thread Larry Wall
On Tue, Sep 06, 2005 at 06:19:01PM +0300, Yuval Kogman wrote:
: On Tue, Sep 06, 2005 at 13:28:24 +, Luke Palmer wrote:
: 
: This should still work:
: 
: > sub map (&code, [EMAIL PROTECTED]) {
: > gather {
: > my @args = @list.splice(0, &code.arity);
: > take &code([EMAIL PROTECTED]);
: > }
: > }
: 
:   multi sub foo ( ... ) { ... } 
:   multi sub foo ( ... ) { ... }
: 
:   my @mapped = map &foo ...;
: 
: I think this is inconsistent.
: 
: There is another option though:
: 
:   sub map (&code, [EMAIL PROTECTED]) {
:   gather {
:   take &code.mutably_bind_some(@list); # removes stuff
:   # from @list
:   }
:   }
: 
: The code object can then look for suitable multimethod alternatives
: for the arguments in question, avoid that alltogether, dispatch
: based on the arity of the first alternative, dispatch based on the
: arity of the most general alternative, or whatever.

Yes, I think that's closer to the mark.  The basic problem is having
to deal with the arity *at all*, much as having to deal with string
positions as integers is becoming wronger as we get into Unicode.
What we're looking for here is a better abstraction, and I suspect that
this abstraction involves defining a class of dispatch that assumes an
implicit slurpy on the end of everything called, and simply returns
any unbound arguments as the "unshifted" part of the list.  It could
maybe even be made to work right with respect to ? parameters that
might or might bind based on type.

It's very much like an inside-out .assuming, only it does the actual
call, and leaves the residue.  Another view is that it's basically
turning a normal call into a mutator call of the splice variety.
So maybe map is just

sub map (&code, [EMAIL PROTECTED]) {
gather {
take @list.splice(&code);
}
}

or some such.

Larry