Compiled in D5.1 but fails on D6

Previous Topic Next Topic
 
classic Classic list List threaded Threaded
8 messages Options
Reply | Threaded
Open this post in threaded view
|

Compiled in D5.1 but fails on D6

Fernando Rodríguez
Hi,

This String method, stolen form Chris Uppal, used to wok fine  on Dolphin
5.1, but fails on D6.  It complains about an illegal assignment... :-?


editDistanceTo: aComparand
 "answer the edit distance between the reciever and the <SequenceableCollection>,
aComparand.
 The edit distance is the minimum number of <<insert>> or <<delete>> operations
needed to turn
 one sequence into another.

 This is an implementation of the algorithm described in:

  An O(NP) Sequence Comparison Algorithm
  Sun Wu, Udi Manber, Gene Myers & Webb Miller
  Information Processing Letters, vol. 35, pp. 317-323, 1990.

 which can be found online at:

  http://www.cs.arizona.edu/peop le/gene/PAPERS/np_diff.ps

 I have followed their presentation of the algorithm almost exactly.

 The main change I've made is to ensure that array N is larger than array
M, which the paper assumes.

 The other big change I've had to make is to the array 'fp', in the paper
pseudo-code this has range
 [-(m+1), (N+1)]; for the Smalltalk implementation I've had to introduce
an offset of M+2 to accommodate
 Smalltalk's 1-based arrays.  I've also introduced the variables M1, M2 and
M3 to help pre-compute some
 of these indexes.

 Other differences are that their Greek 'DELTA' (the index of the target
diagonal) is here called 'diag', and
 their Snake() subroutine is implemented as a block.  I've changed the names
of its local variables, k, x and y,
 to make it clear that there is no aliasing with the main body of this routine"

 | A B M N diag snake fp p M1 M2 M3 |
#CUadded.

 self size <= aComparand size
  ifTrue:
   [A := self.
   B := aComparand]
  ifFalse:
   [A := aComparand.
   B := self].

 M := A size.
 N := B size.
 diag := N - M.
 snake :=
  [:kk :yy || xx |
  xx := yy - kk.
  [xx < M and: [yy < N and: [(A at: xx+1) = (B at: yy+1)]]]
   whileTrue: [xx := xx+1. yy := yy+1].  "<--- Illegal assignment to yy!"
  yy].

 fp := Array new: N + M + 3.
 M1 := M+1.
 M2 := M+2.
 M3 := M+3.
 (-1-M) to: (N+1) do: [:i | fp at: i+M2 put: -1].

 p := -1.
 [p := p + 1.
 (0-p) to: (diag-1) do:
  [:k | fp at: k+M2 put: (snake value: k value: (((fp at: k+M1) + 1) max:
(fp at: k+M3)))].
 (diag+p) to: (diag+1) by: -1
  do: [:k | fp at: k+M2 put: (snake value: k value: (((fp at: k+M1) + 1)
max: (fp at: k+M3)))].
 fp at: diag+M2 put: (snake value: diag value: (((fp at: diag+M1) + 1) max:
(fp at: diag+M3))).
 (fp at: diag+M2) = N]
  whileFalse.

 ^ diag + (2 * p).


Reply | Threaded
Open this post in threaded view
|

Re: Compiled in D5.1 but fails on D6

Chris Uppal-3
Fernando,

>  snake :=
>   [:kk :yy || xx |
>   xx := yy - kk.
>   [xx < M and: [yy < N and: [(A at: xx+1) = (B at: yy+1)]]]
>    whileTrue: [xx := xx+1. yy := yy+1].  "<--- Illegal assignment to yy!"
>   yy].

Dolphin used to allow assignment to block parameters, now it doesn't.

I'm pretty sure that all you have to do is introduce a new temporary variable,
assign yy to it as the block is entered, and then change the rest of the block
to use your temp instead of yy.

E.g. (untested)

snake :=
     [:kk :yyIn || xx yy |
     xx := yyIn - kk.
     yy := yyIn.
     [xx < M and: [yy < N and: [(A at: xx+1) = (B at: yy+1)]]]
           whileTrue: [xx := xx+1. yy := yy+1].
    yy].

