Iterator.st
author Claus Gittinger <cg@exept.de>
Fri, 10 May 1996 09:59:39 +0200
changeset 294 859e8e4e8c4a
parent 290 f4fbe0881e1b
child 355 6d4757eab329
permissions -rw-r--r--
example

"
 COPYRIGHT.
 The above file is a Manchester Goodie protected by copyright.
 These conditions are imposed on the whole Goodie, and on any significant
 part of it which is separately transmitted or stored:
        * You must ensure that every copy includes this notice, and that
          source and author(s) of the material are acknowledged.
        * These conditions must be imposed on anyone who receives a copy.
        * The material shall not be used for commercial gain without the prior
          written consent of the author(s).
 Further information on the copyright conditions may be obtained by
 sending electronic mail:
        To: goodies-lib@cs.man.ac.uk
        Subject: copyright
 or by writing to The Smalltalk Goodies Library Manager, Dept of
 Computer Science, The University, Manchester M13 9PL, UK

 (C) Copyright 1992 University of Manchester
 For more information about the Manchester Goodies Library (from which 
 this file was distributed) send e-mail:
        To: goodies-lib@cs.man.ac.uk
        Subject: help 
"


Collection subclass:#Iterator
	instanceVariableNames:'block'
	classVariableNames:''
	poolDictionaries:''
	category:'Collections-Sequenceable'
!

Iterator comment:'An Iterator is a read-only collection that evaluates a block to yield the elements
 of the collection.'!

!Iterator class methodsFor:'documentation'!

copyright
"
 COPYRIGHT.
 The above file is a Manchester Goodie protected by copyright.
 These conditions are imposed on the whole Goodie, and on any significant
 part of it which is separately transmitted or stored:
        * You must ensure that every copy includes this notice, and that
          source and author(s) of the material are acknowledged.
        * These conditions must be imposed on anyone who receives a copy.
        * The material shall not be used for commercial gain without the prior
          written consent of the author(s).
 Further information on the copyright conditions may be obtained by
 sending electronic mail:
        To: goodies-lib@cs.man.ac.uk
        Subject: copyright
 or by writing to The Smalltalk Goodies Library Manager, Dept of
 Computer Science, The University, Manchester M13 9PL, UK

 (C) Copyright 1992 University of Manchester
 For more information about the Manchester Goodies Library (from which 
 this file was distributed) send e-mail:
        To: goodies-lib@cs.man.ac.uk
        Subject: help 
"

!

documentation
"
    Occasionally you may have a block that when evaluated can be
    treated as a collection -- ie it takes another block as parameter,
    then applies that to a sequence of values.

    This goodie wraps the block into an object -- an iterator -- which is
    part of the collection hierarchy, and therefore inherits a variety of
    useful collection-related methods.

    [info:]
        NAME            Iterator
        AUTHOR          miw@cs.man.ac.uk (Mario Wolczko)
        FUNCTION        a wrapper for blocks that iterate over collections
        ST-VERSION      4.0 4.1
        PREREQUISITES   
        CONFLICTS
        DISTRIBUTION    world
        VERSION         1
        DATE    18 Jun 1991
        SUMMARY

    [organisation:]
        Dept. of Computer Science   Internet:      mario@cs.man.ac.uk
        The University              uucp:        uknet!!!!man.cs!!!!mario
        Manchester M13 9PL          JANET:         mario@uk.ac.man.cs
        U.K.                        Tel: +44-61-275 6146  (FAX: 6236)
        ______the mushroom project___________________________________

    [author:]
        Mario Wolczko miw@cs.man.ac.uk
"

!

examples
"
 an iterator, simulating a collection of 100 random values:
                                                                        [exBegin]
     |i b|

     b := [:whatToDo |
               |rnd|

               rnd := Random new.
               1 to:100 do:[:i | 
                  whatToDo value:(rnd next)
               ] 
          ].

     i := Iterator on:b.
     i do:[:j |
        j printNL
     ].
                                                                        [exEnd]
 an iterator, simulating a collection of the lines
 in a file:
                                                                        [exBegin]
     |i b|

     b := [:whatToDo |
               |s line|

               s := 'smalltalk.rc' asFilename readStream.
               [s atEnd] whileFalse:[
                  line := s nextLine.
                  whatToDo value:line.
               ].
               s close
          ].

     i := Iterator on:b.
     i do:[:j |
        j printNL
     ].
                                                                        [exEnd]
