Magellan Linux

Diff of /trunk/mkinitrd-magellan/isolinux/graphics.inc

Parent Directory Parent Directory | Revision Log Revision Log | View Patch Patch

revision 1132 by niro, Sat Sep 1 22:45:15 2007 UTC revision 1133 by niro, Thu Aug 19 09:50:43 2010 UTC
# Line 1  Line 1 
 ;; $Id: graphics.inc,v 1.1 2007-09-01 22:44:04 niro Exp $  
1  ;; -----------------------------------------------------------------------  ;; -----------------------------------------------------------------------
2  ;;    ;;
3  ;;   Copyright 1994-2002 H. Peter Anvin - All Rights Reserved  ;;   Copyright 1994-2008 H. Peter Anvin - All Rights Reserved
4  ;;  ;;
5  ;;   This program is free software; you can redistribute it and/or modify  ;;   This program is free software; you can redistribute it and/or modify
6  ;;   it under the terms of the GNU General Public License as published by  ;;   it under the terms of the GNU General Public License as published by
# Line 18  Line 17 
17  ;  ;
18  ; vgadisplayfile:  ; vgadisplayfile:
19  ; Display a graphical splash screen.  ; Display a graphical splash screen.
20    ; The file is already opened on the top of the getc stack.
21  ;  ;
22  ; Input:  ; Assumes CS == DS == ES.
 ;  
 ; SI = cluster/socket pointer  
23  ;  ;
24   section .text   section .text
25    
26  vgadisplayfile:  vgadisplayfile:
  mov [VGACluster],si  
  push es  
   
27   ; This is a cheap and easy way to make sure the screen is   ; This is a cheap and easy way to make sure the screen is
28   ; cleared in case we were in graphics mode already   ; cleared in case we were in graphics mode already
29   call vgaclearmode   call vgaclearmode
# Line 36  vgadisplayfile: Line 31  vgadisplayfile:
31   jnz .error_nz   jnz .error_nz
32    
33  .graphalready:  .graphalready:
34   mov ax,xfer_buf_seg ; Use as temporary storage   ; Load the header.
35   mov es,ax   mov cx,4+2*2+16*3
36   mov fs,ax   mov di,LSSHeader
37    .gethdr:
38   call vgagetchunk ; Get the first chunk   call getc
39     stosb
40     loop .gethdr
41     jc .error
42    
43   ; The header WILL be in the first chunk.   ; The header WILL be in the first chunk.
44   cmp dword [es:xbs_vgabuf],0x1413f33d ; Magic number   cmp dword [LSSMagic],0x1413f33d ; Magic number
45  .error_nz: jne .error  .error_nz: jne .error
  mov ax,[es:xbs_vgabuf+4]  
  mov [GraphXSize],ax  
46    
47   mov dx,xbs_vgabuf+8 ; Color map offset   mov dx,GraphColorMap ; Color map offset
48   mov ax,1012h ; Set RGB registers   mov ax,1012h ; Set RGB registers
49   xor bx,bx ; First register number   xor bx,bx ; First register number
50   mov cx,16 ; 16 registers   mov cx,16 ; 16 registers
51   int 10h   int 10h
52    
53  .movecursor:  .movecursor:
54   mov ax,[es:xbs_vgabuf+6] ; Number of pixel rows   mov ax,[GraphYSize] ; Number of pixel rows
55   mov dx,[VGAFontSize]   mov dx,[VGAFontSize]
56   add ax,dx   add ax,dx
57   dec ax   dec ax
# Line 71  vgadisplayfile: Line 67  vgadisplayfile:
67   xor bx,bx   xor bx,bx
68   int 10h ; Set cursor below image   int 10h ; Set cursor below image
69    
70   mov cx,[es:xbs_vgabuf+6] ; Number of graphics rows   mov cx,[GraphYSize] ; Number of graphics rows
   
  mov si,xbs_vgabuf+8+3*16 ; Beginning of pixel data  
71   mov word [VGAPos],0   mov word [VGAPos],0
72    
73  .drawpixelrow:  .drawpixelrow:
74   push cx   push cx
75   mov cx,[GraphXSize]   mov di,VGARowBuffer
76   mov di,xbs_vgatmpbuf ; Row buffer   ; Pre-clear the row buffer
77   call rledecode ; Decode one row   push di
78   push si   push di
  mov si,xbs_vgatmpbuf  
  mov di,si  
  add di,[GraphXSize]  
