source: bootcd/isolinux/syslinux-6.03/dosutil/eltorito.asm @ 26ffad7

Last change on this file since 26ffad7 was e16e8f2, checked in by Edwin Eefting <edwin@datux.nl>, 3 years ago

bootstuff

  • Property mode set to 100644
File size: 24.3 KB
Line 
1
2;-----------------------------------------------------------------------------
3; ElTorito.asm
4;
5; El Torito Bootable CD-ROM driver which does not reset the CD-ROM drive upon
6; loading, but instead accesses the drive through BIOS system calls
7;
8; MIT License
9;
10; (c) 2000 by Gary Tong
11; (c) 2001-2009 by Bart Lagerweij
12;
13; Permission is hereby granted, free of charge, to any person obtaining a copy
14; of this software and associated documentation files (the "Software"), to deal
15; in the Software without restriction, including without limitation the rights
16; to use, copy, modify, merge, publish, distribute, sublicense, and/or sell
17; copies of the Software, and to permit persons to whom the Software is
18; furnished to do so, subject to the following conditions:
19;
20; The above copyright notice and this permission notice shall be included in
21; all copies or substantial portions of the Software.
22;
23; THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR
24; IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY,
25; FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE
26; AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER
27; LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM,
28; OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN
29; THE SOFTWARE.
30;
31;-----------------------------------------------------------------------------
32
33; To assemble and link, use these commands with NASM 2.x:
34;   nasm -Ox -f bin -o eltorito.sys eltorito.asm
35
36; To enable Trace markers uncomment the line below
37; DEBUG_TRACERS=1
38
39; To enable debug info uncomment the line below
40; DEBUG=1
41
42%ifdef DEBUG_TRACERS
43 %macro TRACER  1
44        call debug_tracer
45        db %1
46 %endmacro
47%else
48 %macro TRACER  1
49 %endmacro
50%endif  ; DEBUG_TRACERS
51
52%define Ver     '1.5'
53%define CR      0DH, 0Ah
54RPolyH          equ     0EDB8h
55RPolyL          equ     08320h
56
57                section .text align=16
58                org     0
59
60;=============================================================================
61
62Cdrom:
63
64NextDriver      dd      -1                      ;-+
65Attributes      dw      0C800h                  ; |
66Pointers        dw      Strategy                ; |
67                dw      Commands                ; |   MSCDEX requires this
68DeviceName      db      'ELTORITO'              ; |  data in these locations
69                dw      0                       ; |
70DriveLetter     db      0                       ; |
71NumUnitsSupp    db      1                       ;-+
72
73DriverName      db      'El-Torito CD-ROM Device Driver',0
74                align 4, db 0
75ReqHdrLoc       dd      0
76XferAddr        dd      0
77Checksum        dd      -1
78DriveNumber     db      0
79ReadBytes       db      0                       ;0 --> 2048 bytes/sector
80                                                ;1 --> 1024 bytes/sector
81                                                ;2 -->  512 bytes/sector
82
83Routines        dw      Init            ;Init           ;0
84                dw      Unsupported     ;MediaCheck     ;1
85                dw      Unsupported     ;BuildBPB       ;2
86                dw      IoctlInput      ;IoctlInput     ;3
87                dw      Unsupported     ;Input          ;4
88                dw      Unsupported     ;NonDesInput    ;5
89                dw      Unsupported     ;InputStatus    ;6
90                dw      Unsupported     ;InputFlush     ;7
91                dw      Unsupported     ;Output         ;8
92                dw      Unsupported     ;OutputVerify   ;9
93                dw      Unsupported     ;OutputStatus   ;10
94                dw      Unsupported     ;OutputFlush    ;11
95                dw      IoctlOutput     ;IoctlOutput    ;12
96                dw      DoNothing       ;DeviceOpen     ;13
97                dw      DoNothing       ;DeviceClose    ;14
98                dw      ReadL           ;ReadL          ;128
99
100IoctlICtrl      dw      Raddr           ;Raddr          ;0
101                dw      Unsupported     ;LocHead        ;1
102                dw      Unsupported     ;(Reserved)     ;2
103                dw      Unsupported     ;ErrStat        ;3
104                dw      Unsupported     ;AudInfo        ;4
105                dw      DrvBytes                ;DrvBytes       ;5
106                dw      DevStat         ;DevStat        ;6
107                dw      SectSize                ;SectSize       ;7
108                dw      VolSize         ;VolSize        ;8
109                dw      MedChng         ;MedChng        ;9
110
111SpecPkt         times   19      db      0       ; offset 77h in 1.4
112                times   13      db      0       ; unknown extra 00s in 1.4
113
114Greeting        db      'El-Torito Bootable CD-ROM Driver for Dos v',Ver,', http://www.nu2.nu/eltorito/',CR
115                db      '  (c) 2000 by Gary Tong',CR
116                db      '  (c) 2001-2002 by Bart Lagerweij',CR,0
117DblSpace        db      '  ',0
118
119;=============================================================================
120
121Strategy:
122
123                mov     word [cs:ReqHdrLoc],bx
124                mov     word [cs:ReqHdrLoc+2],es
125                retf
126
127
128;=============================================================================
129
130Commands:
131
132                push    ax
133                push    bx
134                push    cx
135                push    dx
136                push    si
137                push    di
138                push    bp
139;               pushad
140                push    ds
141                push    es
142                TRACER 'C'
143
144                cld                             ;Clear direction
145                sti                             ;Enable interrupts
146
147                mov     ax, cs                  ;ds=cs
148                mov     ds, ax
149
150                les     bx,[ReqHdrLoc]  ;seg:offset ptr into es:bx
151                xor     ax,ax
152                mov     al,[es:bx+2]            ;Get Command code
153%ifdef DEBUG
154                call    print_hex8
155%endif
156                cmp     al,15
157                jb      Mult2                   ;If 0-14
158                cmp     al,128
159                jb      UnknownCmd              ;If 15-127
160                cmp     al,129
161                jb      ShiftDown               ;If 128
162UnknownCmd:     mov     al,121                  ;8 = Unsupported (Reserved)
163ShiftDown:      sub     al,113                  ;128 --> 15, 121 --> 8
164Mult2:          shl     al,1                    ;Convert into offset (*2)
165                mov     di,Routines
166                add     di,ax
167                call    word [di]               ;Execute desired command
168                or      ax,100h                 ;Set Return Status's Done bit
169                lds     bx,[ReqHdrLoc]          ;seg:offset ptr into ds:bx
170                mov     [bx+3],ax               ;Save Status
171
172%ifdef DEBUG
173                cmp     byte [cs:buffer+2048], 96h
174                je      buffer_ok
175                mov     al, '!'
176                call    print_char
177                jmp     $
178buffer_ok:
179%endif
180
181                TRACER 'c'
182                pop     es
183                pop     ds
184;               popad
185                pop     bp
186                pop     di
187                pop     si
188                pop     dx
189                pop     cx
190                pop     bx
191                pop     ax
192                retf
193
194
195;=============================================================================
196
197Unsupported:                    ;Unsupported Command
198
199                mov     ax,8003h                ;Set Status Error bit,
200                TRACER 'U'
201                TRACER 'C'
202                retn                            ;   Error 3 = Unknown Command
203
204
205;=============================================================================
206
207IoctlInput:                     ;IOCTL Input Routine
208
209                mov     di,[es:bx+14]           ;es:bx --> Request Header
210                mov     es,[es:bx+16]           ;Get Xfer Address into es:di
211                xor     ax,ax                   ;Get Control Block Code
212                mov     al,[es:di]
213%ifdef DEBUG
214        TRACER 'I'
215        TRACER 'O'
216        call    print_hex8
217%endif
218                cmp     al,10
219                jb      UnkIoctlI               ;If 0-9
220                mov     al,2                    ;Map to Unsupported
221UnkIoctlI:      shl     al,1                    ;Convert into offset (*2)
222                mov     si,IoctlICtrl
223                add     si,ax
224                call    word [si]               ;Execute desired command
225                retn
226
227
228;=============================================================================
229
230Raddr:                  ;Return Device Header Address
231
232                TRACER 'A'
233                mov     word [es:di+1],0
234                mov     [es:di+3],cs
235                xor     ax, ax                  ;Set Return Status = success
236                TRACER 'a'
237                retn
238
239
240;=============================================================================
241
242DrvBytes:                       ;Read Drive Bytes
243
244                TRACER 'B'
245                push    di                      ;Save original Xfer Addr
246                add     di,2                    ;Point to 1st dest byte
247                mov     si,Greeting     ;Point to Greeting
248DrvB:           movsb                           ;Copy over a byte
249                cmp     byte [si],13    ;Is next char a CR?
250                jne     DrvB                    ;Loop if not
251
252                sub     di,2                    ;Get #bytes copied into ax
253                mov     ax,di
254                pop     di                      ;Retrieve original Xfer Addr
255                sub     ax,di
256                mov     byte [es:di+1],al       ;and save it
257                mov     ax,0                    ;Set Return Status = success
258                TRACER 'b'
259                retn
260
261
262;=============================================================================
263
264DevStat:                        ;Return Device Status
265
266                TRACER 'D'
267                mov     word [es:di+1],202h     ;Door closed
268                mov     word [es:di+3],0        ;Door unlocked
269                                                ;Supports only cooked reading
270                                                ;Read only
271                                                ;Data read only
272                                                ;No interleaving
273                                                ;No prefetching
274                                                ;No audio channel manipulation
275                                                ;Supports both HSG and Redbook
276                                                ;  addressing modes
277
278                xor     ax, ax                  ;Set Return Status = success
279                TRACER 'd'
280                retn
281
282
283;=============================================================================
284
285SectSize:                       ;Return Sector Size
286
287                TRACER 'S'
288                mov     word [es:di+2],2048
289                mov     ax,0                    ;Set Return Status = success
290                TRACER 's'
291                retn
292
293
294;=============================================================================
295
296VolSize:                        ;Return Volume Size
297
298                TRACER 'V'
299                call    PriVolDesc              ;Get and Check Primary Volume
300                                                ;  Descriptor
301                mov     ax,800Fh                ;Assume Invalid Disk Change
302                jc      VolExit                 ;If Read Failure
303
304                mov     ax,word [Buffer+80]     ;Read Successful
305                mov     word [es:di+1],ax       ;Copy over Volume Size
306                mov     ax,word [Buffer+82]
307                mov     word [es:di+3],ax
308                mov     ax,0                    ;Set Return Status = success
309VolExit:
310                TRACER 'v'
311                retn
312
313
314;=============================================================================
315
316MedChng:                        ;Return Media Changed Status
317
318                TRACER 'M'
319                call    PriVolDesc              ;Get and Check Primary Volume
320                                                ;  Descriptor
321                mov     byte [es:di+1],-1       ;Assume Media Changed
322                mov     ax,800Fh                ;  and Invalid Disk Change
323                jc      MedExit                 ;If Media Changed or Bad
324
325                mov     byte [es:di+1],1        ;Media has not changed
326                mov     ax,0                    ;Set Return Status = success
327MedExit:
328                TRACER 'm'
329                retn
330
331
332;=============================================================================
333
334PriVolDesc:                     ;Get and Check Primary Volume
335                                                ;  Descriptor
336                TRACER 'P'
337                mov     ax,cs                   ;Set ds:si --> SpecPkt
338                mov     ds,ax
339
340                mov     cx, 5
341PriVolAgain:
342                mov     byte [SpecPkt],16       ;SpecPkt Size
343                mov     byte [SpecPkt+1],0      ;Reserved
344                mov     word [SpecPkt+2],1      ;Transfer one 2048-byte sector
345                push    cx
346                mov     cl,byte [ReadBytes]     ;Multiply by 4 if reading 512
347                shl     word [SpecPkt+2],cl     ;  bytes at a time
348                pop     cx
349                mov     word [SpecPkt+6],cs     ;Into our Buffer
350                mov     word [SpecPkt+4], Buffer
351                mov     word [SpecPkt+8],16     ;From CD Sector 16
352                mov     word [SpecPkt+10],0
353                mov     word [SpecPkt+12],0
354                mov     word [SpecPkt+14],0
355
356                mov     si, SpecPkt
357                mov     dl, [DriveNumber]
358                mov     ah, 42h                 ;Extended Read
359                int     13h
360                jnc     PriVolPass              ;If success
361
362;               TRACER '1'
363                ; read error
364                loop    PriVolAgain
365
366                TRACER '2'
367                ; read retries exhausted
368                ; flow into below
369                jmp     PriReadErr
370
371PriVolPass:
372                mov     si,Buffer       ;Point input to Buffer
373                mov     ax,-1                   ;Init Checksum registers
374                mov     bx,ax                   ;  bx,ax = 0FFFFFFFFh
375                jc      PriNew                  ;If Read Failure
376
377                push    di                      ;Read Successful,
378                                                ;  so Calculate Checksum
379                mov     di,1024                 ;Init Word counter
380PriWord:        mov     dx,[cs:si]              ;Grab next word from buffer
381                mov     cx,16                   ;Init bit counter
382PriBit:         shr     dx,1                    ;Shift everything right 1 bit
383                rcr     bx,1
384                rcr     ax,1
385                jnc     NoMult                  ;If a zero shifted out
386
387                xor     bx,RPolyH               ;A one shifted out, so XOR
388                xor     ax,RPolyL               ;  Checksum with RPoly
389NoMult:
390                loop    PriBit
391
392                add     si,2                    ;Inc Word Pointer
393                dec     di
394                ja      PriWord
395                TRACER '3'
396
397                pop     di                      ;Checksum calculation complete
398                cmp     bx,[Checksum+2]         ;Has Checksum changed?
399                jne     PriNew                  ;If Checksum Changed
400
401                cmp     ax,[Checksum]
402                jne     PriNew                  ;If Checksum Changed
403
404                clc                             ;Checksum not changed, CF=0
405                mov     ax,0                    ;Status = success
406                jmp     PriOld
407
408PriReadErr:
409                mov     WORD [Checksum+2],bx            ;Save New Checksum
410                mov     [Checksum],ax           ;  or 0FFFFFFFFh if bad read
411                stc                             ;Checksum change, CF=1
412                mov     ax, 800bh               ;Status = read fault
413                jmp     PriOld
414
415PriNew:         mov     WORD [Checksum+2],bx            ;Save New Checksum
416                mov     [Checksum],ax           ;  or 0FFFFFFFFh if bad read
417                stc                             ;Checksum Changed, CF=1
418                mov     ax,800Fh                ;Status = Invalid Media Change
419PriOld:
420                TRACER 'p'
421                retn
422
423
424;=============================================================================
425
426IoctlOutput:                    ;IOCTL Output Routine
427
428                TRACER 'O'
429                mov     di,[es:bx+14]           ;es:bx --> Request Header
430                mov     es,[es:bx+16]           ;Get Xfer Address into es:di
431                xor     ax,ax                   ;Get Control Block Code
432                mov     al,[es:di]
433                cmp     al,2
434                jne     UnkIoctlO               ;If not 2 (ResetDrv)
435                call    DoNothing               ;Reset Drive
436                jmp     IoctlODone
437UnkIoctlO:
438                call    Unsupported             ;Unsupported command
439IoctlODone:
440                TRACER 'o'
441                retn
442
443
444;=============================================================================
445
446DoNothing:                      ;Do Nothing Command
447
448                mov     ax,0                    ;Set Return Status = success
449                retn
450
451
452;=============================================================================
453
454ReadL:                  ;Read Long Command
455
456                TRACER 'R'
457                mov     ax,cs                   ;Set ds=cs
458                mov     ds,ax
459                                                ;es:bx --> Request Header
460                cmp     byte [es:bx+24],0       ;Check Data Read Mode
461                jne     ReadLErr                ;If Cooked Mode
462
463                cmp     byte [es:bx+13],2       ;Check Addressing Mode
464                jb      ReadLOK                 ;If HSG or Redbook Mode
465
466ReadLErr:
467                TRACER '8'
468                mov     ax,8003h                ;Set Return Status = Unknown
469                jmp     ReadLExit               ;  Command Error and exit
470
471ReadLOK:
472                mov     ax,[es:bx+20]           ;Get Starting Sector Number,
473                mov     dx,[es:bx+22]           ;  Assume HSG Addressing Mode
474                cmp     byte [es:bx+13],0       ;Check Addressing Mode again
475                je      ReadLHSG                ;If HSG Addressing Mode
476
477                TRACER '7'
478                ;Using Redbook Addressing Mode.  Convert to HSG format
479                mov     al,dl                   ;Get Minutes
480                mov     dl,60
481                mul     dl                      ;ax = Minutes * 60
482                add     al,byte [es:bx+21]      ;Add in Seconds
483                adc     ah,0
484                mov     dx,75                   ;dx:ax =
485                mul     dx                      ;  ((Min * 60) + Sec) * 75
486                add     al,byte [es:bx+20]      ;Add in Frames
487                adc     ah,0
488                adc     dx,0
489                sub     ax,150                  ;Subtract 2-Second offset
490                sbb     dx,0                    ;dx:ax = HSG Starting Sector
491
492ReadLHSG:
493                mov     word [SpecPkt+8], ax    ;Store Starting
494                mov     word [SpecPkt+10], dx   ;  Sector Number
495                mov     word [SpecPkt+12], 0    ;  (HSG Format)
496                mov     word [SpecPkt+14], 0
497
498                mov     ax,[es:bx+14]           ;Get Transfer Address
499                mov     word [SpecPkt+4],ax
500                mov     ax,[es:bx+16]
501                mov     word [SpecPkt+6],ax
502
503                mov     byte [SpecPkt],16       ;Size of Disk Address Packet
504                mov     byte [SpecPkt+1],0      ;Reserved
505
506                mov     cx, 5
507ReadLAgain:
508                mov     ax,[es:bx+18]           ;Get number of sectors to read
509                mov     word [SpecPkt+2],ax
510                cmp     ax, 3FFFh               ;Too large?
511                ja      ReadLBad                ;If yes
512
513                push    cx
514                mov     cl,byte [ReadBytes]     ;Multiply by 4 if reading 512
515                shl     word [SpecPkt+2],cl     ;  bytes at a time
516                pop     cx
517
518%ifdef DEBUG
519                push    ax
520                push    cx
521                push    si
522                mov     cx, 16
523                mov     si,SpecPkt
524ReadDump:       mov     al, ' '
525                call    print_char
526                mov     al, byte [si]   ;Hexdump a SpecPkt byte
527                call    print_hex8
528                inc     si                      ;Point to next byte
529                loop    ReadDump
530                pop     si
531                pop     cx
532                pop     ax
533%endif
534                mov     si,SpecPkt
535                mov     dl,[DriveNumber]
536                mov     ah,42h                  ;Extended Read
537                int     13h
538                jnc     ReadLGd                 ;If success
539
540;hang:
541;               jmp     hang
542;               TRACER '1'
543                loop    ReadLAgain
544                TRACER '2'
545                jmp short ReadLBad
546ReadLGd:
547                TRACER '3'
548                xor     ax, ax                  ;Status 0 = success
549                jmp short ReadLExit
550
551ReadLBad:
552                TRACER '9'
553                mov     ax, 800Bh               ;Set Read Fault Error
554                ; flow into ReadLExit
555ReadLExit:
556                TRACER 'r'
557                retn
558
559
560
561%ifdef DEBUG_TRACERS
562debug_tracer:   pushad
563                pushfd
564
565                mov     al, '['
566                mov     ah,0Eh                  ;BIOS video teletype output
567                xor     bh, bh
568                int     10h                     ;Print it
569
570                mov     bp,sp
571                mov     bx,[bp+9*4]             ; Get return address
572                mov     al,[cs:bx]              ; Get data byte
573                inc     word [bp+9*4]   ; Return to after data byte
574
575                mov     ah,0Eh                  ;BIOS video teletype output
576                xor     bh, bh
577                int     10h                     ;Print it
578
579                mov     al, ']'
580                mov     ah,0Eh                  ;BIOS video teletype output
581                xor     bh, bh
582                int     10h                     ;Print it
583
584                popfd
585                popad
586                retn
587%endif
588
589;-----------------------------------------------------------------------------
590; PRINT_HEX4
591;-----------------------------------------------------------------------------
592; print a 4 bits integer in hex
593;
594; Input:
595;       AL - 4 bits integer to print (low)
596;
597; Output: None
598;
599; Registers destroyed: None
600;
601print_hex4:
602
603        push    ax
604        and     al, 0fh         ; we only need the first nibble
605        cmp     al, 10
606        jae     hex_A_F
607        add     al, '0'
608        jmp     hex_0_9
609hex_A_F:
610        add     al, 'A'-10
611hex_0_9:
612        call    print_char
613        pop     ax
614        retn
615
616
617;-----------------------------------------------------------------------------
618; print_hex8
619;-----------------------------------------------------------------------------
620; print a 8 bits integer in hex
621;
622; Input:
623;       AL - 8 bits integer to print
624;
625; Output: None
626;
627; Registers destroyed: None
628;
629print_hex8:
630
631        push    ax
632        push    bx
633
634        mov     ah, al
635        shr     al, 4
636        call    print_hex4
637
638        mov     al, ah
639        and     al, 0fh
640        call    print_hex4
641
642        pop     bx
643        pop     ax
644        retn
645
646
647;=============================================================================
648; print_hex16 - print a 16 bits integer in hex
649;
650; Input:
651;       AX - 16 bits integer to print
652;
653; Output: None
654;
655; Registers destroyed: None
656;=============================================================================
657print_hex16:
658
659        push    ax
660        push    bx
661        push    cx
662
663        mov     cx, 4
664print_hex16_loop:
665        rol     ax, 4
666        call    print_hex4
667        loop    print_hex16_loop
668
669        pop     cx
670        pop     bx
671        pop     ax
672        retn
673
674;=============================================================================
675; print_hex32 - print a 32 bits integer in hex
676;
677; Input:
678;       EAX - 32 bits integer to print
679;
680; Output: None
681;
682; Registers destroyed: None
683;=============================================================================
684print_hex32:
685
686        push    eax
687        push    bx
688        push    cx
689
690        mov     cx, 8
691print_hex32_loop:
692        rol     eax, 4
693        call    print_hex4
694        loop    print_hex32_loop
695
696        pop     cx
697        pop     bx
698        pop     eax
699        retn
700
701;=============================================================================
702; print_string - print string at current cursor location
703;
704; Input:
705;       DS:SI - ASCIIZ string to print
706;
707; Output: None
708;
709; Registers destroyed: None
710;=============================================================================
711print_string:
712                push    ax
713                push    si
714
715print_string_again:
716                mov     al, [si]
717                or      al, al
718                jz      print_string_exit
719                call    print_char
720                inc     si
721                jmp     print_string_again
722
723print_string_exit:
724                pop     si
725                pop     ax
726                retn
727
728;-----------------------------------------------------------------------------
729; PRINT_CHAR
730;-----------------------------------------------------------------------------
731; Print's a character at current cursor position
732;
733; Input:
734;       AL - Character to print
735;
736; Output: None
737;
738; Registers destroyed: None
739;
740print_char:
741
742                push    ax
743                push    bx
744
745                mov     ah,0Eh                  ;BIOS video teletype output
746                xor     bh, bh
747                int     10h                     ;Print it
748
749print_char_exit:
750                pop     bx
751                pop     ax
752                retn
753
754
755;=============================================================================
756
757;This space is used as a 2048-byte read buffer plus one test byte.
758;The 96h data is used for testing the number of bytes returned by an Extended
759;  CD-ROM sector read
760
761                align   16, db 0
762Buffer          times   2049    db      96h
763
764;=============================================================================
765
766Init:                   ;Initialization Routine
767
768                TRACER 'I'
769                mov     ax,cs                   ;ds=cs
770                mov     ds,ax
771
772%ifdef DEBUG
773; print CS value (load segment)
774                call    print_hex16
775%endif
776
777                mov     si, Greeting    ;Display Greeting
778                call    print_string
779
780                mov     ax,Unsupported  ;Init is executed only once
781                mov     [Routines],ax
782
783                mov     ax, 5400h
784                int     13h                     ; Get diskemu status
785                jc      FindBoot                ; If CF=1 no diskemu loaded
786
787                mov     [DriveNumber], cl               ; Store drive number
788
789                call    keyflag
790                and     al, 8                   ; alt key ?
791                jz      extread
792
793                mov     si, DrvNumMsg   ; Display "drive number="
794                call    print_string
795                mov     al, [DriveNumber]
796                call    print_hex8
797                mov     si, LineEnd     ; CR/LF
798                call    print_string
799                jmp     extread
800
801; Diskemu is not loaded
802; so loop to find drive number
803                ; *** start of 1.4 changes ***
804                ; ??? mov dl, 0ffh              ;Start at Drive 0xff
805                ; *** FindBoot at c47 in 1.4, at c0c in 1.3 ***
806FindBoot:       call    ScanDrives              ; call new helper in 1.4
807                jnc     FoundBoot               ; ded*df3
808;               mov     si,offset SpecPkt       ;Locate booted CD-ROM drive
809;               mov     [SpecPkt],0             ;Clear 1st byte of SpecPkt
810;               mov     ax,4B01h                ;Get Bootable CD-ROM Status
811;               int     13h
812;               jnc     FindPass                ;If booted CD found
813;
814; Carry is not cleared in buggy Dell BIOSes,
815; so I'm checking packet size byte
816; some bogus bioses (Dell Inspiron 2500) returns packet size 0xff when failed
817; Dell Dimension XPsT returns packet size 0x14 when OK
818
819;               cmp     [SpecPkt], 0
820;               jne     FoundBoot
821
822;               cmp     [SpecPkt], 13h  ; anything between 13h and 20h should be OK
823;               jb      FindFail
824;               cmp     [SpecPkt], 20h
825;               ja      FindFail
826;               jmp     short FoundBoot
827;
828; FindFail:
829;               dec     dl                      ;Next drive
830;               cmp     dl, 80h
831;               jae     FindBoot                ;Check from ffh..80h
832                ; *** end of 1.4 changes ***
833
834                mov     si,NoBootCD     ;No booted CD found,
835                call    print_string
836                jmp     NoEndAddr               ;Do not install driver
837
838FoundBoot:
839;               mov     dl, [SpecPkt+2]         ; 1.4 change
840                ; *** next line at c57 in 1.4, at c3d in 1.3 ***
841                mov     [DriveNumber],dl                ;Booted CD-ROM found,
842                                                ;  so save Drive #
843
844                call    keyflag
845                and     al, 8                   ; alt key ?
846                jz      extread
847
848                mov     si, CDStat
849                call    print_string
850                mov     si, SpecPkt     ;Point to returned CD SpecPkt
851                mov     cx, 19                  ;  containing 19 bytes
852StatDump:       mov     al, ' '                 ;Print a space
853                call    print_char
854                mov     al, byte [si]   ;Hexdump a SpecPkt byte
855                call    print_hex8
856                inc     si                      ;Point to next byte
857                loop    StatDump
858
859                mov     si, LineEnd     ;Print a CR/LF
860                call    print_string
861
862extread:
863;See how many CD Sector bytes are returned by an Extended Read
864                mov     byte [SpecPkt],16       ;SpecPkt Size
865                mov     byte [SpecPkt+1],0      ;Reserved
866                mov     word [SpecPkt+2],1      ;Transfer one sector
867                mov     word [SpecPkt+6],cs     ;Into our Buffer
868                mov     word [SpecPkt+4],Buffer
869                mov     word [SpecPkt+8],16     ;From CD Sector 16
870                mov     word [SpecPkt+10],0
871                mov     word [SpecPkt+12],0
872                mov     word [SpecPkt+14],0
873
874                mov     si, SpecPkt     ;Set ds:si --> SpecPkt
875                mov     dl, [DriveNumber]
876                mov     ah, 42h                 ;Extended Read
877                int     13h
878                jnc     SecSize                 ;If success
879
880                mov     ah, 42h                 ;Always make 2 read attempts
881                int     13h
882                                                ;How many bytes did we get?
883SecSize:        std                             ;Count down
884                mov     ax,cs                   ;Point to end of Buffer
885                mov     es,ax
886                mov     di,Buffer+2047  ;Find end of read data
887                mov     si,Buffer+2048
888                mov     cx,2049
889                repe    cmpsb                   ;cx = number of bytes read
890
891                cld                             ;Restore count direction to up
892                mov     si,CDBytes      ;Display number of bytes read
893                call    print_string
894
895                mov     al, [DriveNumber]
896                call    print_hex8
897
898                mov     si,CDBytesA     ;Remainder A of message
899                call    print_string
900
901                mov     al,ch                   ;Hex-dump cx
902                and     al,0Fh                  ;Second nibble
903                call    print_hex8              ;  (don't need the First)
904                mov     al,cl
905                call    print_hex8              ;  (don't need the First)
906
907                mov     si,CDBytesB     ;Remainder B of message
908                call    print_string
909
910                cmp     cx,2048                 ;Did we read 2048 bytes?
911                je      ParseParm               ;If yes <-- O.K.
912
913                mov     byte [ReadBytes],1
914                cmp     cx,1024                 ;Did we read 1024 bytes?
915                je      ParseParm               ;If yes <-- O.K.
916
917                mov     byte [ReadBytes],2
918                cmp     cx,512                  ;Did we read 512 bytes?
919                jne     NoEndAddr               ;If not, do not load driver
920
921ParseParm:      mov     bx,word [cs:ReqHdrLoc]  ;Parse command line
922                mov     es,word [cs:ReqHdrLoc+2]        ;  parameters
923                mov     si,[es:bx+18]           ;Get BPB array ptr into DS:SI
924                mov     ds,[es:bx+20]
925FindParm:       inc     si
926FindParm1:      cmp     byte [si],0Dh   ;CR? (End of parameters)
927                je      EndOfParms
928
929                cmp     byte [si],0Ah   ;LF?
930                je      EndOfParms
931
932                cmp     byte [si],'/'   ;A parameter?
933                jne     FindParm
934
935                inc     si
936                cmp     byte [si],'D'   ;Device Name parameter?
937                jne     FindParm1
938
939                inc     si
940                cmp     byte [si],':'
941                jne     FindParm1
942
943;bbb
944                push    si
945                mov     si, DevName     ;Device Name is at ds:si
946                push    ds                      ;Keep ptr to Device Name
947                mov     ax, cs
948                mov     ds, ax
949                call    print_string
950                pop     ds                      ;Retrieve Device Name ptr
951                pop     si
952                mov     cx, 8                   ;Get next 8 chars
953                inc     si                      ;  = Device Name
954                mov     ax, cs
955                mov     es, ax
956                mov     di, DeviceName
957NextChar:       cmp     byte [si],' '
958                ja      AboveSpace
959
960                mov     ax,cs                   ;Pad end of Device Name with
961                mov     ds,ax                   ;  spaces if necessary
962                mov     si,DblSpace     ;A space
963AboveSpace:     mov     al, [si]
964                call    print_char
965                movsb                           ;ds:[si] --> es:[di]
966                loop    NextChar
967
968                mov     si,LineEnd
969                mov     ax,cs
970                mov     ds,ax
971                call    print_string
972
973                mov     ax,Init-2       ;Last byte of driver to keep
974                jmp     EndAddr                 ;Install driver
975
976EndOfParms:
977                mov     ax, cs                  ; Restore segment registers (fix)
978                mov     ds, ax
979                mov     es, ax
980
981                mov     si,NoDevName    ;No Device Name Found
982                call    print_string
983
984NoEndAddr:      mov     ax,0                    ;Do not install driver
985
986EndAddr:        mov     es,[ReqHdrLoc+2]                ;Write End Address
987                mov     bx,[ReqHdrLoc]
988                mov     [es:bx+14],ax
989                mov     [es:bx+16],cs
990                mov     bx,ax                   ;Hold onto install status
991
992                mov     si, DrvInst     ;Display driver install status
993                call    print_string
994                mov     si, DrvInst1    ;Assume driver installed
995                cmp     bx,0                    ;Was driver installed?
996                jne     DrvStatus               ;If yes
997                mov     si, NoDrvInst   ;Driver not installed
998DrvStatus:      call    print_string
999
1000                mov     ax,0                    ;Set Return Status = success
1001                cmp     bx,0                    ;Was INIT successful?
1002                jne     InitStat                ;If yes
1003                mov     ax,800Ch                ;Status = General Failure
1004InitStat:
1005                push    ax                      ;Save Return Status
1006
1007                call    keyflag
1008                and     al, 8                   ; alt key ?
1009                jz      InitExit
1010
1011WaitHere:
1012                mov     si, WaitMsg     ;Display Halted message
1013                call    print_string
1014
1015AltWait:
1016                call    keyflag
1017                and     al, 8                   ; Alt key?
1018                jnz     AltWait                 ; Pressed? yes -> wait
1019
1020InitExit:
1021                pop     ax                      ;Retrieve Return Status
1022                TRACER 'i'
1023                retn                            ;That's it for Init!
1024
1025                ; *** start 1.4 changes at ded ***
1026SpecGo:         mov     si,SpecPkt
1027                int     13h
1028                retn
1029
1030ScanDrives:     push    ax              ; at df3 in 1.4
1031                push    si
1032                mov dl, 7fh             ;Start at Drive 0x80
1033NextDrv:        inc     dl
1034                clc
1035                mov     ax,4B01h        ;Get Bootable CD-ROM Status
1036                mov     BYTE [SpecPkt],0        ;Clear 1st byte of SpecPkt
1037                call    SpecGo
1038; Carry is not cleared in buggy Dell BIOSes,
1039; so I'm checking packet size byte
1040; some bogus bioses (Dell Inspiron 2500) returns packet size 0xff when failed
1041; Dell Dimension XPsT returns packet size 0x14 when OK
1042
1043                cmp     BYTE [SpecPkt], 13h     ; anything between 13h and 20h should be OK
1044                jb      FindFail
1045                cmp     BYTE [SpecPkt], 20h
1046                ja      FindFail        ; in 1.4 at e16
1047                jmp     short SendFound ; in 1.4 at e26
1048
1049FindFail:       cmp     dl, 0ffh
1050                je      SendFail                ; Check from 80h..ffh
1051                jmp     short NextDrv           ;Next drive
1052SendFail:       xor     dl,dl
1053                stc
1054                jmp     short ThingDone
1055SendFound:      mov     dl, [SpecPkt+2]
1056                clc
1057ThingDone:      pop     si
1058                pop     ax
1059                retn
1060                ; *** end 1.4 changes ***
1061
1062;=============================================================================
1063
1064;------------------------------------------------------------
1065; keyboard flags - return keyboard flags in AL
1066; bit 3 = ALT key
1067keyflag:        ; at dbc in 1.3, at e2e in 1.4
1068        push    bx
1069        mov     ah, 2
1070        int     16h
1071        pop     bx
1072        retn
1073
1074;=============================================================================
1075
1076DrvNumMsg       db      '  Diskemxx.bin returned drive number=', 0
1077NoBootCD        db      '  No booted CD-ROM found.',CR,0
1078
1079CDStat          db      '  INT 13h / AX=4B01h Specification Packet for '
1080                db      'Booted CD-ROM:',CR,'     ', 0
1081
1082CDBytes         db      '  Drive ', 0
1083CDBytesA        db      ' returns ', 0
1084CDBytesB        db      'h bytes per Sector.',CR,0
1085
1086DevName         db      '  Device Name: ', 0
1087NoDevName       db      '  No Device Name found. '
1088                db      'Usage: device=eltorito.sys /D:<DevName>',CR,0
1089
1090DrvInst         db      '  Driver ', 0
1091NoDrvInst       db      7,'not '                ;7 = Ctrl-G = Beep
1092DrvInst1        db      'installed',CR,0
1093
1094WaitMsg         db      '  Alt pressed, waiting...', CR, 0
1095;ContMsg                db      '  Continuing...'
1096LineEnd         db      CR,0
1097
1098
1099;=============================================================================
Note: See TracBrowser for help on using the repository browser.