Adding upstream version 3.86+dfsg.
[syslinux-debian/hramrach.git] / core / dnsresolv.inc
blobc2c429cbeb5b91283cdbaa21f4edb20eb71158d0
1 ; -*- fundamental -*-
2 ; -----------------------------------------------------------------------
4 ;   Copyright 2004-2008 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 ; -----------------------------------------------------------------------
15 ; dnsresolv.inc
17 ; Very simple DNS resolver (assumes recursion-enabled DNS server;
18 ; this should be the normal thing for client-serving DNS servers.)
21 DNS_PORT        equ htons(53)           ; Default DNS port
22 DNS_MAX_PACKET  equ 512                 ; Defined by protocol
23 ; TFTP uses the range 49152-57343
24 DNS_LOCAL_PORT  equ htons(60053)        ; All local DNS queries come from this port #
25 DNS_MAX_SERVERS equ 4                   ; Max no of DNS servers
27                 section .text
30 ; Turn a string in DS:SI into a DNS "label set" in ES:DI.
31 ; On return, DI points to the first byte after the label set,
32 ; and SI to the terminating byte.
34 ; On return, DX contains the number of dots encountered.
36 dns_mangle:
37                 push ax
38                 push bx
39                 xor dx,dx
40 .isdot:
41                 inc dx
42                 xor al,al
43                 mov bx,di
44                 stosb
45 .getbyte:
46                 lodsb
47                 and al,al
48                 jz .endstring
49                 cmp al,':'
50                 jz .endstring
51                 cmp al,'.'
52                 je .isdot
53                 inc byte [es:bx]
54                 stosb
55                 jmp .getbyte
56 .endstring:
57                 dec si
58                 dec dx                  ; We always counted one high
59                 cmp byte [es:bx],0
60                 jz .done
61                 xor al,al
62                 stosb
63 .done:
64                 pop bx
65                 pop ax
66                 ret
69 ; Compare two sets of DNS labels, in DS:SI and ES:DI; the one in SI
70 ; is allowed pointers relative to a packet in DNSRecvBuf.
72 ; Assumes DS == ES.  ZF = 1 if same; no registers changed.
73 ; (Note: change reference to [di] to [es:di] to remove DS == ES assumption)
75 dns_compare:
76                 pusha
77 %if 0
79 .label:
80                 lodsb
81                 cmp al,0C0h
82                 jb .noptr
83                 and al,03Fh                     ; Get pointer value
84                 mov ah,al                       ; ... in network byte order!
85                 lodsb
86                 mov si,DNSRecvBuf
87                 add si,ax
88                 jmp .label
89 .noptr:
90                 cmp al,[di]
91                 jne .done                       ; Mismatch
92                 inc di
93                 movzx cx,al                     ; End label?
94                 and cx,cx                       ; ZF = 1 if match
95                 jz .done
97                 ; We have a string of bytes that need to match now
98                 repe cmpsb
99                 je .label
101 .done:
102 %else
103                 xor ax,ax
104 %endif
105                 popa
106                 ret
109 ; Skip past a DNS label set in DS:SI.
111 dns_skiplabel:
112                 push ax
113                 xor ax,ax                       ; AH == 0
114 .loop:
115                 lodsb
116                 cmp al,0C0h                     ; Pointer?
117                 jae .ptr
118                 and al,al
119                 jz .done
120                 add si,ax
121                 jmp .loop
122 .ptr:
123                 inc si                          ; Pointer is two bytes
124 .done:
125                 pop ax
126                 ret
128                 ; DNS header format
129                 struc dnshdr
130 .id:            resw 1
131 .flags:         resw 1
132 .qdcount:       resw 1
133 .ancount:       resw 1
134 .nscount:       resw 1
135 .arcount:       resw 1
136                 endstruc
138                 ; DNS query
139                 struc dnsquery
140 .qtype:         resw 1
141 .qclass:        resw 1
142                 endstruc
144                 ; DNS RR
145                 struc dnsrr
146 .type:          resw 1
147 .class:         resw 1
148 .ttl:           resd 1
149 .rdlength:      resw 1
150 .rdata:         equ $
151                 endstruc
153                 section .bss2
154                 alignb 2
155 DNSSendBuf      resb DNS_MAX_PACKET
156 DNSRecvBuf      resb DNS_MAX_PACKET
157 LocalDomain     resb 256                ; Max possible length
158 DNSServers      resd DNS_MAX_SERVERS
160                 section .data
161 pxe_udp_write_pkt_dns:
162 .status:        dw 0                    ; Status
163 .sip:           dd 0                    ; Server IP
164 .gip:           dd 0                    ; Gateway IP
165 .lport:         dw DNS_LOCAL_PORT       ; Local port
166 .rport:         dw DNS_PORT             ; Remote port
167 .buffersize:    dw 0                    ; Size of packet
168 .buffer:        dw DNSSendBuf, 0        ; off, seg of buffer
170 pxe_udp_read_pkt_dns:
171 .status:        dw 0                    ; Status
172 .sip:           dd 0                    ; Source IP
173 .dip:           dd 0                    ; Destination (our) IP
174 .rport:         dw DNS_PORT             ; Remote port
175 .lport:         dw DNS_LOCAL_PORT       ; Local port
176 .buffersize:    dw DNS_MAX_PACKET       ; Max packet size
177 .buffer:        dw DNSRecvBuf, 0        ; off, seg of buffer
179 LastDNSServer   dw DNSServers
181 ; Actual resolver function
182 ; Points to a null-terminated or :-terminated string in DS:SI
183 ; and returns the name in EAX if it exists and can be found.
184 ; If EAX = 0 on exit, the lookup failed.
186 ; No segment assumptions permitted.
188                 section .text
189 dns_resolv:
190                 push ds
191                 push es
192                 push di
193                 push bx
194                 push cx
195                 push dx
197                 push cs
198                 pop es                  ; ES <- CS
200                 ; First, build query packet
201                 mov di,DNSSendBuf+dnshdr.flags
202                 inc word [es:di-2]      ; New query ID
203                 mov ax,htons(0100h)     ; Recursion requested
204                 stosw
205                 mov ax,htons(1)         ; One question
206                 stosw
207                 xor ax,ax               ; No answers, NS or ARs
208                 stosw
209                 stosw
210                 stosw
212                 call dns_mangle         ; Convert name to DNS labels
214                 push cs                 ; DS <- CS
215                 pop ds
217                 push si                 ; Save pointer to after DNS string
219                 ; Initialize...
220                 mov eax,[MyIP]
221                 mov [pxe_udp_read_pkt_dns.dip],eax
223                 and dx,dx
224                 jnz .fqdn               ; If we have dots, assume it's FQDN
225                 dec di                  ; Remove final null
226                 mov si,LocalDomain
227                 call strcpy             ; Uncompressed DNS label set so it ends in null
228 .fqdn:
230                 mov ax,htons(1)
231                 stosw                   ; QTYPE  = 1 = A
232                 stosw                   ; QCLASS = 1 = IN
234                 sub di,DNSSendBuf
235                 mov [pxe_udp_write_pkt_dns.buffersize],di
237                 ; Now, send it to the nameserver(s)
238                 ; Outer loop: exponential backoff
239                 ; Inner loop: scan the various DNS servers
241                 mov bx,TimeoutTable
242 .backoff:
243                 movzx dx,byte [bx]
244                 mov si,DNSServers
245 .servers:
246                 cmp si,[LastDNSServer]
247                 jb .moreservers
249 .nomoreservers:
250                 inc bx
251                 cmp bx,TimeoutTableEnd
252                 jb .backoff
254                 xor eax,eax                     ; Nothing...
255 .done:
256                 pop si
257                 pop dx
258                 pop cx
259                 pop bx
260                 pop di
261                 pop es
262                 pop ds
263                 ret
265 .moreservers:
266                 lodsd                           ; EAX <- next server
267                 push si
268                 push bx
269                 push cx
270                 push dx
272                 mov word [pxe_udp_write_pkt_dns.status],0
274                 mov [pxe_udp_write_pkt_dns.sip],eax
275                 mov [pxe_udp_read_pkt_dns.sip],eax
276                 xor eax,[MyIP]
277                 and eax,[Netmask]
278                 jz .nogw
279                 mov eax,[Gateway]
280 .nogw:
281                 mov [pxe_udp_write_pkt_dns.gip],eax
283                 mov di,pxe_udp_write_pkt_dns
284                 mov bx,PXENV_UDP_WRITE
285                 call pxenv
286                 jc .timeout                             ; Treat failed transmit as timeout
287                 cmp word [pxe_udp_write_pkt_dns.status],0
288                 jne .timeout
290                 mov cx,[BIOS_timer]
291 .waitrecv:
292                 mov ax,[BIOS_timer]
293                 sub ax,cx
294                 cmp ax,dx
295                 jae .timeout
297                 mov word [pxe_udp_read_pkt_dns.status],0
298                 mov word [pxe_udp_read_pkt_dns.buffersize],DNS_MAX_PACKET
299                 mov di,pxe_udp_read_pkt_dns
300                 mov bx,PXENV_UDP_READ
301                 call pxenv
302                 and ax,ax
303                 jnz .waitrecv
304                 cmp [pxe_udp_read_pkt_dns.status],ax
305                 jnz .waitrecv
307                 ; Got a packet, deal with it...
308                 mov si,DNSRecvBuf
309                 lodsw
310                 cmp ax,[DNSSendBuf]             ; ID
311                 jne .waitrecv                   ; Not ours
313                 lodsw                           ; flags
314                 xor al,80h                      ; Query#/Answer bit
315                 test ax,htons(0F80Fh)
316                 jnz .badness
318                 lodsw
319                 xchg ah,al                      ; ntohs
320                 mov cx,ax                       ; Questions echoed
321                 lodsw
322                 xchg ah,al                      ; ntohs
323                 push ax                         ; Replies
324                 lodsw                           ; NS records
325                 lodsw                           ; Authority records
327                 jcxz .qskipped
328 .skipq:
329                 call dns_skiplabel              ; Skip name
330                 add si,4                        ; Skip question trailer
331                 loop .skipq
333 .qskipped:
334                 pop cx                          ; Number of replies
335                 jcxz .badness
337 .parseanswer:
338                 mov di,DNSSendBuf+dnshdr_size
339                 call dns_compare
340                 pushf
341                 call dns_skiplabel
342                 mov ax,[si+8]                   ; RDLENGTH
343                 xchg ah,al                      ; ntohs
344                 popf
345                 jnz .notsame
346                 cmp dword [si],htons(1)*0x10001 ; TYPE = A, CLASS = IN?
347                 jne .notsame
348                 cmp ax,4                        ; RDLENGTH = 4?
349                 jne .notsame
350                 ;
351                 ; We hit paydirt here...
352                 ;
353                 mov eax,[si+10]
354 .gotresult:
355                 add sp,8                        ; Drop timeout information
356                 jmp .done
358 .notsame:
359                 add si,10
360                 add si,ax
361                 loop .parseanswer
363 .badness:
364                 ; We got back no data from this server.
365                 ; Unfortunately, for a recursive, non-authoritative
366                 ; query there is no such thing as an NXDOMAIN reply,
367                 ; which technically means we can't draw any
368                 ; conclusions.  However, in practice that means the
369                 ; domain doesn't exist.  If this turns out to be a
370                 ; problem, we may want to add code to go through all
371                 ; the servers before giving up.
373                 ; If the DNS server wasn't capable of recursion, and
374                 ; isn't capable of giving us an authoritative reply
375                 ; (i.e. neither AA or RA set), then at least try a
376                 ; different setver...
378                 test word [DNSRecvBuf+dnshdr.flags],htons(0480h)
379                 jz .timeout
381                 xor eax,eax
382                 jmp .gotresult
384 .timeout:
385                 pop dx
386                 pop cx
387                 pop bx
388                 pop si
389                 jmp .servers