an MVC puzzle game "Hakoiri Musume"

ohshima at is.titech.ac.jp ohshima at is.titech.ac.jp
Wed Nov 10 14:01:17 UTC 1999


----Next_Part(Wed_Nov_10_23:01:14_1999)--
Content-Type: Text/Plain; charset=us-ascii
Content-Transfer-Encoding: 7bit


  Hi,

  Attached is a puzzle game called "Hakoiri Musume" written
in MVC, which I showed several people at OOPSLA.

  To play it, fileIn the attachment and evaluate

      Hako2 start

in Workspace.  The purpose is to move the biggest piece
("Musume") to the bottom-center position by sliding the
pieces.

  Hakoiri Musume is originally written by Seki-san
<m_seki at mva.biglobe.ne.jp> and later modified and enhanced
by me.

  Even you don't interested in the game, it is still worth
to see how to create "unresizable" view in MVC.

  Have fun!

                                            OHSHIMA, Yoshiki
                                       A nameless student of
                Dept. of Mathematical and Computing Sciences
                               Tokyo Institute of Technology 


----Next_Part(Wed_Nov_10_23:01:14_1999)--
Content-Type: Text/Plain; charset=us-ascii
Content-Transfer-Encoding: quoted-printable


Model subclass: #Hako2=0D	instanceVariableNames: 'people width height ma=
p isGoal '=0D	classVariableNames: ''=0D	poolDictionaries: ''=0D	category=
: 'Hakoiri2'!=0D=0D!Hako2 methodsFor: 'accessing' stamp: 'yo 8/7/1999 00=
:20'!=0Dextent=0D	^width at height! !=0D=0D!Hako2 methodsFor: 'accessing' s=
tamp: 'yo 8/7/1999 00:56'!=0DkomaAt: aPoint=0D	^map at: aPoint! !=0D=0D!=
Hako2 methodsFor: 'accessing' stamp: 'yo 8/12/1999 12:49'!=0DmodelWakeUp=
=0D	self changed: {0 at 0 corner: self extent. self people}.=0D! !=0D=0D!Ha=
ko2 methodsFor: 'accessing' stamp: 'yo 8/12/1999 08:51'!=0Dpeople=0D	^pe=
ople! !=0D=0D=0D!Hako2 methodsFor: 'moving' stamp: 'yo 8/12/1999 13:28'!=
=0DcanMove: aKoma delta: delta=0D	aKoma slots do: [:e |=0D		(map at: e +=
 delta) =3D #empty ifFalse: [^false].=0D	].=0D	^true.! !=0D=0D!Hako2 met=
hodsFor: 'moving' stamp: 'yo 10/14/1999 07:58'!=0Dgoal=0D	self changed: =
#finish.=0D	! !=0D=0D!Hako2 methodsFor: 'moving' stamp: 'yo 10/14/1999 0=
9:21'!=0DmoveKoma: aKoma from: aPoint delta: d=0D	| delta affected topLe=
ft bottomRight |=0D	delta _ d.=0D	delta =3D (0 at 0) ifTrue: [ ^ aPoint].=0D=
	(delta x abs) > (delta y abs)=0D		ifTrue: [ delta _ ((delta x) / (delta=
 x abs))@0 ]=0D		ifFalse: [ delta _ 0@((delta y) / (delta y abs)) ].=0D	=
aKoma slots do: [:e | map at: e put: #empty].=0D	(self canMove: aKoma de=
lta: delta) ifTrue: [=0D		topLeft _ aKoma topLeft.=0D		bottomRight _ aKo=
ma bottomRight.=0D		aKoma move: delta.=0D		topLeft _ topLeft min: aKoma =
topLeft.=0D		bottomRight _ bottomRight max: aKoma bottomRight.=0D		affec=
ted _ OrderedCollection new.=0D		affected add: aKoma.=0D		self changed: =
{(topLeft corner: bottomRight). affected}.=0D	].=0D	aKoma slots do: [:e =
| map at: e put: aKoma].=0D		=0D	^aKoma position! !=0D=0D=0D!Hako2 metho=
dsFor: 'initialize' stamp: 'yo 8/8/1999 20:05'!=0DaddWall=0D	0 to: width=
-1 do: [:i |=0D		map at: (i@(-1)) put: #wall.=0D		map at: (i at height) put=
: #wall.=0D	].=0D	0 to: height-1 do: [:i |=0D		map at: ((-1)@i) put: #wa=
ll.=0D		map at: (width at i) put: #wall.=0D	].=0D	! !=0D=0D!Hako2 methodsFo=
r: 'initialize' stamp: 'yo 10/14/1999 08:23'!=0Dinitialize=0D	| array x =
y koma kwidth kheight |=0D	isGoal _ false.=0D	people _ OrderedCollection=
 new.=0D	width _ 4.=0D	height _ 5.=0D	map _ Dictionary new.=0D	array _ #=
(=0D		'Musume'	1 0 2 2=0D		'Chichi'		0 0 1 2=0D		'Haha'		3 0 1 2=0D		'Ge=
nan'		0 3 1 2=0D		'Genan' 	3 3 1 2=0D		'Kozo' 		0 2 1 1=0D		'Kozo' 		1 2=
 1 1=0D		'Kozo' 		2 2 1 1=0D		'Kozo' 		3 2 1 1=0D		'Banto'		1 3 2 1).=0D=
	1 to: array size by: 5 do: [:i |=0D		x _ array at: i+1.=0D		y _ array a=
t: i+2.=0D		kwidth _ array at: i+3.=0D		kheight _ array at: i+4.=0D		kom=
a _ Koma2 new name: (array at: i) x: x y: y=0D					width: kwidth height:=
 kheight.=0D		people add: koma.=0D		0 to: kwidth-1 do: [:w |=0D			0 to: =
kheight-1 do: [:h |=0D				map at: (x+w)@(y+h) put: koma.=0D			].=0D		].=0D=
	].=0D	map at: (1 at 4) put: #empty.=0D	map at: (2 at 4) put: #empty.=0D	self =
addWall.! !=0D=0D"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- =
"!=0D=0DHako2 class=0D	instanceVariableNames: ''!=0D=0D!Hako2 class meth=
odsFor: 'instance creation' stamp: 'yo 8/7/1999 01:01'!=0Dnew=0D	^super =
new initialize.! !=0D=0D!Hako2 class methodsFor: 'instance creation' sta=
mp: 'yo 11/10/1999 22:32'!=0Dstart=0D	"Hako2 start"=0D	| topView subView=
 size border |=0D		border _ 2.=0D		topView _ HakoiriTopView new.=0D		top=
View borderWidth: border.=0D		topView label: 'Hako'.=0D		subView _ Hakoi=
riView2 new.=0D		subView model: Hako2 new.=0D		subView grid: 64 at 64.=0D		=
size _ subView boundingBox expandBy: border.=0D		size _ size extent.=0D	=
	topView model: subView model.=0D		topView maximumSize: size.=0D		topVie=
w minimumSize: size.=0D		topView addSubView: subView.=0D		topView contro=
ller open! !=0D=0D=0C=0DMouseMenuController subclass: #HakoiriController=
2=0D	instanceVariableNames: ''=0D	classVariableNames: ''=0D	poolDictiona=
ries: ''=0D	category: 'Hakoiri2'!=0D=0D!HakoiriController2 methodsFor: '=
cursor' stamp: 'yo 8/12/1999 12:44'!=0DcursorPoint=0D	^ ((sensor cursorP=
oint - (view insetDisplayBox origin)) / (view grid)) truncated! !=0D=0D=0D=
!HakoiriController2 methodsFor: 'private' stamp: 'yo 10/14/1999 08:28'!=0D=
drag=0D	self trackUntil: [sensor anyButtonPressed].=0D	((model people at=
: 1) position =3D (1 at 3)) ifTrue: [=0D		model goal.=0D	].! !=0D=0D!Hakoir=
iController2 methodsFor: 'private' stamp: 'yo 10/14/1999 09:27'!=0Dtrack=
Until: aBlock=0D	| previousPoint cursorPoint koma delta offset |=0D	prev=
iousPoint _ self cursorPoint.=0D	koma _ (self model) komaAt: previousPoi=
nt.=0D	(koma isMemberOf: Koma2) ifFalse: [ ^ previousPoint].=0D	offset _=
 previousPoint - (koma normalize: previousPoint).=0D	previousPoint _ pre=
