Tvůrce webu je i pro tebe! Postav třeba web. Bez grafika. Bez kodéra. Hned.
wz

12. Hlavní program

Dostáváme se k závěru programu. Naplňte soubor PROGRAM.ASM následujícím obsahem:


; ============================================================================
;
;                       VEGASLOT - Slot Machine Game
; This program requires no system. It can be loaded with linear boot sector.
;
; ============================================================================

;%define	NOVESA			; uncomment this for test VGA graphic
;%define	DEBUG			; uncomment this to print DEBUG
;%define 	FAST			; uncomment this to fast turning
;%define	NOSOUND			; uncomment this to disable sound

; ------------- Constants

StackSize	equ	0x2000		; stack size (paragraph aligned)

; ------------- EXE file header

SECTION		.text

		org	0

%ifdef DOS
EXEStart:	db	4Dh,5Ah		; EXE file signature
		dw	AllocSize % 512
		dw	(AllocSize + 511) / 512
		dw	0		; number of relocation entries
		dw	EXEHead/16	; header size in paragraphs
		dw	StackSize/16+4	; min extra memory
		dw	StackSize/16+4	; max extra memory
		dw	AllocSize/16	; initial SS
		dw	StackSize	; initial SP
		dw	0		; checksum
		dw	Start		; initial IP
		dw	-EXEHead/16	; initial CS
		dw	0		; file offset of the relocation table
		dw	0		; overlay number
		align	16,db 0
EXEEnd:
EXEHead		equ	(EXEEnd - EXEStart) ; EXE head size
%else
EXEHead		equ	0
%endif

; ------------- Macros

%include	"MACROS.ASM"		; macros

; ----------------------------------------------------------------------------
;             Start of program at 0080:0000 (or CS:0020 in case of EXE program)
; ----------------------------------------------------------------------------

; ------------- Identification

Start:		jmp	Init

Ident		dw	8A25h		; identification word

; ------------- Init segments

Init:		cli			; disable interrupts
		mov	ax,cs		; AX <- program segment
		mov	ds,ax		; DS <- program segment
		add	ax,(Graphics - Start + EXEHead)/16 ; add code size
		mov	[GraphSeg],ax	; segment with VGA graphics
		mov	word [GraphOff],BMPData ; offset with VGA graphics
		add	ax,DataSize/16	; add graphics size
		mov	ss,ax		; SS <- stack segment
		mov	sp,StackSize	; SP <- end of stack
		sti			; enable interrupts

; ------------- Init random generator

		call	RandomInit	; init random generator

; ------------- Install new interrupt handlers

		call	IntInit		; install interrupt handlers

; ------------- Push old videomode

		mov	ah,0fh		; AH <- function code
		call	Int10		; call Int 10h interrupt
		mov	[OldVMode],al	; store old video mode

; ------------- Init Graphics

		call	InitGraph	; init graphics
		jnc	GameStart	; game start

; ------------- Error, quit program

		mov	ah,0		; AH <- function code
		mov	al,[OldVMode]	; AL <- old video mode
		call	Int10		; call Int 10h interrupt

; ------------- No VGA, display error message

		mov	si,ErrorNoVGA	; error text - cannot find VGA card
		call	DispText	; display error message

; ------------- Wait for a key press

		call	InChar		; input character from keyboard

; ------------- End program/Repeat booting

Quit:		call	IntTerm		; deinstall interrupt handlers
%ifdef	DOS
		mov	ax,4C00h
		int	21h
%else
		int	19h		; repeat booting
%endif
; ------------- Game init

GameStart:	call	GameInit	; game init
		jmp	NextKey		; jey input

; ------------- Find next turn

NextTurn:	mov	dl,[WinLines]	; number of win lines
		call	GetPos		; get new reel position
		DebugPosition bx	; debug display position
		DebugMode		; debug display winning mode

; ------------- Flag, that it is HIGH game

		mov	byte [LastHigh],0 ; flag, it is not HIGH game
		cmp	word [BetBank],0; is it HIGH game?
		je	Turn1		; it is not HIGH game
		mov	byte [LastHigh],1 ; flag, it is HIGH game
		
; ------------- Subtract bet

Turn1:		call	SubBet		; subtract bet
		DebugGameIn		; debug display Game-In
		DebugGameProfit		; debug display Profit

; ------------- Turn reels

		push	dx		; push DX
		mov	dl,111b		; direction down
		cmp	word [Bonus],0	; is it bonus game?
		je	Turn2		; it is normal game
		mov	dl,0		; direction up for bonus game
Turn2:		mov	dh,1		; whole turns
		call	TurnReels	; animation
		pop	dx

; ------------- Test win

		call	TestSymbol	; test symbols
		call	GetPrize	; get prize of win
		or	ax,ax		; is any win?
		jnz	Win2		; it is a win
		jmp	NextKey		; it is not win

; ------------- Calculate HIGH game

Win2:		cmp	word [Bonus],0	; is it bonus game?
		jne	Win3		; it is bonus game
		cmp	byte [LastHigh],1; is it HIGH game?
		jne	Win3		; it is not HIGH game
		mov	dx,4		; multiple for HIGH game
		mul	dx		; AX <- win for HIGH game

; ------------- Limit win

Win3:		cmp	ax,MAXWIN	; maximal win for bonus game
		jbe	Win4		; win is OK
		add	[Bonus],ax	; push bonus
		mov	ax,MAXWIN	; limit win
		call	DrawBet		; draw new bet

; ------------- Win indication and transfer win to bank (BX=reels, AX=win)

