{TEG] Prueba final de protocolo

Lic. Edgar J. De Cleene edgardec2001 at yahoo.com.ar
Fri Apr 30 10:52:12 UTC 2004


Adjunto el .st probado con éxito en la UTN , bajo Windows 2000.
Funciona bien, hay que ver si todavía hay errores de juego.

-------------- next part --------------
Morph subclass: #DrawCard
	instanceVariableNames: 'nombre deQuienSoy numero '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Morphic-TEG'!

!DrawCard methodsFor: 'initialization'!
dibujaUnaCarta: t1 
	| t2 t3 t4 t5 |
	self numero: t1.
	t4 _ #('Soldado1.jpg' 'Canon.jpg' 'Caballo.jpg' ).
	t1 > 42
		ifTrue: [t3 _ self top + 5.
			t4
				do: [:t6 | 
					self
						addMorph: (DrawPicture new initializeWith: t6 escala: 0.7).
					self submorphs first center: self center.
					self submorphs first top: t3.
					t3 _ t3 + 40]]
		ifFalse: [t5 _ t1 \\\ 3 + 1.
			self
				addMorphBack: (DrawPicture new
						initializeWith: (t4 at: t5)
						valor: t1
						pos: self left + 20 @ self center y).
			t2 _ StringMorph contents: self nombre.
			t2 center: self center.
			t2 top: self top + 8.
			self addMorphBack: t2]! !

!DrawCard methodsFor: 'initialization'!
initialize
	super initialize.
	self setProperty: #dragEnabled toValue: true.
	self extent: 80 @ 120.
	self color: Color lightGray.
	self borderColor: Color black.
	self borderWidth: 2! !

!DrawCard methodsFor: 'initialization'!
initializeOff
	self addMorph: (Form fromFileNamed: 'TEGCarta.jpg') asMorph! !

!DrawCard methodsFor: 'initialization'!
nombre: t1 limites: t2 
	| t3 t4 t5 |
	nombre _ t1.
	ejEnPais _ 0.
	self
		vertices: t2 asArray
		color: Color white
		borderWidth: 2
		borderColor: Color black.
	t4 _ self center.
	t5 _ Morph new.
	t5
		bounds: (Rectangle
				left: t4 x
				right: t4 x + 15
				top: t4 y
				bottom: t4 y + 10).
	t5 color: Color white.
	self addMorph: t5.
	t3 _ TextMorph new.
	t3 autoFit: true.
	t3
		string: ejEnPais asString
		fontName: #ComicBold
		size: 18
		wrap: false.
	t3 contents: ejEnPais asString.
	t3 bounds: t5.
	t3 centered.
	self addMorph: t3.
	t3 lock! !


!DrawCard methodsFor: 'access'!
deQuienSoy
	^ deQuienSoy! !

!DrawCard methodsFor: 'access'!
deQuienSoy: t1 
	deQuienSoy _ t1! !

!DrawCard methodsFor: 'access'!
nombre
	^ nombre! !

!DrawCard methodsFor: 'access'!
nombre: t1 
	nombre _ t1! !

!DrawCard methodsFor: 'access'!
numero
	^ numero! !

!DrawCard methodsFor: 'access'!
numero: t1 
	numero _ t1! !


!DrawCard methodsFor: 'event handling'!
click: t1 
	^ self! !

!DrawCard methodsFor: 'event handling'!
doubleClick: t1 
	submorphs first
		ifNil: [^ 0].
	submorphs first delete.
	self dibujaUnaCarta: numero! !

!DrawCard methodsFor: 'event handling'!
handlesMouseDown: t1 
	^ true! !

!DrawCard methodsFor: 'event handling'!
mouseDown: t1 
	t1 hand waitForClicksOrDrag: self event: t1.
	t1 hand grabMorph: self! !

"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

DrawCard class
	instanceVariableNames: ''!

!DrawCard class methodsFor: 'as yet unclassified'!
initializeOff
	| t1 |
	t1 _ self new.
	FileDirectory default pathParts last = 'STEG'
		ifFalse: [TEGMain setFolder].
	t1 addMorph: (Form fromFileNamed: 'TEGCarta.jpg') asMorph.
	^ t1! !


IconicButton subclass: #DrawPicture
	instanceVariableNames: 'estado valor '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Morphic-TEG'!

!DrawPicture methodsFor: 'as yet unclassified'!
estado
	^ estado! !

!DrawPicture methodsFor: 'as yet unclassified'!
estado: t1 
	| t2 |
	estado _ t1.
	estado
		ifTrue: [t2 _ submorphs first form.
			t2 mapColor: Color white to: Color lightRed]
		ifFalse: [t2 _ submorphs first form.
			t2 mapColor: Color lightRed to: Color white]! !

!DrawPicture methodsFor: 'as yet unclassified'!
initializeWith: t1 escala: t2 
	| t3 |
	t3 _ Form fromFileNamed: t1.
	t3 _ t3 magnify: t3 boundingBox by: t2.
	self labelGraphic: t3! !

!DrawPicture methodsFor: 'as yet unclassified'!
initializeWith: t1 valor: t2 pos: t3 
	| t4 |
	valor _ t2.
	self estado: false.
	t4 _ Form fromFileNamed: t1.
	self labelGraphic: t4.
	self position: t3! !

!DrawPicture methodsFor: 'as yet unclassified'!
initializeWith: t1 valor: t2 rect: t3 
	| t4 |
	valor _ t2.
	self estado: false.
	t4 _ Form fromFileNamed: t1.
	self labelGraphic: t4.
	self bounds: t3.
	self comeToFront! !

!DrawPicture methodsFor: 'as yet unclassified'!
mouseUp: t1 
	(self containsPoint: t1 cursorPoint)
		ifTrue: [self setSwitchState: estado = false.
			self doButtonAction]
		ifFalse: [self setSwitchState: estado = true]! !

!DrawPicture methodsFor: 'as yet unclassified'!
setSwitchState: t1 
	t1
		ifTrue: [self borderColor: #inset.
			self estado: true]
		ifFalse: [self borderColor: #raised.
			self estado: false]! !

!DrawPicture methodsFor: 'as yet unclassified'!
valor
	^ valor! !


Morph subclass: #InformaCartas
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Morphic-TEG'!

!InformaCartas methodsFor: 'initialization'!
initialize: t1 
	| t2 t3 t4 t5 t6 t7 t8 t9 t10 t11 |
	super initialize.
	self
		bounds: (Rectangle
				left: 710
				right: 748
				top: 220
				bottom: 460).
	self color: Color white.
	self borderColor: Color black.
	self borderWidth: 2.
	t2 _ t1 size.
	t3 _ (216 / t2) asInteger.
	t4 _ 224.
	t5 _ 224 + t3.
	t6 _ 237.
	t7 _ 247.
	t3 _ t3 + 3.
	1
		to: t2
		do: [:t12 | 
			t8 _ Morph new.
			t8
				bounds: (Rectangle
						left: 712
						right: 748
						top: t4
						bottom: t5).
			t8 color: (t1 at: t12) miColor.
			t8 borderColor: Color black.
			t8 borderWidth: 2.
			self addMorph: t8.
			(t1 at: t12) vive
				ifTrue: [t9 _ Morph new.
					t9
						bounds: (Rectangle
								left: 720
								right: 738
								top: t6
								bottom: t7).
					t9 color: Color white.
					t9 borderColor: Color black.
					t9 borderWidth: 2.
					self addMorph: t9.
					t10 _ StringMorph contents: (t1 at: t12) misCartas size asString.
					t10 center: t9 center.
					self addMorph: t10]
				ifFalse: [t11 _ DrawPicture new
								initializeWith: 'muerte.gif'
								valor: 0
								pos: t8 topLeft.
					self addMorph: t11].
			t4 _ t4 + t3.
			t5 _ t5 + t3.
			t6 _ t6 + t3.
			t7 _ t7 + t3].
	self openInWorld! !


Object subclass: #Jugador
	instanceVariableNames: 'vive esHumano misPaises misCartas miColor '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Morphic-TEG'!

!Jugador methodsFor: 'accesing'!
esHumano
	^ esHumano! !

!Jugador methodsFor: 'accesing'!
esHumano: t1 
	esHumano _ t1! !

!Jugador methodsFor: 'accesing'!
initialize
	vive _ true.
	esHumano _ false.
	misPaises _ OrderedCollection new.
	misCartas _ OrderedCollection new! !

!Jugador methodsFor: 'accesing'!
miColor
	^ miColor! !

!Jugador methodsFor: 'accesing'!
miColor: t1 
	miColor _ t1! !

!Jugador methodsFor: 'accesing'!
misCartas
	^ misCartas! !

!Jugador methodsFor: 'accesing'!
misCartas: t1 
	misCartas add: t1! !

!Jugador methodsFor: 'accesing'!
misPaises
	^ misPaises! !

!Jugador methodsFor: 'accesing'!
misPaises: t1 
	misPaises add: t1! !

!Jugador methodsFor: 'accesing'!
vive
	^ vive! !

!Jugador methodsFor: 'accesing'!
vive: t1 
	vive _ t1! !


PolygonMorph subclass: #PaisMorph
	instanceVariableNames: 'nombre ejEnPais deQuienSoy instanciaTEG numero misLimites '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Morphic-TEG'!

!PaisMorph methodsFor: 'initialization'!
initialize
	instanciaTEG _ ActiveWorld submorphs
				detect: [:t1 | t1 class == TEGMain].
	super initialize.
	misLimites _ SortedCollection new! !

