66c7cd0b305490e8ca8af25a7e9e7c03cc97195c
[external/syslinux.git] / diag / geodsp / geodspms.lst
1      1                                  ; -----------------------------------------------------------------------
2      2                                  ;
3      3                                  ;   Copyright 2010 Gene Cumm
4      4                                  ;
5      5                                  ;   Portions from diskstart.inc:
6      6                                  ;   Copyright 1994-2009 H. Peter Anvin - All Rights Reserved
7      7                                  ;   Copyright 2009-2010 Intel Corporation; author: H. Peter Anvin
8      8                                  ;
9      9                                  ;   This program is free software; you can redistribute it and/or modify
10     10                                  ;   it under the terms of the GNU General Public License as published by
11     11                                  ;   the Free Software Foundation, Inc., 51 Franklin St, Fifth Floor,
12     12                                  ;   Boston MA 02110-1301, USA; either version 2 of the License, or
13     13                                  ;   (at your option) any later version; incorporated herein by reference.
14     14                                  ;
15     15                                  ; -----------------------------------------------------------------------
16     16                                  
17     17                                  ;
18     18                                  ; geodspms.asm
19     19                                  ;
20     20                                  ; Display geometry translation info for diagnosing misconceptions
21     21                                  ; multi-sector variant
22     22                                  ;
23     23                                  ;       nasm -Ox -f bin -o geodsp.bin -l geodsp.lst geodsp.asm
24     24                                  ;
25     25                                  ;       nasm -Ox -f elf -o geodsp.o -l geodsp.lst geodsp.asm
26     26                                  ;       ld -m elf_i386  -T syslinux.ld -M -o geodsp.elf geodsp.o > geodsp.map
27     27                                  ;       objcopy -O binary geodsp.elf geodsp.raw
28     28                                  ;
29     29                                  ;       # OF=/dev/sdb
30     30                                  ;       # dd if=core/geodsp.bin of=$OF
31     31                                  ;       # dd skip=1 seek=1 if=../dbg/lba-img/lba-img.bin of=$OF
32     32                                  ;       # eject $OF
33     33                                  ;       # dd count=$() if=/dev/zero of=$OF
34     34                                  ;
35     35                                  ;       # OF=geo-2.255.63.i
36     36                                  ;       # (dd if=core/geodsp.bin; dd skip=1 if=../dbg/lba-img/lba-img.bin; dd count=$((2*255*63 - 256*63 - 1)) if=/dev/zero )|dd of=$OF
37     37                                  ;       # OF=geo-20.16.63.i
38     38                                  ;       # (dd if=core/geodsp.bin; dd skip=1 if=../dbg/lba-img/lba-img.bin; dd count=$((40*16*63 - 256*63 - 1)) if=/dev/zero )|dd of=$OF
39     39                                  ;
40     40                                  
41     41                                  ; Just to define it to look like SYSLINUX
42     42                                  %define IS_SYSLINUX 1
43     43                                  
44     44                                  %include "macros.inc"
45     45                              <1> ;; -----------------------------------------------------------------------
46     46                              <1> ;;
47     47                              <1> ;;   Copyright 1994-2008 H. Peter Anvin - All Rights Reserved
48     48                              <1> ;;   Copyright 2009 Intel Corporation; author: H. Peter Anvin
49     49                              <1> ;;
50     50                              <1> ;;   This program is free software; you can redistribute it and/or modify
51     51                              <1> ;;   it under the terms of the GNU General Public License as published by
52     52                              <1> ;;   the Free Software Foundation, Inc., 53 Temple Place Ste 330,
53     53                              <1> ;;   Boston MA 02111-1307, USA; either version 2 of the License, or
54     54                              <1> ;;   (at your option) any later version; incorporated herein by reference.
55     55                              <1> ;;
56     56                              <1> ;; -----------------------------------------------------------------------
57     57                              <1> 
58     58                              <1> ;;
59     59                              <1> ;; macros.inc
60     60                              <1> ;;
61     61                              <1> ;; Convenient macros
62     62                              <1> ;;
63     63                              <1> 
64     64                              <1> %ifndef _MACROS_INC
65     65                              <1> %define _MACROS_INC
66     66                              <1> 
67     67                              <1> ;
68     68                              <1> ; Identify the module we're compiling; the "correct" should be defined
69     69                              <1> ; in the module itself to 1
70     70                              <1> ;
71     71                              <1> %ifdef IS_SYSLINUX
72     72                              <1>  %define MY_NAME 'SYSLINUX'
73     73                              <1> %else
74     74                              <1>  %define IS_SYSLINUX 0
75     75                              <1> %endif
76     76                              <1> %ifdef IS_PXELINUX
77     77                              <1>  %define MY_NAME 'PXELINUX'
78     78                              <1> %else
79     79                              <1>  %define IS_PXELINUX 0
80     80                              <1> %endif
81     81                              <1> %ifdef IS_ISOLINUX
82     82                              <1>  %define MY_NAME 'ISOLINUX'
83     83                              <1> %else
84     84                              <1>  %define IS_ISOLINUX 0
85     85                              <1> %endif
86     86                              <1> %ifdef IS_EXTLINUX
87     87                              <1>  %define MY_NAME 'EXTLINUX'
88     88                              <1> %else
89     89                              <1>  %define IS_EXTLINUX 0
90     90                              <1> %endif
91     91                              <1> 
92     92                              <1> ;
93     93                              <1> ; Macros similar to res[bwd], but which works in the code segment (after
94     94                              <1> ; section .text16) or the data segment (section .data16)
95     95                              <1> ;
96     96                              <1> %macro  zb      1.nolist
97     97                              <1>         times %1 db 0
98     98                              <1> %endmacro
99     99                              <1> 
100    100                              <1> %macro  zw      1.nolist
101    101                              <1>         times %1 dw 0
102    102                              <1> %endmacro
103    103                              <1> 
104    104                              <1> %macro  zd      1.nolist
105    105                              <1>         times %1 dd 0
106    106                              <1> %endmacro
107    107                              <1> 
108    108                              <1> ;
109    109                              <1> ; Align with zero bytes in a progbits segment
110    110                              <1> ;
111    111                              <1> %macro  alignz  1.nolist
112    112                              <1>         times (((%1) - (($-$$) % (%1))) % (%1)) db 0
113    113                              <1> %endmacro
114    114                              <1> 
115    115                              <1> ;
116    116                              <1> ; Macro to emit an unsigned decimal number as a string
117    117                              <1> ;
118    118                              <1> %macro asciidec 1.nolist
119    119                              <1>   %ifndef DEPEND        ; Not safe for "depend"
120    120                              <1>     %push asciidec
121    121                              <1>       %assign %$v %1
122    122                              <1>       %if %$v == 0
123    123                              <1>         db '0'
124    124                              <1>       %else
125    125                              <1>         %assign %$dcount 0
126    126                              <1>         %assign %$n %$v
127    127                              <1>         %assign %$d 1
128    128                              <1>         %rep 20
129    129                              <1>           %if %$n != 0
130    130                              <1>             %assign %$dcount %$dcount + 1
131    131                              <1>             %assign %$n %$n / 10
132    132                              <1>             %assign %$d %$d * 10
133    133                              <1>           %endif
134    134                              <1>         %endrep
135    135                              <1>         %rep %$dcount
136    136                              <1>           %assign %$d %$d / 10
137    137                              <1>           db ((%$v / %$d) % 10) + '0'
138    138                              <1>         %endrep
139    139                              <1>       %endif
140    140                              <1>     %pop
141    141                              <1>   %endif
142    142                              <1> %endmacro
143    143                              <1> 
144    144                              <1> ;
145    145                              <1> ; Macros for network byte order of constants
146    146                              <1> ;
147    147                              <1> %define htons(x)  ( ( ((x) & 0FFh) << 8 ) + ( ((x) & 0FF00h) >> 8 ) )
148    148                              <1> %define ntohs(x) htons(x)
149    149                              <1> %define htonl(x)  ( ( ((x) & 0FFh) << 24) + ( ((x) & 0FF00h) << 8 ) + ( ((x) & 0FF0000h) >> 8 ) + ( ((x) & 0FF000000h) >> 24) )
150    150                              <1> %define ntohl(x) htonl(x)
151    151                              <1> 
152    152                              <1> ;
153    153                              <1> ; ASCII
154    154                              <1> ;
155    155                              <1> CR              equ 13          ; Carriage Return
156    156                              <1> LF              equ 10          ; Line Feed
157    157                              <1> FF              equ 12          ; Form Feed
158    158                              <1> BS              equ  8          ; Backspace
159    159                              <1> 
160    160                              <1> %endif ; _MACROS_INC
161    161                                  ; %include "layout.inc"
162    162                                  
163    163                                  m_CHS0          equ 00534843h           ;'CHS',0
164    164                                  m_EDD0          equ 00444445h           ;'EDD',0
165    165                                  m_EDD_SP        equ 20444445h           ;'EDD '
166    166                                  retry_count     equ 16
167    167                                  dbuf            equ 8000h
168    168                                  ; int13_ret     equ 7e00h
169    169                                  LDLINUX_MAGIC   equ 0x3eb202fe          ; A random number to identify ourselves with
170    170                                  
171    171                                  Sect1Ptr0_VAL   equ 1
172    172                                  Sect1Ptr1_VAL   equ 0
173    173                                  
174    174                                  ;               global STACK_LEN, STACK_TOP, STACK_BASE
175    175                                  ; STACK_LEN     equ 4096
176    176                                  STACK_TOP       equ 7c00h
177    177                                  ; STACK_BASE    equ STACK_TOP - STACK_LEN
178    178                                                  section .init
179    179                                                  org STACK_TOP
180    180                                  geodsp_start:
181    181                                  
182    182                                  %include "diskboot.inc"
183    183                              <1> ; -----------------------------------------------------------------------
184    184                              <1> ;
185    185                              <1> ;   Copyright 1994-2009 H. Peter Anvin - All Rights Reserved
186    186                              <1> ;   Copyright 2009-2011 Intel Corporation; author: H. Peter Anvin
187    187                              <1> ;
188    188                              <1> ;   This program is free software; you can redistribute it and/or modify
189    189                              <1> ;   it under the terms of the GNU General Public License as published by
190    190                              <1> ;   the Free Software Foundation, Inc., 51 Franklin St, Fifth Floor,
191    191                              <1> ;   Boston MA 02110-1301, USA; either version 2 of the License, or
192    192                              <1> ;   (at your option) any later version; incorporated herein by reference.
193    193                              <1> ;
194    194                              <1> ; -----------------------------------------------------------------------
195    195                              <1> 
196    196                              <1> ;
197    197                              <1> ; diskboot.inc
198    198                              <1> ;
199    199                              <1> ; Common boot sector code for harddisk-based Syslinux derivatives.
200    200                              <1> ;
201    201                              <1> ; Requires macros z[bwd], labels ldlinux_ent, ldlinux_magic, ldlinux_sys
202    202                              <1> ; and constants BS_MAGIC_VER, LDLINUX_MAGIC, retry_count, Sect1Ptr[01]_VAL,
203    203                              <1> ; STACK_TOP
204    204                              <1> ;
205    205                              <1> 
206    206                              <1>                 section .init
207    207                              <1> ;
208    208                              <1> ; Some of the things that have to be saved very early are saved
209    209                              <1> ; "close" to the initial stack pointer offset, in order to
210    210                              <1> ; reduce the code size...
211    211                              <1> ;
212    212                              <1> 
213    213                              <1> StackBuf        equ STACK_TOP-44-92     ; Start the stack here (grow down - 4K)
214    214                              <1> PartInfo        equ StackBuf
215    215                              <1> .mbr            equ PartInfo
216    216                              <1> .gptlen         equ PartInfo+16
217    217                              <1> .gpt            equ PartInfo+20
218    218                              <1> FloppyTable     equ PartInfo+76
219    219                              <1> ; Total size of PartInfo + FloppyTable == 76+16 = 92 bytes
220    220                              <1> Hidden          equ StackBuf-24         ; Partition offset (qword)
221    221                              <1> OrigFDCTabPtr   equ StackBuf-16         ; Original FDC table
222    222                              <1> OrigDSSI        equ StackBuf-12         ; DS:SI -> partinfo
223    223                              <1> OrigESDI        equ StackBuf-8          ; ES:DI -> $PnP structure
224    224                              <1> DriveNumber     equ StackBuf-4          ; Drive number
225    225                              <1> StackHome       equ Hidden              ; The start of the canonical stack
226    226                              <1> 
227    227                              <1> ;
228    228                              <1> ; Primary entry point.  Tempting as though it may be, we can't put the
229    229                              <1> ; initial "cli" here; the jmp opcode in the first byte is part of the
230    230                              <1> ; "magic number" (using the term very loosely) for the DOS superblock.
231    231                              <1> ;
232    232                              <1> bootsec         equ $
233    233 00000000 EB58                <1> _start:         jmp short start         ; 2 bytes
234    234 00000002 90                  <1>                 nop                     ; 1 byte
235    235                              <1> ;
236    236                              <1> ; "Superblock" follows -- it's in the boot sector, so it's already
237    237                              <1> ; loaded and ready for us
238    238                              <1> ;
239    239 00000003 5359534C494E5558    <1> bsOemName       db MY_NAME              ; The SYS command sets this, so...
240    240                              <1>                 zb 8-($-bsOemName)
241    241                              <1> 
242    242                              <1> ;
243    243                              <1> ; These are the fields we actually care about.  We end up expanding them
244    244                              <1> ; all to dword size early in the code, so generate labels for both
245    245                              <1> ; the expanded and unexpanded versions.
246    246                              <1> ;
247    247                              <1> %macro          superb 1
248    248                              <1> bx %+ %1        equ SuperInfo+($-superblock)*8+4
249    249                              <1> bs %+ %1        equ $
250    250                              <1>                 zb 1
251    251                              <1> %endmacro
252    252                              <1> %macro          superw 1
253    253                              <1> bx %+ %1        equ SuperInfo+($-superblock)*8
254    254                              <1> bs %+ %1        equ $
255    255                              <1>                 zw 1
256    256                              <1> %endmacro
257    257                              <1> %macro          superd 1
258    258                              <1> bx %+ %1        equ $                   ; no expansion for dwords
259    259                              <1> bs %+ %1        equ $
260    260                              <1>                 zd 1
261    261                              <1> %endmacro
262    262                              <1> superblock      equ $
263    263                              <1>                 superw BytesPerSec
264    264                              <2> bx %+ %1 equ SuperInfo+($-superblock)*8
265    265                              <2> bs %+ %1 equ $
266    266 0000000B 0000                <2>  zw 1
267    267                              <1>                 superb SecPerClust
268    268                              <2> bx %+ %1 equ SuperInfo+($-superblock)*8+4
269    269                              <2> bs %+ %1 equ $
270    270 0000000D 00                  <2>  zb 1
271    271                              <1>                 superw ResSectors
272    272                              <2> bx %+ %1 equ SuperInfo+($-superblock)*8
273    273                              <2> bs %+ %1 equ $
274    274 0000000E 0000                <2>  zw 1
275    275                              <1>                 superb FATs
276    276                              <2> bx %+ %1 equ SuperInfo+($-superblock)*8+4
277    277                              <2> bs %+ %1 equ $
278    278 00000010 00                  <2>  zb 1
279    279                              <1>                 superw RootDirEnts
280    280                              <2> bx %+ %1 equ SuperInfo+($-superblock)*8
281    281                              <2> bs %+ %1 equ $
282    282 00000011 0000                <2>  zw 1
283    283                              <1>                 superw Sectors
284    284                              <2> bx %+ %1 equ SuperInfo+($-superblock)*8
285    285                              <2> bs %+ %1 equ $
286    286 00000013 0000                <2>  zw 1
287    287                              <1>                 superb Media
288    288                              <2> bx %+ %1 equ SuperInfo+($-superblock)*8+4
289    289                              <2> bs %+ %1 equ $
290    290 00000015 00                  <2>  zb 1
291    291                              <1>                 superw FATsecs
292    292                              <2> bx %+ %1 equ SuperInfo+($-superblock)*8
293    293                              <2> bs %+ %1 equ $
294    294 00000016 0000                <2>  zw 1
295    295                              <1>                 superw SecPerTrack
296    296                              <2> bx %+ %1 equ SuperInfo+($-superblock)*8
297    297                              <2> bs %+ %1 equ $
298    298 00000018 0000                <2>  zw 1
299    299                              <1>                 superw Heads
300    300                              <2> bx %+ %1 equ SuperInfo+($-superblock)*8
301    301                              <2> bs %+ %1 equ $
302    302 0000001A 0000                <2>  zw 1
303    303                              <1> superinfo_size  equ ($-superblock)-1    ; How much to expand
304    304                              <1>                 superd Hidden
305    305                              <2> bx %+ %1 equ $
306    306                              <2> bs %+ %1 equ $
307    307 0000001C 00000000            <2>  zd 1
308    308                              <1>                 superd HugeSectors
309    309                              <2> bx %+ %1 equ $
310    310                              <2> bs %+ %1 equ $
311    311 00000020 00000000            <2>  zd 1
312    312                              <1>                 ;
313    313                              <1>                 ; This is as far as FAT12/16 and FAT32 are consistent
314    314                              <1>                 ;
315    315                              <1>                 ; FAT12/16 need 26 more bytes,
316    316                              <1>                 ; FAT32 need 54 more bytes
317    317                              <1>                 ;
318    318                              <1> superblock_len_fat16    equ $-superblock+26
319    319                              <1> superblock_len_fat32    equ $-superblock+54
320    320 00000024 00<rept>            <1>                 zb 54                   ; Maximum needed size
321    321                              <1> superblock_max  equ $-superblock
322    322                              <1> 
323    323                              <1>                 global SecPerClust
324    324                              <1> SecPerClust     equ bxSecPerClust
325    325                              <1> 
326    326                              <1> ;
327    327                              <1> ; Note we don't check the constraints above now; we did that at install
328    328                              <1> ; time (we hope!)
329    329                              <1> ;
330    330                              <1> start:
331    331 0000005A FA                  <1>                 cli                     ; No interrupts yet, please
332    332 0000005B FC                  <1>                 cld                     ; Copy upwards
333    333                              <1> ;
334    334                              <1> ; Set up the stack
335    335                              <1> ;
336    336 0000005C 31C9                <1>                 xor cx,cx
337    337 0000005E 8ED1                <1>                 mov ss,cx
338    338 00000060 BC767B              <1>                 mov sp,StackBuf-2       ; Just below BSS (-2 for alignment)
339    339 00000063 52                  <1>                 push dx                 ; Save drive number (in DL)
340    340 00000064 06                  <1>                 push es                 ; Save initial ES:DI -> $PnP pointer
341    341 00000065 57                  <1>                 push di
342    342 00000066 1E                  <1>                 push ds                 ; Save original DS:SI -> partinfo
343    343 00000067 56                  <1>                 push si
344    344 00000068 8EC1                <1>                 mov es,cx
345    345                              <1> 
346    346                              <1> ;
347    347                              <1> ; DS:SI may contain a partition table entry and possibly a GPT entry.
348    348                              <1> ; Preserve it for us.  This saves 56 bytes of the GPT entry, which is
349    349                              <1> ; currently the maximum we care about.  Total is 76 bytes.
350    350                              <1> ;
351    351 0000006A B126                <1>                 mov cl,(16+4+56)/2      ; Save partition info
352    352 0000006C BF787B              <1>                 mov di,PartInfo
353    353 0000006F F3A5                <1>                 rep movsw               ; This puts CX back to zero
354    354                              <1> 
355    355 00000071 8ED9                <1>                 mov ds,cx               ; Now we can initialize DS...
356    356                              <1> 
357    357                              <1> ;
358    358                              <1> ; Now sautee the BIOS floppy info block to that it will support decent-
359    359                              <1> ; size transfers; the floppy block is 11 bytes and is stored in the
360    360                              <1> ; INT 1Eh vector (brilliant waste of resources, eh?)
361    361                              <1> ;
362    362                              <1> ; Of course, if BIOSes had been properly programmed, we wouldn't have
363    363                              <1> ; had to waste precious space with this code.
364    364                              <1> ;
365    365 00000073 BB7800              <1>                 mov bx,fdctab
366    366 00000076 0FB437              <1>                 lfs si,[bx]             ; FS:SI -> original fdctab
367    367 00000079 0FA0                <1>                 push fs                 ; Save on stack in case we need to bail
368    368 0000007B 56                  <1>                 push si
369    369                              <1> 
370    370                              <1>                 ; Save the old fdctab even if hard disk so the stack layout
371    371                              <1>                 ; is the same.  The instructions above do not change the flags
372    372 0000007C 20D2                <1>                 and dl,dl               ; If floppy disk (00-7F), assume no
373    373                              <1>                                         ; partition table
374    374 0000007E 781B                <1>                 js harddisk
375    375                              <1> 
376    376                              <1> floppy:
377    377 00000080 31C0                <1>                 xor ax,ax
378    378 00000082 B106                <1>                 mov cl,6                ; 12 bytes (CX == 0)
379    379                              <1>                 ; es:di -> FloppyTable already
380    380                              <1>                 ; This should be safe to do now, interrupts are off...
381    381 00000084 893F                <1>                 mov [bx],di             ; FloppyTable
382    382 00000086 894702              <1>                 mov [bx+2],ax           ; Segment 0
383    383 00000089 F364A5              <1>                 fs rep movsw            ; Faster to move words
384    384 0000008C 8A0E[1800]          <1>                 mov cl,[bsSecPerTrack]  ; Patch the sector count
385    385 00000090 884DF8              <1>                 mov [di-12+4],cl
386    386                              <1> 
387    387 00000093 50                  <1>                 push ax                 ; Partition offset == 0
388    388 00000094 50                  <1>                 push ax
389    389 00000095 50                  <1>                 push ax
390    390 00000096 50                  <1>                 push ax
391    391                              <1> 
392    392 00000097 CD13                <1>                 int 13h                 ; Some BIOSes need this
393    393                              <1>                         ; Using xint13 costs +1B
394    394 00000099 EB62                <1>                 jmp short not_harddisk
395    395                              <1> ;
396    396                              <1> ; The drive number and possibly partition information was passed to us
397    397                              <1> ; by the BIOS or previous boot loader (MBR).  Current "best practice" is to
398    398                              <1> ; trust that rather than what the superblock contains.
399    399                              <1> ;
400    400                              <1> ; Note: di points to beyond the end of PartInfo
401    401                              <1> ; Note: false negatives might slip through the handover area's sanity checks,
402    402                              <1> ;       if the region is very close (less than a paragraph) to
403    403                              <1> ;       PartInfo ; no false positives are possible though
404    404                              <1> ;
405    405                              <1> harddisk:
406    406 0000009B 8B55AA              <1>                 mov dx,[di-76-10]       ; Original DS
407    407 0000009E 8B75A8              <1>                 mov si,[di-76-12]       ; Original SI
408    408 000000A1 C1EE04              <1>                 shr si,4
409    409 000000A4 01F2                <1>                 add dx,si
410    410 000000A6 83FA4F              <1>                 cmp dx,4fh              ; DS:SI < 50h:0 (BDA or IVT) ?
411    411 000000A9 7631                <1>                 jbe .no_partition
412    412 000000AB 81FAB207            <1>                 cmp dx,(PartInfo-75)>>4 ; DS:SI in overwritten memory?
413    413 000000AF 732B                <1>                 jae .no_partition
414    414 000000B1 F645B47F            <1>                 test byte [di-76],7Fh   ; Sanity check: "active flag" should
415    415 000000B5 7525                <1>                 jnz .no_partition       ; be 00 or 80
416    416 000000B7 384DB8              <1>                 cmp [di-76+4],cl        ; Sanity check: partition type != 0
417    417 000000BA 7420                <1>                 je .no_partition
418    418 000000BC 663D21475054        <1>                 cmp eax,'!GPT'          ; !GPT signature?
419    419 000000C2 7510                <1>                 jne .mbr
420    420 000000C4 807DB8ED            <1>                 cmp byte [di-76+4],0EDh ; Synthetic GPT partition entry?
421    421 000000C8 750A                <1>                 jne .mbr
422    422                              <1> .gpt:                                   ; GPT-style partition info
423    423 000000CA 66FF75EC            <1>                 push dword [di-76+20+36]
424    424 000000CE 66FF75E8            <1>                 push dword [di-76+20+32]
425    425 000000D2 EB0F                <1>                 jmp .gotoffs
426    426                              <1> .mbr:                                   ; MBR-style partition info
427    427 000000D4 51                  <1>                 push cx                 ; Upper half partition offset == 0
428    428 000000D5 51                  <1>                 push cx
429    429 000000D6 66FF75BC            <1>                 push dword [di-76+8]    ; Partition offset (dword)
430    430 000000DA EB07                <1>                 jmp .gotoffs
431    431                              <1> .no_partition:
432    432                              <1> ;
433    433                              <1> ; No partition table given... assume that the Hidden field in the boot sector
434    434                              <1> ; tells the truth (in particular, is zero if this is an unpartitioned disk.)
435    435                              <1> ;
436    436 000000DC 51                  <1>                 push cx
437    437 000000DD 51                  <1>                 push cx
438    438 000000DE 66FF36[1C00]        <1>                 push dword [bsHidden]
439    439                              <1> .gotoffs:
440    440                              <1> ;
441    441                              <1> ; Get disk drive parameters (don't trust the superblock.)  Don't do this for
442    442                              <1> ; floppy drives -- INT 13:08 on floppy drives will (may?) return info about
443    443                              <1> ; what the *drive* supports, not about the *media*.  Fortunately floppy disks
444    444                              <1> ; tend to have a fixed, well-defined geometry which is stored in the superblock.
445    445                              <1> ;
446    446                              <1>                 ; DL == drive # still
447    447 000000E3 B408                <1>                 mov ah,08h
448    448 000000E5 E8E900              <1>                 call xint13
449    449 000000E8 7213                <1>                 jc no_driveparm
450    450 000000EA 20E4                <1>                 and ah,ah
451    451 000000EC 750F                <1>                 jnz no_driveparm
452    452 000000EE C1EA08              <1>                 shr dx,8
453    453 000000F1 42                  <1>                 inc dx                  ; Contains # of heads - 1
454    454 000000F2 8916[1A00]          <1>                 mov [bsHeads],dx
455    455 000000F6 83E13F              <1>                 and cx,3fh
456    456 000000F9 890E[1800]          <1>                 mov [bsSecPerTrack],cx
457    457                              <1> no_driveparm:
458    458                              <1> not_harddisk:
459    459                              <1> ;
460    460                              <1> ; Ready to enable interrupts, captain
461    461                              <1> ;
462    462 000000FD FB                  <1>                 sti
463    463                              <1> 
464    464                              <1> ;
465    465                              <1> ; Do we have EBIOS (EDD)?
466    466                              <1> ;
467    467                              <1> eddcheck:
468    468 000000FE BBAA55              <1>                 mov bx,55AAh
469    469 00000101 B441                <1>                 mov ah,41h              ; EDD existence query
470    470 00000103 E8CB00              <1>                 call xint13
471    471 00000106 7210                <1>                 jc .noedd
472    472 00000108 81FB55AA            <1>                 cmp bx,0AA55h
473    473 0000010C 750A                <1>                 jne .noedd
474    474 0000010E F6C101              <1>                 test cl,1               ; Extended disk access functionality set
475    475 00000111 7405                <1>                 jz .noedd
476    476                              <1>                 ;
477    477                              <1>                 ; We have EDD support...
478    478                              <1>                 ;
479    479 00000113 C606[4601]00        <1>                 mov byte [getonesec.jmp+1],(getonesec_ebios-(getonesec.jmp+2))
480    480                              <1> .noedd:
481    481                              <1> 
482    482                              <1> ;
483    483                              <1> ; Load the first sector of LDLINUX.SYS; this used to be all proper
484    484                              <1> ; with parsing the superblock and root directory; it doesn't fit
485    485                              <1> ; together with EBIOS support, unfortunately.
486    486                              <1> ;
487    487                              <1> Sect1Load:
488    488 00000118 66B801000000        <1>                 mov eax,strict dword Sect1Ptr0_VAL      ; 0xdeadbeef
489    489                              <1> Sect1Ptr0       equ $-4
490    490 0000011E 66BA00000000        <1>                 mov edx,strict dword Sect1Ptr1_VAL      ; 0xfeedface
491    491                              <1> Sect1Ptr1       equ $-4
492    492 00000124 BB[0002]            <1>                 mov bx,ldlinux_sys      ; Where to load it
493    493 00000127 E80E00              <1>                 call getonesec
494    494                              <1> 
495    495                              <1>                 ; Some modicum of integrity checking
496    496 0000012A 66813E[0402]FF02B2- <1>                 cmp dword [ldlinux_magic+4],LDLINUX_MAGIC^HEXDATE
497    497 00000132 3E                  <1>
498    498 00000133 7574                <1>                 jne kaboom
499    499                              <1> 
500    500                              <1>                 ; Go for it!  This also normalizes CS:IP.
501    501 00000135 E9D000              <1>                 jmp ldlinux_ent
502    502                              <1> 
503    503                              <1> ;
504    504                              <1> ; getonesec: load a single disk linear sector EDX:EAX into the buffer
505    505                              <1> ;            at ES:BX.
506    506                              <1> ;
507    507                              <1> ;            This routine assumes CS == DS == SS, and trashes most registers.
508    508                              <1> ;
509    509                              <1> ; Stylistic note: use "xchg" instead of "mov" when the source is a register
510    510                              <1> ; that is dead from that point; this saves space.  However, please keep
511    511                              <1> ; the order to dst,src to keep things sane.
512    512                              <1> ;
513    513                              <1> getonesec:
514    514 00000138 660306607B          <1>                 add eax,[Hidden]                ; Add partition offset
515    515 0000013D 661316647B          <1>                 adc edx,[Hidden+4]
516    516 00000142 B91000              <1>                 mov cx,retry_count
517    517 00000145 EB2B                <1> .jmp:           jmp strict short getonesec_cbios
518    518                              <1> 
519    519                              <1> ;
520    520                              <1> ; getonesec_ebios:
521    521                              <1> ;
522    522                              <1> ; getonesec implementation for EBIOS (EDD)
523    523                              <1> ;
524    524                              <1> getonesec_ebios:
525    525                              <1> .retry:
526    526                              <1>                 ; Form DAPA on stack
527    527 00000147 6652                <1>                 push edx
528    528 00000149 6650                <1>                 push eax
529    529 0000014B 06                  <1>                 push es
530    530 0000014C 53                  <1>                 push bx
531    531 0000014D 6A01                <1>                 push word 1
532    532 0000014F 6A10                <1>                 push word 16
533    533 00000151 89E6                <1>                 mov si,sp
534    534 00000153 6660                <1>                 pushad
535    535 00000155 B442                <1>                 mov ah,42h                      ; Extended Read
536    536 00000157 E87700              <1>                 call xint13
537    537 0000015A 6661                <1>                 popad
538    538 0000015C 8D6410              <1>                 lea sp,[si+16]                  ; Remove DAPA
539    539 0000015F 7201                <1>                 jc .error
540    540 00000161 C3                  <1>                 ret
541    541                              <1> 
542    542                              <1> .error:
543    543                              <1>                 ; Some systems seem to get "stuck" in an error state when
544    544                              <1>                 ; using EBIOS.  Doesn't happen when using CBIOS, which is
545    545                              <1>                 ; good, since some other systems get timeout failures
546    546                              <1>                 ; waiting for the floppy disk to spin up.
547    547                              <1> 
548    548 00000162 6660                <1>                 pushad                          ; Try resetting the device
549    549 00000164 31C0                <1>                 xor ax,ax
550    550 00000166 E86800              <1>                 call xint13
551    551 00000169 6661                <1>                 popad
552    552 0000016B E2DA                <1>                 loop .retry                     ; CX-- and jump if not zero
553    553                              <1> 
554    554                              <1>                 ; Total failure.  Try falling back to CBIOS.
555    555 0000016D C606[4601]2B        <1>                 mov byte [getonesec.jmp+1],(getonesec_cbios-(getonesec.jmp+2))
556    556                              <1> 
557    557                              <1> ;
558    558                              <1> ; getonesec_cbios:
559    559                              <1> ;
560    560                              <1> ; getlinsec implementation for legacy CBIOS
561    561                              <1> ;
562    562                              <1> getonesec_cbios:
563    563                              <1> .retry:
564    564 00000172 6660                <1>                 pushad
565    565                              <1> 
566    566 00000174 660FB736[1800]      <1>                 movzx esi,word [bsSecPerTrack]
567    567 0000017A 660FB73E[1A00]      <1>                 movzx edi,word [bsHeads]
568    568                              <1>                 ;
569    569                              <1>                 ; Dividing by sectors to get (track,sector): we may have
570    570                              <1>                 ; up to 2^18 tracks, so we need to use 32-bit arithmetric.
571    571                              <1>                 ;
572    572 00000180 66F7F6              <1>                 div esi
573    573 00000183 31C9                <1>                 xor cx,cx
574    574 00000185 87CA                <1>                 xchg cx,dx              ; CX <- sector index (0-based)
575    575                              <1>                                         ; EDX <- 0
576    576                              <1>                 ; eax = track #
577    577 00000187 66F7F7              <1>                 div edi                 ; Convert track to head/cyl
578    578                              <1> 
579    579 0000018A 663DFF030000        <1>                 cmp eax,1023            ; Outside the CHS range?
580    580 00000190 7717                <1>                 ja kaboom
581    581                              <1> 
582    582                              <1>                 ;
583    583                              <1>                 ; Now we have AX = cyl, DX = head, CX = sector (0-based),
584    584                              <1>                 ; SI = bsSecPerTrack, ES:BX = data target
585    585                              <1>                 ;
586    586 00000192 C0E406              <1>                 shl ah,6                ; Because IBM was STOOPID
587    587                              <1>                                         ; and thought 8 bits were enough
588    588                              <1>                                         ; then thought 10 bits were enough...
589    589 00000195 41                  <1>                 inc cx                  ; Sector numbers are 1-based, sigh
590    590 00000196 08E1                <1>                 or cl,ah
591    591 00000198 88C5                <1>                 mov ch,al
592    592 0000019A 88D6                <1>                 mov dh,dl
593    593 0000019C B80102              <1>                 mov ax,0201h            ; Read one sector
594    594 0000019F E82F00              <1>                 call xint13
595    595 000001A2 6661                <1>                 popad
596    596 000001A4 7201                <1>                 jc .error
597    597 000001A6 C3                  <1>                 ret
598    598                              <1> 
599    599                              <1> .error:
600    600 000001A7 E2C9                <1>                 loop .retry
601    601                              <1>                 ; Fall through to disk_error
602    602                              <1> 
603    603                              <1> ;
604    604                              <1> ; kaboom: write a message and bail out.
605    605                              <1> ;
606    606                              <1>                 global kaboom
607    607                              <1> disk_error:
608    608                              <1> kaboom:
609    609 000001A9 31F6                <1>                 xor si,si
610    610 000001AB 8ED6                <1>                 mov ss,si
611    611 000001AD BC687B              <1>                 mov sp,OrigFDCTabPtr    ; Reset stack
612    612 000001B0 8EDE                <1>                 mov ds,si               ; Reset data segment
613    613 000001B2 668F067800          <1>                 pop dword [fdctab]      ; Restore FDC table
614    614                              <1> .patch:                                 ; When we have full code, intercept here
615    615 000001B7 BE[DA01]            <1>                 mov si,bailmsg
616    616 000001BA AC                  <1> .loop:          lodsb
617    617 000001BB 20C0                <1>                 and al,al
618    618 000001BD 7409                <1>                 jz .done
619    619 000001BF B40E                <1>                 mov ah,0Eh              ; Write to screen as TTY
620    620 000001C1 BB0700              <1>                 mov bx,0007h            ; Attribute
621    621 000001C4 CD10                <1>                 int 10h
622    622 000001C6 EBF2                <1>                 jmp short .loop
623    623                              <1> 
624    624                              <1> .done:
625    625 000001C8 31C0                <1>                 xor ax,ax
626    626 000001CA CD16                <1> .again:         int 16h                 ; Wait for keypress
627    627                              <1>                                         ; NB: replaced by int 18h if
628    628                              <1>                                         ; chosen at install time..
629    629 000001CC CD19                <1>                 int 19h                 ; And try once more to boot...
630    630 000001CE F4                  <1> .norge:         hlt                     ; If int 19h returned; this is the end
631    631 000001CF EBFD                <1>                 jmp short .norge
632    632                              <1> 
633    633                              <1> ;
634    634                              <1> ; INT 13h wrapper function
635    635                              <1> ;
636    636                              <1> xint13:
637    637 000001D1 8A16747B            <1>                 mov dl,[DriveNumber]
638    638 000001D5 06                  <1>                 push es         ; ES destroyed by INT 13h AH 08h
639    639 000001D6 CD13                <1>                 int 13h
640    640 000001D8 07                  <1>                 pop es
641    641 000001D9 C3                  <1>                 ret
642    642                              <1> 
643    643                              <1> ;
644    644                              <1> ; Error message on failure
645    645                              <1> ;
646    646 000001DA 426F6F74206572726F- <1> bailmsg:        db 'Boot error', 0Dh, 0Ah, 0
647    647 000001E3 720D0A00            <1>
648    648                              <1> 
649    649                              <1>                 ; This fails if the boot sector overflowsg
650    650 000001E7 00<rept>            <1>                 zb 1F8h-($-$$)
651    651                              <1> 
652    652 000001F8 FE02B23E            <1> bs_magic        dd LDLINUX_MAGIC
653    653 000001FC 1837                <1> bs_link         dw (Sect1Load - bootsec) | BS_MAGIC_VER
654    654 000001FE 55AA                <1> bootsignature   dw 0xAA55
655    655                              <1> 
656    656                              <1> ;
657    657                              <1> ; ===========================================================================
658    658                              <1> ;  End of boot sector
659    659                              <1> ; ===========================================================================
660    660                                  
661    661                                  HEXDATE         equ 1
662    662                                  
663    663                                                  section .init
664    664                                  sector_1:
665    665                                  ldlinux_sys:
666    666                                                  alignz 8
667    667 00000200 FE02B23E                ldlinux_magic   dd LDLINUX_MAGIC
668    668 00000204 FF02B23E                                dd LDLINUX_MAGIC^HEXDATE
669    669                                  
670    670                                  
671    671                                  ldlinux_ent:
672    672                                  
673    673                                  get_geo:                ; DL and ES ready
674    674 00000208 B408                                    mov ah,08h
675    675 0000020A BF0000                                  mov di,0
676    676 0000020D E8C1FF                                  call xint13
677    677                                  write_geo:
678    678 00000210 720E                                    jc .bad_geo
679    679 00000212 BE[4F03]                                mov si,s_chs
680    680 00000215 E84A01                                  call writestr_early
681    681 00000218 E89D00                                  call write_chs
682    682 0000021B E8DC00                                  call crlf
683    683 0000021E EB00                                    jmp short .done
684    684                                  .bad_geo:
685    685                                  .done:
686    686                                  
687    687 00000220 BB0080                                  mov bx,dbuf
688    688                                  get_h1c:                ; 0,1,1
689    689 00000223 B90100                                  mov cx,0001h
690    690 00000226 B601                                    mov dh,01h
691    691 00000228 E86000                                  call getonesec_chs
692    692 0000022B E86D00                                  call write_chs_lba
693    693                                  get_c1c:                ; 1,0,1
694    694 0000022E B90101                                  mov cx,0101h
695    695 00000231 B600                                    mov dh,00h
696    696 00000233 E85500                                  call getonesec_chs
697    697 00000236 E86200                                  call write_chs_lba
698    698                                  
699    699                                  
700    700                                  
701    701                                  ; Do we have EBIOS (EDD)?
702    702                                  ;
703    703                                  edd:
704    704                                  .check:
705    705 00000239 BBAA55                                  mov bx,55AAh
706    706 0000023C B441                                    mov ah,41h              ; EDD existence query
707    707 0000023E E890FF                                  call xint13
708    708 00000241 723F                                    jc .noedd
709    709 00000243 81FB55AA                                cmp bx,0AA55h
710    710 00000247 7539                                    jne .noedd
711    711 00000249 F6C101                                  test cl,1               ; Extended disk access functionality set
712    712 0000024C 7434                                    jz .noedd
713    713                                                  ;
714    714                                                  ; We have EDD support...
715    715                                                  ;
716    716 0000024E BB0080                                  mov bx,dbuf     ; ES should still be safe.
717    717 00000251 6631D2                                  xor edx,edx
718    718 00000254 66C706[4F03]454444-                     mov dword [s_chs],m_EDD_SP
719    719 0000025C 20                 
720    720                                  .get_lba63:
721    721 0000025D 66B83F000000                            mov eax,63      ; Same length as mov al,64; movzx eax,al
722    722 00000263 E8E1FE                                  call getonesec_ebios
723    723 00000266 721A                                    jc .bad_edd     ;read error
724    724 00000268 E87200                                  call write_edd_lba
725    725                                  .get_lba16065:
726    726 0000026B 66B8C13E0000                            mov eax,16065
727    727 00000271 E8D3FE                                  call getonesec_ebios
728    728 00000274 720C                                    jc .bad_edd     ;read error
729    729 00000276 E86400                                  call write_edd_lba
730    730                                  .good_edd:
731    731 00000279 66C706[5603]454444-                     mov dword [s_type],m_EDD0
732    732 00000281 00                 
733    733                                  .bad_edd:
734    734                                  .noedd:
735    735                                  .end:
736    736                                  
737    737                                  write_final_type:
738    738 00000282 BE[5403]                                mov si,s_typespec
739    739 00000285 E8DA00                                  call writestr_early
740    740 00000288 E91EFF                                  jmp kaboom
741    741                                  
742    742                                  ;
743    743                                  ; getonesec_chs:
744    744                                  ;
745    745                                  ; CX,DH specifies CHS address
746    746                                  ;
747    747                                  getonesec_chs:  ; We could use an xchg and get a loop
748    748                                  ;               mov cx,retry_count
749    749                                  .retry:
750    750 0000028B 6660                                    pushad
751    751 0000028D B80102                                  mov ax,0201h            ; Read one sector
752    752 00000290 E83EFF                                  call xint13
753    753 00000293 6661                                    popad
754    754 00000295 7201                                    jc .error
755    755 00000297 C3                                      ret
756    756                                  
757    757                                  .error:
758    758                                  ;               loop .retry
759    759                                                  ; Fall through to disk_error
760    760 00000298 E90EFF                                  jmp disk_error
761    761                                  
762    762                                  %include "geodsplib.inc"
763    763                              <1> ; -----------------------------------------------------------------------
764    764                              <1> ;
765    765                              <1> ;   Copyright 2010 Gene Cumm
766    766                              <1> ;
767    767                              <1> ;   Portions from diskstart.inc:
768    768                              <1> ;   Copyright 1994-2009 H. Peter Anvin - All Rights Reserved
769    769                              <1> ;   Copyright 2009-2010 Intel Corporation; author: H. Peter Anvin
770    770                              <1> ;
771    771                              <1> ;   This program is free software; you can redistribute it and/or modify
772    772                              <1> ;   it under the terms of the GNU General Public License as published by
773    773                              <1> ;   the Free Software Foundation, Inc., 51 Franklin St, Fifth Floor,
774    774                              <1> ;   Boston MA 02110-1301, USA; either version 2 of the License, or
775    775                              <1> ;   (at your option) any later version; incorporated herein by reference.
776    776                              <1> ;
777    777                              <1> ; -----------------------------------------------------------------------
778    778                              <1> 
779    779                              <1> ;
780    780                              <1> ; geodsplib.inc
781    781                              <1> ;
782    782                              <1> ; Library file for geodsp*.asm
783    783                              <1> ;
784    784                              <1> 
785    785                              <1>                 ; ES:BX points to the buffer with address
786    786                              <1>                 ; DX,CX as they should be for INT13h,AH=02
787    787                              <1>                 ; For now assume C<256
788    788                              <1> write_chs_lba:
789    789 0000029B 6660                <1>                 pushad
790    790 0000029D BE[4E03]            <1>                 mov si,s_atchs
791    791 000002A0 E8BF00              <1>                 call writestr_early
792    792 000002A3 E81200              <1>                 call write_chs
793    793 000002A6 B03A                <1>                 mov al,':'
794    794 000002A8 E85800              <1>                 call writechr
795    795 000002AB 26668B07            <1>                 mov eax,[es:bx]
796    796 000002AF E87700              <1>                 call writehex8
797    797 000002B2 E84500              <1>                 call crlf
798    798 000002B5 6661                <1>                 popad
799    799 000002B7 C3                  <1>                 ret
800    800                              <1> 
801    801                              <1>                 ; DX,CX as they should be for INT13h,AH=02
802    802                              <1>                 ; For now assume C<256
803    803                              <1> write_chs:
804    804 000002B8 6660                <1>                 pushad
805    805 000002BA 88E8                <1>                 mov al,ch
806    806 000002BC 88CC                <1>                 mov ah,cl
807    807 000002BE C0EC06              <1>                 shr ah,6
808    808 000002C1 E85800              <1>                 call writehex4
809    809 000002C4 B02C                <1>                 mov al,','
810    810 000002C6 E83A00              <1>                 call writechr
811    811 000002C9 88F0                <1>                 mov al,dh
812    812 000002CB E84100              <1>                 call writehex2
813    813 000002CE B02C                <1>                 mov al,','
814    814 000002D0 E83000              <1>                 call writechr
815    815 000002D3 88C8                <1>                 mov al,cl
816    816 000002D5 243F                <1>                 and al,3Fh
817    817 000002D7 E83500              <1>                 call writehex2
818    818 000002DA 6661                <1>                 popad
819    819 000002DC C3                  <1>                 ret
820    820                              <1> 
821    821                              <1> write_edd_lba:
822    822 000002DD 6660                <1>                 pushad
823    823 000002DF BE[4E03]            <1>                 mov si,s_atchs
824    824 000002E2 E87D00              <1>                 call writestr_early
825    825 000002E5 E84100              <1>                 call writehex8
826    826 000002E8 B03A                <1>                 mov al,':'
827    827 000002EA E81600              <1>                 call writechr
828    828 000002ED 26668B07            <1>                 mov eax,[es:bx]
829    829 000002F1 E83500              <1>                 call writehex8
830    830 000002F4 E80300              <1>                 call crlf
831    831 000002F7 6661                <1>                 popad
832    832 000002F9 C3                  <1>                 ret
833    833                              <1> 
834    834                              <1> 
835    835                              <1> crlf:
836    836 000002FA 56                  <1>                 push si
837    837 000002FB BE[5F03]            <1>                 mov si,s_crlf
838    838 000002FE E86100              <1>                 call writestr_early
839    839 00000301 5E                  <1>                 pop si
840    840 00000302 C3                  <1>                 ret
841    841                              <1> 
842    842                              <1> writechr:
843    843                              <1> writechr_early:
844    844 00000303 6660                <1>                 pushad
845    845 00000305 B40E                <1>                 mov ah,0Eh              ; Write to screen as TTY
846    846 00000307 BB0700              <1>                 mov bx,0007h            ; Attribute
847    847 0000030A CD10                <1>                 int 10h
848    848 0000030C 6661                <1>                 popad
849    849 0000030E C3                  <1>                 ret
850    850                              <1> 
851    851                              <1> %include "writehex.inc"
852    852                              <2> ;; -----------------------------------------------------------------------
853    853                              <2> ;;
854    854                              <2> ;;   Copyright 1994-2008 H. Peter Anvin - All Rights Reserved
855    855                              <2> ;;
856    856                              <2> ;;   This program is free software; you can redistribute it and/or modify
857    857                              <2> ;;   it under the terms of the GNU General Public License as published by
858    858                              <2> ;;   the Free Software Foundation, Inc., 53 Temple Place Ste 330,
859    859                              <2> ;;   Boston MA 02111-1307, USA; either version 2 of the License, or
860    860                              <2> ;;   (at your option) any later version; incorporated herein by reference.
861    861                              <2> ;;
862    862                              <2> ;; -----------------------------------------------------------------------
863    863                              <2> 
864    864                              <2> ;;
865    865                              <2> ;; writehex.inc
866    866                              <2> ;;
867    867                              <2> ;; Write hexadecimal numbers to the console
868    868                              <2> ;;
869    869                              <2> 
870    870                              <2> ;
871    871                              <2> ; writehex[248]: Write a hex number in (AL, AX, EAX) to the console
872    872                              <2> ;
873    873                              <2> writehex2:
874    874 0000030F 669C                <2>                 pushfd
875    875 00000311 6660                <2>                 pushad
876    876 00000313 66C1C018            <2>                 rol eax,24
877    877 00000317 B90200              <2>                 mov cx,2
878    878 0000031A EB14                <2>                 jmp short writehex_common
879    879                              <2> writehex4:
880    880 0000031C 669C                <2>                 pushfd
881    881 0000031E 6660                <2>                 pushad
882    882 00000320 66C1C010            <2>                 rol eax,16
883    883 00000324 B90400              <2>                 mov cx,4
884    884 00000327 EB07                <2>                 jmp short writehex_common
885    885                              <2> writehex8:
886    886 00000329 669C                <2>                 pushfd
887    887 0000032B 6660                <2>                 pushad
888    888 0000032D B90800              <2>                 mov cx,8
889    889                              <2> writehex_common:
890    890 00000330 66C1C004            <2> .loop:          rol eax,4
891    891 00000334 6650                <2>                 push eax
892    892 00000336 240F                <2>                 and al,0Fh
893    893 00000338 3C0A                <2>                 cmp al,10
894    894 0000033A 7304                <2>                 jae .high
895    895 0000033C 0430                <2> .low:           add al,'0'
896    896 0000033E EB02                <2>                 jmp short .ischar
897    897 00000340 0437                <2> .high:          add al,'A'-10
898    898 00000342 E8BEFF              <2> .ischar:        call writechr
899    899 00000345 6658                <2>                 pop eax
900    900 00000347 E2E7                <2>                 loop .loop
901    901 00000349 6661                <2>                 popad
902    902 0000034B 669D                <2>                 popfd
903    903 0000034D C3                  <2>                 ret
904    904                              <1> 
905    905 0000034E 40                  <1> s_atchs:        db '@'
906    906 0000034F 434853              <1> s_chs:          db 'CHS'
907    907 00000352 2000                <1> s_space:        db ' ', 0
908    908 00000354 443D                <1> s_typespec:     db 'D='
909    909 00000356 43485300            <1> s_type:         db 'CHS', 0
910    910 0000035A 0D0A656E64          <1> s_end:          db 0Dh, 0Ah, 'end'
911    911 0000035F 0D0A00              <1> s_crlf:         db 0Dh, 0Ah, 0
912    912                              <1> 
913    913                              <1> ; This indicates the general format of the last few bytes in the boot sector
914    914                              <1> BS_MAGIC_VER    equ 0x1b << 9
915    915                                  
916    916                                  ;
917    917                                  ;
918    918                                  ; writestr_early: write a null-terminated string to the console
919    919                                  ;           This assumes we're on page 0.  This is only used for early
920    920                                  ;           messages, so it should be OK.
921    921                                  ;
922    922                                  writestr_early:
923    923 00000362 6660                                    pushad
924    924 00000364 AC                      .loop:          lodsb
925    925 00000365 20C0                                    and al,al
926    926 00000367 7409                                    jz .return
927    927 00000369 B40E                                    mov ah,0Eh              ; Write to screen as TTY
928    928 0000036B BB0700                                  mov bx,0007h            ; Attribute
929    929 0000036E CD10                                    int 10h
930    930 00000370 EBF2                                    jmp short .loop
931    931 00000372 6661                    .return:        popad
932    932 00000374 C3                                      ret
933    933                                  
934    934 00000375 00000000<rept>          SuperInfo:      zd 32                   ; The first 16 bytes expanded 8 times
935    935                                  
936    936                                                  ; This fails if the sector overflowsg
937    937 000003F5 00<rept>                                zb 400h-($-$$)
938    938                                  end:
939    939                                  
940    940                                                  absolute 4*1Eh
941    941                                  fdctab          equ $
942    942 00000078 <res 00000002>          fdctab1         resw 1
943    943 0000007A <res 00000002>          fdctab2         resw 1