Win4:		call	WinInd		; win indication

; ------------- Substract win from bonus

		cmp	word [Bonus],0	; is it bonus game?
		je	Win5		; it is not bonus game
		sub	[Bonus],ax	; decrease remaining bonus
		ja	Win5		; remains some bonus
		mov	word [Bonus],0	; no bonus remains
		call	DrawBet		; draw new bet

; ------------- Count debug Game-Out

Win5:
%ifdef DEBUG
		add	[GameOut],ax	; add debug Game-Out
		DebugGameOut		; debug display Game-Out
		DebugGameProfit		; debug display Profit
%endif
; ------------- Risk (AX=win)

		call	DoRisk		; risk and transfer win
                call	FlushChar	; flush keyboard buffer
		
; ------------- Wait for key input

NextKey:	DebugBonus		; debug display bonus
		call	SetKeys		; set state of all keys
		cmp	byte [AutoStart],1 ; is it AutoStart?
		jne	NextKey5	; it is not AutoStart
		call	TestChar	; test character
		jc	KeyStart2	; no character, AutoStart
		call	FlushChar	; flush keyboard
		mov	byte [AutoStart],0 ; set autostart off
		call	SetKeys		; set state of all keys
NextKey5:	call	InChar		; input character from keyboard

; Key control:
;         Tab=Toss/Bank <-BS=Refill/Credit
;       Esc=Cash Space=Start/Auto Enter=Bet

; ------------- Tab: Toss or Bank

KeyToss:	cmp	al,9		; is it Tab character?
		jne	KeyRefill	; it is not Tab character
		call	FlushChar	; flush keyboard
		call	DoToss		; toss service
		call	FlushChar	; flush keyboard buffer
		jmp	short NextKey	; input next character

; ------------- BS: Refill or credit

KeyRefill:	cmp	al,8		; is it BS character?
		jne	KeyCash		; it is not BS character
		call	FlushChar	; flush keyboard
		mov	ax,RefillSound	; AX <- refill sound
		call	PlaySound	; play sound
		mov	ax,10		; add credit
		call	SetCredit	; set new credit
KeyRefill9:	jmp	short NextKey	; input new character

; ------------- Esc: Cash or Quit

KeyCash:	cmp	al,27		; is it Esc character?
		jne	KeyStart	; it is not Esc character
		call	FlushChar	; flush keyboard
		call	DoCash		; cash service
%ifdef DOS
		jnc	KeyRefill9	; input next character
		mov	ah,0		; AH <- function code
		mov	al,[OldVMode]	; AL <- old video mode
		call	Int10		; call Int 10h interrupt
		jmp	Quit		; quit the program
%else
		jmp	short KeyRefill9; input next character
%endif
; ------------- Space: Next turn

KeyStart:	cmp	al,32		; is it Space?
		jne	KeyBet		; it is not Space
		call	TestChar	; is next character?
		jc	KeyStart2	; it is not next character
		call	InChar		; AX <- input next character
		cmp	al,32		; is it Space?
		jne	KeyStart2	; it is not Space
		mov	byte [AutoStart],1 ; set autostart on
KeyStart2:	call	FlushChar	; flush keyboard buffer
		cmp	word [Bonus],0	; is it bonus game?
		jne	KeyStart4	; it is bonus game
		mov	al,[Bet]	; current bet
		cmp	al,0		; is any bet?
		je	KeyRefill9	; there is no credit
KeyStart4:	jmp	NextTurn	; next turn

; ------------- Enter: Bet

KeyBet		cmp	al,13		; is it Enter character?
   		jne	KeyBet8		; it is not Enter character
		call	FlushChar	; flush keyboard
		cmp	word [Bonus],0	; is it bonus game?
		jne	KeyBet8		; it is bonus game
		mov	ax,BetSound	; AX <- bet sound
		call	PlaySound	; play sound
		mov	al,[Bet]	; AL <- current bet
		mov	ah,al		; AH <- push current bet
KeyBet2:	inc	ax		; increase bet
		cmp	al,6		; is it max. bet?
		jbe	KeyBet3		; bet is OK
		mov	al,1		; overflow to 1
KeyBet3:	call	SetBet		; set new bet
		cmp	ah,[Bet]	; did bet change?
		jne	KeyBet8		; bet changed
		cmp	al,ah		; is it original bet?
		jne	KeyBet2		; try next bet
KeyBet8:	jmp	NextKey		; input new character

; ----------------------------------------------------------------------------
;                             Game init
; ----------------------------------------------------------------------------
; INPUT:	DS = data segment
; ----------------------------------------------------------------------------

; ------------- Push registers

GameInit:	push	ax		; push AX
		push	bx		; push BX

; ------------- Set typematic rate key generation

		mov	ax,305h		; AX <- function code
		mov	bx,104h		; BL <- rate 20, BH <- delay 500ms
		int	16h		; set typematic rate

; ------------- Game init

		call	DispGraph	; display background image
		call	RedrawReels	; redraw all reels
		call	DrawCredit	; draw credit
		call	DrawBet		; draw bet
		call	DrawWin		; draw win
		call	DrawBank	; draw bank
		mov	al,11111b	; switch all bulbs on
		call	SetBulbs	; set bulbs

; ------------- Display debug informations

		DebugPosition 0		; debug display position
		DebugMode		; debug display winning mode
		DebugGameIn		; debug display Game-In
		DebugGameOut		; debug display Game-Out
		DebugGameProfit		; debug display Profit

; ------------- Key init

		call	KeyInit		; key init
		call	DrawKeys	; draw keys