BTW, D6 comes with a diff implementation.  See SequenceableCollection and the
methods in category 'computing differences'.  It's used in the DiffPresenter.
I don't know how the two algorithms (or their implementations) compare for
efficiency.

    -- chris


Reply | Threaded
Open this post in threaded view
|

Re: Compiled in D5.1 but fails on D6

ian-3
Chris Uppal wrote:

> Fernando,
>
> >  snake :=
> >   [:kk :yy || xx |
> >   xx := yy - kk.
> >   [xx < M and: [yy < N and: [(A at: xx+1) = (B at: yy+1)]]]
> >    whileTrue: [xx := xx+1. yy := yy+1].  "<--- Illegal assignment to yy!"
> >   yy].
>
> Dolphin used to allow assignment to block parameters, now it doesn't.
>
> I'm pretty sure that all you have to do is introduce a new temporary variable,
> assign yy to it as the block is entered, and then change the rest of the block
> to use your temp instead of yy.
>
> E.g. (untested)
>
> snake :=
>      [:kk :yyIn || xx yy |
>      xx := yyIn - kk.
>      yy := yyIn.
>      [xx < M and: [yy < N and: [(A at: xx+1) = (B at: yy+1)]]]
>            whileTrue: [xx := xx+1. yy := yy+1].
>     yy].
>
> BTW, D6 comes with a diff implementation.  See SequenceableCollection and the
> methods in category 'computing differences'.  It's used in the DiffPresenter.
> I don't know how the two algorithms (or their implementations) compare for
> efficiency.
>
>     -- chris

is there a good reason why D6 doesn't allow assignment to block
variables? I can see that this state of affairs could cause some
interesting "workarounds". For instance as part of a log file
renumbering routine I'd got:

renameBackups: aCollection
        aCollection
                inject: aCollection size + 1
                into:
                        [:i :each |
                        File rename: each path to: (File path: each path extension: z
displayString).
                        i := i - 1]

which won't compile in D6. I'm still trying to think of a workaround
for this one...

      Ian


Reply | Threaded
Open this post in threaded view
|

Re: Compiled in D5.1 but fails on D6

ian-3
In reply to this post by Chris Uppal-3
Chris Uppal wrote:

> Fernando,
>
> >  snake :=
> >   [:kk :yy || xx |
> >   xx := yy - kk.
> >   [xx < M and: [yy < N and: [(A at: xx+1) = (B at: yy+1)]]]
> >    whileTrue: [xx := xx+1. yy := yy+1].  "<--- Illegal assignment to yy!"
> >   yy].
>
> Dolphin used to allow assignment to block parameters, now it doesn't.
>
> I'm pretty sure that all you have to do is introduce a new temporary variable,
> assign yy to it as the block is entered, and then change the rest of the block
> to use your temp instead of yy.
>
> E.g. (untested)
>
> snake :=
>      [:kk :yyIn || xx yy |
>      xx := yyIn - kk.
>      yy := yyIn.
>      [xx < M and: [yy < N and: [(A at: xx+1) = (B at: yy+1)]]]
>            whileTrue: [xx := xx+1. yy := yy+1].
>     yy].
>
> BTW, D6 comes with a diff implementation.  See SequenceableCollection and the
> methods in category 'computing differences'.  It's used in the DiffPresenter.
> I don't know how the two algorithms (or their implementations) compare for
> efficiency.
>
>     -- chris

is there a good reason why D6 doesn't allow assignment to block
variables? I can see that this state of affairs could cause some
interesting "workarounds". For instance as part of a log file
renumbering routine I'd got:

renameBackups: aCollection
        aCollection
                inject: aCollection size + 1
                into:
                        [:i :each |
                        File rename: each path to: (File path: each path extension: z
displayString).
                        i := i - 1]

which won't compile in D6. I'm still trying to think of a workaround
for this one...

      Ian


Reply | Threaded
Open this post in threaded view
|

Re: Compiled in D5.1 but fails on D6

Chris Uppal-3
Ian,

> is there a good reason why D6 doesn't allow assignment to block
> variables?

