| 123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357 | 
							- Widget subclass: #Counter
 
- 	instanceVariableNames: 'count header'
 
- 	category: 'Examples'!
 
- !Counter methodsFor: 'actions'!
 
- increase
 
-     count := count + 1.
 
-     header contents: [:html | html with: count asString]
 
- !
 
- decrease
 
-     count := count - 1.
 
-     header contents: [:html | html with: count asString]
 
- ! !
 
- !Counter methodsFor: 'initialization'!
 
- initialize
 
-     super initialize.
 
-     count := 0
 
- ! !
 
- !Counter methodsFor: 'rendering'!
 
- renderOn: html
 
-     header := html h1 
 
- 	with: count asString;
 
- 	yourself.
 
-     html button
 
- 	with: '++';
 
- 	onClick: [self increase].
 
-     html button
 
- 	with: '--';
 
- 	onClick: [self decrease]
 
- ! !
 
- Widget subclass: #Tetris
 
- 	instanceVariableNames: 'renderingContext timer speed score rows movingPiece'
 
- 	category: 'Examples'!
 
- !Tetris methodsFor: 'accessing'!
 
- width
 
- 	^self class width
 
- !
 
- height
 
- 	^self class height
 
- !
 
- squares
 
- 	^self class squares
 
- !
 
- gluePiece: aPiece
 
- 	aPiece glueOn: self
 
- !
 
- rows
 
- 	"An array of rows. Each row is a collection of points."
 
- 	^rows
 
- !
 
- addRow: aCollection
 
- 	self rows add: aCollection
 
- ! !
 
- !Tetris methodsFor: 'actions'!
 
- startNewGame
 
- 	self newGame.
 
- 	timer ifNotNil: [timer clearInterval].
 
- 	timer := [self nextStep] valueWithInterval: speed
 
- !
 
- nextStep
 
- 	movingPiece ifNil: [self newPiece].
 
- 	(movingPiece canMoveIn: self)
 
- 		ifTrue: [movingPiece position: movingPiece position + (0@1)]
 
- 		ifFalse: [self newPiece].
 
- 	self redraw
 
- !
 
- redraw
 
- 	renderingContext clearRectFrom: 0@ self width to: 0@ self height.
 
- 	self 
 
- 		drawMap;
 
- 		drawPiece
 
- !
 
- drawMap
 
- 	renderingContext 
 
- 		fillStyle: '#fafafa';
 
- 		fillRectFrom: 0@0 to: self width@self height.
 
- 	renderingContext 
 
- 		lineWidth: 0.5;
 
- 		strokeStyle: '#999'.
 
- 	0 to: self class squares x do: [:each | | x |
 
- 		x := each * self class squareSize.
 
- 		self drawLineFrom: x@0 to: x@self height].
 
- 	0 to: self class squares y do: [:each | | y |
 
- 		y := each * self class squareSize.
 
- 		self drawLineFrom: 0@y to: self width@y].
 
- !
 
- drawLineFrom: aPoint to: anotherPoint
 
- 	renderingContext 
 
- 		beginPath;
 
- 		moveTo: aPoint;
 
- 		lineTo: anotherPoint;
 
- 		stroke
 
- !
 
- newGame
 
- 	rows := #().
 
- 	movingPiece := nil.
 
- 	speed := 200.
 
- 	score := 0
 
- !
 
- newPiece
 
- 	movingPiece := TetrisPiece atRandom
 
- !
 
- drawRows
 
- 	self rows do: [:each |].
 
- 	movingPiece ifNotNil: [movingPiece drawOn: renderingContext]
 
- !
 
- drawPiece
 
- 	movingPiece ifNotNil: [
 
- 		movingPiece drawOn: renderingContext]
 
- ! !
 
- !Tetris methodsFor: 'initialization'!
 
- initialize
 
- 	super initialize.
 
- 	self newGame
 
- ! !
 
- !Tetris methodsFor: 'rendering'!
 
- renderOn: html
 
- 	html div
 
- 		class: 'tetris';
 
- 		with: [
 
- 			html h3 with: 'Tetris'.
 
- 			self renderCanvasOn: html.
 
- 			self renderButtonsOn: html]
 
- !
 
- renderCanvasOn: html
 
- 	| canvas |
 
- 	canvas := html canvas.
 
- 	canvas at: 'width' put: self width asString.
 
- 	canvas at: 'height' put: self height asString.
 
- 	renderingContext := CanvasRenderingContext tagBrush: canvas.
 
- 	self redraw
 
- !
 
- renderButtonsOn: html
 
- 	html div 
 
- 		class: 'tetris_buttons';
 