; ------------- Pop registers

		pop	bx		; pop BX
		pop	ax		; pop AX
		ret

; ----------------------------------------------------------------------------
;                          Cash service
; ----------------------------------------------------------------------------
; INPUT:	DS = data segment
; OUTPUT:	CY = quit the program (only if DOS mode)
; ----------------------------------------------------------------------------

; ------------- Push registers

DoCash:		push	ax		; push AX

; ------------- Transfer Bank to Credit

		mov	ax,[Bank]	; AX <- current bank value
		or	ax,ax		; is there any bank to transfer?
		jz	DoCash5		; there is no bank to transfer
		cmp	ax,100		; test maximal value to transfer
		jbe	DoCash2		; there is less than maximum
		mov	ax,100		; limit maximal value
DoCash2:	call	SetCredit	; set new credit
		neg	ax		; negative value
		call	SetBank		; set new bank
		jmp	short DoCash8

; ------------- Cash money from Credit

DoCash5:	mov	ax,[Credit]	; AX <- current credit value
		or	ax,ax		; is any credit to cash?
		stc			; flag - quit the program
		jz	DoCash9		; it is no credit
		cmp	ax,100		; maximal value
		jbe	DoCash6		; there is less than maximum
		mov	ax,100		; limit maximal value
DoCash6:	neg	ax		; negative value
		call	SetCredit	; set new credit

; ------------- Play cash sound

DoCash8:	mov	ax,CashSound	; AX <- cash sound
		call	PlaySound	; play sound
		clc			; flag - no quit

; ------------- Pop registers

DoCash9:	pop	ax		; pop AX
		ret

; ----------------------------------------------------------------------------
;                          Toss service
; ----------------------------------------------------------------------------
; INPUT:	DS = data segment
; ----------------------------------------------------------------------------

; ------------- Push registers

DoToss:		push	ax		; push AX
		push	cx		; push CX

; ------------- Play toss sound

		mov	ax,TossSound	; AX <- toss sound
		call	PlaySound	; play toss sound

; ------------- Start toss mode

		mov	byte [Tossing],1 ; set toss mode on
		mov	byte [AutoStart],0 ; set autostart off

; ------------- Test, if there is enough credit

DoToss1:	mov	ax,[BetCredit]	; AX <- bet from credit
		or	ax,ax		; is any bet?
		jz	DoToss12	; there is no bet
		cmp	ax,[Credit]	; is there enough credit?
		jbe	DoToss2		; it is enough credit
DoToss12:	jmp	DoToss9		; low credit, stop tossing

; ------------- Minimal time of one game

DoToss2:	mov	cx,16		; minimal time 0.8 sec		

; ------------- Flush keys (not in AutoStart mode)

		cmp	byte [AutoStart],1 ; is it AutoStart?
		je	DoToss3		; it is AutoStart
		call	FlushChar	; flush keyboard buffer

; ------------- Redraw keys (due to Autostart blinking)

DoToss3:	call	SetKeys		; set keys

; ------------- Draw random number in Bet field

		call	Random		; AX <- random generator
		and	al,7		; AL = value 0 to 7
		inc	ax		; AL = value 1 to 8
		call	DrawBetChar	; draw bet character

; ------------- Short delay (50 msec about)

		mov	ax,7		; time to wait
		call	WaitTime	; wait for a short time

; ------------- Minimal time of one game

		jcxz	DoToss4		; minimal time is OK
		loop	DoToss3		; next waiting		

; ------------- Test, if a key is pressed

DoToss4:	call	TestChar	; test character
		jnc	DoToss42	; there is any character

; ------------- AutoStart service

		cmp	byte [AutoStart],1 ; is it AutoStart?
		je	DoToss5		; AutoStart
		jmp	short DoToss3	; no character was pressed

; ------------- Input character

DoToss42:	call	InChar		; AX <- input character

; ------------- Space: Toss next value

		cmp	al,32		; is it Space?
		jne	DoToss8		; it is not Space
		mov	byte [AutoStart],0 ; set autostart off

; ------------- Test autostart on (more spaces during minimal time)

		call	TestChar	; is next character?
		jc	DoToss5		; it is not next character
		call	InChar		; AX <- input next character
		cmp	al,32		; is it Space?
		jne	DoToss5		; it is not Space
		mov	byte [AutoStart],1 ; set autostart on
		call	FlushChar	; flush keyboard buffer

; ------------- Subtract credits

DoToss5:	mov	ax,[BetCredit]	; AX <- bet from credit
		neg	ax		; AX = -credit
		call	SetCredit	; set new credit

; ------------- Draw random number in Bet field

		call	Random		; AX <- random generator
		and	al,7		; AL = value 0 to 7
		inc	ax		; AL = value 1 to 8
		call	DrawBetChar	; draw bet character

; ------------- Test, if there is a win (=even number)

		test	al,1		; is it win?
		jz	DoToss6		; it is a win

; ------------- It is loss (odd number)

		mov	ax,TossLossSound ; sound of loss
		call	PlaySound	; play sound
		xor	ax,ax		; AX <- 0
		jmp	short DoToss7	; set win

; ------------- It is win (even number)

DoToss6:	mov	ax,TossWinSound	; sound of win
		call	PlaySound	; play sound
		mov	ax,[BetCredit]	; AX <- bet from credit
		shl	ax,1		; AX <- double
		call	SetBank		; add win to bank

; ------------- Display win

DoToss7:	call	SetWin		; set win
		mov	cx,10		; number of loops
