Before this fix, the cpu flags were shifted
[syslinux.git] / conio.inc
blobdae4097ba696c27e8ad1ec5d1c5bc46c3be847fd
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.
11 ;; -----------------------------------------------------------------------
14 ;; conio.inc
16 ;; Console I/O code, except:
17 ;;   writechr, writestr         - module-dependent
18 ;;   cwritestr, crlf            - writestr.inc
19 ;;   writehex*                  - writehex.inc
23 ; loadkeys:     Load a LILO-style keymap; SI and DX:AX set by searchdir
25                 section .text
27 loadkeys:
28                 and dx,dx                       ; Should be 256 bytes exactly
29                 jne loadkeys_ret
30                 cmp ax,256
31                 jne loadkeys_ret
33                 mov bx,trackbuf
34                 mov cx,1                        ; 1 cluster should be >= 256 bytes
35                 call getfssec
37                 mov si,trackbuf
38                 mov di,KbdMap
39                 mov cx,256 >> 2
40                 rep movsd
42 loadkeys_ret:   ret
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
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
56                 mov byte [TextAttribute],07h    ; Default grey on white
57                 mov byte [DisplayMask],07h      ; Display text in all modes
58                 call msg_initvars
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                 inc cl                          ; 01h = text mode, 02h = graphics
77                 call [NextCharJump]             ; Do what shall be done
78                 pop si
79                 pop edx
80                 pop cx
81                 dec edx
82                 jz msg_done
83                 loop print_msg_file
84                 pop si
85                 jmp short get_msg_chunk
86 msg_done_pop:
87                 add sp,byte 6                   ; Drop pushed EDX, CX
88 msg_done:
89                 pop si
90                 pop es
91                 ret
92 msg_putchar:                                    ; Normal character
93                 cmp al,0Fh                      ; ^O = color code follows
94                 je msg_ctrl_o
95                 cmp al,0Dh                      ; Ignore <CR>
96                 je msg_ignore
97                 cmp al,0Ah                      ; <LF> = newline
98                 je msg_newline
99                 cmp al,0Ch                      ; <FF> = clear screen
100                 je msg_formfeed
101                 cmp al,07h                      ; <BEL> = beep
102                 je msg_beep
103                 cmp al,19h                      ; <EM> = return to text mode
104                 je msg_novga
105                 cmp al,18h                      ; <CAN> = VGA filename follows
106                 je msg_vga
107                 jnb .not_modectl
108                 cmp al,10h                      ; 10h to 17h are mode controls
109                 jae msg_modectl
110 .not_modectl:
112 msg_normal:     call write_serial_displaymask   ; Write to serial port
113                 test [DisplayMask],cl
114                 jz msg_ignore                   ; Not screen
115                 test byte [DisplayCon],01h
116                 jz msg_ignore
117                 mov bl,[TextAttribute]
118                 mov bh,[BIOS_page]
119                 mov ah,09h                      ; Write character/attribute
120                 mov cx,1                        ; One character only
121                 int 10h                         ; Write to screen
122                 mov al,[CursorCol]
123                 inc ax
124                 cmp al,[VidCols]
125                 ja msg_line_wrap                ; Screen wraparound
126                 mov [CursorCol],al
128 msg_gotoxy:     mov bh,[BIOS_page]
129                 mov dx,[CursorDX]
130                 mov ah,02h                      ; Set cursor position
131                 int 10h
132 msg_ignore:     ret
134 msg_beep:       mov ax,0E07h                    ; Beep
135                 xor bx,bx
136                 int 10h
137                 ret
139 msg_ctrl_o:                                     ; ^O = color code follows
140                 mov word [NextCharJump],msg_setbg
141                 ret
142 msg_newline:                                    ; Newline char or end of line
143                 mov si,crlf_msg
144                 call write_serial_str_displaymask
145 msg_line_wrap:                                  ; Screen wraparound
146                 test [DisplayMask],cl
147                 jz msg_ignore
148                 mov byte [CursorCol],0
149                 mov al,[CursorRow]
150                 inc ax
151                 cmp al,[VidRows]
152                 ja msg_scroll
153                 mov [CursorRow],al
154                 jmp short msg_gotoxy
155 msg_scroll:     xor cx,cx                       ; Upper left hand corner
156                 mov dx,[ScreenSize]
157                 mov [CursorRow],dh              ; New cursor at the bottom
158                 mov bh,[ScrollAttribute]
159                 mov ax,0601h                    ; Scroll up one line
160                 int 10h
161                 jmp short msg_gotoxy
162 msg_formfeed:                                   ; Form feed character
163                 mov si,crff_msg
164                 call write_serial_str_displaymask
165                 test [DisplayMask],cl
166                 jz msg_ignore
167                 xor cx,cx
168                 mov [CursorDX],cx               ; Upper lefthand corner
169                 mov dx,[ScreenSize]
170                 mov bh,[TextAttribute]
171                 mov ax,0600h                    ; Clear screen region
172                 int 10h
173                 jmp msg_gotoxy
174 msg_setbg:                                      ; Color background character
175                 call unhexchar
176                 jc msg_color_bad
177                 shl al,4
178                 test [DisplayMask],cl
179                 jz .dontset
180                 mov [TextAttribute],al
181 .dontset:
182                 mov word [NextCharJump],msg_setfg
183                 ret
184 msg_setfg:                                      ; Color foreground character
185                 call unhexchar
186                 jc msg_color_bad
187                 test [DisplayMask],cl
188                 jz .dontset
189                 or [TextAttribute],al           ; setbg set foreground to 0
190 .dontset:
191                 jmp short msg_putcharnext
192 msg_vga:
193                 mov word [NextCharJump],msg_filename
194                 mov di, VGAFileBuf
195                 jmp short msg_setvgafileptr
197 msg_color_bad:
198                 mov byte [TextAttribute],07h    ; Default attribute
199 msg_putcharnext:
200                 mov word [NextCharJump],msg_putchar
201                 ret
203 msg_filename:                                   ; Getting VGA filename
204                 cmp al,0Ah                      ; <LF> = end of filename
205                 je msg_viewimage
206                 cmp al,' '
207                 jbe msg_ret                     ; Ignore space/control char
208                 mov di,[VGAFilePtr]
209                 cmp di,VGAFileBufEnd
210                 jnb msg_ret
211                 mov [di],al                     ; Can't use stosb (DS:)
212                 inc di
213 msg_setvgafileptr:
214                 mov [VGAFilePtr],di
215 msg_ret:        ret
217 msg_novga:
218                 call vgaclearmode
219                 jmp short msg_initvars
221 msg_viewimage:
222                 push es
223                 push ds
224                 pop es                          ; ES <- DS
225                 mov si,[VGAFilePtr]
226                 mov byte [si],0                 ; Zero-terminate filename
227                 mov si,VGAFileBuf
228                 mov di,VGAFileMBuf
229                 push di
230                 call mangle_name
231                 pop di
232                 call searchdir
233                 pop es
234                 jz msg_putcharnext              ; Not there
235                 call vgadisplayfile
236                 ; Fall through
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
249 msg_modectl:
250                 and al,07h
251                 mov [DisplayMask],al
252                 jmp short msg_putcharnext
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
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
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:
284                 xchg dx,bx                      ; DX -> THR
285                 pop ax
286                 call slow_out                   ; Send data
287 .noserial:      popad
288                 popfd
289 .end:           ret
292 ; write_serial_str: write_serial for strings
293 ; write_serial_str_displaymask: d:o, but ignore if DisplayMask & 04h == 0
295 write_serial_str_displaymask:
296                 test byte [DisplayMask], 04h
297                 jz write_serial_str.end
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
308 ; pollchar: check if we have an input character pending (ZF = 0)
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
333 ; getchar: Read a character from keyboard or serial port
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
371 %ifdef DEBUG_TRACERS
373 ; debug hack to print a character with minimal code impact
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
387                 section .data
388                 ; This is a word to pc_setint16 can set it
389 DisplayCon      dw 01h                  ; Console display enabled
391 ScrollAttribute db 07h                  ; Grey on white (normal text color)
393                 section .bss
394                 alignb 2
395 NextCharJump    resw 1                  ; Routine to interpret next print char
396 CursorDX        equ $
397 CursorCol       resb 1                  ; Cursor column for message file
398 CursorRow       resb 1                  ; Cursor row for message file
399 ScreenSize      equ $
400 VidCols         resb 1                  ; Columns on screen-1
401 VidRows         resb 1                  ; Rows on screen-1
403 ; Serial console stuff...
404 BaudDivisor     resw 1                  ; Baud rate divisor
405 FlowControl     equ $
406 FlowOutput      resb 1                  ; Outputs to assert for serial flow
407 FlowInput       resb 1                  ; Input bits for serial flow
408 FlowIgnore      resb 1                  ; Ignore input unless these bits set
410 TextAttribute   resb 1                  ; Text attribute for message file
411 DisplayMask     resb 1                  ; Display modes mask