some code

Brian T. Rice water at tunes.org
Tue Jul 20 23:41:34 PDT 2004


Cool, more code! :)

Jeff Cutsinger <seaslug at tunes.org> said:

> I've written a couple of extensions to the slate standard libs. They aren't
> thoroughly tested. They aren't commented, but they seem self explanatory to me.

These are pretty good, but I'll respond with what I'm actually putting into
the code to give an idea of my design process. Hopefully you'll agree and see
why the difference is; it's not criticism, because this kind of style takes a
long time to learn and make a habit of.

> r@(ReadStream traits) upTo: c
> [| char string |
>   char: r next.
>   string: ''.
>   [ ((char = c) \/ (r atEnd)) not ] whileTrue:
>     [ string: string ; { char }.
>       char: r next ].
>   (char = c)
>     ifTrue: [string]
>     ifFalse: [Nil]
> ].

We have this already, which is mostly equivalent, except for the
Nil-on-not-found answer. Instead, it grabs up to the end. Since you brought up
other methods, I factored a block out:

s@(ReadStream traits) upToSatisfying: testBlock
"Answer all objects up to one satisfying the block test."
[| result elem |
  result: s arrayType newEmpty writer.
  [s atEnd or: [testBlock applyWith: (elem: s next)]]
    whileFalse: [result nextPut: elem].
  result contents
].

s@(ReadStream traits) upTo: obj
"Answer all objects up to one equal to the argument."
[s upToSatisfying: [| :each | each = obj]].

A lot of things are different here. I asked the ReadStream for the right
Sequence type. I didn't assume characters. I used a stream (also so I don't
have to care what sequence type it is), I did the fancy expression-embedding
of the assignment of each element, and performed a lazy logic setup with the
block. Also, I used whileFalse: to capture the not whileTrue: pattern.

> r@(ReadStream traits) upToOneOf: c@(Collection traits)
> [| char string |
>   char: r next.
>   string: ''.
>   [ ((c includes: char) \/ (r atEnd)) not ] whileTrue:
>     [ string: string ; { char }.
>       char: r next ].
>   (char = c)
>     ifTrue: [string]
>     ifFalse: [Nil]
> ].

s@(ReadStream traits) upToAnyOf: c@(Collection traits)
"Answer all objects up to one contained by the argument."
[s upToSatisfying: [| :each | c includes: each]].

> r@(ReadStream traits) upTo: s@(String traits)
> [| string sIndex |
>   string: (r upTo: s first).
>   string
>     ifNil: [sIndex: -1]
>     ifNotNil: [sIndex: 1].
>   [ (r atEnd) not /\ (sIndex ~= s size) ] whileTrue:
>     [ | char |
>       char: r next.
>       string: string ; { char }.
>       ((s at: sIndex) = char)
>         ifTrue: [ sIndex: sIndex + 1 ]
>         ifFalse: [ sIndex: 0 ]. ].
>   (sIndex = s size)
>     ifTrue: [string copyFrom: 0 to: (string size - s size)]
>     ifFalse: [Nil]
> ].

This is oddly complex. The concept also needs a little work, since not all
Streams are just for Characters (something I noticed about your previous
examples as well), so Strings really could be elements. It also relies on
answering Nil for not-found, which seems like the only reason to return Nil,
and so probably not the right approach. (After further thought, it seems that
just asking the ReadStream whether it's atEnd after calling it is just as
good.) I noticed that upToAll: seems does the same thing, but for
PositionableStream (which all Sequence Streams are), so I adapted it:

s@(ReadStream traits) upToAll: seq@(Sequence traits)
"TODO: make this actually work!"
[| result match seqIndex each |
  result: s arrayType newEmpty writer.
  match: seq newSameSize writer.
  seqIndex: 0.
  result ; (s upTo: (seq at: seqIndex)).
  [s atEnd /\ (seqIndex >= seq size)] whileFalse:
    [each: r next.
     each = (seq at: seqIndex)
       ifTrue: [match at: seqIndex: seqIndex + 1].
       ifFalse: [result ; match contents.
		 seqIndex: 0]].
  result contents
].

Okay, this is incomplete and doesn't work. I'll add it with a TODO (feel free
to fix it). However, this is a bit questionable as a method, since you have to
read the elements that are in the match to find them, while /not/ being able
to reposition the stream after the read to before the first match. So it
works, but does the wrong thing. I'll leave it in in case users don't mind,
since the elements after the answer are obviously known anyway, and streams
for Sequences are all Positionable, or should be.

> s@(String traits) stripOneOf: c@(Collection traits) startingAt: start
> [ | new |
>   new: (s copyFrom: 0 to: (start - 1)).
>   start below: s size
>     do: [ | :index |
>           (c includes: (s at: index))
>             ifFalse: [ new: new ; { (s at: index) }]].
>   new
> ].

Okay, this time there's only one real method to discuss. Again, the "x: x ;
{y}" idiom should be re-done for what it is, a stream operation.

s@(String traits) stripAll: c@(Collection traits) startingAt: start
[| result |
  result: (s copyFrom: 0 to: start - 1) writer.
  start below: s size
    do: [| :index each |
	 each: (s at: index).
         (c includes: each)
	   ifFalse: [result nextPut: each]].
  result contents
].

The method name of stripOneOf: doesn't sound like what it does, which is to
answer a copy without any of the elements in the argument (copyWithoutAny:,
copyWithoutAnyAfter:? or just withoutAny:, withoutAnyAfter:?). This also
doesn't need to be a String. Actually, the entire idiom is generic, except for
your default #strip method which just uses String Whitespace for the a default
argument. I'll put it in as is and figure out a better way to generalize this
when I need to.

Also, there's no way here to strip at the beginning here, unless you use a
lazy reversal wrapper, and a combinatorial method explosion would probably not
help. So at some point, there's probably a better way to do the whole thing.

> s@(String traits) stripOneOf: c@(Collection traits)
> [ s stripOneOf: c startingAt: 0 ].
> 
> s@(String traits) strip: c@(Character traits) startingAt: start
> [ s stripOneOf: {c} startingAt: start ].
> 
> s@(String traits) strip: c@(Character traits)
> [ s stripOneOf: {c} startingAt: 0 ].
> 
> s@(String traits) stripStartingAt: start
> [ s stripOneOf: { $\s. $\n. $\t. $\r. $\0 } startingAt: start ].
> 
> s@(String traits) strip
> [ s stripOneOf: { $\s. $\n. $\t. $\r. $\0 } startingAt: 0].




More information about the Slate mailing list