DoToss72:	call	SetKeys		; set keys
		mov	ax,7		; delay (50 msec about)
		call	WaitTime	; wait for a short time
		loop	DoToss72	; next wait
		xor	ax,ax		; AX <- 0
		call	SetWin		; clear win
		jmp	DoToss1		; next toss

; ------------- Tab: Stop tossing

DoToss8:	cmp	al,9		; is it Tab character?
		je	DoToss9		; Tab character, stop tossing
		jmp	DoToss3		; it is not Tab character

; ------------- Flush Tab keys

DoToss9:	call	FlushChar	; flush keyboard buffer

; ------------- Play toss sound

		mov	ax,TossSound	; AX <- toss sound
		call	PlaySound	; play toss sound

; ------------- Stop toss mode

		mov	byte [AutoStart],0 ; set autostart off
		mov	byte [Tossing],0 ; set toss mode off
		call	SetKeys		; set keys

; ------------- Redraw valid bet value

		call	DrawBet		; draw valid bet value

; ------------- Pop registers

		pop	cx		; pop CX
		pop	ax		; pop AX
		ret

; ----------------------------------------------------------------------------
;                            Subtract bet
; ----------------------------------------------------------------------------
; INPUT:	DS = data segment
; ----------------------------------------------------------------------------

; ------------- Push registers

SubBet:		push	ax		; push AX

; ------------- Is it bonus game?

		cmp	word [Bonus],0	; is it bonus game?
		jne	SubBet2		; it is bonus game

; ------------- Subtract bet from credits

		mov	ax,[BetCredit]	; bet from credits
%ifdef DEBUG
		add	[GameIn],ax	; add debug Game-In
%endif
		neg	ax		; AX = -credit
		call	SetCredit	; set new credit

; ------------- Subtract bet from bank

		mov	ax,[BetBank]	; bet from bank
%ifdef DEBUG
		add	[GameIn],ax	; add debug Game-In
%endif
		neg	ax		; AX = -bank
		call	SetBank		; set new bank

; ------------- Pop registers

SubBet2:	pop	ax		; pop AX
		ret

; ----------------------------------------------------------------------------
;                              Win indication
; ----------------------------------------------------------------------------
; INPUT:	AX = win
;		BX = reel position
;		DS = data segment
; ----------------------------------------------------------------------------

; ------------- Push registers

WinInd:		push	ax		; push AX
		push	cx		; push CX
		push	dx		; push DX
		push	bp		; push BP

; ------------- Play win sound

		push	ax		; push AX
		mov	ax,WinSound	; win sound
		call	PlaySound	; play win sound
		pop	ax		; pop AX

; ------------- Prepare wining lines (-> DH)

		mov	dl,11111b	; DL <- winning lines mask
		mov	cl,5		; CL <- max. winning lines
		sub	cl,[WinLines]	; CL <- complement to max.
		shr	dl,cl		; DL <- winning lines mask
		call	TestSymbol	; test winning symbol
		and	dh,dl		; mask real winning lines

; ------------- Win blinking

		mov	cx,8		; CX <- number of blinks
WinInd2:	push	ax		; push AX (win)
		call	SetWin		; set win
		mov	al,dh		; AL <- winning lines
		call	SetBulbs	; set winning bulbs
%ifndef FAST
		mov	ax,7		; 50 ms about
		call	WaitTime	; wait for a short time
%endif
		xor	ax,ax		; AX <- 0
		call	SetWin		; set win to 0
		call	SetBulbs	; switch all bulbs off
%ifndef FAST
		mov	ax,7		; 50 ms about
		call	WaitTime	; wait for a short time
%endif
		pop	ax		; pop AX (win)
		loop	WinInd2		; next blink

		mov	al,11111b	; AL <- all bulbs on
		call	SetBulbs	; switch all bulbs on

; ------------- Pop registers

		pop	bp		; pop BP
		pop	dx		; pop DX
		pop	cx		; pop CX
		pop	ax		; pop AX
		ret

; ----------------------------------------------------------------------------
;                               Risk
; ----------------------------------------------------------------------------
; INPUT:	AX = win
;		DS = data segment
; DESTROY:	AX (win is invalid)
; ----------------------------------------------------------------------------

; ------------- Push registers

DoRisk:		push	cx		; push CX
		push	dx		; push DX
		push	di		; push DI

; ------------- AutoStart

		cmp	byte [AutoStart],1 ; is AutoStart?
		jne	DoRisk1		; it is not AutoStart
		xor	di,di		; no win reamins
		mov	dl,1		; transfer to bank
		call	WinTrans	; transfer win to bank
		jmp	DoRisk9		; return

; ------------- Set risk flag

DoRisk1:	mov	byte [Risking],1 ; set flag of risk inprogress
		call	SetKeys		; set state of all keys

; ------------- Push current win

		xchg	ax,di		; BX <- current win

; ------------- It is not second half of win

DoRisk2:	mov	byte [RiskHalf],0 ; it is not second half of win

; ------------- Test, if it is any win

DoRisk22:	or	di,di		; is any win?
		jz	DoRisk9		; there is no win

; ------------- Test if risk start is enabled

		mov	byte [RiskEnable],1 ; risk is enabled
		cmp	di,MAXWIN/2	; can we do risk?
		jbe	DoRisk3		; we can do risk
		mov	byte [RiskEnable],0 ; risk is disabled

; ------------- Display new win value or clear

DoRisk3:	mov	ax,di		; AX <- current win
        	test	byte [AutoStartTime],20h ; test blink win
		jz	DoRisk4		; win is shining
		xor	ax,ax		; AX <- clear win
DoRisk4:	call	SetWin		; display current win