!PaisMorph methodsFor: 'initialization'!
nombre: t1 limites: t2 
	| t3 t4 t5 |
	nombre _ t1.
	ejEnPais _ 0.
	self
		vertices: t2 asArray
		color: Color white
		borderWidth: 2
		borderColor: Color black.
	t4 _ self center.
	t5 _ Morph new.
	t5
		bounds: (Rectangle
				left: t4 x
				right: t4 x + 15
				top: t4 y
				bottom: t4 y + 10).
	t5 color: Color white.
	self addMorph: t5.
	t3 _ TextMorph new.
	t3 autoFit: true.
	t3
		string: ejEnPais asString
		fontName: #ComicBold
		size: 18
		wrap: false.
	t3 contents: ejEnPais asString.
	t3 bounds: t5.
	t3 centered.
	self addMorph: t3.
	t3 lock! !


!PaisMorph methodsFor: 'event handling' stamp: 'edc 4/29/2004 10:24'!
click: t1 
	| t2 t3 |
	t2 _ 'Soy ' , nombre asString , ' numero ' , numero asString , 'y pertenezco a ' , deQuienSoy asString.
	self showBalloon: t2 hand: t1 hand.
	t3 _ 0.
	(instanciaTEG permitido: numero)
		ifFalse: [^ false].
	instanciaTEG submorphs
		do: [:t4 | t4 class == DrawPicture
				ifTrue: [t3 _ t3 + 1.
					instanciaTEG pone: instanciaTEG pone - 1.
					t4 estado
						ifTrue: [ejEnPais _ ejEnPais + t4 valor.
							t3 _ t3 - 1.
							t4 delete]]].
	self mostrar.
	t3 = 1
		ifTrue: [instanciaTEG ronda <= 5
				ifTrue: [instanciaTEG continue]
				ifFalse: [instanciaTEG estado: 2]]! !

!PaisMorph methodsFor: 'event handling'!
firstClickTimedOut: t1 
	| t2 t3 |
	t2 _ owner rootForGrabOf: self.
	t2
		ifNil: [t3 _ self copy.
			self board owner owner addMorphFront: t3.
			self world displayWorld.
			(Delay forMilliseconds: 750) wait.
			t3 delete]
		ifNotNil: [t1 hand grabMorph: t2]! !

!PaisMorph methodsFor: 'event handling'!
handlesMouseDown: t1 
	^ true! !

!PaisMorph methodsFor: 'event handling'!
mouseDown: t1 
	t1 hand waitForClicksOrDrag: self event: t1! !

!PaisMorph methodsFor: 'event handling'!
mouseEnter: t1 
	| t2 |
	t2 _ 'Soy ' , nombre asString , ' y pertenezco a ' , deQuienSoy asString.
	self showBalloon: t2 hand: t1 hand! !


!PaisMorph methodsFor: 'access'!
add: t1 
	ejEnPais _ ejEnPais + t1.
	self mostrar! !

!PaisMorph methodsFor: 'access'!
deQuienSoy
	^ deQuienSoy! !

!PaisMorph methodsFor: 'access'!
deQuienSoy: t1 
	deQuienSoy _ t1! !

!PaisMorph methodsFor: 'access'!
doubleClick: t1 
	1
		to: 42
		do: [:t2 | (instanciaTEG submorphs at: t2)
				color: Color white].
	(instanciaTEG submorphs at: numero)
		color: Color green.
	misLimites
		do: [:t3 | (instanciaTEG submorphs at: t3)
				color: Color red].
	self borderWidth: 4;
		 borderColor: Color red.
	^ self numero! !

!PaisMorph methodsFor: 'access'!
ejercitos
	^ ejEnPais! !

!PaisMorph methodsFor: 'access'!
ejercitos: t1 
	ejEnPais _ t1.
	self mostrar! !

!PaisMorph methodsFor: 'access'!
misLimites
	^ misLimites! !

!PaisMorph methodsFor: 'access'!
misLimites: t1 
	misLimites _ t1! !

!PaisMorph methodsFor: 'access'!
mostrar
	submorphs first contents: ejEnPais asString.
	submorphs
		do: [:t1 | t1 center: self center]! !

!PaisMorph methodsFor: 'access'!
noMostrar
	submorphs
		do: [:t1 | t1 delete]! !

!PaisMorph methodsFor: 'access'!
nombre
	^ nombre! !

!PaisMorph methodsFor: 'access'!
numero
	^ numero! !

!PaisMorph methodsFor: 'access'!
numero: t1 
	numero _ t1! !

!PaisMorph methodsFor: 'access'!
otroLimites: t1 
	misLimites _ misLimites add: t1! !

!PaisMorph methodsFor: 'access'!
redrawInColor: t1 
	self color: t1.
	submorphs first contents: ejEnPais asString.
	submorphs
		do: [:t2 | t2 center: self center]! !


Object subclass: #TEGClient
	instanceVariableNames: 'socket serverName instanciaTEG '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Morphic-TEG'!

!TEGClient methodsFor: 'as yet unclassified' stamp: 'edc 4/27/2004 16:21'!
initialize
	| t1 |
	Transcript open.
	Transcript show: 'starting remote client';
		 cr.
	Transcript show: 'initializing network ... '.
	Socket initializeNetwork.
	Transcript show: 'ok';
		 cr.
	serverName _ FillInTheBlank request: 'Type server name or IPAddress' initialAnswer: 'Enterprise'.
	t1 _ FillInTheBlank request: 'Type client name' initialAnswer: ''.
	Transcript show: 'server start to perform instructions';
		 cr.
	self newSocket.
socket sendData: t1.
	instanciaTEG _ ActiveWorld submorphs
				detect: [:t2 | t2 class == TEGMain].
	instanciaTEG activeSocket: self socket.
	instanciaTEG done: true! !

!TEGClient methodsFor: 'as yet unclassified'!
newSocket
	socket _ Socket newTCP.
	socket
		connectTo: (NetNameResolver addressForName: serverName)
		port: 8000.
	socket waitForConnectionUntil: Socket standardDeadline! !

!TEGClient methodsFor: 'as yet unclassified' stamp: 'edc 4/27/2004 10:31'!
socket
^ socket! !

"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

TEGClient class
	instanceVariableNames: ''!

!TEGClient class methodsFor: 'as yet unclassified'!
new
	super new initialize! !

!TEGClient class methodsFor: 'as yet unclassified'!
start
	super new initialize! !


BorderedMorph subclass: #TEGMain
	instanceVariableNames: 'miArchivo cartasOrden losJugadores jugadoresVivos cartel pone cambiosTotales playerTurn ronda limites done lim estado numCarta mazo activeSocket serverOrClient socketList '
	classVariableNames: 'NewFolder '
	poolDictionaries: ''
	category: 'Morphic-TEG'!

!TEGMain methodsFor: 'accessing' stamp: 'edc 4/26/2004 17:28'!
activeSocket
	"Answer the value of activeSocket"

	^ activeSocket! !

!TEGMain methodsFor: 'accessing' stamp: 'edc 4/26/2004 17:28'!
activeSocket: anObject
	"Set the value of activeSocket"

	activeSocket _ anObject! !

!TEGMain methodsFor: 'accessing' stamp: 'edc 4/26/2004 17:28'!
cambiosTotales
	"Answer the value of cambiosTotales"

	^ cambiosTotales! !

!TEGMain methodsFor: 'accessing'!
cambiosTotales: t1 
	cambiosTotales _ t1! !

!TEGMain methodsFor: 'accessing' stamp: 'edc 4/26/2004 17:28'!
cartasOrden
	"Answer the value of cartasOrden"

	^ cartasOrden! !

!TEGMain methodsFor: 'accessing'!
cartasOrden: t1 
	cartasOrden _ t1! !

!TEGMain methodsFor: 'accessing' stamp: 'edc 4/26/2004 17:28'!
cartel
	"Answer the value of cartel"

	^ cartel! !

!TEGMain methodsFor: 'accessing' stamp: 'edc 4/26/2004 17:28'!
cartel: anObject
	"Set the value of cartel"

	cartel _ anObject! !

!TEGMain methodsFor: 'accessing' stamp: 'edc 4/26/2004 17:28'!
done
	"Answer the value of done"

	^ done! !

!TEGMain methodsFor: 'accessing' stamp: 'edc 4/26/2004 17:28'!
done: anObject
	"Set the value of done"

	done _ anObject! !

!TEGMain methodsFor: 'accessing' stamp: 'edc 4/26/2004 17:28'!
estado
	"Answer the value of estado"

	^ estado! !

!TEGMain methodsFor: 'accessing'!
estado: t1 
	estado _ t1! !

!TEGMain methodsFor: 'accessing'!
jugadoresVivos
	^ jugadoresVivos! !

!TEGMain methodsFor: 'accessing'!
jugadoresVivos: t1 
	jugadoresVivos _ t1! !

!TEGMain methodsFor: 'accessing' stamp: 'edc 4/26/2004 17:28'!
lim
	"Answer the value of lim"

	^ lim! !

!TEGMain methodsFor: 'accessing' stamp: 'edc 4/26/2004 17:28'!
lim: anObject
	"Set the value of lim"

	lim _ anObject! !

!TEGMain methodsFor: 'accessing' stamp: 'edc 4/26/2004 17:28'!
limites
	"Answer the value of limites"

	^ limites! !

!TEGMain methodsFor: 'accessing' stamp: 'edc 4/26/2004 17:28'!
limites: anObject
	"Set the value of limites"

	limites _ anObject! !

!TEGMain methodsFor: 'accessing'!
losJugadores
	^ losJugadores! !

!TEGMain methodsFor: 'accessing'!
losJugadores: t1 
	losJugadores _ t1! !

!TEGMain methodsFor: 'accessing' stamp: 'edc 4/26/2004 17:28'!
mazo
	"Answer the value of mazo"

	^ mazo! !

!TEGMain methodsFor: 'accessing' stamp: 'edc 4/26/2004 17:28'!
mazo: anObject
	"Set the value of mazo"

	mazo _ anObject! !

!TEGMain methodsFor: 'accessing' stamp: 'edc 4/26/2004 17:28'!
miArchivo
	"Answer the value of miArchivo"

	^ miArchivo! !

!TEGMain methodsFor: 'accessing' stamp: 'edc 4/26/2004 17:28'!
miArchivo: anObject
	"Set the value of miArchivo"

	miArchivo _ anObject! !

