Document PXELINUX timeout fix
[syslinux.git] / dnsresolv.inc
blob8a042bd93e55ee4bd2d775fb53026c5cc530c757
1 ; -*- fundamental -*-
2 ; -----------------------------------------------------------------------
4 ;   Copyright 2004-2005 H. Peter Anvin - All Rights Reserved
6 ;   This program is free software; you can redistribute it and/or modify
7 ;   it under the terms of the GNU General Public License as published by
8 ;   the Free Software Foundation, Inc., 53 Temple Place Ste 330,
9 ;   Bostom MA 02111-1307, USA; either version 2 of the License, or
10 ;   (at your option) any later version; incorporated herein by reference.
12 ; -----------------------------------------------------------------------
13 ; $Id$
16 ; dnsresolv.inc
18 ; Very simple DNS resolver (assumes recursion-enabled DNS server;
19 ; this should be the normal thing for client-serving DNS servers.)
22 DNS_PORT        equ htons(53)           ; Default DNS port
23 DNS_MAX_PACKET  equ 512                 ; Defined by protocol
24 ; TFTP uses the range 49152-57343
25 DNS_LOCAL_PORT  equ htons(60053)        ; All local DNS queries come from this port #
26 DNS_MAX_SERVERS equ 4                   ; Max no of DNS servers
28                 section .text
31 ; Turn a string in DS:SI into a DNS "label set" in ES:DI.
32 ; On return, DI points to the first byte after the label set,
33 ; and SI to the terminating byte.
35 ; On return, DX contains the number of dots encountered.
37 dns_mangle:
38                 push ax
39                 push bx
40                 xor dx,dx
41 .isdot:
42                 inc dx
43                 xor al,al
44                 mov bx,di
45                 stosb
46 .getbyte:
47                 lodsb
48                 and al,al
49                 jz .endstring
50                 cmp al,':'
51                 jz .endstring
52                 cmp al,'.'
53                 je .isdot
54                 inc byte [es:bx]
55                 stosb
56                 jmp .getbyte
57 .endstring:
58                 dec si
59                 dec dx                  ; We always counted one high
60                 cmp byte [es:bx],0
61                 jz .done
62                 xor al,al
63                 stosb
64 .done:
65                 pop bx
66                 pop ax
67                 ret
70 ; Compare two sets of DNS labels, in DS:SI and ES:DI; the one in SI
71 ; is allowed pointers relative to a packet in DNSRecvBuf.
73 ; Assumes DS == ES.  ZF = 1 if same; no registers changed.
74 ; (Note: change reference to [di] to [es:di] to remove DS == ES assumption)
76 dns_compare:
77                 pusha
78 %if 0
80 .label:
81                 lodsb
82                 cmp al,0C0h
83                 jb .noptr
84                 and al,03Fh                     ; Get pointer value
85                 mov ah,al                       ; ... in network byte order!
86                 lodsb
87                 mov si,DNSRecvBuf
88                 add si,ax
89                 jmp .label
90 .noptr:
91                 cmp al,[di]
92                 jne .done                       ; Mismatch
93                 inc di
94                 movzx cx,al                     ; End label?
95                 and cx,cx                       ; ZF = 1 if match
96                 jz .done
98                 ; We have a string of bytes that need to match now
99                 repe cmpsb
100                 je .label
102 .done:
103 %else
104                 xor ax,ax
105 %endif
106                 popa
107                 ret
110 ; Skip past a DNS label set in DS:SI.
112 dns_skiplabel:
113                 push ax
114                 xor ax,ax                       ; AH == 0
115 .loop:
116                 lodsb
117                 cmp al,0C0h                     ; Pointer?
118                 jae .ptr
119                 and al,al
120                 jz .done
121                 add si,ax
122                 jmp .loop
123 .ptr:
124                 inc si                          ; Pointer is two bytes
125 .done:
126                 pop ax
127                 ret
129                 ; DNS header format
130                 struc dnshdr
131 .id:            resw 1
132 .flags:         resw 1
133 .qdcount:       resw 1
134 .ancount:       resw 1
135 .nscount:       resw 1
136 .arcount:       resw 1
137                 endstruc
139                 ; DNS query
140                 struc dnsquery
141 .qtype:         resw 1
142 .qclass:        resw 1
143                 endstruc
145                 ; DNS RR
146                 struc dnsrr
147 .type:          resw 1
148 .class:         resw 1
149 .ttl:           resd 1
150 .rdlength:      resw 1
151 .rdata:         equ $
152                 endstruc
154                 section .latebss
155                 alignb 2
156 DNSSendBuf      resb DNS_MAX_PACKET
157 DNSRecvBuf      resb DNS_MAX_PACKET
158 LocalDomain     resb 256                ; Max possible length
159 DNSServers      resd DNS_MAX_SERVERS
161                 section .data
162 pxe_udp_write_pkt_dns:
163 .status:        dw 0                    ; Status
164 .sip:           dd 0                    ; Server IP
165 .gip:           dd 0                    ; Gateway IP
166 .lport:         dw DNS_LOCAL_PORT       ; Local port
167 .rport:         dw DNS_PORT             ; Remote port
168 .buffersize:    dw 0                    ; Size of packet
169 .buffer:        dw DNSSendBuf, 0        ; off, seg of buffer
171 pxe_udp_read_pkt_dns:
172 .status:        dw 0                    ; Status
173 .sip:           dd 0                    ; Source IP
174 .dip:           dd 0                    ; Destination (our) IP
175 .rport:         dw DNS_PORT             ; Remote port
176 .lport:         dw DNS_LOCAL_PORT       ; Local port
177 .buffersize:    dw DNS_MAX_PACKET       ; Max packet size
178 .buffer:        dw DNSRecvBuf, 0        ; off, seg of buffer
180 LastDNSServer   dw DNSServers
182 ; Actual resolver function
183 ; Points to a null-terminated or :-terminated string in DS:SI
184 ; and returns the name in EAX if it exists and can be found.
185 ; If EAX = 0 on exit, the lookup failed.
187                 section .text
188 dns_resolv:
189                 push ds
190                 push es
191                 push di
192                 push cx
193                 push dx
195                 push cs
196                 pop es                  ; ES <- CS
198                 ; First, build query packet
199                 mov di,DNSSendBuf+dnshdr.flags
200                 inc word [es:di-2]      ; New query ID
201                 mov ax,htons(0100h)     ; Recursion requested
202                 stosw
203                 mov ax,htons(1)         ; One question
204                 stosw
205                 xor ax,ax               ; No answers, NS or ARs
206                 stosw
207                 stosw
208                 stosw
210                 call dns_mangle         ; Convert name to DNS labels
212                 push cs                 ; DS <- CS
213                 pop ds
215                 push si                 ; Save pointer to after DNS string
217                 ; Initialize...
218                 mov eax,[MyIP]
219                 mov [pxe_udp_read_pkt_dns.dip],eax
221                 and dx,dx
222                 jnz .fqdn               ; If we have dots, assume it's FQDN
223                 dec di                  ; Remove final null
224                 mov si,LocalDomain
225                 call strcpy             ; Uncompressed DNS label set so it ends in null
226 .fqdn:
228                 mov ax,htons(1)
229                 stosw                   ; QTYPE  = 1 = A
230                 stosw                   ; QCLASS = 1 = IN
232                 sub di,DNSSendBuf
233                 mov [pxe_udp_write_pkt_dns.buffersize],di
235                 ; Now, send it to the nameserver(s)
236                 ; Outer loop: exponential backoff
237                 ; Inner loop: scan the various DNS servers
239                 mov dx,PKT_TIMEOUT
240                 mov cx,PKT_RETRY
241 .backoff:
242                 mov si,DNSServers
243 .servers:
244                 cmp si,[LastDNSServer]
245                 jb .moreservers
247 .nomoreservers:
248                 add dx,dx                       ; Exponential backoff
249                 loop .backoff
251                 xor eax,eax                     ; Nothing...
252 .done:
253                 pop si
254                 pop dx
255                 pop cx
256                 pop di
257                 pop es
258                 pop ds
259                 ret
261 .moreservers:
262                 lodsd                           ; EAX <- next server
263                 push si
264                 push cx
265                 push dx
267                 mov word [pxe_udp_write_pkt_dns.status],0
269                 mov [pxe_udp_write_pkt_dns.sip],eax
270                 mov [pxe_udp_read_pkt_dns.sip],eax
271                 xor eax,[MyIP]
272                 and eax,[Netmask]
273                 jz .nogw
274                 mov eax,[Gateway]
275 .nogw:
276                 mov [pxe_udp_write_pkt_dns.gip],eax
278                 mov di,pxe_udp_write_pkt_dns
279                 mov bx,PXENV_UDP_WRITE
280                 call pxenv
281                 jc .timeout                             ; Treat failed transmit as timeout
282                 cmp word [pxe_udp_write_pkt_dns.status],0
283                 jne .timeout
285                 mov cx,[BIOS_timer]
286 .waitrecv:
287                 mov ax,[BIOS_timer]
288                 sub ax,cx
289                 cmp ax,dx
290                 jae .timeout
292                 mov word [pxe_udp_read_pkt_dns.status],0
293                 mov word [pxe_udp_read_pkt_dns.buffersize],DNS_MAX_PACKET
294                 mov di,pxe_udp_read_pkt_dns
295                 mov bx,PXENV_UDP_READ
296                 call pxenv
297                 and ax,ax
298                 jnz .waitrecv
299                 cmp [pxe_udp_read_pkt_dns.status],ax
300                 jnz .waitrecv
302                 ; Got a packet, deal with it...
303                 mov si,DNSRecvBuf
304                 lodsw
305                 cmp ax,[DNSSendBuf]             ; ID
306                 jne .waitrecv                   ; Not ours
308                 lodsw                           ; flags
309                 xor al,80h                      ; Query#/Answer bit
310                 test ax,htons(0F80Fh)
311                 jnz .badness
313                 lodsw
314                 xchg ah,al                      ; ntohs
315                 mov cx,ax                       ; Questions echoed
316                 lodsw
317                 xchg ah,al                      ; ntohs
318                 push ax                         ; Replies
319                 lodsw                           ; NS records
320                 lodsw                           ; Authority records
322                 jcxz .qskipped
323 .skipq:
324                 call dns_skiplabel              ; Skip name
325                 add si,4                        ; Skip question trailer
326                 loop .skipq
328 .qskipped:
329                 pop cx                          ; Number of replies
330                 jcxz .badness
332 .parseanswer:
333                 mov di,DNSSendBuf+dnshdr_size
334                 call dns_compare
335                 pushf
336                 call dns_skiplabel
337                 mov ax,[si+8]                   ; RDLENGTH
338                 xchg ah,al                      ; ntohs
339                 popf
340                 jnz .notsame
341                 cmp dword [si],htons(1)*0x10001 ; TYPE = A, CLASS = IN?
342                 jne .notsame
343                 cmp ax,4                        ; RDLENGTH = 4?
344                 jne .notsame
345                 ;
346                 ; We hit paydirt here...
347                 ;
348                 mov eax,[si+10]
349 .gotresult:
350                 add sp,6                        ; Drop timeout information
351                 jmp .done
353 .notsame:
354                 add si,10
355                 add si,ax
356                 loop .parseanswer
358 .badness:
359                 ; We got back no data from this server.  Unfortunately, for a recursive,
360                 ; non-authoritative query there is no such thing as an NXDOMAIN reply,
361                 ; which technically means we can't draw any conclusions.  However,
362                 ; in practice that means the domain doesn't exist.  If this turns out
363                 ; to be a problem, we may want to add code to go through all the servers
364                 ; before giving up.
366                 ; If the DNS server wasn't capable of recursion, and isn't capable
367                 ; of giving us an authoritative reply (i.e. neither AA or RA set),
368                 ; then at least try a different setver...
369                 test word [DNSRecvBuf+dnshdr.flags],htons(0480h)
370                 jz .timeout
372                 xor eax,eax
373                 jmp .gotresult
375 .timeout:
376                 pop dx
377                 pop cx
378                 pop si
379                 jmp .servers