; ------------- Display key state

		call	SetKeys		; set state of all keys

; ------------- Test and input key		

		call	TestChar	; test character
		jc	DoRisk3		; there is no character
		call	InChar		; input character

; ------------- Bank key

		mov	dl,1		; transfer to bank
		cmp	al,9		; is it bank?
		je	DoRisk5		; it is bank

; ------------- Credit key

		cmp	al,8		; is it credit?
		jne	DoRisk7		; it is not credit
		mov	dl,0		; transfer to credit

; ------------- Do win transfer

DoRisk5:	mov	ax,di		; AX <- current win
		cmp	byte [RiskHalf],1 ; is half risk?
		je	DoRisk6		; it is half risk
		cmp	ax,10		; minimal value
		jbe	DoRisk6		; it is too low value
		shr	ax,1		; AX <- half risk
		mov	byte [RiskHalf],1 ; it is half risk	
DoRisk6:	sub	di,ax		; decrease remainging risk
		call	WinTrans	; transfer win to bank or to credit
		jmp	short DoRisk22	; continue

; ------------- Start key

DoRisk7:	cmp	al,32		; is it start?
		jne	DoRisk3		; it is not start
		cmp	byte [RiskEnable],1 ; is risk enabled?
		jne	DoRisk3		; risk is not enabled

; ------------- Risk

		call	Random		; random generator
		test	ax,1		; is win?
		jz	DoRisk8		; is lost

; ------------- Risk win

		mov	ax,RiskWinSound	; AX <- risk win sound
		call	PlaySound	; play sound
		shl	di,1		; double win
		jmp	short DoRisk2	; next risk		

; ------------- Risk loss

DoRisk8:	mov	ax,RiskLostSound ; AX <- risk lost sound
		call	PlaySound	; play sound
		shr	di,1		; half win
		cmp	di,10		; minimal win
		jb	DoRisk9		; lost all win
		jmp	DoRisk2		; next risk

; ------------- Stop risk

DoRisk9:	xor	ax,ax		; AX <- 0 no win remains
		call	SetWin		; clear win

; ------------- Reset risk flag

		mov	byte [Risking],0 ; reset flag of risk in progress
		call	SetKeys		; set state of all keys

; ------------- Pop registers

		pop	di		; pop DI
		pop	dx		; pop DX
		pop	cx		; pop CX
		ret

; ----------------------------------------------------------------------------
;                       Transfer win to bank or to credit
; ----------------------------------------------------------------------------
; INPUT:	AX = win
;		DL = 1 to bank, 0 to credit
;		DI = remaining win
;		DS = data segment
; ----------------------------------------------------------------------------

; ------------- Push registers

WinTrans:	push	ax		; push AX
		push	bx		; push BX
		push	cx		; push CX

; ------------- Play trasnfer sound

		push	ax		; push AX
		mov	ax,TransSound	; AX <- transfer sound
		call	PlaySound	; play sound
		pop	ax		; pop AX

; ------------- Prepare value for one transfer (-> BX)

		mov	bx,2		; transfer 2 in one step
		cmp	ax,20		; is it 20 or less?
		jbe	WinTrans2	; it is 20 or less
		mov	bl,5		; transfer 5 in one step
		cmp	ax,50		; is it 50 or less?
		jbe	WinTrans2	; it is 50 or less
		mov	bl,10		; transfer 10 in one step
		cmp	ax,100		; is it 100 or less?
		jbe	WinTrans2	; it is 100 or less
		mov	bl,20		; transfer 20 in one step
		cmp	ax,200		; is it 200 or less?
		jbe	WinTrans2	; it is 200 or less
		mov	bl,50		; transfer 50 in one step
WinTrans2:	xchg	ax,cx		; CX <- remainging value

; ------------- Transfer win to bank or to credit

WinTrans3:	mov	ax,bx		; AX <- value to transfer
		cmp	ax,cx		; is it OK?
		jbe	WinTrans4	; it is OK
		mov	ax,cx		; AX <- limit value to transfer
WinTrans4:	sub	cx,ax		; CX <- decrease win
		or	dl,dl		; transfer to bank?
		jnz	WinTrans5	; transfer to bank
		call	SetCredit	; add to credit
		jmp	short WinTrans6
WinTrans5:	call	SetBank		; add to bank
WinTrans6:	mov	ax,cx		; AX <- remainging value
		add	ax,di		; AX <- reaminging win
		call	SetWin		; decrease win
%ifndef FAST
		mov	ax,15		; 100 ms about
		call	WaitTime	; wait for a short time
%endif
		or	cx,cx		; is it all?
		jnz	WinTrans3	; transfer next win

; ------------- Pop registers

		pop	cx		; pop CX
		pop	bx		; pop BX
		pop	ax		; pop AX
		ret

; ----------------------------------------------------------------------------
;                               Wait some time
; ----------------------------------------------------------------------------
; INPUT:	AX = number of clock ticks (aprox. 7 ms)
; ----------------------------------------------------------------------------

; ------------- Push registers

WaitTime:	push	ax		; push AX
		push	cx		; push CX

; ------------- Load new time

		xchg	ax,cx		; CX <- number of ticks
		jcxz	WaitTime3	; no waiting
WaitTime1:	mov	al,[cs:Int08Next] ; next Int 08h counter
		
; ------------- Wait for next pulse

		sti			; set interrupt
WaitTime2:	cmp	al,[cs:Int08Next] ; is it same pulse?
		je	WaitTime2	; wait for clock pulse

; ------------- Next pulse

		loop	WaitTime1	; next pulse

