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