It's parallel to how (unlike most language which allow assignment at all) you
can't assign to a method's parameter "variables".  To be honest, I have never
been all that convinced that there's a defensible justification for it.  It's
just how Smalltalk is (or rather, how Smalltalk was supposed to be but Dolphin
Smalltalk wasn't ;-)


> aCollection
>    inject: aCollection size + 1
>    into:
>      [:i :each |
>      File rename: each path to: (File path: each path extension: z
>      displayString).
>      i := i - 1].
>
> which won't compile in D6. I'm still trying to think of a workaround
> for this one...

I think that replacing the last line with simply:

      i - 1].

will work fine (in either D5 or D6).

    -- chris


Reply | Threaded
Open this post in threaded view
|

Re: Compiled in D5.1 but fails on D6

ian-3
Chris,
      thanks for the suggestion, worked fine, and code mentor was happy
i.e. no full blocks as per my existing workaround, but the syntax just
doesn't seem right somehow, neither Smalltalk nor C*... I guess that's
the purist in me coming out.

               Ian


Reply | Threaded
Open this post in threaded view
|

Re: Compiled in D5.1 but fails on D6

Chris Uppal-3
Ian,

>       thanks for the suggestion, worked fine, and code mentor was happy
> i.e. no full blocks as per my existing workaround, but the syntax just
> doesn't seem right somehow, neither Smalltalk nor C*...

I agree that there's something odd about it.  I dislike blocks which both
execute several statements, /and/ use the value of the last statement as the
value of the block.  I.e. I'm perfectly happy with:

    aCollection collect: [:each | each displayString].

and also with:

    (self aTest) ifTrue:
        [self bar.
        other foo.
        self bax: 44].

But I get itchy if I have to write (or read) "hybrid" blocks like:

    [| tmp |
    tmp := self baz.
    tmp frobnicate.
    tmp isWhatever]
        whileTrue: [...]

It's not always avoidable, though :-(

    -- chris


Reply | Threaded
Open this post in threaded view
|

Re: Compiled in D5.1 but fails on D6

Blair McGlashan-4
In reply to this post by ian-3
"Ian" <[hidden email]> wrote in message
news:[hidden email]...

>
> Chris Uppal wrote:
>> Fernando,
>>
>> >  snake :=
>> >   [:kk :yy || xx |
>> >   xx := yy - kk.
>> >   [xx < M and: [yy < N and: [(A at: xx+1) = (B at: yy+1)]]]
>> >    whileTrue: [xx := xx+1. yy := yy+1].  "<--- Illegal assignment to
>> > yy!"
>> >   yy].
>>
>> Dolphin used to allow assignment to block parameters, now it doesn't.
>>
>> I'm pretty sure that all you have to do is introduce a new temporary
>> variable,
>> assign yy to it as the block is entered, and then change the rest of the
>> block
>> to use your temp instead of yy.
>>
>> E.g. (untested)
>>
>> snake :=
>>      [:kk :yyIn || xx yy |
>>      xx := yyIn - kk.
>>      yy := yyIn.
>>      [xx < M and: [yy < N and: [(A at: xx+1) = (B at: yy+1)]]]
>>            whileTrue: [xx := xx+1. yy := yy+1].
>>     yy].
>>
>> BTW, D6 comes with a diff implementation.  See SequenceableCollection and
>> the
>> methods in category 'computing differences'.  It's used in the
>> DiffPresenter.
>> I don't know how the two algorithms (or their implementations) compare
>> for
>> efficiency.
>>
>>     -- chris
>
> is there a good reason why D6 doesn't allow assignment to block
> variables? I can see that this state of affairs could cause some
> interesting "workarounds". For instance as part of a log file
> renumbering routine I'd got:
>
> renameBackups: aCollection
> aCollection
> inject: aCollection size + 1
> into:
> [:i :each |
> File rename: each path to: (File path: each path extension: z
> displayString).
> i := i - 1]
>
> which won't compile in D6. I'm still trying to think of a workaround
> for this one...

You don't need the assignment to i. #inject:into: takes the value of the
block (which is the  value of the last expression in the block) and passes
that in as the first argument on the next evaluation.

Regards

Blair