- 		with: [
 
- 			html button
 
- 				with: 'New game';
 
- 				onClick: [self startNewGame].
 
- 			html button
 
- 				with: 'play/pause';
 
- 				onClick: [self update]]
 
- ! !
 
- !Tetris class methodsFor: 'accessing'!
 
- squareSize
 
- 	^22
 
- !
 
- width
 
- 	^self squareSize * (self squares x)
 
- !
 
- height
 
- 	^self squareSize * (self squares y)
 
- !
 
- squares
 
- 	^10@15
 
- ! !
 
- Widget subclass: #TetrisPiece
 
- 	instanceVariableNames: 'rotation position'
 
- 	category: 'Examples'!
 
- !TetrisPiece methodsFor: 'accessing'!
 
- rotation
 
- 	^rotation ifNil: [rotation := 1]
 
- !
 
- rotation: aNumber
 
- 	rotation := aNumber
 
- !
 
- position
 
- 	^position ifNil: [(Tetris squares x / 2) -1 @ 0]
 
- !
 
- position: aPoint
 
- 	^position := aPoint
 
- !
 
- bounds
 
- 	self subclassResponsibility
 
- !
 
- color
 
- 	^'#afa'
 
- !
 
- height
 
- 	^2
 
- ! !
 
- !TetrisPiece methodsFor: 'drawing'!
 
- drawOn: aRenderingContext
 
- 	aRenderingContext fillStyle: self color.
 
- 	self bounds do: [:each |
 
- 		aRenderingContext 
 
- 			fillRectFrom: each + self position* Tetris squareSize to: 1@1 * Tetris squareSize;
 
- 			strokeStyle: '#999';
 
- 			lineWidth: 2;
 
- 			strokeRectFrom: each + self position* Tetris squareSize to: 1@1 * Tetris squareSize]
 
- ! !
 
- !TetrisPiece methodsFor: 'testing'!
 
- canMove
 
- 	^self position y < (Tetris squares y - self height)
 
- !
 
- canMoveIn: aTetris
 
- 	^self position y < (aTetris squares y - self height)
 
- ! !
 
- !TetrisPiece class methodsFor: 'instance creation'!
 
- atRandom
 
- 	^(self subclasses at: self subclasses size atRandom) new
 
- ! !
 
- TetrisPiece subclass: #TetrisPieceO
 
- 	instanceVariableNames: ''
 
- 	category: 'Examples'!
 
- !TetrisPieceO methodsFor: 'accessing'!
 
- bounds
 
- 	^Array new
 
- 		add: 0@0;
 
- 		add: 0@1;
 
- 		add: 1@0;
 
- 		add: 1@1;
 
- 		yourself
 
- ! !
 
- TetrisPiece subclass: #TetrisPieceL
 
- 	instanceVariableNames: ''
 
- 	category: 'Examples'!
 
- !TetrisPieceL methodsFor: 'accessing'!
 
- bounds
 
- 	^Array new
 
- 		add: 0@0;
 
- 		add: 0@1;
 
- 		add: 0@2;
 
- 		add: 1@2;
 
- 		yourself
 
- !
 
- color
 
- 	^'#ffa'
 
- !
 
- height
 
- 	^3
 
- ! !
 
- TetrisPiece subclass: #TetrisPieceJ
 
- 	instanceVariableNames: ''
 
- 	category: 'Examples'!
 
- !TetrisPieceJ methodsFor: 'accessing'!
 
- color
 
- 	^'#aaf'
 
- !
 
- bounds
 
- 	^Array new
 
- 		add: 1@0;
 
- 		add: 1@1;
 
- 		add: 1@2;
 
- 		add: 0@2;
 
- 		yourself
 
- !
 
- height
 
- 	^3
 
- ! !
 
- TetrisPiece subclass: #TetrisPieceI
 
- 	instanceVariableNames: ''
 
- 	category: 'Examples'!
 
- !TetrisPieceI methodsFor: 'accessing'!
 
- color
 
- 	^'#faa'
 
- !
 
- bounds
 
- 	^Array new
 
- 		add: 0@0;
 
- 		add: 0@1;
 
- 		add: 0@2;
 
- 		add: 0@3;
 
- 		yourself
 
- !
 
- height
 
- 	^4
 
- ! !
 
- TetrisPiece subclass: #TetrisPieceT
 
- 	instanceVariableNames: ''
 
- 	category: 'Examples'!
 
- !TetrisPieceT methodsFor: 'accessing'!
 
- bounds
 
- 	^Array new
 
- 		add: 0@0;
 
- 		add: 1@0;
 
- 		add: 2@0;
 
- 		add: 1@1;
 
- 		yourself
 
- !
 
- color
 
- 	^'#aaf'
 
- ! !
 
 
  |