IRStackCount.st
author Jan Vrany <jan.vrany@fit.cvut.cz>
Wed, 11 Jun 2008 14:54:42 +0000
changeset 1 0dd36941955f
child 23 377bc46cad12
permissions -rw-r--r--
Initial revision. All tests pass.

"{ Package: 'stx:goodies/newcompiler' }"

Object subclass:#IRStackCount
	instanceVariableNames:'start position length'
	classVariableNames:''
	poolDictionaries:''
	category:'NewCompiler-Bytecode'
!

IRStackCount comment:'This keeps track of the stack count for the BytecodeGenerator.'
!


!IRStackCount class methodsFor:'instance creation'!

new

	^ super new startAt: 0
! !

!IRStackCount class methodsFor:'as yet unclassified'!

startAt: pos

	^ super new startAt: pos
! !

!IRStackCount methodsFor:'affecting'!

pop

	^ self pop: 1
!

pop: n

	(position _ position - n) "< 0 
		ifTrue: [self error: 'Parse stack underflow']"
!

push

	^ self push: 1
!

push: n

	(position _ position + n) > length 
		ifTrue: [length _ position]
! !

!IRStackCount methodsFor:'comparing'!

= other

	^ self class == other class 
	  and: [start = other start
	  and: [position = other position
	  and: [length = other size]]]
!

hash

	^ position hash bitXor: (length hash bitXor: start hash)
! !

!IRStackCount methodsFor:'error handling'!

errorStackOutOfSync: aStackCount 
	self error: 'stack not in sync!!'.
! !

!IRStackCount methodsFor:'initialize'!

startAt: pos

	start _ position _ length _ pos
! !

!IRStackCount methodsFor:'printing'!

printOn: aStream
	
	super printOn: aStream.
	aStream
		nextPutAll: ' start '; print: start;
		nextPutAll: ' stop '; print: position;
		nextPutAll: ' max '; print: length.
! !

!IRStackCount methodsFor:'results'!

length

	^length
!

linkTo: stackOrNil

	stackOrNil ifNil: [^ self class startAt: self position].
	^ self position = stackOrNil start
		ifTrue: [stackOrNil]
		ifFalse: [self errorStackOutOfSync: stackOrNil]
!

position

	^position
!

size

	^length
!

start

	^ start
! !

!IRStackCount class methodsFor:'documentation'!

version
    ^'$Id$'
! !