syslinux-3.08-2 sources from FC4
[bootcd.git] / syslinux / pxelinux.asm
1 ; -*- fundamental -*- (asm-mode sucks)
2 ; $Id: pxelinux.asm,v 1.168 2005/01/20 18:43:22 hpa Exp $
3 ; ****************************************************************************
4 ;
5 ;  pxelinux.asm
6 ;
7 ;  A program to boot Linux kernels off a TFTP server using the Intel PXE
8 ;  network booting API.  It is based on the SYSLINUX boot loader for
9 ;  MS-DOS floppies.
10 ;
11 ;   Copyright (C) 1994-2005  H. Peter Anvin
12 ;
13 ;  This program is free software; you can redistribute it and/or modify
14 ;  it under the terms of the GNU General Public License as published by
15 ;  the Free Software Foundation, Inc., 53 Temple Place Ste 330,
16 ;  Boston MA 02111-1307, USA; either version 2 of the License, or
17 ;  (at your option) any later version; incorporated herein by reference.
18
19 ; ****************************************************************************
20
21 %define IS_PXELINUX 1
22 %include "macros.inc"
23 %include "config.inc"
24 %include "kernel.inc"
25 %include "bios.inc"
26 %include "tracers.inc"
27 %include "pxe.inc"
28 %include "layout.inc"
29
30 ;
31 ; Some semi-configurable constants... change on your own risk.
32 ;
33 my_id           equ pxelinux_id
34 FILENAME_MAX_LG2 equ 7                  ; log2(Max filename size Including final null)
35 FILENAME_MAX    equ (1 << FILENAME_MAX_LG2)
36 NULLFILE        equ 0                   ; Zero byte == null file name
37 NULLOFFSET      equ 4                   ; Position in which to look
38 REBOOT_TIME     equ 5*60                ; If failure, time until full reset
39 %assign HIGHMEM_SLOP 128*1024           ; Avoid this much memory near the top
40 MAX_OPEN_LG2    equ 5                   ; log2(Max number of open sockets)
41 MAX_OPEN        equ (1 << MAX_OPEN_LG2)
42 PKTBUF_SIZE     equ (65536/MAX_OPEN)    ; Per-socket packet buffer size
43 TFTP_PORT       equ htons(69)           ; Default TFTP port 
44 PKT_RETRY       equ 6                   ; Packet transmit retry count
45 PKT_TIMEOUT     equ 12                  ; Initial timeout, timer ticks @ 55 ms
46 ; Desired TFTP block size
47 ; For Ethernet MTU is normally 1500.  Unfortunately there seems to
48 ; be a fair number of networks with "substandard" MTUs which break.
49 ; The code assumes TFTP_LARGEBLK <= 2K.
50 TFTP_MTU        equ 1472
51 TFTP_LARGEBLK   equ (TFTP_MTU-20-8-4)   ; MTU - IP hdr - UDP hdr - TFTP hdr
52 ; Standard TFTP block size
53 TFTP_BLOCKSIZE_LG2 equ 9                ; log2(bytes/block)
54 TFTP_BLOCKSIZE  equ (1 << TFTP_BLOCKSIZE_LG2)
55 %assign USE_PXE_PROVIDED_STACK 1        ; Use stack provided by PXE?
56
57 SECTOR_SHIFT    equ TFTP_BLOCKSIZE_LG2
58 SECTOR_SIZE     equ TFTP_BLOCKSIZE
59
60 ;
61 ; This is what we need to do when idle
62 ;
63 %macro  RESET_IDLE 0
64         call reset_idle
65 %endmacro
66 %macro  DO_IDLE 0
67         call check_for_arp
68 %endmacro
69
70 ;
71 ; TFTP operation codes
72 ;
73 TFTP_RRQ        equ htons(1)            ; Read request
74 TFTP_WRQ        equ htons(2)            ; Write request
75 TFTP_DATA       equ htons(3)            ; Data packet
76 TFTP_ACK        equ htons(4)            ; ACK packet
77 TFTP_ERROR      equ htons(5)            ; ERROR packet
78 TFTP_OACK       equ htons(6)            ; OACK packet
79
80 ;
81 ; TFTP error codes
82 ;
83 TFTP_EUNDEF     equ htons(0)            ; Unspecified error
84 TFTP_ENOTFOUND  equ htons(1)            ; File not found
85 TFTP_EACCESS    equ htons(2)            ; Access violation
86 TFTP_ENOSPACE   equ htons(3)            ; Disk full
87 TFTP_EBADOP     equ htons(4)            ; Invalid TFTP operation
88 TFTP_EBADID     equ htons(5)            ; Unknown transfer
89 TFTP_EEXISTS    equ htons(6)            ; File exists
90 TFTP_ENOUSER    equ htons(7)            ; No such user
91 TFTP_EOPTNEG    equ htons(8)            ; Option negotiation failure
92
93 ;
94 ; The following structure is used for "virtual kernels"; i.e. LILO-style
95 ; option labels.  The options we permit here are `kernel' and `append
96 ; Since there is no room in the bottom 64K for all of these, we
97 ; stick them at vk_seg:0000 and copy them down before we need them.
98 ;
99                 struc vkernel
100 vk_vname:       resb FILENAME_MAX       ; Virtual name **MUST BE FIRST!**
101 vk_rname:       resb FILENAME_MAX       ; Real name
102 vk_ipappend:    resb 1                  ; "IPAPPEND" flag
103                 resb 1                  ; Pad
104 vk_appendlen:   resw 1
105                 alignb 4
106 vk_append:      resb max_cmd_len+1      ; Command line
107                 alignb 4
108 vk_end:         equ $                   ; Should be <= vk_size
109                 endstruc
110
111 ;
112 ; Segment assignments in the bottom 640K
113 ; 0000h - main code/data segment (and BIOS segment)
114 ;
115 real_mode_seg   equ 4000h
116 vk_seg          equ 3000h               ; Virtual kernels
117 xfer_buf_seg    equ 2000h               ; Bounce buffer for I/O to high mem
118 pktbuf_seg      equ 1000h               ; Packet buffers segments
119 comboot_seg     equ real_mode_seg       ; COMBOOT image loading zone
120
121 ;
122 ; BOOTP/DHCP packet pattern
123 ;
124                 struc bootp_t           
125 bootp:
126 .opcode         resb 1                  ; BOOTP/DHCP "opcode"
127 .hardware       resb 1                  ; ARP hardware type
128 .hardlen        resb 1                  ; Hardware address length
129 .gatehops       resb 1                  ; Used by forwarders
130 .ident          resd 1                  ; Transaction ID
131 .seconds        resw 1                  ; Seconds elapsed
132 .flags          resw 1                  ; Broadcast flags
133 .cip            resd 1                  ; Client IP
134 .yip            resd 1                  ; "Your" IP
135 .sip            resd 1                  ; Next server IP
136 .gip            resd 1                  ; Relay agent IP
137 .macaddr        resb 16                 ; Client MAC address
138 .sname          resb 64                 ; Server name (optional)
139 .bootfile       resb 128                ; Boot file name
140 .option_magic   resd 1                  ; Vendor option magic cookie
141 .options        resb 1260               ; Vendor options
142                 endstruc        
143
144 BOOTP_OPTION_MAGIC      equ htonl(0x63825363)   ; See RFC 2132
145
146 ;
147 ; TFTP connection data structure.  Each one of these corresponds to a local
148 ; UDP port.  The size of this structure must be a power of 2.
149 ; HBO = host byte order; NBO = network byte order
150 ; (*) = written by options negotiation code, must be dword sized
151 ;
152                 struc open_file_t
153 tftp_localport  resw 1                  ; Local port number     (0 = not in use)
154 tftp_remoteport resw 1                  ; Remote port number
155 tftp_remoteip   resd 1                  ; Remote IP address
156 tftp_filepos    resd 1                  ; Bytes downloaded (including buffer)
157 tftp_filesize   resd 1                  ; Total file size(*)
158 tftp_blksize    resd 1                  ; Block size for this connection(*)
159 tftp_bytesleft  resw 1                  ; Unclaimed data bytes
160 tftp_lastpkt    resw 1                  ; Sequence number of last packet (NBO)
161 tftp_dataptr    resw 1                  ; Pointer to available data
162                 resw 2                  ; Currently unusued
163                 ; At end since it should not be zeroed on socked close
164 tftp_pktbuf     resw 1                  ; Packet buffer offset
165                 endstruc
166 %ifndef DEPEND
167 %if (open_file_t_size & (open_file_t_size-1))
168 %error "open_file_t is not a power of 2"
169 %endif
170 %endif
171
172 ; ---------------------------------------------------------------------------
173 ;   BEGIN CODE
174 ; ---------------------------------------------------------------------------
175
176 ;
177 ; Memory below this point is reserved for the BIOS and the MBR
178 ;
179                 section .earlybss
180 trackbufsize    equ 8192
181 trackbuf        resb trackbufsize       ; Track buffer goes here
182 getcbuf         resb trackbufsize
183                 ; ends at 4800h
184
185                 ; Put some large buffers here, before RBFG_brainfuck,
186                 ; where we can still carefully control the address
187                 ; assignments...
188
189                 alignb open_file_t_size
190 Files           resb MAX_OPEN*open_file_t_size
191
192                 alignb FILENAME_MAX
193 BootFile        resb 256                ; Boot file from DHCP packet
194 ConfigServer    resd 1                  ; Null prefix for mangled config name
195 ConfigName      resb 256-4              ; Configuration file from DHCP option
196 PathPrefix      resb 256                ; Path prefix derived from boot file
197 DotQuadBuf      resb 16                 ; Buffer for dotted-quad IP address
198 IPOption        resb 80                 ; ip= option buffer
199 InitStack       resd 1                  ; Pointer to reset stack
200
201 ; Warning here: RBFG build 22 randomly overwrites memory location
202 ; [0x5680,0x576c), possibly more.  It seems that it gets confused and
203 ; screws up the pointer to its own internal packet buffer and starts
204 ; writing a received ARP packet into low memory.
205 RBFG_brainfuck  resb 0E00h
206
207                 section .bss
208                 alignb 4
209 RebootTime      resd 1                  ; Reboot timeout, if set by option
210 StrucPtr        resd 1                  ; Pointer to PXENV+ or !PXE structure
211 APIVer          resw 1                  ; PXE API version found
212 IPOptionLen     resw 1                  ; Length of IPOption
213 IdleTimer       resw 1                  ; Time to check for ARP?
214 LocalBootType   resw 1                  ; Local boot return code
215 PktTimeout      resw 1                  ; Timeout for current packet
216 RealBaseMem     resw 1                  ; Amount of DOS memory after freeing
217 OverLoad        resb 1                  ; Set if DHCP packet uses "overloading"
218
219 ; The relative position of these fields matter!
220 MACLen          resb 1                  ; MAC address len
221 MACType         resb 1                  ; MAC address type
222 MAC             resb 16                 ; Actual MAC address
223 BOOTIFStr       resb 7                  ; Space for "BOOTIF="
224 MACStr          resb 3*17               ; MAC address as a string
225
226 ;
227 ; PXE packets which don't need static initialization
228 ;
229                 alignb 4
230 pxe_unload_stack_pkt:
231 .status:        resw 1                  ; Status
232 .reserved:      resw 10                 ; Reserved
233 pxe_unload_stack_pkt_len        equ $-pxe_unload_stack_pkt
234
235                 alignb 16
236                 ; BOOTP/DHCP packet buffer
237
238                 alignb 16
239 packet_buf      resb 2048               ; Transfer packet
240 packet_buf_size equ $-packet_buf
241
242 ;
243 ; Constants for the xfer_buf_seg
244 ;
245 ; The xfer_buf_seg is also used to store message file buffers.  We
246 ; need two trackbuffers (text and graphics), plus a work buffer
247 ; for the graphics decompressor.
248 ;
249 xbs_textbuf     equ 0                   ; Also hard-coded, do not change
250 xbs_vgabuf      equ trackbufsize
251 xbs_vgatmpbuf   equ 2*trackbufsize
252
253                 section .text
254                 ;
255                 ; PXELINUX needs more BSS than the other derivatives;
256                 ; therefore we relocate it from 7C00h on startup.
257                 ;
258 StackBuf        equ $                   ; Base of stack if we use our own
259
260 ;
261 ; Primary entry point.
262 ;
263 bootsec         equ $
264 _start:
265                 pushfd                  ; Paranoia... in case of return to PXE
266                 pushad                  ; ... save as much state as possible
267                 push ds
268                 push es
269                 push fs
270                 push gs
271
272                 xor ax,ax
273                 mov ds,ax
274                 mov es,ax       
275
276                 ; This is uglier than it should be, but works around
277                 ; some NASM 0.98.38 bugs.
278                 mov di,section..bcopy32.start
279                 add di,__bcopy_size-4
280                 lea si,[di-(TEXT_START-7C00h)]
281                 lea cx,[di-(TEXT_START-4)]
282                 shr cx,2
283                 std                     ; Overlapping areas, copy backwards
284                 rep movsd
285
286                 jmp 0:_start1           ; Canonicalize address
287 _start1:
288                 mov bp,sp
289                 les bx,[bp+48]          ; ES:BX -> !PXE or PXENV+ structure
290
291                 ; That is all pushed onto the PXE stack.  Save the pointer
292                 ; to it and switch to an internal stack.
293                 mov [InitStack],sp
294                 mov [InitStack+2],ss
295
296 %if USE_PXE_PROVIDED_STACK
297                 ; Apparently some platforms go bonkers if we
298                 ; set up our own stack...
299                 mov [BaseStack],sp
300                 mov [BaseStack+4],ss
301 %endif
302
303                 cli                     ; Paranoia
304                 lss esp,[BaseStack]
305
306                 sti                     ; Stack set up and ready
307                 cld                     ; Copy upwards
308
309 ;
310 ; Initialize screen (if we're using one)
311 ;
312                 ; Now set up screen parameters
313                 call adjust_screen
314
315                 ; Wipe the F-key area
316                 mov al,NULLFILE
317                 mov di,FKeyName
318                 mov cx,10*(1 << FILENAME_MAX_LG2)
319                 push es                 ; Save ES -> PXE structure
320                 push ds                 ; ES <- DS
321                 pop es
322                 rep stosb
323                 pop es                  ; Restore ES
324
325 ;
326 ; Tell the user we got this far
327 ;
328                 mov si,syslinux_banner
329                 call writestr
330
331                 mov si,copyright_str
332                 call writestr
333
334 ;
335 ; Assume API version 2.1, in case we find the !PXE structure without
336 ; finding the PXENV+ structure.  This should really look at the Base
337 ; Code ROM ID structure in have_pxe, but this is adequate for now --
338 ; if we have !PXE, we have to be 2.1 or higher, and we don't care
339 ; about higher versions than that.
340 ;
341                 mov word [APIVer],0201h
342
343 ;
344 ; Now we need to find the !PXE structure.  It's *supposed* to be pointed
345 ; to by SS:[SP+4], but support INT 1Ah, AX=5650h method as well.
346 ; FIX: ES:BX should point to the PXENV+ structure on entry as well.
347 ; We should make that the second test, and not trash ES:BX...
348
349                 cmp dword [es:bx], '!PXE'
350                 je have_pxe
351
352                 ; Uh-oh, not there... try plan B
353                 mov ax, 5650h
354                 int 1Ah                                 ; May trash regs
355                 jc no_pxe
356                 cmp ax,564Eh
357                 jne no_pxe
358
359                 ; Okay, that gave us the PXENV+ structure, find !PXE
360                 ; structure from that (if available)
361                 cmp dword [es:bx], 'PXEN'
362                 jne no_pxe
363                 cmp word [es:bx+4], 'V+'
364                 je have_pxenv
365
366                 ; Nothing there either.  Last-ditch: scan memory
367                 call memory_scan_for_pxe_struct         ; !PXE scan
368                 jnc have_pxe
369                 call memory_scan_for_pxenv_struct       ; PXENV+ scan
370                 jnc have_pxenv
371
372 no_pxe:         mov si,err_nopxe
373                 call writestr
374                 jmp kaboom
375
376 have_pxenv:
377                 mov [StrucPtr],bx
378                 mov [StrucPtr+2],es
379
380                 mov si,found_pxenv
381                 call writestr
382
383                 mov si,apiver_str
384                 call writestr
385                 mov ax,[es:bx+6]
386                 mov [APIVer],ax
387                 call writehex4
388                 call crlf
389
390                 cmp ax,0201h                    ; API version 2.1 or higher
391                 jb old_api
392                 mov si,bx
393                 mov ax,es
394                 les bx,[es:bx+28h]              ; !PXE structure pointer
395                 cmp dword [es:bx],'!PXE'
396                 je have_pxe
397
398                 ; Nope, !PXE structure missing despite API 2.1+, or at least
399                 ; the pointer is missing.  Do a last-ditch attempt to find it.
400                 call memory_scan_for_pxe_struct
401                 jnc have_pxe
402
403                 ; Otherwise, no dice, use PXENV+ structure
404                 mov bx,si
405                 mov es,ax
406
407 old_api:        ; Need to use a PXENV+ structure
408                 mov si,using_pxenv_msg
409                 call writestr
410
411                 mov eax,[es:bx+0Ah]             ; PXE RM API
412                 mov [PXENVEntry],eax
413
414                 mov si,undi_data_msg
415                 call writestr
416                 mov ax,[es:bx+20h]
417                 call writehex4
418                 call crlf
419                 mov si,undi_data_len_msg
420                 call writestr
421                 mov ax,[es:bx+22h]
422                 call writehex4
423                 call crlf
424                 mov si,undi_code_msg
425                 call writestr
426                 mov ax,[es:bx+24h]
427                 call writehex4
428                 call crlf
429                 mov si,undi_code_len_msg
430                 call writestr
431                 mov ax,[es:bx+26h]
432                 call writehex4
433                 call crlf
434
435                 ; Compute base memory size from PXENV+ structure
436                 xor esi,esi
437                 movzx eax,word [es:bx+20h]      ; UNDI data seg
438                 cmp ax,[es:bx+24h]              ; UNDI code seg
439                 ja .use_data
440                 mov ax,[es:bx+24h]
441                 mov si,[es:bx+26h]
442                 jmp short .combine
443 .use_data:
444                 mov si,[es:bx+22h]
445 .combine:
446                 shl eax,4
447                 add eax,esi
448                 shr eax,10                      ; Convert to kilobytes
449                 mov [RealBaseMem],ax
450
451                 mov si,pxenventry_msg
452                 call writestr
453                 mov ax,[PXENVEntry+2]
454                 call writehex4
455                 mov al,':'
456                 call writechr
457                 mov ax,[PXENVEntry]
458                 call writehex4
459                 call crlf
460                 jmp have_entrypoint
461
462 have_pxe:
463                 mov [StrucPtr],bx
464                 mov [StrucPtr+2],es
465
466                 mov eax,[es:bx+10h]
467                 mov [PXEEntry],eax
468
469                 mov si,undi_data_msg
470                 call writestr
471                 mov eax,[es:bx+2Ah]
472                 call writehex8
473                 call crlf
474                 mov si,undi_data_len_msg
475                 call writestr
476                 mov ax,[es:bx+2Eh]
477                 call writehex4
478                 call crlf
479                 mov si,undi_code_msg
480                 call writestr
481                 mov ax,[es:bx+32h]
482                 call writehex8
483                 call crlf
484                 mov si,undi_code_len_msg
485                 call writestr
486                 mov ax,[es:bx+36h]
487                 call writehex4
488                 call crlf
489
490                 ; Compute base memory size from !PXE structure
491                 xor esi,esi
492                 mov eax,[es:bx+2Ah]
493                 cmp eax,[es:bx+32h]
494                 ja .use_data
495                 mov eax,[es:bx+32h]
496                 mov si,[es:bx+36h]
497                 jmp short .combine
498 .use_data:
499                 mov si,[es:bx+2Eh]
500 .combine:
501                 add eax,esi
502                 shr eax,10
503                 mov [RealBaseMem],ax
504
505                 mov si,pxeentry_msg
506                 call writestr
507                 mov ax,[PXEEntry+2]
508                 call writehex4
509                 mov al,':'
510                 call writechr
511                 mov ax,[PXEEntry]
512                 call writehex4
513                 call crlf
514
515 have_entrypoint:
516                 push cs
517                 pop es                          ; Restore CS == DS == ES
518
519 ;
520 ; Network-specific initialization
521 ;
522                 xor ax,ax
523                 mov [LocalDomain],al            ; No LocalDomain received
524
525 ;
526 ; Now attempt to get the BOOTP/DHCP packet that brought us life (and an IP
527 ; address).  This lives in the DHCPACK packet (query info 2).
528 ;
529 query_bootp:
530                 mov di,pxe_bootp_query_pkt_2
531                 mov bx,PXENV_GET_CACHED_INFO
532
533                 call pxenv
534                 push word [pxe_bootp_query_pkt_2.status]
535                 jc .pxe_err1
536                 cmp ax,byte 0
537                 je .pxe_ok
538 .pxe_err1:
539                 mov di,pxe_bootp_size_query_pkt
540                 mov bx,PXENV_GET_CACHED_INFO
541
542                 call pxenv
543                 jc .pxe_err
544 .pxe_size:
545                 mov ax,[pxe_bootp_size_query_pkt.buffersize]
546                 call writehex4
547                 call crlf
548
549 .pxe_err:
550                 mov si,err_pxefailed
551                 call writestr
552                 call writehex4
553                 mov al, ' '
554                 call writechr
555                 pop ax                          ; Status
556                 call writehex4
557                 call crlf
558                 jmp kaboom                      ; We're dead
559
560 .pxe_ok:
561                 pop cx                          ; Forget status
562                 mov cx,[pxe_bootp_query_pkt_2.buffersize]
563                 call parse_dhcp                 ; Parse DHCP packet
564 ;
565 ; Save away MAC address (assume this is in query info 2.  If this
566 ; turns out to be problematic it might be better getting it from
567 ; the query info 1 packet.)
568 ;
569 .save_mac:
570                 movzx cx,byte [trackbuf+bootp.hardlen]
571                 mov [MACLen],cl
572                 mov al,[trackbuf+bootp.hardware]
573                 mov [MACType],al
574                 mov si,trackbuf+bootp.macaddr
575                 mov di,MAC
576                 push cx
577                 rep movsb
578                 mov cx,MAC+16
579                 sub cx,di
580                 xor ax,ax
581                 rep stosb
582                 
583                 mov si,bootif_str
584                 mov di,BOOTIFStr
585                 mov cx,bootif_str_len
586                 rep movsb
587         
588                 pop cx
589                 mov si,MACType
590                 inc cx
591                 mov bx,hextbl_lower
592 .hexify_mac:
593                 lodsb
594                 mov ah,al
595                 shr al,4
596                 xlatb
597                 stosb
598                 mov al,ah
599                 and al,0Fh
600                 xlatb
601                 stosb
602                 mov al,'-'
603                 stosb
604                 loop .hexify_mac
605                 mov [di-1],byte 0               ; Null-terminate and strip final colon
606
607 ;
608 ; Now, get the boot file and other info.  This lives in the CACHED_REPLY
609 ; packet (query info 3).
610 ;
611                 mov [pxe_bootp_size_query_pkt.packettype], byte 3
612
613                 mov di,pxe_bootp_query_pkt_3
614                 mov bx,PXENV_GET_CACHED_INFO
615
616                 call pxenv
617                 push word [pxe_bootp_query_pkt_3.status]
618                 jc .pxe_err1
619                 cmp ax,byte 0
620                 jne .pxe_err1
621
622                 ; Packet loaded OK...
623                 pop cx                          ; Forget status
624                 mov cx,[pxe_bootp_query_pkt_3.buffersize]
625                 call parse_dhcp                 ; Parse DHCP packet
626 ;
627 ; Generate ip= option
628 ;
629                 call genipopt
630
631 ;
632 ; Print IP address
633 ;
634                 mov eax,[MyIP]
635                 mov di,DotQuadBuf
636                 push di
637                 call gendotquad                 ; This takes network byte order input
638
639                 xchg ah,al                      ; Convert to host byte order
640                 ror eax,16                      ; (BSWAP doesn't work on 386)
641                 xchg ah,al
642
643                 mov si,myipaddr_msg
644                 call writestr
645                 call writehex8
646                 mov al,' '
647                 call writechr
648                 pop si                          ; DotQuadBuf
649                 call writestr
650                 call crlf
651
652                 mov si,IPOption
653                 call writestr
654                 call crlf
655
656 ;
657 ; Check to see if we got any PXELINUX-specific DHCP options; in particular,
658 ; if we didn't get the magic enable, do not recognize any other options.
659 ;
660 check_dhcp_magic:
661                 test byte [DHCPMagic], 1        ; If we didn't get the magic enable...
662                 jnz .got_magic
663                 mov byte [DHCPMagic], 0         ; If not, kill all other options
664 .got_magic:
665         
666
667 ;
668 ; Initialize UDP stack
669 ;
670 udp_init:
671                 mov eax,[MyIP]
672                 mov [pxe_udp_open_pkt.sip],eax
673                 mov di,pxe_udp_open_pkt
674                 mov bx,PXENV_UDP_OPEN
675                 call pxenv
676                 jc .failed
677                 cmp word [pxe_udp_open_pkt.status], byte 0
678                 je .success
679 .failed:        mov si,err_udpinit
680                 call writestr
681                 jmp kaboom
682 .success:
683
684 ;
685 ; Common initialization code
686 ;
687 %include "init.inc"
688 %include "cpuinit.inc"
689
690 ;
691 ; Now we're all set to start with our *real* business.  First load the
692 ; configuration file (if any) and parse it.
693 ;
694 ; In previous versions I avoided using 32-bit registers because of a
695 ; rumour some BIOSes clobbered the upper half of 32-bit registers at
696 ; random.  I figure, though, that if there are any of those still left
697 ; they probably won't be trying to install Linux on them...
698 ;
699 ; The code is still ripe with 16-bitisms, though.  Not worth the hassle
700 ; to take'm out.  In fact, we may want to put them back if we're going
701 ; to boot ELKS at some point.
702 ;
703
704 ;
705 ; Store standard filename prefix
706 ;
707 prefix:         test byte [DHCPMagic], 04h      ; Did we get a path prefix option
708                 jnz .got_prefix
709                 mov si,BootFile
710                 mov di,PathPrefix
711                 cld
712                 call strcpy
713                 mov cx,di
714                 sub cx,PathPrefix+1
715                 std
716                 lea si,[di-2]                   ; Skip final null!
717 .find_alnum:    lodsb
718                 or al,20h
719                 cmp al,'.'                      ; Count . or - as alphanum
720                 je .alnum
721                 cmp al,'-'
722                 je .alnum
723                 cmp al,'0'
724                 jb .notalnum
725                 cmp al,'9'
726                 jbe .alnum
727                 cmp al,'a'
728                 jb .notalnum
729                 cmp al,'z'
730                 ja .notalnum
731 .alnum:         loop .find_alnum
732                 dec si
733 .notalnum:      mov byte [si+2],0               ; Zero-terminate after delimiter
734                 cld
735 .got_prefix:
736                 mov si,tftpprefix_msg
737                 call writestr
738                 mov si,PathPrefix
739                 call writestr
740                 call crlf
741
742 ;
743 ; Load configuration file
744 ;
745 find_config:
746
747 ;
748 ; Begin looking for configuration file
749 ;
750 config_scan:
751                 mov di,ConfigServer
752                 xor eax,eax
753                 stosd                           ; The config file is always from the server
754
755                 test byte [DHCPMagic], 02h
756                 jz .no_option
757
758                 ; We got a DHCP option, try it first
759                 mov si,trying_msg
760                 call writestr
761                 ; mov di,ConfigName             ; - already the case
762                 mov si,di
763                 call writestr
764                 call crlf
765                 mov di,ConfigServer
766                 call open
767                 jnz .success
768
769 .no_option:
770                 mov di,ConfigName
771                 mov si,cfgprefix
772                 mov cx,cfgprefix_len
773                 rep movsb
774
775                 ; Try loading by MAC address
776                 ; Have to guess config file name
777                 push di
778                 mov si,MACStr
779                 mov cx,(3*17+1)/2
780                 rep movsw
781                 mov si,trying_msg
782                 call writestr
783                 mov di,ConfigName
784                 mov si,di
785                 call writestr
786                 call crlf
787                 mov di,ConfigServer
788                 call open
789                 pop di
790                 jnz .success
791
792 .scan_ip:
793                 mov cx,8
794                 mov eax,[MyIP]
795                 xchg ah,al                      ; Convert to host byte order
796                 ror eax,16
797                 xchg ah,al
798 .hexify_loop:   rol eax,4
799                 push eax
800                 and al,0Fh
801                 cmp al,10
802                 jae .high
803 .low:           add al,'0'
804                 jmp short .char
805 .high:          add al,'A'-10
806 .char:          stosb
807                 pop eax
808                 loop .hexify_loop
809
810                 mov cx,9                        ; Up to 9 attempts
811
812 .tryagain:      mov byte [di],0
813                 cmp cx,byte 1
814                 jne .not_default
815                 pusha
816                 mov si,default_str
817                 mov cx,default_len
818                 rep movsb                       ; Copy "default" string
819                 popa
820 .not_default:   pusha
821                 mov si,trying_msg
822                 call writestr
823                 mov di,ConfigName
824                 mov si,di
825                 call writestr
826                 call crlf
827                 mov di,ConfigServer
828                 call open
829                 popa
830                 jnz .success
831                 dec di
832                 loop .tryagain
833
834                 jmp no_config_file
835
836 .success:
837
838 ;
839 ; Now we have the config file open.  Parse the config file and
840 ; run the user interface.
841 ;
842 %include "ui.inc"
843
844 ;
845 ; Linux kernel loading code is common.  However, we need to define
846 ; a couple of helper macros...
847 ;
848
849 ; Handle "ipappend" option
850 %define HAVE_SPECIAL_APPEND
851 %macro  SPECIAL_APPEND 0
852                 test byte [IPAppend],01h        ; ip=
853                 jz .noipappend1
854                 mov si,IPOption
855                 mov cx,[IPOptionLen]
856                 rep movsb
857                 mov al,' '
858                 stosb
859 .noipappend1:
860                 test byte [IPAppend],02h
861                 jz .noipappend2
862                 mov si,BOOTIFStr
863                 call strcpy
864                 mov byte [es:di-1],' '          ; Replace null with space
865 .noipappend2:
866 %endmacro
867
868 ; Unload PXE stack
869 %define HAVE_UNLOAD_PREP
870 %macro  UNLOAD_PREP 0
871                 call unload_pxe
872 %endmacro
873
874 %include "runkernel.inc"
875
876 ;
877 ; COMBOOT-loading code
878 ;
879 %include "comboot.inc"
880 %include "com32.inc"
881 %include "cmdline.inc"
882
883 ;
884 ; Boot sector loading code
885 ;
886 %include "bootsect.inc"
887
888 ;
889 ; Boot to the local disk by returning the appropriate PXE magic.
890 ; AX contains the appropriate return code.
891 ;
892 local_boot:
893                 mov si,cs
894                 mov ds,si                       ; Restore DI
895                 lss esp,[BaseStack]
896                 mov [LocalBootType],ax
897                 call vgaclearmode
898                 mov si,localboot_msg
899                 call writestr
900                 ; Restore the environment we were called with
901                 lss sp,[InitStack]
902                 pop gs
903                 pop fs
904                 pop es
905                 pop ds
906                 popad
907                 mov ax,[cs:LocalBootType]
908                 popfd
909                 retf                            ; Return to PXE
910
911 ;
912 ; abort_check: let the user abort with <ESC> or <Ctrl-C>
913 ;
914 abort_check:
915                 call pollchar
916                 jz ac_ret1
917                 pusha
918                 call getchar
919                 cmp al,27                       ; <ESC>
920                 je ac_kill
921                 cmp al,3                        ; <Ctrl-C>
922                 jne ac_ret2
923 ac_kill:        mov si,aborted_msg
924
925 ;
926 ; abort_load: Called by various routines which wants to print a fatal
927 ;             error message and return to the command prompt.  Since this
928 ;             may happen at just about any stage of the boot process, assume
929 ;             our state is messed up, and just reset the segment registers
930 ;             and the stack forcibly.
931 ;
932 ;             SI    = offset (in _text) of error message to print
933 ;
934 abort_load:
935                 mov ax,cs                       ; Restore CS = DS = ES
936                 mov ds,ax
937                 mov es,ax
938                 lss esp,[BaseStack]
939                 sti
940                 call cwritestr                  ; Expects SI -> error msg
941 al_ok:          jmp enter_command               ; Return to command prompt
942 ;
943 ; End of abort_check
944 ;
945 ac_ret2:        popa
946 ac_ret1:        ret
947
948
949 ;
950 ; kaboom: write a message and bail out.  Wait for quite a while,
951 ;         or a user keypress, then do a hard reboot.
952 ;
953 kaboom:
954                 mov ax,cs
955                 mov es,ax
956                 mov ds,ax
957                 lss esp,[BaseStack]
958                 sti
959 .patch:         mov si,bailmsg
960                 call writestr           ; Returns with AL = 0
961 .drain:         call pollchar
962                 jz .drained
963                 call getchar
964                 jmp short .drain
965 .drained:
966                 mov edi,[RebootTime]
967                 mov al,[DHCPMagic]
968                 and al,09h              ; Magic+Timeout
969                 cmp al,09h
970                 je .time_set
971                 mov edi,REBOOT_TIME
972 .time_set:
973                 mov cx,18
974 .wait1:         push cx
975                 mov ecx,edi
976 .wait2:         mov dx,[BIOS_timer]
977 .wait3:         call pollchar
978                 jnz .keypress
979                 cmp dx,[BIOS_timer]
980                 je .wait3
981                 loop .wait2,ecx
982                 mov al,'.'
983                 call writechr
984                 pop cx
985                 loop .wait1
986 .keypress:
987                 call crlf
988                 mov word [BIOS_magic],0 ; Cold reboot
989                 jmp 0F000h:0FFF0h       ; Reset vector address
990
991 ;
992 ; memory_scan_for_pxe_struct:
993 ;
994 ;       If none of the standard methods find the !PXE structure, look for it
995 ;       by scanning memory.
996 ;
997 ;       On exit, if found:
998 ;               CF = 0, ES:BX -> !PXE structure
999 ;       Otherwise CF = 1, all registers saved
1000 ;       
1001 memory_scan_for_pxe_struct:
1002                 push ds
1003                 pusha
1004                 mov ax,cs
1005                 mov ds,ax
1006                 mov si,trymempxe_msg
1007                 call writestr
1008                 mov ax,[BIOS_fbm]       ; Starting segment
1009                 shl ax,(10-4)           ; Kilobytes -> paragraphs
1010 ;               mov ax,01000h           ; Start to look here
1011                 dec ax                  ; To skip inc ax
1012 .mismatch:
1013                 inc ax
1014                 cmp ax,0A000h           ; End of memory
1015                 jae .not_found
1016                 call writehex4
1017                 mov si,fourbs_msg
1018                 call writestr
1019                 mov es,ax
1020                 mov edx,[es:0]
1021                 cmp edx,'!PXE'
1022                 jne .mismatch
1023                 movzx cx,byte [es:4]    ; Length of structure
1024                 cmp cl,08h              ; Minimum length
1025                 jb .mismatch
1026                 push ax
1027                 xor ax,ax
1028                 xor si,si
1029 .checksum:      es lodsb
1030                 add ah,al
1031                 loop .checksum
1032                 pop ax
1033                 jnz .mismatch           ; Checksum must == 0
1034 .found:         mov bp,sp
1035                 xor bx,bx
1036                 mov [bp+8],bx           ; Save BX into stack frame (will be == 0)
1037                 mov ax,es
1038                 call writehex4
1039                 call crlf
1040                 popa
1041                 pop ds
1042                 clc
1043                 ret
1044 .not_found:     mov si,notfound_msg
1045                 call writestr
1046                 popa
1047                 pop ds
1048                 stc
1049                 ret
1050
1051 ;
1052 ; memory_scan_for_pxenv_struct:
1053 ;
1054 ;       If none of the standard methods find the PXENV+ structure, look for it
1055 ;       by scanning memory.
1056 ;
1057 ;       On exit, if found:
1058 ;               CF = 0, ES:BX -> PXENV+ structure
1059 ;       Otherwise CF = 1, all registers saved
1060 ;       
1061 memory_scan_for_pxenv_struct:
1062                 pusha
1063                 mov si,trymempxenv_msg
1064                 call writestr
1065 ;               mov ax,[BIOS_fbm]       ; Starting segment
1066 ;               shl ax,(10-4)           ; Kilobytes -> paragraphs
1067                 mov ax,01000h           ; Start to look here
1068                 dec ax                  ; To skip inc ax
1069 .mismatch:
1070                 inc ax
1071                 cmp ax,0A000h           ; End of memory
1072                 jae .not_found
1073                 mov es,ax
1074                 mov edx,[es:0]
1075                 cmp edx,'PXEN'
1076                 jne .mismatch
1077                 mov dx,[es:4]
1078                 cmp dx,'V+'
1079                 jne .mismatch
1080                 movzx cx,byte [es:8]    ; Length of structure
1081                 cmp cl,26h              ; Minimum length
1082                 jb .mismatch
1083                 xor ax,ax
1084                 xor si,si
1085 .checksum:      es lodsb
1086                 add ah,al
1087                 loop .checksum
1088                 and ah,ah
1089                 jnz .mismatch           ; Checksum must == 0
1090 .found:         mov bp,sp
1091                 mov [bp+8],bx           ; Save BX into stack frame
1092                 mov ax,bx
1093                 call writehex4
1094                 call crlf
1095                 clc
1096                 ret
1097 .not_found:     mov si,notfound_msg
1098                 call writestr
1099                 popad
1100                 stc
1101                 ret
1102
1103 ;
1104 ; searchdir:
1105 ;
1106 ;       Open a TFTP connection to the server 
1107 ;
1108 ;            On entry:
1109 ;               DS:DI   = mangled filename
1110 ;            If successful:
1111 ;               ZF clear
1112 ;               SI      = socket pointer
1113 ;               DX:AX   = file length in bytes
1114 ;            If unsuccessful
1115 ;               ZF set
1116 ;
1117
1118 searchdir:
1119                 push es
1120                 mov ax,ds
1121                 mov es,ax
1122                 mov si,di
1123                 push bp
1124                 mov bp,sp
1125
1126                 call allocate_socket
1127                 jz .error
1128
1129                 mov ax,PKT_RETRY        ; Retry counter
1130                 mov word [PktTimeout],PKT_TIMEOUT       ; Initial timeout
1131         
1132 .sendreq:       push ax                 ; [bp-2]  - Retry counter
1133                 push si                 ; [bp-4]  - File name 
1134
1135                 mov di,packet_buf
1136                 mov [pxe_udp_write_pkt.buffer],di
1137
1138                 mov ax,TFTP_RRQ         ; TFTP opcode
1139                 stosw
1140
1141                 lodsd                   ; EAX <- server override (if any)
1142                 and eax,eax
1143                 jnz .noprefix           ; No prefix, and we have the server
1144
1145                 push si                 ; Add common prefix
1146                 mov si,PathPrefix
1147                 call strcpy
1148                 dec di
1149                 pop si
1150
1151                 mov eax,[ServerIP]      ; Get default server
1152
1153 .noprefix:
1154                 call strcpy             ; Filename
1155
1156                 mov [bx+tftp_remoteip],eax
1157
1158                 push bx                 ; [bp-6]  - TFTP block
1159                 mov bx,[bx]
1160                 push bx                 ; [bp-8]  - TID (local port no)
1161
1162                 mov [pxe_udp_write_pkt.status],byte 0
1163                 mov [pxe_udp_write_pkt.sip],eax
1164                 ; Now figure out the gateway
1165                 xor eax,[MyIP]
1166                 and eax,[Netmask]
1167                 jz .nogwneeded
1168                 mov eax,[Gateway]
1169 .nogwneeded:
1170                 mov [pxe_udp_write_pkt.gip],eax
1171                 mov [pxe_udp_write_pkt.lport],bx
1172                 mov ax,[ServerPort]
1173                 mov [pxe_udp_write_pkt.rport],ax
1174                 mov si,tftp_tail
1175                 mov cx,tftp_tail_len
1176                 rep movsb
1177                 sub di,packet_buf       ; Get packet size
1178                 mov [pxe_udp_write_pkt.buffersize],di
1179
1180                 mov di,pxe_udp_write_pkt
1181                 mov bx,PXENV_UDP_WRITE
1182                 call pxenv
1183                 jc .failure
1184                 cmp word [pxe_udp_write_pkt.status],byte 0
1185                 jne .failure
1186
1187                 ;
1188                 ; Danger, Will Robinson!  We need to support timeout
1189                 ; and retry lest we just lost a packet...
1190                 ;
1191
1192                 ; Packet transmitted OK, now we need to receive
1193 .getpacket:     push word [PktTimeout]  ; [bp-10]
1194                 push word [BIOS_timer]  ; [bp-12]
1195
1196 .pkt_loop:      mov bx,[bp-8]           ; TID
1197                 mov di,packet_buf
1198                 mov word [pxe_udp_read_pkt.status],0
1199                 mov [pxe_udp_read_pkt.buffer],di
1200                 mov [pxe_udp_read_pkt.buffer+2],ds
1201                 mov word [pxe_udp_read_pkt.buffersize],packet_buf_size
1202                 mov eax,[MyIP]
1203                 mov [pxe_udp_read_pkt.dip],eax
1204                 mov [pxe_udp_read_pkt.lport],bx
1205                 mov di,pxe_udp_read_pkt
1206                 mov bx,PXENV_UDP_READ
1207                 call pxenv
1208                 and ax,ax
1209                 jz .got_packet                  ; Wait for packet
1210 .no_packet:
1211                 mov dx,[BIOS_timer]
1212                 cmp dx,[bp-12]
1213                 je .pkt_loop
1214                 mov [bp-12],dx
1215                 dec word [bp-10]                ; Timeout
1216                 jnz .pkt_loop
1217                 pop ax  ; Adjust stack
1218                 pop ax
1219                 shl word [PktTimeout],1         ; Exponential backoff
1220                 jmp .failure
1221                 
1222 .got_packet:
1223                 mov si,[bp-6]                   ; TFTP pointer
1224                 mov bx,[bp-8]                   ; TID
1225
1226                 mov eax,[si+tftp_remoteip]
1227                 cmp [pxe_udp_read_pkt.sip],eax  ; This is technically not to the TFTP spec?
1228                 jne .no_packet
1229
1230                 ; Got packet - reset timeout
1231                 mov word [PktTimeout],PKT_TIMEOUT
1232
1233                 pop ax  ; Adjust stack
1234                 pop ax
1235
1236                 mov ax,[pxe_udp_read_pkt.rport]
1237                 mov [si+tftp_remoteport],ax
1238
1239                 ; filesize <- -1 == unknown
1240                 mov dword [si+tftp_filesize], -1
1241                 ; Default blksize unless blksize option negotiated
1242                 mov word [si+tftp_blksize], TFTP_BLOCKSIZE
1243
1244                 mov cx,[pxe_udp_read_pkt.buffersize]
1245                 sub cx,2                ; CX <- bytes after opcode
1246                 jb .failure             ; Garbled reply
1247
1248                 mov si,packet_buf
1249                 lodsw
1250
1251                 cmp ax, TFTP_ERROR
1252                 je .bailnow             ; ERROR reply: don't try again
1253
1254                 cmp ax, TFTP_OACK
1255                 jne .no_tsize
1256
1257                 ; Now we need to parse the OACK packet to get the transfer
1258                 ; size.  SI -> first byte of options; CX -> byte count
1259 .parse_oack:
1260                 jcxz .no_tsize                  ; No options acked
1261 .get_opt_name:
1262                 mov di,si
1263                 mov bx,si
1264 .opt_name_loop: lodsb
1265                 and al,al
1266                 jz .got_opt_name
1267                 or al,20h                       ; Convert to lowercase
1268                 stosb
1269                 loop .opt_name_loop
1270                 ; We ran out, and no final null
1271                 jmp .err_reply
1272 .got_opt_name:  ; si -> option value
1273                 dec cx                          ; bytes left in pkt
1274                 jz .err_reply                   ; Option w/o value
1275
1276                 ; Parse option pointed to by bx; guaranteed to be
1277                 ; null-terminated.
1278                 push cx
1279                 push si
1280                 mov si,bx                       ; -> option name
1281                 mov bx,tftp_opt_table
1282                 mov cx,tftp_opts
1283 .opt_loop:
1284                 push cx
1285                 push si
1286                 mov di,[bx]                     ; Option pointer
1287                 mov cx,[bx+2]                   ; Option len
1288                 repe cmpsb
1289                 pop si
1290                 pop cx
1291                 je .get_value                   ; OK, known option
1292                 add bx,6
1293                 loop .opt_loop
1294
1295                 pop si
1296                 pop cx
1297                 jmp .err_reply                  ; Non-negotiated option returned
1298
1299 .get_value:     pop si                          ; si -> option value
1300                 pop cx                          ; cx -> bytes left in pkt
1301                 mov bx,[bx+4]                   ; Pointer to data target
1302                 add bx,[bp-6]                   ; TFTP socket pointer
1303                 xor eax,eax
1304                 xor edx,edx
1305 .value_loop:    lodsb
1306                 and al,al
1307                 jz .got_value
1308                 sub al,'0'
1309                 cmp al, 9
1310                 ja .err_reply                   ; Not a decimal digit
1311                 imul edx,10
1312                 add edx,eax
1313                 mov [bx],edx
1314                 loop .value_loop
1315                 ; Ran out before final null, accept anyway
1316                 jmp short .done_pkt
1317
1318 .got_value:
1319                 dec cx
1320                 jnz .get_opt_name               ; Not end of packet
1321
1322                 ; ZF == 1
1323
1324                 ; Success, done!
1325 .done_pkt:
1326                 pop si                  ; Junk  
1327                 pop si                  ; We want the packet ptr in SI
1328
1329                 mov eax,[si+tftp_filesize]
1330                 cmp eax,-1
1331                 jz .no_tsize
1332                 mov edx,eax
1333                 shr edx,16              ; DX:AX == EAX
1334
1335                 and eax,eax             ; Set ZF depending on file size
1336                 pop bp                  ; Junk
1337                 pop bp                  ; Junk (retry counter)
1338                 jz .error_si            ; ZF = 1 need to free the socket
1339                 pop bp
1340                 pop es
1341                 ret
1342
1343 .no_tsize:
1344 .err_reply:     ; Option negotiation error.  Send ERROR reply.
1345                 ; ServerIP and gateway are already programmed in
1346                 mov si,[bp-6]
1347                 mov ax,[si+tftp_remoteport]
1348                 mov word [pxe_udp_write_pkt.rport],ax
1349                 mov word [pxe_udp_write_pkt.buffer],tftp_opt_err
1350                 mov word [pxe_udp_write_pkt.buffersize],tftp_opt_err_len
1351                 mov di,pxe_udp_write_pkt
1352                 mov bx,PXENV_UDP_WRITE
1353                 call pxenv
1354
1355                 ; Write an error message and explode
1356                 mov si,err_oldtftp
1357                 call writestr
1358                 jmp kaboom
1359
1360 .bailnow:       mov word [bp-2],1       ; Immediate error - no retry
1361
1362 .failure:       pop bx                  ; Junk
1363                 pop bx
1364                 pop si
1365                 pop ax
1366                 dec ax                  ; Retry counter
1367                 jnz .sendreq            ; Try again
1368
1369 .error:         mov si,bx               ; Socket pointer
1370 .error_si:                              ; Socket pointer already in SI
1371                 call free_socket        ; ZF <- 1, SI <- 0
1372                 pop bp
1373                 pop es
1374                 ret
1375
1376 ;
1377 ; allocate_socket: Allocate a local UDP port structure
1378 ;
1379 ;               If successful:
1380 ;                 ZF set
1381 ;                 BX     = socket pointer
1382 ;               If unsuccessful:
1383 ;                 ZF clear
1384 ;
1385 allocate_socket:
1386                 push cx
1387                 mov bx,Files
1388                 mov cx,MAX_OPEN
1389 .check:         cmp word [bx], byte 0
1390                 je .found
1391                 add bx,open_file_t_size
1392                 loop .check
1393                 xor cx,cx                       ; ZF = 1
1394                 pop cx
1395                 ret
1396                 ; Allocate a socket number.  Socket numbers are made
1397                 ; guaranteed unique by including the socket slot number
1398                 ; (inverted, because we use the loop counter cx); add a
1399                 ; counter value to keep the numbers from being likely to
1400                 ; get immediately reused.
1401                 ;
1402                 ; The NextSocket variable also contains the top two bits
1403                 ; set.  This generates a value in the range 49152 to
1404                 ; 57343.
1405 .found:
1406                 dec cx
1407                 push ax
1408                 mov ax,[NextSocket]
1409                 inc ax
1410                 and ax,((1 << (13-MAX_OPEN_LG2))-1) | 0xC000
1411                 mov [NextSocket],ax
1412                 shl cx,13-MAX_OPEN_LG2
1413                 add cx,ax                       ; ZF = 0
1414                 xchg ch,cl                      ; Convert to network byte order
1415                 mov [bx],cx                     ; Socket in use
1416                 pop ax
1417                 pop cx
1418                 ret
1419
1420 ;
1421 ; Free socket: socket in SI; return SI = 0, ZF = 1 for convenience
1422 ;
1423 free_socket:
1424                 push es
1425                 pusha
1426                 xor ax,ax
1427                 mov es,ax
1428                 mov di,si
1429                 mov cx,tftp_pktbuf >> 1         ; tftp_pktbuf is not cleared
1430                 rep stosw
1431                 popa
1432                 pop es
1433                 xor si,si
1434                 ret
1435
1436 ;
1437 ; parse_dotquad:
1438 ;              Read a dot-quad pathname in DS:SI and output an IP
1439 ;              address in EAX, with SI pointing to the first
1440 ;              nonmatching character.
1441 ;
1442 ;              Return CF=1 on error.
1443 ;
1444 parse_dotquad:
1445                 push cx
1446                 mov cx,4
1447                 xor eax,eax
1448 .parseloop:
1449                 mov ch,ah
1450                 mov ah,al
1451                 lodsb
1452                 sub al,'0'
1453                 jb .notnumeric
1454                 cmp al,9
1455                 ja .notnumeric
1456                 aad                             ; AL += 10 * AH; AH = 0;
1457                 xchg ah,ch
1458                 jmp .parseloop
1459 .notnumeric:
1460                 cmp al,'.'-'0'
1461                 pushf
1462                 mov al,ah
1463                 mov ah,ch
1464                 xor ch,ch
1465                 ror eax,8
1466                 popf
1467                 jne .error
1468                 loop .parseloop
1469                 jmp .done
1470 .error:
1471                 loop .realerror                 ; If CX := 1 then we're done
1472                 clc
1473                 jmp .done
1474 .realerror:
1475                 stc
1476 .done:
1477                 dec si                          ; CF unchanged!
1478                 pop cx
1479                 ret
1480 ;
1481 ; mangle_name: Mangle a filename pointed to by DS:SI into a buffer pointed
1482 ;              to by ES:DI; ends on encountering any whitespace.
1483 ;
1484 ;              This verifies that a filename is < FILENAME_MAX characters
1485 ;              and doesn't contain whitespace, and zero-pads the output buffer,
1486 ;              so "repe cmpsb" can do a compare.
1487 ;
1488 ;              The first four bytes of the manged name is the IP address of
1489 ;              the download host.
1490 ;
1491 mangle_name:
1492                 push si
1493                 mov eax,[ServerIP]
1494                 cmp byte [si],0
1495                 je .noip                        ; Null filename?!?!
1496                 cmp word [si],'::'              ; Leading ::?
1497                 je .gotprefix
1498
1499 .more:
1500                 inc si
1501                 cmp byte [si],0
1502                 je .noip
1503                 cmp word [si],'::'
1504                 jne .more
1505
1506                 ; We have a :: prefix of some sort, it could be either
1507                 ; a DNS name or a dot-quad IP address.  Try the dot-quad
1508                 ; first...
1509 .here:
1510                 pop si
1511                 push si
1512                 call parse_dotquad
1513                 jc .notdq
1514                 cmp word [si],'::'
1515                 je .gotprefix
1516 .notdq:
1517                 pop si
1518                 push si
1519                 call dns_resolv
1520                 cmp word [si],'::'
1521                 jne .noip
1522                 and eax,eax
1523                 jnz .gotprefix
1524
1525 .noip:
1526                 pop si
1527                 xor eax,eax
1528                 jmp .prefix_done
1529
1530 .gotprefix:
1531                 pop cx                          ; Adjust stack
1532                 inc si                          ; Skip double colon
1533                 inc si
1534
1535 .prefix_done:
1536                 stosd                           ; Save IP address prefix
1537                 mov cx,FILENAME_MAX-5
1538
1539 .mn_loop:
1540                 lodsb
1541                 cmp al,' '                      ; If control or space, end
1542                 jna .mn_end
1543                 stosb
1544                 loop .mn_loop
1545 .mn_end:
1546                 inc cx                          ; At least one null byte
1547                 xor ax,ax                       ; Zero-fill name
1548                 rep stosb                       ; Doesn't do anything if CX=0
1549                 ret                             ; Done
1550
1551 ;
1552 ; unmangle_name: Does the opposite of mangle_name; converts a DOS-mangled
1553 ;                filename to the conventional representation.  This is needed
1554 ;                for the BOOT_IMAGE= parameter for the kernel.
1555 ;                NOTE: A 13-byte buffer is mandatory, even if the string is
1556 ;                known to be shorter.
1557 ;
1558 ;                DS:SI -> input mangled file name
1559 ;                ES:DI -> output buffer
1560 ;
1561 ;                On return, DI points to the first byte after the output name,
1562 ;                which is set to a null byte.
1563 ;
1564 unmangle_name:
1565                 push eax
1566                 lodsd
1567                 and eax,eax
1568                 jz .noip
1569                 call gendotquad
1570                 mov ax,'::'
1571                 stosw
1572 .noip:
1573                 call strcpy
1574                 dec di                          ; Point to final null byte
1575                 pop eax
1576                 ret
1577
1578 ;
1579 ; pxenv
1580 ;
1581 ; This is the main PXENV+/!PXE entry point, using the PXENV+
1582 ; calling convention.  This is a separate local routine so
1583 ; we can hook special things from it if necessary.
1584 ;
1585
1586 pxenv:
1587 .jump:          call 0:pxe_thunk                ; Default to calling the thunk
1588                 cld                             ; Make sure DF <- 0
1589                 ret
1590
1591 ; Must be after function def due to NASM bug
1592 PXENVEntry      equ pxenv.jump+1
1593
1594 ;
1595 ; pxe_thunk
1596 ;
1597 ; Convert from the PXENV+ calling convention (BX, ES, DI) to the !PXE
1598 ; calling convention (using the stack.)
1599 ;
1600 ; This is called as a far routine so that we can just stick it into
1601 ; the PXENVEntry variable.
1602 ;
1603 pxe_thunk:      push es
1604                 push di
1605                 push bx
1606 .jump:          call 0:0
1607                 add sp,byte 6
1608                 cmp ax,byte 1
1609                 cmc                             ; Set CF unless ax == 0
1610                 retf
1611
1612 ; Must be after function def due to NASM bug
1613 PXEEntry        equ pxe_thunk.jump+1
1614
1615 ;
1616 ; getfssec: Get multiple clusters from a file, given the starting cluster.
1617 ;
1618 ;       In this case, get multiple blocks from a specific TCP connection.
1619 ;
1620 ;  On entry:
1621 ;       ES:BX   -> Buffer
1622 ;       SI      -> TFTP socket pointer
1623 ;       CX      -> 512-byte block count; 0FFFFh = until end of file
1624 ;  On exit:
1625 ;       SI      -> TFTP socket pointer (or 0 on EOF)
1626 ;       CF = 1  -> Hit EOF
1627 ;
1628 getfssec:       push si
1629                 push fs
1630                 mov di,bx
1631                 mov bx,si
1632                 mov ax,pktbuf_seg
1633                 mov fs,ax
1634
1635                 movzx ecx,cx
1636                 shl ecx,TFTP_BLOCKSIZE_LG2      ; Convert to bytes
1637                 jz .hit_eof                     ; Nothing to do?
1638                 
1639 .need_more:
1640                 push ecx
1641
1642                 movzx eax,word [bx+tftp_bytesleft]
1643                 cmp ecx,eax
1644                 jna .ok_size
1645                 mov ecx,eax
1646                 jcxz .need_packet               ; No bytes available?
1647 .ok_size:
1648
1649                 mov ax,cx                       ; EAX<31:16> == ECX<31:16> == 0
1650                 mov si,[bx+tftp_dataptr]
1651                 sub [bx+tftp_bytesleft],cx
1652                 fs rep movsb                    ; Copy from packet buffer
1653                 mov [bx+tftp_dataptr],si
1654
1655                 pop ecx
1656                 sub ecx,eax
1657                 jnz .need_more
1658
1659
1660 .hit_eof:
1661                 pop fs
1662                 pop si
1663
1664                 ; Is there anything left of this?
1665                 mov eax,[si+tftp_filesize]
1666                 sub eax,[si+tftp_filepos]
1667                 jnz .bytes_left ; CF <- 0
1668
1669                 cmp [si+tftp_bytesleft],ax
1670                 jnz .bytes_left ; CF <- 0
1671
1672                 ; The socket is closed and the buffer drained
1673                 ; Close socket structure and re-init for next user
1674                 call free_socket
1675                 stc
1676 .bytes_left:
1677                 ret
1678
1679 ;
1680 ; No data in buffer, check to see if we can get a packet...
1681 ;
1682 .need_packet:
1683                 pop ecx
1684                 mov eax,[bx+tftp_filesize]
1685                 cmp eax,[bx+tftp_filepos]
1686                 je .hit_eof                     ; Already EOF'd; socket already closed
1687
1688                 pushad
1689                 push es
1690                 mov si,bx
1691                 call get_packet
1692                 pop es
1693                 popad
1694
1695                 jmp .need_more
1696
1697 ;
1698 ; Get a fresh packet; expects fs -> pktbuf_seg and ds:si -> socket structure
1699 ;
1700 get_packet:
1701                 mov ax,ds
1702                 mov es,ax
1703         
1704 .packet_loop:
1705                 ; Start by ACKing the previous packet; this should cause the
1706                 ; next packet to be sent.
1707                 mov cx,PKT_RETRY
1708                 mov word [PktTimeout],PKT_TIMEOUT
1709
1710 .send_ack:      push cx                         ; <D> Retry count
1711
1712                 mov ax,[si+tftp_lastpkt]
1713                 call ack_packet                 ; Send ACK
1714
1715                 ; We used to test the error code here, but sometimes
1716                 ; PXE would return negative status even though we really
1717                 ; did send the ACK.  Now, just treat a failed send as
1718                 ; a normally lost packet, and let it time out in due
1719                 ; course of events.
1720
1721 .send_ok:       ; Now wait for packet.
1722                 mov dx,[BIOS_timer]             ; Get current time
1723
1724                 mov cx,[PktTimeout]
1725 .wait_data:     push cx                         ; <E> Timeout
1726                 push dx                         ; <F> Old time
1727
1728                 mov bx,[si+tftp_pktbuf]
1729                 mov [pxe_udp_read_pkt.buffer],bx
1730                 mov [pxe_udp_read_pkt.buffer+2],fs
1731                 mov [pxe_udp_read_pkt.buffersize],word PKTBUF_SIZE
1732                 mov eax,[si+tftp_remoteip]
1733                 mov [pxe_udp_read_pkt.sip],eax
1734                 mov eax,[MyIP]
1735                 mov [pxe_udp_read_pkt.dip],eax
1736                 mov ax,[si+tftp_remoteport]
1737                 mov [pxe_udp_read_pkt.rport],ax
1738                 mov ax,[si+tftp_localport]
1739                 mov [pxe_udp_read_pkt.lport],ax
1740                 mov di,pxe_udp_read_pkt
1741                 mov bx,PXENV_UDP_READ
1742                 push si                         ; <G>
1743                 call pxenv
1744                 pop si                          ; <G>
1745                 and ax,ax
1746                 jz .recv_ok
1747
1748                 ; No packet, or receive failure
1749                 mov dx,[BIOS_timer]
1750                 pop ax                          ; <F> Old time
1751                 pop cx                          ; <E> Timeout
1752                 cmp ax,dx                       ; Same time -> don't advance timeout
1753                 je .wait_data                   ; Same clock tick
1754                 loop .wait_data                 ; Decrease timeout
1755                 
1756                 pop cx                          ; <D> Didn't get any, send another ACK
1757                 shl word [PktTimeout],1         ; Exponential backoff
1758                 loop .send_ack
1759                 jmp kaboom                      ; Forget it...
1760
1761 .recv_ok:       pop dx                          ; <F>
1762                 pop cx                          ; <E>
1763
1764                 cmp word [pxe_udp_read_pkt.buffersize],byte 4
1765                 jb .wait_data                   ; Bad size for a DATA packet
1766
1767                 mov bx,[si+tftp_pktbuf]
1768                 cmp word [fs:bx],TFTP_DATA      ; Not a data packet?
1769                 jne .wait_data                  ; Then wait for something else
1770
1771                 mov ax,[si+tftp_lastpkt]
1772                 xchg ah,al                      ; Host byte order
1773                 inc ax                          ; Which packet are we waiting for?
1774                 xchg ah,al                      ; Network byte order
1775                 cmp [fs:bx+2],ax
1776                 je .right_packet
1777
1778                 ; Wrong packet, ACK the packet and then try again
1779                 ; This is presumably because the ACK got lost,
1780                 ; so the server just resent the previous packet
1781                 mov ax,[fs:bx+2]
1782                 call ack_packet
1783                 jmp .send_ok                    ; Reset timeout
1784
1785 .right_packet:  ; It's the packet we want.  We're also EOF if the size < blocksize
1786
1787                 pop cx                          ; <D> Don't need the retry count anymore
1788
1789                 mov [si+tftp_lastpkt],ax        ; Update last packet number
1790
1791                 movzx ecx,word [pxe_udp_read_pkt.buffersize]
1792                 sub cx,byte 4                   ; Skip TFTP header
1793
1794                 ; If this is a zero-length block, don't mess with the pointers,
1795                 ; since we may have just set up the previous block that way
1796                 jz .last_block
1797
1798                 ; Set pointer to data block
1799                 lea ax,[bx+4]                   ; Data past TFTP header
1800                 mov [si+tftp_dataptr],ax
1801
1802                 add [si+tftp_filepos],ecx
1803                 mov [si+tftp_bytesleft],cx
1804
1805                 cmp cx,[si+tftp_blksize]        ; Is it a full block?
1806                 jb .last_block                  ; If so, it's not EOF
1807
1808                 ; If we had the exact right number of bytes, always get
1809                 ; one more packet to get the (zero-byte) EOF packet and
1810                 ; close the socket.
1811                 mov eax,[si+tftp_filepos]
1812                 cmp [si+tftp_filesize],eax
1813                 je .packet_loop
1814
1815                 ret
1816
1817
1818 .last_block:    ; Last block - ACK packet immediately
1819                 mov ax,[fs:bx+2]
1820                 call ack_packet
1821
1822                 ; Make sure we know we are at end of file
1823                 mov eax,[si+tftp_filepos]
1824                 mov [si+tftp_filesize],eax
1825         
1826                 ret
1827
1828 ;
1829 ; ack_packet:
1830 ;
1831 ; Send ACK packet.  This is a common operation and so is worth canning.
1832 ;
1833 ; Entry:
1834 ;       SI      = TFTP block
1835 ;       AX      = Packet # to ack (network byte order)
1836 ; Exit:
1837 ;       ZF = 0 -> Error
1838 ;       All registers preserved
1839 ;
1840 ; This function uses the pxe_udp_write_pkt but not the packet_buf.
1841 ;
1842 ack_packet:
1843                 pushad
1844                 mov [ack_packet_buf+2],ax       ; Packet number to ack
1845                 mov ax,[si]
1846                 mov [pxe_udp_write_pkt.lport],ax
1847                 mov ax,[si+tftp_remoteport]
1848                 mov [pxe_udp_write_pkt.rport],ax
1849                 mov eax,[si+tftp_remoteip]
1850                 mov [pxe_udp_write_pkt.sip],eax
1851                 xor eax,[MyIP]
1852                 and eax,[Netmask]
1853                 jz .nogw
1854                 mov eax,[Gateway]
1855 .nogw:
1856                 mov [pxe_udp_write_pkt.gip],eax
1857                 mov [pxe_udp_write_pkt.buffer],word ack_packet_buf
1858                 mov [pxe_udp_write_pkt.buffersize], word 4
1859                 mov di,pxe_udp_write_pkt
1860                 mov bx,PXENV_UDP_WRITE
1861                 call pxenv
1862                 cmp ax,byte 0                   ; ZF = 1 if write OK
1863                 popad
1864                 ret
1865
1866 ;
1867 ; unload_pxe:
1868 ;
1869 ; This function unloads the PXE and UNDI stacks and unclaims
1870 ; the memory.
1871 ;
1872 unload_pxe:
1873                 test byte [KeepPXE],01h         ; Should we keep PXE around?
1874                 jnz reset_pxe
1875
1876                 push ds
1877                 push es
1878
1879                 mov ax,cs
1880                 mov ds,ax
1881                 mov es,ax
1882
1883                 mov si,new_api_unload
1884                 cmp byte [APIVer+1],2           ; Major API version >= 2?
1885                 jae .new_api
1886                 mov si,old_api_unload
1887 .new_api:
1888                 
1889 .call_loop:     xor ax,ax
1890                 lodsb
1891                 and ax,ax
1892                 jz .call_done
1893                 xchg bx,ax
1894                 mov di,pxe_unload_stack_pkt
1895                 push di
1896                 xor ax,ax
1897                 mov cx,pxe_unload_stack_pkt_len >> 1
1898                 rep stosw
1899                 pop di
1900                 call pxenv
1901                 jc .cant_free
1902                 mov ax,word [pxe_unload_stack_pkt.status]
1903                 cmp ax,PXENV_STATUS_SUCCESS
1904                 jne .cant_free
1905                 jmp .call_loop
1906
1907 .call_done:
1908 ;
1909 ; This isn't necessary anymore; we can use the memory area previously
1910 ; used by the PXE stack indefinitely, and the chainload code sets up
1911 ; a new stack independently.  Leave the source code in here for now,
1912 ; but expect to rip it out soonish.
1913 ;
1914 %if 0 ; USE_PXE_PROVIDED_STACK
1915                 ; We need to switch to our local stack here...
1916                 pusha
1917                 pushf
1918                 push gs
1919
1920                 mov si,sp
1921                 mov ax,ss
1922                 mov gs,ax
1923                 sub ax,[BaseStack+4]            ; Are we using the base stack
1924                 je .is_base_stack               ; (as opposed to the COMBOOT stack)?
1925
1926                 lgs si,[SavedSSSP]              ; COMBOOT stack
1927 .is_base_stack:
1928
1929                 mov cx,[InitStack]
1930                 mov di,StackBuf
1931                 mov [BaseStack],di
1932                 mov [BaseStack+4],es
1933                 sub cx,si
1934                 sub di,cx
1935                 mov [SavedSSSP],di              ; New SP
1936                 mov [SavedSSSP+2],es
1937                 gs rep movsb
1938
1939                 and ax,ax                       ; Remember which stack
1940                 jne .combootstack
1941
1942                 ; Update the base stack pointer since it's in use
1943                 lss sp,[SavedSSSP]
1944                 
1945 .combootstack:
1946                 pop gs
1947                 popf
1948                 popa
1949 %endif
1950                 mov bx,0FF00h
1951
1952                 mov dx,[RealBaseMem]
1953                 cmp dx,[BIOS_fbm]               ; Sanity check
1954                 jna .cant_free
1955                 inc bx
1956
1957                 ; Check that PXE actually unhooked the INT 1Ah chain
1958                 movzx eax,word [4*0x1a]
1959                 movzx ecx,word [4*0x1a+2]
1960                 shl ecx,4
1961                 add eax,ecx
1962                 shr eax,10
1963                 cmp ax,dx                       ; Not in range
1964                 jae .ok
1965                 cmp ax,[BIOS_fbm]
1966                 jae .cant_free
1967                 ; inc bx
1968
1969 .ok:
1970                 mov [BIOS_fbm],dx
1971 .pop_ret:
1972                 pop es
1973                 pop ds
1974                 ret
1975                 
1976 .cant_free:
1977                 mov si,cant_free_msg
1978                 call writestr
1979                 push ax
1980                 xchg bx,ax
1981                 call writehex4
1982                 mov al,'-'
1983                 call writechr
1984                 pop ax
1985                 call writehex4
1986                 mov al,'-'
1987                 call writechr
1988                 mov eax,[4*0x1a]
1989                 call writehex8
1990                 call crlf
1991                 jmp .pop_ret
1992
1993                 ; We want to keep PXE around, but still we should reset
1994                 ; it to the standard bootup configuration
1995 reset_pxe:
1996                 push es
1997                 push cs
1998                 pop es
1999                 mov bx,PXENV_UDP_CLOSE
2000                 mov di,pxe_udp_close_pkt
2001                 call pxenv
2002                 pop es
2003                 ret
2004
2005 ;
2006 ; gendotquad
2007 ;
2008 ; Take an IP address (in network byte order) in EAX and
2009 ; output a dotted quad string to ES:DI.
2010 ; DI points to terminal null at end of string on exit.
2011 ;
2012 gendotquad:
2013                 push eax
2014                 push cx
2015                 mov cx,4
2016 .genchar:
2017                 push eax
2018                 cmp al,10               ; < 10?
2019                 jb .lt10                ; If so, skip first 2 digits
2020
2021                 cmp al,100              ; < 100
2022                 jb .lt100               ; If so, skip first digit
2023
2024                 aam 100
2025                 ; Now AH = 100-digit; AL = remainder
2026                 add ah,'0'
2027                 mov [es:di],ah
2028                 inc di
2029
2030 .lt100:
2031                 aam 10
2032                 ; Now AH = 10-digit; AL = remainder
2033                 add ah,'0'
2034                 mov [es:di],ah          
2035                 inc di
2036
2037 .lt10:
2038                 add al,'0'
2039                 stosb
2040                 mov al,'.'
2041                 stosb
2042                 pop eax
2043                 ror eax,8       ; Move next char into LSB
2044                 loop .genchar
2045                 dec di
2046                 mov [es:di], byte 0
2047                 pop cx
2048                 pop eax
2049                 ret
2050
2051 ;
2052 ; parse_dhcp
2053 ;
2054 ; Parse a DHCP packet.  This includes dealing with "overloaded"
2055 ; option fields (see RFC 2132, section 9.3)
2056 ;
2057 ; This should fill in the following global variables, if the
2058 ; information is present:
2059 ;
2060 ; MyIP          - client IP address
2061 ; ServerIP      - boot server IP address
2062 ; Netmask       - network mask
2063 ; Gateway       - default gateway router IP
2064 ; BootFile      - boot file name
2065 ; DNSServers    - DNS server IPs
2066 ; LocalDomain   - Local domain name
2067 ;
2068 ; This assumes the DHCP packet is in "trackbuf" and the length
2069 ; of the packet in in CX on entry.
2070 ;
2071
2072 parse_dhcp:
2073                 mov byte [OverLoad],0           ; Assume no overload
2074                 mov eax, [trackbuf+bootp.yip]
2075                 and eax, eax
2076                 jz .noyip
2077                 cmp al,224                      ; Class D or higher -> bad
2078                 jae .noyip
2079                 mov [MyIP], eax
2080 .noyip:
2081                 mov eax, [trackbuf+bootp.sip]
2082                 and eax, eax
2083                 jz .nosip
2084                 cmp al,224                      ; Class D or higher -> bad
2085                 jae .nosip
2086                 mov [ServerIP], eax
2087 .nosip:
2088                 sub cx, bootp.options
2089                 jbe .nooptions
2090                 mov si, trackbuf+bootp.option_magic
2091                 lodsd
2092                 cmp eax, BOOTP_OPTION_MAGIC
2093                 jne .nooptions
2094                 call parse_dhcp_options
2095 .nooptions:
2096                 mov si, trackbuf+bootp.bootfile
2097                 test byte [OverLoad],1
2098                 jz .nofileoverload
2099                 mov cx,128
2100                 call parse_dhcp_options
2101                 jmp short .parsed_file
2102 .nofileoverload:
2103                 cmp byte [si], 0
2104                 jz .parsed_file                 ; No bootfile name
2105                 mov di,BootFile
2106                 mov cx,32
2107                 rep movsd
2108                 xor al,al
2109                 stosb                           ; Null-terminate
2110 .parsed_file:
2111                 mov si, trackbuf+bootp.sname
2112                 test byte [OverLoad],2
2113                 jz .nosnameoverload
2114                 mov cx,64
2115                 call parse_dhcp_options
2116 .nosnameoverload:
2117                 ret
2118
2119 ;
2120 ; Parse a sequence of DHCP options, pointed to by DS:SI; the field
2121 ; size is CX -- some DHCP servers leave option fields unterminated
2122 ; in violation of the spec.
2123 ;
2124 ; For parse_some_dhcp_options, DH contains the minimum value for
2125 ; the option to recognize -- this is used to restrict parsing to
2126 ; PXELINUX-specific options only.
2127 ;
2128 parse_dhcp_options:
2129                 xor dx,dx
2130
2131 parse_some_dhcp_options:
2132 .loop:
2133                 and cx,cx
2134                 jz .done
2135
2136                 lodsb
2137                 dec cx
2138                 jz .done        ; Last byte; must be PAD, END or malformed
2139                 cmp al, 0       ; PAD option
2140                 je .loop
2141                 cmp al,255      ; END option
2142                 je .done
2143
2144                 ; Anything else will have a length field
2145                 mov dl,al       ; DL <- option number
2146                 xor ax,ax
2147                 lodsb           ; AX <- option length
2148                 dec cx
2149                 sub cx,ax       ; Decrement bytes left counter
2150                 jb .done        ; Malformed option: length > field size
2151
2152                 cmp dl,dh       ; Is the option value valid?
2153                 jb .opt_done
2154
2155                 cmp dl,1        ; SUBNET MASK option
2156                 jne .not_subnet
2157                 mov ebx,[si]
2158                 mov [Netmask],ebx
2159                 jmp .opt_done
2160 .not_subnet:
2161
2162                 cmp dl,3        ; ROUTER option
2163                 jne .not_router
2164                 mov ebx,[si]
2165                 mov [Gateway],ebx
2166                 jmp .opt_done
2167 .not_router:
2168
2169                 cmp dl,6        ; DNS SERVERS option
2170                 jne .not_dns
2171                 pusha
2172                 mov cx,ax
2173                 shr cx,2
2174                 cmp cl,DNS_MAX_SERVERS
2175                 jna .oklen
2176                 mov cl,DNS_MAX_SERVERS
2177 .oklen:
2178                 mov di,DNSServers
2179                 rep movsd
2180                 mov [LastDNSServer],di
2181                 popa
2182                 jmp .opt_done
2183 .not_dns:
2184
2185                 cmp dl,15       ; DNS LOCAL DOMAIN option
2186                 jne .not_localdomain
2187                 pusha
2188                 mov bx,si
2189                 add bx,ax
2190                 xor ax,ax
2191                 xchg [bx],al    ; Zero-terminate option
2192                 mov di,LocalDomain
2193                 call dns_mangle ; Convert to DNS label set
2194                 mov [bx],al     ; Restore ending byte
2195                 popa
2196                 jmp .opt_done
2197 .not_localdomain:
2198
2199                 cmp dl,43       ; VENDOR ENCAPSULATED option
2200                 jne .not_vendor
2201                 pusha
2202                 mov dh,208      ; Only recognize PXELINUX options
2203                 mov cx,ax       ; Length of option = max bytes to parse
2204                 call parse_some_dhcp_options    ; Parse recursive structure
2205                 popa
2206                 jmp .opt_done
2207 .not_vendor:
2208
2209                 cmp dl,52       ; OPTION OVERLOAD option
2210                 jne .not_overload
2211                 mov bl,[si]
2212                 mov [OverLoad],bl
2213                 jmp .opt_done
2214 .not_overload:
2215
2216                 cmp dl,67       ; BOOTFILE NAME option
2217                 jne .not_bootfile
2218                 mov di,BootFile
2219                 jmp short .copyoption
2220 .done:
2221                 ret             ; This is here to make short jumps easier
2222 .not_bootfile:
2223
2224                 cmp dl,208      ; PXELINUX MAGIC option
2225                 jne .not_pl_magic
2226                 cmp al,4        ; Must have length == 4
2227                 jne .opt_done
2228                 cmp dword [si], htonl(0xF100747E)       ; Magic number
2229                 jne .opt_done
2230                 or byte [DHCPMagic], byte 1             ; Found magic #
2231                 jmp short .opt_done
2232 .not_pl_magic:
2233
2234                 cmp dl,209      ; PXELINUX CONFIGFILE option
2235                 jne .not_pl_config
2236                 mov di,ConfigName
2237                 or byte [DHCPMagic], byte 2     ; Got config file
2238                 jmp short .copyoption
2239 .not_pl_config:
2240
2241                 cmp dl,210      ; PXELINUX PATHPREFIX option
2242                 jne .not_pl_prefix
2243                 mov di,PathPrefix
2244                 or byte [DHCPMagic], byte 4     ; Got path prefix
2245                 jmp short .copyoption
2246 .not_pl_prefix:
2247
2248                 cmp dl,211      ; PXELINUX REBOOTTIME option
2249                 jne .not_pl_timeout
2250                 cmp al,4
2251                 jne .opt_done
2252                 mov ebx,[si]
2253                 xchg bl,bh      ; Convert to host byte order
2254                 rol ebx,16
2255                 xchg bl,bh
2256                 mov [RebootTime],ebx
2257                 or byte [DHCPMagic], byte 8     ; Got RebootTime
2258                 ; jmp short .opt_done
2259 .not_pl_timeout:
2260
2261                 ; Unknown option.  Skip to the next one.
2262 .opt_done:
2263                 add si,ax
2264 .opt_done_noskip:
2265                 jmp .loop
2266
2267                 ; Common code for copying an option verbatim
2268 .copyoption:
2269                 xchg cx,ax
2270                 rep movsb
2271                 xchg cx,ax      ; Now ax == 0
2272                 stosb           ; Null-terminate
2273                 jmp short .opt_done_noskip
2274
2275 ;
2276 ; genipopt
2277 ;
2278 ; Generate an ip=<client-ip>:<boot-server-ip>:<gw-ip>:<netmask>
2279 ; option into IPOption based on a DHCP packet in trackbuf.
2280 ; Assumes CS == DS == ES.
2281 ;
2282 genipopt:
2283                 pushad
2284                 mov di,IPOption
2285                 mov eax,'ip='
2286                 stosd
2287                 dec di
2288                 mov eax,[MyIP]
2289                 call gendotquad
2290                 mov al,':'
2291                 stosb
2292                 mov eax,[ServerIP]
2293                 call gendotquad
2294                 mov al,':'
2295                 stosb
2296                 mov eax,[Gateway]
2297                 call gendotquad
2298                 mov al,':'
2299                 stosb
2300                 mov eax,[Netmask]
2301                 call gendotquad ; Zero-terminates its output
2302                 sub di,IPOption
2303                 mov [IPOptionLen],di
2304                 popad
2305                 ret
2306
2307 ;
2308 ; Call the receive loop while idle.  This is done mostly so we can respond to
2309 ; ARP messages, but perhaps in the future this can be used to do network
2310 ; console.
2311 ;
2312 ; hpa sez: people using automatic control on the serial port get very
2313 ; unhappy if we poll for ARP too often (the PXE stack is pretty slow,
2314 ; typically.)  Therefore, only poll if at least 4 BIOS timer ticks have
2315 ; passed since the last poll, and reset this when a character is
2316 ; received (RESET_IDLE).
2317 ;
2318 reset_idle:
2319                 push ax
2320                 mov ax,[cs:BIOS_timer]
2321                 mov [cs:IdleTimer],ax
2322                 pop ax
2323                 ret
2324
2325 check_for_arp:
2326                 push ax
2327                 mov ax,[cs:BIOS_timer]
2328                 sub ax,[cs:IdleTimer]
2329                 cmp ax,4
2330                 pop ax
2331                 jae .need_poll
2332                 ret
2333 .need_poll:     pushad
2334                 push ds
2335                 push es
2336                 mov ax,cs
2337                 mov ds,ax
2338                 mov es,ax
2339                 mov di,packet_buf
2340                 mov [pxe_udp_read_pkt.status],al        ; 0
2341                 mov [pxe_udp_read_pkt.buffer],di
2342                 mov [pxe_udp_read_pkt.buffer+2],ds
2343                 mov word [pxe_udp_read_pkt.buffersize],packet_buf_size
2344                 mov eax,[MyIP]
2345                 mov [pxe_udp_read_pkt.dip],eax
2346                 mov word [pxe_udp_read_pkt.lport],htons(9)      ; discard port
2347                 mov di,pxe_udp_read_pkt
2348                 mov bx,PXENV_UDP_READ
2349                 call pxenv
2350                 ; Ignore result...
2351                 pop es
2352                 pop ds
2353                 popad
2354                 RESET_IDLE
2355                 ret
2356
2357 ; -----------------------------------------------------------------------------
2358 ;  Common modules
2359 ; -----------------------------------------------------------------------------
2360
2361 %include "getc.inc"             ; getc et al
2362 %include "conio.inc"            ; Console I/O
2363 %include "writestr.inc"         ; String output
2364 writestr        equ cwritestr
2365 %include "writehex.inc"         ; Hexadecimal output
2366 %include "parseconfig.inc"      ; High-level config file handling
2367 %include "parsecmd.inc"         ; Low-level config file handling
2368 %include "bcopy32.inc"          ; 32-bit bcopy
2369 %include "loadhigh.inc"         ; Load a file into high memory
2370 %include "font.inc"             ; VGA font stuff
2371 %include "graphics.inc"         ; VGA graphics
2372 %include "highmem.inc"          ; High memory sizing
2373 %include "strcpy.inc"           ; strcpy()
2374 %include "rawcon.inc"           ; Console I/O w/o using the console functions
2375 %include "dnsresolv.inc"        ; DNS resolver
2376
2377 ; -----------------------------------------------------------------------------
2378 ;  Begin data section
2379 ; -----------------------------------------------------------------------------
2380
2381                 section .data
2382
2383 hextbl_lower    db '0123456789abcdef'
2384 copyright_str   db ' Copyright (C) 1994-', year, ' H. Peter Anvin'
2385                 db CR, LF, 0
2386 boot_prompt     db 'boot: ', 0
2387 wipe_char       db BS, ' ', BS, 0
2388 err_notfound    db 'Could not find kernel image: ',0
2389 err_notkernel   db CR, LF, 'Invalid or corrupt kernel image.', CR, LF, 0
2390 err_noram       db 'It appears your computer has less than '
2391                 asciidec dosram_k
2392                 db 'K of low ("DOS")'
2393                 db CR, LF
2394                 db 'RAM.  Linux needs at least this amount to boot.  If you get'
2395                 db CR, LF
2396                 db 'this message in error, hold down the Ctrl key while'
2397                 db CR, LF
2398                 db 'booting, and I will take your word for it.', CR, LF, 0
2399 err_badcfg      db 'Unknown keyword in config file.', CR, LF, 0
2400 err_noparm      db 'Missing parameter in config file.', CR, LF, 0
2401 err_noinitrd    db CR, LF, 'Could not find ramdisk image: ', 0
2402 err_nohighmem   db 'Not enough memory to load specified kernel.', CR, LF, 0
2403 err_highload    db CR, LF, 'Kernel transfer failure.', CR, LF, 0
2404 err_oldkernel   db 'Cannot load a ramdisk with an old kernel image.'
2405                 db CR, LF, 0
2406 err_notdos      db ': attempted DOS system call', CR, LF, 0
2407 err_comlarge    db 'COMBOOT image too large.', CR, LF, 0
2408 err_bssimage    db 'BSS images not supported.', CR, LF, 0
2409 err_a20         db CR, LF, 'A20 gate not responding!', CR, LF, 0
2410 err_bootfailed  db CR, LF, 'Boot failed: press a key to retry, or wait for reset...', CR, LF, 0
2411 bailmsg         equ err_bootfailed
2412 err_nopxe       db "No !PXE or PXENV+ API found; we're dead...", CR, LF, 0
2413 err_pxefailed   db 'PXE API call failed, error ', 0
2414 err_udpinit     db 'Failed to initialize UDP stack', CR, LF, 0
2415 err_oldtftp     db 'TFTP server does not support the tsize option', CR, LF, 0
2416 found_pxenv     db 'Found PXENV+ structure', CR, LF, 0
2417 using_pxenv_msg db 'Old PXE API detected, using PXENV+ structure', CR, LF, 0
2418 apiver_str      db 'PXE API version is ',0
2419 pxeentry_msg    db 'PXE entry point found (we hope) at ', 0
2420 pxenventry_msg  db 'PXENV entry point found (we hope) at ', 0
2421 trymempxe_msg   db 'Scanning memory for !PXE structure... ', 0
2422 trymempxenv_msg db 'Scanning memory for PXENV+ structure... ', 0
2423 undi_data_msg     db 'UNDI data segment at:   ',0
2424 undi_data_len_msg db 'UNDI data segment size: ',0 
2425 undi_code_msg     db 'UNDI code segment at:   ',0
2426 undi_code_len_msg db 'UNDI code segment size: ',0 
2427 cant_free_msg   db 'Failed to free base memory, error ', 0
2428 notfound_msg    db 'not found', CR, LF, 0
2429 myipaddr_msg    db 'My IP address seems to be ',0
2430 tftpprefix_msg  db 'TFTP prefix: ', 0
2431 localboot_msg   db 'Booting from local disk...', CR, LF, 0
2432 cmdline_msg     db 'Command line: ', CR, LF, 0
2433 ready_msg       db 'Ready.', CR, LF, 0
2434 trying_msg      db 'Trying to load: ', 0
2435 crlfloading_msg db CR, LF                       ; Fall through
2436 loading_msg     db 'Loading ', 0
2437 dotdot_msg      db '.'
2438 dot_msg         db '.', 0
2439 fourbs_msg      db BS, BS, BS, BS, 0
2440 aborted_msg     db ' aborted.'                  ; Fall through to crlf_msg!
2441 crlf_msg        db CR, LF
2442 null_msg        db 0
2443 crff_msg        db CR, FF, 0
2444 default_str     db 'default', 0
2445 default_len     equ ($-default_str)
2446 syslinux_banner db CR, LF, 'PXELINUX ', version_str, ' ', date, ' ', 0
2447 cfgprefix       db 'pxelinux.cfg/'              ; No final null!
2448 cfgprefix_len   equ ($-cfgprefix)
2449
2450 ;
2451 ; Command line options we'd like to take a look at
2452 ;
2453 ; mem= and vga= are handled as normal 32-bit integer values
2454 initrd_cmd      db 'initrd='
2455 initrd_cmd_len  equ $-initrd_cmd
2456
2457 ; This one we make ourselves
2458 bootif_str      db 'BOOTIF='
2459 bootif_str_len  equ $-bootif_str
2460 ;
2461 ; Config file keyword table
2462 ;
2463 %include "keywords.inc"
2464
2465 ;
2466 ; Extensions to search for (in *forward* order).
2467 ; (.bs and .bss are disabled for PXELINUX, since they are not supported)
2468 ;
2469                 align 4, db 0
2470 exten_table:    db '.cbt'               ; COMBOOT (specific)
2471                 db '.0', 0, 0           ; PXE bootstrap program
2472                 db '.com'               ; COMBOOT (same as DOS)
2473                 db '.c32'               ; COM32
2474 exten_table_end:
2475                 dd 0, 0                 ; Need 8 null bytes here
2476
2477 ;
2478 ; PXE unload sequences
2479 ;
2480 new_api_unload:
2481                 db PXENV_UDP_CLOSE
2482                 db PXENV_UNDI_SHUTDOWN
2483                 db PXENV_UNLOAD_STACK
2484                 db PXENV_STOP_UNDI
2485                 db 0
2486 old_api_unload:
2487                 db PXENV_UDP_CLOSE
2488                 db PXENV_UNDI_SHUTDOWN
2489                 db PXENV_UNLOAD_STACK
2490                 db PXENV_UNDI_CLEANUP
2491                 db 0
2492
2493 ;
2494 ; PXE query packets partially filled in
2495 ;
2496 pxe_bootp_query_pkt_2:
2497 .status:        dw 0                    ; Status
2498 .packettype:    dw 2                    ; DHCPACK packet
2499 .buffersize:    dw trackbufsize         ; Packet size
2500 .buffer:        dw trackbuf, 0          ; seg:off of buffer
2501 .bufferlimit:   dw trackbufsize         ; Unused
2502
2503 pxe_bootp_query_pkt_3:
2504 .status:        dw 0                    ; Status
2505 .packettype:    dw 3                    ; Boot server packet
2506 .buffersize:    dw trackbufsize         ; Packet size
2507 .buffer:        dw trackbuf, 0          ; seg:off of buffer
2508 .bufferlimit:   dw trackbufsize         ; Unused
2509
2510 pxe_bootp_size_query_pkt:
2511 .status:        dw 0                    ; Status
2512 .packettype:    dw 2                    ; DHCPACK packet
2513 .buffersize:    dw 0                    ; Packet size
2514 .buffer:        dw 0, 0                 ; seg:off of buffer
2515 .bufferlimit:   dw 0                    ; Unused
2516
2517 pxe_udp_open_pkt:
2518 .status:        dw 0                    ; Status
2519 .sip:           dd 0                    ; Source (our) IP
2520
2521 pxe_udp_close_pkt:
2522 .status:        dw 0                    ; Status
2523
2524 pxe_udp_write_pkt:
2525 .status:        dw 0                    ; Status
2526 .sip:           dd 0                    ; Server IP
2527 .gip:           dd 0                    ; Gateway IP
2528 .lport:         dw 0                    ; Local port
2529 .rport:         dw 0                    ; Remote port
2530 .buffersize:    dw 0                    ; Size of packet
2531 .buffer:        dw 0, 0                 ; seg:off of buffer
2532
2533 pxe_udp_read_pkt:
2534 .status:        dw 0                    ; Status
2535 .sip:           dd 0                    ; Source IP
2536 .dip:           dd 0                    ; Destination (our) IP
2537 .rport:         dw 0                    ; Remote port
2538 .lport:         dw 0                    ; Local port
2539 .buffersize:    dw 0                    ; Max packet size
2540 .buffer:        dw 0, 0                 ; seg:off of buffer
2541
2542 ;
2543 ; Misc initialized (data) variables
2544 ;
2545                 alignb 4, db 0
2546 BaseStack       dd StackBuf             ; SS:ESP of base stack
2547 NextSocket      dw 49152                ; Counter for allocating socket numbers
2548 KeepPXE         db 0                    ; Should PXE be kept around?
2549
2550 ;
2551 ; TFTP commands
2552 ;
2553 tftp_tail       db 'octet', 0                           ; Octet mode
2554 tsize_str       db 'tsize' ,0                           ; Request size
2555 tsize_len       equ ($-tsize_str)
2556                 db '0', 0
2557 blksize_str     db 'blksize', 0                         ; Request large blocks
2558 blksize_len     equ ($-blksize_str)
2559                 asciidec TFTP_LARGEBLK
2560                 db 0
2561 tftp_tail_len   equ ($-tftp_tail)
2562
2563                 alignb 2, db 0
2564 ;
2565 ; Options negotiation parsing table (string pointer, string len, offset
2566 ; into socket structure)
2567 ;
2568 tftp_opt_table:
2569                 dw tsize_str, tsize_len, tftp_filesize
2570                 dw blksize_str, blksize_len, tftp_blksize
2571 tftp_opts       equ ($-tftp_opt_table)/6
2572
2573 ;
2574 ; Error packet to return on options negotiation error
2575 ;
2576 tftp_opt_err    dw TFTP_ERROR                           ; ERROR packet
2577                 dw TFTP_EOPTNEG                         ; ERROR 8: bad options
2578                 db 'tsize option required', 0           ; Error message
2579 tftp_opt_err_len equ ($-tftp_opt_err)
2580
2581                 alignb 4, db 0
2582 ack_packet_buf: dw TFTP_ACK, 0                          ; TFTP ACK packet
2583
2584 ;
2585 ; IP information (initialized to "unknown" values)
2586 MyIP            dd 0                    ; My IP address
2587 ServerIP        dd 0                    ; IP address of boot server
2588 Netmask         dd 0                    ; Netmask of this subnet
2589 Gateway         dd 0                    ; Default router
2590 ServerPort      dw TFTP_PORT            ; TFTP server port
2591
2592 ;
2593 ; Variables that are uninitialized in SYSLINUX but initialized here
2594 ;
2595                 alignb 4, db 0
2596 BufSafe         dw trackbufsize/TFTP_BLOCKSIZE  ; Clusters we can load into trackbuf
2597 BufSafeSec      dw trackbufsize/512     ; = how many sectors?
2598 BufSafeBytes    dw trackbufsize         ; = how many bytes?
2599 EndOfGetCBuf    dw getcbuf+trackbufsize ; = getcbuf+BufSafeBytes
2600 %ifndef DEPEND
2601 %if ( trackbufsize % TFTP_BLOCKSIZE ) != 0
2602 %error trackbufsize must be a multiple of TFTP_BLOCKSIZE
2603 %endif
2604 %endif
2605 IPAppend        db 0                    ; Default IPAPPEND option
2606 DHCPMagic       db 0                    ; DHCP site-specific option info