123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835836837838839840841842843844845846847848849850851852853854855856857858859860861862863864865866867868869870871872873874875876877878879880881882883884885886887888889890891892893894895896897898899900901902903904905906907908909910911912913914915916917918919920921922923924925926927928929930931932933934935936937938939940941942943944945946947948949950951952953954955956957958959960961962963964965966967968969970971972973974975976977978979980981982983984985986987988989990991992993994995996997998999100010011002100310041005100610071008100910101011101210131014101510161017101810191020102110221023102410251026102710281029103010311032103310341035103610371038103910401041104210431044104510461047104810491050105110521053105410551056105710581059106010611062106310641065106610671068106910701071107210731074107510761077107810791080108110821083108410851086108710881089109010911092109310941095109610971098109911001101110211031104110511061107110811091110111111121113111411151116111711181119112011211122112311241125112611271128112911301131113211331134113511361137113811391140114111421143114411451146114711481149115011511152115311541155115611571158115911601161116211631164116511661167116811691170117111721173117411751176117711781179118011811182118311841185118611871188118911901191119211931194119511961197119811991200120112021203120412051206120712081209 |
- ;
- ; 2048 For DOS
- ;
- ; Copyright (C) 2017 Aleksandar Andrejevic <theflash@sdf.lonestar.org>
- ;
- ; This program is free software: you can redistribute it and/or modify
- ; it under the terms of the GNU Affero General Public License as
- ; published by the Free Software Foundation, either version 3 of the
- ; License, or (at your option) any later version.
- ;
- ; This program is distributed in the hope that it will be useful,
- ; but WITHOUT ANY WARRANTY; without even the implied warranty of
- ; MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
- ; GNU Affero General Public License for more details.
- ;
- ; You should have received a copy of the GNU Affero General Public License
- ; along with this program. If not, see <http://www.gnu.org/licenses/>.
- ;
- ; NASM Support for anonymous labels:
- %assign __anon_label_num__ 0
- %macro @@ 0-1+
- ..@__anon_label__ %+ __anon_label_num__ %+ %1
- %assign __anon_label_prev__ __anon_label_num__
- %assign __anon_label_num__ __anon_label_num__ + 1
- %endmacro
- %idefine @f ..@__anon_label__ %+ __anon_label_num__
- %idefine @b ..@__anon_label__ %+ __anon_label_prev__
- org 0x100 ; DOS COM Format Executable
- ;**********************************************************************************************************************
- ;
- ; DEFINITIONS
- ;
- ;**********************************************************************************************************************
- VIDEO_SEGMENT EQU 0xA000
- WIDTH EQU 80 ; The width of the screen, in characters
- HEIGHT EQU 480 ; The height of the screen, in pixels
- FIELD_MARGIN EQU 1
- FOUR_THRESHOLD EQU 0x1A1A
- FIELD_ORIGIN EQU FIELD_MARGIN * 8 * WIDTH + FIELD_MARGIN
- FIELD_SIZE EQU HEIGHT / 8 - 2 * FIELD_MARGIN
- ;**********************************************************************************************************************
- ; Macro: vsync
- ;
- ; Parameters: none
- ; Returns: nothing
- ; Trashes: FLAGS
- ; Description: Waits for the vertical retrace interval to start and then end.
- ;**********************************************************************************************************************
- %macro vsync 0
- push ax
- push dx
- mov dx, 0x3DA
- @@: in al, dx ; Loop until the bit becomes set
- and al, 0x08
- jz @b
- @@: in al, dx ; Loop again until it clears
- and al, 0x08
- jnz @b
- pop dx
- pop ax
- %endmacro
- ;**********************************************************************************************************************
- ;
- ; CODE SEGMENT
- ;
- ;**********************************************************************************************************************
- section code progbits align=2
- cpu 286 ; 16-bit Real Mode 286-compatible
- bits 16
- ;**********************************************************************************************************************
- ; Subroutine: start
- ;
- ; Parameters: none
- ; Returns: nothing
- ;**********************************************************************************************************************
- start: cld ; Clear the direction flag
- call uncompress
- mov ah, 0x2A ; Get the current date
- int 0x21
- mov word [random_seed], cx ; Store it as the random seed
- mov word [random_seed + 2], dx
- mov ah, 0x2C ; Get the current time
- int 0x21
- xor word [random_seed], cx ; XOR it onto the random seed
- xor word [random_seed + 2], dx
- push 0x40 ; Load the BDA segment into ES
- pop es
- mov al, byte [es:0x49] ; Save the current video mode
- mov byte [previous_mode], al
- mov ax, 0x0012 ; Switch to mode 12h (640x480x4@60Hz)
- int 0x10
- .restart: push ds ; Load our data segment into ES
- pop es
- mov ax, 0x1002 ; Load the AC palette
- xor bx, bx
- mov dx, palette
- int 0x10
- mov ax, 0x1012 ; Load the DAC palette
- mov cx, 16
- mov dx, palette_colors
- int 0x10
- xor ax, ax
- mov word [score], ax ; Reset the score
- mov word [score + 2], ax
- mov byte [score + 4], al
- mov cx, 8
- mov di, field
- rep stosw ; Clear the field
- push VIDEO_SEGMENT ; Load the video segment into ES
- pop es
- mov dx, 0x3C4 ; Write to all planes
- mov ax, 0x0F02
- out dx, ax
- call redraw_score
- mov di, FIELD_ORIGIN
- xor ax, ax
- not ax
- .draw_field: mov cx, FIELD_SIZE / 2
- rep stosw ; Fill
- add di, WIDTH - FIELD_SIZE
- cmp di, WIDTH * (HEIGHT - FIELD_MARGIN * 8)
- jb .draw_field
- mov dx, 0x3C4 ; Write to plane 0
- mov ax, 0x0102
- out dx, ax
- xor ax, ax ; AX = 0x0000
- mov di, FIELD_ORIGIN
- .draw_vertical: stosw ; Draw 5 vertical bars
- %rep 4
- add di, 96 / 8
- stosw
- %endrep
- add di, WIDTH - FIELD_SIZE
- cmp di, WIDTH * (HEIGHT - FIELD_MARGIN * 8)
- jb .draw_vertical
- mov di, FIELD_ORIGIN
- mov cx, 0x05FF
- .draw_horizontal:
- times FIELD_SIZE / 2 stosw ; Draw 5 horizontal bars
- add di, WIDTH - FIELD_SIZE
- sub cl, 0x10
- jnc .draw_horizontal
- add di, WIDTH * 96
- dec ch
- jnz .draw_horizontal
- call create ; Create an initial square
- .turn: call check_over ; Check if the game is over
- or ax, ax
- jnz .game_over
- call create ; Create a new square
- call check_over ; Check if the game is over (again!)
- or ax, ax ; This is important because creating a new
- jnz .game_over ; ... tile can change the game.
- .keystroke: xor ah, ah ; Wait for a keystroke
- int 0x16
- cmp ah, 0x01 ; Escape
- jz .quit
- @@: cmp ah, 0x48 ; Up Arrow
- jnz @f
- mov dl, 2
- call move_tiles
- or al, al
- jnz .turn
- jmp .keystroke
- @@: cmp ah, 0x4B ; Left Arrow
- jnz @f
- mov dl, 0
- call move_tiles
- or al, al
- jnz .turn
- jmp .keystroke
- @@: cmp ah, 0x4D ; Right Arrow
- jnz @f
- mov dl, 1
- call move_tiles
- or al, al
- jnz .turn
- jmp .keystroke
- @@: cmp ah, 0x50 ; Down Arrow
- jnz @f
- mov dl, 3
- call move_tiles
- or al, al
- jnz .turn
- @@: jmp .keystroke
- .game_over: mov ax, 0x1C1C
- mov dx, 0xA01C
- js @f
- mov ax, 0xFFFF
- @@: call fade_to_color
- vsync
- mov si, game_over_bg
- mov di, 0x3706
- mov cx, 0x8030
- mov bl, 1
- call draw_pattern
- inc bl
- mov si, game_over
- call draw_pattern
- @@: xor ah, ah ; Wait for a reply
- int 0x16
- cmp ah, 0x15 ; 'Y' pressed
- jz .restart
- cmp ah, 0x31 ; 'N' pressed
- jz .quit
- jmp @b
- .quit: xor ah, ah
- mov al, byte [previous_mode] ; Restore the previous mode
- int 0x10
- ret ; Exit
- ;**********************************************************************************************************************
- ; Subroutine: uncompress
- ;
- ; Parameters: none
- ; Returns: nothing
- ; Trashes: AX, CX, DX, BX, SI, DI, FLAGS
- ; Description: Uncompresses the textures
- ;**********************************************************************************************************************
- uncompress: mov si, compressed_data
- mov di, tiles
- mov cx, word [compressed_length]
- mov dx, 0xFE00 ; Start with zeros
- xor bh, bh
- .loop: lodsb ; Read a compressed byte
- add al, al ; Fetch the actual run length
- mov bl, al
- mov ax, dx
- mov dx, word [run_length_table + bx]
- .append: sahf ; Set CF to the lowest bit of AH
- adc al, al ; Push that bit into AL
- sub ah, 0x20 ; Less space remains in our bit buffer
- jnc @f ; Is it full?
- stosb ; Then flush it
- @@: dec dx
- jnz .append
- mov dx, ax
- xor dh, 1 ; Toggle the bit we're appending
- loop .loop
- mov ax, dx ; Check if the buffer has something left
- cmp ah, 0xFE
- jnc @f
- xor dh, dh ; Calculate how many more we need to shift
- mov dl, ah
- shr dl, 5
- inc dl
- inc cx ; Make sure it doesn't loop again
- jmp .append
- @@: ret
- ;**********************************************************************************************************************
- ; Subroutine: create
- ;
- ; Parameters: none
- ; Returns: nothing
- ; Trashes: AX, CX, DX, BX, SI, DI, FLAGS
- ; Description: Creates a new tile and adds it to the game.
- ;**********************************************************************************************************************
- create: push es
- push ds
- pop es
- mov bx, field
- mov di, bx
- xor al, al
- mov cx, 16
- repnz scasb
- pop es
- jz .random_empty
- ret
- .random_empty: call random ; Get a random number in DX:AX
- %rep 4
- mov si, ax ; Load the low 4 bits of AX into SI
- and si, 0x000F
- mov di, dx ; And the low 4 bits of DX into DI
- and di, 0x000F
- cmp byte [bx + si], 0 ; Is field number SI free?
- jz .found_low ; Then use that
- cmp byte [bx + di], 0 ; Is field number DI free?
- jz .found_high ; Then use that
- shr ax, 4 ; If neither, shift both by 4 and try again
- shr dx, 4
- %endrep
- jmp .random_empty ; All random bits exhausted, start over
- .found_low: mov di, si ; Make sure the field number is in DI
- .found_high: push di ; We'll need it later
- mov cl, 1 ; Create a 2 tile there
- call random ; Check if it should be a 4
- cmp ax, FOUR_THRESHOLD
- jae @f
- inc cl ; If so, make it a 4
- @@: mov byte [bx + di], cl ; Store it in the field array
- mov ah, 13 ; Get the appropriate plane mask
- sub ah, cl
- mov dx, 0x3C4 ; Select the plane mask
- mov al, 0x02
- out dx, ax
- mov bx, di
- mov si, word [field_coords + bx + di] ; Get the coordinates of the tile
- xor ax, ax
- mov dx, 0x0FF0 ; Pattern: 1111000000001111
- xor ch, ch
- xor bh, bh
- %assign i 0
- %rep 12
- %assign offset 44 * WIDTH + 5 - i * 4 * WIDTH - (i >> 1)
- vsync
- lea di, [si + offset]
- mov bl, (i + 1) << 3 ; The number of lines
- @@: mov byte [es:di], dl ; Draw the pattern's first half
- inc di
- %if i > 1
- mov cl, i >> 1
- rep stosw ; Draw the area in between
- %endif
- mov byte [es:di], dh ; Draw the pattern's second half
- add di, WIDTH - (i | 1) ; Next scanline
- dec bl
- jnz @b
- xor dx, 0x0FF0 ; Flip the sides of the pattern
- %assign i i + 1
- %endrep
- pop di ; Grab the saved field number
- xor al, al
- mov ah, byte [field + di] ; Get the value of the field
- add ah, ah
- add ax, tiles - 0x200
- mov si, ax
- mov bx, di
- mov di, word [field_coords + bx + di] ; Get the video offset
- add di, 16 * WIDTH + 2 ; Move 16x16 pixels right and down
- mov cx, 0x4008
- mov bl, 1
- jmp draw_pattern
- ;**********************************************************************************************************************
- ; Subroutine: random
- ;
- ; Parameters: none
- ; Returns: DX:AX - a 32-bit random number
- ; Trashes: FLAGS
- ;**********************************************************************************************************************
- random: push cx
- mov ax, word [random_seed] ; Load the 32-bit random seed into DX:AX
- mov dx, word [random_seed + 2]
- mov ch, dl ; DX:AX ^= DX:AX << 13
- mov cl, ah
- shl cx, 5
- xor dx, cx
- xor ch, ch
- mov cl, al
- shr cl, 3
- xor dx, cx
- mov ch, al
- xor cl, cl
- shl ch, 5
- xor ax, cx
- mov cx, dx ; DX:AX ^= DX:AX >> 17
- shr cx, 1
- xor ax, cx
- mov cx, dx ; DX:AX ^= DX:AX << 5
- shl cx, 5
- xor dx, cx
- xor ch, ch
- mov cl, ah
- shr cl, 3
- xor dx, cx
- mov cx, ax
- shl cx, 5
- xor ax, cx
- mov word [random_seed], ax ; Save DX:AX as the new random seed
- mov word [random_seed + 2], dx
- pop cx
- ret
- ;**********************************************************************************************************************
- ; Subroutine: build_movement_list
- ;
- ; Parameters: ES:DI - a pointer to the list that should be filled
- ; DL - direction (0 - left, 1 - right, 2 - up, 3 - down)
- ; Returns: AX - the size of the list, in bytes
- ; Trashes: FLAGS
- ; Description: Creates a list of movements. Each entry is 16-bit and contains four 4-bit values that correspond to the
- ; new value, old value, new location, and old location, in that order (from MSB to LSB)
- ;**********************************************************************************************************************
- build_movement_list: push bp ; Setup a stack frame
- mov bp, sp
- xor ax, ax
- times 8 push ax ; Reserve memory for the movement table:
- ; Each entry is such that the lower 4 bits
- ; keep the new location and the higher 4
- ; bits keep the new value for any given
- ; tile.
- push dx
- push bx
- push si
- mov bx, move_slice_back
- test dl, 1 ; Towards the front or back?
- jz @f
- mov bx, move_slice_front
- @@: test dl, 2 ; By row or by column?
- jnz .columns
- %assign i 0
- %rep 4
- mov ax, word [field + %+ i] ; Load the entire row into DX:AX
- mov dx, word [field + 2 + %+ i]
- call bx
- and ax, 0xF3F3 ; Store the proper row numbers
- and dx, 0xF3F3
- %if i > 0
- or ax, i | (i << 8)
- or dx, i | (i << 8)
- %endif
- mov word [bp - 16 + %+ i], ax ; Store the changes
- mov word [bp - 16 + 2 + %+ i], dx
- %assign i i + 4
- %endrep
- jmp .prepare_list
- .columns:
- %assign i 0
- %rep 4
- mov al, byte [field + %+ i] ; Load the entire column into DX:AX
- mov ah, byte [field + 4 + %+ i]
- mov dl, byte [field + 8 + %+ i]
- mov dh, byte [field + 12 + %+ i]
- call bx
- and ax, 0xFCFC ; Store the proper column numbers
- and dx, 0xFCFC
- %if i > 0
- or ax, i | (i << 8)
- or dx, i | (i << 8)
- %endif
- mov byte [bp - 16 + %+ i], al ; Store the changes
- mov byte [bp - 16 + 4 + %+ i], ah
- mov byte [bp - 16 + 8 + %+ i], dl
- mov byte [bp - 16 + 12 + %+ i], dh
- %assign i i + 1
- %endrep
- .prepare_list: mov bx, di ; Save DI
- mov si, -16
- .fill_list: mov ah, byte [field + si + 16] ; Read the tile value
- or ah, ah
- jz @f ; Skip blank tiles
- mov dx, si ; Store the current location into AL
- and dx, 0x000F
- mov al, dl
- mov dl, byte [bp + si] ; Read the change entry
- shl dx, 4 ; Shift the new location into the top 4 of DL
- shl dh, 4 ; and the new value into the top 4 of DH
- or ax, dx ; Form the list entry
- mov dx, ax ; Make a copy of it
- rol dl, 4 ; Swap the old / new values
- rol dh, 4
- cmp ax, dx ; Did it change it all?
- jz @f ; No, so there is no change - skip it
- stosw ; Yes, append it to the list
- @@: inc si
- jnz .fill_list
- xchg bx, di ; Restore DI
- sub bx, di ; Calculate the list size
- mov ax, bx
- pop si
- pop bx
- pop dx
- leave
- ret
- ;**********************************************************************************************************************
- ; Subroutine: move_slice_back
- ;
- ; Parameters: DX:AX - the contents of the row/column
- ; Returns: DX:AX - an entry for the movement table
- ; Trashes: FLAGS
- ; Description: Moves a row or column towards the back.
- ;**********************************************************************************************************************
- move_slice_back: push cx
- push bx
- mov cx, ax
- mov bx, dx
- shl cx, 4 ; Store the values into the upper 4 bits
- shl bx, 4 ; and put the numbers into the lower 4 bits
- or ch, 0x05 ; Note that the row number and the column
- or bx, 0x0F0A ; number are the same at this point
- or al, al
- jz .second
- cmp al, ah ; Are the first two the same?
- jnz @f
- xor al, al
- add ch, 0x10
- jmp .third ; We can't merge the second one again
- @@: or ah, ah
- jnz @f ; There is a tile in between, skip
- cmp al, dl ; Are the first and third the same?
- jnz @f
- xor al, al
- add bl, 0x10
- jmp .slide ; No more merging
- @@: or ah, ah
- jnz .second
- or dl, dl
- jnz .third
- cmp al, dh ; Are the first and fourth the same?
- jnz .slide ; No, so nothing can be merged
- xor al, al
- add bh, 0x10
- jmp .slide ; No more merging either way
- .second: or ah, ah
- jz .third
- cmp ah, dl ; Are the middle two the same?
- jnz @f ; If not, we can try the second and fourth
- xor ah, ah
- add bl, 0x10
- jmp .slide
- @@: or dl, dl
- jnz .third
- cmp ah, dh ; Are the second and fourth the same?
- jnz .slide ; If not, we can't merge anything
- xor ah, ah
- add bh, 0x10
- jmp .slide
- .third: or dl, dl
- jz .slide
- cmp dl, dh ; Are the final two the same?
- jnz .slide ; If not, nothing can be merged
- xor dl, dl
- add bh, 0x10
- .slide: or al, al ; Is the first blank?
- jnz @f
- sub ch, 5 ; Move the remaining three one step back
- sub bx, 0x0505
- @@: or ah, ah
- jnz @f
- sub bx, 0x0505 ; Move the final two one step back
- @@: or dl, dl
- jnz @f
- sub bh, 5 ; Move the last tile one step back
- @@: mov ax, cx
- mov dx, bx
- pop bx
- pop cx
- ret
- ;**********************************************************************************************************************
- ; Subroutine: move_slice_front
- ;
- ; Parameters: DX:AX - the contents of the row/column
- ; Returns: DX:AX - an entry for the movement table
- ; Trashes: FLAGS
- ; Description: Moves a row or column towards the front.
- ;**********************************************************************************************************************
- move_slice_front: push cx
- push bx
- mov cx, ax
- mov bx, dx
- shl cx, 4 ; Store the values into the upper 4 bits
- shl bx, 4 ; and put the numbers into the lower 4 bits
- or ch, 0x05 ; Note that the row number and the column
- or bx, 0x0F0A ; number are the same at this point
- or dh, dh
- jz .third
- cmp dh, dl ; Are the last two the same?
- jnz @f
- xor dh, dh
- add bl, 0x10
- jmp .second ; We can't merge the third one again
- @@: or dl, dl
- jnz @f ; There is a tile in between, skip
- cmp dh, ah ; Are the second and fourth the same?
- jnz @f
- xor dh, dh
- add ch, 0x10
- jmp .slide ; No more merging
- @@: or dl, dl
- jnz .third
- or ah, ah
- jnz .second
- cmp dh, al ; Are the first and fourth the same?
- jnz .slide ; No, so nothing can be merged
- xor dh, dh
- add cl, 0x10
- jmp .slide ; No more merging either way
- .third: or dl, dl
- jz .second
- cmp dl, ah ; Are the middle two the same?
- jnz @f ; If not, we can try the first and third
- xor dl, dl
- add ch, 0x10
- jmp .slide
- @@: or ah, ah
- jnz .second
- cmp dl, al ; Are the first and the third the same?
- jnz .slide ; If not, we can't merge anything
- xor dl, dl
- add cl, 0x10
- jmp .slide
- .second: or ah, ah
- jz .slide
- cmp ah, al ; Are the first two the same?
- jnz .slide ; If not, nothing can be merged
- xor ah, ah
- add cl, 0x10
- .slide: or dh, dh ; Is the fourth blank?
- jnz @f
- add cx, 0x0505 ; Move the first three one step forward
- add bl, 5
- @@: or dl, dl ; Is the third blank?
- jnz @f
- add cx, 0x0505 ; Move the first two one step forward
- @@: or ah, ah ; Is the second blank?
- jnz @f
- add cl, 5 ; Move the first tile one step forward
- @@: mov ax, cx
- mov dx, bx
- pop bx
- pop cx
- ret
- ;**********************************************************************************************************************
- ; Subroutine: move_tiles
- ;
- ; Parameters: DL - direction (0 - left, 1 - right, 2 - up, 3 - down)
- ; Returns: AX - the number of tiles moved
- ; Trashes: CX, DX, BX, SI, DI, FLAGS
- ; Description: Moves all the tiles in a certain direction, possibly combining some of them.
- ;**********************************************************************************************************************
- move_tiles: push bp
- mov bp, sp
- sub sp, 32 ; Reserve memory for the tiles list
- mov di, sp ; Point DI to the list
- push es ; Save ES
- push ss ; Load the stack segment into ES
- pop es
- call build_movement_list ; Build the list of movements
- pop es ; Restore ES
- push ax ; Push the list size
- or ax, ax
- jnz @f
- leave ; If the list is empty, exit early
- ret
- @@: mov dh, dl ; Calculate the change in position
- and dh, 1 ; Get the direction
- jnz @f
- dec dh ; If it's a 0, it should be -1
- @@: mov cl, dl
- and cl, 2
- shl dh, cl ; Multiply it by 4 if it's vertical
- mov di, field
- xor bh, bh
- mov si, word [bp - 34] ; Get the list size
- @@: mov bl, byte [bp - 34 + si] ; Read the location byte
- and bl, 0x0F ; Find the old location of this entry
- mov byte [bx + di], bh ; Clear the tile
- sub si, 2
- jnz @b
- mov cx, dx ; Save DX
- mov dx, 0x3C4
- mov ax, 0x0F02 ; Write to all planes
- out dx, ax
- mov dx, 0x3CE
- mov al, 0x05
- out dx, al
- inc dx
- in al, dx
- push ax ; Save the old write mode
- and al, 0xFE
- or al, 0x02 ; Write mode 2
- out dx, al
- mov dx, cx ; Restore DX
- .animation:
- %assign i 0
- %rep 4
- vsync
- mov si, word [bp - 34]
- .draw_frame %+ i: mov bx, word [bp - 34 + si]
- mov ax, bx
- rol al, 4
- cmp al, bl
- jz .next %+ i
- and ah, 0x0F
- add ah, 2 ; Get the palette index
- mov al, ah ; Duplicate it
- and bx, 0x000F
- add bx, bx
- mov di, word [field_coords + bx] ; Get the base coordinates of this field
- push dx ; Save DX
- cmp dl, 1
- jz .right %+ i
- cmp dl, 2
- jz .up %+ i
- cmp dl, 3
- jz .down %+ i
- .left %+ i: mov cl, 96
- %if i < 3
- sub di, (i + 1) * 4
- %else
- sub di, i * 4 + 2
- %endif
- mov dx, di
- @@: times 6 stosw
- %if i < 3
- mov word [es:di], 0x0F0F ; Field background
- mov word [es:di + 2], 0x0F0F
- %else
- mov word [es:di], 0x0E0E ; Border
- %endif
- add di, WIDTH - 12
- dec cl
- jnz @b
- jmp .pattern %+ i
- .right %+ i: mov cl, 96
- %if i < 3
- add di, (i + 1) * 4
- mov dx, di
- @@: mov word [es:di - 4], 0x0F0F ; Field background
- mov word [es:di - 2], 0x0F0F
- %else
- add di, i * 4 + 2
- mov dx, di
- @@: mov word [es:di - 2], 0x0E0E ; Border
- %endif
- times 6 stosw
- add di, WIDTH - 12
- dec cl
- jnz @b
- jmp .pattern %+ i
- .up %+ i: mov cl, 96
- %if i < 3
- sub di, 32 * (i + 1) * WIDTH
- %else
- sub di, (32 * i + 16) * WIDTH
- %endif
- mov dx, di
- @@: times 6 stosw
- add di, WIDTH - 12
- dec cl
- jnz @b
- push ax
- %if i < 3
- mov ax, 0x0F0F ; Field background
- mov cl, 32
- %else
- mov ax, 0x0E0E ; Border
- mov cl, 16
- %endif
- @@: times 6 stosw
- add di, WIDTH - 12
- dec cl
- jnz @b
- pop ax
- jmp .pattern %+ i
- .down %+ i: add di, i * 32 * WIDTH
- push ax
- %if i < 3
- lea dx, [di + 32 * WIDTH]
- mov ax, 0x0F0F ; Field background
- mov cl, 32
- %else
- lea dx, [di + 16 * WIDTH]
- mov ax, 0x0E0E ; Border
- mov cl, 16
- %endif
- @@: times 6 stosw
- add di, WIDTH - 12
- dec cl
- jnz @b
- pop ax
- mov cl, 96
- @@: times 6 stosw
- add di, WIDTH - 12
- dec cl
- jnz @b
- .pattern %+ i: mov di, dx
- pop dx ; Restore DX
- add di, 16 * WIDTH + 2
- add ah, ah ; Shift the palette entry to the left
- xor al, al ; by 9 places, in total
- add ax, tiles - 0x600 ; Get the tile address from that
- push cx
- push si
- mov cx, 0x4008
- mov si, ax
- mov bl, 1
- call draw_pattern
- pop si
- pop cx
- .next %+ i: sub si, 2
- jnz .draw_frame %+ i
- %assign i i + 1
- %endrep
- vsync
- xor cx, cx ; Count the number of updates
- mov si, word [bp - 34] ; Get the list size
- .update_loop: mov bx, word [bp - 34 + si] ; Read an entry from the list
- mov ax, bx ; Make a copy of it
- rol al, 4 ; Swap old/new
- cmp al, bl ; Did it change?
- jz @f ; If not, check if there was a merge
- add byte [bp - 34 + si], dh ; Update the table entry
- inc cx ; Increase the number of updates
- jmp .update_next
- @@: rol ah, 4 ; Swap old/new
- cmp ah, bh ; Did it change?
- jz .update_next ; If not, skip this
- push si ; Save SI
- mov al, bh ; Save the value in AL
- and ax, 0x0FF0 ; Take the new values of AL and AH
- or al, ah ; and store them in one byte
- mov byte [bp - 34 + si + 1], al ; Update the entry
- call increase_score
- and bx, 0x000F ; Extract the tile location
- add bx, bx
- mov di, word [field_coords + bx] ; Get the coordinates of the tile
- and ax, 0x0F00 ; Extract the new tile value
- mov si, ax ; Point SI to the pattern for this value
- add si, si
- add si, tiles - 0x200
- add ah, 2 ; Convert it into a palette index
- mov al, ah ; Duplicate it
- mov bx, di ; Save DI
- push cx ; Save CX
- mov cx, 96
- @@: times 6 stosw ; Redraw the square
- add di, WIDTH - 12
- loop @b
- lea di, [bx + 16 * WIDTH + 2] ; Restore DI and move it
- mov cx, 0x4008
- mov bl, 1
- call draw_pattern
- pop cx ; Restore CX
- pop si ; Restore SI
- .update_next: sub si, 2
- jnz .update_loop
- jcxz @f
- jmp .animation
- @@: mov dx, 0x3CE
- pop ax ; Restore the old write mode
- mov ah, al
- mov al, 0x05
- out dx, ax
- mov ax, word [bp - 34] ; Get the list size
- mov si, ax
- mov di, field
- .commit_changes: mov bx, word [bp - 34 + si] ; Read the whole entry
- shr bx, 4 ; Discard the old values
- mov dh, bh ; Get the new tile value
- and bx, 0x000F ; Find the new location
- mov dl, byte [bx + di] ; Read the value that is there
- cmp dl, dh ; Make sure it's not smaller
- jae @f
- mov byte [bx + di], dh ; And store the new tile value there
- @@: sub si, 2
- jnz .commit_changes
- shr al, 1 ; Return the number of list entries
- leave
- ret
- ;**********************************************************************************************************************
- ; Subroutine: draw_pattern
- ;
- ; Parameters: DS:SI - The pattern to write
- ; ES:DI - Destination (in video memory)
- ; CH - the pattern height, in pixels
- ; CL - the pattern width, in characters
- ; BL - the palette entry to use
- ; Returns: nothing
- ; Trashes: FLAGS
- ; Description: Draws a pattern on the screen
- ;**********************************************************************************************************************
- draw_pattern: pusha
- mov dx, 0x3C4
- mov ax, 0x0F02 ; Write to all planes
- out dx, ax
- mov dx, 0x3CE
- mov ah, bl
- xor al, al
- out dx, ax
- mov al, 0x05
- out dx, al
- inc dx
- in al, dx
- push ax ; Save the old write mode
- or al, 3 ; Write mode 3
- out dx, al
- xor bh, bh
- mov bl, cl
- .pattern_line: mov cl, bl
- @@: mov al, byte [es:di] ; Load the latch register
- movsb ; Write the bit pattern
- dec cl
- jnz @b
- add di, WIDTH
- sub di, bx
- dec ch
- jnz .pattern_line
- pop ax ; Restore the old write mode
- out dx, al
- popa
- ret
- ;**********************************************************************************************************************
- ; Subroutine: check_over
- ;
- ; Parameters: none
- ; Returns: AX - zero if the game is still in progress, positive if the player won, negative if the player lost
- ; Trashes: FLAGS
- ;**********************************************************************************************************************
- check_over: push bp
- mov bp, sp
- sub sp, 32 ; Allocate space for a dummy list
- push es
- push cx
- push dx
- push di
- push ss ; Load the stack segment into ES
- pop es
- mov di, field
- mov al, 11 ; We're searching for the 2048 tile
- mov cx, 16
- repnz scasb ; Search
- jnz @f ; Skip the next part if not found
- mov ax, 1 ; The player won!
- jmp .leave
- @@: xor dl, dl ; Check if moves are still possible
- lea di, [bp - 32]
- %rep 4
- call build_movement_list
- or ax, ax
- jz @f
- xor ax, ax ; Not over yet
- jmp .leave
- @@: inc dl ; Try another direction
- %endrep
- mov ax, -1 ; The player lost
- .leave: pop di
- pop dx
- pop cx
- pop es
- leave
- ret
- ;**********************************************************************************************************************
- ; Subroutine: increase_score
- ;
- ; Parameters: AL - the value of the newly formed tile
- ; Returns: nothing
- ; Trashes: FLAGS
- ;**********************************************************************************************************************
- increase_score: pusha
- push es
- push ds ; Load the data segment into ES
- pop es
- and ax, 0x000F ; Sanitize the input and clear AH
- dec al ; Make AL 0-based
- shl al, 2
- mov bx, ax
- mov dx, word [bcd_values + bx] ; Load the number we should add
- mov bx, word [bcd_values + bx + 2]
- mov si, score + 4
- mov di, si
- std ; Go backwards
- lodsb
- add al, bh
- aaa
- stosb
- lodsb
- adc al, bl
- aaa
- stosb
- lodsb
- adc al, dh
- aaa
- stosb
- lodsb
- adc al, dl
- aaa
- stosb
- lodsb
- adc al, 0
- aaa
- stosb
- cld ; The direction flag should be kept clear
- pop es
- call redraw_score
- popa
- ret
- ;**********************************************************************************************************************
- ; Subroutine: redraw_score
- ;
- ; Parameters: none
- ; Returns: nothing
- ; Trashes: AX, CX, DX, BX, SI, DI, FLAGS
- ;**********************************************************************************************************************
- redraw_score: mov si, score
- mov di, segment_coords
- mov bx, segment_display
- mov cx, 4
- xor dl, dl
- .draw_digit: mov ah, 1 ; Current bit
- lodsb
- or al, al ; Is this digit a zero?
- jnz @f ; Always print non-zeros
- jcxz @f ; Always print the rightmost digit
- or dl, dl ; Have we written a digit already?
- jz .draw_segments ; This is a leading zero, don't draw it
- @@: or dl, 1 ; Memorize that we have written one
- xlatb ; Convert the digit into a display mask
- .draw_segments: push cx
- push bx
- push si
- push di
- xor bl, bl
- test al, ah ; Should we print or clear?
- jz @f
- inc bl ; Print
- @@: mov di, word [di] ; Get the coordinates of this segment
- mov cx, 0x0804 ; Horizontal segments are 32x8
- mov si, horizontal_segment
- test ah, 0x36 ; Should it be vertical instead?
- jz @f
- mov cx, 0x2001 ; Vertical segments are 8x32
- mov si, vertical_segment
- @@: call draw_pattern
- pop di
- pop si
- pop bx
- pop cx
- add di, 2 ; Move to the next segment position
- add ah, ah
- jns .draw_segments ; Repeat until we've exhausted all 7
- sub cx, 1 ; Go to the next digit
- jnc .draw_digit
- ret
- ;**********************************************************************************************************************
- ; Subroutine: fade_to_color
- ;
- ; Parameters: AL - the red color channel of the destination color
- ; AH - the green color channel of the destination color
- ; DL - the blue color channel of the destination color
- ; DH - how much should we fade
- ; Returns: nothing
- ; Trashes: AX, CX, DX, BX, SI, DI, FLAGS
- ;**********************************************************************************************************************
- fade_to_color: push bp
- mov bp, sp
- sub sp, 120 ; Reserve memory
- push es ; Save ES
- push ss ; Load the stack segment into ES
- pop es
- shl ax, 2 ; Make the color channels 8-bit
- shl dl, 2
- mov word [bp - 42], ax ; Save them
- mov byte [bp - 40], dl
- mov si, palette_colors + 9
- lea di, [bp - 120]
- mov cx, 39
- @@: lodsb ; Read a 6-bit color value
- mov ah, al ; Shift it left 8 bits and make it 14-bit
- xor al, al
- stosw
- loop @b
- mov ch, dh
- shr ch, 2 ; We need our counter to be 6-bit
- .frame: vsync
- lea si, [bp - 120]
- lea di, [bp - 39]
- mov cl, 39
- @@: lodsw ; Read a 14-bit color value
- mov al, ah
- stosb ; Store the top 6 bits into the palette
- dec cl
- jnz @b
- push cx
- mov ax, 0x1012
- mov cx, 13
- lea dx, [bp - 39]
- mov bx, 3
- int 0x10 ; Change the DAC palette
- pop cx
- mov si, palette_colors + 9
- lea bx, [bp - 120]
- mov cl, 13
- xor dh, dh
- @@:
- %assign i 0
- %rep 3
- mov dl, byte [bp - 42 + i] ; Load the 8-bit destination color
- xor ah, ah
- lodsb ; Load the 6-bit source color
- shl al, 2 ; Make it 8-bit
- sub ax, dx ; Get the difference between the colors
- sub word [es:bx + i * 2], ax ; Subtract it from the 14-bit color
- %assign i i + 1
- %endrep
- add bx, 6
- dec cl
- jnz @b
- dec ch
- jnz .frame
- pop es
- leave
- ret
- ;**********************************************************************************************************************
- ;
- ; DATA SEGMENT
- ;
- ;**********************************************************************************************************************
- section data progbits align=2 follows=code
- palette: DB 0, 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13, 14, 15, 0
- palette_colors: DB 0x33, 0x33, 0x33 ; Background
- DB 0x08, 0x08, 0x08 ; Text
- DB 0x3F, 0x3F, 0x3F ; White
- DB 0x3B, 0x39, 0x36 ; 2
- DB 0x3B, 0x38, 0x32 ; 4
- DB 0x3C, 0x2C, 0x1E ; 8
- DB 0x3E, 0x3D, 0x3C ; 16
- DB 0x3D, 0x25, 0x18 ; 32
- DB 0x3D, 0x17, 0x0E ; 64
- DB 0x3B, 0x33, 0x1C ; 128
- DB 0x3B, 0x33, 0x18 ; 256
- DB 0x3B, 0x32, 0x14 ; 512
- DB 0x3B, 0x31, 0x0F ; 1024
- DB 0x3B, 0x30, 0x0B ; 2048
- DB 0x20, 0x20, 0x20 ; Field border
- DB 0x2A, 0x2A, 0x2A ; Field background
- field_coords: DW 0x0783, 0x0791, 0x079F, 0x07AD
- DW 0x2A83, 0x2A91, 0x2A9F, 0x2AAD
- DW 0x4D83, 0x4D91, 0x4D9F, 0x4DAD
- DW 0x7083, 0x7091, 0x709F, 0x70AD
- bcd_values: DB 0, 0, 0, 2
- DB 0, 0, 0, 4
- DB 0, 0, 0, 8
- DB 0, 0, 1, 6
- DB 0, 0, 3, 2
- DB 0, 0, 6, 4
- DB 0, 1, 2, 8
- DB 0, 2, 5, 6
- DB 0, 5, 1, 2
- DB 1, 0, 2, 4
- DB 2, 0, 4, 8
- segment_display: DB 0x3F, 0x06, 0x5B, 0x4F, 0x66 ; Seven-segment display bits
- DB 0x6D, 0x7D, 0x07, 0x7F, 0x6F
- segment_coords: DW 0x035C, 0x03FF, 0x0CBF, 0x14DC, 0x0CBC, 0x03FC, 0x0C1C
- DW 0x0360, 0x0403, 0x0CC3, 0x14E0, 0x0CC0, 0x0400, 0x0C20
- DW 0x0364, 0x0407, 0x0CC7, 0x14E4, 0x0CC4, 0x0404, 0x0C24
- DW 0x0368, 0x040B, 0x0CCB, 0x14E8, 0x0CC8, 0x0408, 0x0C28
- DW 0x036C, 0x040F, 0x0CCF, 0x14EC, 0x0CCC, 0x040C, 0x0C2C
- horizontal_segment: DB 0x01, 0xFF, 0xFF, 0x80
- DB 0x03, 0xFF, 0xFF, 0xC0
- DB 0x07, 0xFF, 0xFF, 0xE0
- DB 0x0F, 0xFF, 0xFF, 0xF0
- DB 0x0F, 0xFF, 0xFF, 0xF0
- DB 0x07, 0xFF, 0xFF, 0xE0
- DB 0x03, 0xFF, 0xFF, 0xC0
- DB 0x01, 0xFF, 0xFF, 0x80
- vertical_segment: DB 0x00, 0x00, 0x00, 0x00
- DB 0x10, 0x38, 0x7C, 0xFE
- DB 0xFE, 0xFE, 0xFE, 0xFE
- DB 0xFE, 0xFE, 0xFE, 0xFE
- DB 0xFE, 0xFE, 0xFE, 0xFE
- DB 0xFE, 0xFE, 0xFE, 0xFE
- DB 0xFE, 0x7C, 0x38, 0x10
- DB 0x00, 0x00, 0x00, 0x00
- run_length_table: DW 0x005A, 0x000B, 0x0031, 0x0013, 0x002B, 0x0018, 0x0027, 0x001A
- DW 0x0024, 0x001E, 0x0021, 0x0020, 0x001F, 0x0022, 0x001D, 0x0023
- DW 0x001B, 0x0025, 0x000F, 0x0007, 0x0010, 0x0019, 0x000E, 0x000A
- DW 0x000D, 0x000C, 0x0017, 0x0009, 0x0033, 0x0032, 0x0030, 0x002F
- DW 0x0011, 0x002E, 0x002D, 0x0012, 0x0015, 0x00AE, 0x002C, 0x0014
- DW 0x002A, 0x0016, 0x0029, 0x0001, 0x0028, 0x0002, 0x0003, 0x0026
- DW 0x0004, 0x0005, 0x0006, 0x0008, 0x001C, 0x0034, 0x0347, 0x0036
- DW 0x0596, 0x05B8, 0x0035, 0x0773, 0x0990, 0x098B, 0x0A49, 0x0B4B
- DW 0x14DB, 0x00BE, 0x00A7, 0x00B5, 0x007E, 0x00B1, 0x007C, 0x007B
- DW 0x00AC, 0x0079, 0x00AB, 0x0078, 0x00AA, 0x0077, 0x00A9, 0x0076
- DW 0x00A8, 0x0075, 0x0074, 0x0037, 0x005F, 0x0046, 0x3E20, 0x0073
- DW 0x00F4, 0x008E, 0x008F, 0x00C3, 0x0063, 0x00DE, 0x0062, 0x0141
- DW 0x0142, 0x0143, 0x0FE0, 0x00BA, 0x00A3, 0x007A, 0x00AD, 0x00A6
- DW 0x00A5, 0x0072, 0x00A4, 0x0071, 0x0070, 0x005B, 0x0042, 0x381C
- DW 0x006F, 0x00F0, 0x008A, 0x00BD, 0x005E, 0x00D6, 0x00D7, 0x013D
- DW 0x013E, 0x013F, 0x00CB, 0x0000, 0x0000, 0x0000, 0x0000, 0x0000
- compressed_length: DW 5701
- compressed_data: incbin 'textures.bin'
- ;**********************************************************************************************************************
- ;
- ; BSS SEGMENT
- ;
- ;**********************************************************************************************************************
- section bss nobits align=2 follows=data
- previous_mode: RESB 1
- random_seed: RESD 1
- field: RESB 16 ; 4x4 field
- score: RESB 5 ; 5-digit unpacked BCD
- tiles: RESB 11 * 8 * 64
- game_over: RESB 48 * 128
- game_over_bg: RESB 48 * 128
|