viousPoint - offset.=0D	[aBlock value] whileTrue: [=0D		cursorPoint _ se=
lf cursorPoint - offset.=0D		delta _ cursorPoint - previousPoint.=0D		pr=
eviousPoint _ model moveKoma: koma from: previousPoint delta: delta.=0D	=
].=0D! !=0D=0D=0D!HakoiriController2 methodsFor: 'control access' stamp:=
 'yo 8/12/1999 08:10'!=0DcontrolActivity=0D	super controlActivity.=0D
	(sensor anyButtonPressed) ifTrue: [self drag]! !=0D=0D!HakoiriControlle=
r2 methodsFor: 'control access' stamp: 'yo 8/12/1999 08:10'!=0DisControl=
Active=0D
	^ sensor anyButtonPressed! !=0D=0D=0C=0DColorSystemView subclass: #Hako=
iriTopView=0D	instanceVariableNames: ''=0D	classVariableNames: ''=0D	poo=
lDictionaries: ''=0D	category: 'Hakoiri2'!=0D=0D!HakoiriTopView methodsF=
or: 'as yet unclassified' stamp: 'yo 8/12/1999 13:07'!=0DconstrainFrame:=
 aRectangle=0D	"Constrain aRectangle, to the minimum and maximum size=0D=
	for this window"=0D=0D	^ aRectangle origin extent:=0D		((aRectangle ext=
