mboot.c32:load ELF segments from the segment header
[syslinux.git] / conio.inc
blob5860333ec36fd200754799ad017c678a88bfd892
1 ;; $Id$
2 ;; -----------------------------------------------------------------------
3 ;;   
4 ;;   Copyright 1994-2005 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.
12 ;; -----------------------------------------------------------------------
15 ;; conio.inc
17 ;; Console I/O code, except:
18 ;;   writechr, writestr         - module-dependent
19 ;;   cwritestr, crlf            - writestr.inc
20 ;;   writehex*                  - writehex.inc
24 ; loadkeys:     Load a LILO-style keymap; SI and DX:AX set by searchdir
26                 section .text
28 loadkeys:
29                 and dx,dx                       ; Should be 256 bytes exactly
30                 jne loadkeys_ret
31                 cmp ax,256
32                 jne loadkeys_ret
34                 mov bx,trackbuf
35                 mov cx,1                        ; 1 cluster should be >= 256 bytes
36                 call getfssec
38                 mov si,trackbuf
39                 mov di,KbdMap
40                 mov cx,256 >> 2
41                 rep movsd
43 loadkeys_ret:   ret
44                 
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
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
57                 mov byte [TextAttribute],07h    ; Default grey on white
58                 mov byte [DisplayMask],07h      ; Display text in all modes
59                 call msg_initvars
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,07h                      ; <BEL> = beep
103                 je msg_beep
104                 cmp al,19h                      ; <EM> = return to text mode
105                 je msg_novga
106                 cmp al,18h                      ; <CAN> = VGA filename follows
107                 je msg_vga
108                 jnb .not_modectl
109                 cmp al,10h                      ; 10h to 17h are mode controls
110                 jae msg_modectl
111 .not_modectl:
113 msg_normal:     call write_serial_displaymask   ; Write to serial port
114                 test [DisplayMask],cl
115                 jz msg_ignore                   ; Not screen
116                 test byte [DisplayCon],01h
117                 jz msg_ignore
118                 mov bl,[TextAttribute]
119                 mov bh,[BIOS_page]
120                 mov ah,09h                      ; Write character/attribute
121                 mov cx,1                        ; One character only
122                 int 10h                         ; Write to screen
123                 mov al,[CursorCol]
124                 inc ax
125                 cmp al,[VidCols]
126                 ja msg_line_wrap                ; Screen wraparound
127                 mov [CursorCol],al
129 msg_gotoxy:     mov bh,[BIOS_page]
130                 mov dx,[CursorDX]
131                 mov ah,02h                      ; Set cursor position
132                 int 10h
133 msg_ignore:     ret
135 msg_beep:       mov ax,0E07h                    ; Beep
136                 xor bx,bx
137                 int 10h
138                 ret
140 msg_ctrl_o:                                     ; ^O = color code follows
141                 mov word [NextCharJump],msg_setbg
142                 ret
143 msg_newline:                                    ; Newline char or end of line
144                 mov si,crlf_msg
145                 call write_serial_str_displaymask
146 msg_line_wrap:                                  ; Screen wraparound
147                 test [DisplayMask],cl
148                 jz msg_ignore
149                 mov byte [CursorCol],0
150                 mov al,[CursorRow]
151                 inc ax
152                 cmp al,[VidRows]
153                 ja msg_scroll
154                 mov [CursorRow],al
155                 jmp short msg_gotoxy
156 msg_scroll:     xor cx,cx                       ; Upper left hand corner
157                 mov dx,[ScreenSize]
158                 mov [CursorRow],dh              ; New cursor at the bottom
159                 mov bh,[ScrollAttribute]
160                 mov ax,0601h                    ; Scroll up one line
161                 int 10h
162                 jmp short msg_gotoxy
163 msg_formfeed:                                   ; Form feed character
164                 mov si,crff_msg
165                 call write_serial_str_displaymask
166                 test [DisplayMask],cl
167                 jz msg_ignore
168                 xor cx,cx
169                 mov [CursorDX],cx               ; Upper lefthand corner
170                 mov dx,[ScreenSize]
171                 mov bh,[TextAttribute]
172                 mov ax,0600h                    ; Clear screen region
173                 int 10h
174                 jmp msg_gotoxy
175 msg_setbg:                                      ; Color background character
176                 call unhexchar
177                 jc msg_color_bad
178                 shl al,4
179                 test [DisplayMask],cl
180                 jz .dontset
181                 mov [TextAttribute],al
182 .dontset:
183                 mov word [NextCharJump],msg_setfg
184                 ret
185 msg_setfg:                                      ; Color foreground character
186                 call unhexchar
187                 jc msg_color_bad
188                 test [DisplayMask],cl
189                 jz .dontset
190                 or [TextAttribute],al           ; setbg set foreground to 0
191 .dontset:
192                 jmp short msg_putcharnext
193 msg_vga:
194                 mov word [NextCharJump],msg_filename
195                 mov di, VGAFileBuf
196                 jmp short msg_setvgafileptr
198 msg_color_bad:
199                 mov byte [TextAttribute],07h    ; Default attribute
200 msg_putcharnext:
201                 mov word [NextCharJump],msg_putchar
202                 ret
204 msg_filename:                                   ; Getting VGA filename
205                 cmp al,0Ah                      ; <LF> = end of filename
206                 je msg_viewimage
207                 cmp al,' '
208                 jbe msg_ret                     ; Ignore space/control char
209                 mov di,[VGAFilePtr]
210                 cmp di,VGAFileBufEnd
211                 jnb msg_ret
212                 mov [di],al                     ; Can't use stosb (DS:)
213                 inc di
214 msg_setvgafileptr:
215                 mov [VGAFilePtr],di
216 msg_ret:        ret
218 msg_novga:
219                 call vgaclearmode
220                 jmp short msg_initvars
222 msg_viewimage:
223                 push es
224                 push ds
225                 pop es                          ; ES <- DS
226                 mov si,[VGAFilePtr]
227                 mov byte [si],0                 ; Zero-terminate filename
228                 mov si,VGAFileBuf
229                 mov di,VGAFileMBuf
230                 push di
231                 call mangle_name
232                 pop di
233                 call searchdir
234                 pop es
235                 jz msg_putcharnext              ; Not there
236                 call vgadisplayfile
237                 ; Fall through
239                 ; Subroutine to initialize variables, also needed
240                 ; after loading a graphics file
241 msg_initvars:
242                 pusha
243                 mov bh,[BIOS_page]
244                 mov ah,03h                      ; Read cursor position
245                 int 10h
246                 mov [CursorDX],dx
247                 popa
248                 jmp short msg_putcharnext       ; Initialize state machine
250 msg_modectl:
251                 and al,07h
252                 mov [DisplayMask],al
253                 jmp short msg_putcharnext
256 ; write_serial: If serial output is enabled, write character on serial port
257 ; write_serial_displaymask: d:o, but ignore if DisplayMask & 04h == 0
259 write_serial_displaymask:
260                 test byte [DisplayMask], 04h
261                 jz write_serial.end
262 write_serial:
263                 pushfd
264                 pushad
265                 mov bx,[SerialPort]
266                 and bx,bx
267                 je .noserial
268                 push ax
269                 mov ah,[FlowInput]
270 .waitspace:
271                 ; Wait for space in transmit register
272                 lea dx,[bx+5]                   ; DX -> LSR
273                 in al,dx
274                 test al,20h
275                 jz .waitspace
277                 ; Wait for input flow control
278                 inc dx                          ; DX -> MSR
279                 in al,dx
280                 and al,ah
281                 cmp al,ah
282                 jne .waitspace  
283 .no_flow:               
285                 xchg dx,bx                      ; DX -> THR
286                 pop ax
287                 call slow_out                   ; Send data
288 .noserial:      popad
289                 popfd
290 .end:           ret
293 ; write_serial_str: write_serial for strings
294 ; write_serial_str_displaymask: d:o, but ignore if DisplayMask & 04h == 0
296 write_serial_str_displaymask:
297                 test byte [DisplayMask], 04h
298                 jz write_serial_str.end
300 write_serial_str:
301 .loop           lodsb
302                 and al,al
303                 jz .end
304                 call write_serial
305                 jmp short .loop
306 .end:           ret
309 ; pollchar: check if we have an input character pending (ZF = 0)
311 pollchar:
312                 pushad
313                 mov ah,11h              ; Poll keyboard
314                 int 16h
315                 jnz .done               ; Keyboard response
316                 mov dx,[SerialPort]
317                 and dx,dx
318                 jz .done                ; No serial port -> no input
319                 add dx,byte 5           ; DX -> LSR
320                 in al,dx
321                 test al,1               ; ZF = 0 if data pending
322                 jz .done
323                 inc dx                  ; DX -> MSR
324                 mov ah,[FlowIgnore]     ; Required status bits
325                 in al,dx
326                 and al,ah
327                 cmp al,ah
328                 setne al
329                 dec al                  ; Set ZF = 0 if equal
330 .done:          popad
331                 ret
334 ; getchar: Read a character from keyboard or serial port
336 getchar:
337                 RESET_IDLE
338 .again:
339                 DO_IDLE
340                 mov ah,11h              ; Poll keyboard
341                 int 16h
342                 jnz .kbd                ; Keyboard input?
343                 mov bx,[SerialPort]
344                 and bx,bx
345                 jz .again
346                 lea dx,[bx+5]           ; DX -> LSR
347                 in al,dx
348                 test al,1
349                 jz .again
350                 inc dx                  ; DX -> MSR
351                 mov ah,[FlowIgnore]
352                 in al,dx
353                 and al,ah
354                 cmp al,ah
355                 jne .again
356 .serial:        xor ah,ah               ; Avoid confusion
357                 xchg dx,bx              ; Data port
358                 in al,dx
359                 ret
360 .kbd:           mov ah,10h              ; Get keyboard input
361                 int 16h
362                 cmp al,0E0h
363                 jnz .not_ext
364                 xor al,al
365 .not_ext:
366                 and al,al
367                 jz .func_key
368                 mov bx,KbdMap           ; Convert character sets
369                 xlatb
370 .func_key:      ret
372 %ifdef DEBUG_TRACERS
374 ; debug hack to print a character with minimal code impact
376 debug_tracer:   pushad
377                 pushfd
378                 mov bp,sp
379                 mov bx,[bp+9*4]         ; Get return address
380                 mov al,[cs:bx]          ; Get data byte
381                 inc word [bp+9*4]       ; Return to after data byte
382                 call writechr
383                 popfd
384                 popad
385                 ret
386 %endif  ; DEBUG_TRACERS
388                 section .data
389                 ; This is a word to pc_setint16 can set it
390 DisplayCon      dw 01h                  ; Console display enabled
392 ScrollAttribute db 07h                  ; Grey on white (normal text color)
394                 section .bss
395                 alignb 2
396 NextCharJump    resw 1                  ; Routine to interpret next print char
397 CursorDX        equ $
398 CursorCol       resb 1                  ; Cursor column for message file
399 CursorRow       resb 1                  ; Cursor row for message file
400 ScreenSize      equ $
401 VidCols         resb 1                  ; Columns on screen-1
402 VidRows         resb 1                  ; Rows on screen-1
404 ; Serial console stuff...
405 BaudDivisor     resw 1                  ; Baud rate divisor
406 FlowControl     equ $
407 FlowOutput      resb 1                  ; Outputs to assert for serial flow
408 FlowInput       resb 1                  ; Input bits for serial flow
409 FlowIgnore      resb 1                  ; Ignore input unless these bits set
411 TextAttribute   resb 1                  ; Text attribute for message file
412 DisplayMask     resb 1                  ; Display modes mask