Imported Upstream version 23.2
[rrq/maintain_lilo.git] / src / crt.S
1 #if 0
2 ; crt.S  is
3 Copyright 2000-2005 John Coffman.
4 All rights reserved.
5
6 Licensed under the terms contained in the file 'COPYING' in the 
7 source directory.
8
9 #endif
10 ;
11
12 XPITCH  =       MAX_IMAGE_NAME+6
13 MINROW  =       4
14 MAX2COL =       14
15 MAXTITLE  =     3
16 MAXCOMMENT  =   3
17
18
19 ; menu_setup:
20 ;   main setup menu for LILO boot selection process
21 ;
22 menu_setup:
23         pusha
24         call    mn_getcursor
25         push    dx              ; save cursor position
26         call    mn_init
27         mov     dx,cx
28
29         cmp     byte [abs_cx+1],#0
30         jne     findl0          ; skip clearing screen on second time thru
31 ; clear the screen
32         xor     cx,cx
33         mov     bh,[mn_at_mono]
34         mov     al,#0
35         call    mn_drawbox
36
37 findl0:
38         xor     si,si           ; number of names
39         xor     di,di           ; max. name length
40         mov     cx,#IMAGES      ; get max number to search
41         mov     bx,#DESCR0      ; get address to start at
42 findl1: call    strlen          ; get length in ax
43         or      ax,ax
44         jz      findl3
45 #ifdef LCF_VIRTUAL
46         test    word ptr (bx+id_flags),#FLAG_VMDEFAULT
47         jz      findl1c
48         call    vmtest
49         jnc     findl1c
50         mov     [vimage],si
51 findl1c:
52 #endif
53 #ifdef LCF_NOKEYBOARD
54         test    word ptr (bx+id_flags),#FLAG_NOKBDEFAULT
55         jz      findl1d
56         call    kbtest
57         jc      findl1d
58         mov     [vimage],si
59 findl1d:
60 #endif
61         cmp     ax,di
62         jb      findl2
63         xchg    ax,di
64 findl2: add     bx,#id_size
65         inc     si
66         loop    findl1
67
68 findl3: mov     [nimage],si
69         mov     [limage],di
70         mov     bx,#str_title   ;
71         call    strlen
72         mov     bl,[mn_max_row_col]
73         sub     bl,al
74         shr     bl,#1
75
76         push    bx
77
78         mov     ax,si
79         mov     bl,#2           ;set for 2 columns
80         cmp     al,#MAX2COL
81         jle     col1
82         inc     bl
83 col1:   mov     [ncol],bl
84         add     al,bl
85         dec     al
86         div     bl
87         cmp     al,#MINROW
88         jg      row1
89         mov     al,#MINROW
90 row1:   cbw
91         mov     [nrow],ax
92 ;;;     add     ax,#4+4+1
93         add     ax,#MAXTITLE+1 +MAXCOMMENT+1 +1
94         mov     dh,al           ; 
95         mov     al,#XPITCH              ; standard width
96         mul     bl
97         mov     dl,al
98         mov     cl,[mn_max_row_col]
99         sub     cl,dl
100         shr     cl,#1
101         mov     ch,#1
102         mov     al,#0x83
103         mov     bh,[mn_at_text]
104         call    mn_drawbox
105         mov     [area_cx],cx
106         mov     [area_dx],dx
107         push    dx
108         add     dx,cx           ; absolute location
109         sub     dx,#0x0306
110         mov     [timer_dx],dx   ; save location of timer
111         pop     dx
112         add     ch,#2           ; title height
113
114         mov     bp,sp
115         xchg    dx,(bp)
116
117         mov     dh,ch
118         mov     bx,#str_title
119         mov     al,[mn_at_title]
120         call    mn_wrstra
121
122         pop     dx
123
124         add     ch,#2
125         mov     al,#1
126         call    mn_hline
127
128         push    cx
129
130         inc     ch
131         add     ch,[nrow]
132         mov     al,#1
133         call    mn_hline
134         mov     dx,cx
135
136         push    dx
137
138         add     dx,#0x102
139         mov     al,[mn_at_text]
140         mov     bx,#str_com1
141         test    byte ptr par2_flag2,#FLAG2_UNATTENDED
142         jz      mn_attended
143         mov     bx,#str_com1u   ; unattended
144 mn_attended:
145         call    mn_wrstra
146         inc     dh
147         mov     bx,#str_com2
148         call    mn_wrstra
149         inc     dh
150         mov     bx,#str_com3
151         call    mn_wrstra
152         mov     dx,[timer_dx]
153         mov     bx,#str_timer
154         call    mn_wrstra
155
156         pop     dx
157         pop     cx
158
159         sub     dh,ch
160         mov     ah,[ncol]
161         mov     si,#DESCR0      ; get start pointer
162         mov     di,[nimage]
163         mov     [norigin],cx
164 vlines:
165         add     cl,#3
166         mov     al,#1
167         call    mn_vline
168
169         push    cx
170         push    dx
171
172         mov     dx,cx
173         add     dx,#0x102
174         mov     cx,[nrow]
175         cmp     cx,di
176         jb      vl1
177         mov     cx,di
178 vl1:    jcxz    vl3
179 vl2:    mov     bx,si
180         mov     al,[mn_at_text]
181         call    mn_wrstra
182
183         push    ax
184         push    dx
185         sub     dl,#4
186         mov     ah,al
187         test    word [id_flags](si),#FLAG_TOOBIG        ; test for unbootable
188         mov     al,#0x55                ; 'U' for possibly unbootable
189         jnz     vl20
190         mov     al,#0x46                ; 'F' for fallback
191         test    byte [id_flags](si),#FLAG_FALLBACK
192         jnz     vl20
193         mov     al,#0x4C                ; 'L' for lock
194         test    byte [id_flags](si),#FLAG_LOCK
195 #ifdef LCF_VIRTUAL
196         jnz     vl20
197         mov     al,#0x57                ; 'W' for vmWarn
198         test    word [id_flags](si),#FLAG_VMWARN
199 #endif
200         jz      vl21
201 vl20:   call    mn_wrcha
202 vl21:   
203         inc     dl
204         test    byte [id_flags](si),#FLAG_PASSWORD      ; test for password
205         jz      vl23
206         mov     al,#0x50                ; 'P' for password
207         test    byte [id_flags](si),#FLAG_RESTR
208         jz      vl22
209         mov     al,#0x52                ; 'R' for restricted options
210 vl22:   call    mn_wrcha
211 vl23:   pop     dx
212         pop     ax
213
214         inc     dh
215         dec     di
216         add     si,#id_size
217         loop    vl2
218 vl3:
219         pop     dx
220         pop     cx
221
222         add     cl,#XPITCH-3
223         dec     ah
224         jz      vdone
225         mov     al,#2
226         call    mn_vline
227         jmp     vlines
228 vdone:
229         mov     ax,[dimage]             ; usually zero
230 #if defined(LCF_VIRTUAL) || defined(LCF_NOKEYBOARD)
231         test    byte ptr [cmdline],#0xFF
232         jnz     vdone3
233         mov     ax,[vimage]
234 vdone3:
235 #endif
236         call    hilite
237
238         pop     dx                      ; get saved cursor position
239         cmp     byte [abs_cx+1],#0
240         jne     nohome
241
242         mov     dx,[area_cx]
243         add     dx,[area_dx]
244         xor     dl,dl
245         add     dh,#2
246         mov     [abs_cx],dx             ; set home cursor position
247 nohome: 
248         call    mn_setcursor
249
250         popa
251         ret
252 ; end of menu_setup subroutine
253
254 #if 0
255 ; find_image
256 ;       if there is something on the command line
257 ;       return the image number it selects
258 ;
259 ;       enter with:
260 ;               nothing
261 ;       exit with:
262 ;               If nothing selected:
263 ;                   Carry Clear
264 ;                   AX==0
265 ;               If an image is selected:
266 ;                   Carry SET
267 ;                   AX==#image
268 ;                   BX==pointer to descriptor
269 ;                   
270 ;
271 ;       side effect:
272 ;               The selected image is hi-lited if the menu is displayed
273 ;
274 find_image:
275         push    cx
276         push    si
277         push    di
278         
279         mov     cx,#IMAGES      ! test all names
280         mov     si,#DESCR0
281         push    si
282 fi_nextn:
283         mov     di,#cmdline
284 fi_nextc:
285         mov     al,(si)         ! get next character in descr
286                                 ! get the character
287 #ifdef LCF_IGNORECASE
288         call    upcase
289 #endif
290         mov     ah,al
291         mov     al,(di)         ! get next char in cmdline
292 #ifdef LCF_IGNORECASE
293         call    upcase
294 #endif
295         or      ah,ah           ! NUL in descriptor name
296         jz      fi_dscend
297         cmp     al,ah           ! character equal ?
298         jne     fi_skipn                ! no -> try next one
299         inc     si              ! test next character
300         inc     di
301         jmp     fi_nextc
302 fi_dscend:      
303         cmp     al,#32          ! space or NUL -> equal
304         je      fi_found
305         or      al,al
306         jz      fi_found
307
308 fi_skipn:
309         pop     si
310         add     si,#id_size     ! test next name
311         push    si
312         loop    fi_nextn
313
314         pop     si
315         xor     ax,ax           ; clears the carry
316 fi_exit:
317         pop     di
318         pop     si
319         pop     cx
320         ret
321         
322 fi_found:
323         pop     bx              ! BX is matched descriptor
324         mov     ax,bx
325         sub     ax,#DESCR0
326         mov     cl,#id_size
327         div     cl
328         cbw
329         mov     di,[dimage]
330         cmp     ax,di
331         je      fi_nochange
332         mov     [dimage],ax
333         cmp     byte [abs_cx+1],#0      ! see if menu is displayed
334         je      fi_nochange
335         xchg    ax,di
336         call    lowlite
337         xchg    ax,di
338         call    hilite
339 fi_nochange:
340         stc
341         jmp     fi_exit
342 #endif
343
344 ; menu_delline:
345 ;       delete the current command line
346 ;                               common code from original second.S
347 ;
348 ;       enter with:
349 ;               BX = command line pointer
350 ;
351 ;       exit with:
352 ;               BX = updated command line pointer
353 ;
354 ;
355 menu_delline:
356         cmp     bx,#cmdline     ! done ?
357         je      mdel9           ! yes -> done
358         push    bx              ! display BS,SPC,BS
359         mov     bx,#bs
360         call    say
361         pop     bx
362         dec     bx              ! move the pointer
363         jmp     menu_delline            ! next one
364 mdel9:  ret
365
366
367 ; menu_setcmd:
368 ;       set currently selected image to be the command line
369 ;
370 ;       enter with:
371 ;               AX = image# to select
372 ;               BX = cmdline pointer
373 ;
374 ;       exit with:
375 ;               BX = updated
376 ;
377 ;
378 menu_setcmd:
379         push    si
380
381         push    ax
382
383         call    menu_delline    ; delete the current line
384
385         pop     si              ; get image# back
386
387         imul    si,#id_size
388         add     si,#DESCR0
389 mset1:  lodsb
390         or      al,al
391         jz      mset6
392         mov     (bx),al
393         inc     bx
394         push    bx
395         call    display
396         pop     bx
397         jmp     mset1
398         
399 mset6:
400         pop     si      
401         ret
402
403
404 ; arrow
405 ;
406 ;   Code that handles the arrow keys:  left, up, down, right
407 ;
408 ;
409 arrow:  cbw                     ; signed delta vector in AL
410         mov     dx,[dimage]     ;
411         add     dx,ax           ; new position
412         or      dx,dx
413         jns     arr1
414 arr0:   xor     dx,dx           ; set to zero if neg.
415 arr1:   mov     ax,[nimage]
416         cmp     dx,ax           ; compare to max.
417         jb      arr2
418         mov     dx,ax
419         dec     dx
420 arr2:                   ; we know the one to hi-lite is in range
421         mov     ax,[dimage]
422         cmp     ax,dx
423         je      arr6
424
425         call    lowlite         ; un-hilite the old
426         xchg    ax,dx
427         call    hilite
428
429         call    menu_setcmd     ; set new command line
430 arr6:
431         jmp     arr_vector
432
433         
434 null:   mov     al,#1
435         cmp     ah,#0x50                ; down arrow
436         je      arrow
437
438         neg     al
439         cmp     ah,#0x48                ; up arrow
440         je      arrow
441
442         mov     dx,[nimage]
443         cmp     ah,#0x4f                ; end
444         je      arr1
445
446         cmp     ah,#0x47                ; home
447         je      arr0
448
449         mov     al,[nrow]
450         xchg    ax,dx
451         mov     ax,[dimage]
452         div     dl                      
453         xchg    ax,dx                   ; DL = cur col.
454
455         cmp     ah,#0x4d                ; right arrow
456         jne     arr8
457         inc     dx                      ; similar to  dec al
458         cmp     dl,[ncol]               ; cmp (CUR COL + 1) : (NCOL)
459         jb      arrow
460         jmp     arr9
461         
462 arr8:
463         cmp     ah,#0x49                ; pg up
464         jne     arr84
465         neg     dh                      ; remainder [0..(nrow-1)]
466         mov     al,dh
467 arrow1: jmp     arrow
468
469 arr84:
470         cmp     ah,#0x51                ; pg dn
471         jne     arr88
472         not     dh
473         add     al,dh
474         jmp     arrow
475
476 arr88:
477         neg     al
478         cmp     ah,#0x4b                ; left arrow
479         jne     arr9
480         or      dl,dl
481         jnz     arrow1
482
483 arr9:
484         cmp     ah,#0x53                ; DEL
485         jne     arr_vector
486         br      delch                   ; treat as 0177 (rubout)
487
488 arr_vector:
489         br      input           ; ignore the rest
490
491 ; menu_exit:
492 ;       erase the menu box to black
493 ;
494 menu_exit:
495         pusha
496         mov     cx,[area_cx]
497         mov     dx,[area_dx]
498         mov     al,#0x80
499         mov     bh,[mn_at_mono]
500         call    mn_drawbox
501         popa
502         ret
503
504 ; menu_form_feed:
505 ;       simulate a FF on the console
506 ;
507 menu_form_feed:
508         pusha
509 ;;      push    ds
510 ;;      push    cs
511 ;;      pop     ds
512         mov     cx,[abs_cx]     ! get home position
513         mov     dx,[mn_max_row_col]
514         xor     al,al
515         mov     bh,#0x07
516         call    mn_drawbox
517         mov     dx,cx
518         call    mn_setcursor
519 ;;      pop     ds
520         popa
521         ret
522
523 ; timer_display:
524 ;       check the timer 'cntdown' and display changes
525 ;
526 timer_display:
527         pusha
528
529         cmp     word [timer_dx],#0      ; see if not initialized
530         jz      timer99
531
532         mov     dx,#0x2d2d      ; get "--" means disabled
533         mov     [tim_min],dx
534         mov     [tim_sec],dx
535         mov     ax,[cntdown]    ; get timer countdown location
536         cmp     ax,[tim_tick]
537         je      timer99
538         mov     [tim_tick],ax   ; save last tick count  
539         inc     ax
540         jz      timer8
541
542         mul     c55             ; get time remaining in ms.
543         div     c1000           ; convert to seconds
544         xor     dx,dx
545         div     c60             ; minutes in AX, seconds in DX  
546         aam
547         add     ax,#0x3030
548         xchg    ah,al
549         mov     [tim_min],ax    ; put characters in buffer
550         xchg    ax,dx
551         aam
552         add     ax,#0x3030
553         xchg    ah,al
554         mov     [tim_sec],ax    ; put characters in buffer
555
556 timer8:
557         call    mn_getcursor
558         push    dx
559         mov     dx,[timer_dx]
560         mov     ah,[mn_at_text]
561         mov     si,#tim_min
562         mov     bx,#tim_old
563         mov     cx,#5
564 timer91:
565         lodsb
566         cmp     al,(bx)
567         je      timer92
568         call    mn_wrcha
569         mov     (bx),al
570 timer92:
571         inc     bx
572         inc     dl
573         loop    timer91
574         pop     dx
575         call    mn_setcursor
576 timer99:
577         popa
578         ret
579
580 tim_min: db     0,0
581         .ascii  ":"
582 tim_sec: db     0,0
583
584 tim_old: .ascii "*****"
585 tim_tick: dw    0               ; last timer tick value examined
586
587 c55:    .word   2197            ;was 55, now 54.925*40
588 c1000:  .word   40000           ;was 1000, now 40*1000
589 c60:    .word   60
590
591
592 ; hilite/lowlite
593 ;       enter with:
594 ;               AX = number [0..(nimage-1)] of entry to hilite
595 ;
596 hilite: push    bx
597         mov     [dimage],ax             ; remember the latest
598         mov     bh,[mn_at_hilite]
599         jmp     lowlite1
600
601 lowlite:  push  bx
602         mov     bh,[mn_at_text]
603 lowlite1:
604         push    cx
605         push    dx
606         push    ax
607
608         call    mn_getcursor
609         push    dx                      ;save current cursor position
610
611         mov     dx,[norigin]
612         add     dx,#0x104
613         mov     cx,[limage]
614         inc     cx
615         inc     cx
616
617         push    bx
618         mov     bx,[nrow]
619 ll1:    cmp     ax,bx
620         jb      ll2
621         add     dl,#XPITCH              ; index by column
622         sub     ax,bx
623         jmp     ll1
624 ll2:    add     dh,al
625         pop     bx              ; restore attribute in BH
626
627 ll3:    call    mn_rdcha        ; read char and attribute
628         mov     ah,bh
629         call    mn_wrcha        ; write back with new attribute
630         inc     dl
631         loop    ll3
632
633         pop     dx              ; restore cursor
634         call    mn_setcursor
635
636         pop     ax
637         pop     dx
638         pop     cx
639         pop     bx
640         ret
641
642
643 ; title_stuff
644 ;
645 ;
646 title_stuff:
647         cmp     dword (bx),#0x554e454d  ; "MENU"
648         jne     noschema
649         mov     edx,(bx+4)
650         mov     [mn_attrib],edx
651 noschema:
652         add     bx,#9           ; point at possible title
653         mov     al,(bx-1)       ; get length stored by installer
654         or      al,al
655         jz      notitle         ; no title if supplied length is 0
656         cbw
657         xchg    ax,cx           ; supplied length to CX
658         call    strlen
659         cmp     ax,cx
660         jne     notitle
661         cmp     ax,#str_title_len
662         jae     notitle
663         push    di
664         mov     di,#str_title   ;
665 titlemov:
666         mov     al,(bx)
667         inc     bx
668         seg ds
669           stosb
670         or      al,al
671         jnz     titlemov
672
673         pop     di
674 notitle:
675         ret
676
677
678 dimage: dw      0       ; default image
679 #if defined(LCF_VIRTUAL) || defined(LCF_NOKEYBOARD)
680 vimage: dw      0       ; vmdefault image
681 #endif
682 norigin: dw     0       ; row/col origin of names on screen
683 nimage: dw      0       ; number of images
684 limage: dw      0       ; longest length of image name
685 nrow:   dw      0       ; number of rows of selections
686 ncol:   dw      0       ; number of columns (default=2)
687 ;wcol:  db      0       ; width of each column (default=XPITCH=21)
688 area_cx:  dw    0       ; area of interaction
689 area_dx:  dw    0       ; area of interaction
690 abs_cx: dw      0       ; upper left of scrolling area
691 ;abs_dx:        dw      0       ; lower right of scrolling area
692 ;       mn_max_row_col is the same as the above (abs_dx)
693 timer_dx: dw    0       ; timer location
694
695
696 str_title:
697         .ascii  "GNU/Linux - "
698         .ascii  "LILO "
699 #ifdef LCF_VERSION
700         .ascii  SA(VERSION_MAJOR)
701         .ascii  " - "   
702 #endif
703         .ascii  "Boot Menu"
704         .byte   0
705         .org    str_title+MAX_MENU_TITLE+1
706
707 str_timer:
708         .ascii  "--:--"
709         db      0
710
711 str_title_len   = str_timer-str_title-1
712
713 str_com1:
714         .ascii  "Hit any key to cancel timeout"
715 ;               "XXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXXX 00:00"
716         db      0
717 str_com1u:
718         .ascii  "Hit any key to restart timeout"
719         db      0
720
721 str_com2:
722         .ascii  "Use "
723         db      27              ; left-arrow
724         db      24,25           ; up-arrow, down-arrow
725         db      26              ; right-arrow
726         .ascii  " arrow keys to make selection"
727         db      0
728 str_com3:
729         .ascii  "Enter choice & options, hit CR to boot"
730         db      0
731
732 ; end of crt.S