Email |
|
avaldez(ARROBA)dc.uba.ar |
Implementar el Pacman.
Comentarios preliminares
El informe cuenta con las siguientes
secciones:
-
Diagramas del modelo
-
Diagramas de la vista
-
Cosas que sé que no estan del todo bién
-
Apendice A: Código fuente
-
Apendice B: Como iniciar el juego
-
Apendice C: Artwork (un cierre informal)
Algunos gráficos no logré que se vean lo
suficientemente bien, en caso de que no
sean legibles se pueden encontrar un
file-out de la jerarquía de Jacaranda con los gráficos originales en el
directorio ‘extra\jacaranda’.
Diagramas de instancia del modelo
Comienza un juego nuevo:
aPacManGame carga el nivel 1:
aLevel obtiene el layout y la fruta correspondiente al nivel 1:
aGameTimer
envía un step a aPacManGame:
aPacManGame procesa un turno:
aPacManGame
mueve los actores:
aRuleManager
procesa las reglas del juego:
aLevel procesa el layout para inicializar aBoard, agrega aWall en aBoard:
Se
agrega aWall en aBoard:
aFruitManager
pone aCherry en juego:
aPillManager elimina las pills comidas:
aPowerPillManager elimina las powerPills comidas:
aPillManager
inicia el efecto de una powerPill que
fue comida:
aPillManager pone a los ghosts en estado recovering (el efecto de la powerPill esta por terminar):
Expiró el efecto de la powerPill activa, aPowerPillManager pone a los ghosts en estado normal:
aRuleManager
verifica las reglas del juego:
aRuleManager
detecta que aPacMan esta muerto, resta una vida y reinicia el nivel actual:
aRuleManager detecta que aPacMan esta muerto, resta una vida y da por terminado el juego:
aRuleManager
verifica que el nivel actual esta terminado y pasa al siguiente:
aMovilActor
(en este caso aBliny) se mueve:
aChaseHard
(una estrategia) elije la dirección hacia donde se moverá un aMovilActor (en
este caso aBlinky) que tiene asociado:
aChaseHard (una estrategia) calcula la nueva direccion de movimiento:
aCollisionManager encuentra las direcciones en las que se puede mover aMovilActor (en este caso aBlinky):
aCollisionManager pide permiso a los objetos que estan en colision con aMovilActor (en este caso aBlinky):
aCollisionManager notifica los objetos que estan en colision con aMovilActor (en este caso aBlinky) de esta situacion:
aCherry se mueve, expira su tiempo de vida en el juego:
aPacMan es notificado de una colision con aGhost (en este caso aBlinky), aPacMan muere:
aGhost (en este caso aBlinky) es notificado de una colision con aPacMan, aBlinky (muy contrariado) se pone en estado eated:
aGhost (en este caso
aBlinky) se pone en estado eated:
aBlinky colisiona con aGhostHome, se pone en estado leavingHome y abandona su casita:
aLeaveHome (una estrategia) termina su trabajo y pone al aMovilActor que tiene asociado (aBlinky) en estado normal para salir a perseguir al engreido PacMan:
Diagrama de clases de la vista
Se crea una vista:
Se inicializan las subvistas:
Se
incializa la vista del board:
aBoardView crea las vistas de los actores:
Se
crea aGhostView:
Luego que el modelo se actualiza, se actualiza la vista:
aGhostView se actualiza:
Algunas aclaraciones del modelo
Qué es un gridPoint?, y
el gridSize?
Al mirar el pacMan de
ejemplo que esta en la pagina de la materia, pude observar que las paredes
estaban formadas por cuadrados dispuestos uno al lado de otro, también que el
pacMan y los ghosts eran dibujos que no excedían en tamaño al de una pared. De
alguna manera ese tamaño servia como una unidad de medida, que era la longitud
del lado del cuadrado, llame a esa longitud gridSize.
Luego imaginé un board lleno de paredes (todas cuadradas), formando
algo así:
A mi se me hacia mas
fácil pensar en la posición de cada cuadrado considerando su centro (algunas
personas se les hace mas fácil pensando en su esquina superior izquierda). Los
centros de los cuadrados son lo que llame gridPoint (puntos de grilla),
representan las posiciones donde inicialmente se colocan las piezas y además
son las posiciones en las que un actor
móvil puede girar hacia los lados en caso de que no haya algún objeto que le
impida moverse en esa dirección.
Manejo de colisiones
Cada actor móvil tiene una dirección de movimiento, antes de que pueda
avanzar en esa dirección se calcula su nueva posición y considerando esa nueva
posición se pregunta a los objetos que están en colisión si el objeto
colisionante puede solaparse con ellos. Para que se realice el movimiento a la
nueva posición todos los objetos en colisión deben dar su permiso, para esto
cada actor del juego sabe contestar a los mensajes #canGhostCollision:on:,
#canPacManCollision:on: y #canFruitCollision:on:.
Una vez realizado el
movimiento del actor a la nueva posición, se notifica a los objetos que están
en colisión con él de esta situación, para eso cada actor móvil guarda como
colaborador interno el selector que se utilizara en la notificación a los
objetos colisionados.
Cuando los objetos
colisionados reciben la notificación realizan las acciones que correspondan a
esa colisión.
Los
siguientes son algunas autocríticas el modelo, estas cuestiones las fui dejando
para solucionarlas si disponía de
tiempo suficiente antes de la fecha de entrega, cosa que no sucedió:
El
mecanismo con el que se almacena la especificación de cada nivel debería realizarse con algún objeto extra,
la solución de tener dos colecciones e
indexarlas según el numero de nivel fue para salir del paso. Una mejor solución
seria leer los niveles de disco y generar el layout a partir del contenido de
archivos con nombres conocidos.
La
separación de level y levelNumebr es un tanto artificial e incomoda para
operar, una mejor idea seria que aLevel conociera su propio numero de nivel e
incluso supiera cambiarse (o generar una nueva instancia) con el nivel que
sigue en el juego.
Cada
vez que se actualiza el modelo, toda la vista se actualiza (y redibuja en
pantalla) ya que se propaga el mensaje #updateView a todos los subMorphs tengan
o no que actualizarse. Una mejor solución seria que cada elemento de la vista
reciba un mensaje #updated del objeto que tiene asociado en el modelo solo
cuando ese objeto cambia.
En
general el código tiene mas IF de los que a mi me gustaría, y se que eso
denota falta de polimorfismo. Imagino
que con mas tiempo podría mejorar el diseño para disminuir esa cantidad. En
particular la vista tiene muchos IF, esto se debe a que cuando un objeto de la
vista recibe el mensaje #updateView no tiene suficiente información para saber
que aspecto del objeto observado cambio y debe preguntárselo (por ejemplo,
‘esta el fantasma débil?’ o ‘esta el fantasma recuperándose?’) lo cual lleva a
que aparezcan IF.
Por
algún motivo que no recuerdo, hay una sola instancia de CollisionManager y es
compartida por todos los actores del juego, además la utilizan las estrategias
de movimiento. Algunas relaciones de conocimiento (en especial entre una
estrategia y al actor que tiene como colaborador interno) están a los efectos
de permitir tener acceso a esa instancia de Collision Manager, que ciertamente
es un motivo baste pobre y mas relacionado con la implementación que con el
dominio que quería modelar.
Apéndice A: Código fuente
addScore: aNumber
self score: (self score + aNumber).! !
board
^ board! !
!PacManGame methodsFor: 'accessing' stamp: 'Ale 7/16/2004 16:45'!
board: aBoard
board := aBoard! !
!PacManGame methodsFor: 'accessing' stamp: 'Ale 7/16/2004 16:46'!
collisionManager
^ collisionManager! !
!PacManGame methodsFor: 'accessing' stamp: 'Ale 7/16/2004 16:46'!
collisionManager: aCollisionManager
collisionManager := aCollisionManager! !
!PacManGame methodsFor: 'accessing' stamp: 'Ale 7/16/2004 16:46'!
fruits
^ fruits! !
!PacManGame methodsFor: 'accessing' stamp: 'Ale 7/16/2004 16:46'!
fruits: aFruitSet
fruits := aFruitSet! !
!PacManGame methodsFor: 'accessing' stamp: 'Ale 7/16/2004 16:46'!
gameOver
^ gameOver! !
!PacManGame methodsFor: 'accessing' stamp: 'Ale 7/16/2004 16:46'!
gameOver: aBoolean
gameOver := aBoolean! !
!PacManGame methodsFor: 'accessing' stamp: 'Ale 7/16/2004 16:46'!
gameTimer
^ gameTimer! !
!PacManGame methodsFor: 'accessing' stamp: 'Ale 7/16/2004 16:46'!
gameTimer: aGameTimer
gameTimer := aGameTimer! !
!PacManGame methodsFor: 'accessing' stamp: 'Ale 7/16/2004 16:46'!
ghosts
^ ghosts! !
!PacManGame methodsFor: 'accessing' stamp: 'Ale 7/16/2004 16:46'!
ghosts: aGhostSet
ghosts := aGhostSet! !
!PacManGame methodsFor: 'accessing' stamp: 'Ale 7/16/2004 16:46'!
level
^ level! !
!PacManGame methodsFor: 'accessing' stamp: 'Ale 7/16/2004 16:47'!
level: aLevel
level := aLevel
! !
!PacManGame methodsFor: 'accessing' stamp: 'Ale 7/16/2004 16:46'!
levelNumber
^ levelNumber! !
!PacManGame methodsFor: 'accessing' stamp: 'Ale 7/16/2004 16:47'!
levelNumber: aNumber
levelNumber := aNumber! !
!PacManGame methodsFor: 'accessing' stamp: 'Ale 7/16/2004 16:47'!
lives
^ lives! !
!PacManGame methodsFor: 'accessing' stamp: 'Ale 7/16/2004 16:47'!
lives: aNumber
lives := aNumber! !
!PacManGame methodsFor: 'accessing' stamp: 'Ale 7/16/2004 16:47'!
pacMan
^ pacMan! !
!PacManGame methodsFor: 'accessing' stamp: 'Ale 7/16/2004 16:47'!
pacMan: aPacMan
pacMan := aPacMan! !
!PacManGame methodsFor: 'accessing' stamp: 'Ale 7/16/2004 16:47'!
ruleManager
^ ruleManager! !
!PacManGame methodsFor: 'accessing' stamp: 'Ale 7/16/2004 16:47'!
ruleManager: aRuleManager
ruleManager := aRuleManager! !
!PacManGame methodsFor: 'accessing' stamp: 'Ale 7/16/2004 16:47'!
score
^ score! !
!PacManGame methodsFor: 'accessing' stamp: 'Ale 7/16/2004 16:47'!
score: aNumber
score := aNumber ! !
buildActors
"Crear los actores y agregarlos al game."
self
pacMan:
(PacMan new collisionManager: (self
collisionManager)).
self ghosts
add: Blinky new;
add: Pinky new;
add: Inky new;
add: Sue new.
self ghosts
do: [:each| each
collisionManager:
(self collisionManager);
pacMan: self pacMan]
! !
!PacManGame methodsFor: 'initializing' stamp: 'Ale 7/17/2004 21:20'!
initialize
self ghosts: Set new.
self fruits: Set new.
self board: Board new.
self score: 0.
self lives: 0.
self levelNumber: 1.
self gameOver: true.
self gameTimer: ((GameTimer new) initializeWith: self).
self collisionManager: (CollisionManager new).
self ruleManager: (RuleManager new).
self buildActors.
! !
loadLevel: aNumber
"Cargar un nuevo nivel y reinicializar el juego."
self level:
((Level new) loadLevel: aNumber).
self levelNumber: aNumber.
self level fruit collisionManager: self collisionManager.
self level initializeBoard: board.
self level initializeGhosts: self ghosts.
self ruleManager initializeWith: self.
self putActors.
self fruits: Set new.
self resetActorsState.
self changed: #resetView.! !
!PacManGame methodsFor: 'level loading' stamp: 'Ale 7/19/2004 16:36'!
newGame
self lives: 3.
self score: 0.
self loadLevel: 1.
self gameTimer openInWorld.
self gameOver: false.
! !
!PacManGame methodsFor: 'level loading' stamp: 'Ale 7/17/2004 12:57'!
putActors
"Poner al pacMan y los ghosts en las posiciones
iniciales del board para
el nivel actual."
self ghosts
do: [:g | board
put: g
at:
(board positionOf: self level ghostHome)].
self board
put: self pacMan
at: (board positionOf: self level
pacManHome)! !
!PacManGame methodsFor: 'level loading' stamp: 'Ale 7/16/2004 18:51'!
removeActors
"Quita al pacman, los ghosts y la fruit del board.
"
self board remove: (self pacMan).
self ghosts
do: [:each | board remove: each].
self fruits
do: [:each | board remove: each].
self fruits: Set new.
! !
!PacManGame methodsFor: 'level loading' stamp: 'Ale 7/16/2004 16:59'!
resetActorsPosition
"Quitar los actores de sus posiciones actuales y
ponerlos en la de inicio de nivel."
self
removeActors.
self putActors.! !
!PacManGame methodsFor: 'level loading' stamp: 'Ale 7/16/2004 18:51'!
resetActorsState
"Poner a los actores con su estado inicial."
pacMan
resetState.
self ghosts
do:[:each | each resetState].! !
!PacManGame methodsFor: 'level loading' stamp: 'Ale 7/16/2004 17:01'!
resetLevel
"Reiniciar posiciones y estado de los actores en el
board."
self
resetActorsPosition.
self resetActorsState.
! !
pacManDown
"Se indico que el pacMan vaya hacia abajo."
self pacMan
wantedDirection: (0@1).! !
!PacManGame methodsFor: 'pacManMoves' stamp: 'Ale 7/16/2004 17:01'!
pacManLeft
"Se indico que el pacMan vaya hacia la izquierda."
self pacMan
wantedDirection: (-1@0).! !
!PacManGame methodsFor: 'pacManMoves' stamp: 'Ale 7/16/2004 17:01'!
pacManRight
"Se indico que el pacMan vaya hacia la derecha."
self pacMan
wantedDirection: (1@0).! !
!PacManGame methodsFor: 'pacManMoves' stamp: 'Ale 7/16/2004 17:02'!
pacManUp
"Se indico que el pacMan vaya hacia arriba."
self pacMan
wantedDirection: (0@-1).! !
isLevelClear
"Informa si todas las pastillas del nivel actual fueron
comidas."
^ (level
pills union: level powerPills) size isZero
! !
!PacManGame methodsFor: 'turn processing' stamp: 'Ale 7/16/2004 17:02'!
isPacManDead
"Informa si el pacMan esta muerto."
^ self pacMan alive not! !
!PacManGame methodsFor: 'turn processing' stamp: 'Ale 7/16/2004 18:51'!
moveActors
"Mueve todos los actores."
pacMan moveOn: board.
ghosts
do: [:each | each moveOn: board].
fruits
do: [:each | each moveOn: board].
! !
!PacManGame methodsFor: 'turn processing' stamp: 'Ale 7/16/2004 17:03'!
processTurn
"Procesar un turno."
self moveActors.
self ruleManager process: self.
self changed.! !
!PacManGame methodsFor: 'turn processing' stamp: 'Ale 7/16/2004 18:51'!
step
"Se recibio un step desde el timer del modelo."
self gameOver
ifFalse:[ self processTurn ]! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
new
^(super new) initialize.! !
pacManGame
^ pacManGame ! !
!GameTimer methodsFor: 'accesing' stamp: 'Ale 7/16/2004 16:42'!
pacManGame: aPacManGame
pacManGame := aPacManGame! !
!GameTimer methodsFor: 'accesing' stamp: 'Ale 7/16/2004 16:42'!
stepTime
^ stepTime! !
!GameTimer methodsFor: 'accesing' stamp: 'Ale 7/16/2004 16:42'!
stepTime: aNumber
stepTime := aNumber! !
step
self pacManGame step.
! !
initializeWith:
aPacManGame
self stopStepping.
self pacManGame: aPacManGame.
self stepTime: 1.
self position: 500@0.
self contents: 'Un Timer'! !
'From
Squeak3.6 of ''6 October 2003'' [latest update: #5429] on 20 July 2004 at
2:33:12 am'!
extent
^ extent! !
!Board methodsFor: 'accesors' stamp: 'Ale 7/16/2004 16:21'!
extent: aPoint
extent := aPoint! !
!Board methodsFor: 'accesors' stamp: 'Ale 7/16/2004 16:22'!
gridSize
^ gridSize! !
!Board methodsFor: 'accesors' stamp: 'Ale 7/16/2004 16:23'!
gridSize: aNumber
^ gridSize := aNumber! !
!Board methodsFor: 'accesors' stamp: 'Ale 6/23/2004 17:00'!
objects
^ objects! !
!Board methodsFor: 'accesors' stamp: 'Ale 7/16/2004 16:22'!
objects: aDictionary
objects := aDictionary! !
!Board methodsFor: 'accesors' stamp: 'Ale 6/28/2004 17:27'!
positions
^ positions! !
!Board methodsFor: 'accesors' stamp: 'Ale 7/16/2004 16:22'!
positions: aDictionary
positions := aDictionary! !
isAtGridPoint: anObject
" Informa si anObject esta ubicado en un gridPoint.
"
^ self isGridPoint: (self positionOf: anObject).
! !
!Board methodsFor: 'game concepts' stamp: 'Ale 7/16/2004 16:23'!
isGridPoint: aPoint
" Informa si una coordenada es un gridPoint. "
| grid |
grid := self gridSize.
^ ((aPoint x) - (grid/2) / grid) isInteger and: [((aPoint y)
- (grid/2) / grid) isInteger].
! !
initialize
self positions: Dictionary new.
self objects: Dictionary new.
self extent: (0@0).
self gridSize: 0.! !
put: anObject at: aPoint
" Agregar anObject en la posicion aPoint al
board."
positions at: anObject put: aPoint.
self objects at: aPoint put: ((self objectsAt: aPoint) add:
anObject; yourself).
! !
!Board methodsFor: 'adding/removing' stamp: 'Ale 7/11/2004 14:28'!
remove: anObject
| aPoint |
aPoint := self positionOf: anObject.
(self objects at: aPoint) remove: anObject.
(self objects at: aPoint) isEmpty
ifTrue: [ self objects removeKey: aPoint
].
positions removeKey: anObject
! !
includes: anObject
" Informa si anObejct esta presente en el board."
^ positions keys includes: anObject.! !
!Board methodsFor: 'observing' stamp: 'Ale 7/16/2004 16:25'!
objectsAt: aPoint
" Informa los objetos presentes en el board en la
posicion aPoint. "
(self objects includesKey: aPoint)
ifTrue: [ ^ objects at: aPoint ]
ifFalse: [ ^ (Set new) ]! !
!Board methodsFor: 'observing' stamp: 'Ale 7/16/2004 16:41'!
objectsAt: aPoint axis: aDirection distance: aNumber
"Objetos a distancia aNumner en direccion aDirection
desde aPoint."
| returnSet inspectPoint |
returnSet := Set new.
0 to: aNumber do:
[ :each |
inspectPoint := aPoint
+ (aDirection * each).
returnSet := returnSet
union: (self objectsAt: inspectPoint).].
^ returnSet
! !
!Board methodsFor: 'observing' stamp: 'Ale 7/16/2004 16:24'!
positionOf: anObject
" Informa la posicion de anObject en el board."
^ positions at: anObject! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
new
^ (super new) initialize! !
'From Squeak3.6 of ''6 October 2003'' [latest update: #5429]
on 20 July 2004 at 2:34:02 am'!
addFile: aFile number:
aFileNumber to: aBoard
"Agregar una fila del layout al board."
1 to: aFile size
do: [:aColNumber | self
addPiece: (aFile at: aColNumber)
at:
aColNumber - 1 @ aFileNumber
to:
aBoard]! !
!Level methodsFor: 'layout processing' stamp: 'Ale 7/16/2004 18:00'!
addPiece: aSymbol at: aPoint to: aBoard
"Agregar un elemento del layout al board."
| aGridPoint aPiece |
aPiece := self symbolToInstance: aSymbol.
aGridPoint := self pointToGrid: aPoint.
aPiece addToLevel: self.
aBoard put: aPiece at: aGridPoint.
! !
!Level methodsFor: 'layout processing' stamp: 'Ale 7/16/2004 17:17'!
gridSize
"Separacion entre puntos de grilla."
^18! !
!Level methodsFor: 'layout processing' stamp: 'Ale 7/17/2004 21:28'!
initializeBoard: aBoard
aBoard initialize.
1
to: layout size
do: [:fileNumber | self
addFile: (layout at: fileNumber)
number: fileNumber - 1
to:
aBoard].
aBoard extent: (layout at: 1) size * self gridSize @ (layout
size * self gridSize).
aBoard gridSize: self gridSize.
! !
!Level methodsFor: 'layout processing' stamp: 'Ale 7/17/2004 11:53'!
initializeGhosts: aGhostSet
aGhostSet do: [:each | each ghostHome: (self ghostHome)].! !
!Level methodsFor: 'layout processing' stamp: 'Ale 7/16/2004 18:12'!
numberToGrid: aNumber.
"Convierte un numero a la posicion de grid
asociada."
aNumber = 0
ifTrue: [^ self gridSize / 2]
ifFalse: [^ self gridSize * aNumber +
(self gridSize / 2)].
! !
!Level methodsFor: 'layout processing' stamp: 'Ale 7/16/2004 18:12'!
pointToGrid: aPoint
"Convierte una posicion del layout del nivel a una
posicion grid del
board. "
| xGrid yGrid |
xGrid := self numberToGrid: aPoint x.
yGrid := self numberToGrid: aPoint y.
^ (xGrid@yGrid)
! !
!Level methodsFor: 'layout processing' stamp: 'Ale 7/16/2004 18:03'!
symbolToInstance: aSymbol
"Convierte un simbolo del layout a una instancia para
poner en el
board. "
^ (self classRepository
select: [:each | each isMyLayoutId:
aSymbol]) anyOne new! !
initialize
self pills: Set new.
self powerPills: Set new.
self walls: Set new.
self ghostOnlyWalls: Set new.
self initializeClassRepository.
self initializeLayoutRepository.
self initializeFruitRepository.! !
!Level methodsFor: 'initialize' stamp: 'Ale 7/18/2004 20:47'!
initializeClassRepository
"Clases asociadas a los simbolos que pueden aparecer en
un layout de un nivel."
self classRepository: Set new.
self classRepository add: Wall.
self classRepository add: Pill.
self classRepository add: PowerPill.
self classRepository add: GhostOnlyWall.
self classRepository add: GhostHome.
self classRepository add: PacManHome.! !
!Level methodsFor: 'initialize' stamp: 'Ale 7/19/2004 15:44'!
initializeFruitRepository
"Fruits del juego, una por nivel."
| aFruitRepository |
aFruitRepository := OrderedCollection new.
aFruitRepository addLast: (Cherry new) initialize.
aFruitRepository addLast: (Apple new) initialize.
aFruitRepository addLast: (Bannana new) initialize.
aFruitRepository addLast: (Peach new) initialize.
fruitRepository := aFruitRepository.! !
!Level methodsFor: 'initialize' stamp: 'Ale 7/19/2004 15:46'!
initializeLayoutRepository
"Layouts del juego, uno por nivel."
| aLayoutRepository |
aLayoutRepository := OrderedCollection new.
aLayoutRepository addLast: #(
#(w w w w w w w w w w w w w w w)
#(w s p p p p p p p p p p p s w)
#(w p w w w w p w p w w w w p w)
#(w p p p p w p p p w p p p p w)
#(w p w w p w p w p w p w w p w)
#(w p p p p p p p p p p p p p w)
#(w p w p w p w w w p w p w p w)
#(w p w p p p p p p p p p w p w)
#(w p w w p w w d w w p w w p w)
#(w p p p p p w G w p p p p p w)
#(w p w w w p w w w p w w w p w)
#(w s p p p p p P p p p p p s w)
#(w w w w w w w w w w w w w w w)
).
aLayoutRepository addLast: #(
#(w w w w w w w w w w w w w w w)
#(w p p p p p w w w p p p p p w)
#(w p w p w p p s p p w p w p w)
#(w p p p w w p w p w w p p p w)
#(w p w w w w p w p w w w w p w)
#(w p p p p p p p p p p p p p w)
#(w w w p w w w s w w w p w w w)
#(w p p p p p p p p p p p p p w)
#(w p w w w p w d w p w w w p w)
#(w p p p w p w G w p w p p p w)
#(w p w p w p w w w p w p w p w)
#(w p p p p p p p P p p p p p w)
#(w w w w w w w w w w w w w w w)
).
aLayoutRepository addLast: #(
#(w w w w w w w w w w w)
#(w p p p p p p p p s w)
#(w p w w p w p w w p w)
#(w p w p p p p p w p w)
#(w p p p w d w p p p w)
#(w p w w w G w w w p w)
#(w p p p w w w p p p w)
#(w p w p p P p p w p w)
#(w p w w p w p w w p w)
#(w s p p p p p p p p w)
#(w w w w w w w w w w w)
).
aLayoutRepository addLast:
#(
#(w w w w w w w w w w w w w w w w w w w)
#(w s p p p p p p p p p p p p p p p s w)
#(w p w w p w p w p w p w p w p w w p w)
#(w p p p p p p p p w p p p p p p p p w)
#(w p w w p w p w w w w w p w p w w p w)
#(w p p p p p p p p p p p p p p p p p w)
#(w p w p w w p p w d w p p w w p w p w)
#(w p w p w w p p w G w p p w w p w p w)
#(w p p p p p p p w w w p p p p p p p w)
#(w p w p w w p p p p p p p w w p w p w)
#(w p w p w w p w w w w w p w w p w p w)
#(w p w p w w p p p p p p p w w p w p w)
#(w p w p p p p w w w w w p p p p w p w)
#(w p p p w w p w w w w w p w w p p p w)
#(w p w p p w p p p P p p p w p p w p w)
#(w p w w p w w w w p w w w w p w w p w)
#(w s p p p p p p p p p p p p p p p s w)
#(w w w w w w w w w w w w w w w w w w w)
).
layoutRepository := aLayoutRepository.! !
!Level methodsFor: 'initialize' stamp: 'Ale 7/18/2004 10:01'!
loadLevel: aNumber
self initialize.
self layout: (layoutRepository at: aNumber).
self fruit: (fruitRepository at: aNumber).
self turnsToFruit: 400 atRandom.
! !
addGhostOnlyWall:
aGhostOnlyWall
self ghostOnlyWalls add: aGhostOnlyWall! !
!Level methodsFor: 'set wrapers' stamp: 'Ale 7/16/2004 17:14'!
addPill: aPill
self pills add: aPill ! !
!Level methodsFor: 'set wrapers' stamp: 'Ale 7/16/2004 17:14'!
addPowerPill: aPowerPill
self powerPills add: aPowerPill ! !
!Level methodsFor: 'set wrapers' stamp: 'Ale 7/16/2004 17:14'!
addWall: aWall
self walls add: aWall! !
!Level methodsFor: 'set wrapers' stamp: 'Ale 7/16/2004 17:14'!
removePill: aPill
self pills remove: aPill ! !
!Level methodsFor: 'set wrapers' stamp: 'Ale 7/16/2004 17:14'!
removePowerPill: aPowerPill
self powerPills remove: aPowerPill ! !
classRepository
^ classRepository! !
!Level methodsFor: 'accesors' stamp: 'Ale 7/16/2004 17:50'!
classRepository: aSet
classRepository := aSet! !
!Level methodsFor: 'accesors' stamp: 'Ale 7/16/2004 17:13'!
fruit
^ fruit! !
!Level methodsFor: 'accesors' stamp: 'Ale 7/16/2004 17:13'!
fruit: aFruit
fruit := aFruit! !
!Level methodsFor: 'accesors' stamp: 'Ale 7/16/2004 17:13'!
fruitHome
"La fruit tiene la misma posicion inicial que el pacman
(asi lo hace la version de
ejemplo que esta en la pagina de la materia)"
^ pacManHome! !
!Level methodsFor: 'accesors' stamp: 'Ale 7/17/2004 10:41'!
fruitHome: aFruitHome
fruitHome := aFruitHome! !
!Level methodsFor: 'accesors' stamp: 'Ale 7/17/2004 11:54'!
ghostHome
^ ghostHome! !
!Level methodsFor: 'accesors' stamp: 'Ale 7/17/2004 11:54'!
ghostHome: aGhostHome
ghostHome := aGhostHome! !
!Level methodsFor: 'accesors' stamp: 'Ale 7/16/2004 17:11'!
ghostOnlyWalls
^ ghostOnlyWalls! !
!Level methodsFor: 'accesors' stamp: 'Ale 7/16/2004 17:11'!
ghostOnlyWalls: aGhostOnlyWallSet
ghostOnlyWalls := aGhostOnlyWallSet.! !
!Level methodsFor: 'accesors' stamp: 'Ale 7/16/2004 17:11'!
layout
^ layout! !
!Level methodsFor: 'accesors' stamp: 'Ale 7/16/2004 17:11'!
layout: aSortedCollection
layout := aSortedCollection.! !
!Level methodsFor: 'accesors' stamp: 'Ale 7/16/2004 17:11'!
pacManHome
^ pacManHome! !
!Level methodsFor: 'accesors' stamp: 'Ale 7/17/2004 10:42'!
pacManHome: aPacManHome
pacManHome := aPacManHome! !
!Level methodsFor: 'accesors' stamp: 'Ale 7/16/2004 17:10'!
pills
^ pills! !
!Level methodsFor: 'accesors' stamp: 'Ale 7/16/2004 17:10'!
pills: aPillSet
pills := aPillSet! !
!Level methodsFor: 'accesors' stamp: 'Ale 7/16/2004 17:10'!
powerPills
^ powerPills! !
!Level methodsFor: 'accesors' stamp: 'Ale 7/16/2004 17:10'!
powerPills: aPowerPillSet
powerPills := aPowerPillSet! !
!Level methodsFor: 'accesors' stamp: 'Ale 7/16/2004 17:10'!
turnsToFruit
^ turnsToFruit! !
!Level methodsFor: 'accesors' stamp: 'Ale 7/16/2004 17:10'!
turnsToFruit: aNumber
turnsToFruit := aNumber! !
!Level methodsFor: 'accesors' stamp: 'Ale 7/16/2004 17:10'!
walls
^ walls! !
!Level methodsFor: 'accesors' stamp: 'Ale 7/16/2004 17:10'!
walls: aWallSet
walls := aWallSet! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
'From Squeak3.6 of ''6 October 2003'' [latest update: #5429]
on 20 July 2004 at 2:35:47 am'!
fruitManager
^ fruitManager! !
!RuleManager methodsFor: 'accesing' stamp: 'Ale 7/17/2004 10:11'!
fruitManager: aFruitManager
fruitManager := aFruitManager! !
!RuleManager methodsFor: 'accesing' stamp: 'Ale 7/17/2004 10:11'!
pillManager
^ pillManager! !
!RuleManager methodsFor: 'accesing' stamp: 'Ale 7/17/2004 10:11'!
pillManager: aPillManager
pillManager := aPillManager! !
!RuleManager methodsFor: 'accesing' stamp: 'Ale 7/17/2004 10:11'!
powerPillManager
^ powerPillManager! !
!RuleManager methodsFor: 'accesing' stamp: 'Ale 7/17/2004 10:11'!
powerPillManager: aPowerPillManager
powerPillManager := aPowerPillManager! !
decrementLives: aGame.
aGame lives: (aGame lives - 1). ! !
!RuleManager methodsFor: 'processing' stamp: 'Ale 7/17/2004 10:10'!
isOver: aGame
^ aGame lives isZero
! !
!RuleManager methodsFor: 'processing' stamp: 'Ale 7/17/2004 10:10'!
loadNextLevel: aGame
aGame loadLevel: ( aGame levelNumber + 1).! !
!RuleManager methodsFor: 'processing' stamp: 'Ale 7/17/2004 10:10'!
pacManDead: aGame
"Acciones a tomar cuando el pacMan muere."
self decrementLives: aGame.
(self isOver: aGame)
ifFalse: [aGame resetLevel]
ifTrue: [aGame gameOver: true].! !
!RuleManager methodsFor: 'processing' stamp: 'Ale 7/17/2004 10:08'!
process: aGame
self fruitManager process: aGame.
self powerPillManager process: aGame.
self pillManager process: aGame.
self processGameRules: aGame.! !
!RuleManager methodsFor: 'processing' stamp: 'Ale 7/17/2004 10:09'!
processGameRules: aGame
aGame isPacManDead
ifTrue: [self pacManDead: aGame].
aGame isLevelClear
ifTrue: [self loadNextLevel: aGame].! !
'From Squeak3.6 of ''6 October 2003'' [latest update: #5429]
on 20 July 2004 at 2:36:56 am'!
initialize
self duration: -1.! !
duration
^ duration! !
!PowerPillManager methodsFor: 'accesing' stamp: 'Ale 7/17/2004 09:57'!
duration: aNumber
duration := aNumber! !
aliveGhosts: aGame
^ aGame ghosts select:[:each | each eated not].
! !
!PowerPillManager methodsFor: 'filtering ghosts' stamp: 'Ale 7/17/2004 09:57'!
weakGhosts: aGame
^ aGame ghosts select:[:each | each weak].
! !
decreaseDuration
self duration: (self duration) - 1.! !
!PowerPillManager methodsFor: 'process' stamp: 'Ale 7/17/2004 10:06'!
process: aGame
"Remueve las superPills comidas, revisa si es momento
de detener el efecto
de alguna superPill activada."
self removeEated: aGame.
self isActive
ifTrue: [
self decreaseDuration.
self tryRecoverGhosts:
aGame.
self tryStopEffect:
aGame. ]
! !
!PowerPillManager methodsFor: 'process' stamp: 'Ale 7/17/2004 09:59'!
recoveringGhosts: aGame
"Avisar a los ghost que esta por expriar el efecto de
la powerPill."
(self aliveGhosts: aGame) do: [:each | each beRecovering].
! !
!PowerPillManager methodsFor: 'process' stamp: 'Ale 7/17/2004 10:04'!
removeEated: aGame
"Elimina las superPills comidas, inicia el efecto de la
superPill."
| pillsToRemove |
pillsToRemove := aGame level powerPills select: [:each |
each eated].
pillsToRemove do: [:each |
aGame board remove: each.
aGame level removePowerPill: each.
aGame addScore: each score.
self startEffect: each turnsToLive on: aGame ]! !
!PowerPillManager methodsFor: 'process' stamp: 'Ale 7/17/2004 10:01'!
startEffect: turnsNumber on: aGame
"Iniciar los efectos de la powerPill."
self duration: turnsNumber.
aGame pacMan bePowerUp.
(self aliveGhosts: aGame) do: [:each | each beWeak]
! !
!PowerPillManager methodsFor: 'process' stamp: 'Ale 7/17/2004 10:01'!
stopEffect: aGame
"Detener los efectos de la powerPill."
aGame pacMan beNormal.
(self aliveGhosts: aGame) do: [:each | each beNormal].
! !
!PowerPillManager methodsFor: 'process' stamp: 'Ale 7/17/2004 09:58'!
tryRecoverGhosts: aGame
"Si esta por expirar el efecto de la pildora avisar a
los ghost que se
estan por recuperar."
self isNearExpire ifTrue: [ self recoveringGhosts: aGame ].!
!
!PowerPillManager methodsFor: 'process' stamp: 'Ale 7/17/2004 10:05'!
tryStopEffect: aGame
"Si se termino la duracion de la superPill, detener su
efecto."
self shouldStopEffect ifTrue: [ self stopEffect: aGame ].
! !
'From Squeak3.6 of ''6 October 2003'' [latest update: #5429]
on 20 July 2004 at 2:37:35 am'!
'From Squeak3.6 of ''6 October 2003'' [latest update: #5429]
on 20 July 2004 at 2:38:34 am'!
initializeWith: aGame
self turnsToFruit: aGame level turnsToFruit! !
turnsToFruit
^ turnsToFruit! !
!FruitManager methodsFor: 'accesing' stamp: 'Ale 7/18/2004 20:56'!
turnsToFruit: aNumber
turnsToFruit := aNumber! !
'From Squeak3.6 of ''6 October 2003'' [latest update: #5429]
on 20 July 2004 at 2:39 am'!
'From Squeak3.6 of ''6 October 2003'' [latest update: #5429]
on 20 July 2004 at 2:40:22 am'!
actor
^ actor! !
!MoveStrategy methodsFor: 'accesors' stamp: 'Ale 7/9/2004 15:58'!
actor: anObject
actor := anObject! !
!MoveStrategy methodsFor: 'accesors' stamp: 'Ale 7/9/2004 16:35'!
turnsToChoose
^ turnsToChoose! !
!MoveStrategy methodsFor: 'accesors' stamp: 'Ale 7/9/2004 16:35'!
turnsToChoose: aNumber
turnsToChoose := aNumber! !
initializeWith: anActor
"Una estrategia esta asociada a un actor."
self actor: anActor.
self forceTurnsToChoose.! !
aviableDirectionsOn: aBoard
"Las direcciones disponibles dependen de si el actor
esta o no en una
posicion gridPoint."
( aBoard isAtGridPoint: (self actor))
ifTrue: [^ self
gridPointAviableDirectionsOn: aBoard ]
ifFalse: [^ self
nonGridPointAviableDirectionsOn: aBoard ].
! !
!MoveStrategy methodsFor: 'strategy AI' stamp: 'Ale 7/19/2004 00:57'!
calculateDirectionOn: aBoard
" Seleccionar las direcciones posibles, quedarse con la
mejor segun la estrategia."
| aviableDirections |
aviableDirections := self aviableDirectionsOn: aBoard.
^ self selectBestDirection: aviableDirections on: aBoard.
! !
!MoveStrategy methodsFor: 'strategy AI' stamp: 'Ale 7/19/2004 00:58'!
gridPointAviableDirectionsOn: aBoard
"Direcciones disponibles cuando el actor esta en un
gridPoint."
self subclassResponsibility.! !
!MoveStrategy methodsFor: 'strategy AI' stamp: 'Ale 7/19/2004 00:58'!
nonGridPointAviableDirectionsOn: aBoard
"Direcciones disponibles cuando el actor no esta en un
gridPoint."
self subclassResponsibility.! !
!MoveStrategy methodsFor: 'strategy AI' stamp: 'Ale 7/19/2004 00:59'!
selectBestDirection: aviableDirections on: aBoard
"Seleccionar la mejor direccion entre las
aviableDirections."
self subclassResponsibility.! !
'From Squeak3.6 of ''6 October 2003'' [latest update: #5429]
on 20 July 2004 at 2:40:54 am'!
target
^ target! !
!Targeted methodsFor: 'accesors' stamp: 'Ale 7/9/2004 16:04'!
target: anObject
target := anObject! !
farestDirectionToTarget:
aDirectionSet on: aBoard
| myPosition aDistance targetPosition bestDirection |
myPosition := aBoard positionOf: (self actor).
targetPosition := aBoard positionOf: (self target).
aDistance := 0.
aDirectionSet do:[ :each || testPosition|
testPosition := myPosition + each.
(aDistance < (testPosition dist:
targetPosition))
ifTrue: [aDistance :=
(testPosition dist: targetPosition). bestDirection := each]].
^ bestDirection.
! !
!Targeted methodsFor: 'distance' stamp: 'Ale 7/17/2004 19:47'!
nearestDirectionToTarget: aDirectionSet on: aBoard
| myPosition aDistance targetPosition bestDirection |
myPosition := aBoard positionOf: (self actor).
targetPosition := aBoard positionOf: (self target).
aDistance := (aBoard extent x) squared + (aBoard extent y)
squared.
aDirectionSet do:[ :each || testPosition|
testPosition := myPosition + each.
(aDistance > (testPosition dist:
targetPosition))
ifTrue: [aDistance :=
(testPosition dist: targetPosition). bestDirection := each]].
^ bestDirection.
! !
'From Squeak3.6 of ''6 October 2003'' [latest update: #5429]
on 20 July 2004 at 2:41:36 am'!
gridPointAviableDirectionsOn:
aBoard
" pedir las direcciones libres de colision, eliminar la
opcion de retroceder "
| aviableDirections |
aviableDirections := self actor collisionManager
permitedDirections: (self actor) on: aBoard.
aviableDirections remove: ((self actor direction) * -1)
ifAbsent: [].
^ aviableDirections! !
!ChaseEasy methodsFor: 'strategy' stamp: 'Ale 7/20/2004 02:21'!
nonGridPointAviableDirectionsOn: aBoard
" Fuera de un gridPoint solo se puede seguir en la
misma direccion. "
| aviableDirections |
aviableDirections := Set new.
aviableDirections add: (self actor direction).
^ aviableDirections! !
!ChaseEasy methodsFor: 'strategy' stamp: 'Ale 7/17/2004 12:28'!
resetTurnsToChoose
self turnsToChoose: self actor smartness.! !
!ChaseEasy methodsFor: 'strategy' stamp: 'Ale 7/17/2004 12:36'!
selectBestDirection: aviableDirections on: aBoard
"Si es momento de elegir una direccion buscar la mejor,
pero sino (no puede avanzar en
su direccion) entonces elegir una al azar."
self turnsToChoose isZero
ifTrue: [^ self nearestDirectionToTarget:
aviableDirections on: aBoard]
ifFalse: [^ aviableDirections atRandom]
! !
'From Squeak3.6 of ''6 October 2003'' [latest update: #5429]
on 20 July 2004 at 2:42:06 am'!
gridPointAviableDirectionsOn:
aBoard
" pedir las direcciones libres de colision,, eliminar
la opcion de retroceder "
| aviableDirections |
aviableDirections := self actor collisionManager
permitedDirections: (self actor) on: aBoard.
aviableDirections remove: ((self actor direction) * -1)
ifAbsent: [].
^ aviableDirections! !
!ChaseHard methodsFor: 'strategy' stamp: 'Ale 7/20/2004 02:21'!
nonGridPointAviableDirectionsOn: aBoard
" Fuera de un gridPoint solo se puede seguir en la
misma direccion. "
| aviableDirections |
aviableDirections := Set new.
aviableDirections add: (self actor direction).
^ aviableDirections! !
!ChaseHard methodsFor: 'strategy' stamp: 'Ale 7/9/2004 17:40'!
resetTurnsToChoose
self turnsToChoose: self actor smartness.! !
!ChaseHard methodsFor: 'strategy' stamp: 'Ale 7/17/2004 12:37'!
selectBestDirection: aviableDirections on: aBoard
"Siempre elegir la direccion mas cercana al
target."
^ self nearestDirectionToTarget: aviableDirections on:
aBoard.
! !
'From Squeak3.6 of ''6 October 2003'' [latest update: #5429]
on 20 July 2004 at 2:42:46 am'!
gridPointAviableDirectionsOn:
aBoard
| aviableDirections |
aviableDirections := self actor collisionManager
permitedDirections: (self actor) on: aBoard.
aviableDirections remove: ((self actor direction) * -1)
ifAbsent: [].
^ aviableDirections
! !
!Escape methodsFor: 'strategy' stamp: 'Ale 7/20/2004 02:22'!
nonGridPointAviableDirectionsOn: aBoard
| aviableDirections |
aviableDirections := Set new. aviableDirections add: (self
actor direction).
^aviableDirections .
! !
!Escape methodsFor: 'strategy' stamp: 'Ale 7/17/2004 11:11'!
resetTurnsToChoose
self turnsToChoose: self actor smartness.! !
!Escape methodsFor: 'strategy' stamp: 'Ale 7/9/2004 19:17'!
selectBestDirection: aviableDirections on: aBoard
^ self farestDirectionToTarget: aviableDirections on:
aBoard.
! !
'From Squeak3.6 of ''6 October 2003'' [latest update: #5429]
on 20 July 2004 at 2:43:30 am'!
gridPointAviableDirectionsOn:
aBoard
| aviableDirections |
aviableDirections := self actor collisionManager
permitedDirections: (self actor) on: aBoard.
aviableDirections remove: ((self actor direction) * -1)
ifAbsent: [].
^ aviableDirections.
! !
!GoHome methodsFor: 'strategy' stamp: 'Ale 7/9/2004 19:21'!
nonGridPointAviableDirectionsOn: aBoard
| aviableDirections |
aviableDirections := Set new. aviableDirections add: (self
actor direction).
^aviableDirections.
! !
!GoHome methodsFor: 'strategy' stamp: 'Ale 7/9/2004 17:54'!
resetTurnsToChoose
self forceTurnsToChoose.! !
!GoHome methodsFor: 'strategy' stamp: 'Ale 7/9/2004 19:21'!
selectBestDirection: aviableDirections on: aBoard
^ self nearestDirectionToTarget: aviableDirections on:
aBoard.
! !
'From Squeak3.6 of ''6 October 2003'' [latest update: #5429]
on 20 July 2004 at 2:44:25 am'!
gridPointAviableDirectionsOn:
aBoard
| aviableDirections |
aviableDirections := (self actor collisionManager)
permitedDirections: (self actor) on: aBoard.
aviableDirections remove: ((self actor direction) * -1)
ifAbsent: [].
^ aviableDirections.
! !
!GridRandom methodsFor: 'strategy' stamp: 'Ale 7/9/2004 21:33'!
nonGridPointAviableDirectionsOn: aBoard
| aviableDirections |
aviableDirections := Set new.
aviableDirections add: (self actor direction).
^ aviableDirections
! !
!GridRandom methodsFor: 'strategy' stamp: 'Ale 7/17/2004 19:44'!
resetTurnsToChoose
self turnsToChoose: 1! !
!GridRandom methodsFor: 'strategy' stamp: 'Ale 7/9/2004 21:34'!
selectBestDirection: aviableDirections on: aBoard
^ aviableDirections atRandom.
! !
'From Squeak3.6 of ''6 October 2003'' [latest update: #5429]
on 20 July 2004 at 2:44:53 am'!
chooseDirectionOn: aBoard
self decreaseTurnsToChoose.
(self shouldChooseDirectionOn: aBoard)
ifTrue:[ self actor beNormal].! !
!LeaveHome methodsFor: 'strategy' stamp: 'Ale 7/9/2004 17:06'!
resetTurnsToChoose
^ self turnsToChoose: 20! !
'From Squeak3.6 of ''6 October 2003'' [latest update: #5429]
on 20 July 2004 at 2:45:24 am'!
gridPointAviableDirectionsOn:
aBoard
^ (self actor collisionManager) permitedDirections: (self
actor) on: aBoard.
! !
!UserControlled methodsFor: 'strategy' stamp: 'Ale 7/9/2004 19:22'!
nonGridPointAviableDirectionsOn: aBoard
| aviableDirections |
aviableDirections := Set new.
aviableDirections add: (self actor direction).
aviableDirections add: ((self actor direction) *-1).
^ aviableDirections
! !
!UserControlled methodsFor: 'strategy' stamp: 'Ale 7/9/2004 17:02'!
resetTurnsToChoose
^ self turnsToChoose: 1! !
!UserControlled methodsFor: 'strategy' stamp: 'Ale 7/9/2004 19:23'!
selectBestDirection: aviableDirections on: aBoard
(aviableDirections includes: self actor wantedDirection)
ifTrue: [ ^ self actor wantedDirection ]
ifFalse: [ ^ self actor direction ]
! !
'From Squeak3.6 of ''6 October 2003'' [latest update: #5429]
on 20 July 2004 at 2:48:31 am'!
defaultExtent
self subclassResponsibility.! !
!Actor methodsFor: 'initializing' stamp: 'Ale 7/18/2004 19:51'!
initialize
self extent: self defaultExtent.
! !
extent
^ extent! !
!Actor methodsFor: 'accessing' stamp: 'Ale 7/18/2004 19:51'!
extent: aPoint
extent := aPoint! !
canFruitCollision: aFruit
on: aBoard
"Informa si aFruit tiene permiso de colisionar con el
receptor."
self subclassResponsibility.! !
!Actor methodsFor: 'collision handling' stamp: 'Ale 7/18/2004 19:51'!
canGhostCollision: aGhost on: aBoard
"Informa si aGhost tiene permiso de colisionar con el receptor."
self subclassResponsibility.! !
!Actor methodsFor: 'collision handling' stamp: 'Ale 7/18/2004 19:51'!
canPacManCollision: aPacMan on: aBoard
"Informa si aPacMan tiene permiso de colisionar con el
receptor."
self subclassResponsibility.! !
!Actor methodsFor: 'collision handling' stamp: 'Ale 7/18/2004 19:51'!
fruitCollision: aFruit on: aBoard
"Informa al receptor que esta en colision con
aFruit."
self subclassResponsibility.! !
!Actor methodsFor: 'collision handling' stamp: 'Ale 7/18/2004 19:51'!
ghostCollision: aGhost on: aBoard
"Informa al receptor que esta en colision con
aGhost."
self subclassResponsibility.! !
!Actor methodsFor: 'collision handling' stamp: 'Ale 7/18/2004 19:51'!
pacManCollision: aPacMan on: aBoard
"Informa al receptor que esta en colision con
aPacMan."
self subclassResponsibility.! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
'From Squeak3.6 of ''6 October 2003'' [latest update: #5429]
on 20 July 2004 at 2:48:57 am'!
collisionAskSelector
^ collisionAskSelector! !
!MovilActor methodsFor: 'accessing' stamp: 'Ale 7/18/2004 20:04'!
collisionAskSelector: aSymbol
collisionAskSelector := aSymbol! !
!MovilActor methodsFor: 'accessing' stamp: 'Ale 7/18/2004 20:04'!
collisionManager
^ collisionManager! !
!MovilActor methodsFor: 'accessing' stamp: 'Ale 7/18/2004 20:04'!
collisionManager: aCollisionManager
collisionManager := aCollisionManager.! !
!MovilActor methodsFor: 'accessing' stamp: 'Ale 7/18/2004 20:04'!
collisionSelector
^ collisionSelector! !
!MovilActor methodsFor: 'accessing' stamp: 'Ale 7/18/2004 20:04'!
collisionSelector: aSymbol
collisionSelector := aSymbol! !
!MovilActor methodsFor: 'accessing' stamp: 'Ale 7/18/2004 20:04'!
direction
^ direction! !
!MovilActor methodsFor: 'accessing' stamp: 'Ale 7/18/2004 20:04'!
direction: aPoint
direction := aPoint! !
!MovilActor methodsFor: 'accessing' stamp: 'Ale 7/18/2004 20:04'!
moveStrategy
^ moveStrategy! !
!MovilActor methodsFor: 'accessing' stamp: 'Ale 7/18/2004 20:04'!
moveStrategy: aMoveStrategy
moveStrategy := aMoveStrategy! !
!MovilActor methodsFor: 'accessing' stamp: 'Ale 7/18/2004 20:04'!
speed
^ speed! !
!MovilActor methodsFor: 'accessing' stamp: 'Ale 7/18/2004 20:04'!
speed: aNumber
speed := aNumber! !
calculateNewPositionOn:
aBoard
"Calcular la siguiente posicion en aBoard."
"Se asume que la estrategia del actor siempre le provee
una direction en
la que pueda moverse."
^ (aBoard positionOf: self) + self direction.
! !
!MovilActor methodsFor: 'moving' stamp: 'Ale 7/18/2004 20:05'!
moveOn: aBoard
" Moverse en aBoard. "
^ self moveOn: aBoard times: (self speed)
! !
!MovilActor methodsFor: 'moving' stamp: 'Ale 7/18/2004 20:11'!
moveOn: aBoard times: aNumber
" Moverse en aBoard devolviendo la nueva posicion y
notificar las colisiones. "
| newPosition |
aNumber isZero
ifTrue: [^ aBoard positionOf: self].
self moveStrategy
chooseDirectionOn: aBoard.
newPosition := self calculateNewPositionOn: aBoard.
aBoard
remove: self;
put: self at: newPosition.
self collisionManager
notifyCollisions: self on: aBoard.
^ self moveOn: aBoard times: (aNumber - 1)
! !
initialize
super initialize.
self speed: 5.
self direction: (-1@0).
! !
canFruitCollision: aGhost
on: aBoard
"Los actores moviles de este juego pueden colisionar
todos con todos."
^ true! !
!MovilActor methodsFor: 'colision handling' stamp: 'Ale 7/18/2004 20:12'!
canGhostCollision: aGhost on: aBoard
"Los actores moviles de este juego pueden colisionar
todos con todos."
^ true! !
!MovilActor methodsFor: 'colision handling' stamp: 'Ale 7/18/2004 20:12'!
canPacManCollision: aPacMan on: aBoard
"Los actores moviles de este juego pueden colisionar
todos con todos."
^ true! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
'From Squeak3.6 of ''6 October 2003'' [latest update: #5429]
on 20 July 2004 at 2:49 am'!
addToLevel: aLevel
self subclassResponsibility.! !
isAtCollision: anObject on:
aBoard
"Verifica que la distancia entre centros de anObject
con el receptor
sea menor al extent del receptor."
^ ((aBoard positionOf: self) dist: (aBoard positionOf:
anObject)) <= (self extent)! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
'From Squeak3.6 of ''6 October 2003'' [latest update: #5429]
on 20 July 2004 at 2:50:21 am'!
eated
^ eated! !
!Ghost methodsFor: 'accessing' stamp: 'Ale 7/17/2004 19:52'!
eated: aBoolean
eated := aBoolean.
! !
!Ghost methodsFor: 'accessing' stamp: 'Ale 7/17/2004 11:50'!
ghostHome
^ ghostHome! !
!Ghost methodsFor: 'accessing' stamp: 'Ale 7/17/2004 11:50'!
ghostHome: aGhostHome
ghostHome := aGhostHome! !
!Ghost methodsFor: 'accessing' stamp: 'Ale 7/17/2004 19:51'!
pacMan
^ pacMan! !
!Ghost methodsFor: 'accessing' stamp: 'Ale 7/17/2004 19:51'!
pacMan: aPacMan
pacMan := aPacMan! !
!Ghost methodsFor: 'accessing' stamp: 'Ale 7/17/2004 19:51'!
recovering
^ recovering! !
!Ghost methodsFor: 'accessing' stamp: 'Ale 7/17/2004 19:51'!
recovering: aBoolean
recovering := aBoolean! !
!Ghost methodsFor: 'accessing' stamp: 'Ale 7/17/2004 19:51'!
speed
^ speed! !
!Ghost methodsFor: 'accessing' stamp: 'Ale 7/17/2004 19:52'!
speed: aNumber
speed := aNumber! !
!Ghost methodsFor: 'accessing' stamp: 'Ale 7/17/2004 19:52'!
weak
^ weak! !
!Ghost methodsFor: 'accessing' stamp: 'Ale 7/17/2004 19:52'!
weak: aBoolean
weak := aBoolean.
! !
defaultExtent
^ (18@18)! !
!Ghost methodsFor: 'initializing' stamp: 'Ale 7/17/2004 11:12'!
initialize
super initialize.
self resetState.
self collisionSelector: #ghostCollision:on:.
self collisionAskSelector: #canGhostCollision:on:.
! !
!Ghost methodsFor: 'initializing' stamp: 'Ale 7/18/2004 20:15'!
resetState
self
weak: false;
recovering: false;
eated:false;
speed: self normalSpeed;
leaveHome.! !
chaseEasy
"Seleccionar esta estrategia de movimiento."
self moveStrategy: (ChaseEasy new initializeWith: self
target: (self pacMan))! !
!Ghost methodsFor: 'strategy' stamp: 'Ale 7/18/2004 20:16'!
chaseHard
"Seleccionar esta estrategia de movimiento."
self moveStrategy: (ChaseHard new initializeWith: self
target: (self pacMan))! !
!Ghost methodsFor: 'strategy' stamp: 'Ale 7/18/2004 20:16'!
escape
"Seleccionar esta estrategia de movimiento."
self moveStrategy: (Escape new initializeWith: self target:
(self pacMan)).! !
!Ghost methodsFor: 'strategy' stamp: 'Ale 7/18/2004 20:16'!
goHome
"Seleccionar esta estrategia de movimiento."
self moveStrategy: (GoHome new initializeWith: self target:
self ghostHome).! !
!Ghost methodsFor: 'strategy' stamp: 'Ale 7/18/2004 20:16'!
gridRandom
"Seleccionar esta estrategia de movimiento."
self moveStrategy: (GridRandom new initializeWith: self)! !
!Ghost methodsFor: 'strategy' stamp: 'Ale 7/18/2004 20:16'!
isGoingHome
"Informar si esta usando esta estategia de
movimiento."
^ (self moveStrategy class) = GoHome.! !
!Ghost methodsFor: 'strategy' stamp: 'Ale 7/18/2004 20:17'!
isLeavingHome
"Informar si esta usando esta estategia de
movimiento."
^ (self moveStrategy class) = LeaveHome.! !
!Ghost methodsFor: 'strategy' stamp: 'Ale 7/18/2004 20:17'!
leaveHome
"Seleccionar esta estrategia de movimiento."
self moveStrategy: (LeaveHome new initializeWith: self)! !
beEated
"Poner al ghost como comido."
self eated: true.
self weak: false.
self recovering: false.
self speed: (self normalSpeed * 1.4) ceiling.
self goHome.! !
!Ghost methodsFor: 'state changes' stamp: 'Ale 7/18/2004 20:19'!
beLeavingHome
"Poner al ghost partiendo de su casa."
self resetState! !
!Ghost methodsFor: 'state changes' stamp: 'Ale 7/18/2004 20:19'!
beNormal
"Poner al ghost en estado normal."
self weak: false.
self recovering: false.
self speed: self normalSpeed.
self normalStrategy.
! !
!Ghost methodsFor: 'state changes' stamp: 'Ale 7/18/2004 20:19'!
beRecovering
"Poner al ghost recuperandose del efecto de la
powerPill."
self recovering: true.! !
!Ghost methodsFor: 'state changes' stamp: 'Ale 7/18/2004 20:19'!
beWeak
"Poner al ghost debil."
self weak: true.
self recovering: false.
self speed: 3.
self escape.
! !
!Ghost methodsFor: 'state changes' stamp: 'Ale 7/18/2004 20:18'!
normalSpeed
"Velocidad default que utiliza el ghost."
self subclassResponsibility.
! !
!Ghost methodsFor: 'state changes' stamp: 'Ale 7/18/2004 20:18'!
normalStrategy
"Estrategia default que utiliza el ghost."
self subclassResponsibility.
! !
!Ghost methodsFor: 'state changes' stamp: 'Ale 7/18/2004 20:18'!
smartness
"Un numero que indica cuan inteligente es el actor, lo
utilizan
las distintas estrategias. A mayor numero menor inteligencia."
self subclassResponsibility.
! !
fruitCollision: aFruit on:
aBoard
"No realizar ninguna accion."! !
!Ghost methodsFor: 'colision handling' stamp: 'Ale 7/18/2004 20:21'!
ghostCollision: aGhost on: aBoard
"No realizar ninguna accion."! !
!Ghost methodsFor: 'colision handling' stamp: 'Ale 7/18/2004 20:20'!
pacManCollision: aPacman on: aBoard
"Al colisionar con aPacMan verificar si estaba debil y
cambiar su estado
en consecuencia."
self weak
ifTrue: [self beEated]
! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
'From Squeak3.6 of ''6 October 2003'' [latest update: #5429]
on 20 July 2004 at 2:50:46 am'!
'From Squeak3.6 of ''6 October 2003'' [latest update: #5429]
on 20 July 2004 at 2:51:15 am'!
'From Squeak3.6 of ''6 October 2003'' [latest update: #5429]
on 20 July 2004 at 2:51:39 am'!
'From Squeak3.6 of ''6 October 2003'' [latest update: #5429]
on 20 July 2004 at 2:52:10 am'!
'From Squeak3.6 of ''6 October 2003'' [latest update: #5429]
on 20 July 2004 at 3:02:30 am'!
defaultExtent
^ (18@18)! !
!Fruit methodsFor: 'initializing' stamp: 'Ale 7/18/2004 20:29'!
defaultScore
"El score de la fruit cambia segun la clase de
fruit."
self subclassResponsibility! !
!Fruit methodsFor: 'initializing' stamp: 'Ale 7/18/2004 20:29'!
defaultSpeed
"La velocidad de la fruit cambia segun la clase de
fruit."
self subclassResponsibility! !
!Fruit methodsFor: 'initializing' stamp: 'Ale 7/18/2004 20:29'!
defaultTurnsToLive
"El tiempo de vida de la fruit cambia segun la clase de
fruit."
self subclassResponsibility! !
!Fruit methodsFor: 'initializing' stamp: 'Ale 7/17/2004 20:02'!
initialize
super initialize.
self collisionSelector: #fruitCollision:on:.
self collisionAskSelector: #canFruitCollision:on:.
self resetState.
self gridRandom.! !
!Fruit methodsFor: 'initializing' stamp: 'Ale 7/17/2004 20:02'!
resetState
self eated: false.
self speed: self defaultSpeed.
self score: self defaultScore.
self turnsToLive: self defaultTurnsToLive.! !
eated
^ eated! !
!Fruit methodsFor: 'accesing' stamp: 'Ale 7/17/2004 09:31'!
eated: aBoolean
eated := aBoolean! !
!Fruit methodsFor: 'accesing' stamp: 'Ale 7/17/2004 09:31'!
score
^ score! !
!Fruit methodsFor: 'accesing' stamp: 'Ale 7/17/2004 09:31'!
score: aNumber
score := aNumber! !
!Fruit methodsFor: 'accesing' stamp: 'Ale 7/17/2004 09:31'!
turnsToLive
^ turnsToLive! !
!Fruit methodsFor: 'accesing' stamp: 'Ale 7/17/2004 09:31'!
turnsToLive: aNumber
turnsToLive := aNumber! !
gridRandom
"Seleccionar esta estrategia de movimiento."
self moveStrategy: (GridRandom new initializeWith: self)! !
fruitCollision: aPacman on:
aBoard
"No realizar ninguna accion."! !
!Fruit methodsFor: 'colision handling' stamp: 'Ale 7/18/2004 20:25'!
ghostCollision: aGhost on: aBoard
"No realizar ninguna accion."! !
!Fruit methodsFor: 'colision handling' stamp: 'Ale 7/18/2004 20:24'!
pacManCollision: aPacman on: aBoard
"En colision con aPacMan, fue comida por aPacMan."
self eated: true.! !
decreaseLiveTime
"Decrementar la cantidad de turnos que le quedan a la
fruit."
self turnsToLive: self turnsToLive - 1
! !
!Fruit methodsFor: 'moving' stamp: 'Ale 7/17/2004 09:36'!
moveOn: aBoard
"Moverse, luego revisar si ya es momento de salir del
board."
super moveOn: aBoard.
self decreaseLiveTime.
self removeIfExpired.! !
!Fruit methodsFor: 'moving' stamp: 'Ale 7/17/2004 09:37'!
removeIfExpired
"Si es momento de salir del board, marcarse como que
fue comida."
self turnsToLive isZero
ifTrue: [self score: 0; eated: true]! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
'From Squeak3.6 of ''6 October 2003'' [latest update: #5429]
on 20 July 2004 at 3:03 am'!
'From Squeak3.6 of ''6 October 2003'' [latest update: #5429]
on 20 July 2004 at 3:03:04 am'!
'From Squeak3.6 of ''6 October 2003'' [latest update: #5429]
on 20 July 2004 at 3:03:07 am'!
'From Squeak3.6 of ''6 October 2003'' [latest update: #5429]
on 20 July 2004 at 3:03:10 am'!
'From Squeak3.6 of ''6 October 2003'' [latest update: #5429]
on 20 July 2004 at 3:04:46 am'!
alive
^ alive! !
!PacMan methodsFor: 'accesors' stamp: 'Ale 7/17/2004 10:29'!
alive: aBoolean
alive := aBoolean! !
!PacMan methodsFor: 'accesors' stamp: 'Ale 7/17/2004 10:30'!
powerUp
^ powerUp! !
!PacMan methodsFor: 'accesors' stamp: 'Ale 7/17/2004 10:30'!
powerUp: aBoolean
powerUp := aBoolean! !
!PacMan methodsFor: 'accesors' stamp: 'Ale 7/17/2004 10:30'!
wantedDirection
^ wantedDirection! !
!PacMan methodsFor: 'accesors' stamp: 'Ale 7/17/2004 10:30'!
wantedDirection: aPoint
wantedDirection := aPoint.! !
calculateNewPositionOn:
aBoard
"Avanzar en la direccion deseada o quedarse en el lugar
si no puede avanzar."
| myPosition |
myPosition := aBoard positionOf: self.
(self collisionManager canAdvance: self on: aBoard)
ifTrue: [ ^ (myPosition + self direction)
]
ifFalse: [ ^ myPosition ].
! !
shouldDeadWith: aGhost
"Si aPacMan colisiona con aGhost y no esta powerUp,
entonces muere."
self powerUp
ifFalse: [self alive: false].
! !
defaultExtent
^ (18@18)! !
!PacMan methodsFor: 'initializing' stamp: 'Ale 7/18/2004 20:03'!
initialize
super initialize.
self speed: 5.
self direction: (-1@0).
self wantedDirection: (-1@0).
self resetState.
self collisionSelector: #pacManCollision:on:.
self collisionAskSelector: #canPacManCollision:on:.
self userControlled.! !
!PacMan methodsFor: 'initializing' stamp: 'Ale 7/18/2004 20:01'!
resetState
self alive: true; powerUp: false.! !
fruitCollision: aFruit on:
aBoard
"No realizar ninguna accion."! !
!PacMan methodsFor: 'colision handling' stamp: 'Ale 7/18/2004 20:03'!
ghostCollision: aGhost on: aBoard
"Si aPacMan colisiona con aGhost verificar si debe
morir."
aGhost eated
ifFalse: [ self shouldDeadWith: aGhost ].
! !
!PacMan methodsFor: 'colision handling' stamp: 'Ale 7/18/2004 20:13'!
pacManCollision: aPacman on: aBoard
"No realizar ninguna accion."! !
userControlled
"Estrategia de movimiento controlada por el
usuario."
self moveStrategy: (UserControlled new initializeWith:
self)! !
beNormal
self powerUp: false! !
!PacMan methodsFor: 'state change' stamp: 'Ale 7/18/2004 20:00'!
bePowerUp
self powerUp: true! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
'From Squeak3.6 of ''6 October 2003'' [latest update: #5429]
on 20 July 2004 at 3:05:41 am'!
addToLevel: aLevel
aLevel ghostHome: self.! !
!GhostHome methodsFor: 'initializing' stamp: 'Ale 7/18/2004 19:12'!
defaultExtent
^ (1@1)! !
canGhostCollision: aGhost
on: aBoard
^ true! !
!GhostHome methodsFor: 'collision handling' stamp: 'Ale 7/18/2004 19:16'!
ghostCollision: aGhost on: aBoard
" Hubo una colision con aGhost, realizar las acciones
del caso. "
(self isAtCollision: aGhost on: aBoard)
ifTrue: [self tryLeaveHome: aGhost]
! !
!GhostHome methodsFor: 'collision handling' stamp: 'Ale 7/18/2004 19:17'!
tryLeaveHome: aGhost
"Si aGhost esta comido, prepararlo para salir de
casa."
aGhost eated ifTrue: [aGhost beLeavingHome]
! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
'From Squeak3.6 of ''6 October 2003'' [latest update: #5429]
on 20 July 2004 at 3:06:26 am'!
addToLevel: aLevel
aLevel pacManHome: self.! !
!PacManHome methodsFor: 'initializing' stamp: 'Ale 7/18/2004 19:20'!
defaultExtent
^ (1@1)! !
canFruitCollision: aFruit
on: aBoard
^ true! !
!PacManHome methodsFor: 'collision handling' stamp: 'Ale 7/18/2004 19:20'!
canGhostCollision: aGhost on: aBoard
^ true! !
!PacManHome methodsFor: 'collision handling' stamp: 'Ale 7/18/2004 19:20'!
canPacManCollision: aPacMan on: aBoard
^ true! !
!PacManHome methodsFor: 'collision handling' stamp: 'Ale 7/10/2004 16:04'!
fruitCollision: aFruit on: aBoard
! !
!PacManHome methodsFor: 'collision handling' stamp: 'Ale 7/10/2004 17:32'!
ghostCollision: aGhost on: aBoard
! !
!PacManHome methodsFor: 'collision handling' stamp: 'Ale 7/10/2004 17:33'!
pacManCollision: aPacMan on: aBoard
! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
'From Squeak3.6 of ''6 October 2003'' [latest update: #5429]
on 20 July 2004 at 3:06:54 am'!
addToLevel: aLevel
aLevel addPill: self.! !
!Pill methodsFor: 'initializing' stamp: 'Ale 7/18/2004 19:21'!
defaultExtent
^ (5@5)! !
!Pill methodsFor: 'initializing' stamp: 'Ale 7/18/2004 19:21'!
initialize
super initialize.
self score: 10; eated: false.! !
eated
^ eated! !
!Pill methodsFor: 'accessing' stamp: 'Ale 7/18/2004 19:21'!
eated: aBoolean
eated := aBoolean! !
!Pill methodsFor: 'accessing' stamp: 'Ale 7/18/2004 19:21'!
score
^ score! !
!Pill methodsFor: 'accessing' stamp: 'Ale 7/18/2004 19:21'!
score: aNumber
score := aNumber! !
canFruitCollision: aFruit
on: aBoard
^ true! !
!Pill methodsFor: 'collision handling' stamp: 'Ale 7/18/2004 19:21'!
canGhostCollision: aGhost on: aBoard
^ true! !
!Pill methodsFor: 'collision handling' stamp: 'Ale 7/18/2004 19:22'!
canPacManCollision: aPacMan on: aBoard
^ true! !
!Pill methodsFor: 'collision handling' stamp: 'Ale 7/10/2004 16:04'!
fruitCollision: aFruit on: aBoard
! !
!Pill methodsFor: 'collision handling' stamp: 'Ale 7/10/2004 17:38'!
ghostCollision: aGhost on: aBoard
! !
!Pill methodsFor: 'collision handling' stamp: 'Ale 7/18/2004 19:26'!
pacManCollision: aPacMan on: aBoard
" Si hay colision con aPacMan, la pill fue comida.
"
(self isAtCollision: aPacMan on: aBoard)
ifTrue: [self eated: true]
! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
'From Squeak3.6 of ''6 October 2003'' [latest update: #5429]
on 20 July 2004 at 3:06:56 am'!
addToLevel: aLevel
aLevel addPowerPill: self.! !
!PowerPill methodsFor: 'initializing' stamp: 'Ale 7/18/2004 19:27'!
defaultExtent
^ (8@8)! !
!PowerPill methodsFor: 'initializing' stamp: 'Ale 7/19/2004 15:47'!
initialize
super initialize.
self turnsToLive: 40.! !
turnsToLive
^ turnsToLive! !
!PowerPill methodsFor: 'accessing' stamp: 'Ale 7/18/2004 19:27'!
turnsToLive: aNumber
turnsToLive := aNumber! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
'From Squeak3.6 of ''6 October 2003'' [latest update: #5429]
on 20 July 2004 at 3:07:43 am'!
addToLevel: aLevel
aLevel addWall: self.! !
!Wall methodsFor: 'initializing' stamp: 'Ale 7/18/2004 19:38'!
defaultExtent
^ (18@18)! !
canFruitCollision: aFruit
on: aBoard
^ false! !
!Wall methodsFor: 'collision handling' stamp: 'Ale 7/18/2004 19:38'!
canGhostCollision: aGhost on: aBoard
^ false! !
!Wall methodsFor: 'collision handling' stamp: 'Ale 7/18/2004 19:38'!
canPacManCollision: aPacMan on: aBoard
^ false! !
!Wall methodsFor: 'collision handling' stamp: 'Ale 7/10/2004 17:22'!
fruitCollision: aFruit on: aBoard! !
!Wall methodsFor: 'collision handling' stamp: 'Ale 7/10/2004 17:22'!
ghostCollision: aPacman on: aBoard
! !
!Wall methodsFor: 'collision handling' stamp: 'Ale 7/10/2004 17:22'!
pacManCollision: aPacman on: aBoard
! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
'From Squeak3.6 of ''6 October 2003'' [latest update: #5429]
on 20 July 2004 at 3:07:46 am'!
addToLevel: aLevel
aLevel addGhostOnlyWall: self.! !
!GhostOnlyWall methodsFor: 'collision handling' stamp: 'Ale 7/18/2004 19:20'!
canGhostCollision: aGhost on: aBoard
" Solo pueden pasar ghosts comidos o que recien fueron
revividos."
^ aGhost isLeavingHome or:[aGhost isGoingHome]
! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
'From Squeak3.6 of ''6 October 2003'' [latest update: #5429]
on 20 July 2004 at 3:10:50 am'!
game
^ game! !
!PacManGameView methodsFor: 'accessing' stamp: 'Ale 7/17/2004 20:59'!
game: aGame
game := aGame! !
initialize
super initialize.
self game: PacManGame new newGame.
self game addDependent: self.
self position: (-2@-2).
self color: Color black.
self toggleStickiness.
self openInWorld.
self initializeView.! !
!PacManGameView methodsFor: 'initialization' stamp: 'Ale 7/18/2004 18:59'!
initializeView
"Agrega las dos vistas principales: de tablero y de
estado del juego."
self removeAllMorphs.
self addMorph: ((GameStatusView newColumn) initializeWith:
self game).
self addMorph: ((BoardView new) initializeWith: self game).
! !
'From Squeak3.6 of ''6 October 2003'' [latest update: #5429]
on 20 July 2004 at 3:11:52 am'!
updateView
"Poner la fruta (si entro en juego) y actualizar la
vista del board."
checkForFruit
ifTrue: [self createFruitsView: self
game].
self submorphs do: [:each | each updateView].
self changed.! !
checkForFruit
^ checkForFruit! !
!BoardView methodsFor: 'accessing' stamp: 'Ale 7/18/2004 18:22'!
checkForFruit: aBoolean
checkForFruit := aBoolean! !
!BoardView methodsFor: 'accessing' stamp: 'Ale 7/18/2004 18:22'!
game
^ game! !
!BoardView methodsFor: 'accessing' stamp: 'Ale 7/18/2004 18:22'!
game: aGame
game := aGame! !
'From Squeak3.6 of ''6 October 2003'' [latest update: #5429]
on 20 July 2004 at 3:12:37 am'!
game
^ game! !
!GameStatusView methodsFor: 'accessing' stamp: 'Ale 7/18/2004 00:21'!
game: aGame
game := aGame! !
updateView
self submorphs do: [:each | each updateView].
self changed
! !
'From Squeak3.6 of ''6 October 2003'' [latest update: #5429]
on 20 July 2004 at 3:13:02 am'!
'From Squeak3.6 of ''6 October 2003'' [latest update: #5429]
on 20 July 2004 at 3:13:55 am'!
fruit
^ fruit! !
!FruitView methodsFor: 'accessing' stamp: 'Ale 7/18/2004 18:49'!
fruit: aFruit
fruit := aFruit! !
!FruitView methodsFor: 'accessing' stamp: 'Ale 7/18/2004 00:30'!
fruitsColor
^ fruitsColor! !
!FruitView methodsFor: 'accessing' stamp: 'Ale 7/18/2004 00:30'!
fruitsColor: aFruitsColor
fruitsColor := aFruitsColor! !
!FruitView methodsFor: 'accessing' stamp: 'Ale 7/18/2004 18:49'!
game
^ game! !
!FruitView methodsFor: 'accessing' stamp: 'Ale 7/18/2004 18:49'!
game: aGame
game:= aGame! !
doUpdateView
"Actualizar la posicion o esconderse si fue
comida."
(self fruit) eated
ifTrue: [ self visible: fruit eated not]
ifFalse: [ self center: ((self game
board) positionOf: (self fruit))].
! !
!FruitView methodsFor: 'updating' stamp: 'Ale 7/18/2004 18:50'!
isOnBoard
"Informa si fruit esa en el board."
^ self game board includes: (self fruit).! !
!FruitView methodsFor: 'updating' stamp: 'Ale 7/18/2004 18:50'!
updateView
"Actualizar la vista si esta en el board, sino borrarse
de la vista."
self isOnBoard
ifTrue: [ self doUpdateView ]
ifFalse: [ self delete ]! !
'From Squeak3.6 of ''6 October 2003'' [latest update: #5429]
on 20 July 2004 at 3:13:56 am'!
initializeGhostColor
"Contiene la asociacion entre la clase de ghost y su
color."
| aGhostsColor |
aGhostsColor := Dictionary new.
aGhostsColor at: Blinky put: (Color red).
aGhostsColor at: Pinky put: (Color lightRed).
aGhostsColor at: Inky put: (Color lightCyan).
aGhostsColor at: Sue put: (Color lightOrange).
self ghostsColor: aGhostsColor
! !
!GhostView methodsFor: 'initializing' stamp: 'Ale 7/18/2004 18:54'!
initializeWith: aGame ghost: aGhost
self initializeGhostColor.
self game: aGame.
self ghost: aGhost.
self extent: aGhost extent.
self center: (aGame board positionOf: (aGame level
ghostHome)).
! !
updateColor
"Actualiza el color del ghost segun su estado. Si, esto
es una especie de case y a mi
me resulta tan desagradable como a ustedes, pero no encontre
una forma mejor de
hacerlo ya que el modelo no entiende de colores, y el
mecanismo de dependent/update
no me ayuda a distinguir el estado del ghost."
(self ghost) weak
ifTrue: [ self
color: Color blue;
borderColor: Color
black].
((self ghost weak) and: [self ghost recovering])
ifTrue: [ self
color: Color white;
borderColor: Color
black].
(self ghost) eated
ifTrue: [ self
color: Color black;
borderColor: Color
white].
(((self ghost) eated not) and: [self ghost weak not] )
ifTrue: [self
color: (self
ghostsColor at: (self ghost class));
borderColor: Color
black].
! !
!GhostView methodsFor: 'updating' stamp: 'Ale 7/18/2004 18:58'!
updateView
self center: ((self game board) positionOf: (self ghost)).
self updateColor! !
'From Squeak3.6 of ''6 October 2003'' [latest update: #5429]
on 20 July 2004 at 3:13:59 am'!
initializeWith: aGame
self game: aGame.
self pacMan: (aGame pacMan).
self extent: aGame pacMan extent.
self center: (aGame board positionOf: (aGame level pacManHome)).
! !
game
^ game! !
!PacManView methodsFor: 'accessing' stamp: 'Ale 7/18/2004 00:23'!
game: aGame
game := aGame! !
!PacManView methodsFor: 'accessing' stamp: 'Ale 7/18/2004 00:23'!
pacMan
^ pacMan! !
!PacManView methodsFor: 'accessing' stamp: 'Ale 7/18/2004 00:23'!
pacMan: aPacMan
pacMan := aPacMan! !
'From Squeak3.6 of ''6 October 2003'' [latest update: #5429]
on 20 July 2004 at 3:15:35 am'!
initializeWith: aGame
self game: aGame.
self color: Color white.! !
game
^ game! !
!LevelView methodsFor: 'accessing' stamp: 'Ale 7/18/2004 00:20'!
game: aGame.
game := aGame! !
'From Squeak3.6 of ''6 October 2003'' [latest update: #5429]
on 20 July 2004 at 3:15:42 am'!
'From Squeak3.6 of ''6 October 2003'' [latest update: #5429]
on 20 July 2004 at 3:16:40 am'!
'From Squeak3.6 of ''6 October 2003'' [latest update: #5429]
on 20 July 2004 at 3:17:25 am'!
'From Squeak3.6 of ''6 October 2003'' [latest update: #5429]
on 20 July 2004 at 3:17:27 am'!
'From Squeak3.6 of ''6 October 2003'' [latest update: #5429]
on 20 July 2004 at 3:17:29 am'!
En el CD que acompaña este trabajo, en el directorio tp1\pcMan se encuentra la imagen de Squeak donde desarrolle el trabajo. Al iniciar Squeak aparece un Transcript con un par de instrucciones para el docente y lo invita a evaluar:
PacManGameView new.
Aparecerá
en la esquina superior izquierda una vista del juego, para que la vista reciba
los eventos del teclado es necesario minimizar el Transcript (y cualquier otro
browser o inspector) y colocar el puntero del mouse sobre la vista. En esta
situación las teclas con las que funciona el juego son:
UP: PacMan hacia arriba
DOWN: PacMan hacia abajo
LEFT: PacMan hacia la izquierda
RIGHT: PacMan hacia la derecha
SPACE: Reset del juego
Notar
que no se puede arrastrar la vista a otra posición de la pantalla, la vista no
esta preparada para ser arrastrada (por favor, no lo haga se ve tan feo que me
da pena L), al respecto hay una nota
en la sección Cosas que sé que no están del todo bien.