ent=0D			max: (minimumSize + (0 at self labelHeight)))=0D			min: (maximumSi=
ze + (0 at self labelHeight)))! !=0D=0D!HakoiriTopView methodsFor: 'as yet =
unclassified' stamp: 'yo 8/12/1999 13:11'!=0Dmoved=0D	model modelWakeUp.=
! !=0D=0D!HakoiriTopView methodsFor: 'as yet unclassified' stamp: 'yo 8/=
24/1999 15:13'!=0DresizeTo: aRectangle1=0D	| aRectangle |=0D	"Resize thi=
s view to aRectangle"=0D	"Transcript show: aRectangle1 printString; cr."=
=0D	aRectangle _ aRectangle1 origin extent: self minimumSize.=0D=0D	"Fir=
st get scaling right inside borders"=0D	self window: self window=0D		vie=
wport: aRectangle.=0D=0D	"Then ensure window maps to aRectangle"=0D	wind=
ow _ transformation applyInverseTo: aRectangle.=0D	model modelWakeUp.=0D=
! !=0D=0D=0C=0DView subclass: #HakoiriView2=0D	instanceVariableNames: 'g=
rid bgcolor fgcolor affectedArea affectedKoma form '=0D	classVariableNam=
es: ''=0D	poolDictionaries: ''=0D	category: 'Hakoiri2'!=0D=0D!HakoiriVie=
w2 methodsFor: 'updating' stamp: 'yo 10/14/1999 08:31'!=0Dupdate: anObje=
ct=0D	(anObject isMemberOf: Array) ifTrue: [=0D		affectedKoma _ anObject=
 second.=0D		affectedArea _ anObject first.=0D		^self displayView.=0D	].=
=0D	anObject =3D #finish ifTrue: [=0D		self displayGoal.=0D	] .! !=0D=0D=
=0D!HakoiriView2 methodsFor: 'displaying' stamp: 'yo 10/14/1999 07:42'!=0D=
displayForm=0D	form displayOn: Display=0D		at: (self insetDisplayBox ori=
gin)=0D		clippingBox: ((affectedArea scaleBy: grid) translateBy: self in=
setDisplayBox origin)=0D		rule: Form over=0D		fillColor: nil.=0D! !=0D=0D=
!HakoiriView2 methodsFor: 'displaying' stamp: 'yo 10/14/1999 08:30'!=0Dd=
isplayGoal=0D	| para |=0D	form fill: (((0.5 at 1) scaleBy: grid) asIntegerP=
oint=0D				corner: ((3.5 at 2.5) scaleBy: grid) asIntegerPoint) fillColor: =
Color black.=0D	para _ 'Finish!!' asParagraph.=0D	para foregroundColor: =
Color white backgroundColor: Color black.=0D	para displayOn: form=0D		at=
: (((3 at 1.5 * grid - para compositionRectangle extent) // 2) + ((0.5 at 1) *=
 grid)) asIntegerPoint.=0D		affectedArea _ 0 at 0 corner: 4 at 3.=0D		self dis=