; ------------- Pop registers

WaitTime3:	pop	cx		; pop CX
		pop	ax		; pop AX
		ret

; ----------------------------------------------------------------------------
;                Input character from keyboard (wait for input)
; ----------------------------------------------------------------------------
; OUTPUT:	AL = ASCII character
;		AH = SCAN code
; ----------------------------------------------------------------------------

InChar:		mov	ah,10h		; AH <- function code
		int	16h		; input character
		ret

; ----------------------------------------------------------------------------
;                      Test character from keyboard
; ----------------------------------------------------------------------------
; OUTPUT:	AL = ASCII character (or 0 if no character)
;		AH = SCAN code (or 0 if no character)
;		CY = no character (then AL,AH=0)
; ----------------------------------------------------------------------------

TestChar:	mov	ah,11h		; AH <- function code
		int	16h		; test character
		clc			; clear flag - character is ready
		jnz	TestChar2	; character is ready
		xor	ax,ax		; AX <- 0 no character
		stc			; set flag - no character
TestChar2:	ret

; ----------------------------------------------------------------------------
;                Flush keyboard buffer
; ----------------------------------------------------------------------------

; ------------- Push registers

FlushChar:	push	ax		; push AX

; ------------- Flush characters

FlushChar2:	call	TestChar	; test character from keyboard
		jc	FlushChar3	; no character is ready
		call	InChar		; input character
		jmp	short FlushChar2 ; flush next character

; ------------- Pop registers

FlushChar3:	pop	ax		; pop AX
		ret

; ----------------------------------------------------------------------------
;                          Set cursor position
; ----------------------------------------------------------------------------
; INPUT:	DL = column
;		DH = row
; ----------------------------------------------------------------------------

; ------------- Push registers

SetCursor:	push	ax		; push AX
		push	bx		; push BX

; ------------- Set cursor position

		mov	ah,2		; AH <- 2 function code
		mov	bh,0		; page
		call	Int10		; call Int 10h

; ------------- Pop registers

		pop	bx		; pop BX
		pop	ax		; pop AX
		ret

; ----------------------------------------------------------------------------
;                        Display number with BIOS
; ----------------------------------------------------------------------------
; INPUT:	AX = number
; ----------------------------------------------------------------------------

; ------------- Push registers

DispNum:	push	ax		; push AX
		push	bx		; push BX
		push	cx		; push CX
		push	dx		; push DX

; ------------- Convert number to digits

		mov	bx,10		; BX <- 10 divider
		xor	cx,cx		; CX <- 0 counter
DispNum2:	xor	dx,dx		; DX <- 0 number HIGH
		div	bx		; divide number with 10
		push	dx		; push character in DL
		inc	cx		; increment counter in CX
		or	ax,ax		; was it last digit?
		jnz	DispNum2	; convert next digit

; ------------- Display digits

DispNum3:	pop	ax		; AL <- digit
		add	al,"0"		; AL <- convert to character
		call	DispChar	; display character
		loop	DispNum3	; display next digit

; ------------- Pop registers

		pop	dx		; pop DX
		pop	cx		; pop CX
		pop	bx		; pop BX
		pop	ax		; pop AX
		ret

; ----------------------------------------------------------------------------
;                           Display text with BIOS
; ----------------------------------------------------------------------------
; INPUT:	CS:SI = error message ASCIIZ (ends with zero)
; ----------------------------------------------------------------------------

; ------------- Push registers

DispText:	push	ax		; push AX
		push	si		; push SI
		push	ds		; push DS

; ------------- Display text
	
		cld			; set direction up
		push	cs		; push CS
		pop	ds		; DS <- program segment with texts
DispText2:	lodsb			; AL <- load next character from DS:SI
		or	al,al		; AL == 0? is it end of text?
		jz	DispText3	; it is end of text
		call	DispChar	; display character in AL
		jmp	short DispText2	; next character

; ------------- Pop registers

DispText3:	pop	ds		; pop DS
		pop	si		; pop SI
		pop	ax		; pop AX
		ret

; ----------------------------------------------------------------------------
;                        Display one character with BIOS
; ----------------------------------------------------------------------------
; INPUT:	AL = character to display
; ----------------------------------------------------------------------------

; ------------- Push registers

DispChar:	push	ax		; push AX
		push	bx		; push BX
		push	cx		; push CX
		push	dx		; push DX

; ------------- Display character

		mov	ah,0eh		; AH <- 0Eh function code
		mov	bx,7		; BL <- color of text, BH <- page 0
		call	Int10		; call Int 10h
%ifdef DEBUG
		mov	word [VESAMap],0ffffh ; undefined VESA current page
%endif
; ------------- Pop registers

		pop	dx		; pop DX
		pop	cx		; pop CX
		pop	bx		; pop BX
		pop	ax		; pop AX
		ret

; ----------------------------------------------------------------------------
;                            Init random generator
; ----------------------------------------------------------------------------

;  ------------ Push registers

RandomInit:	push	ax		; push AX
		push	ds		; push DS

; ------------- Init random generator

		xor	ax,ax		; AX <- 0
		mov	ds,ax		; DS <- 0
		mov	ax,[46ch]	; AX <- timer LOW
		mov	[cs:RandSeed],ax; random seed LOW
		mov	ax,[46ch+2]	; AX <- timer HIGH
		mov	[cs:RandSeed+2],ax ; random seed HIGH

; ------------- Pop registers

		pop	ds		; pop DS
		pop	ax		; pop AX
		ret

