; =============================================================================
;
; Litos - General display
;
; =============================================================================
CODE_SECTION 32
; -----------------------------------------------------------------------------
; Enumerate standard videomodes
; -----------------------------------------------------------------------------
; INPUT: EAX = index (0..., -1 = get max. index)
; EBX = display driver
; EDX = videomode structure VMODE (NULL=not used)
; OUTPUT: CY = invalid index (EAX = maximum index)
; NC = videomode is valid (EDX structure is filled-up)
; EAX = index or maximum index (in case of error)
; NOTES: Structure VMODE (EDX) will be filled-up (if EDX is not NULL).
; This function enumerates only recommended standard videomodes.
; -----------------------------------------------------------------------------
DispEnumMode: DRVFNC ebx,DDFB_EnumMode
; -----------------------------------------------------------------------------
; Test videomode
; -----------------------------------------------------------------------------
; INPUT: EBX = display driver
; EDX = videomode structure VMODE (full dimension, display
; dimension, font dimension, frequency and memory mode
; entries can be set or 0 = auto)
; OUTPUT: CY = invalid videomode
; NC = videomode is valid (EDX structure is filled-up)
; -----------------------------------------------------------------------------
DispTestMode: DRVFNC ebx,DDFB_TestMode
; -----------------------------------------------------------------------------
; Set videomode
; -----------------------------------------------------------------------------
; INPUT: EBX = display driver
; EDX = videomode structure VMODE (full dimension, display
; dimension, font dimension, frequency and memory mode
; entries can be set or 0 = auto)
; OUTPUT: CY = invalid videomode
; NC = videomode is valid and set (EDX structure is filled-up)
; -----------------------------------------------------------------------------
DispSetMode: DRVFNC ebx,DDFB_SetMode
; -----------------------------------------------------------------------------
; Clear screen and reset cursor
; -----------------------------------------------------------------------------
; INPUT: EBX = display driver
; NOTES: It clears entire screen, sets offset to 0 and resets cursor.
; -----------------------------------------------------------------------------
DispClear: DRVFNC ebx,DDFB_Clear
; -----------------------------------------------------------------------------
; Set display offset
; -----------------------------------------------------------------------------
; INPUT: EBX = display driver
; ECX = X coordinate of visible region of display
; EDX = Y coordinate of visible region of display
; -----------------------------------------------------------------------------
DispSetOffset: DRVFNC ebx,DDFB_SetOffset
; -----------------------------------------------------------------------------
; Set cursor position
; -----------------------------------------------------------------------------
; INPUT: EBX = display driver
; ECX = cursor column
; EDX = cursor row
; -----------------------------------------------------------------------------
DispSetCursor: DRVFNC ebx,DDFB_SetCursor
; -----------------------------------------------------------------------------
; Set cursor size
; -----------------------------------------------------------------------------
; INPUT: EBX = display driver
; ECX = top scan line
; EDX = bottom scan line
; -----------------------------------------------------------------------------
DispSetCurSize: DRVFNC ebx,DDFB_SetCurSize
; -----------------------------------------------------------------------------
; Set cursor visible
; -----------------------------------------------------------------------------
; INPUT: AL = 0 cursor off, 1 cursor on, 2 flip state
; EBX = display driver
; -----------------------------------------------------------------------------
DispSetVisible: DRVFNC ebx,DDFB_SetVisible
; -----------------------------------------------------------------------------
; Load text font
; -----------------------------------------------------------------------------
; INPUT: AL = font bank (0..3 for EGA, 0..7 for VGA)
; AH = font height (1..32, 0=default)
; EBX = display driver
; CL = first index (0..255)
; DL = last index (0..255, must not be lesser than first index)
; ESI = pointer to font (character with start index)
; -----------------------------------------------------------------------------
DispLoadFont: DRVFNC ebx,DDFB_LoadFont
; -----------------------------------------------------------------------------
; Set font bank
; -----------------------------------------------------------------------------
; INPUT: EBX = display driver
; CL = font bank for color attribute bit 3 = 0 (0..3 or 0..7)
; DL = font bank for color attribute bit 3 = 1 (0..3 or 0..7)
; -----------------------------------------------------------------------------
DispSetFont: DRVFNC ebx,DDFB_SetFont
; -----------------------------------------------------------------------------
; Set border color
; -----------------------------------------------------------------------------
; INPUT: AL = border color (0..15 for 16-color or 0..255 for 256-color)
; EBX = display driver
; -----------------------------------------------------------------------------
DispSetBorder: DRVFNC ebx,DDFB_SetBorder
; -----------------------------------------------------------------------------
; Set CGA palette (only CGA videomode)
; -----------------------------------------------------------------------------
; INPUT: AL = palette set (0=red/green/yellow, 1=cyan/magenta/white)
; EBX = display driver
; -----------------------------------------------------------------------------
DispSetPalCGA: DRVFNC ebx,DDFB_SetPalCGA
; -----------------------------------------------------------------------------
; Set EGA palette
; -----------------------------------------------------------------------------
; INPUT: AL = start index (0..16, last entry is border color)
; EBX = display driver
; CL = stop index (0..16)
; EDX = pointer to EGA palette (palette entry with start index)
; NOTES: EGA palettes are array of 17 bytes: B0 blue 2/3, B1 green 2/3,
; B2 red 2/3, B3 blue 1/3, B4 green 1/3, B5 red 1/3. Last palette entry
; (index 16) is border color. On VGA card EGA palette is index into
; VGA palette table indexed 64 to 127.
; -----------------------------------------------------------------------------
DispSetPalEGA: DRVFNC ebx,DDFB_SetPalEGA
; -----------------------------------------------------------------------------
; Set VGA palette
; -----------------------------------------------------------------------------
; INPUT: AL = start index (0..255)
; EBX = display driver
; CL = stop index (0..255)
; EDX = pointer to VGA palette (palette entry with start index)
; NOTES: VGA palettes are array of byte triples: red, green and blue color
; components with range 0 to 63.
; -----------------------------------------------------------------------------
DispSetPalVGA: DRVFNC ebx,DDFB_SetPalVGA
; -----------------------------------------------------------------------------
; Set indexed palette
; -----------------------------------------------------------------------------
; INPUT: EAX = index table (array of bytes with value 0 to 255)
; EBX = display driver
; ECX = number of color entries (1 to 255)
; EDX = pointer to VGA palette
; NOTES: VGA palettes are array of byte triples: red, green and blue color
; components with range 0 to 63.
; -----------------------------------------------------------------------------
DispSetPalInx: DRVFNC ebx,DDFB_SetPalInx
; -----------------------------------------------------------------------------
; Fill-up region
; -----------------------------------------------------------------------------
; INPUT: AL = color (in graphics mode) or character (in text mode)
; AH = color attribute (only in text mode)
; EBX = display driver
; ECX = region width
; EDX = region height
; ESI = region left margin (in display area)
; EDI = region top margin (in display area)
; NOTES: Parameters are not checked and can be used to fill-up hide regions.
; -----------------------------------------------------------------------------
DispFillUp: DRVFNC ebx,DDFB_FillUp
; -----------------------------------------------------------------------------
; Move region
; -----------------------------------------------------------------------------
; INPUT: EAX = destination offset in videomemory
; EBX = display driver
; ECX = region width
; EDX = region height
; ESI = region left margin (in display area)
; EDI = region top margin (in display area)
; NOTES: Parameters are not checked and can be used to move in invisible area.
; -----------------------------------------------------------------------------
DispMove: DRVFNC ebx,DDFB_Move
; -----------------------------------------------------------------------------
; Get buffer size
; -----------------------------------------------------------------------------
; INPUT: EBX = display driver
; ECX = region width
; EDX = region height
; OUTPUT: EAX = buffer size
; -----------------------------------------------------------------------------
DispBufferSize: DRVFNC ebx,DDFB_BufferSize
; -----------------------------------------------------------------------------
; Get region
; -----------------------------------------------------------------------------
; INPUT: EAX = destination buffer
; EBX = display driver
; ECX = region width
; EDX = region height
; ESI = region left margin (in display area)
; EDI = region top margin (in display area)
; NOTES: Parameters are not checked and can be used to get hide regions.
; -----------------------------------------------------------------------------
DispGetRegion: DRVFNC ebx,DDFB_GetRegion
; -----------------------------------------------------------------------------
; Set region
; -----------------------------------------------------------------------------
; INPUT: EAX = source buffer
; EBX = display driver
; ECX = region width
; EDX = region height
; ESI = region left margin (in display area)
; EDI = region top margin (in display area)
; NOTES: Parameters are not checked and can be used to set hide regions.
; -----------------------------------------------------------------------------
DispSetRegion: DRVFNC ebx,DDFB_SetRegion
; -----------------------------------------------------------------------------
; Set text region with color
; -----------------------------------------------------------------------------
; INPUT: EAX = source buffer (only characters without color attributes)
; EBX = display driver
; ECX = region width
; EDX = region height
; ESI = region left margin (in display area)
; EDI = region top margin (in display area)
; EBP = color attribute
; NOTES: Parameters are not checked and can be used to set hide regions.
; -----------------------------------------------------------------------------
DispSetRegCol: DRVFNC ebx,DDFB_SetRegCol
; -----------------------------------------------------------------------------
; Set region with color mask
; -----------------------------------------------------------------------------
; INPUT: EAX = source buffer
; EBX = display driver
; ECX = region width
; EDX = region height
; ESI = region left margin (in display area)
; EDI = region top margin (in display area)
; EBP = transparent color
; NOTES: Parameters are not checked and can be used to set hide regions.
; -----------------------------------------------------------------------------
DispSetColMask: DRVFNC ebx,DDFB_SetColMask
; -----------------------------------------------------------------------------
; Set region with mask
; -----------------------------------------------------------------------------
; INPUT: EAX = source buffer with data and bit mask
; EBX = display driver
; ECX = region width
; EDX = region height
; ESI = region left margin (in display area)
; EDI = region top margin (in display area)
; NOTES: Parameters are not checked and can be used to set hide regions.
; Bit mask follow after region data, one bit = 1 if point is visible.
; -----------------------------------------------------------------------------
DispSetMasked: DRVFNC ebx,DDFB_SetMasked
; -----------------------------------------------------------------------------
; Set region with alpha
; -----------------------------------------------------------------------------
; INPUT: EAX = source buffer with data and alpha
; EBX = display driver
; ECX = region width
; EDX = region height
; ESI = region left margin (in display area)
; EDI = region top margin (in display area)
; NOTES: Parameters are not checked and can be used to set hide regions.
; Alpha is array of bytes in range 0 (transparent) to 255 (opaque).
; -----------------------------------------------------------------------------
DispSetAlpha: DRVFNC ebx,DDFB_SetAlpha
; -----------------------------------------------------------------------------
; Output byte to display register
; -----------------------------------------------------------------------------
; INPUT: AL = data byte
; CL = register number
; EBX = display driver parameter block
; NOTES: Function takes approximately 3 us if it is not cached.
; -----------------------------------------------------------------------------
; ------------- Push registers
DispOutByte: push ecx ; push ECX
push edx ; push EDX
; ------------- Check if register is already set
movzx ecx,cl ; ECX <- register number
cmp al,[ebx+DDPB_Regs+ecx] ; is register already set?
je DispOutByte8 ; register is already set
mov [ebx+DDPB_Regs+ecx],al ; store byte into cache
; ------------- Select register and output data byte
mov edx,[ebx+DDPB_Port] ; EDX <- control port
xchg eax,ecx ; AL <- register, CL <- data byte
out dx,al ; select register
xchg eax,ecx ; AL <- data byte
inc edx ; EDX <- data port
out dx,al ; set data byte
; ------------- Pop registers
DispOutByte8: pop edx ; pop EDX
pop ecx ; pop ECX
ret
; -----------------------------------------------------------------------------
; Output word to display registers
; -----------------------------------------------------------------------------
; INPUT: AX = data word
; CL = first register number (for HIGH, CL+1=register for LOW)
; EBX = display driver parameter block
; NOTES: Function takes approximately 6 us if it is not cached.
; -----------------------------------------------------------------------------
; ------------- Push registers
DispOutWord: push ecx ; push ECX
push edx ; push EDX
; ------------- Prepare registers
movzx ecx,cl ; ECX <- first register number
xchg al,ah ; AL <- data HIGH, AH <- data LOW
mov edx,[ebx+DDPB_Port] ; EDX <- control port
; ------------- Check if display register HIGH is already set
cmp al,[ebx+DDPB_Regs+ecx] ; is register already set?
je DispOutWord4 ; register is already set
mov [ebx+DDPB_Regs+ecx],al ; save new register value
; ------------- Select display register HIGH and output HIGH byte
xchg eax,ecx ; AL <- register, CX <- data X-word
out dx,al ; select register HIGH
xchg eax,ecx ; AX <- data X-word, CL <- register
inc edx ; EDX <- data port
out dx,al ; set data byte HIGH
dec edx ; EDX <- control port
; ------------- Check if display register LOW is already set
DispOutWord4: xchg ah,al ; AL <- data LOW, AH <- data HIGH
cmp al,[ebx+DDPB_Regs+ecx+1] ; is register already set?
je DispOutWord8 ; register is already set
mov [ebx+DDPB_Regs+ecx+1],al ; save new register value
; ------------- Select display register LOW and output LOW byte
inc ecx ; ECX <- register number + 1
xchg eax,ecx ; AL <- register+1, CX <- data word
out dx,al ; select register LOW
xchg eax,ecx ; AX <- data word, CL <- register+1
inc edx ; EDX <- data port
out dx,al ; set data byte LOW
; ------------- Pop registers
DispOutWord8: pop edx ; pop EDX
pop ecx ; pop ECX
ret
; -----------------------------------------------------------------------------
; Output byte to display register with validity test
; -----------------------------------------------------------------------------
; INPUT: AL = data byte
; CL = register number
; EBX = display driver parameter block
; OUTPUT: ZY = data is OK, NZ = data error
; NOTES: Function takes approximately 25 us if it is not cached.
; -----------------------------------------------------------------------------
; ------------- Push registers
DispOutTest: push eax ; push EAX
push ecx ; push ECX
push edx ; push EDX
; ------------- Store data byte into register cache
movzx ecx,cl ; ECX <- register number
mov [ebx+DDPB_Regs+ecx],al ; store data byte into cache
; ------------- Select register and output data byte
mov edx,[ebx+DDPB_Port] ; EDX <- control port
xchg eax,ecx ; EAX <- register, CL <- data byte
out dx,al ; select register
xchg eax,ecx ; AL <- data byte, ECX <- register
inc edx ; EDX <- data port
out dx,al ; set data byte
; ------------- Short delay (aprox. 20 us)
mov ah,al ; AH <- data byte
mov cl,14 ; ECX <- 14, aprox. 20 us delay
DispOutTest2 SHORT_DELAY ; short delay (aprox. 1.5 us)
loop DispOutTest2 ; wait
; ------------- Check data validity
in al,dx ; read data byte
cmp al,ah ; is data valid?
; ------------- Pop registers
pop edx ; pop EDX
pop ecx ; pop ECX
pop eax ; pop EAX
ret
; -----------------------------------------------------------------------------
; Set group of display registers
; -----------------------------------------------------------------------------
; INPUT: AL = index of first register
; EBX = display driver parameter block
; CL = number of registers
; EDX = pointer to group of registers to set
; NOTES: Function takes approximately CL * 3 us if it is not cached.
; -----------------------------------------------------------------------------
; ------------- Push registers
DispOutReg: push eax ; push EAX
push ecx ; push ECX
push edx ; push EDX
push esi ; push ESI
push edi ; push EDI
; ------------- Prepare registers
movzx eax,al ; EAX <- index of first register
movzx ecx,cl ; ECX <- number of registers
mov esi,edx ; ESI <- pointer to registers
lea edi,[ebx+DDPB_Regs+eax] ; EDI <- cache of registers
mov edx,[ebx+DDPB_Port] ; EDX <- control port
mov ah,al ; AH <- index of first register
; ------------- Check if register is already set
DispOutReg2: lodsb ; load register to set
cmp al,[edi] ; change register?
je DispOutReg6 ; register is already set
mov [edi],al ; store new register value
; ------------- Select register and output data byte
xchg al,ah ; AL <- register, AH <- data byte
out dx,al ; select register
inc eax ; increase register number
inc edx ; EDX <- data port
xchg al,ah ; AL <- data byte, AH <- next register
out dx,al ; set data byte
dec edx ; EDX <- return index port
; ------------- Next register
DispOutReg6: inc edi ; increase cache pointer
loop DispOutReg2 ; next register
; ------------- Pop registers
pop edi ; pop EDI
pop esi ; pop ESI
pop edx ; pop EDX
pop ecx ; pop ECX
pop eax ; pop EAX
ret
; -----------------------------------------------------------------------------
; Set all display registers
; -----------------------------------------------------------------------------
; INPUT: EBX = display driver parameter block
; EDX = pointer to register array (1st byte=number of registers)
; NOTES: Function takes approximately N * 3 us if it is not cached.
; -----------------------------------------------------------------------------
; ------------- Push registers
DispOutAllReg: push eax ; push EAX
push ecx ; push ECX
; ------------- Set registers
xor eax,eax ; AL <- 0, index of first register
mov cl,[edx] ; CL <- number of registers
inc edx ; EDX <- first register to set
call DispOutReg ; set registers
dec edx ; EDX <- return pointer to array
; ------------- Pop registers
pop ecx ; pop ECX
pop eax ; pop EAX
ret
; -----------------------------------------------------------------------------
; Clear Unicode mapping
; -----------------------------------------------------------------------------
; INPUT: EBX = display driver parameter block
; -----------------------------------------------------------------------------
; ------------- Push registers
DispUniMapClr: push eax ; push EAX
push ecx ; push ECX
push edx ; push EDX
push esi ; push ESI
push edi ; push EDI
; ------------- Prepare registers
mov esi,[ebx+DDPB_FromUni] ; ESI <- mapping table
mov edx,FONTMAP ; EDX <- number of pages
; ------------- Get next page
DispUniMapClr2: lodsd ; EAX <- page address
or eax,eax ; is page allocated?
jz DispUniMapClr8 ; page is not allocated
; ------------- Clear page
xchg eax,edi ; EDI <- page address
xor ecx,ecx ; ECX <- 0
xor eax,eax ; EAX <- 0
mov cl,128 ; ECX <- 256*2 / 4
rep stosd ; clear page
; ------------- Next page
DispUniMapClr8: dec edx ; counter of pages
jnz DispUniMapClr2 ; next page
; ------------- Pop registers
pop edi ; pop EDI
pop esi ; pop ESI
pop edx ; pop EDX
pop ecx ; pop ECX
pop eax ; pop EAX
ret
; -----------------------------------------------------------------------------
; Add one code into Unicode mapping
; -----------------------------------------------------------------------------
; INPUT: AX = character code (Unicode)
; EBX = display driver parameter block
; DX = character (character + attribute B3)
; [ESI-2] = original character code
; NOTES: If character code is equivalent to original code, it does not check if
; code is already in mapping table.
; -----------------------------------------------------------------------------
; ------------- Push registers
DispUniMap1Add: push ecx ; push ECX
push edi ; push EDI
; ------------- Prepare page address (-> EDI)
movzx edi,ah ; EDI <- page index
shl edi,2 ; EDI <- page address offset
add edi,[ebx+DDPB_FromUni] ; EDI <- page address
cmp dword [edi],byte 0 ; is page allocated?
jne DispUniMap1Add4 ; page is allocated
; ------------- Push registers 2
push eax ; push EAX
push ecx ; push ECX
push edi ; push EDI
; ------------- Allocate new page
xor eax,eax ; EAX <- 0
mov ah,2 ; EAX <- 2*256
call SysMemAlloc ; allocate memory
jc DispUniMap1Add2 ; memory error
mov [edi],eax ; store page address
; ------------- Initialize page
xchg eax,edi ; EDI <- page address
xor ecx,ecx ; ECX <- 0
xor eax,eax ; EAX <- 0
mov cl,128 ; ECX <- page size / 4
rep stosd ; clear page
; ------------- Pop registers 2
DispUniMap1Add2:pop edi ; pop EDI
pop ecx ; pop ECX
pop eax ; pop EAX
jc DispUniMap1Add8 ; memory error
; ------------- Prepare entry address
DispUniMap1Add4:mov edi,[edi] ; EDI <- entry address
movzx ecx,al ; ECX <- character index in page
; ------------- Check if store character code
cmp ax,[esi-2] ; is it original character code?
je DispUniMap1Add6 ; store code without check
cmp word [edi+ecx*2],byte 0 ; is code already used?
jne DispUniMap1Add8 ; code is already used
; ------------- Store character code
DispUniMap1Add6:mov [edi+ecx*2],dx ; store code index
; ------------- Pop registers
DispUniMap1Add8:pop edi ; pop EDI
pop ecx ; pop ECX
ret
; -----------------------------------------------------------------------------
; Add one Unicode mapping
; -----------------------------------------------------------------------------
; INPUT: EBX = display driver parameter block
; DL = character start value (0 or 128)
; DH = attributes (0 = first bank or B3 = second bank)
; ESI = character set (128 characters, Unicode WORD each)
; EDI = font table FIXFONT
; -----------------------------------------------------------------------------
; ------------- Push registers
DispUniMapAdd: pusha ; push all registers
; ------------- Prepare registers
xor ecx,ecx ; ECX <- 0
mov cl,128 ; ECX <- 128, number of characters
; ------------- Load one character from charset (-> EAX)
DispUniMapAdd2: xor eax,eax ; EAX <- 0
lodsw ; EAX <- load next character
cmp eax,FONTMAX ; check code range
ja DispUniMapAdd3 ; invalid code
; ------------- Get font address (-> EBP)
movzx ebp,ah ; EBP <- font page
shl ebp,2 ; EBP <- page address offset
add ebp,[edi+FIXFONT_Map] ; EBP <- mapping page
mov ebp,[ebp] ; EBP <- mapping page
or ebp,ebp ; is page allocated?
jz DispUniMapAdd3 ; page is not allocated
; ------------- Get character address (-> EBP)
movzx eax,al ; EAX <- character offset
mov ebp,[ebp+eax*4] ; EAX <- character address
or ebp,ebp ; is address valid?
jnz DispUniMapAdd4 ; address is valid
; ------------- Invalid character
DispUniMapAdd3: mov ebp,[edi+FIXFONT_Invalid] ; EBP <- invalid character
; ------------- Prepare registers to store character codes
DispUniMapAdd4: push ecx ; push ECX
movzx ecx,byte [ebp] ; ECX <- number of codes
mov ch,cl ; CH <- save flags
and cl,FIXFONT_MASK ; mask number of codes
inc ebp ; increase font pointer
; ------------- Get one code (-> AX)
DispUniMapAdd5: mov ax,[ebp] ; AX <- Unicode code
inc ebp ; increase font pointer
inc ebp ; increase font pointer
; ------------- Store character code
call DispUniMap1Add ; store one character code
dec cl ; decrement code counter
jnz short DispUniMapAdd5 ; next code
; ------------- Push registers 2
push esi ; push ESI
push edi ; push EDI
push edx ; push EDX
push ebp ; push EBP
mov dh,ch ; DH <- attributes
; ------------- Prepare source (-> ESI) and destination (-> EDI) address
xor eax,eax ; EAX <- 0
mov al,dl ; AL <- character value
and al,7fh ; mask character value
mov dl,[ebx+DDPB_FontH] ; DL <- font height
mul dl ; EAX <- destination offset
add eax,[ebx+DDPB_FontBuff] ; EAX <- address in buffer
xchg eax,edi ; EDI <- font buffer, EAX <- fixfont
mov esi,ebp ; ESI <- font data
xchg eax,ebp ; EAX <- font head, EBP <- fixfont
; ------------- Copy font data (if font is big enough)
cmp dl,[ebp+FIXFONT_Height] ; check font height
ja DispUniMapAdd51 ; font is smaller
movzx ecx,dl ; ECX <- font height
rep movsb ; copy font data
jmp short DispUniMapAdd58
; ------------- Prepare height of margins
DispUniMapAdd51:sub dl,[ebp+FIXFONT_Height] ; DL <- rest of lines
shr dl,1 ; DL <- lines / 2 round down
movzx ecx,dl ; ECX <- rest of lines / 2
adc dl,0 ; DL <- lines / 2 round up
jecxz DispUniMapAdd54 ; no lines
; ------------- Initialize top lines
xor eax,eax ; AX <- 0
test dh,FIXFONT_VGRAPHT ; expand top?
jz DispUniMapAdd52 ; don't expand top
mov ax,[esi] ; AX <- first 2 lines
test cl,1 ; even lines?
jz DispUniMapAdd53 ; even lines
DispUniMapAdd52:xchg al,ah ; exchange lines
DispUniMapAdd53:stosb ; store one line
loop DispUniMapAdd52 ; next line
; ------------- Copy font data (if font is smaller)
DispUniMapAdd54:mov ecx,[ebp+FIXFONT_Height] ; ECX <- font height
rep movsb ; copy font data
; ------------- Initialize bottom lines
mov cl,dl ; CL <- lines / 2 round up
jecxz DispUniMapAdd58 ; no lines
xor eax,eax ; AX <- 0
test dh,FIXFONT_VGRAPHB ; expand bottom?
jz DispUniMapAdd56 ; don't expand top
mov ax,[esi-2] ; AX <- last 2 lines
DispUniMapAdd56:stosb ; store one line
xchg al,ah ; exchange lines
loop DispUniMapAdd56 ; next line
; ------------- Pop registers 2
DispUniMapAdd58:pop ebp ; pop EBP
pop edx ; pop EDX
pop edi ; pop EDI
pop esi ; pop ESI
pop ecx ; pop ECX
; ------------- Next character
inc edx ; increase character value
dec ecx ; decrease character counter
jnz DispUniMapAdd2 ; next character
; ------------- Load font
dec edx ; DL <- last character
mov al,0 ; AL <- 0, bank 0
or dh,dh ; second bank?
jz DispUniMapAdd6 ; no, first bank
inc eax ; AL <- 1, second bank
DispUniMapAdd6: mov ah,[ebx+DDPB_FontH] ; AH <- font height
mov cl,dl ; CL <- last character
sub cl,7fh ; CL <- first character
mov esi,[ebx+DDPB_FontBuff] ; ESI <- font buffer
call DispLoadFont ; load font
; ------------- Pop registers
popa ; pop all registers
ret
; -----------------------------------------------------------------------------
; Load character set
; -----------------------------------------------------------------------------
; INPUT: EBX = display driver parameter block
; ECX = character set table 0 to 7fh
; EDX = character set table 80h to 0ffh
; ESI = character set table 100h to 1ffh (NULL=none)
; EDI = font table FIXFONT
; -----------------------------------------------------------------------------
; ------------- Clear Unicode mapping
DispLoadSet: call DispUniMapClr ; clear Unicode mapping
; ------------- Push registers
pusha ; push all registers
; ------------- Load character set 100h to 17fh
or esi,esi ; use character set 100h to 1ffh?
jz DispLoadSet4 ; don't use character set 100h to 1ffh
push edx ; push EDX
xor edx,edx ; EDX <- 0
mov dh,B3 ; DH <- attribute for bank 1
call DispUniMapAdd ; add one Unicode mapping
; ------------- Load character set 180h to 1ffh
add dl,80h ; DL <- second character value
add esi,80h*2 ; ESI <- second half of character set
call DispUniMapAdd ; add second Unicode mapping
pop edx ; pop EDX
; ------------- Load character set 80h to 0ffh
DispLoadSet4: mov esi,edx ; ESI <- character set 80h to 0ffh
xor edx,edx ; EDX <- 0
mov dl,80h ; DL <- second character value
call DispUniMapAdd ; add second Unicode mapping
; ------------- Load character set 0 to 80h
mov esi,ecx ; ESI <- character set 0 to 80h
xor edx,edx ; EDX <- 0
call DispUniMapAdd ; add first Unicode mapping
; ------------- Pop registers
popa ; pop all registers
ret
; -----------------------------------------------------------------------------
; Map Unicode character into display code
; -----------------------------------------------------------------------------
; INPUT: EAX = Unicode character
; EBX = display driver parameter block
; EDX = invalid character
; OUTPUT: EAX = display character (EAX <- EDX on invalid cahracter)
; AL = display character (0 to 255)
; AH = attributes (0 = bank 0, B3 = bank 1)
; -----------------------------------------------------------------------------
DispMapChar: push ecx ; push ECX
cmp eax,FONTMAX ; check maximal character value
ja DispMapChar4 ; invalid character
movzx ecx,ah ; ECX <- character page
shl ecx,2 ; ECX <- page offset
add ecx,[ebx+DDPB_FromUni] ; ECX <- page address
mov ecx,[ecx] ; ECX <- page address
jecxz DispMapChar4 ; invalid page
movzx eax,al ; EAX <- character offset
mov ax,[ecx+eax*2] ; EAX <- load character
or eax,eax ; is character valid?
jnz DispMapChar6 ; character is valid
DispMapChar4: mov eax,edx ; EAX <- invalid character
DispMapChar6: pop ecx ; pop EAX
ret
; -----------------------------------------------------------------------------
; Data
; -----------------------------------------------------------------------------
DATA_SECTION
; ------------- IBM PC character set 0 to 7fh
align 4, db 0
DispCharTab: dw 0h, 263ah, 263bh, 2665h, 2666h, 2663h, 2660h, 2022h
dw 25d8h, 25cbh, 25d9h, 2642h, 2640h, 266ah, 266bh, 263ch
dw 25b6h, 25c0h, 2195h, 203ch, 0b6h, 0a7h, 25ach, 21a8h
dw 2191h, 2193h, 2192h, 2190h, 221fh, 2194h, 25b2h, 25bch
INCW 20h, 7eh
dw 2302h
; ------------- Multipage character set - Latin (for 512-character display)
; Warning: Characters C0h-DFh can have duplicated last column (9-point font).
;
; Supported code pages:
; 1: DEC VT100
; 437: IBM-437 (United States)
; 737: IBM-737 (Greek)
; 775: IBM-775 (Baltic)
; 850: IBM-850 (Latin 1 West Europe)
; 852: IBM-852 (Latin 2 Cent.Europe)
; 857: IBM-857 (Turkish)
; 858: IBM-858 (Latin 1 + Euro)
; 860: IBM-860 (Portuguese)
; 861: IBM-861 (Icelandic)
; 863: IBM-863 (French Canadian)
; 865: IBM-865 (Nordic)
; 869: IBM-869 (Modern Greek)
; 895: IBM-895 (Kamenickych, Czech)
; 1250: Windows-1250 (Central Europe)
; 1252: Windows-1252 (Latin 1 Windows)
; 1253: Windows-1253 (Greek)
; 1254: Windows-1254 (Turkish)
; 1257: Windows-1257 (Baltic)
; 1258: Windows-1258 (Vietnam)
; 28591: ISO 8859-1 (Latin 1)
; 28592: ISO 8859-2 (Latin 2)
; 28593: ISO 8859-3 (Latin 3)
; 28594: ISO 8859-4 (Baltic)
; 28597: ISO 8859-7 (Greek)
; 28599: ISO 8859-9 (Turkish)
; 28605: ISO 8859-15 (Latin 9)
DispCharTabLat: ; 0 to 0fh
dw 0a4h, 0a6h, 0a8h, 0a9h, 0adh, 0aeh, 0afh, 0b1h
dw 0b3h, 0b4h, 0b8h, 0b9h, 0beh, 0c0h, 0c1h, 0c2h
; 10h to 1fh
dw 0c3h, 0c8h, 0cah, 0cbh, 0cch, 0cdh, 0ceh, 0cfh
dw 0d0h, 0d2h, 0d3h, 0d4h, 0d5h, 0d7h, 0d8h, 0d9h
; 20h to 2fh
dw 0dah, 0dbh, 0ddh, 0deh, 0dfh, 0e3h, 0f0h, 0f5h
dw 0f7h, 0f8h, 0fdh, 0feh, 100h, 101h, 102h, 103h
; 30h to 3fh
INCW 104h, 10bh
dw 10ch, 10dh, 10eh, 10fh, 111h, 112h, 113h, 116h
; 40h to 4fh
INCW 117h, 126h
; 50h to 5fh
dw 127h, 128h, 129h, 12ah, 12bh, 12eh, 12fh, 130h
dw 131h, 134h, 135h, 136h, 137h, 138h, 139h, 13ah
; 60h to 6fh
dw 13bh, 13ch, 13dh, 13eh, 141h, 142h, 143h, 144h
dw 145h, 146h, 147h, 148h, 14ah, 14bh, 14ch, 14dh
; 70h to 7fh
INCW 150h, 15fh
; 80h to 8fh
INCW 160h, 16fh
; 90h to 9fh
dw 170h, 171h, 172h, 173h, 178h, 179h, 17ah, 17bh
dw 17ch, 17dh, 17eh, 192h, 1a0h, 1a1h, 1afh, 1b0h
; 0a0h to 0afh
dw 2c6h, 2c7h, 2d8h, 2d9h, 2dbh, 2dch, 2ddh, 309h
dw 323h, 385h, 386h, 388h, 389h, 38ah, 38ch, 38eh
; 0b0h to 0bfh
dw 38fh, 390h, 393h, 394h, 396h, 398h, 39bh, 39eh
dw 3a0h, 3a3h, 3a6h, 3a8h, 3a9h, 3ach, 3adh, 3b0h
; ------------- start of graphic area
; 0c0h to 0cfh
dw 3aeh, 3afh, 3b2h, 3b6h, 3b7h, 3b8h, 3b9h, 3beh
dw 3c1h, 3c2h, 3cah, 2013h, 2014h, 2017h, 2018h, 2019h
; 0d0h to 0dfh
dw 201ah, 201ch, 201dh, 201eh, 2020h, 2021h, 2039h, 203ah
dw 20abh, 20ach, 23bah, 23bbh, 23bch, 23bdh, 0, 0
; ------------- end of graphic area
; 0e0h to 0efh
dw 3b3h, 3bbh, 3c5h, 3c7h, 3c8h, 3c9h, 3cbh, 3cdh
dw 3ceh, 2026h, 2030h, 2122h, 2260h, 2409h, 240ah, 240bh
; 0f0h to 0ffh
dw 240ch, 240dh, 2424h, 25c6h, 0, 0, 0, 0
dw 0, 0, 0, 0, 0, 0, 0, 0
|