!TEGMain methodsFor: 'accessing' stamp: 'edc 4/26/2004 17:28'!
numCarta
	"Answer the value of numCarta"

	^ numCarta! !

!TEGMain methodsFor: 'accessing'!
numCarta: t1 
	numCarta _ t1! !

!TEGMain methodsFor: 'accessing'!
paises: t1 
	| t2 t3 |
	1
		to: 42
		do: [:t4 | 
			(submorphs at: t4)
				ejercitos: ((t1 at: t4)
						at: 1).
			(submorphs at: t4)
				deQuienSoy: ((t1 at: t4)
						at: 2).
			t2 _ (submorphs at: t4) deQuienSoy.
			t3 _ (losJugadores at: t2) miColor.
			(submorphs at: t4)
				redrawInColor: t3]! !

!TEGMain methodsFor: 'accessing' stamp: 'edc 4/26/2004 17:28'!
playerTurn
	"Answer the value of playerTurn"

	^ playerTurn! !

!TEGMain methodsFor: 'accessing'!
playerTurn: t1 
	playerTurn _ t1! !

!TEGMain methodsFor: 'accessing'!
pone
	^ pone! !

!TEGMain methodsFor: 'accessing'!
pone: t1 
	pone _ t1! !

!TEGMain methodsFor: 'accessing'!
ronda
	^ ronda! !

!TEGMain methodsFor: 'accessing'!
ronda: t1 
	ronda _ t1! !

!TEGMain methodsFor: 'accessing' stamp: 'edc 4/26/2004 15:03'!
serverOrClient
	^serverOrClient! !

!TEGMain methodsFor: 'accessing' stamp: 'edc 4/26/2004 14:57'!
serverOrClient: aChoice
serverOrClient _ aChoice! !

!TEGMain methodsFor: 'accessing' stamp: 'edc 4/27/2004 15:13'!
socketList: aDictionary
socketList _ aDictionary.
done _ true.! !


!TEGMain methodsFor: 'as yet unclassified'!
hacerListaPaises
	| t1 t2 |
	t1 _ Set new.
	(losJugadores at: playerTurn) misPaises
		do: [:t3 | limites
				do: [:t4 | (t4 includes: t3)
						ifTrue: [t1 add: t4]]].
	t2 _ t1 copy.
	t1
		do: [:t5 | (((losJugadores at: playerTurn) misPaises
						includes: (t5 at: 1))
					and: [(losJugadores at: playerTurn) misPaises
							includes: (t5 at: 2)])
				ifTrue: [t2 remove: t5]].
	^ t2! !

!TEGMain methodsFor: 'as yet unclassified'!
in: t1 pos1: t2 pos2: t3 
	| t4 t5 |
	t4 _ (losJugadores at: playerTurn) misPaises includes: t1.
	t4
		ifTrue: [t5 _ (losJugadores at: playerTurn) misCartas at: t2.
			(losJugadores at: playerTurn) misCartas
				at: t2
				put: ((losJugadores at: playerTurn) misCartas at: t3).
			(losJugadores at: playerTurn) misCartas at: t3 put: t5]! !

!TEGMain methodsFor: 'as yet unclassified'!
optimizarCambio
	| t1 t2 t3 t4 t5 |
	t5 _ Array new: 6.
	(losJugadores at: playerTurn) misCartas
		do: [:t6 | t2 _ t6 \\\ 3 , self halt].
	(losJugadores at: playerTurn) misCartas
		do: [:t6 | ((losJugadores at: playerTurn) misPaises includes: t6)
				ifTrue: [t1 _ (losJugadores at: playerTurn) misCartas indexOf: t6.
					t2 _ t6 \\\ 3]].
	t3 _ 0.
	(losJugadores at: playerTurn) misCartas
		do: [:t7 | 
			t3 _ t3 + 1.
			t7 \\\ 3 = t2
				ifTrue: [t4 _ (losJugadores at: playerTurn) misCartas at: t1.
					(losJugadores at: playerTurn) misCartas
						at: t1
						put: ((losJugadores at: playerTurn) misCartas at: t3).
					(losJugadores at: playerTurn) misCartas at: t3 put: t4.
					^ true].
			nil]! !


!TEGMain methodsFor: 'debug and other'!
debug
	submorphs
		do: [:t1 | t1 class == DrawPicture
				ifTrue: [t1 delete]].
	17
		to: 99
		do: [:t2 | 
			pone _ t2.
			self eligeEjercitos: t2 jugador: 1]! !

!TEGMain methodsFor: 'debug and other'!
maximo: t1 
	| t2 t3 t4 |
	t1
		do: [:t5 | t2
				ifNil: [t3 _ t5 x.
					t2 _ t5 x]
				ifNotNil: [(t4 _ t5 x) > t2
						ifTrue: [t3 _ t5 x.
							t2 _ t4]]].
	^ t2! !

!TEGMain methodsFor: 'debug and other'!
minimo: t1 
	| t2 t3 t4 |
	t1
		do: [:t5 | t2
				ifNil: [t3 _ t5 x.
					t2 _ t5 x]
				ifNotNil: [(t4 _ t5 x) < t2
						ifTrue: [t3 _ t5 x.
							t2 _ t4]]].
	^ t2! !

!TEGMain methodsFor: 'debug and other'!
split
	self eligeEjercitos: pone jugador: playerTurn! !


!TEGMain methodsFor: 'event handling'!
handlesMouseDown: t1 
	^ Smalltalk isMorphic not
		or: [t1 yellowButtonPressed]! !

!TEGMain methodsFor: 'event handling'!
mouseDown: t1 
	| t2 |
	t1 yellowButtonPressed
		ifFalse: [^ self].
	t2 _ MenuMorph new defaultTarget: self.
	self addMenuItemsTo: t2 hand: t1 hand.
	t2 popUpEvent: t1 in: self world! !


!TEGMain methodsFor: 'fileIn/out'!
grabaEstado
	| t1 |
	t1 _ ReferenceStream fileNamed: 'estado.teg'.
	t1 nextPut: losJugadores.
	t1 nextPut: cartasOrden.
	t1 nextPut: jugadoresVivos.
	t1 nextPut: playerTurn.
	t1 nextPut: ronda.
	t1 nextPut: numCarta.
	t1 nextPut: cambiosTotales.
	1
		to: 42
		do: [:t2 | 
			t1 nextPut: (submorphs at: t2) ejercitos.
			t1 nextPut: (submorphs at: t2) deQuienSoy].
	t1 close! !

!TEGMain methodsFor: 'fileIn/out'!
leerEstado
	| t1 |
	t1 _ ReferenceStream fileNamed: 'estado.teg'.
	losJugadores _ t1 next.
	cartasOrden _ t1 next.
	jugadoresVivos _ t1 next.
	playerTurn _ t1 next.
	ronda _ t1 next.
	numCarta _ t1 next.
	cambiosTotales _ t1 next.
	1
		to: 42
		do: [:t2 | 
			(submorphs at: t2)
				ejercitos: t1 next.
			(submorphs at: t2)
				deQuienSoy: t1 next].
	t1 close.
	self miColor! !


!TEGMain methodsFor: 'game sequence'!
armaBatallones
	| t1 t2 t3 t4 t5 t6 t7 |
	t7 _ Array new: 5.
	t1 _ pone.
	t2 _ 0.
	t3 _ 0.
	t4 _ 0.
	t5 _ 0.
	t6 _ 0.
	t2 _ (t1 / 50) asInteger.
	t1 _ t1 \\\ 50.
	t3 _ (t1 / 20) asInteger.
	t1 _ t1 \\\ 20.
	t4 _ (t1 / 10) asInteger.
	t1 _ t1 \\\ 10.
	t1 = 5
		ifTrue: [t6 _ 5]
		ifFalse: [t5 _ (t1 / 5) asInteger.
			t6 _ t1 \\\ 5].
	pone <= 9
		ifFalse: [[t2 + t3 + t4 + t5 + t6 <= 5]
				whileTrue: [t4 > 0
						ifTrue: [t4 _ t4 - 1.
							t5 _ t5 + 2]
						ifFalse: [t3 > 0
								ifTrue: [t3 _ t3 - 1.
									t4 _ t4 + 2]
								ifFalse: [t2 > 0
										ifTrue: [t2 _ t2 - 1.
											t3 _ t3 + 2.
											t4 _ t4 + 5]
										ifFalse: [t5 > 0
												ifTrue: [t5 _ t5 - 1.
													t6 _ t6 + 5]]]]]].
	t7 at: 1 put: t6.
	t7 at: 2 put: t5.
	t7 at: 3 put: t4.
	t7 at: 4 put: t3.
	t7 at: 5 put: t2.
	^ t7! !

!TEGMain methodsFor: 'game sequence'!
atacaMaquina
	| t1 t2 t3 t4 t5 t6 t7 t8 t9 t10 |
	t10 _ self hacerListaPaises: true.
	t10
		do: [:t11 | 
			((losJugadores at: playerTurn) misPaises
					includes: (t11 at: 1))
				ifTrue: [t7 _ t11 at: 1.
					t6 _ t11 at: 2]
				ifFalse: [t7 _ t11 at: 2.
					t6 _ t11 at: 1].
			t1
				ifNil: [t1 _ (submorphs at: t7) ejercitos - (submorphs at: t6) ejercitos.
					t2 _ t7]
				ifNotNil: [(t3 _ (submorphs at: t7) ejercitos - (submorphs at: t6) ejercitos) > t1
						ifTrue: [t2 _ t7.
							t8 _ t6.
							t1 _ t3]]].
	t8
		ifNil: [^ false].
	t6 _ t8.
	t7 _ t2.
	t4 _ self
				suerte: (submorphs at: t7)
				contra: (submorphs at: t6).
	t4
		ifTrue: [pone > 2
				ifTrue: [t5 _ (pone - 2 / 2) asInteger.
					t9 _ pone - t5.
					(submorphs at: t7)
						add: t9.
					(submorphs at: t6)
						add: t5.
					(submorphs at: t6)
						deQuienSoy: playerTurn.
					^ true].
			^ false].
	^ false! !

