home *** CD-ROM | disk | FTP | other *** search
- ; Assembly language learning project for Thomas Hill
- ;
- ; Goal: To design and implement a windowing package in assembly language.
- ;
- ; Version: 1.0 Jan 1989
- ;
- ; Version: 1.1 01/27/89 - corrected window size problem with InitWindow/
- ; EraseTopWin on last (original) window.
- ;
- ; The routines defined here depend upon the routines found in
- ; David Bennett's "VIDEO.ASM" file.
- ;
-
- IDEAL ; use TASM's ideal mode
-
- MODEL SMALL ; and small model
-
- INCLUDE 'VIDEO.INC' ; global values
-
-
- ; define window record structure
-
- STRUC WinRec
- Row DB 1 ; top left window row
- Col DB 1 ; leftmost column
- Hite DB 25 ; hieght of window
- Wide DB 80 ; width of window
- FAtr DB Reverse ; frame attribute, if framed
- BAtr DB Normal ; background attribute for fill
- Flags DB SaveBit+FrameBit+FillBit
- Title DB 20 DUP (0) ; title storage
- SavePtr DW 0 ; segment address of saved screen
- ENDS
-
- TITLEFLD EQU 07H ; offset to title in structure
- MAXWINDOW EQU 15 ; maximum number of windows
-
- ;--------------
- ; Data Area
- ;--------------
-
- DATASEG
-
- WinList WinRec 5 DUP (<>) ; array of window structures
- TopWindow DB 0 ; current window structure
- WinInUse DB 0 ; windows currently defined
-
- ;copy of the 'current' window displayed
-
- CurWin WinRec <1,1,25,80,Reverse,Normal,07H,?>
-
- WRSize equ SIZE CurWin ; size of the window structure
-
- CurWinPtr DW 0 ; pointer into array
-
- ;--------------
- ; Code Area
- ;--------------
-
- CODESEG
-
- PROC ClipXY
- ;
- ; Procedure to check the current row,col against the current window limits.
- ; If the input row or column is outside the window, the ZERO flag is set.
- ;
- ; Input
- ; AH - Row
- ; AL - Col
- ;
- ; Returns ZERO if outside current window
- ;
-
- push ax
- push bx
- cmp ah,[CurWin.Row]
- jl NoGood ; check against upper row
- cmp al,[CurWin.Col]
- jl NoGood ; and upper left column
- mov bl,[CurWin.Row]
- add bl,[CurWin.Hite]
- cmp ah,bl
- jge NoGood ; check lower row limit
- mov bl,[CurWin.Col]
- add bl,[CurWin.Wide]
- cmp al,bl
- jge NoGood ; and rightmost column
- xor ax,ax ; all ok, reset zero flag
- inc ax
- pop bx
- pop ax
- ret
- NoGood: xor ax,ax ; set ZERO and exit
- pop bx
- pop ax
- ret
-
- ENDP ClipXY
-
-
- PROC GetCurWin
- ;
- ; This procedure will compute the offset to the specified window record
- ; A pointer is returned in the DS:SI pair. If the requested window is
- ; and invalid handle, the CARRY flag is set on return.
- ;
- ; Input
- ; AL - window number(handle)
- ;
- ; Output
- ; CY reset - DS:SI altered
- ; CY set - no changes
-
- push ax
- push bx
- cmp al,MAXWINDOW
- jg GCW_Bad
- mov ah,0 ; make sure AH = 0
- mov bx,WRSize ; size of the window structure
- mul bx
- mov si,OFFSET WinList
- add si,ax ; SI now points to window record
- mov [CurWinPtr],si ; so does this
- pop bx
- pop ax
- clc ; clear the carry flag
- ret
- GCW_Bad:
- pop bx
- pop ax
- stc ; set the carry
- ret
-
- ENDP GetCurWin
-
-
- PROC FrameWindow
- ;
- ; THis procedure creates a frame around the specified window coordinates
- ;
- ; Input
- ; AH - Top row
- ; AL - left column
- ; BH - number of rows
- ; BL - number of columns
- ; DH - attribute for frame
- ;
- ; Output
- ; None
- ;
-
- push cx
- push dx
- push ax
- push bx
- mov bl,'╒'
- mov bh,dh
- mov cx,1
- call DWriteCH ; upper left corner
- inc al
- pop bx
- push bx
- dec bl
- dec bl ; account for left/right edges
- xor cx,cx
- mov cl,bl
- mov bh,dh
- mov bl,'═'
- call DWriteCH ; top edge
- pop bx
- push bx
- dec bl
- dec bl
- add al,bl ; end of row
- mov bh,dh
- mov bl,'╕'
- mov cx,1
- call DWriteCH ; upper right corner
- pop bx
- pop ax
- dec bh
-
- FW_Loop:
-
- inc ah ; row counter
- dec bh ; rows to do
- jz FW_Bottom
- push ax
- push bx
- mov bh,dh
- mov bl,'│'
- mov cx,1
- call DWriteCH ; left edge
- pop bx
- push bx
- add al,bl
- dec al
- mov bh,dh
- mov bl,'│'
- mov cx,1
- call DWriteCH ; right edge
- pop bx
- pop ax
- jmp FW_Loop
-
- FW_Bottom:
-
- push bx
- mov bl,'╘'
- mov bh,dh
- mov cx,1
- call DWriteCH ; lower left corner
- inc al
- pop bx
- push bx
- dec bl
- dec bl
- xor cx,cx
- mov cl,bl
- mov bh,dh
- mov bl,'═'
- call DWriteCH ; bottom edge
- pop bx
- push bx
- dec bl
- dec bl
- add al,bl
- mov bh,dh
- mov bl,'╛'
- mov cx,1
- call DWriteCH ; lower right corner
- pop bx
- pop dx
- pop cx
- ret
-
- ENDP FrameWindow
-
-
- GLOBAL InitWindows:PROC
- PROC InitWindows
- ;
- ; This procedure initializes the window array and data structures,
- ; The procedure checks the available memory from DOS using the Allocate
- ; Memory Block DOS call. If no memory is available in that manner,
- ; we return an error.
- ; Note that the contents of the screen at the time of initialization is
- ; saved into window 0. A final ERASETOPWIN call will restore the screen
- ; contents at the time INITWINDOWS was called.
- ;
- ; Input
- ; None
- ;
- ; OutPut
- ; CARRY is SET if we could not find any un-used memory.
- ; If CARRY is not set, then AL contains the maximum number of
- ; windows that may be defined.
-
- push si
- push di
- push dx
- push cx
- push bx
- mov bx,MAXSIZE SHR 4
- mov ah,48H ; allocate memory block
- int 21H
- jc IW_NoMem ; no memory available
-
- ; if we have enough memory, save the screen at program startup in window 0
-
- push ax
- mov ax,0
- call GetCurWin ; point to window 0
- pop ax
- mov [(WinRec PTR si).SavePtr],ax
- push es
- mov es,ax ; set up to save screen
- xor di,di
- mov ah,[(WinRec PTR si).Row]
- mov al,[(WinRec PTR si).Col]
- mov bh,[(WinRec PTR si).Hite]
- mov bl,[(WinRec PTR si).Wide]
- mov [(WinRec PTR si).Flags],SaveBit
- call StoreToMem ; save whole screen to window 0
- pop es
- pop bx
- pop cx
- pop dx
- pop di
- pop si
- mov al,MAXWINDOW ; tell how many windows we support
- clc
- ret
-
- IW_NoMem:
-
- pop bx ; can't get memory
- pop cx
- pop dx
- pop di
- pop si
- stc
- ret
-
-
- ENDP InitWindows
-
- GLOBAL MakeWindow:PROC
- PROC MakeWindow
- ;
- ; This procedure will create a window record for the passed window, but
- ; will not display it. If no more room exists in the window array,
- ; the CARRY flag will be set on return.
- ; On exit AL will contain the created window's "handle" for further use.
- ;
- ; Input
- ; AH - Top Row
- ; AL - Left Column
- ; BH - number of rows
- ; BL - number of columns
- ; CL - Various flags:
- ; Bit 0 - (1) - save underlay; (0) do not save
- ; Bit 1 - (1) - Frame the window; (0) do not frame
- ; Bit 2 - (1) - clear the window; (0) do not clear
- ; DH - Frame attribute
- ; DL - Fill attribute
- ; DS:SI - Title for window, null terminated
- ;
- ; Output
- ; CARRY SET if invalid window, else
- ; AL - window handle
- ;
-
-
- push di
- push si
- push dx
- push cx
- push bx
- push ax
- mov al,MAXWINDOW
- cmp [WinInUse],al ; no more left?
- jge MW_Full
- mov al,[TopWindow]
- inc al ; note: window 0 is always defined
- mov [TopWindow],al
- call GetCurWin ; compute offset to next window rec.
- pop ax
- pop bx
- pop cx
- pop dx
- mov [(WinRec PTR si).Row],ah
- mov [(WinRec PTR si).Col],al
- mov [(WinRec PTR si).Wide],bl
- mov [(WinRec PTR si).HIte],bh ; save the data
- mov [(WinRec PTR si).FAtr],dh
- mov [(WinRec PTR si).BAtr],dl
- mov [(WinRec PTR si).Flags],cl
- mov ax,@data
- mov es,ax ; set up for move
- mov di,[CurWinPtr]
- mov ax,TitleFld
- add di,ax ; address of title field in structure
- pop si ; title address
- MW_Loop:
- lodsb ; get a byte....
- stosb ; ... put a byte
- or al,al
- jnz MW_Loop ; until null is seen (and moved)
- mov si,[CurWinPtr]
- mov di,OFFSET CurWin
- mov cx,WRSize
- rep movsb ; also make a copy for ease of access
- inc [WinInUse]
- pop di ; stack is clear
- mov al,[TopWindow] ; window handle
- clc ; everything worked, clear carry
- ret
- MW_Full:
- stc ; full up, set carry
- pop ax
- pop bx
- pop cx
- pop dx
- pop si
- pop di
- ret
-
- ENDP MakeWindow
-
-
- GLOBAL DispWindow:PROC
- PROC DispWindow
- ;
- ; This procedure will display the selected window.
- ;
- ; Input
- ; AL - window handle
- ;
- ; Output
- ; CY set - invalid handle
- ;
- cmp al,MAXWINDOW
- jl DW_Good
- jmp DW_Bad
-
- DW_Good:
-
- push di
- push si
- push dx
- push cx ; save the world
- push bx
- push ax
- push si
- call GetCurWin ; get the offset
- mov di,OFFSET CurWin
- mov cx,WRSize
- rep movsb ; make a copy for ease of access
- pop si ; original offset
-
- ; check for underlay save
-
- test [CurWin.Flags],SaveBit
- jz DW_NoSave
-
- ;now save the underlying bytes
-
-
- mov al,[CurWin.Hite]
- mov bl,[CurWin.Wide]
- mul bl ; compute memory needed
- mov cl,3
- shr ax,cl ; make it a paragraph size
- inc ax ; ( plus one for slack)
- mov bx,ax
- mov ah,48H
- int 21H ; ask for memory
- jnc DW_SaveScrn
- jmp DW_Bad ; oops, got problems.
-
- DW_SaveScrn:
-
- mov [CurWin.SavePtr],ax ; save the pointer
- push es
- mov es,ax
- mov ah,[CurWin.Row]
- mov al,[CurWin.Col]
- mov bh,[CurWin.Hite]
- mov bl,[CurWin.Wide]
- xor di,di
- call StoreToMem
- pop es ; saved
-
- DW_NoSave:
-
- test [CurWin.Flags],FrameBit ; frame the window?
- jz DW_NoFrame
- mov ah,[CurWin.Row]
- mov al,[CurWin.Col]
- mov bh,[CurWin.Hite]
- mov bl,[CurWin.Wide]
- mov dh,[CurWin.FAtr]
- call FrameWindow
-
- DW_NoFrame:
-
- mov si,OFFSET CurWin.Title
- xor cx,cx
-
- DW_Loop:
-
- lodsb ; look for end of string
- or al,al
- jz DW_Title
- inc cx
- jmp DW_Loop
-
- DW_Title:
-
- or cx,cx ; anything there?
- jz DW_Adj ; nope
- mov al,[CurWin.Wide]
- cmp al,cl
- jl DW_Adj ; title too long
- mov si,OFFSET CurWin.Title
- mov ah,[CurWin.Row]
- mov al,[CurWin.Wide]
- sub al,cl
- shr al,1 ; AL = ((Wide - len(Title)) / 2
- add al,[CurWin.Col]
- call DWriteStrNA
-
- DW_Adj:
-
- test [CurWin.Flags],FrameBit
- jz DW_NoAdj ; if no frame do not adjust edges
- inc [CurWin.Row]
- inc [CurWin.Col]
- dec [CurWin.Hite]
- dec [CurWin.Hite]
- dec [CurWin.Wide]
- dec [CurWin.Wide] ; adjust for frame characters
-
- DW_NoAdj:
-
- test [CurWin.Flags],FillBit ; clear the window?
- jz DW_Exit
- mov ah,[CurWin.Row]
- mov al,[CurWin.Col]
- mov bh,[CurWin.Hite]
- mov bl,[CurWin.Wide]
- mov dh,[CurWin.BAtr]
- mov dl,' ' ; default fill is space
- call DFillCH
-
- DW_Exit:
-
- mov di,[CurWinPtr]
- mov si,OFFSET CurWin
- mov cx,WRSize ; make sure both copies of the
- rep movsb ; window record are the same
- clc
- pop ax
- pop bx
- pop cx
- pop dx
- pop si
- pop di
- ret
-
- DW_Bad:
-
- stc
- ret
-
-
- ENDP DispWindow
-
- GLOBAL EraseTopWin:PROC
- PROC EraseTopWin
- ;
- ; THis procedure will erase the current, or top window. If the background
- ; was saved, it is put back. The Current Window will be set to the
- ; window immediately 'below' the top window.
- ;
- ; Input
- ; None
- ;
- ; Output
- ; CY - set if window stack underflow (no window to erase)
- ;
- push di
- push si
- push dx
- push cx
- push bx
- push ax
- mov ah,[CurWin.Row]
- mov al,[CurWin.Col]
- mov bh,[CurWin.Hite]
- mov bl,[CurWin.Wide]
- test [CurWin.Flags],FrameBit
- jz ETW_NoAdj ; no frame do not adjust
- dec ah
- dec al ; adjust for frame
- inc bl
- inc bl
- inc bh
- inc bh
-
- ETW_NoAdj:
-
- push ds
- mov dx,[CurWin.SavePtr] ; segment of image
- xor si,si
- call StoreToScr ; put the underlay back
- pop ds
- mov al,[TopWindow]
- dec al
- mov [TopWindow],al
- call GetCurWin ; update pointer into array
- mov di,OFFSET CurWin
- mov cx,WRSize
- rep movsb ; update copy of structure
- clc ; everything ok.
-
- ETW_Exit:
-
- pop ax
- pop bx
- pop cx
- pop dx
- pop si
- pop di
- ret
-
- ETW_Bad:
-
- stc
- jmp ETW_Exit
-
- ENDP EraseTopWin
-
-
- GLOBAL WWriteStr:PROC
- PROC WWriteStr
- ;
- ; This proceudre will attempt to write the passed null terminated string
- ; in the current window. If the starting row,col is not within the window,
- ; nothing is written. If the string is too long to fit the current window,
- ; the string is wrapped at the window edge. If the string wraps past the
- ; bottom of the window, the window is scrolled up.
- ;
- ; Input
- ; AH - Row
- ; AL - Col
- ; BH - Attribute
- ; DS:SI - string pointer
- ;
- ; Output
- ; CARRY SET if string truncated or not written.
- ; DS:SI points to byte following null, or character which truncated.
-
- push di
- push dx
- push cx
- push bx
- call ClipXY ; check starting point
- jz WWS_Bad ; cannot write
-
- WWS_Loop:
-
- push ax
- lodsb ; character
- or al,al ; null ?
- jz WWS_Exit ; yes, done.
- mov bl,al ; character to bl
- pop ax
- mov cx,1
- call DWriteCH ; write it
- inc al ; next column
- call ClipXY ; gone too far?
- jnz WWS_Loop ; next char
- inc ah ; next row if at edge
- mov al,[CurWin.Col] ; start at left edge
- call ClipXY ; check new row value
- jnz WWS_Loop ; no problem
- dec ah ; back row up one
- push ax
- push bx
- push cx
- push dx
- mov ah,06H ; ROM VIDEO BIOS service
- mov al,01 ; scroll one line
- mov ch,[CurWin.Row]
- mov cl,[CurWin.Col]
- dec cl
- dec ch ; make zero based for BIOS
- mov dx,cx
- add dh,[CurWin.Hite]
- add dl,[CurWin.Wide]
- test [CurWin.Flags],FrameBit
- jz WWS_NoAdj
- dec dh
- dec dl ; adjust for frame
-
- WWS_NoAdj:
-
- mov bh,[CurWin.BAtr]
- int 10H ; all set up, scroll the window
- pop ax
- pop bx
- pop cx
- pop dx
- jmp WWS_Loop ; and keep going
-
- WWS_Bad:
- pop bx
- pop cx ; done all we can.
- pop dx
- pop di
- stc
- ret
-
- WWS_Exit:
-
- pop ax
- pop bx ; normal exit
- pop cx
- pop dx
- pop di
- clc
- ret
-
- ENDP WWriteStr
-
-
- END
-
-