; ----------------------------------------------------------------------------
;                           Random generator
; ----------------------------------------------------------------------------
; OUTPUT:	AX = random number
; ----------------------------------------------------------------------------

RandSeed:	dd	5623489		; random seed
RandCoef1:	dd	214013		; random coefficient 1
RandCoef2:	dd	2531011		; random coefficient 2

; General algorithm (new_number = old_number*coef1 + coef2) for the random
; function is taken from interpreted BASIC and is described in Microsoft
; Knowledgebase article Q28150. Other possible coefficients are:
; 214013/2531011, 17405/10395331, 214013/13737667, 214013/10395331

; ------------- Push registers

Random:		push	bx		; push BX
		push	cx		; push CX
		push	dx		; push DX
		push	ds		; push DS

; ------------- Prepare registers

		push	cs		; push CS
		pop	ds		; DS <- CS

; ------------- New random seed (randseed = randseed * coef1 + coef2)

		mov	ax,[RandSeed]	; AX <- random seed LOW
		push	ax		; push AX
		mul	word [RandCoef1]; * coef1 LOW
		xchg	ax,bx		; BX <- push multiple LOW
		mov	cx,dx		; CX <- push multiple HIGH
		pop	ax		; pop AX
		mul	word [RandCoef1+2] ; * coef HIGH
		add	cx,ax		; add multiple LOW
		mov	ax,[RandSeed+2]	; AX <- random seed HIGH
		mul	word [RandCoef1]; * coef1 LOW
		add	ax,cx		; AX <- multiple HIGH
		add	bx,[RandCoef2]	; + coef2 LOW
		adc	ax,[RandCoef2+2]; + coef2 HIGH
		mov	[RandSeed],bx	; new random seed LOW
		mov	[RandSeed+2],ax	; new random seed HIGH

; ------------- Pop registers (AX=new random seed HIGH)

		pop	ds		; pop DS
		pop	dx		; pop DX
		pop	cx		; pop CX
		pop	bx		; pop BX
		ret

; ----------------------------------------------------------------------------
;                         Initialize interrupts
; ----------------------------------------------------------------------------

; ------------- Push registers

IntInit:	push	ax		; push AX
		push	dx		; push DX
		push	ds		; push DS

; ------------- Prepare registers

		cli			; disable interrupts
		xor	ax,ax		; AX <- 0
		mov	ds,ax		; DS <- 0

; ------------- Install Int 08h handler

		mov	ax,[8*4]	; old handler LOW
		mov	[cs:Old08],ax	; save old handler LOW
		mov	ax,[8*4+2]	; old handler HIGH
		mov	[cs:Old08+2],ax	; save old handler HIGH
		mov	word [8*4],Int08; new offset of Int 08h
		mov	[8*4+2],cs	; new segment of Int 08h

; ------------- Turn off diskette motor

		mov	dx,3f2h		; floppy control port
		mov	al,0ch		; AL <- control byte
		out	dx,al		; turn off diskette motor
		and	byte [43fh],0f0h ; turn off motor runnings bits

; ------------- Set clock rate to 1/8 (e.g. 1193182/8192=145.652 Hz, 7 ms)

		mov	al,34h		; AL <- command code
		out	43h,al		; set command for rate setting
		mov	al,0		; AL <- rate LOW
		out	40h,al		; set rate LOW
		mov	al,32		; AL <- rate HIGH
		out	40h,al		; set rate HIGH

; ------------- Enable interrupts

		sti			; enbale interrupts

; ------------- Pop registers

		pop	ds		; pop DS
		pop	dx		; pop DX
		pop	ax		; pop AX
		ret

; ----------------------------------------------------------------------------
;                         Deinitialize interrupts
; ----------------------------------------------------------------------------

; ------------- Push registers

IntTerm:	push	ax		; push AX
		push	ds		; push DS

; ------------- Prepare registers

		cli			; disable interrupts
		xor	ax,ax		; AX <- 0
		mov	ds,ax		; DS <- 0

; ------------- Return clock rate

		mov	al,34h		; AL <- command code
		out	43h,al		; set command for rate setting
		mov	al,0		; AL <- rate LOW
		out	40h,al		; set rate LOW
		out	40h,al		; set rate HIGH

; ------------- Return old Int 08h handler

		mov	ax,[cs:Old08]	; old handler LOW
		mov	[8*4],ax	; return old handler LOW
		mov	ax,[cs:Old08+2]	; old handler HIGH
		mov	[8*4+2],ax	; return old handler HIGH

; ------------- Enable interrupts

		sti			; enbale interrupts

; ------------- Pop registers

		pop	ds		; pop DS
		pop	ax		; pop AX
		ret

; ----------------------------------------------------------------------------
;                                 Includes
; ----------------------------------------------------------------------------

%include	"GAME.ASM"		; game services
%include	"GAMETAB.INC"		; winning tables
%include	"GRAPHIC.ASM"		; graphic
%include	"REELS.ASM"		; reels
%include	"DIGITS.ASM"		; digits
%include	"KEYS.ASM"		; keys
%include	"SOUND.ASM"		; sound

; ------------- Added graphics

SECTION		.text

		align	16
Graphics:

AllocSize	equ	(Graphics - Start) + DataSize

; ----------------------------------------------------------------------------
;          Uninitialized data (60 KB area in place of VGA graphics)
; ----------------------------------------------------------------------------

SECTION		.bss

Tento soubor je jakousi "omáčkou" završující celý program. Obsahuje ovládání programu, jeho inicializace a veškeré ostatní globální funkce. Začněme od nejjednodušších funkcí - funkce WaitTime. Ta slouží ke vkládání prodlev do programu. Funkce testuje změnu pomocné proměnné Int08Next, dekrementované obsluhou Int08, a čeká na požadovaný počet 7 ms kroků.