!TEGMain methodsFor: 'game sequence'!
ataque
	| t1 t2 t3 t4 t5 |
	estado _ 2.
	Cursor crossHair
		showWhile: [[Sensor anyButtonPressed]
				whileFalse: [self currentWorld displayWorldSafely; runStepMethods].
			t1 _ Sensor cursorPoint].
	t3 _ submorphs
				detect: [:t6 | t6 containsPoint: t1].
	t2 _ t3 nombre.
	PopUpMenu confirm: t2.
	((losJugadores at: playerTurn) misPaises includes: t3 numero)
		ifFalse: [^ self].
	Cursor crossHair
		showWhile: [[Sensor anyButtonPressed]
				whileFalse: [self currentWorld displayWorldSafely; runStepMethods].
			t1 _ Sensor cursorPoint].
	t4 _ submorphs
				detect: [:t6 | t6 containsPoint: t1].
	lim _ Array new: 2.
	lim at: 1 put: t3 numero.
	lim at: 2 put: t4 numero.
	(limites includes: lim)
		ifFalse: [lim at: 1 put: t4 numero.
			lim at: 2 put: t3 numero.
			(limites includes: lim)
				ifFalse: [PopUpMenu inform: 'No son limitrofes'.
					^ false]].
	t5 _ self suerte: t3 contra: t4.
	t5
		ifTrue: [self eligeEjercitos: pone jugador: playerTurn.
			estado _ 3]! !

!TEGMain methodsFor: 'game sequence'!
continue
	done _ true! !

!TEGMain methodsFor: 'game sequence'!
continue: t1 
	t1 delete.
	estado _ 4! !

!TEGMain methodsFor: 'game sequence'!
dibuCartas: t1 hayCambio: t2 
	| t3 t4 t5 t6 t7 t8 t9 |
	t3 _ (Form fromFileNamed: 'CardsDLOG.gif') asMorph.
	t7 _ DrawPicture new
				initializeWith: 'OK.gif'
				valor: 1
				rect: (463 @ 327 corner: 535 @ 358).
	t7 target: self.
	t7 actionSelector: #cambiaCartas:.
	t7
		arguments: (Array with: t3).
	t9 _ DrawPicture new
				initializeWith: 'Cancel.gif'
				valor: 1
				rect: (468 @ 292 corner: 530 @ 314).
	t9 target: self.
	t9 actionSelector: #continue:.
	t9
		arguments: (Array with: t3).
	t3 position: 90 @ 90.
	t3 openInWorld.
	1
		to: t1
		do: [:t10 | 
			t10 caseOf: {
				[1] -> [t6 _ 110 @ 110].
				[2] -> [t6 _ 286 @ 110].
				[3] -> [t6 _ 462 @ 110].
				[4] -> [t6 _ 198 @ 254].
				[5] -> [t6 _ 374 @ 254].
				[6] -> [t6 _ 110 @ 254]}
				 otherwise: [t6 _ 20 @ 20].
			t8 _ (losJugadores at: playerTurn) misCartas at: t10.
			t8 > 42
				ifTrue: [t4 _ DrawCard new dibujaUnaCarta: t8]
				ifFalse: [t4 _ mazo at: t8.
					t4 submorphs last noMostrar.
					t4 submorphs last color: (submorphs at: t8) color].
			t10 <= 3
				ifTrue: [t2
						ifTrue: [t4 submorphs first estado: true]].
			t4 position: t6.
			t3 addMorphBack: t4].
	t3 addMorphBack: t7.
	t3 addMorphBack: t9.
	self world displayWorld.
	(losJugadores at: playerTurn) esHumano
		ifTrue: [t2
				ifTrue: [[estado = 4]
						whileFalse: [World doOneCycle]].
			estado _ 1]
		ifFalse: [3
				timesRepeat: [(Delay forSeconds: 1) wait.
					SampledSound playSoundNamed: 'chirp'.
					t2
						ifTrue: [self cambiaCartas: t3].
					t5 _ true.
					(Delay forSeconds: 3) wait.
					t3 delete.
					^ t5]]! !

!TEGMain methodsFor: 'game sequence' stamp: 'edc 4/29/2004 11:38'!
dibujaUnaCarta2: t1 
	| t2 t3 t4 |
(losJugadores at: playerTurn) esHumano ifFalse:[^self].
	t1 openInWorld.
	t1 center: Display center.
	t2 _ Player new.
	t2 costume: t1.
	t3 _ 1.0.
	t2 show.
	1
		to: 8
		do: [:t5 | 
			t4 _ 1600 - (100 * t5).
			(Delay forMilliseconds: t4) wait.
			"FMSound randomWeird1 play."
			t2 setScaleFactor: t3.
			t2 forward: 100 atRandom.
			t2 turn: 360 atRandom.
			self world displayWorld.
			t3 _ t3 - 0.125].
	t2 erase! !

