More fixes to the extlinux installer; change back to writable types
[profile/ivi/syslinux.git] / conio.inc
1 ;; $Id$
2 ;; -----------------------------------------------------------------------
3 ;;   
4 ;;   Copyright 1994-2004 H. Peter Anvin - All Rights Reserved
5 ;;
6 ;;   This program is free software; you can redistribute it and/or modify
7 ;;   it under the terms of the GNU General Public License as published by
8 ;;   the Free Software Foundation, Inc., 53 Temple Place Ste 330,
9 ;;   Boston MA 02111-1307, USA; either version 2 of the License, or
10 ;;   (at your option) any later version; incorporated herein by reference.
11 ;;
12 ;; -----------------------------------------------------------------------
13
14 ;;
15 ;; conio.inc
16 ;;
17 ;; Console I/O code, except:
18 ;;   writechr, writestr         - module-dependent
19 ;;   cwritestr, crlf            - writestr.inc
20 ;;   writehex*                  - writehex.inc
21 ;;
22
23 ;
24 ; loadkeys:     Load a LILO-style keymap; SI and DX:AX set by searchdir
25 ;
26                 section .text
27
28 loadkeys:
29                 and dx,dx                       ; Should be 256 bytes exactly
30                 jne loadkeys_ret
31                 cmp ax,256
32                 jne loadkeys_ret
33
34                 mov bx,trackbuf
35                 mov cx,1                        ; 1 cluster should be >= 256 bytes
36                 call getfssec
37
38                 mov si,trackbuf
39                 mov di,KbdMap
40                 mov cx,256 >> 2
41                 rep movsd
42
43 loadkeys_ret:   ret
44                 
45 ;
46 ; get_msg_file: Load a text file and write its contents to the screen,
47 ;               interpreting color codes.  Is called with SI and DX:AX
48 ;               set by routine searchdir
49 ;
50 get_msg_file:
51                 push es
52                 shl edx,16                      ; EDX <- DX:AX (length of file)
53                 mov dx,ax
54                 mov ax,xfer_buf_seg             ; Use for temporary storage
55                 mov es,ax
56
57                 mov byte [TextAttribute],07h    ; Default grey on white
58                 mov byte [DisplayMask],07h      ; Display text in all modes
59                 call msg_initvars
60
61 get_msg_chunk:  push edx                        ; EDX = length of file
62                 xor bx,bx                       ; == xbs_textbuf
63                 mov cx,[BufSafe]
64                 call getfssec
65                 pop edx
66                 push si                         ; Save current cluster
67                 xor si,si                       ; == xbs_textbuf
68                 mov cx,[BufSafeBytes]           ; Number of bytes left in chunk
69 print_msg_file:
70                 push cx
71                 push edx
72                 es lodsb
73                 cmp al,1Ah                      ; DOS EOF?
74                 je msg_done_pop
75                 push si
76                 mov cl,[UsingVGA]
77                 inc cl                          ; 01h = text mode, 02h = graphics
78                 call [NextCharJump]             ; Do what shall be done
79                 pop si
80                 pop edx
81                 pop cx
82                 dec edx
83                 jz msg_done
84                 loop print_msg_file
85                 pop si
86                 jmp short get_msg_chunk
87 msg_done_pop:
88                 add sp,byte 6                   ; Drop pushed EDX, CX
89 msg_done:
90                 pop si
91                 pop es
92                 ret
93 msg_putchar:                                    ; Normal character
94                 cmp al,0Fh                      ; ^O = color code follows
95                 je msg_ctrl_o
96                 cmp al,0Dh                      ; Ignore <CR>
97                 je msg_ignore
98                 cmp al,0Ah                      ; <LF> = newline
99                 je msg_newline
100                 cmp al,0Ch                      ; <FF> = clear screen
101                 je msg_formfeed
102                 cmp al,19h                      ; <EM> = return to text mode
103                 je msg_novga
104                 cmp al,18h                      ; <CAN> = VGA filename follows
105                 je msg_vga
106                 jnb .not_modectl
107                 cmp al,10h                      ; 10h to 17h are mode controls
108                 jae msg_modectl
109 .not_modectl:
110
111 msg_normal:     call write_serial_displaymask   ; Write to serial port
112                 test [DisplayMask],cl
113                 jz msg_ignore                   ; Not screen
114                 mov bl,[TextAttribute]
115                 mov bh,[BIOS_page]
116                 mov ah,09h                      ; Write character/attribute
117                 mov cx,1                        ; One character only
118                 int 10h                         ; Write to screen
119                 mov al,[CursorCol]
120                 inc ax
121                 cmp al,[VidCols]
122                 ja msg_line_wrap                ; Screen wraparound
123                 mov [CursorCol],al
124
125 msg_gotoxy:     mov bh,[BIOS_page]
126                 mov dx,[CursorDX]
127                 mov ah,02h                      ; Set cursor position
128                 int 10h
129 msg_ignore:     ret
130 msg_ctrl_o:                                     ; ^O = color code follows
131                 mov word [NextCharJump],msg_setbg
132                 ret
133 msg_newline:                                    ; Newline char or end of line
134                 mov si,crlf_msg
135                 call write_serial_str_displaymask
136 msg_line_wrap:                                  ; Screen wraparound
137                 test [DisplayMask],cl
138                 jz msg_ignore
139                 mov byte [CursorCol],0
140                 mov al,[CursorRow]
141                 inc ax
142                 cmp al,[VidRows]
143                 ja msg_scroll
144                 mov [CursorRow],al
145                 jmp short msg_gotoxy
146 msg_scroll:     xor cx,cx                       ; Upper left hand corner
147                 mov dx,[ScreenSize]
148                 mov [CursorRow],dh              ; New cursor at the bottom
149                 mov bh,[ScrollAttribute]
150                 mov ax,0601h                    ; Scroll up one line
151                 int 10h
152                 jmp short msg_gotoxy
153 msg_formfeed:                                   ; Form feed character
154                 mov si,crff_msg
155                 call write_serial_str_displaymask
156                 test [DisplayMask],cl
157                 jz msg_ignore
158                 xor cx,cx
159                 mov [CursorDX],cx               ; Upper lefthand corner
160                 mov dx,[ScreenSize]
161                 mov bh,[TextAttribute]
162                 mov ax,0600h                    ; Clear screen region
163                 int 10h
164                 jmp msg_gotoxy
165 msg_setbg:                                      ; Color background character
166                 call unhexchar
167                 jc msg_color_bad
168                 shl al,4
169                 test [DisplayMask],cl
170                 jz .dontset
171                 mov [TextAttribute],al
172 .dontset:
173                 mov word [NextCharJump],msg_setfg
174                 ret
175 msg_setfg:                                      ; Color foreground character
176                 call unhexchar
177                 jc msg_color_bad
178                 test [DisplayMask],cl
179                 jz .dontset
180                 or [TextAttribute],al           ; setbg set foreground to 0
181 .dontset:
182                 jmp short msg_putcharnext
183 msg_vga:
184                 mov word [NextCharJump],msg_filename
185                 mov di, VGAFileBuf
186                 jmp short msg_setvgafileptr
187
188 msg_color_bad:
189                 mov byte [TextAttribute],07h    ; Default attribute
190 msg_putcharnext:
191                 mov word [NextCharJump],msg_putchar
192                 ret
193
194 msg_filename:                                   ; Getting VGA filename
195                 cmp al,0Ah                      ; <LF> = end of filename
196                 je msg_viewimage
197                 cmp al,' '
198                 jbe msg_ret                     ; Ignore space/control char
199                 mov di,[VGAFilePtr]
200                 cmp di,VGAFileBufEnd
201                 jnb msg_ret
202                 mov [di],al                     ; Can't use stosb (DS:)
203                 inc di
204 msg_setvgafileptr:
205                 mov [VGAFilePtr],di
206 msg_ret:        ret
207
208 msg_novga:
209                 call vgaclearmode
210                 jmp short msg_initvars
211
212 msg_viewimage:
213                 push es
214                 push ds
215                 pop es                          ; ES <- DS
216                 mov si,VGAFileBuf
217                 mov di,VGAFileMBuf
218                 push di
219                 call mangle_name
220                 pop di
221                 call searchdir
222                 pop es
223                 jz msg_putcharnext              ; Not there
224                 call vgadisplayfile
225                 ; Fall through
226
227                 ; Subroutine to initialize variables, also needed
228                 ; after loading a graphics file
229 msg_initvars:
230                 pusha
231                 mov bh,[BIOS_page]
232                 mov ah,03h                      ; Read cursor position
233                 int 10h
234                 mov [CursorDX],dx
235                 popa
236                 jmp short msg_putcharnext       ; Initialize state machine
237
238 msg_modectl:
239                 and al,07h
240                 mov [DisplayMask],al
241                 jmp short msg_putcharnext
242
243 ;
244 ; write_serial: If serial output is enabled, write character on serial port
245 ; write_serial_displaymask: d:o, but ignore if DisplayMask & 04h == 0
246 ;
247 write_serial_displaymask:
248                 test byte [DisplayMask], 04h
249                 jz write_serial.end
250 write_serial:
251                 pushfd
252                 pushad
253                 mov bx,[SerialPort]
254                 and bx,bx
255                 je .noserial
256                 push ax
257                 mov ah,[FlowInput]
258 .waitspace:
259                 ; Wait for space in transmit register
260                 lea dx,[bx+5]                   ; DX -> LSR
261                 in al,dx
262                 test al,20h
263                 jz .waitspace
264
265                 ; Wait for input flow control
266                 inc dx                          ; DX -> MSR
267                 in al,dx
268                 and al,ah
269                 cmp al,ah
270                 jne .waitspace  
271 .no_flow:               
272
273                 xchg dx,bx                      ; DX -> THR
274                 pop ax
275                 call slow_out                   ; Send data
276 .noserial:      popad
277                 popfd
278 .end:           ret
279
280 ;
281 ; write_serial_str: write_serial for strings
282 ; write_serial_str_displaymask: d:o, but ignore if DisplayMask & 04h == 0
283 ;
284 write_serial_str_displaymask:
285                 test byte [DisplayMask], 04h
286                 jz write_serial_str.end
287
288 write_serial_str:
289 .loop           lodsb
290                 and al,al
291                 jz .end
292                 call write_serial
293                 jmp short .loop
294 .end:           ret
295
296 ;
297 ; pollchar: check if we have an input character pending (ZF = 0)
298 ;
299 pollchar:
300                 pushad
301                 mov ah,11h              ; Poll keyboard
302                 int 16h
303                 jnz .done               ; Keyboard response
304                 mov dx,[SerialPort]
305                 and dx,dx
306                 jz .done                ; No serial port -> no input
307                 add dx,byte 5           ; DX -> LSR
308                 in al,dx
309                 test al,1               ; ZF = 0 if data pending
310                 jz .done
311                 inc dx                  ; DX -> MSR
312                 mov ah,[FlowIgnore]     ; Required status bits
313                 in al,dx
314                 and al,ah
315                 cmp al,ah
316                 setne al
317                 dec al                  ; Set ZF = 0 if equal
318 .done:          popad
319                 ret
320
321 ;
322 ; getchar: Read a character from keyboard or serial port
323 ;
324 getchar:
325                 RESET_IDLE
326 .again:
327                 DO_IDLE
328                 mov ah,11h              ; Poll keyboard
329                 int 16h
330                 jnz .kbd                ; Keyboard input?
331                 mov bx,[SerialPort]
332                 and bx,bx
333                 jz .again
334                 lea dx,[bx+5]           ; DX -> LSR
335                 in al,dx
336                 test al,1
337                 jz .again
338                 inc dx                  ; DX -> MSR
339                 mov ah,[FlowIgnore]
340                 in al,dx
341                 and al,ah
342                 cmp al,ah
343                 jne .again
344 .serial:        xor ah,ah               ; Avoid confusion
345                 xchg dx,bx              ; Data port
346                 in al,dx
347                 ret
348 .kbd:           mov ah,10h              ; Get keyboard input
349                 int 16h
350                 cmp al,0E0h
351                 jnz .not_ext
352                 xor al,al
353 .not_ext:
354                 and al,al
355                 jz .func_key
356                 mov bx,KbdMap           ; Convert character sets
357                 xlatb
358 .func_key:      ret
359
360 %ifdef DEBUG_TRACERS
361 ;
362 ; debug hack to print a character with minimal code impact
363 ;
364 debug_tracer:   pushad
365                 pushfd
366                 mov bp,sp
367                 mov bx,[bp+9*4]         ; Get return address
368                 mov al,[cs:bx]          ; Get data byte
369                 inc word [bp+9*4]       ; Return to after data byte
370                 call writechr
371                 popfd
372                 popad
373                 ret
374 %endif  ; DEBUG_TRACERS
375
376                 section .data
377 ScrollAttribute db 07h                  ; Grey on white (normal text color)
378
379                 section .bss
380                 alignb 2
381 NextCharJump    resw 1                  ; Routine to interpret next print char
382 CursorDX        equ $
383 CursorCol       resb 1                  ; Cursor column for message file
384 CursorRow       resb 1                  ; Cursor row for message file
385 ScreenSize      equ $
386 VidCols         resb 1                  ; Columns on screen-1
387 VidRows         resb 1                  ; Rows on screen-1
388
389 ; Serial console stuff...
390 BaudDivisor     resw 1                  ; Baud rate divisor
391 FlowControl     equ $
392 FlowOutput      resb 1                  ; Outputs to assert for serial flow
393 FlowInput       resb 1                  ; Input bits for serial flow
394 FlowIgnore      resb 1                  ; Ignore input unless these bits set
395
396 TextAttribute   resb 1                  ; Text attribute for message file
397 DisplayMask     resb 1                  ; Display modes mask