-
Notifications
You must be signed in to change notification settings - Fork 0
/
LaberintoMorph.st
1870 lines (1391 loc) · 55.5 KB
/
LaberintoMorph.st
1
2
3
PolygonMorph subclass: #AristaMorph instanceVariableNames: 'verticeA verticeB ' classVariableNames: '' poolDictionaries: '' category: 'LaberintoMorph'!!AristaMorph methodsFor: 'modificadores' stamp: 'rma 10/9/2000 14:48'!verticeA: unPunto | elOtro | elOtro _ verticeB. self setVertices:(Array with:unPunto with:elOtro). verticeA _ unPunto. verticeB _ elOtro! !!AristaMorph methodsFor: 'modificadores' stamp: 'rma 10/9/2000 14:48'!verticeB: unPunto | elOtro | elOtro _ verticeA. self setVertices:(Array with:unPunto with:elOtro). verticeA _ unPunto. verticeB _ elOtro! !!AristaMorph methodsFor: 'observadores' stamp: 'rma 10/7/2000 13:11'!verticeA ^verticeA ! !!AristaMorph methodsFor: 'observadores' stamp: 'rma 10/7/2000 13:12'!verticeB ^verticeB! !!AristaMorph methodsFor: 'private' stamp: 'rma 10/7/2000 14:31'!setVariables self setVertices:(Array with: 986@218 with:986@322). self makeOpen. self borderColor: Color black. self borderWidth: 3. "self goBehind. " verticeA _ Set new. verticeB _ Set new. verticeA _ self vertices at:1. verticeB _ self vertices at:2 ! !"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!AristaMorph class instanceVariableNames: ''!!AristaMorph class methodsFor: 'instance creation' stamp: 'rma 10/5/2000 19:28'!new ^ super new setVariables! !EllipseMorph subclass: #BichoMorph instanceVariableNames: 'estoyEn path ' classVariableNames: '' poolDictionaries: '' category: 'LaberintoMorph'!!BichoMorph methodsFor: 'observadores' stamp: 'rma 10/27/2000 17:11'!dondeEstoy "Informa al bicho cuales son los nodos vecinos de su posicion" ^estoyEn ! !!BichoMorph methodsFor: 'observadores' stamp: 'rma 10/11/2000 16:11'!dondeEstoyVecinos "Informa al bicho cuales son los nodos vecinos de su posicion" ^estoyEn vecinos! !!BichoMorph methodsFor: 'observadores' stamp: 'rma 11/4/2000 00:05'!olor: cantidad| bicho colores |(self class == GatoMorph) ifTrue:[bicho _ 'gato'].(self class == RatonMorph) ifTrue:[bicho _ 'raton'].(bicho = 'raton ') ifTrue:[ (cantidad = 'caliente') ifTrue:[colores _ (Color r: 0.8 g: 0.4 b: 0.0)]. (cantidad = 'tibio') ifTrue:[colores _ (Color r: 1.0 g: 0.599 b: 0.0)]. (cantidad = 'frio') ifTrue:[colores _ (Color r: 1.0 g: 0.8 b: 0.0)]. ]. (bicho = 'gato') ifTrue:[ (cantidad = 'caliente') ifTrue:[colores _ (Color r: 0 g: 0.8 b: 0.4) ]. (cantidad = 'tibio') ifTrue:[colores _(Color r: 0.0 g: 1 b: 0)]. (cantidad = 'frio') ifTrue:[colores _ (Color r: 0.4 g: 1.0 b: 0.7)]. ].^colores.! !!BichoMorph methodsFor: 'observadores' stamp: 'rma 10/27/2000 21:43'!posicionEnNodo ^(((self dondeEstoy ) habitan) keyAtValue: self)! !!BichoMorph methodsFor: 'observadores' stamp: 'rma 11/6/2000 17:14'!recorrido ^path! !!BichoMorph methodsFor: 'modificadores' stamp: 'rma 10/11/2000 16:10'!seVa: unNodo unNodo noHabita: self. estoyEn _ nil "el bicho esta en camino hacia el siguiente nodo"! !!BichoMorph methodsFor: 'modificadores' stamp: 'rma 10/30/2000 18:16'!vaA: unNodo estoyEn _ unNodo. "Ubicacion Grafica Aca iria la animacion!!!!!!" self center: (unNodo ubicaA: self posicion: (unNodo ubicaA)). . "Se le avisa al nodo que tiene un nuevo bicho" unNodo bichoAgregar: self. ! !!BichoMorph methodsFor: 'modificadores' stamp: 'rma 10/30/2000 18:27'!vaAnimadoA: elNodo | camino | camino _ OrderedCollection new. "Ubicacion Grafica Aca iria la animacion!!!!!!" camino _ self moveTo: elNodo center. camino add: ( elNodo ubicaA: self posicion: (elNodo ubicaA)). "Se le avisa al nodo que tiene un nuevo bicho" elNodo bichoAgregar: self. estoyEn _ elNodo. self moveNow: camino. ^camino ! !!BichoMorph methodsFor: 'modificadores' stamp: 'rma 10/30/2000 18:18'!vaDe: unNodo a: otroNodo | bichoUnNodoPosicion | bichoUnNodoPosicion _ self posicionEnNodo. "UnBicho sale del nodo en el que esta y va a otro nodo" unNodo bichoQuitar: self. "Animacion: el bicho va al centro de unNodo" (bichoUnNodoPosicion ~~ 1) ifFalse:[self center: unNodo center]. "Animacion: El bicho se mueve hasta el otro Nodo" "camino _ self moveTo: otroNodo center. " "Actualizacion de Variables: El bicho ya esta dentro de otroNodo" ^( self vaAnimadoA: otroNodo ). "Animacion: El bicho se ubica dentro del nodo" " ((bichoOtroNodoPosicion) ~~ 1) ifTrue:[ camino add: (otroNodo ubicaA: self posicion: (otroNodo ubicaA))]. " ! !!BichoMorph methodsFor: 'propiedades visuales' stamp: 'rma 10/27/2000 21:13'!animation: origen a: destino "Crea el Camino" | orx ory desy desx casox casoy distx disty dmaParteX dmaParteY posActX posActY posAntX posAntY camino | camino _ OrderedCollection new. orx _ origen x. ory _ origen y. desx _ destino x. desy _ destino y. orx == desx ifTrue:[casox _ 0]. orx > desx ifTrue:[casox _ -1]. orx < desx ifTrue:[casox _ 1]. ory == desy ifTrue:[casoy _ 0]. ory > desy ifTrue:[casoy _ -1]. ory < desy ifTrue:[casoy _ 1]. (orx < desx ) ifTrue: [distx _ desx - orx]. (orx > desx ) ifTrue: [distx _ orx - desx]. (orx == desx ) ifTrue: [distx _ 0]. (ory < desy ) ifTrue: [disty _ desy - ory]. (ory > desy ) ifTrue: [disty _ ory - desy]. (ory == desy ) ifTrue: [disty _ 0]. dmaParteX _ (distx // 10). dmaParteY _ (disty // 10). posActX _ orx. posActY _ ory. "[((posActX <= desx) & (posActY <= desy) )] whileFalse:" 9 timesRepeat:[ posAntX _ posActX. posAntY _ posActY. posActX _ posAntX + (dmaParteX * casox). posActY _ posAntY + (dmaParteY * casoy). camino add: posActX@posActY. ]. camino add: desx@desy. ^camino. ! !!BichoMorph methodsFor: 'propiedades visuales' stamp: 'rma 11/10/2000 10:09'!estaEnMovimiento ^(path size ~~ 0).! !!BichoMorph methodsFor: 'propiedades visuales' stamp: 'rma 11/10/2000 10:04'!moveNow: camino " [(path size = 0) ifFalse:[(Delay forSeconds: (self stepTime)) wait ] ifTrue:[" path _ camino. self startStepping." ] ] fork." "[ (camino size ) = 0 ] whileFalse:[ path addLast: (camino first). camino removeFirst]." "[ (path size ) = 0 ] whileFalse:[ (Delay forSeconds: (self stepTime * (path size))) wait]"! !!BichoMorph methodsFor: 'propiedades visuales' stamp: 'rma 10/30/2000 15:55'!moveTo: unaCoordenada "Devuelve el cjto de coordenadas del lugar que ocupa actualmente hasta unaCoordenada" | estoy camino | estoy _ ((self dondeEstoy) center). camino _ self animation: estoy a: unaCoordenada. ^camino.! !!BichoMorph methodsFor: 'propiedades visuales' stamp: 'rma 10/27/2000 20:42'!moverseA: unaCoordenada "Se mueve del lugar que ocupa actualmente hasta unaCoordenada" | estoy | estoy _ self center. self startAnimation: estoy a: unaCoordenada.! !!BichoMorph methodsFor: 'propiedades visuales' stamp: 'rma 10/27/2000 20:57'!startAnimation: origen a: destino | orx ory desy desx casox casoy distx disty dmaParteX dmaParteY posActX posActY posAntX posAntY | path _ OrderedCollection new. orx _ origen x. ory _ origen y. desx _ destino x. desy _ destino y. orx == desx ifTrue:[casox _ 0]. orx > desx ifTrue:[casox _ -1]. orx < desx ifTrue:[casox _ 1]. ory == desy ifTrue:[casoy _ 0]. ory > desy ifTrue:[casoy _ -1]. ory < desy ifTrue:[casoy _ 1]. (orx < desx ) ifTrue: [distx _ desx - orx]. (orx > desx ) ifTrue: [distx _ orx - desx]. (orx == desx ) ifTrue: [distx _ 0]. (ory < desy ) ifTrue: [disty _ desy - ory]. (ory > desy ) ifTrue: [disty _ ory - desy]. (ory == desy ) ifTrue: [disty _ 0]. dmaParteX _ (distx // 10). dmaParteY _ (disty // 10). posActX _ orx. posActY _ ory. "[((posActX <= desx) & (posActY <= desy) )] whileFalse:" 9 timesRepeat:[ posAntX _ posActX. posAntY _ posActY. posActX _ posAntX + (dmaParteX * casox). posActY _ posAntY + (dmaParteY * casoy). path add: posActX@posActY. ]. path add: desx@desy. " 1 to: 10 do: [:i | path add: (orx + ((distx // i) * casox ))@(ory + ((disty // i) *casoy ))]." "path := path reversed." self startStepping. ! !!BichoMorph methodsFor: 'propiedades visuales' stamp: 'rma 11/11/2000 18:19'!startStepping " add me to the world " "World addMorphFront: self." super startStepping.! !!BichoMorph methodsFor: 'propiedades visuales' stamp: 'rma 11/11/2000 16:59'!step path size > 0 ifTrue: [self center: path removeFirst]. (path size = 0) ifTrue: [ self stopStepping ]." counter > ((path size) - 1) ifTrue: [ self stopStepping ]."! !!BichoMorph methodsFor: 'propiedades visuales' stamp: 'rma 12/15/2000 15:35'!stepTime ^100.! !!BichoMorph methodsFor: 'propiedades visuales' stamp: 'rma 11/11/2000 17:03'!stopStepping super stopStepping. " and tell my sender that I am done " "sender _ self valueOfProperty: #sender." "self showBalloon: ' msgString'." ! !!BichoMorph methodsFor: 'private' stamp: 'rma 11/9/2000 22:36'!initialize super initialize. estoyEn _ Set new. path _ OrderedCollection new.! !!BichoMorph methodsFor: 'acciones' stamp: 'pa 11/8/2000 17:05'!actuar "El bicho evala su estrategia y se mueve en consecuencia" | nodo1 nodo2 | "Si el nodo a donde decide ir es el mismo en el que esta no hace nada" ( (nodo1 _(self dondeEstoy)) = (nodo2 _(self estrategia)) ) ifFalse: [ self vaDe: nodo1 a:nodo2 ]. ! !BichoMorph subclass: #GatoMorph instanceVariableNames: 'nombre ' classVariableNames: '' poolDictionaries: '' category: 'LaberintoMorph'!!GatoMorph methodsFor: 'private' stamp: 'rma 12/14/2000 22:10'!setVariables self openInWorld. self extent: 10 @ 10. self borderColor: Color black. self borderWidth: 2. ! !!GatoMorph methodsFor: 'observadores' stamp: 'rma 11/4/2000 17:07'!bichoOlor: cantidad| colores | (cantidad = 'caliente') ifTrue:[colores _ (Color r: 0.8 g: 0.4 b: 0.0)].(cantidad = 'tibio') ifTrue:[colores _ (Color r: 1.0 g: 0.599 b: 0.0)].(cantidad = 'frio') ifTrue:[colores _ (Color r: 1.0 g: 0.8 b: 0.0)]. ^colores.! !!GatoMorph methodsFor: 'observadores' stamp: 'pa 11/7/2000 17:12'!numero "Devuelve el numero del gato" ^numero! !!GatoMorph methodsFor: 'observadores' stamp: 'pa 11/7/2000 20:51'!tipo "Devuelve la estrategia del gato" ^tipo! !!GatoMorph methodsFor: 'modificadores' stamp: 'rma 10/11/2000 21:56'!nuevoGatoEn: aPuerta "ifTrue [] luego" ! !!GatoMorph methodsFor: 'modificadores' stamp: 'pa 11/7/2000 17:12'!numero: unNumero "Asigna un numero al gato" numero _ unNumero! !!GatoMorph methodsFor: 'modificadores' stamp: 'pa 11/7/2000 20:52'!tipo: unaEstrategia "Asigna una estrategia al gato" tipo _ unaEstrategia! !!GatoMorph methodsFor: 'accion' stamp: 'rma 11/11/2000 19:20'!estrategia "Segun la estrategia devuelve un nodo" "(self tipo) habria que hacer un switch y segun el nro elige un metodo. ej: cobarde, vago, solitario" ^(self dondeEstoy).! !"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!GatoMorph class instanceVariableNames: ''!!GatoMorph class methodsFor: 'instance creation' stamp: 'rma 10/11/2000 21:53'!new ^ super new setVariables! !GatoMorph subclass: #GatoEstandarMorph instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'LaberintoMorph'!!GatoEstandarMorph methodsFor: 'acciones' stamp: 'pa 11/28/2000 20:10'!estrategia"Devuelve el nodo al que le conviene ir segun una estrategia""El gato estandar camina al azar hasta que encuentra al ratn y lo persigue" | puntajes vec temp valor habitantes elegidos | "Evaluar cada nodo vecino y le asignar puntajes a cada uno segn distntos criterios" puntajes _ RunArray new. ( ( vec _ (self dondeEstoyVecinos)asArray)isEmpty ) "obtiene los vecinos y los guarda en un array" ifTrue: [self error: 'Un nodo est aislado'] "si no hay vecinos enva un error" ifFalse: [ "Si hay un ratn en donde est se queda donde est" "Obtiene un array con los habitantes del nodo y se fija si hay un ratn" temp _ RunArray new. ((self dondeEstoy)habitan)asArray do: [:i| temp addLast:(i)class]. "arma un array con las clases solas(no los objetos)" ((temp indexOf:RatonMorph) == 0) "para poder identificar si hay un ratn" ifFalse: [ ^(self dondeEstoy) ] "en cuyo caso devuelve el nodo actual" ifTrue: [ vec do: [:nodo| "para cada vecino evala:" valor _ 10. "valor inicial del nodo" habitantes _ (nodo habitan)asArray. "los habitantes del nodo vecino" "si hay un ratn cerca se lanza sobre l" habitantes do: [:alguien| ((alguien)class == RatonMorph) ifTrue: [ valor _ (valor - 10)] ]. "Asigna valores segn los rastros" "Se acerca a los rastros de ratn" ( ((nodo)olor: #bicho)class == RatonMorph ) ifTrue: [ ( ((nodo)olor: #olor) = 'caliente' ) ifTrue: [valor _ (valor - 9)]. ( ((nodo)olor: #olor) = 'tibio' ) ifTrue: [valor _ (valor - 7)]. ( ((nodo)olor: #olor) = 'frio' ) ifTrue: [valor _ (valor - 5)]. ]. "arma el arreglo 'puntajes' con los valores asignados a cada nodo" puntajes addLast:valor. Transcript show: (puntajes asString). ]. "fin de: vec do" "Arma un array con los nodos de puntaje minimo y elige uno al azar" elegidos _ RunArray new. 1 to:(puntajes size) do: [:nodo| ((puntajes minimo) == (puntajes at:nodo)) ifTrue: [elegidos addLast:(vec at:nodo)] ]. ^(elegidos atRandom). ]. "fin de: si no elige el nodo actual" ]! !!GatoEstandarMorph methodsFor: 'private' stamp: 'rma 12/18/2000 22:54'!setVariables self color: Color black. super setVariables.! !"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!GatoEstandarMorph class instanceVariableNames: ''!!GatoEstandarMorph class methodsFor: 'instance creation' stamp: 'rma 12/14/2000 22:10'!new ^ super new setVariables! !GatoMorph subclass: #GatoGruperoMorph instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'LaberintoMorph'!!GatoGruperoMorph methodsFor: 'private' stamp: 'rma 12/18/2000 22:54'!setVariables self color: Color yellow. super setVariables.! !!GatoGruperoMorph methodsFor: 'accion' stamp: 'pa 11/23/2000 16:36'!estrategia"Devuelve el nodo al que le conviene ir segun una estrategia""El gato grupero sigue a los otros gatos" | puntajes vec temp valor habitantes elElegido elegidos | "Evaluar cada nodo vecino y le asignar puntajes a cada uno segn distntos criterios" puntajes _ RunArray new. ( ( vec _ (self dondeEstoyVecinos)asArray)isEmpty ) "obtiene los vecinos y los guarda en un array" ifTrue: [self error: 'Un nodo est aislado'] "si no hay vecinos enva un error" ifFalse: [ "Si hay un ratn en donde est se queda donde est" "Obtiene un array con los habitantes del nodo y se fija si hay un ratn" temp _ RunArray new. ((self dondeEstoy)habitan)asArray do: [:i| temp addLast:(i)class]. "arma un array con las clases solas(no los objetos)" ((temp indexOf:RatonMorph) == 0) "para poder identificar si hay un ratn" ifFalse: [ ^(self dondeEstoy) ] "en cuyo caso devuelve el nodo actual" ifTrue: [ vec do: [:nodo| "para cada vecino evala:" valor _ 100. "valor inicial del nodo" habitantes _ (nodo habitan)asArray. "los habitantes del nodo vecino" "por cada gato que hay en el nodo vecino resta un valor" "es decir, se acerca, por eso se llama 'grupero' " habitantes do: [:alguien| ( ((alguien)class == GatoPorteroMorph) or: [(alguien)class == GatoSolitarioMorph] ) ifTrue: [ valor _ (valor - 10)] ]. "si hay un ratn cerca se lanza sobre l" habitantes do: [:alguien| ((alguien)class == RatonMorph) ifTrue: [ valor _ (valor - 10)] ]. "Asigna valores segn los rastros" "Se acerca a los rastros de gato" ( (((nodo)olor: #bicho)class == GatoPorteroMorph) or: [ ((nodo)olor: #bicho)class == GatoSolitarioMorph ] ) ifTrue: [ ( ((nodo)olor: #olor) = 'caliente' ) ifTrue: [valor _ (valor - 8)]. ( ((nodo)olor: #olor) = 'tibio' ) ifTrue: [valor _ (valor - 6)]. ( ((nodo)olor: #olor) = 'frio' ) ifTrue: [valor _ (valor - 4)]. ]. "Pero se aleja de los rastros de gatos gruperos (para no seguir su propio rastro)" ( ((nodo)olor: #bicho)class == GatoPorteroMorph ) ifTrue: [ ( ((nodo)olor: #olor) = 'caliente' ) ifTrue: [valor _ (valor + 8)]. ( ((nodo)olor: #olor) = 'tibio' ) ifTrue: [valor _ (valor + 6)]. ( ((nodo)olor: #olor) = 'frio' ) ifTrue: [valor _ (valor + 4)]. ]. "Se acerca a los rastros de ratn" ( ((nodo)olor: #bicho)class == RatonMorph ) ifTrue: [ ( ((nodo)olor: #olor) = 'caliente' ) ifTrue: [valor _ (valor - 9)]. ( ((nodo)olor: #olor) = 'tibio' ) ifTrue: [valor _ (valor - 7)]. ( ((nodo)olor: #olor) = 'frio' ) ifTrue: [valor _ (valor - 5)]. ]. "arma el arreglo 'puntajes' con los valores asignados a cada nodo" puntajes addLast:valor. Transcript show: (puntajes asString). ]. "fin de: vec do" "Arma un array con los nodos de puntaje minimo y elige uno al azar" elegidos _ RunArray new. 1 to:(puntajes size) do: [:nodo| ((puntajes minimo) == (puntajes at:nodo)) ifTrue: [elegidos addLast:(vec at:nodo)] ]. ^(elegidos atRandom). ]. "fin de: si no elige el nodo actual" ]! !"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!GatoGruperoMorph class instanceVariableNames: ''!!GatoGruperoMorph class methodsFor: 'instance creation' stamp: 'rma 12/14/2000 22:11'!new ^ super new setVariables! !GatoMorph subclass: #GatoHechadoMorph instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'LaberintoMorph'!!GatoHechadoMorph methodsFor: 'accion' stamp: 'pa 11/23/2000 16:14'!estrategia"Devuelve el nodo al que le conviene ir segun una estrategia""El gato hechado no se mueve a menos que pase un gato al lado"| vec habitantes | ( ( vec _ (self dondeEstoyVecinos)asArray)isEmpty ) "obtiene los vecinos y los guarda en un array" ifTrue: [self error: 'Un nodo est aislado'] "si no hay vecinos enva un error" ifFalse: [ vec do: [:nodo| "para cada vecino evala:" habitantes _ (nodo habitan)asArray. "los habitantes del nodo vecino" "si hay un ratn cerca se lanza sobre l" habitantes do: [:alguien| ((alguien)class == RatonMorph) ifTrue: [ ^(nodo) ] ]. ]. "fin de: vec do:" ^(self dondeEstoy). "sino devuelve el nodo actual" ].! !!GatoHechadoMorph methodsFor: 'private' stamp: 'rma 12/18/2000 22:55'!setVariables self color: Color cyan. super setVariables.! !"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!GatoHechadoMorph class instanceVariableNames: ''!!GatoHechadoMorph class methodsFor: 'instance creation' stamp: 'rma 12/14/2000 22:11'!new ^ super new setVariables! !GatoMorph subclass: #GatoPorteroMorph instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'LaberintoMorph'!!GatoPorteroMorph methodsFor: 'accion' stamp: 'pa 11/23/2000 16:37'!estrategia"Devuelve el nodo al que le conviene ir segun una estrategia""El gato portero busca una puerta y se queda esperando all, persigue al ratn si lo huele o ve durante el paseo inicial" | puntajes vec temp valor habitantes elElegido elegidos | "Evaluar cada nodo vecino y le asignar puntajes a cada uno segn distntos criterios" puntajes _ RunArray new. ( ( vec _ (self dondeEstoyVecinos)asArray)isEmpty ) "obtiene los vecinos y los guarda en un array" ifTrue: [self error: 'Un nodo est aislado'] "si no hay vecinos enva un error" ifFalse: [ "Si hay un ratn en donde est se queda donde est" "Obtiene un array con los habitantes del nodo y se fija si hay un ratn" temp _ RunArray new. ((self dondeEstoy)habitan)asArray do: [:i| temp addLast:(i)class]. "arma un array con las clases solas(no los objetos)" ((temp indexOf:RatonMorph) == 0) "para poder identificar si hay un ratn" ifFalse: [ ^(self dondeEstoy) ] "en cuyo caso devuelve el nodo actual" ifTrue: [ vec do: [:nodo| "para cada vecino evala:" valor _ 10. "valor inicial del nodo" "si un vecino es una salida, va sin dudarlo" ((nodo)class == PuertaMorph ) ifTrue: [ ^nodo ]. habitantes _ (nodo habitan)asArray. "los habitantes del nodo vecino" "si hay un ratn cerca se lanza sobre l" habitantes do: [:alguien| ((alguien)class == RatonMorph) ifTrue: [ valor _ (valor - 10)] ]. "Asigna valores segn los rastros" "Se aleja de los rastros de gatos porteros" (((nodo)olor: #bicho)class == GatoPorteroMorph) ifTrue: [ ( ((nodo)olor: #olor) = 'caliente' ) ifTrue: [valor _ (valor + 6)]. ( ((nodo)olor: #olor) = 'tibio' ) ifTrue: [valor _ (valor + 4)]. ( ((nodo)olor: #olor) = 'frio' ) ifTrue: [valor _ (valor + 2)]. ]. "Se acerca a los rastros de ratn" ( ((nodo)olor: #bicho)class == RatonMorph ) ifTrue: [ ( ((nodo)olor: #olor) = 'caliente' ) ifTrue: [valor _ (valor - 9)]. ( ((nodo)olor: #olor) = 'tibio' ) ifTrue: [valor _ (valor - 7)]. ( ((nodo)olor: #olor) = 'frio' ) ifTrue: [valor _ (valor - 5)]. ]. "arma el arreglo 'puntajes' con los valores asignados a cada nodo" puntajes addLast:valor. Transcript show: (puntajes asString). ]. "fin de: vec do" "Arma un array con los nodos de puntaje minimo y elige uno al azar" elegidos _ RunArray new. 1 to:(puntajes size) do: [:nodo| ((puntajes minimo) == (puntajes at:nodo)) ifTrue: [elegidos addLast:(vec at:nodo)] ]. ^(elegidos atRandom). ]. "fin de: si no elige el nodo actual" ]! !!GatoPorteroMorph methodsFor: 'private' stamp: 'rma 12/14/2000 22:16'!setVariables self color: Color green. super setVariables.! !"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!GatoPorteroMorph class instanceVariableNames: ''!!GatoPorteroMorph class methodsFor: 'instance creation' stamp: 'rma 12/14/2000 22:11'!new ^ super new setVariables! !GatoMorph subclass: #GatoSolitarioMorph instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'LaberintoMorph'!!GatoSolitarioMorph methodsFor: 'private' stamp: 'rma 12/18/2000 22:51'!setVariables self color: Color blue. super setVariables.! !!GatoSolitarioMorph methodsFor: 'accion' stamp: 'pa 11/23/2000 16:38'!estrategia"Devuelve el nodo al que le conviene ir segun una estrategia""El gato solitario se aleja de los otros gatos y de sus huellas y busca activamente al ratn" | puntajes vec temp valor habitantes elElegido elegidos | "Evaluar cada nodo vecino y le asignar puntajes a cada uno segn distntos criterios" puntajes _ RunArray new. ( ( vec _ (self dondeEstoyVecinos)asArray)isEmpty ) "obtiene los vecinos y los guarda en un array" ifTrue: [self error: 'Un nodo est aislado'] "si no hay vecinos enva un error" ifFalse: [ "Si hay un ratn en donde est se queda donde est" "Obtiene un array con los habitantes del nodo y se fija si hay un ratn" temp _ RunArray new. ((self dondeEstoy)habitan)asArray do: [:i| temp addLast:(i)class]. "arma un array con las clases solas(no los objetos)" ((temp indexOf:RatonMorph) == 0) "para poder identificar si hay un ratn" ifFalse: [ ^(self dondeEstoy) ] "en cuyo caso devuelve el nodo actual" ifTrue: [ vec do: [:nodo| "para cada vecino evala:" valor _ 10. "valor inicial del nodo" habitantes _ (nodo habitan)asArray. "los habitantes del nodo vecino" "por cada gato que hay en el nodo vecino suma un valor" "es decir, se aleja, por eso se llama 'solitario' " habitantes do: [:alguien| ( ((alguien)class == GatoPorteroMorph) or: [(alguien)class == GatoSolitarioMorph] ) ifTrue: [ valor _ (valor + 10)] ]. "si hay un ratn cerca se lanza sobre l" habitantes do: [:alguien| ((alguien)class == RatonMorph) ifTrue: [ valor _ (valor - 10)] ]. "Asigna valores segn los rastros" "Se aleja de los rastros de gato" ( (((nodo)olor: #bicho)class == GatoPorteroMorph) or: [ ((nodo)olor: #bicho)class == GatoSolitarioMorph ] ) ifTrue: [ ( ((nodo)olor: #olor) = 'caliente' ) ifTrue: [valor _ (valor + 8)]. ( ((nodo)olor: #olor) = 'tibio' ) ifTrue: [valor _ (valor + 6)]. ( ((nodo)olor: #olor) = 'frio' ) ifTrue: [valor _ (valor + 4)]. ]. "Se acerca a los rastros de ratn" ( ((nodo)olor: #bicho)class == RatonMorph ) ifTrue: [ ( ((nodo)olor: #olor) = 'caliente' ) ifTrue: [valor _ (valor - 9)]. ( ((nodo)olor: #olor) = 'tibio' ) ifTrue: [valor _ (valor - 7)]. ( ((nodo)olor: #olor) = 'frio' ) ifTrue: [valor _ (valor - 5)]. ]. "arma el arreglo 'puntajes' con los valores asignados a cada nodo" puntajes addLast:valor. Transcript show: (puntajes asString). ]. "fin de: vec do" "Arma un array con los nodos de puntaje minimo y elige uno al azar" elegidos _ RunArray new. 1 to:(puntajes size) do: [:nodo| ((puntajes minimo) == (puntajes at:nodo)) ifTrue: [elegidos addLast:(vec at:nodo)] ]. ^(elegidos atRandom). ]. "fin de: si no elige el nodo actual" ]! !"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!GatoSolitarioMorph class instanceVariableNames: ''!!GatoSolitarioMorph class methodsFor: 'instance creation' stamp: 'rma 12/14/2000 22:12'!new ^ super new setVariables! !EllipseMorph subclass: #NodoMorph instanceVariableNames: 'habita vecinos olor ' classVariableNames: '' poolDictionaries: '' category: 'LaberintoMorph'!!NodoMorph commentStamp: '<historical>' prior: 0!Vecinos deberia ser un diccionario que contenga para un vecino una arista!!NodoMorph methodsFor: 'private' stamp: 'rma 11/8/2000 14:14'!setVariables habita _ Dictionary new. olor _ Dictionary new. (olor) at:#bicho put: nil. (olor) at:#olor put: 'helado'. vecinos _ Set new. self extent: 40 @ 40. self color: Color white. self borderWidth: 2.1. self borderColor: (Color r: 0.0 g: 0.599 b: 1.0) ! !!NodoMorph methodsFor: 'private' stamp: 'rma 10/5/2000 15:25'!vecinos: aSet "Asignacion un cjto de vecinos al nodo" vecinos add: aSet! !!NodoMorph methodsFor: 'modificadores' stamp: 'rma 10/8/2000 00:31'!aristas: Algo "" aristas add: Algo! !!NodoMorph methodsFor: 'modificadores' stamp: 'rma 11/11/2000 18:08'!bichoAgregar: unBicho "Llega un bicho al nodo" | unUbicacion | "Olor y sus hermosas propiedades visuales" self hayOlorA: unBicho cuanto: 'helado'. unUbicacion _ (self ubicaA). (self habitan) at:unUbicacion put:unBicho. " self addMorph: unBicho."! !!NodoMorph methodsFor: 'modificadores' stamp: 'rma 11/11/2000 18:08'!bichoQuitar: unBicho | cjto loQuito | "Olor y sus hermosas propiedades visuales" (self habitanCuantos = 1) ifTrue:[self hayOlorA: unBicho cuanto: 'caliente']. "Quita unBicho de habita" loQuito _( (self habitan) keyAtValue: unBicho). self habitan removeKey: loQuito. cjto _ Set new. cjto add: unBicho. "self removeAllMorphsIn: cjto." "Actualizacion del Nodo" self bichoActualizarNodo. ! !!NodoMorph methodsFor: 'modificadores' stamp: 'rma 11/4/2000 01:19'!habita: Algo "Un bicho se instala en el nodo" olor add: Algo ! !!NodoMorph methodsFor: 'modificadores' stamp: 'rma 11/6/2000 14:05'!hayOlorA: unBicho cuanto: cantidad"Cambia el olor en un nodo." (cantidad = 'helado') ifTrue:[self color: Color white. self olorA: unBicho cantidad: 'helado'. ] ifFalse:[ (cantidad = 'caliente') ifTrue:[self color: (unBicho bichoOlor: 'caliente'). self olorA: unBicho cantidad: 'caliente'. ]. (cantidad = 'tibio') ifTrue:[self color: (unBicho bichoOlor: 'tibio'). self olorA: unBicho cantidad: 'tibio'. ]. (cantidad = 'frio') ifTrue:[self color: ( unBicho bichoOlor: 'frio'). self olorA: unBicho cantidad: 'frio'.]. ]. ! !!NodoMorph methodsFor: 'modificadores' stamp: 'rma 10/15/2000 00:55'!noHabita: algo "Quita Algo de habita, habria que agregar el ifAbsent" habita removeKey:algo "ifAbsent: "! !!NodoMorph methodsFor: 'modificadores' stamp: 'pa 10/28/2000 17:58'!nuevoVecino: unVecino conectadoPor: unArista "Reubicamos la arista graficamente" unArista verticeA:(unVecino center). "Informacion para la arista" unArista verticeB: self center. "Informacion para la arista" "Se le dice a self quien es su Vecino y viceversa" self vecinos: unVecino. "Agraga el vecino a self". unVecino vecinos: self. "Agrega self al vecino". "La arista debe estar siempre atras del nodo" unArista goBehind! !!NodoMorph methodsFor: 'modificadores' stamp: 'rma 11/4/2000 01:23'!olorA: unBicho cantidad: cuanto "Un un olor se instala en el nodo" (olor) at:#bicho put: unBicho. (olor) at:#olor put: cuanto. ! !!NodoMorph methodsFor: 'observadores' stamp: 'rma 10/15/2000 01:09'!enPosicion: unNumero "Devuelve el bicho en la posicion unNumero" ^(self habitan at: unNumero)! !!NodoMorph methodsFor: 'observadores' stamp: 'rma 12/14/2000 21:54'!fin| g r resultado |"Hay un gato y un raton en habita?" g _ false. r _ false. 1 to: (((self habitan) size) ) do:[ :index | ((( self habitan at: index) class ) = GatoMorph ) ifTrue:[g _true]. ((( self habitan at: index) class ) = GatoEstandarMorph ) ifTrue:[g _true]. ((( self habitan at: index) class ) = GatoGruperoMorph ) ifTrue:[g _true]. ((( self habitan at: index) class ) = GatoHechadoMorph ) ifTrue:[g _true]. ((( self habitan at: index) class ) = GatoPorteroMorph ) ifTrue:[g _true]. ((( self habitan at: index) class ) = GatoSolitarioMorph ) ifTrue:[g _true]. ((( self habitan at: index) class) = RatonMorph ) ifTrue:[r _true] ].((g = true) and:[ r = true]) ifTrue:[resultado _ true ] ifFalse:[resultado _ false]. ^resultado. ! !!NodoMorph methodsFor: 'observadores' stamp: 'rma 10/5/2000 10:16'!habita ^ habita! !!NodoMorph methodsFor: 'observadores' stamp: 'rma 10/14/2000 23:55'!habitan "Diccionario con bichos de un nodo" ^habita! !!NodoMorph methodsFor: 'observadores' stamp: 'rma 11/1/2000 16:37'!habitanCuantos "Diccionario con bichos de un nodo" ^((self habitan) size)! !!NodoMorph methodsFor: 'observadores' stamp: 'rma 11/4/2000 01:27'!olor "Devuelve el diccionario con bichos de un nodo" ^(olor). ! !!NodoMorph methodsFor: 'observadores' stamp: 'rma 11/4/2000 01:48'!olor: llave "Diccionario con bichos de un nodo" ^(olor at: llave)! !!NodoMorph methodsFor: 'observadores' stamp: 'rma 10/15/2000 00:54'!posicionEsta: unNumero "Esta una posicion ocupada" ^((self posiciones) includes: unNumero)! !!NodoMorph methodsFor: 'observadores' stamp: 'rma 10/15/2000 00:28'!posiciones "Lista de posiciones ocupadas" ^self habitan keys! !!NodoMorph methodsFor: 'observadores' stamp: 'rma 10/5/2000 10:26'!queSos "Devuelve la clase del objeto que es" self basicType! !!NodoMorph methodsFor: 'observadores' stamp: 'rma 10/5/2000 10:17'!vecinos ^ vecinos asArray! !!NodoMorph methodsFor: 'propieades visuales' stamp: 'rma 10/30/2000 16:23'!bichoActualizarNodo | elem | elem _ ((self habitan) values) asArray. elem do: [:element | self bichoQuitar: element]. elem do: [:element | element vaA: self]. ! !!NodoMorph methodsFor: 'propieades visuales' stamp: 'rma 10/15/2000 01:00'!encontrarUbicacion | encontro numero | "Dado un nodo devuelve en que ubicacion del nodo debe ir el bicho" encontro _ false. numero _ 0. [encontro & (numero < 15)] whileFalse: [ (self posicionEsta: numero) ifTrue:[numero _ (numero+1) ] ifFalse:[encontro _ true] ]. ^numero! !!NodoMorph methodsFor: 'propieades visuales' stamp: 'rma 10/30/2000 16:52'!ubicaA | encontro numero | "Dado un nodo devuelve en que ubicacion del nodo debe ir el bicho" encontro _ false. numero _ 1. [encontro] whileFalse: [ (self posicionEsta: numero) ifTrue:[numero _ (numero + 1)] ifFalse:[encontro _ true] ]. ^numero! !!NodoMorph methodsFor: 'propieades visuales' stamp: 'rma 10/30/2000 19:28'!ubicaA: unBicho posicion: unLugar "Dado un bicho y un nodo devuelve una ubicacion grafica" |numero resultado | numero _ unLugar rem: 10. (numero == 1) ifTrue:[resultado _ self center
.] . "El bicho se ubica en el centro" (numero == 2 ) ifTrue:[resultado _ self center + (( unBicho width - 2)@( (unBicho height -2) * (-1) )) ]."derecha arriba" (numero == 3) ifTrue:[ resultado _ self center + ((unBicho width - 2 )@(unBicho height -2 )) ]. "derecha abajo" (numero == 4) ifTrue:[ resultado _ self center + (( ( unBicho width - 2) * (-1) )@( unBicho height -2 )) ]. "izquierda abajo" (numero == 5) ifTrue:[ resultado _ self center - ((unBicho width - 2 )@(unBicho height -2 )) ]. "izquierda arriba" (numero == 6) ifTrue:[resultado _ self center - (0@(unBicho height + 1)) ]. "arriba al centro" (numero == 7) ifTrue:[ resultado _ self center + ((unBicho width + 2)@(0))]. (numero == 8) ifTrue:[resultado _ self center + (0@( unBicho height + 1)) ]. "derecha al centro" (numero == 9) ifTrue:[resultado _ self center - (( unBicho width + 2)@(0)) ]. ^resultado.! !!NodoMorph methodsFor: 'acciones' stamp: 'rma 11/4/2000 16:57'!actualizarOlor | olorAntes unBicho | "Actualiza el olor de un nodo" olorAntes _ (self olor: #olor). unBicho _ (self olor: #bicho). (olorAntes = 'caliente') ifTrue:[ self hayOlorA: unBicho cuanto: 'tibio']. (olorAntes = 'tibio') ifTrue:[self hayOlorA: unBicho cuanto: 'frio']. (olorAntes = 'frio') ifTrue:[self hayOlorA: unBicho cuanto: 'helado']. ! !!NodoMorph methodsFor: 'acciones' stamp: 'rma 11/4/2000 02:10'!actuar"Cuando el objeto entra en escena" "Termino el juego?" "Actualizacion del olor"! !"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!NodoMorph class instanceVariableNames: ''!!NodoMorph class methodsFor: 'instance creation' stamp: 'rma 10/5/2000 11:05'!new ^ super new setVariables! !NodoMorph subclass: #PuertaMorph instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'LaberintoMorph'!!PuertaMorph methodsFor: 'observador' stamp: 'rma 11/15/2000 19:48'!hayRaton | torf | "Se fija si hay un raton en la puerta" torf _ false . (self habita values) do:[ :thebicho | torf _ (thebicho class = RatonMorph) or:[torf] ] . ^torf. ! !!PuertaMorph methodsFor: 'private' stamp: 'rma 11/4/2000 01:47'!setVariables super setVariables. self borderColor: (Color r: 1.0 g: 0.599 b: 0.4). ! !BichoMorph subclass: #RatonMorph instanceVariableNames: 'nombre ' classVariableNames: '' poolDictionaries: '' category: 'LaberintoMorph'!!RatonMorph methodsFor: 'observadores' stamp: 'rma 11/4/2000 17:11'!bichoOlor: cantidad| colores | (cantidad = 'caliente') ifTrue:[colores _ (Color r: 0 g: 0.8 b: 0.4) ]. (cantidad = 'tibio') ifTrue:[colores _(Color r: 0.0 g: 1 b: 0)]. (cantidad = 'frio') ifTrue:[colores _ (Color r: 0.4 g: 1.0 b: 0.7)]. ^colores.! !!RatonMorph methodsFor: 'private' stamp: 'rma 12/18/2000 22:51'!setVariables self openInWorld. self extent: 10 @ 10. self color: Color red. self borderColor: Color red. self borderWidth: 2. ! !!RatonMorph methodsFor: 'accion' stamp: 'rma 12/18/2000 23:00'!estrategia "Devuelve el nodo al que le conviene ir segun una estrategia" | vec puntajes habitantes valor elegidos | "Evaluar cada nodo vecino y le asignar puntajes a cada uno segn distntos criterios" puntajes _ RunArray new. ( ( vec _ (self dondeEstoyVecinos)asArray)isEmpty ) "obtiene los vecinos y los guarda en un array" ifTrue: [self error: 'Un nodo est aislado'] "si no hay vecinos enva un error" ifFalse: [ ((self dondeEstoy)class == PuertaMorph) ifTrue: [ ^(self dondeEstoy) ] "Si est en una puerta la elige" ifFalse: [ "sino..." 1 to: (vec size) do: [:nodo| "para cada vecino evala:" valor _ 100. "valor inicial del nodo" "si un vecino es una salida, resta un valor" ((vec at:nodo)class == PuertaMorph ) ifTrue: [ valor _ (valor - 10)]. habitantes _ ((vec at:nodo)habitan)asArray. "los habitantes del nodo vecino" "por cada gato que hay en el nodo vecino suma un valor" 1 to: (habitantes size) do: [:alguien| ((habitantes at:alguien)class == GatoMorph) ifTrue: [ valor _ (valor + 20)] ]. "Asigna valores segn los rastros" ( ((vec at:nodo)olor: #bicho)class == GatoMorph ) ifTrue: [ ( ((vec at:nodo)olor: #olor) = 'caliente' ) ifTrue: [valor _ (valor + 8)]. ( ((vec at:nodo)olor: #olor) = 'tibio' ) ifTrue: [valor _ (valor + 5)]. ( ((vec at:nodo)olor: #olor) = 'frio' ) ifTrue: [valor _ (valor + 3)]. ]. ( ((vec at:nodo)olor: #bicho)class == RatonMorph ) ifTrue: [ ( ((vec at:nodo)olor: #olor) = 'caliente' ) ifTrue: [valor _ (valor + 7)]. ( ((vec at:nodo)olor: #olor) = 'tibio' ) ifTrue: [valor _ (valor + 4)]. ( ((vec at:nodo)olor: #olor) = 'frio' ) ifTrue: [valor _ (valor + 2)]. ]. "arma el arreglo 'puntajes' con los valores asignados a cada nodo" puntajes addLast:valor. Transcript show: (puntajes asString). ]. "Arma un array con los nodos de puntaje minimo y elige uno al azar" elegidos _ RunArray new. 1 to:(puntajes size) do: [:nodo| ((puntajes minimo) == (puntajes at:nodo)) ifTrue: [elegidos addLast:(vec at:nodo)] ]. ^(elegidos atRandom). ]. ]! !"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!RatonMorph class instanceVariableNames: ''!!RatonMorph class methodsFor: 'instance creation' stamp: 'rma 10/19/2000 17:27'!new ^ super new setVariables! !SystemWindow subclass: #TableroMorph instanceVariableNames: 'tipoTablero nodos puertas bichos pausa ' classVariableNames: '' poolDictionaries: '' category: 'LaberintoMorph'!!TableroMorph methodsFor: 'observadores' stamp: 'rma 10/15/2000 03:59'!NodoNro: unNumero "Devuelve el nodo unNumero" ! !!TableroMorph methodsFor: 'observadores' stamp: 'rma 10/17/2000 18:31'!cantidadNodos "Devuelve la cantidad de nodos" ^nodos size.! !!TableroMorph methodsFor: 'observadores' stamp: 'pa 10/15/2000 03:47'!cantidadPuertas "Devuelve la cantidad de puertas" ^ puertas size.! !!TableroMorph methodsFor: 'initialization' stamp: 'pa 12/24/2000 20:42'!comenzar "Lee archivo de configuracion para armar el juego" | file cantNodos templine arista raton gato gatoTemp tipoGato | file _ FileStream fileNamed: 'Laberinto.txt'. file==nil ifTrue: [ self error: 'Error al leer el archivo' ]. "Lee la cantidad de nodos" file skipTo: $:. cantNodos _ (file upTo: $.)asNumber . "Le da un tamao al tablero" ( (cantNodos sqrt) - (cantNodos sqrt truncated) = 0) ifTrue: [ self tipo: ((cantNodos sqrt) truncated)] ifFalse: [ self tipo: (((cantNodos sqrt) truncated) + 1) ]. "Lee cuales son las puertas" file skipTo: $:. puertas _ RunArray new. "Para guardar la ubicacion de las puertas" "Guarda en un stream temporal la lnea de las puertas para leerla en «puertas« " templine _ ReadStream on: (file upTo: $.). [templine atEnd] whileFalse: [puertas addLast: (templine upTo: $,)asNumber]. "Crea los nodos (y las puertas)" self crearNodos: cantNodos. "Arma los vrtices" file skipTo: $:. templine _ ReadStream on: (file upTo: $.). "Guarda la lnea de los vrtices" [templine atEnd] whileFalse: [ arista _ AristaMorph new. "Crea una arista" self agregarArista:arista. "y la agrega al tablero" templine skipTo: $(. "la linea que sigue crea las vecindades y esta muy buena" (nodos at:(templine upTo: $,)asNumber) nuevoVecino: (nodos at:(templine upTo: $) )asNumber) conectadoPor: arista. "<----- primer nodo ---------------------> <----- segundo nodo -----------------------> " ]. "Crea al ratn y lo ubica en el tablero" raton _ RatonMorph new. file skipTo: $:. raton vaA: ( nodos at:((file upTo: $.)asNumber) ). self crearBicho: raton. "Crea a los gatos y los ubica en el tablero" file skipTo: $:. templine _ ReadStream on: (file upTo: $.). "Guarda la lnea de los gatos" "Transcript show: (templine skipTo: $()asString." [templine atEnd] whileFalse: [ gatoTemp _ RunArray new. "arreglo donde guarda los datos del futuro gato" templine skipTo: $(. gatoTemp addLast: ( templine upTo: $, )asNumber. "guarda el nmero" gatoTemp addLast: ( templine upTo: $, )asNumber. "y la posicin" "ahora se crea el gato segn su tipo" tipoGato _ ( templine upTo: $) )asNumber. (tipoGato == 1 ) ifTrue: [ gato _ GatoEstandarMorph new ]. (tipoGato == 2 ) ifTrue: [ gato _ GatoSolitarioMorph new ]. (tipoGato == 3 ) ifTrue: [ gato _ GatoPorteroMorph new ]. (tipoGato == 4 ) ifTrue: [ gato _ GatoGruperoMorph new ]. (tipoGato == 5 ) ifTrue: [ gato _ GatoHechadoMorph new ]. "una vez creado el gato le asigna sus variables" gato numero: (gatoTemp at:1). gato vaA: (nodos at: (gatoTemp at:2)). self crearBicho: gato. ].! !!TableroMorph methodsFor: 'initialization' stamp: 'pa 11/4/2000 01:10'!crearNodos: cantNodos "Crea los nodos (y las puertas)" | index | index _ 1. "Indice del array 'puertas« " 1 to: cantNodos do: [:i| ( i == (puertas at:index) ) "Si el indice «i« es igual al nro almacenado en el array:" ifTrue: [nodos addLast: PuertaMorph new. index _ index +1] "crear puerta" ifFalse: [nodos addLast: NodoMorph new]. "else -> nodo" self dibujarNodo: (nodos at:i) posicion:i. ].! !!TableroMorph methodsFor: 'private' stamp: 'rma 10/17/2000 18:55'!NodosInsertados "Nro. de Nodos dentro de la ventana" ! !!TableroMorph methodsFor: 'private' stamp: 'rma 11/23/2000 00:36'!buildWindowMenu | aMenu | aMenu _ MenuMorph new defaultTarget: self. aMenu add: 'Enviar hacia atras' action: #sendToBack. aMenu addLine. aMenu add: 'Comenzar' action: #menuActuar. aMenu addLine. aMenu add: 'Referencias' action: #menuReferencias. aMenu add: 'Acerca de...' action: #menuAcerca." aMenu add: 'full screen' action: #fullScreen." ^aMenu ! !!TableroMorph methodsFor: 'private' stamp: 'rma 11/23/2000 00:36'!menuAcerca| ref | ref _ VentanasAdicionales new. ref acercaDe. ref center: self center. ref openInWorld.! !!TableroMorph methodsFor: 'private' stamp: 'rma 11/23/2000 00:36'!menuActuar self actuar.! !!TableroMorph methodsFor: 'private' stamp: 'rma 11/23/2000 00:36'!menuReferencias| ref | ref _ VentanasAdicionales new. ref referencias. ref center: self center. ref left: self right + 10. ref openInWorld.! !!TableroMorph methodsFor: 'private' stamp: 'rma 10/19/2000 17:24'!openInWorld: aWorld "This msg and its callees result in the window being activeOnlyOnTop" "self bounds: (RealEstateAgent initialFrameFor: self)." aWorld addMorph: self. self activate. aWorld startSteppingSubmorphsOf: self! !!TableroMorph methodsFor: 'private' stamp: 'rma 10/17/2000 17:33'!setStripeColorsFrom: paneColor self isActive ifFalse: [stripes second color: Color cyan ; borderColor: Color cyan . stripes first color: Color cyan ; borderColor: Color cyan] ifTrue: [ stripes second color: Color white ; borderColor: Color white . stripes first color: Color white ; borderColor: Color white].! !!TableroMorph methodsFor: 'private' stamp: 'rma 11/11/2000 19:59'!setVariables nodos _ RunArray new. puertas _ RunArray new. bichos _ RunArray new. pausa _ false. tipoTablero _ 0. "Propiedades Graficas de la ventana" collapseBox hide. "En vez usar esto se podria hacer: un submorhps hide y luego show" self tipo: 0. self color: (Color r: 0.0 g: 0.8 b: 0.8). self setLabel: 'Raton y Gatos'. self comenzar.! !!TableroMorph methodsFor: 'rezize' stamp: 'rma 10/18/2000 15:47'!collapse! !!TableroMorph methodsFor: 'rezize' stamp: 'rma 10/18/2000 15:48'!collapseOrExpand! !!TableroMorph methodsFor: 'rezize' stamp: 'rma 10/18/2000 15:48'!collapsedFrame! !!TableroMorph methodsFor: 'rezize' stamp: 'rma 10/18/2000 15:53'!spawnPaneFrameHandle: event ! !!TableroMorph methodsFor: 'rezize' stamp: 'rma 10/18/2000 15:54'!spawnReframeHandle: event! !!TableroMorph methodsFor: 'tablero' stamp: 'rma 10/18/2000 17:34'!cantMaxNodos "Cantidad maxima de nodos" ^tipoTablero squared! !!TableroMorph methodsFor: 'tablero' stamp: 'pa 10/28/2000 17:47'!nodos "Cantidad de nodos en el tablero" ^ nodos size! !!TableroMorph methodsFor: 'tablero' stamp: 'rma 11/14/2000 03:32'!pausa "Esta en pausa la simulacion" ^pausa! !!TableroMorph methodsFor: 'tablero' stamp: 'rma 11/15/2000 20:35'!pausa: aBool "Cambia el estado de pausa de la simulacion" pausa _ aBool.! !!TableroMorph methodsFor: 'tablero' stamp: 'rma 10/17/2000 19:06'!tipo "Devuelve el tipo de tablero: son diez. cada tipo tiene un numero maximo de nodos asociados. para saber eso se hace: nro. de tipo = nro. tipo * nro. de tipo" ^tipoTablero ! !!TableroMorph methodsFor: 'tablero' stamp: 'rma 10/19/2000 16:04'!tipo: unTipo "Define el tipo de tablero" (unTipo >= 0) & (unTipo < 11 ) ifTrue:[ tipoTablero _ unTipo] ifFalse:[self error:' Numero de tablero erroneo ']. "Se Define tamanio grafico" "(unTipo == 0) ifTrue:[self extent:420@19]. " (unTipo == 1) ifTrue:[self extent:62@72]. (unTipo == 2) ifTrue:[self extent: 136@146]. (unTipo == 3) ifTrue:[self extent: 210@220]. (unTipo == 4) ifTrue:[self extent: 284@294 ]. (unTipo == 5) ifTrue:[self extent: 358@368]. (unTipo == 6) ifTrue:[self extent: 432@442]. (unTipo == 7) ifTrue:[self extent: 506@516]. (unTipo == 8) ifTrue:[self extent: 580@590]. (unTipo == 9) ifTrue:[self extent: 654@663]. (unTipo == 10) ifTrue:[self extent: 728@738]. ! !!TableroMorph methodsFor: 'propiedades visuales' stamp: 'rma 11/14/2000 03:42'!startStepping | booleana | booleana _ true. (self bichos) do:[ :uno | booleana _ ((uno estaEnMovimiento) not) and:[booleana] ]. (booleana and:[((self pausa) not)]) ifFalse:[ "(pausa) ifFalse:[(Delay forSeconds: ((BichoMorph stepTime) * 2) ). self startStepping] ifTrue:[Mostrar cuadro: PAUSA]"] ifTrue:[super startStepping].! !!TableroMorph methodsFor: 'propiedades visuales' stamp: 'rma 12/17/2000 23:26'!step | ratonGana gatoGana todosBichos unBicho | pausa ifTrue:[] ifFalse:[ "Llego un raton a una puerta?" ratonGana _ false. (self lasPuertas) do:[ :uno | ratonGana _ (ratonGana ) or:[(uno hayRaton) ] ]. gatoGana _ false. (self losNodos) do:[ :uno | gatoGana _ ((gatoGana) or:[(uno fin)]) ]. "Termino el juego?" ( gatoGana) ifTrue:[ self pausa: true. ( ( ( ( VentanasAdicionales new) ganaGato) center: self center) ) openInWorld. ]. ( ratonGana) ifTrue:[ self pausa: true. ( ( ( ( VentanasAdicionales new) ganaRaton) center: self center)) openInWorld. ]. (gatoGana or:[ratonGana] ) ifFalse: [ "Se actualiza el olor" (self losNodos) do:[ :uno | uno actualizarOlor]. "Se mueven los bichos " "((self bichos) reversed) do:[ :uno | uno actuar]." todosBichos _ (self bichos)asSet. "La inicitiva para actuar entre el grupo de bichos es al azar, es decir mientras mas gatos haya menos iniciativa tiene el raton, por la tanto mas se ve favorecido... ver documentacion" [(todosBichos size) == 0] whileFalse:[ unBicho _ (todosBichos asArray) atRandom. (todosBichos remove: unBicho) actuar. ]. ] ].! !!TableroMorph methodsFor: 'propiedades visuales' stamp: 'rma 12/15/2000 15:34'!stepTime ^((BichoMorph stepTime) + 200)! !!TableroMorph methodsFor: 'nodos aristas y bichos' stamp: 'rma 10/27/2000 16:25'!agregarArista: unArista self addMorph: unArista! !!TableroMorph methodsFor: 'nodos aristas y bichos' stamp: 'rma 11/4/2000 03:09'!bichos "Bichos del tablero" ^(bichos asArray)! !!TableroMorph methodsFor: 'nodos aristas y bichos' stamp: 'rma 11/11/2000 19:06'!crearBicho: unBicho"Agrega un bicho al tablero" bichos addLast: unBicho. self addMorph: unBicho.! !!TableroMorph methodsFor: 'nodos aristas y bichos' stamp: 'rma 10/18/2000 18:39'!dibujarNodo: unNodo posicion: unNumero "Dibuja un nodo en la ventana" "Primero se lo ubica dentro de la ventana" |nro fila columna cuentas indice| ((unNumero > 0) and: [ unNumero <= (self cantMaxNodos) ] ) ifFalse:[ self error:'Numero fuera de rango']. nro _ (unNumero - 1). (nro == 0) ifTrue: [unNodo top: self top + 24. unNodo left: self left + 10] ifFalse:[ "Calculamos la columna" columna _ nro rem: (self tipo). "Calculamos la fila" cuentas _ (nro // self tipo) . indice _ 0. [ (indice <= self tipo ) and:[indice == cuentas] ] whileFalse:[indice _ indice + 1]. (indice ~~ cuentas) ifTrue:[ self error:'Error: si no fuera por la guarda... ']. fila _ cuentas. "Tenemos fila y columna: calculamos la posicion" unNodo top: (self top + 24) + (fila * 74). unNodo left: (self left + 10) +(columna * 74). ]. "Despues se regala el nodo a la ventana" self addMorph: unNodo.! !!TableroMorph methodsFor: 'nodos aristas y bichos' stamp: 'rma 11/18/2000 20:24'!lasPuertas | k | "Devuelve un array de puertas" k _ Set new . 1 to: (self puertas size) do:[ :i | k add: ((self losNodos) at: (self puertas at: i))]. ^(k asArray).! !!TableroMorph methodsFor: 'nodos aristas y bichos' stamp: 'rma 11/11/2000 19:10'!losNodos "Devuelve un array con los nodos del tablero" ^(nodos asArray)! !!TableroMorph methodsFor: 'nodos aristas y bichos' stamp: 'rma 11/11/2000 19:23'!puertas "Bichos del tablero" ^(puertas asArray).! !!TableroMorph methodsFor: 'acciones' stamp: 'rma 11/15/2000 20:55'!actuar (self pausa) ifFalse:[ self startStepping. [self actuar] fork].! !"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!TableroMorph class instanceVariableNames: ''!!TableroMorph class methodsFor: 'instance creation' stamp: 'pa 10/14/2000 19:59'!new ^ super new setVariables! !TableroMorph subclass: #VentanasAdicionales instanceVariableNames: '' classVariableNames: '' poolDictionaries: '' category: 'LaberintoMorph'!!VentanasAdicionales methodsFor: 'private' stamp: 'rma 11/21/2000 21:33'!buildWindowMenu | aMenu | aMenu _ MenuMorph new defaultTarget: self. aMenu add: 'Enviar hacia atras' action: #sendToBack. ^aMenu ! !!VentanasAdicionales methodsFor: 'private' stamp: 'rma 11/4/2000 17:42'!comenzar! !!VentanasAdicionales methodsFor: 'acercaDe' stamp: 'rma 11/23/2000 00:20'!acercaDe"Acerca de..." | m m1 m2 m3 m4 m5 m6 | self tipo: 10. self extent: 340@200. self color: (Color r: 0.972 g: 0.658 b: 0.035). self setLabel: 'Acerca de...'. m _ StringMorph contents: 'Universidad Nacional de Crdoba'. m font: ((TextStyle default fontOfSize: 22) ). m center: self center. m top: (self top + 30). m color: Color black. self addMorph: m. m1 _ StringMorph contents: 'Facultad de Matemtica Astronoma y Fsica'. m1 font: ((TextStyle default fontOfSize: 20) ). m1 center: self center. m1 top: (m bottom ). m1 color: Color black. self addMorph: m1. m2 _ StringMorph contents: 'Paradigmas de Programacin'. m2 font: ((TextStyle default fontOfSize: 22) ). m2 center: self center. m2 top: (m1 bottom + 5). m2 color: Color black. self addMorph: m2. m3 _ StringMorph contents: 'Allende Roberto'. m3 font: ((TextStyle default fontOfSize: 20) ). m3 center: self center. m3 top: (m2 bottom + 15). m3 color: Color black. self addMorph: m3. m4 _ StringMorph contents: 'rallende@hal.famaf.unc.edu.ar'. m4 font: ((TextStyle default fontOfSize: 12) ). m4 center: self center. m4 top: (m3 bottom ). m4 color: Color black. self addMorph: m4. m5 _ StringMorph contents: 'Ambrosio Pablo'. m5 font: ((TextStyle default fontOfSize: 20) ). m5 center: self center. m5 top: (m4 bottom + 15). m5 color: Color black. self addMorph: m5. m6 _ StringMorph contents: 'pambros@hal.famaf.unc.edu.ar'. m6 font: ((TextStyle default fontOfSize: 12) ). m6 center: self center. m6 top: (m5 bottom ). m6 color: Color black. self addMorph: m6.! !!VentanasAdicionales methodsFor: 'fin' stamp: 'rma 11/21/2000 22:09'!ganaGato "Gana Raton" | m m1 | self tipo: 10. self extent: 230@104. self setLabel: 'Fin'. m _ StringMorph contents: 'Fin de Simulacin'. m font: ((TextStyle default fontOfSize: 22) ). m center: self center. m top: (m top - 10). m color: Color black. self addMorph: m. m1 _ StringMorph contents: 'Un Gato Cazo al Raton'. m1 font: ((TextStyle default fontOfSize: 20) ). m1 center: self center. m1 top: (m bottom + 10). m1 color: Color black. self addMorph: m1. ! !!VentanasAdicionales methodsFor: 'fin' stamp: 'rma 11/21/2000 22:09'!ganaRaton "Gana Raton" | m m1 | self tipo: 10. self extent: 230@104. self setLabel: 'Fin'. m _ StringMorph contents: 'Fin de Simulacin'. m font: ((TextStyle default fontOfSize: 22) ). m center: self center. m top: (m top - 10). m color: Color black. self addMorph: m. m1 _ StringMorph contents: 'El Raton Ha Escapado'. m1 font: ((TextStyle default fontOfSize: 20) ). m1 center: self center. m1 top: (m bottom + 10). m1 color: Color black. self addMorph: m1.! !!VentanasAdicionales methodsFor: 'referencias' stamp: 'rma 12/18/2000 22:39'!referencias "Abre la ventana de referencias" |ref r1 r1s r2 r2s r3 r3s r4 r4s r4a r4b r4c r4d r4e r5 r5s r5a r5sa r4sa | "ref _ VentanasAdicionales new." ref _ self. ref setLabel: 'Referencias'. ref tipo: 10. ref extent: 170@300. r1 _ PuertaMorph new. ref dibujarNodo: r1 posicion:1. r1s _ StringMorph new. r1s contents: 'Una Puerta'. ref addMorph: r1s. r1s center: r1 center. r1s left: r1 right + 20. r2 _ NodoMorph new . ref addMorph: r1. ref addMorph: r2. r2 center: r1 center. r2 top: r1 bottom + 15. r2s _ StringMorph new . r2s contents: 'Un Nodo'. r2s center: r2 center. r2s left: r2 right + 20. ref addMorph: r2s. r3 _ AristaMorph new . ref addMorph: r3. r3 verticeA: r2 topLeft +10. r3 verticeB: r2 bottomRight -10. r3 top: r2 bottom + 22. r3s _ StringMorph new . r3s contents: 'Una Arista'. r3s center: r3 center. r3s left: r2 right + 20. ref addMorph: r3s. r4 _ NodoMorph new . ref addMorph: r4. r4 center: r3 center. r4 top: r3 bottom + 22. r4s _ StringMorph new . r4s contents: 'Un nodo con'. r4s center: r4 center. r4s left: r4 right + 20. r4s top: r4s top - 7. ref addMorph: r4s. r4sa _ StringMorph new . r4sa contents: 'diferentes gatos'. r4sa center: r4 center. r4sa left: r4 right + 20. r4sa top: r4sa top + 7. ref addMorph: r4sa. r4a _ GatoEstandarMorph new. r4a vaA: r4. ref addMorph: r4a. r4b _ GatoSolitarioMorph new. r4b vaA: r4. ref addMorph: r4b. r4c _ GatoPorteroMorph new. r4c vaA: r4. ref addMorph: r4c. r4d _ GatoGruperoMorph new. r4d vaA: r4. ref addMorph: r4d. r4e _ GatoHechadoMorph new. r4e vaA: r4. ref addMorph: r4e. r5 _ NodoMorph new . ref addMorph: r5. r5 center: r4 center. r5 top: r4 bottom + 22. r5a _ RatonMorph new. r5a vaA: r5. ref addMorph: r5a. r5s _ StringMorph new . r5s contents: 'Un Nodo con'. r5s center: r5 center. r5s left: r5 right + 20. r5s top: r5s top - 7. ref addMorph: r5s. r5sa _ StringMorph new . r5sa contents: 'un raton'. r5sa center: r5 center. r5sa left: r5 right + 20. r5sa top: r5sa top + 7. ref addMorph: r5sa. ! !