79   mov cx,640/4   mov cx,640/4
80   xor eax,eax   xor eax,eax
81   rep stosd ; Clear rest of row   rep stosd
82     pop di
83     mov cx,[GraphXSize]
84     call rledecode ; Decode one row
85     pop si
86     mov di,VGAPlaneBuffer
87     push di
88     mov bp,640
89     call packedpixel2vga
90     pop si
91     push es
92   mov di,0A000h ; VGA segment   mov di,0A000h ; VGA segment
93   mov es,di   mov es,di
94   mov di,[VGAPos]   mov di,[VGAPos]
95   mov bp,640   call outputvga
  call packedpixel2vga  
  add word [VGAPos],byte 80 ; Advance to next pixel row  
  push fs  
96   pop es   pop es
97   pop si   add word [VGAPos],640/8
98   pop cx   pop cx
99   loop .drawpixelrow   loop .drawpixelrow
100    
101  .error:  .error:
102   pop es   jmp close ; Tailcall!
  ret  
103    
104  ;  ;
105  ; rledecode:  ; rledecode:
106  ; Decode a pixel row in RLE16 format.  ; Decode a pixel row in RLE16 format.
107  ;  ;
108  ; FS:SI -> input  ; getc stack -> input
109  ; CX -> pixel count  ; CX -> pixel count
110  ; ES:DI -> output (packed pixel)  ; ES:DI -> output (packed pixel)
111  ;  ;
112  rledecode:  rledecode:
113   shl esi,1 ; Nybble pointer   xor dx,dx ; DL = last pixel, DH = nybble buffer
  xor dl,dl ; Last pixel  
114  .loop:  .loop:
115   call .getnybble   call .getnybble
116   cmp al,dl   cmp al,dl
# Line 124  rledecode: Line 120  rledecode:
120   dec cx   dec cx
121   jnz .loop   jnz .loop
122  .done:  .done:
  shr esi,1  
  adc si,byte 0  
123   ret   ret
124  .run:  .run:
125   xor bx,bx   xor bx,bx
126   call .getnybble   call .getnybble
127   and al,al   or bl,al
128   jz .longrun   jz .longrun
  mov bl,al  
129  .dorun:  .dorun:
130   push cx   push cx
131   mov cx,bx   mov cx,bx
# Line 144  rledecode: Line 137  rledecode:
137   jmp short .done   jmp short .done
138  .longrun:  .longrun:
139   call .getnybble   call .getnybble
140   mov ah,al   mov bl,al
141   call .getnybble   call .getnybble
142   shl al,4   shl al,4
143   or al,ah   or bl,al
  mov bl,al  
144   add bx,16   add bx,16
145   jmp short .dorun   jmp short .dorun
146    
147  .getnybble:  .getnybble:
148   shr esi,1   test dh,10h
149   fs lodsb   jz .low
150   jc .high   and dh,0Fh
151   dec si   mov al,dh
  and al,0Fh  
  stc  
  rcl esi,1  
  ret  
 .high:  
  shr al,4  
  cmp si,xbs_vgabuf+trackbufsize ; Chunk overrun  
  jb .nonewchunk  
  call vgagetchunk  
  mov si,xbs_vgabuf ; Start at beginning of buffer  
 .nonewchunk:  
  shl esi,1  
152   ret   ret
153    .low:
154  ;   call getc
155  ; vgagetchunk:   mov dh,al
156  ; Get a new trackbufsize chunk of VGA image data   shr dh,4
157  ;   or dh,10h ; Nybble already read
158  ; On input, ES is assumed to point to the buffer segment.   and al,0Fh
 ;  
 vgagetchunk:  
  pushad  
  mov si,[VGACluster]  
  and si,si  
  jz .eof ; EOF overrun, not much to do...  
   
  mov cx,[BufSafe] ; One trackbuf worth of data  
  mov bx,xbs_vgabuf  
  call getfssec  
   
  jnc .noteof  
  xor si,si  
 .noteof: mov [VGACluster],si  
   
 .eof: popad  