Funkce WinTrans je obsluha převedení výhry nebo její části do banku nebo do kreditu. Funkce provede převod animovaně po malých částkách.

Funkce DoRisk je obsluha risku. Je-li během hry vyhrána nějaká výhra, předá se výhra této funkci. Hráč má možnost převést výhru (nebo její část) do banku nebo do kreditu, popř. může o hru losovat v riskové hře. Rozhodne-li se pro risk (klávesa mezerník), je výhra náhodně buď zdvojnásobena nebo hráč o polovinu hry přijde. Při částce menší než 10 risk končí. Při částce větší než 750/2 není povoleno hrát riskovou hru, hráč může pouze výhru převádět. Výhra může být převáděna po částech. Po prvním stisku klávesy pro převod se převede pouze polovina výhry, po druhém stisku druhá polovina a risková hra končí. Losuje-li hráč risk, je možné po losování opět převést první polovinu výhry.

Funkce WinInd je indikace výhry. Během obsluhy indikace bliká výhra v poli "Win" a také blikají žárovky na výherních liniích.

Funkce SubBet odečte sázku od banku a kreditů po odstartování jedné hry. Během bonusové hry se sázka neodečítá (bonusová hra je zdarma).

Funkce DoToss je hra "Sudá+Lichá". Během této hry v poli displeje "Bet" problikávají náhodné číslice. Hráč hraje stiskem klávesy mezerníku. Při každé hře se mu odečte z kreditů částka odpovídající sázce. Vylosuje-li sudé číslo, vyhrává dvojnásobek sázky, výhra je mu připsána do banku. Výhernost v této hře je 100%. V praxi se tato hra používá k "převodu" kreditů do banku, aby hráč mohl hrát "Horní hru". Ve funkci je zajištěn požadavek vyplývající ze zákona, že délka jedné hry musí být minimálně 1 sekunda. Je-li během losování podržena klávesa mezerníku, je aktivován autostart, automat pokračuje ve hře dále i bez držení klávesy. Režim autostartu je indikován blikajícím textem klávesy mezerníku. Vypnutí autostartu je možné opětovným stiskem mezerníku. Spuštění i ukončení hry je možné stiskem klávesy Tab.

DoCash je obsluha výběru peněz klávesou Esc. Je-li obsah banku nenulový, převádí se při každém stisku klávesy Esc částka 100 z banku do kreditů. Je-li obsah banku nulový, vyplácí se hráči peníze hopperem (a protože hopper nemáme obsluhovaný, pouze se kredity snižují o hodnotu 100). Je-li obsah kreditů nulový, ukončí program (platí pouze pro DOS verzi).

GameInit je inicializace programu. Funkce je zavolána při startu programu. Obsahuje nastavení rychlosti klávesnice, zobrazení pozadí grafiky, překreslení válců, překreslení digitálních displejů, nastavení žárovek, zobrazení ladících informací a překreslení kláves.

Hlavní funkce začíná na návěští Init. Obsahuje inicializaci segmentových registrů, inicializaci generátoru náhody (podle čítače času), instalaci obsluh přerušení, inicializaci grafiky, herní inicializaci programu, čekání na stisk klávesy. Je-li aktivován autostart, je automaticky spuštěna hra jako při stisku mezerníku. Při stisku klávesy Tab se spustí hra losování "Sudá+Lichá" (funkce DoToss). Klávesa <-BackSpace slouží k vložení kreditů do automatu. Klávesou Esc je možné vyplácet. Klávesa Enter mění výšku sázky. Výše sázky je limitována množstvím kreditů a banku.

Mezerníkem se odstartuje hra. Pokud během otáčení válců je mezerník chvíli podržen, aktivuje se autostart, při kterém probíhá automatické spouštění dalších her a namísto riskové hry se výhra vždy převádí do banku. Autostart je indikovaný blikáním textu klávesy mezerníku. Ukončení autostartu je možné opětovným stiskem mezerníku.

Losování další hry začíná na návěští NextTurn. Pozice válců je vygenerována voláním funkce GetPos. Neprobíhá-li bonusová hra, je odečtena sázka. Po ukončení otáčení válců je cílová pozice vyhodnocena. Pokud se jednalo o výhru, je v případě horní hry výhra vynásobena násobícím koeficientem (4x). Je-li výhra vyšší než 750, je výše výhry omezena na 750 a přesahující část výhry je uschována do bonusové hry. Následuje indikace výhry a odečtení výhry od bonusu, pokud se jednalo o bonusovou hru. V závěru je spuštěna risková hra, ve které může hráč výhru uložit do banku nebo do kreditů nebo o ni hrát v riskové hře.

Na začátku souboru je připraveno několik přepínačů, které umožňují překládat program s modifikacemi. NOVESA zabrání použití VESA rozhraní, je tak možné otestovat VGA grafiku i na počítači s VESA rozhraním. Přepínač DEBUG zobrazí interní ladící informace. Ve spolupráci s následujícím přepínačem, FAST, který aktivuje zrychlenou hru bez prodlev, je možné testovat statistiku výhernosti automatu. Statistika dosáhne výhernosti předepsaných 94% až při větším počtu her, proto se doporučuje test zahájit s kredity alespoň 5000. Přepínač NOSOUND zakáže použití zvuku.

Download zdrojového kódu programu VEGASLOT

Zpět na aplikaci VEGASLOT