!TEGMain methodsFor: 'game sequence' stamp: 'edc 4/27/2004 14:41'!
eligeEjercitos: t1 jugador: t2 
	| t3 t4 t5 t6 t7 t8 t9 t10 t11 t14 |
	t10 _ Array new: 9.
	t9 _ Array new: 9.
	1
		to: 9
		do: [:t12 | 
			t10
				at: t12
				put: (Rectangle
						left: 155 + (t12 * 45)
						right: 195 + (t12 * 45)
						top: (self bottom - 70)
						bottom: (self bottom - 50)).
			t9 at: t12 put: 0].
	t11 _ self armaBatallones.
	t8 _ 1.
	t7 _ t11 at: 1.
	t6 _ t11 at: 2.
	t5 _ t11 at: 3.
	t4 _ t11 at: 4.
	t3 _ t11 at: 5.
	t7 > 0
		ifTrue: [1
				to: t7
				do: [:t13 | 
					t8 _ t8 + 1.
					self
						addMorphBack: (DrawPicture new
								initializeWith: 'Soldado1.gif'
								valor: 1
								rect: (t10 at: t13)).
					t9 at: t13 put: 1]].
	t6 > 0
		ifTrue: [t14 _ t6 + t8 - 1.
			t8
				to: t14
				do: [:t13 | 
					t8 _ t8 + 1.
					self
						addMorphBack: (DrawPicture new
								initializeWith: 'Soldado5.gif'
								valor: 5
								rect: (t10 at: t13)).
					t9 at: t13 put: 5]].
	t5 > 0
		ifTrue: [t14 _ t5 + t8 - 1.
			t8
				to: t14
				do: [:t13 | 
					t8 _ t8 + 1.
					self
						addMorphBack: (DrawPicture new
								initializeWith: 'Soldado10.gif'
								valor: 10
								rect: (t10 at: t13)).
					t9 at: t13 put: 10]].
	t4 > 0
		ifTrue: [t14 _ t4 + t8 - 1.
			t8
				to: t14
				do: [:t13 | 
					t8 _ t8 + 1.
					self
						addMorphBack: (DrawPicture new
								initializeWith: 'Soldado20.gif'
								valor: 20
								rect: (t10 at: t13)).
					t9 at: t13 put: 20]].
	t3 > 0
		ifTrue: [t14 _ t3 + t8 - 1.
			t8
				to: t14
				do: [:t13 | 
					t8 _ t8 + 1.
					self
						addMorphBack: (DrawPicture new
								initializeWith: 'Soldado50.gif'
								valor: 50
								rect: (t10 at: t13)).
					t9 at: t13 put: 50]].
	(t9 at: 9)
			= 0
		ifTrue: [self addMorphBack: (DrawPicture new
					initializeWith: 'Split.gif'
					valor: 0
					rect: (t10 at: 9);
					 target: self;
					 actionSelector: #split)]! !

!TEGMain methodsFor: 'game sequence'!
endGameFor: t1 
	^ self halt! !

!TEGMain methodsFor: 'game sequence'!
finAtaque
	done _ true.
	estado _ 3! !

!TEGMain methodsFor: 'game sequence' stamp: 'edc 4/27/2004 14:41'!
finRonda
	ronda _ ronda + 1.
	cartel newContents: 'Ronda ' , ronda asString.
	cartel center: self center.
	cartel top: self top + 10! !

!TEGMain methodsFor: 'game sequence'!
fortificar
	| t1 t2 t3 t4 |
	estado _ 2.
	Cursor crossHair
		showWhile: [[Sensor anyButtonPressed]
				whileFalse: [self currentWorld displayWorldSafely; runStepMethods].
			t1 _ Sensor cursorPoint].
	t2 _ submorphs
				detect: [:t5 | t5 containsPoint: t1].
	((losJugadores at: playerTurn) misPaises includes: t2 numero)
		ifFalse: [^ self].
	t4 _ t2 nombre.
	PopUpMenu confirm: t4.
	Cursor crossHair
		showWhile: [[Sensor anyButtonPressed]
				whileFalse: [self currentWorld displayWorldSafely; runStepMethods].
			t1 _ Sensor cursorPoint].
	t3 _ submorphs
				detect: [:t5 | t5 containsPoint: t1].
	((losJugadores at: playerTurn) misPaises includes: t3 numero)
		ifFalse: [self halt].
	lim _ Array new: 2.
	lim at: 1 put: t2 numero.
	lim at: 2 put: t3 numero.
	(limites includes: lim)
		ifFalse: [lim at: 1 put: t3 numero.
			lim at: 2 put: t2 numero.
			(limites includes: lim)
				ifFalse: [PopUpMenu inform: 'No son limitrofes'.
					^ false]].
	pone _ t2 ejercitos - 1.
	t2 ejercitos: 1.
	self eligeEjercitos: pone jugador: playerTurn! !

!TEGMain methodsFor: 'game sequence'!
fortificarMaquina
	| t1 t2 t3 t4 t5 t6 |
	t1 _ OrderedCollection new.
	t3 _ (losJugadores at: playerTurn) misPaises asSortedCollection.
	t3
		do: [:t7 | 
			t2 _ false.
			(submorphs at: t7) misLimites
				do: [:t8 | (t3 includes: t8)
						ifFalse: [t2 _ true]].
			t2
				ifFalse: [(submorphs at: t7) ejercitos even
						ifTrue: [t4 _ (submorphs at: t7) ejercitos - 2.
							(submorphs at: t7)
								ejercitos: 2]
						ifFalse: [t4 _ (submorphs at: t7) ejercitos - 1.
							(submorphs at: t7)
								ejercitos: 1].
					t5 _ (submorphs at: t7) misLimites size.
					t6 _ (t4 / t5) asInteger.
					(submorphs at: t7) misLimites
						do: [:t9 | (submorphs at: t9)
								add: t6]]]! !

!TEGMain methodsFor: 'game sequence'!
hacerLimites
	| t1 |
	1
		to: 42
		do: [:t2 | 
			t1 _ limites
						select: [:t3 | t3 includes: t2]
						thenCollect: [:t4 | (t4 at: 2)
									~= t2
								ifTrue: [t4 at: 2]
								ifFalse: [t4 at: 1]].
			(submorphs at: t2)
				misLimites: t1].
	1
		to: 42
		do: [:t5 | (submorphs at: t5)
				color: Color white]! !

!TEGMain methodsFor: 'game sequence'!
leerCartas
	| t1 t2 |
	mazo _ OrderedCollection new.
	t1 _ ReferenceStream fileNamed: 'cartas.teg'.
	1
		to: 42
		do: [:t3 | 
			t2 _ t1 next.
			(t2 submorphs at: 3) lock.
			mazo add: t2].
	t1 close! !

!TEGMain methodsFor: 'game sequence' stamp: 'edc 4/29/2004 10:00'!
makeMove
	[jugadoresVivos > 1]
		whileTrue: [submorphs
				do: [:t1 | t1 class == DrawPicture
						ifTrue: [t1 delete]].
			(losJugadores at: playerTurn) vive
				ifFalse: [playerTurn _ playerTurn \\ 6 + 1].
			cartel color: (losJugadores at: playerTurn) miColor.
			cartel newContents: 'Ronda ' , ronda asString , ' Turno del jugador ' , playerTurn asString.
			cartel center: self center.
			cartel top: self top + 10.
			done _ false.
			estado _ 1.
			(losJugadores at: playerTurn) esHumano & (serverOrClient = #server)
				ifTrue: [self sendMyData.done _ true].
			ronda caseOf: {
				[1] -> [pone _ 5].
				[2] -> [pone _ 4].
				[3] -> [pone _ 3].
				[4] -> [pone _ 1].
				[5] -> [pone _ 1]}
				 otherwise: [pone _ self cuantosEjercitos].
			(losJugadores at: playerTurn) misCartas size >= 3
				ifTrue: [self verCartas].
			(losJugadores at: playerTurn) esHumano & (serverOrClient = #cliente)
				ifTrue: [self eligeEjercitos: pone jugador: playerTurn].
			(losJugadores at: playerTurn) esHumano not & (serverOrClient = #server)
				ifTrue: [self maquinaPone].
			"ifFalse: [(losJugadores at: playerTurn) misPaises size = 0 
			ifTrue: [self muerte]"
			ronda > 5
				ifTrue: [submorphs last class == InformaCartas
						ifTrue: [submorphs last delete]
						ifFalse: [self
								addMorphBack: (InformaCartas new initialize: losJugadores)]].
			[done]
				whileFalse: [World doOneCycle].
			((losJugadores at: playerTurn) esHumano
					and: [estado = 3])
				ifTrue: [self obtenerCarta].
			playerTurn = 6
				ifTrue: [ronda _ ronda + 1].
			serverOrClient = #cliente
				ifTrue: [self sendMyData]
				ifFalse: [playerTurn _ playerTurn \\ 6 + 1].
			self world displayWorld]! !

!TEGMain methodsFor: 'game sequence'!
maquinaPone
	| t1 t2 t3 t4 |
	t2 _ (losJugadores at: playerTurn) misPaises size.
	t1 _ 1.
	[pone > 0]
		whileTrue: [t3 _ (losJugadores at: playerTurn) misPaises at: t1.
			(submorphs at: t3)
				add: 1.
			pone _ pone - 1.
			t1 _ t1 + 1.
			t1 > t2
				ifTrue: [t1 _ 1]].
	ronda > 5
		ifTrue: [t4 _ self atacaMaquina.
			t4
				ifTrue: [self obtenerCarta].
			self fortificarMaquina].
	done _ true! !

!TEGMain methodsFor: 'game sequence'!
muerte
	(losJugadores at: playerTurn)
		vive: false.
	jugadoresVivos _ jugadoresVivos - 1.
	done _ true! !

!TEGMain methodsFor: 'game sequence'!
obtenerCarta
	| t1 |
	numCarta < 45
		ifTrue: [t1 _ cartasOrden at: numCarta.
			(losJugadores at: playerTurn)
				misCartas: t1.
			t1 > 42
				ifTrue: [self
						dibujaUnaCarta2: (DrawCard new dibujaUnaCarta: t1)]
				ifFalse: [self
						dibujaUnaCarta2: (mazo at: t1)]].
	numCarta _ numCarta + 1! !

!TEGMain methodsFor: 'game sequence'!
permitido: t1 
	estado = 1
		ifTrue: [((losJugadores at: playerTurn) misPaises includes: t1)
				ifTrue: [^ true]].
	estado = 2 | (estado = 3)
		ifTrue: [(lim includes: t1)
				ifTrue: [^ true]].
	^ false! !

!TEGMain methodsFor: 'game sequence'!
ponerEjercitos: t1 enPais: t2 
	ejEnPais at: t2 put: (ejEnPais at: t2)
			+ t1! !

!TEGMain methodsFor: 'game sequence' stamp: 'edc 4/29/2004 11:17'!
suerte: paisAtacante contra: paisAcacado 
	"self soundEffects."
	| dadoAtaque dadoDefensa elColor |
	cartel newContents: paisAtacante nombre , ' Ataca a ' , paisAcacado nombre.
	cartel center: self center.
	cartel top: self top + 10.
	cartel color: (losJugadores at: playerTurn) miColor.
	self world displayWorld.
	"(Delay forSeconds: 3) wait."
	[paisAtacante ejercitos > 0
		and: [paisAcacado ejercitos > 0]]
		whileTrue: [dadoAtaque _ 0.
			dadoDefensa _ 0.
			[dadoAtaque = dadoDefensa]
				whileTrue: [dadoAtaque _ 6 atRandom.
					dadoDefensa _ 6 atRandom].
			dadoAtaque > dadoDefensa
				ifTrue: [paisAcacado ejercitos: paisAcacado ejercitos - 1]
				ifFalse: [paisAtacante ejercitos: paisAtacante ejercitos - 1]].
	paisAcacado ejercitos = 0
		ifTrue: [elColor _ (losJugadores at: playerTurn) miColor.
			paisAcacado color: elColor.
			(losJugadores at: paisAcacado deQuienSoy) misPaises
				remove: paisAcacado numero
				ifAbsent: [].
			paisAcacado deQuienSoy: playerTurn.
			(losJugadores at: paisAcacado deQuienSoy) misPaises size = 0
				ifTrue: [self muerte].
			paisAcacado deQuienSoy: playerTurn.
			(losJugadores at: playerTurn)
				misPaises: paisAcacado numero]
		ifFalse: [^ false].
	paisAtacante ejercitos > 2
		ifTrue: [paisAcacado ejercitos: 2.
			pone _ paisAtacante ejercitos - 2.
			paisAtacante ejercitos: 0.
			^ true]
		ifFalse: [pone _ 0.
			^ false].
	self halt! !

!TEGMain methodsFor: 'game sequence'!
verCartas
	| t1 t2 t3 t4 t5 t6 t7 t8 t9 t10 |
	t1 _ 0.
	t2 _ 0.
	t3 _ 0.
	t4 _ 0.
	t5 _ 0.
	t6 _ 0.
	t7 _ 0.
	t4 _ 0.
	t8 _ false.
	1
		to: (losJugadores at: playerTurn) misCartas size
		do: [:t11 | 
			t10 _ (losJugadores at: playerTurn) misCartas at: t11.
			t10 >= 43
				ifTrue: [t4 _ t4 + 1].
			t9 _ ((losJugadores at: playerTurn) misCartas at: t11)
						\\\ 3.
			t9 caseOf: {
				[0] -> 
					[t1 _ t1 + 1.
					t5 = 0
						ifTrue: [t5 _ t11.
							t4 _ t4 + 1]
						ifFalse: [self
								in: t10
								pos1: t11
								pos2: t5]].
				[1] -> 
					[t2 _ t2 + 1.
					t6 = 0
						ifTrue: [t6 _ t11.
							t4 _ t4 + 1]
						ifFalse: [self
								in: t10
								pos1: t11
								pos2: t6]].
				[2] -> 
					[t3 _ t3 + 1.
					t7 = 0
						ifTrue: [t7 _ t11.
							t4 _ t4 + 1]
						ifFalse: [self
								in: t10
								pos1: t11
								pos2: t7]]}
				 otherwise: [Transcript open]].
	t1 >= 3 | (t2 >= 3) | (t3 >= 3) | (t4 >= 3)
		ifTrue: [t8 _ true].
	(losJugadores at: playerTurn) misCartas size > 3
		ifTrue: [t8
				ifTrue: [self optimizarCambio]].
	t8
		ifTrue: [self dibuCartas: (losJugadores at: playerTurn) misCartas size hayCambio: t8]! !


!TEGMain methodsFor: 'initialization'!
cuantosEjercitos
	| t1 t2 t3 t4 t5 t6 t7 |
	t1 _ 0.
	t2 _ 0.
	t3 _ 0.
	t4 _ 0.
	t5 _ 0.
	t6 _ 0.
	t7 _ 0.
	1
		to: 42
		do: [:t8 | (submorphs at: t8) deQuienSoy = playerTurn
				ifTrue: [t1 _ t1 + 1.
					(t8 >= 1
							and: [t8 <= 4])
						ifTrue: [t2 _ t2 + 1].
					(t8 >= 5
							and: [t8 <= 12])
						ifTrue: [t3 _ t3 + 1].
					(t8 >= 13
							and: [t8 <= 20])
						ifTrue: [t4 _ t4 + 1].
					(t8 >= 21
							and: [t8 <= 33])
						ifTrue: [t5 _ t5 + 1].
					(t8 >= 34
							and: [t8 <= 37])
						ifTrue: [t6 _ t6 + 1].
					(t8 > 38
							and: [t8 < 42])
						ifTrue: [t7 _ t7 + 1]]].
	t1 _ 1 + (t1 / 3) asInteger.
	(t2 = 4
			or: [t6 = 4])
		ifTrue: [t1 _ t1 + 2].
	(t3 = 7
			or: [t4 = 7])
		ifTrue: [t1 _ t1 + 5].
	t5 = 8
		ifTrue: [t1 _ t1 + 7].
	t7 = 5
		ifTrue: [t1 _ t1 + 3].
	t1 < 3
		ifTrue: [t1 _ 3].
	^ t1! !

!TEGMain methodsFor: 'initialization'!
dibujaRegion2: t1 color: t2 
	(miRegion at: t1)
		color: t2! !

!TEGMain methodsFor: 'initialization'!
distribuyePaises
	| t1 t2 t3 t4 t5 |
	t2 _ 42 / jugadoresVivos.
	t3 _ OrderedCollection new.
	[t3 size < 42]
		whileTrue: [(t3 includes: (t1 _ 42 atRandom))
				ifFalse: [t3 add: t1]].
	t4 _ 1.
	1
		to: jugadoresVivos
		do: [:t6 | 1
				to: t2
				do: [:t7 | 
					t5 _ t3 at: t4.
					(losJugadores at: t6)
						misPaises: t5.
					(submorphs at: t5)
						deQuienSoy: t6.
					t4 _ t4 + 1]]! !

!TEGMain methodsFor: 'initialization'!
elijeColor
	| t1 t2 t3 |
	t1 _ Array new: 16.
	t1
		at: 1
		put: (Color
				r: 1.0
				g: 5000 / 65535
				b: 5000 / 65535).
	t1
		at: 2
		put: (Color
				r: 1.0
				g: 25000 / 65535
				b: 5000 / 65535).
	t1
		at: 3
		put: (Color
				r: 1.0
				g: 45000 / 65535
				b: 5000 / 65535).
	t1
		at: 4
		put: (Color
				r: 65000 / 65535
				g: 65000 / 65535
				b: 25000 / 65535).
	t1
		at: 5
		put: (Color
				r: 65000 / 65535
				g: 65000 / 65535
				b: 500 / 65535).
	t1
		at: 6
		put: (Color
				r: 45000 / 65535
				g: 45000 / 65535
				b: 500 / 65535).
	t1
		at: 7
		put: (Color
				r: 25000 / 65535
				g: 25000 / 65535
				b: 500 / 65535).
	t1
		at: 8
		put: (Color
				r: 5000 / 65535
				g: 65535 / 65535
				b: 20000 / 65535).
	t1
		at: 9
		put: (Color
				r: 5000 / 65535
				g: 65535 / 65535
				b: 65535 / 65535).
	t1
		at: 10
		put: (Color
				r: 5000 / 65535
				g: 45000 / 65535
				b: 65535 / 65535).
	t1
		at: 11
		put: (Color
				r: 5000 / 65535
				g: 25000 / 65535
				b: 65535 / 65535).
	t1
		at: 12
		put: (Color
				r: 5000 / 65535
				g: 5000 / 65535
				b: 65535 / 65535).
	t1
		at: 13
		put: (Color
				r: 1.0
				g: 5000 / 65535
				b: 25000 / 65535).
	t1
		at: 14
		put: (Color
				r: 1.0
				g: 5000 / 65535
				b: 45000 / 65535).
	t1
		at: 15
		put: (Color
				r: 1.0
				g: 5000 / 65535
				b: 65000 / 65535).
	t1
		at: 16
		put: (Color
				r: 45000 / 65535
				g: 5000 / 65535
				b: 65535 / 65535).
	t2 _ AlignmentMorph newColumn.
	t3 _ OrderedCollection new.
	1
		to: 16
		do: [:t4 | t3 add: (SimpleButtonMorph new label: 'Color ';
					
					color: (t1 at: t4);
					 target: self;
					 actionSelector: #miColor:;
					
					arguments: (Array
							with: (t1 at: t4)))].
	t3
		reverseDo: [:t5 | t2 addMorph: t5].
	t2 position: 650 @ 30.
	self addMorph: t2.
	cartel _ t2! !

!TEGMain methodsFor: 'initialization'!
informaCartas
	self halt.
	self
		addMorphBack: (InformaCartas new initialize: losJugadores)! !

!TEGMain methodsFor: 'initialization'!
initialize
	| t1 t2 t3 t4 |
	self setFolder.
	(StreamingMP3Sound onFileNamed: NewFolder pathName , FileDirectory slash , 'combat.mp3') play.
	super initialize.
	self remoteCommServer.
	self extent: 750 @ 490.
	self color: Color paleBlue.
	self borderWidth: 2.
	self position: 18 @ 0.
	self toggleStickiness.
	self openInWorld.
	miArchivo _ FileStream readOnlyFileNamed: 'PRUEBA'.
	cartasOrden _ OrderedCollection new.
	[cartasOrden size < 44]
		whileTrue: [(cartasOrden includes: (t4 _ 44 atRandom))
				ifFalse: [cartasOrden add: t4]].
	losJugadores _ Array new: 6.
	1
		to: 6
		do: [:t5 | losJugadores at: t5 put: Jugador new initialize].
	(losJugadores at: 1)
		esHumano: true.
	jugadoresVivos _ 6.
	1
		to: 42
		do: [:t6 | 
			t2 _ String new.
			t2 _ self leerArchivo.
			t3 _ OrderedCollection new.
			t1 _ Point readFromString: self leerArchivo.
			t3 add: t1.
			10
				timesRepeat: [t1 _ Point readFromString: self leerArchivo.
					t3 add: t1].
			self addMorphBack: (PaisMorph new nombre: t2 limites: t3;
					 numero: t6)].
	self distribuyePaises.
	self miColor.
	ronda _ 1.
	estado _ 1.
	numCarta _ 1.
	playerTurn _ 1.
	cambiosTotales _ 0.
	self initialize2! !

!TEGMain methodsFor: 'initialization' stamp: 'edc 4/27/2004 16:27'!
initialize2
	| t1 t2 t3 t4 |
	limites _ #(#(1 2) #(1 3) #(2 3) #(2 4) #(3 2) #(3 4) #(3 38) #(4 3) #(4 5) #(5 6) #(5 7) #(6 5) #(6 7) #(6 9) #(6 10) #(7 8) #(7 9) #(8 9) #(8 11) #(8 12) #(9 10) #(9 12) #(10 13) #(11 27) #(12 13) #(13 14) #(14 15) #(14 18) #(15 16) #(15 18) #(15 19) #(16 17) #(16 20) #(16 20) #(16 21) #(16 22) #(16 23) #(17 19) #(18 19) #(19 38) #(20 16) #(20 21) #(20 23) #(20 38) #(20 39) #(21 25) #(22 23) #(22 24) #(22 29) #(23 24) #(23 39) #(23 40) #(24 33) #(25 21) #(25 29) #(29 33) #(33 29) #(38 39) #(38 40) #(38 41) #(40 41) #(20 23) #(19 20) #(39 40) #(25 26) #(26 27) #(31 32) #(27 32) #(30 32) #(29 30) #(34 35) #(37 35) #(35 36) #(11 12) #(40 42) #(42 41) #(34 37) #(36 37) #(33 34) #(24 29) #(28 30) #(25 30) #(18 17) #(18 19) #(17 20) #(21 22) #(21 29) #(25 28) #(26 28) #(26 31) #(28 31) #(30 31) ).
	t1 _ SimpleButtonMorph new label: 'Ataque';
				 target: self;
				 actionSelector: #ataque;
				 position: 180 @ 460;
				 bottom: self bottom - 20.
	self addMorphBack: t1.
	t1 _ SimpleButtonMorph new label: 'Fin Ataque';
				 target: self;
				 actionSelector: #finAtaque;
				 position: 280 @ 460;
				 bottom: self bottom - 20.
	self addMorphBack: t1.
	t2 _ SimpleButtonMorph new label: 'Continuar';
				 target: self;
				 actionSelector: #continue;
				 position: 380 @ 460;
				 bottom: self bottom - 20.
	self addMorphBack: t2.
	t3 _ SimpleButtonMorph new label: 'Fortificar';
				 target: self;
				 actionSelector: #fortificar;
				 position: 480 @ 460;
				 bottom: self bottom - 20.
	self addMorphBack: t3.
	t4 _ SimpleButtonMorph new label: 'DEBUG';
				 target: self;
				 actionSelector: #debug;
				 position: 580 @ 460;
				 bottom: self bottom - 20.
	self addMorphBack: t4.
	done _ true.
	cartel _ TextMorph borderedPrototype.
	cartel
		beAllFont: (StrikeFont familyName: #ComicBold size: 18).
	cartel color: Color red.
	cartel newContents: 'SqueakRos fight the evil '.
	cartel extent: self width - 30 @ 40.
	cartel center: self center.
	cartel top: self top + 10.
	self addMorphBack: cartel.
	World displayWorldSafely.
	(Delay forSeconds: 5) wait.
	self leerCartas.
	self startStepping.
	done _ false.
	self serverOrClient = #server
		ifTrue: [TEGServer start]
		ifFalse: [TEGClient start.
[activeSocket dataAvailable] whileFalse.
	
	self askMyData].
	[done] whileFalse.
	self makeMove! !

!TEGMain methodsFor: 'initialization' stamp: 'edc 4/29/2004 11:44'!
initializeN
	| t1 |
	ScreenController new fullScreenOn.
	cartasOrden _ OrderedCollection new.
	[cartasOrden size < 44]
		whileTrue: [(cartasOrden includes: (t1 _ 44 atRandom))
				ifFalse: [cartasOrden add: t1]].
	losJugadores _ Array new: 6.
	1
		to: 6
		do: [:t2 | losJugadores at: t2 put: Jugador new initialize].
	(losJugadores at: 1)
		esHumano: true.
	(losJugadores at: 2)
		esHumano: true.
(losJugadores at: 3)
		esHumano: true.
	jugadoresVivos _ 6.
	serverOrClient = #server
		ifTrue: [self distribuyePaises.
			self miColor].
	ronda _ 1.
	estado _ 1.
	numCarta _ 1.
	playerTurn _ 1.
	cambiosTotales _ 0.
	self initialize2! !

!TEGMain methodsFor: 'initialization'!
initializeP
	| t1 t2 t3 t4 |
	self setFolder.
	super initialize.
	self extent: 750 @ 490.
	self color: Color paleBlue.
	self borderWidth: 2.
	self position: 18 @ 0.
	self toggleStickiness.
	self openInWorld.
	miArchivo _ FileStream readOnlyFileNamed: 'PRUEBA'.
	cartasOrden _ OrderedCollection new.
	[cartasOrden size < 44]
		whileTrue: [(cartasOrden includes: (t4 _ 44 atRandom))
				ifFalse: [cartasOrden add: t4]].
	losJugadores _ Array new: 6.
	1
		to: 6
		do: [:t5 | losJugadores at: t5 put: Jugador new initialize].
	(losJugadores at: 1)
		esHumano: true.
	jugadoresVivos _ 6.
	1
		to: 42
		do: [:t6 | 
			t2 _ String new.
			t2 _ self leerArchivo.
			t3 _ OrderedCollection new.
			t1 _ Point readFromString: self leerArchivo.
			t3 add: t1.
			10
				timesRepeat: [t1 _ Point readFromString: self leerArchivo.
					t3 add: t1].
			self addMorphBack: (PaisMorph new nombre: t2 limites: t3;
					 numero: t6)].
	self distribuyePaises.
	self miColor.
	ronda _ 1.
	estado _ 1.
	numCarta _ 1.
	playerTurn _ 1.
	cambiosTotales _ 0.
	self initialize2! !

!TEGMain methodsFor: 'initialization'!
leerArchivo
	| t1 t2 |
	t2 _ String new.
	[miArchivo atEnd]
		whileFalse: [t1 _ miArchivo next asCharacter.
			t1 asciiValue = 13
				ifTrue: [^ t2].
			t2 _ t2 , t1 asString]! !

!TEGMain methodsFor: 'initialization'!
miColor
	| t1 t2 |
	t1 _ Color
				wheel: 6
				saturation: 0.7
				brightness: 0.9.
	t2 _ 1.
	t1
		do: [:t3 | 
			(losJugadores at: t2)
				miColor: t3.
			t2 _ t2 + 1].
	submorphs
		do: [:t4 | t4 color: (losJugadores at: t4 deQuienSoy) miColor]! !

!TEGMain methodsFor: 'initialization' stamp: 'edc 4/27/2004 14:43'!
miColor: t1 
	1
		to: 6
		do: [:t2 | (losJugadores at: t2) miColor
				ifNil: [(losJugadores at: t2)
						miColor: t1.
					(losJugadores at: t2) misPaises
						do: [:t3 | (submorphs at: t3)
								color: t1].
					t2 = 6
						ifTrue: [cartel delete.
							cartel _ TextMorph borderedPrototype.
	cartel
		beAllFont: (StrikeFont familyName: #ComicBold size: 18).
	cartel color: Color red.
	cartel newContents: 'SqueakRos fight the evil '.
	cartel extent: self width - 30 @ 40.
	cartel center: self center.
	cartel top: self top + 10.
	self addMorphBack: cartel.
							self startStepping.
							self makeMove].
					^ t2]]! !

!TEGMain methodsFor: 'initialization'!
repeat
	| t1 t2 t3 |
	t1 _ (losJugadores at: playerTurn) misCartas size.
	t2 _ 1.
	[t2 > t1]
		whileFalse: [((losJugadores at: playerTurn) misCartas at: t2)
					\\\ 3 = 0
				ifFalse: [t3 _ (losJugadores at: playerTurn) misCartas at: t2.
					(losJugadores at: playerTurn) misCartas
						at: t2
						put: ((losJugadores at: playerTurn) misCartas at: t1).
					(losJugadores at: playerTurn) misCartas at: t1 put: t3.
					t1 _ t1 - 1].
			t2 _ t2 + 1]! !

!TEGMain methodsFor: 'initialization' stamp: 'edc 4/27/2004 14:46'!
verificarCambio: t1 
	| t2 t3 t4 t5 t6 |
	t3 _ 0.
	t4 _ 0.
	t5 _ 0.
	t2 _ t1 submorphs
				count: [:t7 | t7 class name = 'DrawCard'
						and: [t7 submorphs first estado = true]].
	t2 > 3
		ifTrue: ["(StreamingMP3Sound onFileNamed: NewFolder pathName , FileDirectory slash , 'tramposo.mp3') play."
			cartel newContents: 'Tramposo '.
			cartel center: t1 center.
			t1 addMorph: cartel].
	t6 _ t1 submorphs
				select: [:t7 | t7 class name = 'DrawCard'
						and: [t7 submorphs first estado = true]]
				thenCollect: [:t8 | t8 numero \\\ 3].
	t2 _ 0.
	t6
		do: [:t9 | t9 caseOf: {
				[0] -> 
					[t3 = 0
						ifTrue: [t3 _ 1.
							t2 _ t2 + 1]].
				[1] -> 
					[t4 = 0
						ifTrue: [t4 _ 1.
							t2 _ t2 + 1]].
				[2] -> 
					[t5 = 0
						ifTrue: [t5 _ 1.
							t2 _ t2 + 1]]}
				 otherwise: [Transcript open]].
	t6 _ t1 submorphs
				select: [:t7 | t7 class name = 'DrawCard'
						and: [t7 submorphs first estado = true]]
				thenCollect: [:t8 | t8 numero > 42
						ifTrue: [t2 _ t2 + 1]].
	t2 = 3
		ifTrue: [^ true].
	"(StreamingMP3Sound onFileNamed: NewFolder pathName , FileDirectory slash , 'tramposo.mp3') play."
	cartel newContents: 'Tramposo '.
	cartel center: t1 center.
	t1 addMorph: cartel! !


!TEGMain methodsFor: 'menus'!
addCustomMenuItems: t1 hand: t2 
	super addCustomMenuItems: t1 hand: t2.
	t1 addLine.
	self addMenuItemsTo: t1 hand: t2! !

!TEGMain methodsFor: 'menus'!
addMenuItemsTo: t1 hand: t2 
	t1
		add: 'new game'
		target: self
		action: #newGame.
	t1
		add: 'reset...'
		target: self
		action: #reset.
	t1
		add: 'grabar estado'
		target: self
		action: #grabaEstado.
	t1
		add: 'leer estado'
		target: self
		action: #leerEstado.
	t1
		add: 'debug'
		target: self
		action: #debug! !

!TEGMain methodsFor: 'menus'!
cambiaCartas: t1 
	| t2 t3 t4 |
	estado _ 4.
	t3 _ #(4 6 8 10 12 15 ).
	(losJugadores at: playerTurn) esHumano
		ifTrue: [t4 _ self verificarCambio: t1]
		ifFalse: [t4 _ true].
	t1 submorphs
		do: [:t5 | t5 class name = 'DrawCard'
				ifTrue: [t5 submorphs first estado
						ifTrue: [t2 _ (losJugadores at: playerTurn) misPaises includes: t5 numero.
							t2
								ifTrue: [(submorphs at: t5 numero)
										add: 2].
							(losJugadores at: playerTurn) misCartas
								remove: t5 numero
								ifAbsent: []]]].
	cambiosTotales _ cambiosTotales + 1.
	cambiosTotales < 7
		ifTrue: [pone _ pone + t3 at: cambiosTotales]
		ifFalse: [pone _ pone + 15 + 5 * (cambiosTotales - 6)].
	t1 delete! !

!TEGMain methodsFor: 'menus'!
hacerListaPaises: t1 
	| t2 t3 |
	t2 _ Set new.
	(losJugadores at: playerTurn) misPaises
		do: [:t4 | limites
				do: [:t5 | (t5 includes: t4)
						ifTrue: [t2 add: t5]]].
	t3 _ t2 copy.
	t1
		ifTrue: [t2
				do: [:t6 | (((losJugadores at: playerTurn) misPaises
								includes: (t6 at: 1))
							and: [(losJugadores at: playerTurn) misPaises
									includes: (t6 at: 2)])
						ifTrue: [t3 remove: t6]]]
		ifFalse: [t2
				do: [:t6 | (((losJugadores at: playerTurn) misPaises
								includes: (t6 at: 1))
							and: [(losJugadores at: playerTurn) misPaises
									includes: (t6 at: 2)])
						ifFalse: [t3 remove: t6]]].
	^ t3! !

!TEGMain methodsFor: 'menus'!
reset
	^ self! !


!TEGMain methodsFor: 'sound effects'!
soundEffects
	| t1 t2 |
	t1 _ 3 atRandom.
	t2 _ 'batalla' , t1 asString , '.wav'.
	(SampledSound fromWaveFileNamed: t2) play! !


!TEGMain methodsFor: 'sending-receiving objects' stamp: 'edc 4/27/2004 17:43'!
askMyData
	| estadoTEG losPaises losPaisesData elPais soyDe nuevoColor |
	estadoTEG _ activeSocket getObject.
	self
		losJugadores: (estadoTEG at: 1).
	self
		cartasOrden: (estadoTEG at: 2).
	self
		ronda: (estadoTEG at: 3).
	self
		numCarta: (estadoTEG at: 4).
	self
		cambiosTotales: (estadoTEG at: 5).
	losPaises _ estadoTEG at: 6.
	1
		to: 42
		do: [:pais | 
			losPaisesData _ losPaises at: pais.
			elPais _ self submorphs at: pais.
			elPais
				ejercitos: (losPaisesData at: 1).
			elPais
				deQuienSoy: (losPaisesData at: 2).
			soyDe _ elPais deQuienSoy.
			nuevoColor _ (self losJugadores at: soyDe) miColor.
			elPais redrawInColor: nuevoColor].
self playerTurn: ( estadoTEG at: 7)! !

!TEGMain methodsFor: 'sending-receiving objects' stamp: 'edc 4/28/2004 15:37'!
sendMyData
	| estadoTEG losPaises elPais losPaisesData |
	serverOrClient = #server
		ifTrue: [
			activeSocket _ socketList at: playerTurn].
	(activeSocket isValid
			and: [activeSocket isConnected])
		ifTrue: [estadoTEG _ OrderedCollection new.
			estadoTEG add: self losJugadores.
			estadoTEG add: self cartasOrden.
			estadoTEG add: self ronda.
			estadoTEG add: self numCarta.
			estadoTEG add: self cambiosTotales.
			losPaises _ Array new: 42.
			1
				to: 42
				do: [:pais | 
					elPais _ self submorphs at: pais.
					losPaisesData _ Array new: 2.
					losPaisesData at: 1 put: elPais ejercitos.
					losPaisesData at: 2 put: elPais deQuienSoy.
					losPaises at: pais put: losPaisesData].
			estadoTEG add: losPaises.
			estadoTEG add: self playerTurn.
			activeSocket sendObject: estadoTEG].
	[activeSocket dataAvailable] whileFalse.
	self askMyData! !

"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

TEGMain class
	instanceVariableNames: ''!

!TEGMain class methodsFor: 'as yet unclassified'!
debug
	self maquinaPone! !

!TEGMain class methodsFor: 'as yet unclassified'!
new
	| t1 t2 |
	FileDirectory default pathParts last = 'STEG'
		ifFalse: [self setFolder].
	t1 _ FileStream readOnlyFileNamed: 'TEGBlank.morph'.
	t2 _ t1 fileInObjectAndCode.
	t2 openCenteredInWorld.
	t2 initializeN! !

!TEGMain class methodsFor: 'as yet unclassified'!
reset
	| t1 t2 |
	FileDirectory default pathParts last = 'STEG'
		ifFalse: [self setFolder].
	t1 _ FileStream readOnlyFileNamed: 'TEGBlank.morph'.
	t2 _ t1 fileInObjectAndCode.
	t2 leerEstado.
	t2 openCenteredInWorld.
	t2 initialize2! !

!TEGMain class methodsFor: 'as yet unclassified'!
resetFolder
	FileDirectory setDefaultDirectory: OldFolder! !

!TEGMain class methodsFor: 'as yet unclassified'!
setFolder
	OldFolder _ FileDirectory default pathName.
	FileDirectory setDefaultDirectory: OldFolder , FileDirectory slash , 'STEG'.
	NewFolder _ FileDirectory default! !

!TEGMain class methodsFor: 'as yet unclassified'!
startAsCliente
	| t1 t2 |
	FileDirectory default pathParts last = 'STEG'
		ifFalse: [self setFolder].
	t1 _ FileStream readOnlyFileNamed: 'TEGBlank.morph'.
	t2 _ t1 fileInObjectAndCode.
	t2 openCenteredInWorld.
	t2 serverOrClient: #cliente.
	t2 initializeN! !

!TEGMain class methodsFor: 'as yet unclassified'!
startAsServer
	| t1 t2 |
	FileDirectory default pathParts last = 'STEG'
		ifFalse: [self setFolder].
	t1 _ FileStream readOnlyFileNamed: 'TEGBlank.morph'.
	t2 _ t1 fileInObjectAndCode.
	t2 openCenteredInWorld.
	t2 serverOrClient: #server.
	t2 initializeN! !


Object subclass: #TEGServer
	instanceVariableNames: 'port socketList activeClient addClient '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Morphic-TEG'!

!TEGServer methodsFor: 'as yet unclassified' stamp: 'edc 4/27/2004 14:58'!
addClient
^ addClient! !

!TEGServer methodsFor: 'as yet unclassified' stamp: 'edc 4/29/2004 11:44'!
addClient: t1 
	| t2 instanciaTEG |
	t2 _ NetNameResolver stringFromAddress: t1 remoteAddress.
	Transcript show: t2;
		 tab.
	Transcript show: t1 getData;
		 cr.
	activeClient _ activeClient + 1.
	socketList
		at: t2
		ifAbsent: [socketList at: activeClient put: t1].
	activeClient = 3
		ifTrue: [instanciaTEG _ ActiveWorld submorphs
						detect: [:t | t class == TEGMain].
			instanciaTEG socketList: self socketList]! !

!TEGServer methodsFor: 'as yet unclassified'!
port: t1 
	port _ t1! !

!TEGServer methodsFor: 'as yet unclassified' stamp: 'edc 4/27/2004 11:56'!
ringLoop
	| t1 t2 t3 instanciaTEG elPais estadoTEG losPaises losPaisesData |
	instanciaTEG _ ActiveWorld submorphs
				detect: [:t | t class == TEGMain].
	[true]
		whileTrue: [activeClient _ activeClient \\ 2 + 1.
			t1 _ socketList at: activeClient.
			(t1 isValid
					and: [t1 isConnected])
				ifTrue: [instanciaTEG activeSocket: t1.

estadoTEG _ OrderedCollection new.
					estadoTEG add: instanciaTEG losJugadores.
					estadoTEG add: instanciaTEG cartasOrden.
					estadoTEG add: instanciaTEG ronda.
					estadoTEG add: instanciaTEG numCarta.
					estadoTEG add: instanciaTEG cambiosTotales.
					losPaises _ Array new: 42.
					1
						to: 42
						do: [:pais | 
							elPais _ instanciaTEG submorphs at: pais.
							losPaisesData _ Array new: 2.
							losPaisesData at: 1 put: elPais ejercitos.
							losPaisesData at: 2 put: elPais deQuienSoy.
							losPaises at: pais put: losPaisesData].
					estadoTEG add: losPaises.
					t1 sendObject: estadoTEG.
					[t1 dataAvailable] whileFalse.
					instanciaTEG askMyData.
					self halt.
					t3 _ NetNameResolver stringFromAddress: t1 remoteAddress.
					Transcript show: t3;
						 tab.
					Transcript show: t2 printString;
						 cr.
					self halt]]! !

!TEGServer methodsFor: 'as yet unclassified' stamp: 'edc 4/27/2004 15:10'!
socketList
^ socketList! !

!TEGServer methodsFor: 'as yet unclassified' stamp: 'edc 4/26/2004 15:34'!
start
	| listener |
	socketList _ Dictionary new.
	activeClient _ 0.
	addClient _ true.
	listener _ TcpListener
				on: 8000
				handler: [:socket | addClient
						ifTrue: [self addClient: socket]].
	listener
		forkAndListenWhile: [addClient].
	! !

!TEGServer methodsFor: 'as yet unclassified' stamp: 'edc 4/27/2004 09:02'!
stop
	Socket  allInstancesDo: [ :i | i closeAndDestroy].
 socketList  _ nil.
 self becomeForward: nil! !

"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

TEGServer class
	instanceVariableNames: ''!

!TEGServer class methodsFor: 'defaults'!
defaultPort
	^ 8000! !

!TEGServer class methodsFor: 'defaults'!
priority
	^ Processor lowIOPriority! !

!TEGServer class methodsFor: 'defaults'!
start
	Transcript open.
	Transcript show: 'TEGServer starting...';
		 cr.
	^ self startOn: self defaultPort! !


!TEGServer class methodsFor: 'running'!
startOn: t1 
	^ self new port: t1;
		 start! !

!TEGServer class methodsFor: 'running'!
stop
	self
		allInstancesDo: [:t1 | t1 stop]! !


ImageMorph subclass: #TEGStartButton
	instanceVariableNames: ''
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Morphic-TEG'!

!TEGStartButton methodsFor: 'menu'!
addMenuItemsTo: t1 hand: t2 
	| t3 |
	t3 _ MenuMorph new.
	t3 color: Color blue.
	t3
		color: (t3 color alpha: 0.5).
	t3
		add: 'Soy server'
		target: TEGMain
		action: #startAsServer.
	t3
		add: 'Soy cliente '
		target: TEGMain
		action: #startAsCliente.
	t3 items
		do: [:t4 | t4 color: Color yellow;
				
				font: (StrikeFont
						familyName: 'Comic Bold'
						size: 18
						emphasized: 1)].
	t3 invokeModal! !


!TEGStartButton methodsFor: 'event handling'!
handlesMouseDown: t1 
	^ true! !

!TEGStartButton methodsFor: 'event handling'!
mouseDown: t1 
	| t2 |
	t1 yellowButtonPressed
		ifFalse: [^ t1 hand waitForClicksOrDrag: self event: t1].
	t2 _ MenuMorph new defaultTarget: self.
	self addMenuItemsTo: t2 hand: t1 hand.
	t2 popUpEvent: t1 in: self world! !


More information about the Squeak-dev mailing list