159   ret   ret
160    
161  ;  ;
162  ; packedpixel2vga:  ; packedpixel2vga:
163  ; Convert packed-pixel to VGA bitplanes  ; Convert packed-pixel to VGA bitplanes
164  ;  ;
165  ; FS:SI -> packed pixel string  ; DS:SI -> packed pixel string
166  ; BP    -> pixel count (multiple of 8)  ; BP    -> pixel count (multiple of 8)
167  ; ES:DI -> output  ; DS:DI -> output (four planes)
168  ;  ;
169  packedpixel2vga:  packedpixel2vga:
170   mov dx,3C4h ; VGA Sequencer Register select port   xor cx,cx
  mov al,2 ; Sequencer mask  
  out dx,al ; Select the sequencer mask  
  inc dx ; VGA Sequencer Register data port  
  mov al,1  
  mov bl,al  
171  .planeloop:  .planeloop:
172   pusha   inc cx
173   out dx,al   push si
174     push bp
175  .loop1:  .loop1:
176   mov cx,8   mov bx,8
177  .loop2:  .loop2:
178   xchg cx,bx   lodsb
  fs lodsb  
179   shr al,cl   shr al,cl
180   rcl ch,1 ; VGA is bigendian.  Sigh.   rcl dl,1 ; VGA is bigendian.  Sigh.
181   xchg cx,bx   dec bx
182   loop .loop2   jnz .loop2
183   mov al,bh   mov [di],dl
184   stosb   inc di
185   sub bp,byte 8   sub bp,byte 8
186   ja .loop1   ja .loop1
187   popa   pop bp
188   inc bl   pop si
189   shl al,1   cmp cl,3
  cmp bl,4  
190   jbe .planeloop   jbe .planeloop
191   ret   ret
192    
193  ;  ;
194    ; outputvga:
195    ; Output four subsequent lines of VGA data
196    ;
197    ; DS:SI -> four planes @ 640/8=80 bytes
198    ; ES:DI -> pointer into VGA memory
199    ;
200    outputvga:
201     mov dx,3C4h ; VGA Sequencer Register select port
202     mov al,2 ; Sequencer mask
203     out dx,al ; Select the sequencer mask
204     inc dx ; VGA Sequencer Register data port
205     dec ax ; AL <- 1
206    .loop1:
207     out dx,al ; Select the bit plane to write
208     push di
209     mov cx,640/32
210     rep movsd
211     pop di
212     add ax,ax
213     cmp al,8
214     jbe .loop1
215     ret
216    
217    ;
218  ; vgasetmode:  ; vgasetmode:
219  ; Enable VGA graphics, if possible; return ZF=1 on success  ; Enable VGA graphics, if possible; return ZF=1 on success
220  ; DS must be set to the base segment; ES is set to DS.  ; DS must be set to the base segment; ES is set to DS.
# Line 239  packedpixel2vga: Line 222  packedpixel2vga:
222  vgasetmode:  vgasetmode:
223   push ds   push ds
224   pop es   pop es
225     mov al,[UsingVGA]
226     cmp al,01h
227     je .success ; Nothing to do...
228     test al,04h
229     jz .notvesa
230     ; We're in a VESA mode, which means VGA; use VESA call
231     ; to revert the mode, and then call the conventional
232     ; mode-setting for good measure...
233     mov ax,4F02h
234     mov bx,0012h
235     int 10h
236     jmp .setmode
237    .notvesa:
238   mov ax,1A00h ; Get video card and monitor   mov ax,1A00h ; Get video card and monitor
239   xor bx,bx   xor bx,bx
240   int 10h   int 10h
# Line 248  vgasetmode: Line 244  vgasetmode:
244  ; mov bx,TextColorReg  ; mov bx,TextColorReg
245  ; mov dx,1009h ; Read color registers  ; mov dx,1009h ; Read color registers
246  ; int 10h  ; int 10h
247    .setmode:
248   mov ax,0012h ; Set mode = 640x480 VGA 16 colors   mov ax,0012h ; Set mode = 640x480 VGA 16 colors
249   int 10h   int 10h
250   mov dx,linear_color   mov dx,linear_color
# Line 255  vgasetmode: Line 252  vgasetmode:
252   int 10h   int 10h
253   mov [UsingVGA], byte 1   mov [UsingVGA], byte 1
254    
255     ; Set GXPixCols and GXPixRows
256     mov dword [GXPixCols],640+(480 << 16)
257    
258   call use_font ; Set graphics font/data   call use_font ; Set graphics font/data
259   mov byte [ScrollAttribute], 00h   mov byte [ScrollAttribute], 00h
260    
261    .success:
262   xor ax,ax ; Set ZF   xor ax,ax ; Set ZF
263  .error:  .error:
264   ret   ret
# Line 274  vgaclearmode: Line 275  vgaclearmode:
275   mov ax,cs   mov ax,cs
276   mov ds,ax   mov ds,ax
277   mov es,ax   mov es,ax
278   cmp [UsingVGA], byte 1   mov al,[UsingVGA]
279   jne .done   and al,al ; Already in text mode?
280     jz .done
281     test al,04h
282     jz .notvesa
283     mov ax,4F02h ; VESA return to normal video mode
284     mov bx,0003h
285     int 10h
286    .notvesa:
287   mov ax,0003h ; Return to normal video mode   mov ax,0003h ; Return to normal video mode
288   int 10h   int 10h
289  ; mov dx,TextColorReg ; Restore color registers  ; mov dx,TextColorReg ; Restore color registers
# Line 283  vgaclearmode: Line 291  vgaclearmode:
291  ; int 10h  ; int 10h
292   mov [UsingVGA], byte 0   mov [UsingVGA], byte 0
293    
  call use_font ; Restore text font/data  