"
! !

!Iterator class methodsFor:'instance creation'!

on: aBlock
    ^ self new block: aBlock

    "
     |i b|

     b := [:whatToDo | 
               1 to:10 do:[:i | 
                  whatToDo value:i
               ] 
          ].

     i := Iterator on:b.
     i do:[:j |
        j printNL
     ].
    "

    "
     an iterator, simulating a collection of 100 random values:

     |i b|

     b := [:whatToDo |
               |rnd|

               rnd := Random new.
               1 to:100 do:[:i | 
                  whatToDo value:(rnd next)
               ] 
          ].

     i := Iterator on:b.
     i do:[:j |
        j printNL
     ].
    "

    "Modified: 9.5.1996 / 14:26:49 / cg"
!

on:collection msg:msg
    ^ self new block: [ :aBlock | collection perform: msg with: aBlock]

    "
     |rnd i|

     rnd := Random new.
     i := Iterator on:[:a | rnd next].
     i do:[:j |
        j printNL
     ].
    "

    "Modified: 9.5.1996 / 14:21:40 / cg"
! !

!Iterator methodsFor:'accessing'!

identityIndexOf: anElement 
    "Answer the identity index of anElement within the receiver.  
     If the receiver does not contain anElement, answer 0."

    ^self identityIndexOf: anElement ifAbsent: [0]
!

identityIndexOf: anElement ifAbsent: exceptionBlock 
    "Answer the identity index of anElement within the receiver.  
     If the receiver does not contain anElement, answer the result 
     of evaluating the exceptionBlock."

    | index |
    index := 1.
    self do: [ :el | el == anElement ifTrue: [^index].  index := index + 1].
    ^exceptionBlock value
!

indexOf: anElement 
    "Answer the index of anElement within the receiver.  If the receiver does
    not contain anElement, answer 0."

    ^self indexOf: anElement ifAbsent: [0]
!

indexOf: anElement ifAbsent: exceptionBlock 
    "Answer the index of anElement within the receiver.  If the receiver does
    not contain anElement, answer the result of evaluating the exceptionBlock."


    | index |
    index := 1.
    self do: [ :el | el = anElement ifTrue: [^index].  index := index + 1].
    ^exceptionBlock value
! !

!Iterator methodsFor:'adding & removing'!

add: anObject
    "Iterators are read-only"
    self shouldNotImplement
!

remove: oldObject ifAbsent: anExceptionBlock 
    "Iterators are read-only."
    self shouldNotImplement
! !

!Iterator methodsFor:'converting'!

asOrderedCollection
    "Answer a new instance of OrderedCollection whose elements are the elements of
    the receiver.  The order in which elements are added depends on the order in
    which the receiver enumerates its elements.  In the case of unordered collections,
    the ordering is not necessarily the same for multiple requests for the conversion."


    | anOrderedCollection |
    anOrderedCollection := OrderedCollection new.
    self do: [:each | anOrderedCollection addLast: each].
    ^anOrderedCollection
! !

!Iterator methodsFor:'enumerating'!

do: aBlock
    block value: aBlock
!

findFirst: aBlock
    "Answer the index of the first element of the receiver
    for which aBlock evaluates as true."

    | index |
    index := 1.
    self do: [ :el | (aBlock value: el) ifTrue: [^index].  index := index + 1].

    ^0
!

findLast: aBlock
    "Answer the index of the last element of the receiver
    for which aBlock evaluates as true."

    | index last |
    index := 1.
    last := 0.
    self do: [ :el | (aBlock value: el) ifTrue: [last := index].  index := index + 1].
    ^last
!

keysAndValuesDo: aBlock  
    "Evaluate aBlock with each of the receiver's key/value pairs
    (e.g. indexes and elements) as the arguments."

    | index |
    index := 1.
    self do: [:el | aBlock value: index value: el.  index := index + 1]
! !

!Iterator methodsFor:'private'!

block: aBlock
    block := aBlock
!

species
    ^OrderedCollection
! !

!Iterator class methodsFor:'documentation'!

version
    ^ '$Header: /cvs/stx/stx/libbasic2/Iterator.st,v 1.3 1996-05-10 07:59:39 cg Exp $'
! !