cachepc-linux

Fork of AMDESE/linux with modifications for CachePC side-channel attack
git clone https://git.sinitax.com/sinitax/cachepc-linux
Log | Files | Refs | README | LICENSE | sfeed.txt

libipw_rx.c (50115B)


      1// SPDX-License-Identifier: GPL-2.0-only
      2/*
      3 * Original code based Host AP (software wireless LAN access point) driver
      4 * for Intersil Prism2/2.5/3 - hostap.o module, common routines
      5 *
      6 * Copyright (c) 2001-2002, SSH Communications Security Corp and Jouni Malinen
      7 * <j@w1.fi>
      8 * Copyright (c) 2002-2003, Jouni Malinen <j@w1.fi>
      9 * Copyright (c) 2004-2005, Intel Corporation
     10 */
     11
     12#include <linux/compiler.h>
     13#include <linux/errno.h>
     14#include <linux/if_arp.h>
     15#include <linux/in6.h>
     16#include <linux/gfp.h>
     17#include <linux/in.h>
     18#include <linux/ip.h>
     19#include <linux/kernel.h>
     20#include <linux/module.h>
     21#include <linux/netdevice.h>
     22#include <linux/proc_fs.h>
     23#include <linux/skbuff.h>
     24#include <linux/tcp.h>
     25#include <linux/types.h>
     26#include <linux/wireless.h>
     27#include <linux/etherdevice.h>
     28#include <linux/uaccess.h>
     29#include <linux/ctype.h>
     30
     31#include <net/lib80211.h>
     32
     33#include "libipw.h"
     34
     35static void libipw_monitor_rx(struct libipw_device *ieee,
     36					struct sk_buff *skb,
     37					struct libipw_rx_stats *rx_stats)
     38{
     39	struct ieee80211_hdr *hdr = (struct ieee80211_hdr *)skb->data;
     40	u16 fc = le16_to_cpu(hdr->frame_control);
     41
     42	skb->dev = ieee->dev;
     43	skb_reset_mac_header(skb);
     44	skb_pull(skb, libipw_get_hdrlen(fc));
     45	skb->pkt_type = PACKET_OTHERHOST;
     46	skb->protocol = htons(ETH_P_80211_RAW);
     47	memset(skb->cb, 0, sizeof(skb->cb));
     48	netif_rx(skb);
     49}
     50
     51/* Called only as a tasklet (software IRQ) */
     52static struct libipw_frag_entry *libipw_frag_cache_find(struct
     53							      libipw_device
     54							      *ieee,
     55							      unsigned int seq,
     56							      unsigned int frag,
     57							      u8 * src,
     58							      u8 * dst)
     59{
     60	struct libipw_frag_entry *entry;
     61	int i;
     62
     63	for (i = 0; i < LIBIPW_FRAG_CACHE_LEN; i++) {
     64		entry = &ieee->frag_cache[i];
     65		if (entry->skb != NULL &&
     66		    time_after(jiffies, entry->first_frag_time + 2 * HZ)) {
     67			LIBIPW_DEBUG_FRAG("expiring fragment cache entry "
     68					     "seq=%u last_frag=%u\n",
     69					     entry->seq, entry->last_frag);
     70			dev_kfree_skb_any(entry->skb);
     71			entry->skb = NULL;
     72		}
     73
     74		if (entry->skb != NULL && entry->seq == seq &&
     75		    (entry->last_frag + 1 == frag || frag == -1) &&
     76		    ether_addr_equal(entry->src_addr, src) &&
     77		    ether_addr_equal(entry->dst_addr, dst))
     78			return entry;
     79	}
     80
     81	return NULL;
     82}
     83
     84/* Called only as a tasklet (software IRQ) */
     85static struct sk_buff *libipw_frag_cache_get(struct libipw_device *ieee,
     86						struct libipw_hdr_4addr *hdr)
     87{
     88	struct sk_buff *skb = NULL;
     89	u16 sc;
     90	unsigned int frag, seq;
     91	struct libipw_frag_entry *entry;
     92
     93	sc = le16_to_cpu(hdr->seq_ctl);
     94	frag = WLAN_GET_SEQ_FRAG(sc);
     95	seq = WLAN_GET_SEQ_SEQ(sc);
     96
     97	if (frag == 0) {
     98		/* Reserve enough space to fit maximum frame length */
     99		skb = dev_alloc_skb(ieee->dev->mtu +
    100				    sizeof(struct libipw_hdr_4addr) +
    101				    8 /* LLC */  +
    102				    2 /* alignment */  +
    103				    8 /* WEP */  + ETH_ALEN /* WDS */ );
    104		if (skb == NULL)
    105			return NULL;
    106
    107		entry = &ieee->frag_cache[ieee->frag_next_idx];
    108		ieee->frag_next_idx++;
    109		if (ieee->frag_next_idx >= LIBIPW_FRAG_CACHE_LEN)
    110			ieee->frag_next_idx = 0;
    111
    112		if (entry->skb != NULL)
    113			dev_kfree_skb_any(entry->skb);
    114
    115		entry->first_frag_time = jiffies;
    116		entry->seq = seq;
    117		entry->last_frag = frag;
    118		entry->skb = skb;
    119		memcpy(entry->src_addr, hdr->addr2, ETH_ALEN);
    120		memcpy(entry->dst_addr, hdr->addr1, ETH_ALEN);
    121	} else {
    122		/* received a fragment of a frame for which the head fragment
    123		 * should have already been received */
    124		entry = libipw_frag_cache_find(ieee, seq, frag, hdr->addr2,
    125						  hdr->addr1);
    126		if (entry != NULL) {
    127			entry->last_frag = frag;
    128			skb = entry->skb;
    129		}
    130	}
    131
    132	return skb;
    133}
    134
    135/* Called only as a tasklet (software IRQ) */
    136static int libipw_frag_cache_invalidate(struct libipw_device *ieee,
    137					   struct libipw_hdr_4addr *hdr)
    138{
    139	u16 sc;
    140	unsigned int seq;
    141	struct libipw_frag_entry *entry;
    142
    143	sc = le16_to_cpu(hdr->seq_ctl);
    144	seq = WLAN_GET_SEQ_SEQ(sc);
    145
    146	entry = libipw_frag_cache_find(ieee, seq, -1, hdr->addr2,
    147					  hdr->addr1);
    148
    149	if (entry == NULL) {
    150		LIBIPW_DEBUG_FRAG("could not invalidate fragment cache "
    151				     "entry (seq=%u)\n", seq);
    152		return -1;
    153	}
    154
    155	entry->skb = NULL;
    156	return 0;
    157}
    158
    159#ifdef NOT_YET
    160/* libipw_rx_frame_mgtmt
    161 *
    162 * Responsible for handling management control frames
    163 *
    164 * Called by libipw_rx */
    165static int
    166libipw_rx_frame_mgmt(struct libipw_device *ieee, struct sk_buff *skb,
    167			struct libipw_rx_stats *rx_stats, u16 type,
    168			u16 stype)
    169{
    170	if (ieee->iw_mode == IW_MODE_MASTER) {
    171		printk(KERN_DEBUG "%s: Master mode not yet supported.\n",
    172		       ieee->dev->name);
    173		return 0;
    174/*
    175  hostap_update_sta_ps(ieee, (struct hostap_libipw_hdr_4addr *)
    176  skb->data);*/
    177	}
    178
    179	if (ieee->hostapd && type == WLAN_FC_TYPE_MGMT) {
    180		if (stype == WLAN_FC_STYPE_BEACON &&
    181		    ieee->iw_mode == IW_MODE_MASTER) {
    182			struct sk_buff *skb2;
    183			/* Process beacon frames also in kernel driver to
    184			 * update STA(AP) table statistics */
    185			skb2 = skb_clone(skb, GFP_ATOMIC);
    186			if (skb2)
    187				hostap_rx(skb2->dev, skb2, rx_stats);
    188		}
    189
    190		/* send management frames to the user space daemon for
    191		 * processing */
    192		ieee->apdevstats.rx_packets++;
    193		ieee->apdevstats.rx_bytes += skb->len;
    194		prism2_rx_80211(ieee->apdev, skb, rx_stats, PRISM2_RX_MGMT);
    195		return 0;
    196	}
    197
    198	if (ieee->iw_mode == IW_MODE_MASTER) {
    199		if (type != WLAN_FC_TYPE_MGMT && type != WLAN_FC_TYPE_CTRL) {
    200			printk(KERN_DEBUG "%s: unknown management frame "
    201			       "(type=0x%02x, stype=0x%02x) dropped\n",
    202			       skb->dev->name, type, stype);
    203			return -1;
    204		}
    205
    206		hostap_rx(skb->dev, skb, rx_stats);
    207		return 0;
    208	}
    209
    210	printk(KERN_DEBUG "%s: hostap_rx_frame_mgmt: management frame "
    211	       "received in non-Host AP mode\n", skb->dev->name);
    212	return -1;
    213}
    214#endif
    215
    216/* See IEEE 802.1H for LLC/SNAP encapsulation/decapsulation */
    217/* Ethernet-II snap header (RFC1042 for most EtherTypes) */
    218static unsigned char libipw_rfc1042_header[] =
    219    { 0xaa, 0xaa, 0x03, 0x00, 0x00, 0x00 };
    220
    221/* Bridge-Tunnel header (for EtherTypes ETH_P_AARP and ETH_P_IPX) */
    222static unsigned char libipw_bridge_tunnel_header[] =
    223    { 0xaa, 0xaa, 0x03, 0x00, 0x00, 0xf8 };
    224/* No encapsulation header if EtherType < 0x600 (=length) */
    225
    226/* Called by libipw_rx_frame_decrypt */
    227static int libipw_is_eapol_frame(struct libipw_device *ieee,
    228				    struct sk_buff *skb)
    229{
    230	struct net_device *dev = ieee->dev;
    231	u16 fc, ethertype;
    232	struct libipw_hdr_3addr *hdr;
    233	u8 *pos;
    234
    235	if (skb->len < 24)
    236		return 0;
    237
    238	hdr = (struct libipw_hdr_3addr *)skb->data;
    239	fc = le16_to_cpu(hdr->frame_ctl);
    240
    241	/* check that the frame is unicast frame to us */
    242	if ((fc & (IEEE80211_FCTL_TODS | IEEE80211_FCTL_FROMDS)) ==
    243	    IEEE80211_FCTL_TODS &&
    244	    ether_addr_equal(hdr->addr1, dev->dev_addr) &&
    245	    ether_addr_equal(hdr->addr3, dev->dev_addr)) {
    246		/* ToDS frame with own addr BSSID and DA */
    247	} else if ((fc & (IEEE80211_FCTL_TODS | IEEE80211_FCTL_FROMDS)) ==
    248		   IEEE80211_FCTL_FROMDS &&
    249		   ether_addr_equal(hdr->addr1, dev->dev_addr)) {
    250		/* FromDS frame with own addr as DA */
    251	} else
    252		return 0;
    253
    254	if (skb->len < 24 + 8)
    255		return 0;
    256
    257	/* check for port access entity Ethernet type */
    258	pos = skb->data + 24;
    259	ethertype = (pos[6] << 8) | pos[7];
    260	if (ethertype == ETH_P_PAE)
    261		return 1;
    262
    263	return 0;
    264}
    265
    266/* Called only as a tasklet (software IRQ), by libipw_rx */
    267static int
    268libipw_rx_frame_decrypt(struct libipw_device *ieee, struct sk_buff *skb,
    269			   struct lib80211_crypt_data *crypt)
    270{
    271	struct libipw_hdr_3addr *hdr;
    272	int res, hdrlen;
    273
    274	if (crypt == NULL || crypt->ops->decrypt_mpdu == NULL)
    275		return 0;
    276
    277	hdr = (struct libipw_hdr_3addr *)skb->data;
    278	hdrlen = libipw_get_hdrlen(le16_to_cpu(hdr->frame_ctl));
    279
    280	atomic_inc(&crypt->refcnt);
    281	res = crypt->ops->decrypt_mpdu(skb, hdrlen, crypt->priv);
    282	atomic_dec(&crypt->refcnt);
    283	if (res < 0) {
    284		LIBIPW_DEBUG_DROP("decryption failed (SA=%pM) res=%d\n",
    285				     hdr->addr2, res);
    286		if (res == -2)
    287			LIBIPW_DEBUG_DROP("Decryption failed ICV "
    288					     "mismatch (key %d)\n",
    289					     skb->data[hdrlen + 3] >> 6);
    290		ieee->ieee_stats.rx_discards_undecryptable++;
    291		return -1;
    292	}
    293
    294	return res;
    295}
    296
    297/* Called only as a tasklet (software IRQ), by libipw_rx */
    298static int
    299libipw_rx_frame_decrypt_msdu(struct libipw_device *ieee,
    300				struct sk_buff *skb, int keyidx,
    301				struct lib80211_crypt_data *crypt)
    302{
    303	struct libipw_hdr_3addr *hdr;
    304	int res, hdrlen;
    305
    306	if (crypt == NULL || crypt->ops->decrypt_msdu == NULL)
    307		return 0;
    308
    309	hdr = (struct libipw_hdr_3addr *)skb->data;
    310	hdrlen = libipw_get_hdrlen(le16_to_cpu(hdr->frame_ctl));
    311
    312	atomic_inc(&crypt->refcnt);
    313	res = crypt->ops->decrypt_msdu(skb, keyidx, hdrlen, crypt->priv);
    314	atomic_dec(&crypt->refcnt);
    315	if (res < 0) {
    316		printk(KERN_DEBUG "%s: MSDU decryption/MIC verification failed"
    317		       " (SA=%pM keyidx=%d)\n", ieee->dev->name, hdr->addr2,
    318		       keyidx);
    319		return -1;
    320	}
    321
    322	return 0;
    323}
    324
    325/* All received frames are sent to this function. @skb contains the frame in
    326 * IEEE 802.11 format, i.e., in the format it was sent over air.
    327 * This function is called only as a tasklet (software IRQ). */
    328int libipw_rx(struct libipw_device *ieee, struct sk_buff *skb,
    329		 struct libipw_rx_stats *rx_stats)
    330{
    331	struct net_device *dev = ieee->dev;
    332	struct libipw_hdr_4addr *hdr;
    333	size_t hdrlen;
    334	u16 fc, type, stype, sc;
    335	unsigned int frag;
    336	u8 *payload;
    337	u16 ethertype;
    338#ifdef NOT_YET
    339	struct net_device *wds = NULL;
    340	struct sk_buff *skb2 = NULL;
    341	struct net_device *wds = NULL;
    342	int frame_authorized = 0;
    343	int from_assoc_ap = 0;
    344	void *sta = NULL;
    345#endif
    346	u8 dst[ETH_ALEN];
    347	u8 src[ETH_ALEN];
    348	struct lib80211_crypt_data *crypt = NULL;
    349	int keyidx = 0;
    350	int can_be_decrypted = 0;
    351
    352	hdr = (struct libipw_hdr_4addr *)skb->data;
    353	if (skb->len < 10) {
    354		printk(KERN_INFO "%s: SKB length < 10\n", dev->name);
    355		goto rx_dropped;
    356	}
    357
    358	fc = le16_to_cpu(hdr->frame_ctl);
    359	type = WLAN_FC_GET_TYPE(fc);
    360	stype = WLAN_FC_GET_STYPE(fc);
    361	sc = le16_to_cpu(hdr->seq_ctl);
    362	frag = WLAN_GET_SEQ_FRAG(sc);
    363	hdrlen = libipw_get_hdrlen(fc);
    364
    365	if (skb->len < hdrlen) {
    366		printk(KERN_INFO "%s: invalid SKB length %d\n",
    367			dev->name, skb->len);
    368		goto rx_dropped;
    369	}
    370
    371	/* Put this code here so that we avoid duplicating it in all
    372	 * Rx paths. - Jean II */
    373#ifdef CONFIG_WIRELESS_EXT
    374#ifdef IW_WIRELESS_SPY		/* defined in iw_handler.h */
    375	/* If spy monitoring on */
    376	if (ieee->spy_data.spy_number > 0) {
    377		struct iw_quality wstats;
    378
    379		wstats.updated = 0;
    380		if (rx_stats->mask & LIBIPW_STATMASK_RSSI) {
    381			wstats.level = rx_stats->signal;
    382			wstats.updated |= IW_QUAL_LEVEL_UPDATED;
    383		} else
    384			wstats.updated |= IW_QUAL_LEVEL_INVALID;
    385
    386		if (rx_stats->mask & LIBIPW_STATMASK_NOISE) {
    387			wstats.noise = rx_stats->noise;
    388			wstats.updated |= IW_QUAL_NOISE_UPDATED;
    389		} else
    390			wstats.updated |= IW_QUAL_NOISE_INVALID;
    391
    392		if (rx_stats->mask & LIBIPW_STATMASK_SIGNAL) {
    393			wstats.qual = rx_stats->signal;
    394			wstats.updated |= IW_QUAL_QUAL_UPDATED;
    395		} else
    396			wstats.updated |= IW_QUAL_QUAL_INVALID;
    397
    398		/* Update spy records */
    399		wireless_spy_update(ieee->dev, hdr->addr2, &wstats);
    400	}
    401#endif				/* IW_WIRELESS_SPY */
    402#endif				/* CONFIG_WIRELESS_EXT */
    403
    404#ifdef NOT_YET
    405	hostap_update_rx_stats(local->ap, hdr, rx_stats);
    406#endif
    407
    408	if (ieee->iw_mode == IW_MODE_MONITOR) {
    409		dev->stats.rx_packets++;
    410		dev->stats.rx_bytes += skb->len;
    411		libipw_monitor_rx(ieee, skb, rx_stats);
    412		return 1;
    413	}
    414
    415	can_be_decrypted = (is_multicast_ether_addr(hdr->addr1) ||
    416			    is_broadcast_ether_addr(hdr->addr2)) ?
    417	    ieee->host_mc_decrypt : ieee->host_decrypt;
    418
    419	if (can_be_decrypted) {
    420		if (skb->len >= hdrlen + 3) {
    421			/* Top two-bits of byte 3 are the key index */
    422			keyidx = skb->data[hdrlen + 3] >> 6;
    423		}
    424
    425		/* ieee->crypt[] is WEP_KEY (4) in length.  Given that keyidx
    426		 * is only allowed 2-bits of storage, no value of keyidx can
    427		 * be provided via above code that would result in keyidx
    428		 * being out of range */
    429		crypt = ieee->crypt_info.crypt[keyidx];
    430
    431#ifdef NOT_YET
    432		sta = NULL;
    433
    434		/* Use station specific key to override default keys if the
    435		 * receiver address is a unicast address ("individual RA"). If
    436		 * bcrx_sta_key parameter is set, station specific key is used
    437		 * even with broad/multicast targets (this is against IEEE
    438		 * 802.11, but makes it easier to use different keys with
    439		 * stations that do not support WEP key mapping). */
    440
    441		if (is_unicast_ether_addr(hdr->addr1) || local->bcrx_sta_key)
    442			(void)hostap_handle_sta_crypto(local, hdr, &crypt,
    443						       &sta);
    444#endif
    445
    446		/* allow NULL decrypt to indicate an station specific override
    447		 * for default encryption */
    448		if (crypt && (crypt->ops == NULL ||
    449			      crypt->ops->decrypt_mpdu == NULL))
    450			crypt = NULL;
    451
    452		if (!crypt && (fc & IEEE80211_FCTL_PROTECTED)) {
    453			/* This seems to be triggered by some (multicast?)
    454			 * frames from other than current BSS, so just drop the
    455			 * frames silently instead of filling system log with
    456			 * these reports. */
    457			LIBIPW_DEBUG_DROP("Decryption failed (not set)"
    458					     " (SA=%pM)\n", hdr->addr2);
    459			ieee->ieee_stats.rx_discards_undecryptable++;
    460			goto rx_dropped;
    461		}
    462	}
    463#ifdef NOT_YET
    464	if (type != WLAN_FC_TYPE_DATA) {
    465		if (type == WLAN_FC_TYPE_MGMT && stype == WLAN_FC_STYPE_AUTH &&
    466		    fc & IEEE80211_FCTL_PROTECTED && ieee->host_decrypt &&
    467		    (keyidx = hostap_rx_frame_decrypt(ieee, skb, crypt)) < 0) {
    468			printk(KERN_DEBUG "%s: failed to decrypt mgmt::auth "
    469			       "from %pM\n", dev->name, hdr->addr2);
    470			/* TODO: could inform hostapd about this so that it
    471			 * could send auth failure report */
    472			goto rx_dropped;
    473		}
    474
    475		if (libipw_rx_frame_mgmt(ieee, skb, rx_stats, type, stype))
    476			goto rx_dropped;
    477		else
    478			goto rx_exit;
    479	}
    480#endif
    481	/* drop duplicate 802.11 retransmissions (IEEE 802.11 Chap. 9.29) */
    482	if (sc == ieee->prev_seq_ctl)
    483		goto rx_dropped;
    484	else
    485		ieee->prev_seq_ctl = sc;
    486
    487	/* Data frame - extract src/dst addresses */
    488	if (skb->len < LIBIPW_3ADDR_LEN)
    489		goto rx_dropped;
    490
    491	switch (fc & (IEEE80211_FCTL_FROMDS | IEEE80211_FCTL_TODS)) {
    492	case IEEE80211_FCTL_FROMDS:
    493		memcpy(dst, hdr->addr1, ETH_ALEN);
    494		memcpy(src, hdr->addr3, ETH_ALEN);
    495		break;
    496	case IEEE80211_FCTL_TODS:
    497		memcpy(dst, hdr->addr3, ETH_ALEN);
    498		memcpy(src, hdr->addr2, ETH_ALEN);
    499		break;
    500	case IEEE80211_FCTL_FROMDS | IEEE80211_FCTL_TODS:
    501		if (skb->len < LIBIPW_4ADDR_LEN)
    502			goto rx_dropped;
    503		memcpy(dst, hdr->addr3, ETH_ALEN);
    504		memcpy(src, hdr->addr4, ETH_ALEN);
    505		break;
    506	default:
    507		memcpy(dst, hdr->addr1, ETH_ALEN);
    508		memcpy(src, hdr->addr2, ETH_ALEN);
    509		break;
    510	}
    511
    512#ifdef NOT_YET
    513	if (hostap_rx_frame_wds(ieee, hdr, fc, &wds))
    514		goto rx_dropped;
    515	if (wds) {
    516		skb->dev = dev = wds;
    517		stats = hostap_get_stats(dev);
    518	}
    519
    520	if (ieee->iw_mode == IW_MODE_MASTER && !wds &&
    521	    (fc & (IEEE80211_FCTL_TODS | IEEE80211_FCTL_FROMDS)) ==
    522	    IEEE80211_FCTL_FROMDS && ieee->stadev &&
    523	    ether_addr_equal(hdr->addr2, ieee->assoc_ap_addr)) {
    524		/* Frame from BSSID of the AP for which we are a client */
    525		skb->dev = dev = ieee->stadev;
    526		stats = hostap_get_stats(dev);
    527		from_assoc_ap = 1;
    528	}
    529#endif
    530
    531#ifdef NOT_YET
    532	if ((ieee->iw_mode == IW_MODE_MASTER ||
    533	     ieee->iw_mode == IW_MODE_REPEAT) && !from_assoc_ap) {
    534		switch (hostap_handle_sta_rx(ieee, dev, skb, rx_stats,
    535					     wds != NULL)) {
    536		case AP_RX_CONTINUE_NOT_AUTHORIZED:
    537			frame_authorized = 0;
    538			break;
    539		case AP_RX_CONTINUE:
    540			frame_authorized = 1;
    541			break;
    542		case AP_RX_DROP:
    543			goto rx_dropped;
    544		case AP_RX_EXIT:
    545			goto rx_exit;
    546		}
    547	}
    548#endif
    549
    550	/* Nullfunc frames may have PS-bit set, so they must be passed to
    551	 * hostap_handle_sta_rx() before being dropped here. */
    552
    553	stype &= ~IEEE80211_STYPE_QOS_DATA;
    554
    555	if (stype != IEEE80211_STYPE_DATA &&
    556	    stype != IEEE80211_STYPE_DATA_CFACK &&
    557	    stype != IEEE80211_STYPE_DATA_CFPOLL &&
    558	    stype != IEEE80211_STYPE_DATA_CFACKPOLL) {
    559		if (stype != IEEE80211_STYPE_NULLFUNC)
    560			LIBIPW_DEBUG_DROP("RX: dropped data frame "
    561					     "with no data (type=0x%02x, "
    562					     "subtype=0x%02x, len=%d)\n",
    563					     type, stype, skb->len);
    564		goto rx_dropped;
    565	}
    566
    567	/* skb: hdr + (possibly fragmented, possibly encrypted) payload */
    568
    569	if ((fc & IEEE80211_FCTL_PROTECTED) && can_be_decrypted &&
    570	    (keyidx = libipw_rx_frame_decrypt(ieee, skb, crypt)) < 0)
    571		goto rx_dropped;
    572
    573	hdr = (struct libipw_hdr_4addr *)skb->data;
    574
    575	/* skb: hdr + (possibly fragmented) plaintext payload */
    576	// PR: FIXME: hostap has additional conditions in the "if" below:
    577	// ieee->host_decrypt && (fc & IEEE80211_FCTL_PROTECTED) &&
    578	if ((frag != 0) || (fc & IEEE80211_FCTL_MOREFRAGS)) {
    579		int flen;
    580		struct sk_buff *frag_skb = libipw_frag_cache_get(ieee, hdr);
    581		LIBIPW_DEBUG_FRAG("Rx Fragment received (%u)\n", frag);
    582
    583		if (!frag_skb) {
    584			LIBIPW_DEBUG(LIBIPW_DL_RX | LIBIPW_DL_FRAG,
    585					"Rx cannot get skb from fragment "
    586					"cache (morefrag=%d seq=%u frag=%u)\n",
    587					(fc & IEEE80211_FCTL_MOREFRAGS) != 0,
    588					WLAN_GET_SEQ_SEQ(sc), frag);
    589			goto rx_dropped;
    590		}
    591
    592		flen = skb->len;
    593		if (frag != 0)
    594			flen -= hdrlen;
    595
    596		if (frag_skb->tail + flen > frag_skb->end) {
    597			printk(KERN_WARNING "%s: host decrypted and "
    598			       "reassembled frame did not fit skb\n",
    599			       dev->name);
    600			libipw_frag_cache_invalidate(ieee, hdr);
    601			goto rx_dropped;
    602		}
    603
    604		if (frag == 0) {
    605			/* copy first fragment (including full headers) into
    606			 * beginning of the fragment cache skb */
    607			skb_copy_from_linear_data(skb, skb_put(frag_skb, flen), flen);
    608		} else {
    609			/* append frame payload to the end of the fragment
    610			 * cache skb */
    611			skb_copy_from_linear_data_offset(skb, hdrlen,
    612				      skb_put(frag_skb, flen), flen);
    613		}
    614		dev_kfree_skb_any(skb);
    615		skb = NULL;
    616
    617		if (fc & IEEE80211_FCTL_MOREFRAGS) {
    618			/* more fragments expected - leave the skb in fragment
    619			 * cache for now; it will be delivered to upper layers
    620			 * after all fragments have been received */
    621			goto rx_exit;
    622		}
    623
    624		/* this was the last fragment and the frame will be
    625		 * delivered, so remove skb from fragment cache */
    626		skb = frag_skb;
    627		hdr = (struct libipw_hdr_4addr *)skb->data;
    628		libipw_frag_cache_invalidate(ieee, hdr);
    629	}
    630
    631	/* skb: hdr + (possible reassembled) full MSDU payload; possibly still
    632	 * encrypted/authenticated */
    633	if ((fc & IEEE80211_FCTL_PROTECTED) && can_be_decrypted &&
    634	    libipw_rx_frame_decrypt_msdu(ieee, skb, keyidx, crypt))
    635		goto rx_dropped;
    636
    637	hdr = (struct libipw_hdr_4addr *)skb->data;
    638	if (crypt && !(fc & IEEE80211_FCTL_PROTECTED) && !ieee->open_wep) {
    639		if (		/*ieee->ieee802_1x && */
    640			   libipw_is_eapol_frame(ieee, skb)) {
    641			/* pass unencrypted EAPOL frames even if encryption is
    642			 * configured */
    643		} else {
    644			LIBIPW_DEBUG_DROP("encryption configured, but RX "
    645					     "frame not encrypted (SA=%pM)\n",
    646					     hdr->addr2);
    647			goto rx_dropped;
    648		}
    649	}
    650
    651	if (crypt && !(fc & IEEE80211_FCTL_PROTECTED) && !ieee->open_wep &&
    652	    !libipw_is_eapol_frame(ieee, skb)) {
    653		LIBIPW_DEBUG_DROP("dropped unencrypted RX data "
    654				     "frame from %pM (drop_unencrypted=1)\n",
    655				     hdr->addr2);
    656		goto rx_dropped;
    657	}
    658
    659	/* If the frame was decrypted in hardware, we may need to strip off
    660	 * any security data (IV, ICV, etc) that was left behind */
    661	if (!can_be_decrypted && (fc & IEEE80211_FCTL_PROTECTED) &&
    662	    ieee->host_strip_iv_icv) {
    663		int trimlen = 0;
    664
    665		/* Top two-bits of byte 3 are the key index */
    666		if (skb->len >= hdrlen + 3)
    667			keyidx = skb->data[hdrlen + 3] >> 6;
    668
    669		/* To strip off any security data which appears before the
    670		 * payload, we simply increase hdrlen (as the header gets
    671		 * chopped off immediately below). For the security data which
    672		 * appears after the payload, we use skb_trim. */
    673
    674		switch (ieee->sec.encode_alg[keyidx]) {
    675		case SEC_ALG_WEP:
    676			/* 4 byte IV */
    677			hdrlen += 4;
    678			/* 4 byte ICV */
    679			trimlen = 4;
    680			break;
    681		case SEC_ALG_TKIP:
    682			/* 4 byte IV, 4 byte ExtIV */
    683			hdrlen += 8;
    684			/* 8 byte MIC, 4 byte ICV */
    685			trimlen = 12;
    686			break;
    687		case SEC_ALG_CCMP:
    688			/* 8 byte CCMP header */
    689			hdrlen += 8;
    690			/* 8 byte MIC */
    691			trimlen = 8;
    692			break;
    693		}
    694
    695		if (skb->len < trimlen)
    696			goto rx_dropped;
    697
    698		__skb_trim(skb, skb->len - trimlen);
    699
    700		if (skb->len < hdrlen)
    701			goto rx_dropped;
    702	}
    703
    704	/* skb: hdr + (possible reassembled) full plaintext payload */
    705
    706	payload = skb->data + hdrlen;
    707	ethertype = (payload[6] << 8) | payload[7];
    708
    709#ifdef NOT_YET
    710	/* If IEEE 802.1X is used, check whether the port is authorized to send
    711	 * the received frame. */
    712	if (ieee->ieee802_1x && ieee->iw_mode == IW_MODE_MASTER) {
    713		if (ethertype == ETH_P_PAE) {
    714			printk(KERN_DEBUG "%s: RX: IEEE 802.1X frame\n",
    715			       dev->name);
    716			if (ieee->hostapd && ieee->apdev) {
    717				/* Send IEEE 802.1X frames to the user
    718				 * space daemon for processing */
    719				prism2_rx_80211(ieee->apdev, skb, rx_stats,
    720						PRISM2_RX_MGMT);
    721				ieee->apdevstats.rx_packets++;
    722				ieee->apdevstats.rx_bytes += skb->len;
    723				goto rx_exit;
    724			}
    725		} else if (!frame_authorized) {
    726			printk(KERN_DEBUG "%s: dropped frame from "
    727			       "unauthorized port (IEEE 802.1X): "
    728			       "ethertype=0x%04x\n", dev->name, ethertype);
    729			goto rx_dropped;
    730		}
    731	}
    732#endif
    733
    734	/* convert hdr + possible LLC headers into Ethernet header */
    735	if (skb->len - hdrlen >= 8 &&
    736	    ((memcmp(payload, libipw_rfc1042_header, SNAP_SIZE) == 0 &&
    737	      ethertype != ETH_P_AARP && ethertype != ETH_P_IPX) ||
    738	     memcmp(payload, libipw_bridge_tunnel_header, SNAP_SIZE) == 0)) {
    739		/* remove RFC1042 or Bridge-Tunnel encapsulation and
    740		 * replace EtherType */
    741		skb_pull(skb, hdrlen + SNAP_SIZE);
    742		memcpy(skb_push(skb, ETH_ALEN), src, ETH_ALEN);
    743		memcpy(skb_push(skb, ETH_ALEN), dst, ETH_ALEN);
    744	} else {
    745		__be16 len;
    746		/* Leave Ethernet header part of hdr and full payload */
    747		skb_pull(skb, hdrlen);
    748		len = htons(skb->len);
    749		memcpy(skb_push(skb, 2), &len, 2);
    750		memcpy(skb_push(skb, ETH_ALEN), src, ETH_ALEN);
    751		memcpy(skb_push(skb, ETH_ALEN), dst, ETH_ALEN);
    752	}
    753
    754#ifdef NOT_YET
    755	if (wds && ((fc & (IEEE80211_FCTL_TODS | IEEE80211_FCTL_FROMDS)) ==
    756		    IEEE80211_FCTL_TODS) && skb->len >= ETH_HLEN + ETH_ALEN) {
    757		/* Non-standard frame: get addr4 from its bogus location after
    758		 * the payload */
    759		skb_copy_to_linear_data_offset(skb, ETH_ALEN,
    760					       skb->data + skb->len - ETH_ALEN,
    761					       ETH_ALEN);
    762		skb_trim(skb, skb->len - ETH_ALEN);
    763	}
    764#endif
    765
    766	dev->stats.rx_packets++;
    767	dev->stats.rx_bytes += skb->len;
    768
    769#ifdef NOT_YET
    770	if (ieee->iw_mode == IW_MODE_MASTER && !wds && ieee->ap->bridge_packets) {
    771		if (is_multicast_ether_addr(dst)) {
    772			/* copy multicast frame both to the higher layers and
    773			 * to the wireless media */
    774			ieee->ap->bridged_multicast++;
    775			skb2 = skb_clone(skb, GFP_ATOMIC);
    776			if (skb2 == NULL)
    777				printk(KERN_DEBUG "%s: skb_clone failed for "
    778				       "multicast frame\n", dev->name);
    779		} else if (hostap_is_sta_assoc(ieee->ap, dst)) {
    780			/* send frame directly to the associated STA using
    781			 * wireless media and not passing to higher layers */
    782			ieee->ap->bridged_unicast++;
    783			skb2 = skb;
    784			skb = NULL;
    785		}
    786	}
    787
    788	if (skb2 != NULL) {
    789		/* send to wireless media */
    790		skb2->dev = dev;
    791		skb2->protocol = htons(ETH_P_802_3);
    792		skb_reset_mac_header(skb2);
    793		skb_reset_network_header(skb2);
    794		/* skb2->network_header += ETH_HLEN; */
    795		dev_queue_xmit(skb2);
    796	}
    797#endif
    798
    799	if (skb) {
    800		skb->protocol = eth_type_trans(skb, dev);
    801		memset(skb->cb, 0, sizeof(skb->cb));
    802		skb->ip_summed = CHECKSUM_NONE;	/* 802.11 crc not sufficient */
    803		if (netif_rx(skb) == NET_RX_DROP) {
    804			/* netif_rx always succeeds, but it might drop
    805			 * the packet.  If it drops the packet, we log that
    806			 * in our stats. */
    807			LIBIPW_DEBUG_DROP
    808			    ("RX: netif_rx dropped the packet\n");
    809			dev->stats.rx_dropped++;
    810		}
    811	}
    812
    813      rx_exit:
    814#ifdef NOT_YET
    815	if (sta)
    816		hostap_handle_sta_release(sta);
    817#endif
    818	return 1;
    819
    820      rx_dropped:
    821	dev->stats.rx_dropped++;
    822
    823	/* Returning 0 indicates to caller that we have not handled the SKB--
    824	 * so it is still allocated and can be used again by underlying
    825	 * hardware as a DMA target */
    826	return 0;
    827}
    828
    829/* Filter out unrelated packets, call libipw_rx[_mgt]
    830 * This function takes over the skb, it should not be used again after calling
    831 * this function. */
    832void libipw_rx_any(struct libipw_device *ieee,
    833		     struct sk_buff *skb, struct libipw_rx_stats *stats)
    834{
    835	struct libipw_hdr_4addr *hdr;
    836	int is_packet_for_us;
    837	u16 fc;
    838
    839	if (ieee->iw_mode == IW_MODE_MONITOR) {
    840		if (!libipw_rx(ieee, skb, stats))
    841			dev_kfree_skb_irq(skb);
    842		return;
    843	}
    844
    845	if (skb->len < sizeof(struct ieee80211_hdr))
    846		goto drop_free;
    847
    848	hdr = (struct libipw_hdr_4addr *)skb->data;
    849	fc = le16_to_cpu(hdr->frame_ctl);
    850
    851	if ((fc & IEEE80211_FCTL_VERS) != 0)
    852		goto drop_free;
    853
    854	switch (fc & IEEE80211_FCTL_FTYPE) {
    855	case IEEE80211_FTYPE_MGMT:
    856		if (skb->len < sizeof(struct libipw_hdr_3addr))
    857			goto drop_free;
    858		libipw_rx_mgt(ieee, hdr, stats);
    859		dev_kfree_skb_irq(skb);
    860		return;
    861	case IEEE80211_FTYPE_DATA:
    862		break;
    863	case IEEE80211_FTYPE_CTL:
    864		return;
    865	default:
    866		return;
    867	}
    868
    869	is_packet_for_us = 0;
    870	switch (ieee->iw_mode) {
    871	case IW_MODE_ADHOC:
    872		/* our BSS and not from/to DS */
    873		if (ether_addr_equal(hdr->addr3, ieee->bssid))
    874		if ((fc & (IEEE80211_FCTL_TODS+IEEE80211_FCTL_FROMDS)) == 0) {
    875			/* promisc: get all */
    876			if (ieee->dev->flags & IFF_PROMISC)
    877				is_packet_for_us = 1;
    878			/* to us */
    879			else if (ether_addr_equal(hdr->addr1, ieee->dev->dev_addr))
    880				is_packet_for_us = 1;
    881			/* mcast */
    882			else if (is_multicast_ether_addr(hdr->addr1))
    883				is_packet_for_us = 1;
    884		}
    885		break;
    886	case IW_MODE_INFRA:
    887		/* our BSS (== from our AP) and from DS */
    888		if (ether_addr_equal(hdr->addr2, ieee->bssid))
    889		if ((fc & (IEEE80211_FCTL_TODS+IEEE80211_FCTL_FROMDS)) == IEEE80211_FCTL_FROMDS) {
    890			/* promisc: get all */
    891			if (ieee->dev->flags & IFF_PROMISC)
    892				is_packet_for_us = 1;
    893			/* to us */
    894			else if (ether_addr_equal(hdr->addr1, ieee->dev->dev_addr))
    895				is_packet_for_us = 1;
    896			/* mcast */
    897			else if (is_multicast_ether_addr(hdr->addr1)) {
    898				/* not our own packet bcasted from AP */
    899				if (!ether_addr_equal(hdr->addr3, ieee->dev->dev_addr))
    900					is_packet_for_us = 1;
    901			}
    902		}
    903		break;
    904	default:
    905		/* ? */
    906		break;
    907	}
    908
    909	if (is_packet_for_us)
    910		if (!libipw_rx(ieee, skb, stats))
    911			dev_kfree_skb_irq(skb);
    912	return;
    913
    914drop_free:
    915	dev_kfree_skb_irq(skb);
    916	ieee->dev->stats.rx_dropped++;
    917}
    918
    919#define MGMT_FRAME_FIXED_PART_LENGTH		0x24
    920
    921static u8 qos_oui[QOS_OUI_LEN] = { 0x00, 0x50, 0xF2 };
    922
    923/*
    924* Make the structure we read from the beacon packet to have
    925* the right values
    926*/
    927static int libipw_verify_qos_info(struct libipw_qos_information_element
    928				     *info_element, int sub_type)
    929{
    930	if (info_element->elementID != QOS_ELEMENT_ID)
    931		return -1;
    932	if (info_element->qui_subtype != sub_type)
    933		return -1;
    934	if (memcmp(info_element->qui, qos_oui, QOS_OUI_LEN))
    935		return -1;
    936	if (info_element->qui_type != QOS_OUI_TYPE)
    937		return -1;
    938	if (info_element->version != QOS_VERSION_1)
    939		return -1;
    940
    941	return 0;
    942}
    943
    944/*
    945 * Parse a QoS parameter element
    946 */
    947static int libipw_read_qos_param_element(
    948			struct libipw_qos_parameter_info *element_param,
    949			struct libipw_info_element *info_element)
    950{
    951	size_t size = sizeof(*element_param);
    952
    953	if (!element_param || !info_element || info_element->len != size - 2)
    954		return -1;
    955
    956	memcpy(element_param, info_element, size);
    957	return libipw_verify_qos_info(&element_param->info_element,
    958				      QOS_OUI_PARAM_SUB_TYPE);
    959}
    960
    961/*
    962 * Parse a QoS information element
    963 */
    964static int libipw_read_qos_info_element(
    965			struct libipw_qos_information_element *element_info,
    966			struct libipw_info_element *info_element)
    967{
    968	size_t size = sizeof(struct libipw_qos_information_element) - 2;
    969
    970	if (!element_info || !info_element || info_element->len != size - 2)
    971		return -1;
    972
    973	memcpy(element_info, info_element, size);
    974	return libipw_verify_qos_info(element_info, QOS_OUI_INFO_SUB_TYPE);
    975}
    976
    977/*
    978 * Write QoS parameters from the ac parameters.
    979 */
    980static void libipw_qos_convert_ac_to_parameters(struct
    981						  libipw_qos_parameter_info
    982						  *param_elm, struct
    983						  libipw_qos_parameters
    984						  *qos_param)
    985{
    986	int i;
    987	struct libipw_qos_ac_parameter *ac_params;
    988	u32 txop;
    989	u8 cw_min;
    990	u8 cw_max;
    991
    992	for (i = 0; i < QOS_QUEUE_NUM; i++) {
    993		ac_params = &(param_elm->ac_params_record[i]);
    994
    995		qos_param->aifs[i] = (ac_params->aci_aifsn) & 0x0F;
    996		qos_param->aifs[i] -= (qos_param->aifs[i] < 2) ? 0 : 2;
    997
    998		cw_min = ac_params->ecw_min_max & 0x0F;
    999		qos_param->cw_min[i] = cpu_to_le16((1 << cw_min) - 1);
   1000
   1001		cw_max = (ac_params->ecw_min_max & 0xF0) >> 4;
   1002		qos_param->cw_max[i] = cpu_to_le16((1 << cw_max) - 1);
   1003
   1004		qos_param->flag[i] =
   1005		    (ac_params->aci_aifsn & 0x10) ? 0x01 : 0x00;
   1006
   1007		txop = le16_to_cpu(ac_params->tx_op_limit) * 32;
   1008		qos_param->tx_op_limit[i] = cpu_to_le16(txop);
   1009	}
   1010}
   1011
   1012/*
   1013 * we have a generic data element which it may contain QoS information or
   1014 * parameters element. check the information element length to decide
   1015 * which type to read
   1016 */
   1017static int libipw_parse_qos_info_param_IE(struct libipw_info_element
   1018					     *info_element,
   1019					     struct libipw_network *network)
   1020{
   1021	int rc = 0;
   1022	struct libipw_qos_parameters *qos_param = NULL;
   1023	struct libipw_qos_information_element qos_info_element;
   1024
   1025	rc = libipw_read_qos_info_element(&qos_info_element, info_element);
   1026
   1027	if (rc == 0) {
   1028		network->qos_data.param_count = qos_info_element.ac_info & 0x0F;
   1029		network->flags |= NETWORK_HAS_QOS_INFORMATION;
   1030	} else {
   1031		struct libipw_qos_parameter_info param_element;
   1032
   1033		rc = libipw_read_qos_param_element(&param_element,
   1034						      info_element);
   1035		if (rc == 0) {
   1036			qos_param = &(network->qos_data.parameters);
   1037			libipw_qos_convert_ac_to_parameters(&param_element,
   1038							       qos_param);
   1039			network->flags |= NETWORK_HAS_QOS_PARAMETERS;
   1040			network->qos_data.param_count =
   1041			    param_element.info_element.ac_info & 0x0F;
   1042		}
   1043	}
   1044
   1045	if (rc == 0) {
   1046		LIBIPW_DEBUG_QOS("QoS is supported\n");
   1047		network->qos_data.supported = 1;
   1048	}
   1049	return rc;
   1050}
   1051
   1052#ifdef CONFIG_LIBIPW_DEBUG
   1053#define MFIE_STRING(x) case WLAN_EID_ ##x: return #x
   1054
   1055static const char *get_info_element_string(u16 id)
   1056{
   1057	switch (id) {
   1058		MFIE_STRING(SSID);
   1059		MFIE_STRING(SUPP_RATES);
   1060		MFIE_STRING(FH_PARAMS);
   1061		MFIE_STRING(DS_PARAMS);
   1062		MFIE_STRING(CF_PARAMS);
   1063		MFIE_STRING(TIM);
   1064		MFIE_STRING(IBSS_PARAMS);
   1065		MFIE_STRING(COUNTRY);
   1066		MFIE_STRING(REQUEST);
   1067		MFIE_STRING(CHALLENGE);
   1068		MFIE_STRING(PWR_CONSTRAINT);
   1069		MFIE_STRING(PWR_CAPABILITY);
   1070		MFIE_STRING(TPC_REQUEST);
   1071		MFIE_STRING(TPC_REPORT);
   1072		MFIE_STRING(SUPPORTED_CHANNELS);
   1073		MFIE_STRING(CHANNEL_SWITCH);
   1074		MFIE_STRING(MEASURE_REQUEST);
   1075		MFIE_STRING(MEASURE_REPORT);
   1076		MFIE_STRING(QUIET);
   1077		MFIE_STRING(IBSS_DFS);
   1078		MFIE_STRING(ERP_INFO);
   1079		MFIE_STRING(RSN);
   1080		MFIE_STRING(EXT_SUPP_RATES);
   1081		MFIE_STRING(VENDOR_SPECIFIC);
   1082		MFIE_STRING(QOS_PARAMETER);
   1083	default:
   1084		return "UNKNOWN";
   1085	}
   1086}
   1087#endif
   1088
   1089static int libipw_parse_info_param(struct libipw_info_element
   1090				      *info_element, u16 length,
   1091				      struct libipw_network *network)
   1092{
   1093	u8 i;
   1094#ifdef CONFIG_LIBIPW_DEBUG
   1095	char rates_str[64];
   1096	char *p;
   1097#endif
   1098
   1099	while (length >= sizeof(*info_element)) {
   1100		if (sizeof(*info_element) + info_element->len > length) {
   1101			LIBIPW_DEBUG_MGMT("Info elem: parse failed: "
   1102					     "info_element->len + 2 > left : "
   1103					     "info_element->len+2=%zd left=%d, id=%d.\n",
   1104					     info_element->len +
   1105					     sizeof(*info_element),
   1106					     length, info_element->id);
   1107			/* We stop processing but don't return an error here
   1108			 * because some misbehaviour APs break this rule. ie.
   1109			 * Orinoco AP1000. */
   1110			break;
   1111		}
   1112
   1113		switch (info_element->id) {
   1114		case WLAN_EID_SSID:
   1115			network->ssid_len = min(info_element->len,
   1116						(u8) IW_ESSID_MAX_SIZE);
   1117			memcpy(network->ssid, info_element->data,
   1118			       network->ssid_len);
   1119			if (network->ssid_len < IW_ESSID_MAX_SIZE)
   1120				memset(network->ssid + network->ssid_len, 0,
   1121				       IW_ESSID_MAX_SIZE - network->ssid_len);
   1122
   1123			LIBIPW_DEBUG_MGMT("WLAN_EID_SSID: '%*pE' len=%d.\n",
   1124					  network->ssid_len, network->ssid,
   1125					  network->ssid_len);
   1126			break;
   1127
   1128		case WLAN_EID_SUPP_RATES:
   1129#ifdef CONFIG_LIBIPW_DEBUG
   1130			p = rates_str;
   1131#endif
   1132			network->rates_len = min(info_element->len,
   1133						 MAX_RATES_LENGTH);
   1134			for (i = 0; i < network->rates_len; i++) {
   1135				network->rates[i] = info_element->data[i];
   1136#ifdef CONFIG_LIBIPW_DEBUG
   1137				p += scnprintf(p, sizeof(rates_str) -
   1138					      (p - rates_str), "%02X ",
   1139					      network->rates[i]);
   1140#endif
   1141				if (libipw_is_ofdm_rate
   1142				    (info_element->data[i])) {
   1143					network->flags |= NETWORK_HAS_OFDM;
   1144					if (info_element->data[i] &
   1145					    LIBIPW_BASIC_RATE_MASK)
   1146						network->flags &=
   1147						    ~NETWORK_HAS_CCK;
   1148				}
   1149			}
   1150
   1151			LIBIPW_DEBUG_MGMT("WLAN_EID_SUPP_RATES: '%s' (%d)\n",
   1152					     rates_str, network->rates_len);
   1153			break;
   1154
   1155		case WLAN_EID_EXT_SUPP_RATES:
   1156#ifdef CONFIG_LIBIPW_DEBUG
   1157			p = rates_str;
   1158#endif
   1159			network->rates_ex_len = min(info_element->len,
   1160						    MAX_RATES_EX_LENGTH);
   1161			for (i = 0; i < network->rates_ex_len; i++) {
   1162				network->rates_ex[i] = info_element->data[i];
   1163#ifdef CONFIG_LIBIPW_DEBUG
   1164				p += scnprintf(p, sizeof(rates_str) -
   1165					      (p - rates_str), "%02X ",
   1166					      network->rates_ex[i]);
   1167#endif
   1168				if (libipw_is_ofdm_rate
   1169				    (info_element->data[i])) {
   1170					network->flags |= NETWORK_HAS_OFDM;
   1171					if (info_element->data[i] &
   1172					    LIBIPW_BASIC_RATE_MASK)
   1173						network->flags &=
   1174						    ~NETWORK_HAS_CCK;
   1175				}
   1176			}
   1177
   1178			LIBIPW_DEBUG_MGMT("WLAN_EID_EXT_SUPP_RATES: '%s' (%d)\n",
   1179					     rates_str, network->rates_ex_len);
   1180			break;
   1181
   1182		case WLAN_EID_DS_PARAMS:
   1183			LIBIPW_DEBUG_MGMT("WLAN_EID_DS_PARAMS: %d\n",
   1184					     info_element->data[0]);
   1185			network->channel = info_element->data[0];
   1186			break;
   1187
   1188		case WLAN_EID_FH_PARAMS:
   1189			LIBIPW_DEBUG_MGMT("WLAN_EID_FH_PARAMS: ignored\n");
   1190			break;
   1191
   1192		case WLAN_EID_CF_PARAMS:
   1193			LIBIPW_DEBUG_MGMT("WLAN_EID_CF_PARAMS: ignored\n");
   1194			break;
   1195
   1196		case WLAN_EID_TIM:
   1197			network->tim.tim_count = info_element->data[0];
   1198			network->tim.tim_period = info_element->data[1];
   1199			LIBIPW_DEBUG_MGMT("WLAN_EID_TIM: partially ignored\n");
   1200			break;
   1201
   1202		case WLAN_EID_ERP_INFO:
   1203			network->erp_value = info_element->data[0];
   1204			network->flags |= NETWORK_HAS_ERP_VALUE;
   1205			LIBIPW_DEBUG_MGMT("MFIE_TYPE_ERP_SET: %d\n",
   1206					     network->erp_value);
   1207			break;
   1208
   1209		case WLAN_EID_IBSS_PARAMS:
   1210			network->atim_window = info_element->data[0];
   1211			LIBIPW_DEBUG_MGMT("WLAN_EID_IBSS_PARAMS: %d\n",
   1212					     network->atim_window);
   1213			break;
   1214
   1215		case WLAN_EID_CHALLENGE:
   1216			LIBIPW_DEBUG_MGMT("WLAN_EID_CHALLENGE: ignored\n");
   1217			break;
   1218
   1219		case WLAN_EID_VENDOR_SPECIFIC:
   1220			LIBIPW_DEBUG_MGMT("WLAN_EID_VENDOR_SPECIFIC: %d bytes\n",
   1221					     info_element->len);
   1222			if (!libipw_parse_qos_info_param_IE(info_element,
   1223							       network))
   1224				break;
   1225
   1226			if (info_element->len >= 4 &&
   1227			    info_element->data[0] == 0x00 &&
   1228			    info_element->data[1] == 0x50 &&
   1229			    info_element->data[2] == 0xf2 &&
   1230			    info_element->data[3] == 0x01) {
   1231				network->wpa_ie_len = min(info_element->len + 2,
   1232							  MAX_WPA_IE_LEN);
   1233				memcpy(network->wpa_ie, info_element,
   1234				       network->wpa_ie_len);
   1235			}
   1236			break;
   1237
   1238		case WLAN_EID_RSN:
   1239			LIBIPW_DEBUG_MGMT("WLAN_EID_RSN: %d bytes\n",
   1240					     info_element->len);
   1241			network->rsn_ie_len = min(info_element->len + 2,
   1242						  MAX_WPA_IE_LEN);
   1243			memcpy(network->rsn_ie, info_element,
   1244			       network->rsn_ie_len);
   1245			break;
   1246
   1247		case WLAN_EID_QOS_PARAMETER:
   1248			printk(KERN_ERR
   1249			       "QoS Error need to parse QOS_PARAMETER IE\n");
   1250			break;
   1251			/* 802.11h */
   1252		case WLAN_EID_PWR_CONSTRAINT:
   1253			network->power_constraint = info_element->data[0];
   1254			network->flags |= NETWORK_HAS_POWER_CONSTRAINT;
   1255			break;
   1256
   1257		case WLAN_EID_CHANNEL_SWITCH:
   1258			network->power_constraint = info_element->data[0];
   1259			network->flags |= NETWORK_HAS_CSA;
   1260			break;
   1261
   1262		case WLAN_EID_QUIET:
   1263			network->quiet.count = info_element->data[0];
   1264			network->quiet.period = info_element->data[1];
   1265			network->quiet.duration = info_element->data[2];
   1266			network->quiet.offset = info_element->data[3];
   1267			network->flags |= NETWORK_HAS_QUIET;
   1268			break;
   1269
   1270		case WLAN_EID_IBSS_DFS:
   1271			network->flags |= NETWORK_HAS_IBSS_DFS;
   1272			break;
   1273
   1274		case WLAN_EID_TPC_REPORT:
   1275			network->tpc_report.transmit_power =
   1276			    info_element->data[0];
   1277			network->tpc_report.link_margin = info_element->data[1];
   1278			network->flags |= NETWORK_HAS_TPC_REPORT;
   1279			break;
   1280
   1281		default:
   1282			LIBIPW_DEBUG_MGMT
   1283			    ("Unsupported info element: %s (%d)\n",
   1284			     get_info_element_string(info_element->id),
   1285			     info_element->id);
   1286			break;
   1287		}
   1288
   1289		length -= sizeof(*info_element) + info_element->len;
   1290		info_element =
   1291		    (struct libipw_info_element *)&info_element->
   1292		    data[info_element->len];
   1293	}
   1294
   1295	return 0;
   1296}
   1297
   1298static int libipw_handle_assoc_resp(struct libipw_device *ieee, struct libipw_assoc_response
   1299				       *frame, struct libipw_rx_stats *stats)
   1300{
   1301	struct libipw_network network_resp = { };
   1302	struct libipw_network *network = &network_resp;
   1303	struct net_device *dev = ieee->dev;
   1304
   1305	network->flags = 0;
   1306	network->qos_data.active = 0;
   1307	network->qos_data.supported = 0;
   1308	network->qos_data.param_count = 0;
   1309	network->qos_data.old_param_count = 0;
   1310
   1311	//network->atim_window = le16_to_cpu(frame->aid) & (0x3FFF);
   1312	network->atim_window = le16_to_cpu(frame->aid);
   1313	network->listen_interval = le16_to_cpu(frame->status);
   1314	memcpy(network->bssid, frame->header.addr3, ETH_ALEN);
   1315	network->capability = le16_to_cpu(frame->capability);
   1316	network->last_scanned = jiffies;
   1317	network->rates_len = network->rates_ex_len = 0;
   1318	network->last_associate = 0;
   1319	network->ssid_len = 0;
   1320	network->erp_value =
   1321	    (network->capability & WLAN_CAPABILITY_IBSS) ? 0x3 : 0x0;
   1322
   1323	if (stats->freq == LIBIPW_52GHZ_BAND) {
   1324		/* for A band (No DS info) */
   1325		network->channel = stats->received_channel;
   1326	} else
   1327		network->flags |= NETWORK_HAS_CCK;
   1328
   1329	network->wpa_ie_len = 0;
   1330	network->rsn_ie_len = 0;
   1331
   1332	if (libipw_parse_info_param
   1333	    (frame->info_element, stats->len - sizeof(*frame), network))
   1334		return 1;
   1335
   1336	network->mode = 0;
   1337	if (stats->freq == LIBIPW_52GHZ_BAND)
   1338		network->mode = IEEE_A;
   1339	else {
   1340		if (network->flags & NETWORK_HAS_OFDM)
   1341			network->mode |= IEEE_G;
   1342		if (network->flags & NETWORK_HAS_CCK)
   1343			network->mode |= IEEE_B;
   1344	}
   1345
   1346	memcpy(&network->stats, stats, sizeof(network->stats));
   1347
   1348	if (ieee->handle_assoc_response != NULL)
   1349		ieee->handle_assoc_response(dev, frame, network);
   1350
   1351	return 0;
   1352}
   1353
   1354/***************************************************/
   1355
   1356static int libipw_network_init(struct libipw_device *ieee, struct libipw_probe_response
   1357					 *beacon,
   1358					 struct libipw_network *network,
   1359					 struct libipw_rx_stats *stats)
   1360{
   1361	network->qos_data.active = 0;
   1362	network->qos_data.supported = 0;
   1363	network->qos_data.param_count = 0;
   1364	network->qos_data.old_param_count = 0;
   1365
   1366	/* Pull out fixed field data */
   1367	memcpy(network->bssid, beacon->header.addr3, ETH_ALEN);
   1368	network->capability = le16_to_cpu(beacon->capability);
   1369	network->last_scanned = jiffies;
   1370	network->time_stamp[0] = le32_to_cpu(beacon->time_stamp[0]);
   1371	network->time_stamp[1] = le32_to_cpu(beacon->time_stamp[1]);
   1372	network->beacon_interval = le16_to_cpu(beacon->beacon_interval);
   1373	/* Where to pull this? beacon->listen_interval; */
   1374	network->listen_interval = 0x0A;
   1375	network->rates_len = network->rates_ex_len = 0;
   1376	network->last_associate = 0;
   1377	network->ssid_len = 0;
   1378	network->flags = 0;
   1379	network->atim_window = 0;
   1380	network->erp_value = (network->capability & WLAN_CAPABILITY_IBSS) ?
   1381	    0x3 : 0x0;
   1382
   1383	if (stats->freq == LIBIPW_52GHZ_BAND) {
   1384		/* for A band (No DS info) */
   1385		network->channel = stats->received_channel;
   1386	} else
   1387		network->flags |= NETWORK_HAS_CCK;
   1388
   1389	network->wpa_ie_len = 0;
   1390	network->rsn_ie_len = 0;
   1391
   1392	if (libipw_parse_info_param
   1393	    (beacon->info_element, stats->len - sizeof(*beacon), network))
   1394		return 1;
   1395
   1396	network->mode = 0;
   1397	if (stats->freq == LIBIPW_52GHZ_BAND)
   1398		network->mode = IEEE_A;
   1399	else {
   1400		if (network->flags & NETWORK_HAS_OFDM)
   1401			network->mode |= IEEE_G;
   1402		if (network->flags & NETWORK_HAS_CCK)
   1403			network->mode |= IEEE_B;
   1404	}
   1405
   1406	if (network->mode == 0) {
   1407		LIBIPW_DEBUG_SCAN("Filtered out '%*pE (%pM)' network.\n",
   1408				  network->ssid_len, network->ssid,
   1409				  network->bssid);
   1410		return 1;
   1411	}
   1412
   1413	memcpy(&network->stats, stats, sizeof(network->stats));
   1414
   1415	return 0;
   1416}
   1417
   1418static inline int is_same_network(struct libipw_network *src,
   1419				  struct libipw_network *dst)
   1420{
   1421	/* A network is only a duplicate if the channel, BSSID, and ESSID
   1422	 * all match.  We treat all <hidden> with the same BSSID and channel
   1423	 * as one network */
   1424	return ((src->ssid_len == dst->ssid_len) &&
   1425		(src->channel == dst->channel) &&
   1426		ether_addr_equal_64bits(src->bssid, dst->bssid) &&
   1427		!memcmp(src->ssid, dst->ssid, src->ssid_len));
   1428}
   1429
   1430static void update_network(struct libipw_network *dst,
   1431				  struct libipw_network *src)
   1432{
   1433	int qos_active;
   1434	u8 old_param;
   1435
   1436	/* We only update the statistics if they were created by receiving
   1437	 * the network information on the actual channel the network is on.
   1438	 *
   1439	 * This keeps beacons received on neighbor channels from bringing
   1440	 * down the signal level of an AP. */
   1441	if (dst->channel == src->stats.received_channel)
   1442		memcpy(&dst->stats, &src->stats,
   1443		       sizeof(struct libipw_rx_stats));
   1444	else
   1445		LIBIPW_DEBUG_SCAN("Network %pM info received "
   1446			"off channel (%d vs. %d)\n", src->bssid,
   1447			dst->channel, src->stats.received_channel);
   1448
   1449	dst->capability = src->capability;
   1450	memcpy(dst->rates, src->rates, src->rates_len);
   1451	dst->rates_len = src->rates_len;
   1452	memcpy(dst->rates_ex, src->rates_ex, src->rates_ex_len);
   1453	dst->rates_ex_len = src->rates_ex_len;
   1454
   1455	dst->mode = src->mode;
   1456	dst->flags = src->flags;
   1457	dst->time_stamp[0] = src->time_stamp[0];
   1458	dst->time_stamp[1] = src->time_stamp[1];
   1459
   1460	dst->beacon_interval = src->beacon_interval;
   1461	dst->listen_interval = src->listen_interval;
   1462	dst->atim_window = src->atim_window;
   1463	dst->erp_value = src->erp_value;
   1464	dst->tim = src->tim;
   1465
   1466	memcpy(dst->wpa_ie, src->wpa_ie, src->wpa_ie_len);
   1467	dst->wpa_ie_len = src->wpa_ie_len;
   1468	memcpy(dst->rsn_ie, src->rsn_ie, src->rsn_ie_len);
   1469	dst->rsn_ie_len = src->rsn_ie_len;
   1470
   1471	dst->last_scanned = jiffies;
   1472	qos_active = src->qos_data.active;
   1473	old_param = dst->qos_data.old_param_count;
   1474	if (dst->flags & NETWORK_HAS_QOS_MASK)
   1475		memcpy(&dst->qos_data, &src->qos_data,
   1476		       sizeof(struct libipw_qos_data));
   1477	else {
   1478		dst->qos_data.supported = src->qos_data.supported;
   1479		dst->qos_data.param_count = src->qos_data.param_count;
   1480	}
   1481
   1482	if (dst->qos_data.supported == 1) {
   1483		if (dst->ssid_len)
   1484			LIBIPW_DEBUG_QOS
   1485			    ("QoS the network %s is QoS supported\n",
   1486			     dst->ssid);
   1487		else
   1488			LIBIPW_DEBUG_QOS
   1489			    ("QoS the network is QoS supported\n");
   1490	}
   1491	dst->qos_data.active = qos_active;
   1492	dst->qos_data.old_param_count = old_param;
   1493
   1494	/* dst->last_associate is not overwritten */
   1495}
   1496
   1497static inline int is_beacon(__le16 fc)
   1498{
   1499	return (WLAN_FC_GET_STYPE(le16_to_cpu(fc)) == IEEE80211_STYPE_BEACON);
   1500}
   1501
   1502static void libipw_process_probe_response(struct libipw_device
   1503						    *ieee, struct
   1504						    libipw_probe_response
   1505						    *beacon, struct libipw_rx_stats
   1506						    *stats)
   1507{
   1508	struct net_device *dev = ieee->dev;
   1509	struct libipw_network network = { };
   1510	struct libipw_network *target;
   1511	struct libipw_network *oldest = NULL;
   1512#ifdef CONFIG_LIBIPW_DEBUG
   1513	struct libipw_info_element *info_element = beacon->info_element;
   1514#endif
   1515	unsigned long flags;
   1516
   1517	LIBIPW_DEBUG_SCAN("'%*pE' (%pM): %c%c%c%c %c%c%c%c-%c%c%c%c %c%c%c%c\n",
   1518		     info_element->len, info_element->data,
   1519		     beacon->header.addr3,
   1520		     (beacon->capability & cpu_to_le16(1 << 0xf)) ? '1' : '0',
   1521		     (beacon->capability & cpu_to_le16(1 << 0xe)) ? '1' : '0',
   1522		     (beacon->capability & cpu_to_le16(1 << 0xd)) ? '1' : '0',
   1523		     (beacon->capability & cpu_to_le16(1 << 0xc)) ? '1' : '0',
   1524		     (beacon->capability & cpu_to_le16(1 << 0xb)) ? '1' : '0',
   1525		     (beacon->capability & cpu_to_le16(1 << 0xa)) ? '1' : '0',
   1526		     (beacon->capability & cpu_to_le16(1 << 0x9)) ? '1' : '0',
   1527		     (beacon->capability & cpu_to_le16(1 << 0x8)) ? '1' : '0',
   1528		     (beacon->capability & cpu_to_le16(1 << 0x7)) ? '1' : '0',
   1529		     (beacon->capability & cpu_to_le16(1 << 0x6)) ? '1' : '0',
   1530		     (beacon->capability & cpu_to_le16(1 << 0x5)) ? '1' : '0',
   1531		     (beacon->capability & cpu_to_le16(1 << 0x4)) ? '1' : '0',
   1532		     (beacon->capability & cpu_to_le16(1 << 0x3)) ? '1' : '0',
   1533		     (beacon->capability & cpu_to_le16(1 << 0x2)) ? '1' : '0',
   1534		     (beacon->capability & cpu_to_le16(1 << 0x1)) ? '1' : '0',
   1535		     (beacon->capability & cpu_to_le16(1 << 0x0)) ? '1' : '0');
   1536
   1537	if (libipw_network_init(ieee, beacon, &network, stats)) {
   1538		LIBIPW_DEBUG_SCAN("Dropped '%*pE' (%pM) via %s.\n",
   1539				  info_element->len, info_element->data,
   1540				  beacon->header.addr3,
   1541				  is_beacon(beacon->header.frame_ctl) ?
   1542				  "BEACON" : "PROBE RESPONSE");
   1543		return;
   1544	}
   1545
   1546	/* The network parsed correctly -- so now we scan our known networks
   1547	 * to see if we can find it in our list.
   1548	 *
   1549	 * NOTE:  This search is definitely not optimized.  Once its doing
   1550	 *        the "right thing" we'll optimize it for efficiency if
   1551	 *        necessary */
   1552
   1553	/* Search for this entry in the list and update it if it is
   1554	 * already there. */
   1555
   1556	spin_lock_irqsave(&ieee->lock, flags);
   1557
   1558	list_for_each_entry(target, &ieee->network_list, list) {
   1559		if (is_same_network(target, &network))
   1560			break;
   1561
   1562		if ((oldest == NULL) ||
   1563		    time_before(target->last_scanned, oldest->last_scanned))
   1564			oldest = target;
   1565	}
   1566
   1567	/* If we didn't find a match, then get a new network slot to initialize
   1568	 * with this beacon's information */
   1569	if (&target->list == &ieee->network_list) {
   1570		if (list_empty(&ieee->network_free_list)) {
   1571			/* If there are no more slots, expire the oldest */
   1572			list_del(&oldest->list);
   1573			target = oldest;
   1574			LIBIPW_DEBUG_SCAN("Expired '%*pE' (%pM) from network list.\n",
   1575					  target->ssid_len, target->ssid,
   1576					  target->bssid);
   1577		} else {
   1578			/* Otherwise just pull from the free list */
   1579			target = list_entry(ieee->network_free_list.next,
   1580					    struct libipw_network, list);
   1581			list_del(ieee->network_free_list.next);
   1582		}
   1583
   1584#ifdef CONFIG_LIBIPW_DEBUG
   1585		LIBIPW_DEBUG_SCAN("Adding '%*pE' (%pM) via %s.\n",
   1586				  network.ssid_len, network.ssid,
   1587				  network.bssid,
   1588				  is_beacon(beacon->header.frame_ctl) ?
   1589				  "BEACON" : "PROBE RESPONSE");
   1590#endif
   1591		memcpy(target, &network, sizeof(*target));
   1592		list_add_tail(&target->list, &ieee->network_list);
   1593	} else {
   1594		LIBIPW_DEBUG_SCAN("Updating '%*pE' (%pM) via %s.\n",
   1595				  target->ssid_len, target->ssid,
   1596				  target->bssid,
   1597				  is_beacon(beacon->header.frame_ctl) ?
   1598				  "BEACON" : "PROBE RESPONSE");
   1599		update_network(target, &network);
   1600	}
   1601
   1602	spin_unlock_irqrestore(&ieee->lock, flags);
   1603
   1604	if (is_beacon(beacon->header.frame_ctl)) {
   1605		if (ieee->handle_beacon != NULL)
   1606			ieee->handle_beacon(dev, beacon, target);
   1607	} else {
   1608		if (ieee->handle_probe_response != NULL)
   1609			ieee->handle_probe_response(dev, beacon, target);
   1610	}
   1611}
   1612
   1613void libipw_rx_mgt(struct libipw_device *ieee,
   1614		      struct libipw_hdr_4addr *header,
   1615		      struct libipw_rx_stats *stats)
   1616{
   1617	switch (WLAN_FC_GET_STYPE(le16_to_cpu(header->frame_ctl))) {
   1618	case IEEE80211_STYPE_ASSOC_RESP:
   1619		LIBIPW_DEBUG_MGMT("received ASSOCIATION RESPONSE (%d)\n",
   1620				     WLAN_FC_GET_STYPE(le16_to_cpu
   1621						       (header->frame_ctl)));
   1622		libipw_handle_assoc_resp(ieee,
   1623					    (struct libipw_assoc_response *)
   1624					    header, stats);
   1625		break;
   1626
   1627	case IEEE80211_STYPE_REASSOC_RESP:
   1628		LIBIPW_DEBUG_MGMT("received REASSOCIATION RESPONSE (%d)\n",
   1629				     WLAN_FC_GET_STYPE(le16_to_cpu
   1630						       (header->frame_ctl)));
   1631		break;
   1632
   1633	case IEEE80211_STYPE_PROBE_REQ:
   1634		LIBIPW_DEBUG_MGMT("received auth (%d)\n",
   1635				     WLAN_FC_GET_STYPE(le16_to_cpu
   1636						       (header->frame_ctl)));
   1637
   1638		if (ieee->handle_probe_request != NULL)
   1639			ieee->handle_probe_request(ieee->dev,
   1640						   (struct
   1641						    libipw_probe_request *)
   1642						   header, stats);
   1643		break;
   1644
   1645	case IEEE80211_STYPE_PROBE_RESP:
   1646		LIBIPW_DEBUG_MGMT("received PROBE RESPONSE (%d)\n",
   1647				     WLAN_FC_GET_STYPE(le16_to_cpu
   1648						       (header->frame_ctl)));
   1649		LIBIPW_DEBUG_SCAN("Probe response\n");
   1650		libipw_process_probe_response(ieee,
   1651						 (struct
   1652						  libipw_probe_response *)
   1653						 header, stats);
   1654		break;
   1655
   1656	case IEEE80211_STYPE_BEACON:
   1657		LIBIPW_DEBUG_MGMT("received BEACON (%d)\n",
   1658				     WLAN_FC_GET_STYPE(le16_to_cpu
   1659						       (header->frame_ctl)));
   1660		LIBIPW_DEBUG_SCAN("Beacon\n");
   1661		libipw_process_probe_response(ieee,
   1662						 (struct
   1663						  libipw_probe_response *)
   1664						 header, stats);
   1665		break;
   1666	case IEEE80211_STYPE_AUTH:
   1667
   1668		LIBIPW_DEBUG_MGMT("received auth (%d)\n",
   1669				     WLAN_FC_GET_STYPE(le16_to_cpu
   1670						       (header->frame_ctl)));
   1671
   1672		if (ieee->handle_auth != NULL)
   1673			ieee->handle_auth(ieee->dev,
   1674					  (struct libipw_auth *)header);
   1675		break;
   1676
   1677	case IEEE80211_STYPE_DISASSOC:
   1678		if (ieee->handle_disassoc != NULL)
   1679			ieee->handle_disassoc(ieee->dev,
   1680					      (struct libipw_disassoc *)
   1681					      header);
   1682		break;
   1683
   1684	case IEEE80211_STYPE_ACTION:
   1685		LIBIPW_DEBUG_MGMT("ACTION\n");
   1686		if (ieee->handle_action)
   1687			ieee->handle_action(ieee->dev,
   1688					    (struct libipw_action *)
   1689					    header, stats);
   1690		break;
   1691
   1692	case IEEE80211_STYPE_REASSOC_REQ:
   1693		LIBIPW_DEBUG_MGMT("received reassoc (%d)\n",
   1694				     WLAN_FC_GET_STYPE(le16_to_cpu
   1695						       (header->frame_ctl)));
   1696
   1697		LIBIPW_DEBUG_MGMT("%s: LIBIPW_REASSOC_REQ received\n",
   1698				     ieee->dev->name);
   1699		if (ieee->handle_reassoc_request != NULL)
   1700			ieee->handle_reassoc_request(ieee->dev,
   1701						    (struct libipw_reassoc_request *)
   1702						     header);
   1703		break;
   1704
   1705	case IEEE80211_STYPE_ASSOC_REQ:
   1706		LIBIPW_DEBUG_MGMT("received assoc (%d)\n",
   1707				     WLAN_FC_GET_STYPE(le16_to_cpu
   1708						       (header->frame_ctl)));
   1709
   1710		LIBIPW_DEBUG_MGMT("%s: LIBIPW_ASSOC_REQ received\n",
   1711				     ieee->dev->name);
   1712		if (ieee->handle_assoc_request != NULL)
   1713			ieee->handle_assoc_request(ieee->dev);
   1714		break;
   1715
   1716	case IEEE80211_STYPE_DEAUTH:
   1717		LIBIPW_DEBUG_MGMT("DEAUTH\n");
   1718		if (ieee->handle_deauth != NULL)
   1719			ieee->handle_deauth(ieee->dev,
   1720					    (struct libipw_deauth *)
   1721					    header);
   1722		break;
   1723	default:
   1724		LIBIPW_DEBUG_MGMT("received UNKNOWN (%d)\n",
   1725				     WLAN_FC_GET_STYPE(le16_to_cpu
   1726						       (header->frame_ctl)));
   1727		LIBIPW_DEBUG_MGMT("%s: Unknown management packet: %d\n",
   1728				     ieee->dev->name,
   1729				     WLAN_FC_GET_STYPE(le16_to_cpu
   1730						       (header->frame_ctl)));
   1731		break;
   1732	}
   1733}
   1734
   1735EXPORT_SYMBOL_GPL(libipw_rx_any);
   1736EXPORT_SYMBOL(libipw_rx_mgt);
   1737EXPORT_SYMBOL(libipw_rx);