294   mov byte [ScrollAttribute], 07h   mov byte [ScrollAttribute], 07h
295     call use_font ; Restore text font/data
296  .done:  .done:
297   popad   popad
298   pop es   pop es
# Line 317  vgacursorcommon: Line 325  vgacursorcommon:
325   section .data   section .data
326   ; Map colors to consecutive DAC registers   ; Map colors to consecutive DAC registers
327  linear_color db 0, 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13, 14, 15, 0  linear_color db 0, 1, 2, 3, 4, 5, 6, 7, 8, 9, 10, 11, 12, 13, 14, 15, 0
328    
329     ; See comboot.doc, INT 22h AX=0017h for the semantics
330     ; of this byte.
331  UsingVGA db 0  UsingVGA db 0
332    
333   section .latebss   section .bss2
334   alignb 2   alignb 4
335    LSSHeader equ $
336    LSSMagic resd 1 ; Magic number
337  GraphXSize resw 1 ; Width of splash screen file  GraphXSize resw 1 ; Width of splash screen file
338    GraphYSize resw 1 ; Height of splash screen file
339    GraphColorMap resb 3*16
340  VGAPos resw 1 ; Pointer into VGA memory  VGAPos resw 1 ; Pointer into VGA memory
 VGACluster resw 1 ; Cluster pointer for VGA image file  
341  VGAFilePtr resw 1 ; Pointer into VGAFileBuf  VGAFilePtr resw 1 ; Pointer into VGAFileBuf
342  TextColorReg resb 17 ; VGA color registers for text mode  ; TextColorReg resb 17 ; VGA color registers for text mode
343  %if IS_SYSLINUX  %if IS_SYSLINUX
344  VGAFileBuf resb FILENAME_MAX+2 ; Unmangled VGA image name  VGAFileBuf resb FILENAME_MAX+2 ; Unmangled VGA image name
345  %else  %else
# Line 334  VGAFileBuf resb FILENAME_MAX ; Unmangled Line 348  VGAFileBuf resb FILENAME_MAX ; Unmangled
348  VGAFileBufEnd equ $  VGAFileBufEnd equ $
349  VGAFileMBuf resb FILENAME_MAX ; Mangled VGA image name  VGAFileMBuf resb FILENAME_MAX ; Mangled VGA image name
350    
351     alignb 4
352    VGARowBuffer resb 640+80 ; Decompression buffer
353    VGAPlaneBuffer resb (640/8)*4 ; Plane buffers

Legend:
Removed from v.1132  
changed lines
  Added in v.1133