Home | History | Annotate | Line # | Download | only in iomd
iomd_irq.S revision 1.4.16.2
      1  1.4.16.2     yamt /*	$NetBSD: iomd_irq.S,v 1.4.16.2 2008/01/21 09:35:44 yamt Exp $	*/
      2       1.1  reinoud 
      3       1.1  reinoud /*
      4       1.1  reinoud  * Copyright (c) 1994-1998 Mark Brinicombe.
      5       1.1  reinoud  * Copyright (c) 1994 Brini.
      6       1.1  reinoud  * All rights reserved.
      7       1.1  reinoud  *
      8       1.1  reinoud  * This code is derived from software written for Brini by Mark Brinicombe
      9       1.1  reinoud  *
     10       1.1  reinoud  * Redistribution and use in source and binary forms, with or without
     11       1.1  reinoud  * modification, are permitted provided that the following conditions
     12       1.1  reinoud  * are met:
     13       1.1  reinoud  * 1. Redistributions of source code must retain the above copyright
     14       1.1  reinoud  *    notice, this list of conditions and the following disclaimer.
     15       1.1  reinoud  * 2. Redistributions in binary form must reproduce the above copyright
     16       1.1  reinoud  *    notice, this list of conditions and the following disclaimer in the
     17       1.1  reinoud  *    documentation and/or other materials provided with the distribution.
     18       1.1  reinoud  * 3. All advertising materials mentioning features or use of this software
     19       1.1  reinoud  *    must display the following acknowledgement:
     20       1.1  reinoud  *	This product includes software developed by Mark Brinicombe
     21       1.1  reinoud  *	for the NetBSD Project.
     22       1.1  reinoud  * 4. The name of the company nor the name of the author may be used to
     23       1.1  reinoud  *    endorse or promote products derived from this software without specific
     24       1.1  reinoud  *    prior written permission.
     25       1.1  reinoud  *
     26       1.1  reinoud  * THIS SOFTWARE IS PROVIDED BY THE AUTHOR ``AS IS'' AND ANY EXPRESS OR
     27       1.1  reinoud  * IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES
     28       1.1  reinoud  * OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED.
     29       1.1  reinoud  * IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY DIRECT, INDIRECT,
     30       1.1  reinoud  * INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT
     31       1.1  reinoud  * NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE,
     32       1.1  reinoud  * DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY
     33       1.1  reinoud  * THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
     34       1.1  reinoud  * (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF
     35       1.1  reinoud  * THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
     36       1.1  reinoud  *
     37       1.1  reinoud  * Low level irq and fiq handlers
     38       1.1  reinoud  *
     39       1.1  reinoud  * Created      : 27/09/94
     40       1.1  reinoud  */
     41       1.1  reinoud 
     42       1.1  reinoud #include "opt_irqstats.h"
     43       1.1  reinoud 
     44       1.1  reinoud #include "assym.h"
     45       1.1  reinoud #include <machine/asm.h>
     46       1.1  reinoud #include <machine/cpu.h>
     47       1.1  reinoud #include <machine/frame.h>
     48       1.1  reinoud #include <arm/iomd/iomdreg.h>
     49       1.1  reinoud 
     50       1.1  reinoud 	.text
     51       1.1  reinoud 	.align	0
     52       1.1  reinoud /*
     53       1.1  reinoud  * ffs table used for servicing irq's quickly must be here otherwise adr can't
     54       1.1  reinoud  * reach it
     55       1.1  reinoud  * The algorithm for ffs was devised by D. Seal and posted to
     56       1.1  reinoud  * comp.sys.arm on 16 Feb 1994.
     57       1.1  reinoud  */
     58       1.1  reinoud .type Lirq_ffs_table, _ASM_TYPE_OBJECT;
     59       1.1  reinoud Lirq_ffs_table:
     60       1.1  reinoud /* same as ffs table but all nums are -1 from that */
     61       1.1  reinoud /*               0   1   2   3   4   5   6   7           */
     62       1.1  reinoud 	.byte	 0,  0,  1, 12,  2,  6,  0, 13  /*  0- 7 */
     63       1.1  reinoud 	.byte	 3,  0,  7,  0,  0,  0,  0, 14  /*  8-15 */
     64       1.1  reinoud 	.byte	10,  4,  0,  0,  8,  0,  0, 25  /* 16-23 */
     65       1.1  reinoud 	.byte	 0,  0,  0,  0,  0, 21, 27, 15  /* 24-31 */
     66       1.1  reinoud 	.byte	31, 11,  5,  0,  0,  0,  0,  0	/* 32-39 */
     67       1.1  reinoud 	.byte	 9,  0,  0, 24,  0,  0, 20, 26  /* 40-47 */
     68       1.1  reinoud 	.byte	30,  0,  0,  0,  0, 23,  0, 19  /* 48-55 */
     69       1.1  reinoud 	.byte   29,  0, 22, 18, 28, 17, 16,  0  /* 56-63 */
     70       1.1  reinoud 
     71       1.1  reinoud /*
     72       1.1  reinoud  *
     73       1.1  reinoud  * irq_entry
     74       1.1  reinoud  *
     75       1.1  reinoud  * Main entry point for the IRQ vector
     76       1.1  reinoud  *
     77       1.1  reinoud  * This function reads the irq request bits in the IOMD registers
     78       1.1  reinoud  * IRQRQA, IRQRQB and DMARQ
     79       1.1  reinoud  * It then calls an installed handler for each bit that is set.
     80       1.1  reinoud  * The function stray_irqhandler is called if a handler is not defined
     81       1.1  reinoud  * for a particular interrupt.
     82       1.1  reinoud  * If a interrupt handler is found then it is called with r0 containing
     83       1.1  reinoud  * the argument defined in the handler structure. If the field ih_arg
     84       1.1  reinoud  * is zero then a pointer to the IRQ frame on the stack is passed instead.
     85       1.1  reinoud  */
     86       1.1  reinoud 
     87       1.1  reinoud Ldisabled_mask:
     88       1.1  reinoud 	.word	_C_LABEL(disabled_mask)
     89       1.1  reinoud 
     90       1.1  reinoud Lcurrent_spl_level:
     91       1.1  reinoud 	.word	_C_LABEL(current_spl_level)
     92       1.1  reinoud 
     93       1.1  reinoud Lcurrent_intr_depth:
     94  1.4.16.2     yamt 	.word	_C_LABEL(cpu_info_store) + CI_IDEPTH
     95       1.1  reinoud 
     96       1.1  reinoud Lspl_masks:
     97       1.1  reinoud 	.word	_C_LABEL(spl_masks)
     98       1.1  reinoud 
     99  1.4.16.1     yamt LOCK_CAS_CHECK_LOCALS
    100  1.4.16.1     yamt 
    101       1.4      scw AST_ALIGNMENT_FAULT_LOCALS
    102       1.4      scw 
    103       1.1  reinoud /*
    104       1.1  reinoud  * Register usage
    105       1.1  reinoud  *
    106       1.1  reinoud  *  r5  - Address of ffs table
    107       1.1  reinoud  *  r6  - Address of current handler
    108       1.1  reinoud  *  r7  - Pointer to handler pointer list
    109       1.1  reinoud  *  r8  - Current IRQ requests.
    110       1.1  reinoud  *  r10 - Base address of IOMD
    111       1.1  reinoud  *  r11 - IRQ requests still to service.
    112       1.1  reinoud  */
    113       1.1  reinoud 
    114       1.1  reinoud Liomd_base:
    115       1.1  reinoud 	.word	_C_LABEL(iomd_base)
    116       1.1  reinoud 
    117       1.1  reinoud Larm7500_ioc_found:
    118       1.1  reinoud 	.word	_C_LABEL(arm7500_ioc_found)
    119       1.1  reinoud 
    120       1.1  reinoud ASENTRY_NP(irq_entry)
    121       1.1  reinoud 	sub	lr, lr, #0x00000004	/* Adjust the lr */
    122       1.1  reinoud 
    123       1.1  reinoud 	PUSHFRAMEINSVC			/* Push an interrupt frame */
    124       1.4      scw 	ENABLE_ALIGNMENT_FAULTS
    125       1.1  reinoud 
    126       1.1  reinoud 	/* Load r8 with the IOMD interrupt requests */
    127       1.1  reinoud 
    128       1.1  reinoud 	ldr	r10, Liomd_base
    129       1.1  reinoud  	ldr	r10, [r10]			/* Point to the IOMD */
    130       1.1  reinoud 	ldrb	r8, [r10, #(IOMD_IRQRQA << 2)]	/* Get IRQ request A */
    131       1.1  reinoud 	ldrb	r9, [r10, #(IOMD_IRQRQB << 2)]	/* Get IRQ request B */
    132       1.1  reinoud 	orr	r8, r8, r9, lsl #8
    133       1.1  reinoud 
    134       1.1  reinoud 	ldr	r9, Larm7500_ioc_found
    135       1.1  reinoud 	ldr	r9, [r9]			/* get the flag      */
    136       1.1  reinoud 	cmp	r9, #0
    137       1.1  reinoud 	beq	skip_extended_IRQs_reading
    138       1.1  reinoud 
    139       1.1  reinoud 	/* ARM 7500 only */
    140       1.1  reinoud 	ldrb	r9, [r10, #(IOMD_IRQRQC << 2)]	/* Get IRQ request C */
    141       1.1  reinoud 	orr	r8, r8, r9, lsl #16
    142       1.1  reinoud 	ldrb	r9, [r10, #(IOMD_IRQRQD << 2)]	/* Get IRQ request D */
    143       1.1  reinoud 	orr	r8, r8, r9, lsl #24
    144       1.1  reinoud 	ldrb	r9, [r10, #(IOMD_DMARQ << 2)]	/* Get DMA Request */
    145       1.1  reinoud 	tst	r9, #0x10
    146       1.1  reinoud 	orrne	r8, r8, r9, lsl #27
    147       1.1  reinoud 	b	irq_entry_continue
    148       1.1  reinoud 
    149       1.1  reinoud skip_extended_IRQs_reading:
    150       1.1  reinoud 	/* non ARM7500 machines */
    151       1.1  reinoud 	ldrb	r9, [r10, #(IOMD_DMARQ << 2)]	/* Get DMA Request */
    152       1.1  reinoud 	orr	r8, r8, r9, lsl #16
    153       1.1  reinoud irq_entry_continue:
    154       1.1  reinoud 
    155       1.1  reinoud 	and	r0, r8, #0x7d		/* Clear IOMD IRQA bits */
    156       1.1  reinoud 	strb	r0, [r10, #(IOMD_IRQRQA << 2)]
    157       1.1  reinoud 
    158       1.1  reinoud 	/*
    159       1.1  reinoud 	 * Note that we have entered the IRQ handler.
    160       1.1  reinoud 	 * We are in SVC mode so we cannot use the processor mode
    161       1.1  reinoud 	 * to determine if we are in an IRQ. Instead we will count the
    162       1.1  reinoud 	 * each time the interrupt handler is nested.
    163       1.1  reinoud 	 */
    164       1.1  reinoud 
    165       1.1  reinoud 	ldr	r0, Lcurrent_intr_depth
    166       1.1  reinoud 	ldr	r1, [r0]
    167       1.1  reinoud 	add	r1, r1, #1
    168       1.1  reinoud 	str	r1, [r0]
    169       1.1  reinoud 
    170       1.1  reinoud 	/* Block the current requested interrupts */
    171       1.1  reinoud 	ldr	r1, Ldisabled_mask
    172       1.1  reinoud 	ldr	r0, [r1]
    173       1.1  reinoud 	stmfd	sp!, {r0}
    174       1.1  reinoud 	orr	r0, r0, r8
    175       1.1  reinoud 
    176       1.1  reinoud 	/*
    177       1.1  reinoud  	 * Need to block all interrupts at the IPL or lower for
    178       1.1  reinoud 	 * all asserted interrupts.
    179       1.1  reinoud 	 * This basically emulates hardware interrupt priority levels.
    180       1.1  reinoud 	 * Means we need to go through the interrupt mask and for
    181       1.1  reinoud 	 * every asserted interrupt we need to mask out all other
    182       1.1  reinoud 	 * interrupts at the same or lower IPL.
    183       1.1  reinoud 	 * If only we could wait until the main loop but we need to sort
    184       1.1  reinoud 	 * this out first so interrupts can be re-enabled.
    185       1.1  reinoud 	 *
    186       1.1  reinoud 	 * This would benefit from a special ffs type routine
    187       1.1  reinoud 	 */
    188       1.1  reinoud 
    189       1.1  reinoud 	mov	r9, #(_SPL_LEVELS - 1)
    190       1.1  reinoud 	ldr	r7, Lspl_masks
    191       1.1  reinoud 
    192       1.1  reinoud Lfind_highest_ipl:
    193       1.1  reinoud 	ldr	r2, [r7, r9, lsl #2]
    194       1.1  reinoud 	tst	r8, r2
    195       1.1  reinoud 	subeq	r9, r9, #1
    196       1.1  reinoud 	beq	Lfind_highest_ipl
    197       1.1  reinoud 
    198       1.1  reinoud 	/* r9 = SPL level of highest priority interrupt */
    199       1.1  reinoud 	add	r9, r9, #1
    200       1.1  reinoud 	ldr	r2, [r7, r9, lsl #2]
    201       1.1  reinoud 	mvn	r2, r2
    202       1.1  reinoud 	orr	r0, r0, r2
    203       1.1  reinoud 
    204       1.1  reinoud 	str	r0, [r1]
    205       1.1  reinoud 
    206       1.1  reinoud 	ldr	r0, Lcurrent_spl_level
    207       1.1  reinoud 	ldr	r1, [r0]
    208       1.1  reinoud 	str	r9, [r0]
    209       1.1  reinoud 	stmfd	sp!, {r1}
    210       1.1  reinoud 
    211       1.1  reinoud 	/* Update the IOMD irq masks */
    212       1.1  reinoud 	bl	_C_LABEL(irq_setmasks)
    213       1.1  reinoud 
    214       1.1  reinoud         mrs     r0, cpsr_all		/* Enable IRQ's */
    215       1.1  reinoud 	bic	r0, r0, #I32_bit
    216       1.1  reinoud 	msr	cpsr_all, r0
    217       1.1  reinoud 
    218       1.3    bjh21 	ldr	r7, Lirqhandlers
    219       1.1  reinoud 
    220       1.1  reinoud 	/*
    221       1.1  reinoud 	 * take a copy of the IRQ request so that we can strip bits out of it
    222       1.1  reinoud 	 * note that we only use 24 bits with iomd2 chips
    223       1.1  reinoud 	 */
    224       1.1  reinoud 	ldr	r4, Larm7500_ioc_found
    225       1.1  reinoud 	ldr	r4, [r4]			/* get the flag      */
    226       1.1  reinoud 	cmp	r4, #0
    227       1.1  reinoud 	movne	r11, r8				/* ARM7500  -> copy all bits   */
    228       1.1  reinoud 	biceq	r11, r8, #0xff000000		/* !ARM7500 -> only use 24 bit */
    229       1.1  reinoud 
    230       1.1  reinoud 	/* ffs routine to find first irq to service */
    231       1.1  reinoud 	/* standard trick to isolate bottom bit in a0 or 0 if a0 = 0 on entry */
    232       1.1  reinoud 	rsb	r4, r11, #0
    233       1.1  reinoud 	ands	r10, r11, r4
    234       1.1  reinoud 
    235       1.1  reinoud 	/*
    236       1.1  reinoud 	 * now r10 has at most 1 set bit, call this X
    237       1.1  reinoud 	 * if X = 0, branch to exit code
    238       1.1  reinoud 	 */
    239       1.1  reinoud 	beq	exitirq
    240       1.1  reinoud 	adr	r5, Lirq_ffs_table
    241       1.1  reinoud irqloop:
    242       1.1  reinoud 	/*
    243       1.1  reinoud 	 * at this point:
    244       1.1  reinoud 	 *	r5 = address of ffs table
    245       1.1  reinoud 	 *	r7 = address of irq handlers table
    246       1.1  reinoud 	 *	r8 = irq request
    247       1.1  reinoud 	 *	r10 = bit of irq to be serviced
    248       1.1  reinoud 	 *	r11 = bitmask of IRQ's to service
    249       1.1  reinoud 	 */
    250       1.1  reinoud 
    251       1.1  reinoud 	/* find the set bit */
    252       1.1  reinoud 	orr	r9, r10, r10, lsl #4	/* X * 0x11 */
    253       1.1  reinoud 	orr	r9, r9, r9, lsl #6	/* X * 0x451 */
    254       1.1  reinoud 	rsb	r9, r9, r9, lsl #16	/* X * 0x0450fbaf */
    255       1.1  reinoud 	/* fetch the bit number */
    256       1.1  reinoud 	ldrb	r9, [r5, r9, lsr #26 ]
    257       1.1  reinoud 
    258       1.1  reinoud 	/*
    259       1.1  reinoud 	 * r9 = irq to service
    260       1.1  reinoud 	 */
    261       1.1  reinoud 
    262       1.1  reinoud 	/* apologies for the dogs dinner of code here, but it's in an attempt
    263       1.1  reinoud 	 * to minimise stalling on SA's, hence lots of things happen here:
    264       1.1  reinoud 	 *	- getting address of handler, if it doesn't exist we call
    265       1.1  reinoud 	 *	  stray_irqhandler this is assumed to be rare so we don't
    266       1.1  reinoud 	 *	  care about performance for it
    267       1.1  reinoud 	 *	- statinfo is updated
    268       1.1  reinoud 	 *	- unsetting of the irq bit in r11
    269       1.1  reinoud 	 *	- irq stats (if enabled) also get put in the mix
    270       1.1  reinoud 	 */
    271       1.1  reinoud 	ldr	r4, Lcnt		/* Stat info A */
    272       1.1  reinoud 	ldr	r6, [r7, r9, lsl #2]	/* Get address of first handler structure */
    273       1.1  reinoud 
    274       1.1  reinoud 	ldr	r1, [r4, #(V_INTR)]	/* Stat info B */
    275       1.1  reinoud 
    276       1.1  reinoud 	teq	r6, #0x00000000		/* Do we have a handler */
    277       1.1  reinoud 	moveq	r0, r8			/* IRQ requests as arg 0 */
    278       1.3    bjh21 	adreq	lr, nextirq		/* return Address */
    279       1.1  reinoud 	beq	_C_LABEL(stray_irqhandler) /* call special handler */
    280       1.1  reinoud 
    281       1.1  reinoud #ifdef IRQSTATS
    282       1.1  reinoud 	ldr	r2, Lintrcnt
    283       1.1  reinoud 	ldr	r3, [r6, #(IH_NUM)]
    284       1.1  reinoud #endif
    285       1.1  reinoud 	/* stat info C */
    286       1.1  reinoud 	add	r1, r1, #0x00000001
    287       1.1  reinoud 	str	r1, [r4, #(V_INTR)]
    288       1.1  reinoud 
    289       1.1  reinoud #ifdef IRQSTATS
    290       1.1  reinoud 	ldr	r3, [r2, r3, lsl #2]!
    291       1.1  reinoud #endif
    292       1.1  reinoud 	bic	r11, r11, r10		/* clear the IRQ bit */
    293       1.1  reinoud 
    294       1.1  reinoud #ifdef IRQSTATS
    295       1.1  reinoud 	add	r3, r3, #0x00000001
    296       1.1  reinoud 	str	r3, [r2]
    297       1.1  reinoud #endif	/* IRQSTATS */
    298       1.1  reinoud 
    299       1.1  reinoud irqchainloop:
    300       1.1  reinoud 	ldr	r0, [r6, #(IH_ARG)]	/* Get argument pointer */
    301       1.1  reinoud 	teq	r0, #0x00000000		/* If arg is zero pass stack frame */
    302       1.1  reinoud 	addeq	r0, sp, #8		/* ... stack frame [XXX needs care] */
    303       1.3    bjh21 	mov	lr, pc			/* return address */
    304       1.1  reinoud 	ldr	pc, [r6, #(IH_FUNC)]	/* Call handler */
    305       1.1  reinoud 
    306       1.1  reinoud 	ldr	r6, [r6, #(IH_NEXT)]	/* fetch next handler */
    307       1.1  reinoud 
    308       1.1  reinoud 	teq	r0, #0x00000001		/* Was the irq serviced ? */
    309       1.1  reinoud 
    310       1.1  reinoud 	/* if it was it'll just fall through this: */
    311       1.1  reinoud 	teqne	r6, #0x00000000
    312       1.1  reinoud 	bne	irqchainloop
    313       1.1  reinoud nextirq:
    314       1.1  reinoud 	/* Check for next irq */
    315       1.1  reinoud 	rsb	r4, r11, #0
    316       1.1  reinoud 	ands	r10, r11, r4
    317       1.1  reinoud 	/* check if there are anymore irq's to service */
    318       1.1  reinoud 	bne 	irqloop
    319       1.1  reinoud 
    320       1.1  reinoud exitirq:
    321       1.1  reinoud 	ldmfd	sp!, {r2, r3}
    322       1.1  reinoud 	ldr	r9, Lcurrent_spl_level
    323       1.1  reinoud 	ldr	r1, Ldisabled_mask
    324       1.1  reinoud 	str	r2, [r9]
    325       1.1  reinoud 	str	r3, [r1]
    326       1.1  reinoud 
    327       1.1  reinoud 	bl	_C_LABEL(irq_setmasks)
    328       1.1  reinoud 
    329  1.4.16.2     yamt #if __HAVE_FAST_SOFTINTS
    330       1.1  reinoud 	bl	_C_LABEL(dosoftints)	/* Handle the soft interrupts */
    331  1.4.16.2     yamt #endif
    332       1.1  reinoud 
    333       1.1  reinoud 	/* Kill IRQ's in preparation for exit */
    334       1.1  reinoud         mrs     r0, cpsr_all
    335       1.1  reinoud         orr     r0, r0, #(I32_bit)
    336       1.1  reinoud         msr     cpsr_all, r0
    337       1.1  reinoud 
    338       1.1  reinoud 	/* Decrement the nest count */
    339       1.1  reinoud 	ldr	r0, Lcurrent_intr_depth
    340       1.1  reinoud 	ldr	r1, [r0]
    341       1.1  reinoud 	sub	r1, r1, #1
    342       1.1  reinoud 	str	r1, [r0]
    343       1.1  reinoud 
    344  1.4.16.1     yamt 	LOCK_CAS_CHECK
    345  1.4.16.1     yamt 
    346       1.4      scw 	DO_AST_AND_RESTORE_ALIGNMENT_FAULTS
    347       1.1  reinoud 	PULLFRAMEFROMSVCANDEXIT
    348       1.1  reinoud 
    349       1.1  reinoud 	/* NOT REACHED */
    350       1.1  reinoud 	b	. - 8
    351       1.1  reinoud 
    352       1.1  reinoud Lcurrent_mask:
    353       1.1  reinoud 	.word	_C_LABEL(current_mask)	/* irq's that are usable */
    354       1.1  reinoud 
    355       1.1  reinoud ENTRY(irq_setmasks)
    356       1.1  reinoud 	/* Disable interrupts */
    357       1.1  reinoud 	mrs	r3, cpsr_all
    358       1.1  reinoud 	orr	r1, r3,  #(I32_bit)
    359       1.1  reinoud 	msr	cpsr_all, r1
    360       1.1  reinoud 
    361       1.1  reinoud 	/* Calculate IOMD interrupt mask */
    362       1.1  reinoud 	ldr	r1, Lcurrent_mask	/* All the enabled interrupts */
    363       1.1  reinoud 	ldr	r1, [r1]
    364  1.4.16.1     yamt 	ldr	r0, Lspl_masks		/* Block due to current spl level */
    365  1.4.16.1     yamt 	ldr	r2, Lcurrent_spl_level
    366       1.1  reinoud 	ldr	r2, [r2]
    367  1.4.16.1     yamt 	ldr	r2, [r0, r2, lsl #2]
    368       1.1  reinoud 	and	r1, r1, r2
    369       1.1  reinoud 	ldr	r2, Ldisabled_mask	/* Block due to active interrupts */
    370       1.1  reinoud 	ldr	r2, [r2]
    371       1.1  reinoud 	bic	r1, r1, r2
    372       1.1  reinoud 
    373       1.1  reinoud 	ldr	r0, Liomd_base
    374       1.1  reinoud  	ldr	r0, [r0]			/* Point to the IOMD */
    375       1.1  reinoud 	strb	r1, [r0, #(IOMD_IRQMSKA << 2)]	/* Set IRQ mask A */
    376       1.1  reinoud 	mov	r1, r1, lsr #8
    377       1.1  reinoud 	strb	r1, [r0, #(IOMD_IRQMSKB << 2)]	/* Set IRQ mask B */
    378       1.1  reinoud 	mov	r1, r1, lsr #8
    379       1.1  reinoud 
    380       1.1  reinoud 	ldr	r2, Larm7500_ioc_found
    381       1.1  reinoud 	ldr	r2, [r2]
    382       1.1  reinoud 	cmp	r2, #0
    383       1.1  reinoud 	beq	skip_setting_extended_DMA_mask
    384       1.1  reinoud 
    385       1.1  reinoud 	/* only for ARM7500's */
    386       1.1  reinoud 	strb	r1, [r0, #(IOMD_IRQMSKC << 2)]
    387       1.1  reinoud 	mov	r1, r1, lsr #8
    388       1.1  reinoud 	and	r2, r1, #0xef
    389       1.1  reinoud 	strb	r2, [r0, #(IOMD_IRQMSKD << 2)]
    390       1.1  reinoud 	mov	r1, r1, lsr #3
    391       1.1  reinoud 	and	r2, r1, #0x10
    392       1.1  reinoud 	strb	r2, [r0, #(IOMD_DMAMSK << 2)]	/* Set DMA mask */
    393       1.1  reinoud 	b	continue_setting_masks
    394       1.1  reinoud 
    395       1.1  reinoud skip_setting_extended_DMA_mask:
    396       1.1  reinoud 	/* non ARM7500's */
    397       1.1  reinoud 	strb	r1, [r0, #(IOMD_DMAMSK << 2)]	/* Set DMA mask */
    398       1.1  reinoud 
    399       1.1  reinoud continue_setting_masks:
    400       1.1  reinoud 
    401       1.1  reinoud 	/* Restore old cpsr and exit */
    402       1.1  reinoud 	msr	cpsr_all, r3
    403       1.1  reinoud 	mov	pc, lr
    404       1.1  reinoud 
    405       1.1  reinoud Lcnt:
    406       1.1  reinoud 	.word	_C_LABEL(uvmexp)
    407       1.1  reinoud 
    408       1.1  reinoud Lintrcnt:
    409       1.1  reinoud 	.word	_C_LABEL(intrcnt)
    410       1.1  reinoud 
    411       1.1  reinoud 
    412       1.1  reinoud Lirqhandlers:
    413       1.1  reinoud 	.word	_C_LABEL(irqhandlers)	/* Pointer to array of irqhandlers */
    414       1.1  reinoud 
    415       1.1  reinoud #ifdef IRQSTATS
    416       1.1  reinoud /* These symbols are used by vmstat */
    417       1.1  reinoud 
    418       1.1  reinoud 	.text
    419       1.1  reinoud 	.global	_C_LABEL(_intrnames)
    420       1.1  reinoud _C_LABEL(_intrnames):
    421       1.1  reinoud 	.word	_C_LABEL(intrnames)
    422       1.1  reinoud 
    423       1.1  reinoud 	.data
    424       1.1  reinoud 
    425       1.1  reinoud         .globl  _C_LABEL(intrnames), _C_LABEL(eintrnames), _C_LABEL(intrcnt), _C_LABEL(sintrcnt), _C_LABEL(eintrcnt)
    426       1.1  reinoud _C_LABEL(intrnames):
    427       1.1  reinoud 	.asciz	"interrupt  0 "
    428       1.1  reinoud 	.asciz	"interrupt  1 "	/* reserved0 */
    429       1.1  reinoud 	.asciz	"interrupt  2 "
    430       1.1  reinoud 	.asciz	"interrupt  3 "
    431       1.1  reinoud 	.asciz	"interrupt  4 "
    432       1.1  reinoud 	.asciz	"interrupt  5 "
    433       1.1  reinoud 	.asciz	"interrupt  6 "
    434       1.1  reinoud 	.asciz	"interrupt  7 "	/* reserved1 */
    435       1.1  reinoud 	.asciz	"interrupt  8 " /* reserved2 */
    436       1.1  reinoud 	.asciz	"interrupt  9 "
    437       1.1  reinoud 	.asciz	"interrupt 10 "
    438       1.1  reinoud 	.asciz	"interrupt 11 "
    439       1.1  reinoud 	.asciz	"interrupt 12 "
    440       1.1  reinoud 	.asciz	"interrupt 13 "
    441       1.1  reinoud 	.asciz	"interrupt 14 "
    442       1.1  reinoud 	.asciz	"interrupt 15 "
    443       1.1  reinoud 	.asciz	"dma channel 0"
    444       1.1  reinoud 	.asciz	"dma channel 1"
    445       1.1  reinoud 	.asciz	"dma channel 2"
    446       1.1  reinoud 	.asciz	"dma channel 3"
    447       1.1  reinoud 	.asciz	"interrupt 20 "
    448       1.1  reinoud 	.asciz	"interrupt 21 "
    449       1.1  reinoud 	.asciz	"reserved 3   "
    450       1.1  reinoud 	.asciz	"reserved 4   "
    451       1.1  reinoud 	.asciz	"exp card 0   "
    452       1.1  reinoud 	.asciz	"exp card 1   "
    453       1.1  reinoud 	.asciz	"exp card 2   "
    454       1.1  reinoud 	.asciz	"exp card 3   "
    455       1.1  reinoud 	.asciz	"exp card 4   "
    456       1.1  reinoud 	.asciz	"exp card 5   "
    457       1.1  reinoud 	.asciz	"exp card 6   "
    458       1.1  reinoud 	.asciz	"exp card 7   "
    459       1.1  reinoud 
    460       1.1  reinoud _C_LABEL(sintrnames):
    461       1.1  reinoud 	.asciz	"softclock    "
    462       1.1  reinoud 	.asciz	"softnet      "
    463       1.1  reinoud 	.asciz	"softserial   "
    464       1.1  reinoud 	.asciz	"softintr  3  "
    465       1.1  reinoud 	.asciz	"softintr  4  "
    466       1.1  reinoud 	.asciz	"softintr  5  "
    467       1.1  reinoud 	.asciz	"softintr  6  "
    468       1.1  reinoud 	.asciz	"softintr  7   "
    469       1.1  reinoud 	.asciz	"softintr  8  "
    470       1.1  reinoud 	.asciz	"softintr  9  "
    471       1.1  reinoud 	.asciz	"softintr 10  "
    472       1.1  reinoud 	.asciz	"softintr 11  "
    473       1.1  reinoud 	.asciz	"softintr 12  "
    474       1.1  reinoud 	.asciz	"softintr 13  "
    475       1.1  reinoud 	.asciz	"softintr 14  "
    476       1.1  reinoud 	.asciz	"softintr 15  "
    477       1.1  reinoud 	.asciz	"softintr 16  "
    478       1.1  reinoud 	.asciz	"softintr 17  "
    479       1.1  reinoud 	.asciz	"softintr 18  "
    480       1.1  reinoud 	.asciz	"softintr 19  "
    481       1.1  reinoud 	.asciz	"softintr 20  "
    482       1.1  reinoud 	.asciz	"softintr 21  "
    483       1.1  reinoud 	.asciz	"softintr 22  "
    484       1.1  reinoud 	.asciz	"softintr 23  "
    485       1.1  reinoud 	.asciz	"softintr 24  "
    486       1.1  reinoud 	.asciz	"softintr 25  "
    487       1.1  reinoud 	.asciz	"softintr 26  "
    488       1.1  reinoud 	.asciz	"softintr 27  "
    489       1.1  reinoud 	.asciz	"softintr 28  "
    490       1.1  reinoud 	.asciz	"softintr 29  "
    491       1.1  reinoud 	.asciz	"softintr 30  "
    492       1.1  reinoud 	.asciz	"softintr 31  "
    493       1.1  reinoud _C_LABEL(eintrnames):
    494       1.1  reinoud 
    495       1.1  reinoud 	.bss
    496       1.1  reinoud 	.align	0
    497       1.1  reinoud _C_LABEL(intrcnt):
    498       1.1  reinoud 	.space	32*4	/* XXX Should be linked to number of interrupts */
    499       1.1  reinoud 
    500       1.1  reinoud _C_LABEL(sintrcnt):
    501       1.1  reinoud 	.space	32*4	/* XXX Should be linked to number of interrupts */
    502       1.1  reinoud _C_LABEL(eintrcnt):
    503       1.1  reinoud 
    504       1.1  reinoud #else	/* IRQSTATS */
    505       1.1  reinoud 	/* Dummy entries to keep vmstat happy */
    506       1.1  reinoud 
    507       1.1  reinoud 	.text
    508       1.1  reinoud         .globl  _C_LABEL(intrnames), _C_LABEL(eintrnames), _C_LABEL(intrcnt), _C_LABEL(eintrcnt)
    509       1.1  reinoud _C_LABEL(intrnames):
    510       1.1  reinoud 	.long	0
    511       1.1  reinoud _C_LABEL(eintrnames):
    512       1.1  reinoud 
    513       1.1  reinoud _C_LABEL(intrcnt):
    514       1.1  reinoud 	.long	0
    515       1.1  reinoud _C_LABEL(eintrcnt):
    516       1.1  reinoud #endif	/* IRQSTATS */
    517