LazyCons.st
author Stefan Vogel <sv@exept.de>
Wed, 22 Feb 2017 15:33:50 +0100
changeset 4346 7a4c996ac8f0
parent 4327 e93faaf4e55a
child 4536 dfe30da3c1ea
permissions -rw-r--r--
#BUGFIX by stefan class: SharedQueue fix bug in #nextIfEmpty: if exceptionblock returns. add missing methods added: #remove:ifAbsent: #reverseDo: comment/format in: #commonWriteWith: changed: #do: #next #nextIfEmpty: #nextPut: #nextPutFirst: #nextWithTimeout: #removeIdentical:ifAbsent: #removeLast

"
 COPYRIGHT (c) 2003 by Claus Gittinger
              All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
"{ Package: 'stx:libbasic2' }"

"{ NameSpace: Smalltalk }"

Cons subclass:#LazyCons
	instanceVariableNames:''
	classVariableNames:''
	poolDictionaries:''
	category:'Collections-Linked'
!

!LazyCons class methodsFor:'documentation'!

copyright
"
 COPYRIGHT (c) 2003 by Claus Gittinger
              All Rights Reserved

 This software is furnished under a license and may be used
 only in accordance with the terms of that license and with the
 inclusion of the above copyright notice.   This software may not
 be provided or otherwise made available to, or used by, any
 other person.  No title to or ownership of the software is
 hereby transferred.
"
!

documentation
"
    This is an experimental (academic ?) goody for demonstration purposes.

    A pair with lazy evaluation of the tail.
    Useful to implement infinite lists as possible in lazy functional languages.

    [author:]
        Claus Gittinger (Jun 2003)

    [see also:]
"
!

examples
"
  allNumbers represents an infinite list (1..)
                                                                            [exBegin]
    |gen allNumbers|

    gen := [:n | LazyCons car:n cdr:[ gen value:n+1 ]].
    allNumbers := gen value:1. 

    allNumbers head.   
    allNumbers tail head. 
    allNumbers tail tail head. 
                                                                            [exEnd]

  sieve
                                                                            [exBegin]
    |gen filter sieve primeNumberList|

    gen := [:n | LazyCons car:n cdr:[ gen value:n+1 ]].
    filter := [:n :l |
                |head rest|

                head := l car.
                rest := l cdr.
                (head \\ n) ~~ 0 ifTrue:[
                    LazyCons car:head cdr:[ filter value:n value:rest ].
                ] ifFalse:[
                    filter value:n value:rest.
                ]
              ].

    sieve := [:l |
                |prime rest|

                prime := l car.
                rest := l cdr.
                LazyCons car:prime cdr:[ sieve value:(filter value:prime value:rest) ]
             ].

    primeNumberList := sieve value:(gen value:2).
    primeNumberList
                                                                            [exEnd]
"
! !

!LazyCons methodsFor:'accessing - basic'!

cdr
    "return the tail, second or cdr - whatever you wonna call it.
     Here, the tail is evaluated. 
     This makes me a non-lazy cons."

    cdr := cdr value.
    self changeClassTo:Cons.
    ^ cdr

    "Modified (comment): / 27-09-2011 / 11:37:09 / cg"
!

isLazyValue
    ^ true
! !

!LazyCons class methodsFor:'documentation'!

version
    ^ '$Header$'
!

version_CVS
    ^ '$Header$'
! !