playForm.=0D! !=0D=0D!HakoiriView2 methodsFor: 'displaying' stamp: 'yo 1=
0/14/1999 07:42'!=0DdisplayView=0D	super displayView.=0D	form fill: (aff=
ectedArea scaleBy: grid) rule: Form over fillColor: fgcolor.=0D	affected=
Koma do: [:e | self drawKoma: e on: form].=0D	self displayForm! !=0D=0D!=
HakoiriView2 methodsFor: 'displaying' stamp: 'yo 8/12/1999 08:53'!=0Ddra=
wKoma: aKoma on: aForm=0D	| quad displayText topLeft |=0D	quad _ Quadran=
gle new.=0D	quad _ Quadrangle region: ((aKoma area scaleBy: grid)=0D			i=
nsetBy: 1 at 1) borderWidth: 2 borderColor: Color black insideColor: bgcolo=
r.=0D	quad displayOn: aForm.=0D	displayText _ DisplayText text: aKoma na=
me asText.=0D	displayText foregroundColor: fgcolor backgroundColor: bgco=
lor.=0D	topLeft _ (quad center) - (displayText boundingBox extent // 2).=
=0D	displayText displayOn: aForm at: topLeft.=0D! !=0D=0D=0D!HakoiriView=
2 methodsFor: 'controller access' stamp: 'yo 8/12/1999 08:19'!=0Ddefault=
ControllerClass=0D	^ HakoiriController2! !=0D=0D=0D!HakoiriView2 methods=
For: 'accessing' stamp: 'yo 8/12/1999 08:12'!=0Dgrid=0D	^ grid! !=0D=0D=0D=
!HakoiriView2 methodsFor: 'initialize' stamp: 'yo 8/12/1999 08:51'!=0Dgr=
id: aPoint=0D	| pt |=0D	grid _ aPoint.=0D	pt _ (model extent) * aPoint.=0D=
	boundingBox _ (0 at 0) extent: pt.=0D	form _ Form extent: (boundingBox ext=
ent) depth: 8.	=0D	affectedArea _ 0 at 0 corner: model extent.=0D	affectedK=
oma _ model people.! !=0D=0D!HakoiriView2 methodsFor: 'initialize' stamp=
: 'yo 8/12/1999 08:49'!=0Dinitialize=0D	super initialize.=0D	fgcolor _ C=
olor black.=0D	bgcolor _ Color yellow.=0D	^ self! !=0D=0D!HakoiriView2 m=
ethodsFor: 'initialize' stamp: 'yo 8/24/1999 15:12'!=0DstretchFrame: new=
FrameBlock startingWith: startFrame=0D	^startFrame! !=0D=0D=0C=0DObject =
subclass: #Koma2=0D	instanceVariableNames: 'name x y width height slots =
'=0D	classVariableNames: ''=0D	poolDictionaries: ''=0D	category: 'Hakoir=
i2'!=0D=0D!Koma2 methodsFor: 'operation' stamp: 'yo 8/8/1999 20:06'!=0D=3D=
 anObject=0D	^self =3D=3D anObject! !=0D=0D!Koma2 methodsFor: 'operation=
' stamp: 'yo 8/12/1999 07:20'!=0Dhash=0D	^super hash! !=0D=0D!Koma2 meth=
odsFor: 'operation' stamp: 'yo 8/12/1999 07:30'!=0Dmove: deltaPoint=0D	x=
 _ x + deltaPoint x.=0D	y _ y + deltaPoint y.=0D	slots _ slots collect: =
[:e | e + deltaPoint].! !=0D=0D!Koma2 methodsFor: 'operation' stamp: 'yo=
 10/14/1999 09:12'!=0Dnormalize: aPoint=0D	| p |=0D	p _ aPoint - (1 at 0).=0D=
	[slots includes: p] whileTrue: [=0D		p _ p - (1 at 0).=0D	].=0D	p _ p + (1=
@0).=0D	p _ p - (0 at 1).=0D	(slots includes: p) ifTrue: [=0D		p _ p - (0 at 1=
).=0D	].=0D	p _ p + (0 at 1).=0D	^p=0D		! !=0D=0D=0D!Koma2 methodsFor: 'acc=
essing' stamp: 'yo 8/7/1999 01:05'!=0Darea=0D	^ (x at y) extent: (width at hei=
ght)! !=0D=0D!Koma2 methodsFor: 'accessing' stamp: 'yo 8/12/1999 08:17'!=
=0DbottomRight=0D	^(x+width)@(y+height).! !=0D=0D!Koma2 methodsFor: 'acc=
essing' stamp: 'yo 8/7/1999 01:05'!=0Dname=0D	^ name! !=0D=0D!Koma2 meth=
odsFor: 'accessing' stamp: 'yo 8/7/1999 01:05'!=0Dposition=0D	^ x at y! !=0D=
=0D!Koma2 methodsFor: 'accessing' stamp: 'yo 8/7/1999 01:08'!=0DprintOn:=
 aStream=0D	aStream nextPutAll: name.=0D	aStream nextPut: $(.=0D	aStream=
 nextPutAll: (x at y) printString.=0D	aStream nextPut: $).! !=0D=0D!Koma2 m=
ethodsFor: 'accessing' stamp: 'yo 8/12/1999 07:45'!=0Dslots=0D	^slots! !=
=0D=0D!Koma2 methodsFor: 'accessing' stamp: 'yo 8/12/1999 08:16'!=0DtopL=
eft=0D	^x at y.! !=0D=0D=0D!Koma2 methodsFor: 'initialize' stamp: 'yo 8/12/=
1999 07:47'!=0Dname: aString x: xpos y: ypos width: w height:h=0D	name _=
 aString.=0D	x _ xpos.=0D	y _ ypos.=0D	width _ w.=0D	height _ h.=0D	slot=
s _ OrderedCollection new.=0D	0 to: width-1 do: [:i |=0D		0 to: height-1=
 do: [:j |=0D			slots add: ((x+i)@(y+j)).=0D		]=0D	].=0D	^ self! !=0D=

----Next_Part(Wed_Nov_10_23:01:14_1999)----





More information about the Squeak-dev mailing list