Source
...
Target
......@@ -18,3 +18,4 @@
#define USBDriver_InsertTransfer 0x054a42
#define USBDriver_TransferComplete 0x054a43
#define USBDriver_ScheduleSoftInterrupt 0x054a44
#define USBDriver_Version 0x054a45
; Copyright 2011 Castle Technology Ltd
;
; Licensed under the Apache License, Version 2.0 (the "License");
; you may not use this file except in compliance with the License.
; You may obtain a copy of the License at
;
; http://www.apache.org/licenses/LICENSE-2.0
;
; Unless required by applicable law or agreed to in writing, software
; distributed under the License is distributed on an "AS IS" BASIS,
; WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
; See the License for the specific language governing permissions and
; limitations under the License.
;
; Simple heap manager for HAL USB drivers. This is a hacked apart version of
; the OS_Heap code, with the following changes:
;
; * Support for re-entrancy removed, since the HAL can't really gain access
; to IRQSema. Instead, all heap ops run with IRQs disabled.
; * No support for expanding/describing the heap, etc.
; * Proper support for aligned allocs. Rather than using the cheap-and-nasty
; hack of allocating (blocksize+align) it considers each free block on a case
; by case basis to work out whether it can be used to satisfy the size &
; alignment constriants, then allocates the appropriate subsection of the
; free block.
; * Register allocation & calling conventions tweaked:
; - Uses HAL-compatible calling conventions
; - InitHeap: hpd = r0, size = r1
; - GetArea: hpd = r0, size = r1, result in R0 (either a pointer or NULL)
; - FreeArea: hpd = r0, addr = r1
; * Some debugging/error checking code maintained, other bits stripped out.
; Debug code will need converting to use HAL-friendly macros before it can be
; used.
; * Added GetAreaAligned, for memory-efficient allocation of aligned blocks:
; hpd = r0, size = r1, alignment = r2, result in R0 (either a pointer or NULL)
GET Hdr:ListOpts
GET Hdr:Macros
GET Hdr:System
GET Hdr:Machine.<Machine>
GET Hdr:ImageSize.<ImageSize>
AREA |C$$code|, CODE, READONLY
EXPORT HALHeap_InitHeap
EXPORT HALHeap_GetArea
EXPORT HALHeap_GetAreaAligned
EXPORT HALHeap_FreeArea
GBLL debheap
debheap SETL 1=0
GBLL bkptonfail
bkptonfail SETL {TRUE}
Nil * 0
hpd RN r0 ; The punter sees these
size RN r1
addr RN r2
work RN r3 ; But not these
tp RN r4
bp RN r5
HpTemp RN r12
; +++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
; + H E A P O R G A N I S A T I O N +
; +++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
; A heap block descriptor (hpd) has the form
; +--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+ -+ -+ -+ -+
; | magic | free | base | end | debug |
; +--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+--+- +- +- +- +
; 0 1 2 3 4 5 6 7 8 9 10 11 12 13 14 15 16 17 18 19 20
^ 0, hpd
hpdmagic # 4
hpdfree # 4
hpdbase # 4
hpdend # 4 ; Needed for debugging heap, and top end validation
[ debheap
hpddebug # 4 ; 0 -> No debug, ~0 -> Debug
]
hpdsize * @-hpdmagic
magic_heap_descriptor * (((((("p":SHL:8)+"a"):SHL:8)+"e"):SHL:8)+"H")
; hpdmagic is a unique identification field
; hpdfree is the offset of the first block in the free space list
; hpdbase is the offset of the byte above the last one used
; hpdend is the offset of the byte above the last one usable
; | hpdbase
; \|/
; +---+--------------------+--------+
; low |hpd| heap blocks | unused | high
; +---+--------------------+---------+
; /|\ /|\ 
; | hpdfree | hpdend
; | in here somewhere.
; +++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
; Blocks in the free space list have the form :
; +--+--+--+--+--+--+--+--+--+ ~ -+--+
; | long link | long size | |
; +--+--+--+--+--+--+--+--+--+ ~ -+--+
; 0 1 2 3 4 5 6 7 8 (size-1)
;
; where the link field is an offset to the next free block
^ 0 ; Can't use register relative unfortunately as many regs used
frelink # 4
fresize # 4
freblksize # 0
; The link field is Nil (0) for the last block in the list
; Block sizes must be forced to a multiple of 8 bytes for subsequent link and
; size information to be stored in them if they are disposed of by the user.
; They must also be capable of storing a 4 byte size field while allocated.
; This field is used to size the block to free when FreeArea is called.
ALIGN
; +++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
;
; InitHeap. Top level HeapEntry
; ========
;
; Initialise a heap descriptor block
; In : hpd -> block to initialise, size = size of block
; To initialise (or even reinitialise) a heap descriptor:
; $(
; hpd!magic := magic_heap_descriptor
; hpd!free := Nil
; hpd!base := hpdsize
; hpd!end := size
; $)
HALHeap_InitHeap
LDR HpTemp, =magic_heap_descriptor
STR HpTemp, hpdmagic ; hpd!magic := magic_heap_desc
MOV HpTemp, #Nil
STR HpTemp, hpdfree ; hpd!free := Nil
MOV HpTemp, #hpdsize
STR HpTemp, hpdbase ; hpd!base := hpdsize
STR size, hpdend ; hpd!end := size
[ debheap
MOV HpTemp, #0 ; No debugging until the punter sets this Word
STR HpTemp, hpddebug
]
MOV pc, lr
LTORG
; +++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
;
; GetArea. Top level HeapEntry
; =======
;
; Allocate a block of memory from the heap
; This will allocate the first block of sufficiently large size in the free
; list, with an oversize block being split.
; Failure to find a large enough block on the free list will try to claim
; space out of the heap block.
; Fails if requesting size = 0
; In : hpd -> heap pointer, size = size of block required
; Out : R0 -> got a block
; R0 = 0, couldn't get block
HALHeap_GetArea
MRS ip, CPSR
Push "tp,bp,ip,lr"
ORR ip, ip, #I32_bit
MSR CPSR_c, ip
[ debheap
; HpTemp not critical
LDR HpTemp, hpddebug
CMP HpTemp, #0
BEQ %FT00
Push "r0, link"
MOV r0, size
DREG r0, "GetArea "
BL iShowHeap
Pull "r0, link"
00
]
CMP size, #0 ; Can't deallocate 0, so there!
BLE garfailed_zero ; And -ve is invalid as well!
; note sizes of many megabytes thrown out by looking.
ADD size, size, #(freblksize-1)+4 ; Make block size granular
BIC size, size, #(freblksize-1) ; with size field added
ADR addr, hpdfree-frelink ; addr:= @(hpd!free)-frelink
garloop
LDR tp, [addr, #frelink] ; tp := addr!fre.link
CMP tp, #Nil ; Is this the end of the chain ?
BEQ garmore ; - so try main blk
ADD addr, addr, tp ; convert offset
LDR HpTemp, [addr, #fresize] ; If length < size then no good
SUBS HpTemp, HpTemp, size ; In case this works, for below split
BLO garloop
; Now addr -> a block on the free space list that our item will fit in
; If we have an exact fit (or as close as the granularity of the free list will
; allow), unlink this block and return it
BNE SplitFreeBlock
[ debheap
LDR HpTemp, hpddebug
CMP HpTemp, #0
BEQ %FT60
WRLN "Got an exact fit block"
60
]
LDR HpTemp, [addr, #frelink] ; Move this block's link field
CMP HpTemp, #Nil
ADDNE HpTemp, HpTemp, tp ; convert offset into offset from
; previous block
ASSERT frelink=0
STR HpTemp, [addr, -tp] ; store in link of previous block
B ResultIsAddrPlus4
SplitFreeBlock
; Need to split the free block, returning the end portion to the caller
[ debheap
; HpTemp critical
Push HpTemp
LDR HpTemp, hpddebug
CMP HpTemp, #0
BEQ %FT70
WRLN "Splitting free block"
70
Pull HpTemp
]
STR HpTemp, [addr, #fresize] ; Adjust size of free block remaining
ADD addr, addr, HpTemp ; addr -> free block just deallocated
ResultIsAddrPlus4
STR size, [addr] ; Store block size
ADD r0, addr, #4 ; Move to correct return reg & add offset
Pull "tp,bp,ip,lr"
MSR CPSR_c, ip
MOV pc, lr
; Got no more free blocks of length >= size, so try to allocate more heap space
; out of the block described by hpd
garmore
[ debheap
; HpTemp not critical
LDR HpTemp, hpddebug
CMP HpTemp, #0
BEQ %FT80
WRLN "Trying to get more from main block"
80
]
LDR addr, hpdbase
ADD tp, addr, size ; addr := (hpd!base +:= size)
LDR HpTemp, hpdend
CMP tp, HpTemp ; See if we'd fall out of the bottom
STRLS tp, hpdbase ; Only adjust hpdbase if valid alloc
ADDLS addr, addr, hpd ; offset conversion
BLS ResultIsAddrPlus4
[ debheap
STRIM "Not enough room to allocate in main block"
]
garfailed
[ debheap
WRLN " : GetArea failed"
]
garfail_common
[ bkptonfail
BKPT &123
]
MOV R0, #0 ; addr := 0 if we couldn't allocate
Pull "tp,bp,ip,lr"
MSR CPSR_c, ip
MOV pc, lr
[ debheap
garfailed_zero
STRIM "Can't allocate 0 or less bytes"
B garfailed
|
garfailed_zero * garfailed
]
; +++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
;
; GetAreaAligned. Top level HeapEntry
; ==============
;
; Allocate an aligned block of memory from the heap
; This is the same as GetArea, except it will only allocate areas with the given
; (power-of-two) alignment.
; Fails if requesting size = 0
; In : hpd -> heap pointer, size = size of block required, addr = alignment
; Out : R0 -> got a block
; R0 = 0, couldn't get block
HALHeap_GetAreaAligned
MRS ip, CPSR
Push "tp,bp,ip,lr"
ORR ip, ip, #I32_bit
MSR CPSR_c, ip
CMP size, #0 ; Can't deallocate 0, so there!
BLE garfailed_zero ; And -ve is invalid as well!
; note sizes of many megabytes thrown out by looking.
ADD size, size, #(freblksize-1) ; Make block size granular
BIC size, size, #(freblksize-1)
SUB bp, addr, #1 ; Store alignment-1 in bp
CMP bp, #3
MOVLT bp, #3 ; Minimum alignment is 4
ADR addr, hpdfree-frelink ; addr:= @(hpd!free)-frelink
garaloop
LDR tp, [addr, #frelink] ; tp := addr!fre.link
CMP tp, #Nil ; Is this the end of the chain ?
BEQ garamore ; - so try main blk
ADD addr, addr, tp ; convert offset
LDR HpTemp, [addr, #fresize]
; Calculate start and end addresses as if we were to allocate from this block
ADD work,addr,#4 ; 4 bytes for storing block size
ADD work,work,bp
garaloop2
BIC work,work,bp ; work = start of user block
SUB lr,work,addr
CMP lr,#4
BEQ garastartok ; Start alignment is exact
CMP lr,#freblksize+4
BGE garastartok ; Enough space to fit a free block at the start
; We need a free block, but there isn't enough space for it.
; Shift 'work' up by one unit of alignment and try again.
ADD work,work,bp,LSL #1
B garaloop2
garastartok
; Calculate block end address
ADD lr,work,size ; End of user block
ADD HpTemp,HpTemp,addr ; End of free block
SUBS lr,HpTemp,lr ; Gap after user block
BLO garaloop ; Not big enough
; We have a suitable space to allocate from.
ADD size,size,#4 ; Correct size to store
SUB work,work,#4 ; Correct block start
; Work out if we need a new free block afterwards
CMP lr, #freblksize
ADDLT size, size, lr ; Not enough space, so enlarge allocated block
BLT %FT10
; Create a new free block that will lie after our allocated block
SUB HpTemp, HpTemp, lr
STR lr, [HpTemp, #fresize] ; Write size
LDR lr, [addr, #frelink]
CMP lr, #Nil
ADDNE lr, lr, addr
SUBNE lr, lr, HpTemp
STR lr, [HpTemp, #frelink] ; Write next ptr
SUB HpTemp, HpTemp, addr
STR HpTemp, [addr, #frelink] ; Fix up link from previous block
10
; Shrink this free block to take up the space preceeding the allocated block.
SUBS bp,work,addr
STRNE bp, [addr, #fresize]
BNE ResultIsWorkPlus4
; No space for an initial free block. Get rid of it.
ASSERT frelink=0 ; otherwise LDR lr,[addr,#frelink]!
LDR lr, [addr]
CMP lr, #0
ADDNE lr, lr, tp
STR lr, [addr, -tp]
B ResultIsWorkPlus4
; Got no more free blocks of length >= size, so try to allocate more heap space
; out of the block described by hpd
garamore
LDR work, hpdbase
ADD work, work, hpd
ADD tp, work, #4
ADD tp, tp, bp
garamoreloop
BIC tp, tp, bp ; tp = pointer to return to user
; Make sure there's enough space for a free block if necessary
SUB HpTemp, tp, work ; HpTemp = tp-(hpd+hpdbase)
CMP HpTemp, #4
BEQ garamoreok
CMP HpTemp, #freblksize+4
ADDLT tp, tp, bp, LSL #1 ; Not enough space for free block
BLT garamoreloop
garamoreok
ADD HpTemp, tp, size ; New heap end
SUB HpTemp, HpTemp, hpd ; New heap size
LDR lr, hpdend
CMP HpTemp, lr
BGT garfailed
; Set up the block to return to the user
ADD size, size, #4
STR size, [tp, #-4]!
; Grow the heap
STR HpTemp, hpdbase
; Create preceeding free block if necessary
SUBS HpTemp, tp, work
BEQ ResultIsTpPlus4
; Write the free block
STR HpTemp, [work, #fresize]
MOV HpTemp, #Nil
STR HpTemp, [work, #frelink]
; Patch up the preceeding block
SUB HpTemp, work, addr
STR HpTemp, [addr, #frelink]
ResultIsTpPlus4
; Block size is already stored
ADD r0, tp, #4
Pull "tp,bp,ip,lr"
MSR CPSR_c, ip
MOV pc, lr
ResultIsWorkPlus4
STR size, [work] ; Store block size
ADD r0, work, #4 ; Move to correct return reg & add offset
Pull "tp,bp,ip,lr"
MSR CPSR_c, ip
MOV pc, lr
; +++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
;
; FreeArea. Top level HeapEntry
; ========
;
; Return an area of store to the heap
; In : hpd -> heap descriptor, r1 -> block to free
; The block to be freed is matched against those on the free list and inserted
; in it's correct place, with the list being maintained in ascending address
; order. If possible, the freed block is merged with contigous blocks above
; and below it to give less fragmentation, and if contiguous with main memory,
; is merged with that. If the latter, check to see if there is a block which
; would be made contiguous with main memory by the former's freeing, and if so,
; merge that with main memory too. Phew !
HALHeap_FreeArea
MRS ip, CPSR
MOV addr, r1
Push "tp,bp,ip,lr"
ORR ip, ip, #I32_bit
MSR CPSR_c, ip
[ debheap
; HpTemp not critical
LDR HpTemp, hpddebug
CMP HpTemp, #0
BEQ %FT00
Push "r0, link"
STRIM "FreeArea "
SUB r0, addr, hpd
SUB r0, r0, #4
BL PrintOffsetLine
BL iShowHeap
Pull "r0, link"
00
]
BL FindHeapBlock
BLVC FreeChunkWithConcatenation
Pull "tp,bp,ip,lr"
MSR CPSR_c, ip
MOV pc, lr
;**************************************************************************
; Common routines for free/extend
FindHeapBlock ROUT
; Convert addr to address
; Validate heap
; check block is an allocated block
; return tp = free list entry before the block (hpdfree if none)
; work = free list before that (if exists)
; corrupts HpTemp, bp
Push lr
SUB addr, addr, hpd ; convert to offset
SUB addr, addr, #4 ; real block posn
; Find block in heap by chaining down freelist, stepping through blocks
; TMD 01-Mar-89
; no need to check explicitly for null free list, code drops thru OK
[ debheap
LDR HpTemp, hpddebug
CMP HpTemp, #0
BEQ %FT03
Push lr
WRLN "Scanning freelist"
Pull lr
03
]
; step down free list to find appropriate chunk
; get tp = free block before addr
; HpTemp = " " after "
; work = block before tp
MOV tp, #:INDEX: hpdfree
StepDownFreeList
LDR HpTemp, [hpd, tp] ; link offset
CMP HpTemp,#Nil
BEQ ListEnded ; EQ state used!
ADD HpTemp, HpTemp, tp
CMP HpTemp, addr
MOVLS work, tp
MOVLS tp, HpTemp
BLS StepDownFreeList
ListEnded
LDREQ HpTemp, hpdbase ; if EQ from CMP HpTemp, addr
; then bad block anyway
CMP tp, #:INDEX: hpdfree
MOVEQ bp, #hpdsize ; is this a fudge I see before me?
BEQ ScanAllocForAddr
ADD bp, tp, #fresize
LDR bp, [hpd, bp]
ADD bp, tp, bp
ScanAllocForAddr
; bp -> start of allocated chunk
; HpTemp -> end " " "
; scan to find addr, error if no in here
Push work ; keep prevlink ptr
[ debheap
; HpTemp critical
Push "HpTemp, R0, link"
LDR HpTemp, hpddebug
CMP HpTemp, #0
BEQ %FT02
STRIM "Scan for addr from "
MOV R0, bp
BL PrintOffset
STRIM " to "
LDR R0,[stack,#4] ; HpTemp
BL PrintOffsetLine
02
Pull "HpTemp, r0, link"
]
B CheckForNullAllocn
ScanAllocForAddrLoop
CMP bp, addr
BEQ ValidBlock
LDR work, [bp, hpd] ; get size
ADD bp, bp, work
CheckForNullAllocn
CMP bp, HpTemp
BLT ScanAllocForAddrLoop
[ debheap
Push lr
STRIM "Given pointer not a block"
Pull lr
]
SETV
Pull "work, pc"
ValidBlock ; tp = free link offset, addr = block offset
CLRV
Pull "work, pc"
;****************************************************************************
FreeChunkWithConcatenation ROUT
; in : addr -> block
; tp -> preceding free list entry
; out : block freed, concatenated with any free parts on either side,
; base reduced if can do
; corrupts HpTemp, bp, size, addr
; TMD 01-Mar-89: FindHeapBlock now never returns tp=Nil, only tp=hpdfree,
; so no need for check, code will get there eventually!
; attempt concatenation with free blocks on both/either side
[ debheap
Push "R0, lr"
LDR HpTemp, hpddebug
CMP HpTemp, #0
BEQ %FT04
STRIM "concatenation attempt with free ptr "
MOV R0,tp
BL PrintOffsetLine
04
Pull "R0, lr"
]
LDR size, [addr, hpd] ; block size
ADD bp, size, addr ; eob offset
LDR HpTemp, [tp, hpd] ; Nil doesn't matter here!
ADD HpTemp, HpTemp, tp ; offset of free block after ours
CMP HpTemp, bp ; if tp was hpdfree then <> bp
BNE NoConcatWithNext ; so will take branch
[ debheap
Push lr
LDR bp, hpddebug
CMP bp, #0
BEQ %FT05
WRLN "concatenating with block after"
05
Pull lr
]
ADD bp, hpd, HpTemp
LDR bp, [bp, #fresize]
ADD bp, bp, size
STR bp, [addr, hpd] ; enlarge our block
LDR bp, [HpTemp, hpd] ; offset in free list
CMP bp, #Nil
ADDNE bp, HpTemp, bp ; offset from heap start
SUBNE bp, bp, tp ; free list offset
STR bp, [tp, hpd] ; free list updated, our block bigger
; - but not in the free list yet!
NoConcatWithNext ; tp = free link offset, addr = block offset
; now try for concatenation with previous block
CMP tp, #:INDEX: hpdfree ; are we before any real free blocks?
BEQ NoConcatenation ; yup
ADD HpTemp, tp, hpd
LDR size, [HpTemp, #fresize]
ADD bp, size, tp
CMP bp, addr
BNE NoConcatenation
[ debheap
Push lr
LDR bp, hpddebug
CMP bp, #0
BEQ %FT06
WRLN "concatenating with block before"
STRIM "prevfree = "
Push R0
MOV R0, work
BL PrintOffsetLine
Pull R0
06
Pull lr
]
LDR bp, [addr, hpd] ; get block size
ADD size, bp, size ; new free block size
STR size, [HpTemp, #fresize]
; now check for butts against base : work is still prevnode to tp
ADD HpTemp, size, tp
LDR bp, hpdbase
CMP bp, HpTemp
BNE %FT06 ; all done : exit keeping IRQs off
SUB bp, bp, size
STR bp, hpdbase ; step unused bit back
MOV bp, #Nil ; this MUST have been last free block!
STR bp, [work, hpd]
06
CLRV
MOV PC, lr ; Whew!
NoConcatenation ; check if block butts against base
; tp = previous freelink offset
LDR size, [addr, hpd]
ADD HpTemp, size, addr
LDR bp, hpdbase
CMP bp, HpTemp
BNE AddToFreeList
SUB bp, bp, size
STR bp, hpdbase
CLRV
MOV PC, lr
AddToFreeList ; block at addr, previous free at tp
[ debheap
Push "R0, lr"
LDR HpTemp, hpddebug
CMP HpTemp, #0
BEQ %FT07
STRIM "add to free list : free link "
MOV R0,tp
BL PrintOffset
STRIM ", block "
MOV R0, addr
BL PrintOffsetLine
07
Pull "R0, lr"
]
LDR size, [addr, hpd]!
STR size, [addr, #fresize]
SUB addr, addr, hpd
LDR size, [hpd, tp] ; prevlink
CMP size, #Nil
SUBNE size, size, addr
ADDNE size, size, tp ; form offset if not eolist
STR size, [addr, hpd]
SUB size, addr, tp
STR size, [tp, hpd]
CLRV
MOV PC, lr
; ++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
END
; Copyright 2011 Castle Technology Ltd
;
; Licensed under the Apache License, Version 2.0 (the "License");
; you may not use this file except in compliance with the License.
; You may obtain a copy of the License at
;
; http://www.apache.org/licenses/LICENSE-2.0
;
; Unless required by applicable law or agreed to in writing, software
; distributed under the License is distributed on an "AS IS" BASIS,
; WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
; See the License for the specific language governing permissions and
; limitations under the License.
;
; Assembler version of port.c, for use with HAL version of the USB drivers
; See also usbhal.c for some bits which were easier done in C.
GET Hdr:ListOpts
GET Hdr:Macros
GET Hdr:System
GET Hdr:Machine.<Machine>
GET Hdr:ImageSize.<ImageSize>
GET Hdr.usbhal
sb RN 9
AREA |C$$code|, CODE, READONLY
; External interfaces to HAL code
IMPORT USBHAL_WorkspaceOffset
IMPORT HAL_CounterDelay
IMPORT snprintf
IMPORT printf
; Internal interfaces to rest of HAL USB code
EXPORT spltty
EXPORT splx
EXPORT splbio
EXPORT delay
EXPORT selrecord
EXPORT selwakeup
EXPORT config_deactivate
EXPORT uiomove
EXPORT psignal
EXPORT kthread_create
EXPORT kthread_create1
EXPORT kthread_exit
EXPORT device_probe_and_attach
EXPORT ratecheck
EXPORT malloc_contig
EXPORT free_contig
EXPORT min
EXPORT logprintf
EXPORT cold
EXPORT hz
EXPORT _snprintf
EXPORT malloc
EXPORT free
IMPORT HALHeap_GetArea
IMPORT HALHeap_GetAreaAligned
IMPORT HALHeap_FreeArea
cold
DCD 0
hz
DCD 1000
spltty
MRS a1, CPSR
AND a1, a1, #I32_bit
MOV pc, lr
splx
TST a1, #I32_bit
MRSEQ a2, CPSR
BICEQ a2, a2, #I32_bit
MSREQ CPSR_c, a2
MOV pc, lr
splbio
MRS a1, CPSR
ORR a2, a1, #I32_bit
AND a1, a1, #I32_bit
MSR CPSR_c, a2
MOV pc, lr
delay
B HAL_CounterDelay
logprintf
B printf
kthread_create1
config_deactivate
uiomove
kthread_create
ratecheck
MOV a1, #0
selrecord
selwakeup
psignal
kthread_exit
device_probe_and_attach
MOV pc, lr
min
CMP a1, a2
MOVGT a1, a2
MOV pc, lr
_snprintf
B snprintf
malloc
; Note that this is a vanilla implementation, i.e. no M_ZERO support
; (but the usbdriver sources already deal with that)
MOV r1, r0
LDR r2, =USBHAL_WorkspaceOffset+USBHAL_WS_Heap_Normal
LDR r0, [sb, r2]
B HALHeap_GetArea
free
MOV r1, r0
LDR r2, =USBHAL_WorkspaceOffset+USBHAL_WS_Heap_Normal
LDR r0, [sb, r2]
B HALHeap_FreeArea
malloc_contig
; R0 = length
; R1 = alignment
ADD r0, r0, #3 ; Make size multiple of 4 for easy memset
BIC r0, r0, #3
Push "r0,lr"
LDR r3, =USBHAL_WorkspaceOffset+USBHAL_WS_Heap_NCNB
MOV r2, r1
MOV r1, r0
LDR r0, [sb, r3]
BL HALHeap_GetAreaAligned
Pull "r1,lr"
CMP r0, #0
MOVEQ pc, lr
; Zero the memory
MOV ip, #0
10
SUBS r1, r1, #4
STR ip, [r0, r1]
BGT %BT10
MOV pc, lr
free_contig
; R0 = pointer to pointer
LDR r2, =USBHAL_WorkspaceOffset+USBHAL_WS_Heap_NCNB
LDR r1, [r0]
LDR r0, [sb, r2]
B HALHeap_FreeArea
END
......@@ -16,32 +16,43 @@
; trigger callbacks by calling OS_LeaveOS and OS_EnterOS
GET Hdr:ListOpts
OPT OptNoList
OPT OptNoList
GET Hdr:PublicWS
GET Hdr:Macros
GET Hdr:System
GET Hdr:OSRSI6
AREA |C$$code|, CODE, READONLY
AREA |C$$data|, DATA
ptr_IRQsema
DCD 0 ; Cached IRQsema ptr
EXPORT triggercbs
AREA |C$$code|, CODE, READONLY
EXPORT triggercbs
triggercbs
; MOV ip, lr ; seen cases of ip corrupted
stmfd r13!, {lr}
MOV lr, #0
; LDR lr, [lr,#&420] ; kernel's CDA semaphore
; MOVS lr, lr
; BNE %ft2
LDR lr, [lr,#IRQsema] ; kernel's IRQ semaphore
MOVS lr, lr
; BNE %ft1
LDMNEFD r13!,{pc} ; NZ is within IRQ.. so no CB allowed
SWI &7c
SWI &16
ldmfd r13!,{pc}
; MOV pc, ip
;2
; DCD &ff000000 ;illegal instr to abort to indicate
; attempt to trigger cb whilst cda threaded
;1
; DCD &ff000000 ;illegal instr to abort to indicate
; attempt to trigger CB in IRQ
stmfd r13!, {lr}
LDR r3, =ptr_IRQsema
LDR r1, [sl,#-536] ; Get relocation
ADD r3, r3, r1
LDR r2, [r3]
CMP r2, #0
BNE %FT10
MOV r0, #6
MOV r1, #0
MOV r2, #OSRSI6_IRQsema
SWI XOS_ReadSysInfo
MOVVS r2, #0
CMP r2, #0
MOVEQ r2, #Legacy_IRQsema
STR r2, [r3]
10
LDR lr, [r2]
MOVS lr, lr
LDMNEFD r13!,{pc} ; NZ is within IRQ.. so no CB allowed
SWI OS_LeaveOS
SWI OS_EnterOS
ldmfd r13!,{pc}
LTORG
END
END
/* $NetBSD: ehci.c,v 1.91 2005/02/27 00:27:51 perry Exp $ */
/* $NetBSD: ehci.c,v 1.169 2010/07/07 03:55:01 msaitoh Exp $ */
/*
* Copyright (c) 2004 The NetBSD Foundation, Inc.
* Copyright (c) 2004-2008 The NetBSD Foundation, Inc.
* All rights reserved.
*
* This code is derived from software contributed to The NetBSD Foundation
* by Lennart Augustsson (lennart@augustsson.net) and by Charles M. Hannum.
* by Lennart Augustsson (lennart@augustsson.net), Charles M. Hannum and
* Jeremy Morse (jeremy.morse@gmail.com).
*
* Redistribution and use in source and binary forms, with or without
* modification, are permitted provided that the following conditions
......@@ -40,9 +41,9 @@
* USB Enhanced Host Controller Driver, a.k.a. USB 2.0 controller.
*
* The EHCI 1.0 spec can be found at
* http://developer.intel.com/technology/usb/download/ehci-r10.pdf
* http://www.intel.com/technology/usb/spec.htm
* and the USB 2.0 spec at
* http://www.usb.org/developers/docs/usb_20.zip
* http://www.usb.org/developers/docs/
*
*/
......@@ -50,20 +51,16 @@
* TODO:
* 1) hold off explorations by companion controllers until ehci has started.
*
* 2) The EHCI driver lacks support for interrupt isochronous transfers, so
* devices using them don't work.
* Interrupt transfers are not difficult, it's just not done.
*
* 3) The meaty part to implement is the support for USB 2.0 hubs.
* They are quite complicated since the need to be able to do
* "transaction translation", i.e., converting to/from USB 2 and USB 1.
* So the hub driver needs to handle and schedule these things, to
* assign place in frame where different devices get to go. See chapter
* 2) The hub driver needs to handle and schedule the transaction translator,
* to assign place in frame where different devices get to go. See chapter
* on hubs in USB 2.0 for details.
*
* 4) command failures are not recovered correctly
* 3) Command failures are not recovered correctly.
*/
#ifdef __riscos
#include <dev/usb/usbhal.h>
#endif
#include <sys/cdefs.h>
//__KERNEL_RCSID(0, "$NetBSD: ehci.c,v 1.91 2005/02/27 00:27:51 perry Exp $");
......@@ -75,8 +72,13 @@
#include <sys/select.h>
#include <sys/proc.h>
#include <sys/queue.h>
#ifndef __riscos
#include <sys/mutex.h>
#include <sys/bus.h>
#else
#include <machine/bus.h>
#endif
#include <machine/endian.h>
#include <dev/usb/usb.h>
......@@ -87,34 +89,27 @@
#include <dev/usb/ehcireg.h>
#include <dev/usb/ehcivar.h>
#include <dev/usb/usbroothub_subr.h>
#ifdef __riscos
#define printf logprintf
#define aprint_verbose logprintf
#define aprint_normal logprintf
#endif
#ifdef EHCI_DEBUG
#define DPRINTF(x) if (ehcidebug) logprintf x
#define DPRINTFN(n,x) if (ehcidebug>(n)) logprintf x
#define DPRINTF(x) do { if (ehcidebug) printf x; } while(0)
#define DPRINTFN(n,x) do { if (ehcidebug>(n)) printf x; } while (0)
int ehcidebug = 0;
#ifndef __NetBSD__
#define bitmask_snprintf(q,f,b,l) snprintf((b), (l), "%b", (q), (f))
#endif
#else
#define DPRINTF(x)
#define DPRINTFN(n,x)
#endif
#ifdef __riscos
#define printf logprintf
#endif
#ifdef __riscos
#define MS_TO_TICKS(ms) ((ms) * hz / 1000)
#endif
struct ehci_pipe {
struct usbd_pipe pipe;
int nexttoggle;
int nexttoggle;
ehci_soft_qh_t *sqh;
union {
ehci_soft_qtd_t *qtd;
......@@ -125,34 +120,35 @@ struct ehci_pipe {
struct {
usb_dma_t reqdma;
u_int length;
/*ehci_soft_qtd_t *setup, *data, *stat;*/
} ctl;
/* Interrupt pipe */
struct {
u_int length;
} intr;
struct {
u_int length;
} intr;
/* Bulk pipe */
struct {
u_int length;
} bulk;
/* Iso pipe */
/* XXX */
struct {
u_int next_frame;
u_int cur_xfers;
} isoc;
} u;
};
Static void ehci_shutdown(void *);
Static void ehci_power(int, void *);
Static usbd_status ehci_open(usbd_pipe_handle);
Static void ehci_poll(struct usbd_bus *);
Static void ehci_softintr(void *);
Static int ehci_intr1(ehci_softc_t *);
Static void ehci_waitintr(ehci_softc_t *, usbd_xfer_handle);
Static void ehci_check_intr(ehci_softc_t *, struct ehci_xfer *);
Static void ehci_check_qh_intr(ehci_softc_t *, struct ehci_xfer *);
Static void ehci_check_itd_intr(ehci_softc_t *, struct ehci_xfer *);
Static void ehci_idone(struct ehci_xfer *);
Static void ehci_timeout(void *);
Static void ehci_timeout_task(void *);
Static void ehci_intrlist_timeout(void *);
Static usbd_status ehci_allocm(struct usbd_bus *, usb_dma_t *, u_int32_t);
Static void ehci_freem(struct usbd_bus *, usb_dma_t *);
......@@ -199,10 +195,7 @@ Static void ehci_device_isoc_done(usbd_xfer_handle);
Static void ehci_device_clear_toggle(usbd_pipe_handle pipe);
Static void ehci_noop(usbd_pipe_handle pipe);
Static int ehci_str(usb_string_descriptor_t *, int, char *);
Static void ehci_pcd(ehci_softc_t *, usbd_xfer_handle);
Static void ehci_pcd_able(ehci_softc_t *, int);
Static void ehci_pcd_enable(void *);
Static void ehci_disown(ehci_softc_t *, int, int);
Static ehci_soft_qh_t *ehci_alloc_sqh(ehci_softc_t *);
......@@ -216,10 +209,17 @@ Static usbd_status ehci_alloc_sqtd_chain(struct ehci_pipe *,
Static void ehci_free_sqtd_chain(ehci_softc_t *, ehci_soft_qtd_t *,
ehci_soft_qtd_t *);
Static ehci_soft_itd_t *ehci_alloc_itd(ehci_softc_t *sc);
Static void ehci_free_itd(ehci_softc_t *sc, ehci_soft_itd_t *itd);
Static void ehci_rem_free_itd_chain(ehci_softc_t *sc,
struct ehci_xfer *exfer);
Static void ehci_abort_isoc_xfer(usbd_xfer_handle xfer,
usbd_status status);
Static usbd_status ehci_device_request(usbd_xfer_handle xfer);
Static usbd_status ehci_device_setintr(ehci_softc_t *, ehci_soft_qh_t *,
int ival);
Static usbd_status ehci_device_setintr(ehci_softc_t *, ehci_soft_qh_t *,
int ival);
Static void ehci_add_qh(ehci_soft_qh_t *, ehci_soft_qh_t *);
Static void ehci_rem_qh(ehci_softc_t *, ehci_soft_qh_t *,
......@@ -232,13 +232,17 @@ Static void ehci_abort_xfer(usbd_xfer_handle, usbd_status);
#ifdef EHCI_DEBUG
Static void ehci_dump_regs(ehci_softc_t *);
Static void ehci_dump(void);
void ehci_dump(void);
Static ehci_softc_t *theehci;
Static void ehci_dump_link(ehci_link_t, int);
Static void ehci_dump_sqtds(ehci_soft_qtd_t *);
Static void ehci_dump_sqtd(ehci_soft_qtd_t *);
Static void ehci_dump_qtd(ehci_qtd_t *);
Static void ehci_dump_sqh(ehci_soft_qh_t *);
#if notyet
Static void ehci_dump_sitd(struct ehci_soft_itd *itd);
Static void ehci_dump_itd(struct ehci_soft_itd *);
#endif
#ifdef DIAGNOSTIC
Static void ehci_dump_exfer(struct ehci_xfer *);
#endif
......@@ -249,14 +253,18 @@ Static void ehci_dump_exfer(struct ehci_xfer *);
#define EHCI_INTR_ENDPT 1
#define ehci_add_intr_list(sc, ex) \
LIST_INSERT_HEAD(&(sc)->sc_intrhead, (ex), inext);
#define ehci_del_intr_list(ex) \
do { \
LIST_REMOVE((ex), inext); \
(ex)->inext.le_prev = NULL; \
} while (0)
#define ehci_active_intr_list(ex) ((ex)->inext.le_prev != NULL)
TAILQ_INSERT_TAIL(&(sc)->sc_intrhead, (ex), inext);
#define ehci_del_intr_list(sc, ex) \
do { \
TAILQ_REMOVE(&sc->sc_intrhead, (ex), inext); \
(ex)->inext.tqe_prev = NULL; \
} while (0)
#define ehci_active_intr_list(ex) ((ex)->inext.tqe_prev != NULL)
#ifdef USBHAL
extern int usbhal_ehci_do_intr(struct usbd_bus *,int irqdevno);
extern void usbhal_ehci_shutdown(struct usbd_bus *);
#endif
Static struct usbd_bus_methods ehci_bus_methods = {
ehci_open,
......@@ -266,6 +274,10 @@ Static struct usbd_bus_methods ehci_bus_methods = {
ehci_freem,
ehci_allocx,
ehci_freex,
#ifdef USBHAL
usbhal_ehci_do_intr,
usbhal_ehci_shutdown,
#endif
};
Static struct usbd_pipe_methods ehci_root_ctrl_methods = {
......@@ -322,7 +334,36 @@ Static struct usbd_pipe_methods ehci_device_isoc_methods = {
ehci_device_isoc_done,
};
#if defined (__riscos)
#ifdef USBHAL
static const uint8_t revbits[EHCI_MAX_POLLRATE] = {0x00,0x02,0x01,0x03};
#else
static const uint8_t revbits[EHCI_MAX_POLLRATE] = {
0x00,0x40,0x20,0x60,0x10,0x50,0x30,0x70,0x08,0x48,0x28,0x68,0x18,0x58,0x38,0x78,
0x04,0x44,0x24,0x64,0x14,0x54,0x34,0x74,0x0c,0x4c,0x2c,0x6c,0x1c,0x5c,0x3c,0x7c,
0x02,0x42,0x22,0x62,0x12,0x52,0x32,0x72,0x0a,0x4a,0x2a,0x6a,0x1a,0x5a,0x3a,0x7a,
0x06,0x46,0x26,0x66,0x16,0x56,0x36,0x76,0x0e,0x4e,0x2e,0x6e,0x1e,0x5e,0x3e,0x7e,
0x01,0x41,0x21,0x61,0x11,0x51,0x31,0x71,0x09,0x49,0x29,0x69,0x19,0x59,0x39,0x79,
0x05,0x45,0x25,0x65,0x15,0x55,0x35,0x75,0x0d,0x4d,0x2d,0x6d,0x1d,0x5d,0x3d,0x7d,
0x03,0x43,0x23,0x63,0x13,0x53,0x33,0x73,0x0b,0x4b,0x2b,0x6b,0x1b,0x5b,0x3b,0x7b,
0x07,0x47,0x27,0x67,0x17,0x57,0x37,0x77,0x0f,0x4f,0x2f,0x6f,0x1f,0x5f,0x3f,0x7f,
};
#endif
#ifdef USBHAL
/* TODO - Move elsewhere */
static void abort_pipe(void *v)
{
splbio(); /* Code in cmodule runs with interrupts enabled(!) */
ehci_abort_xfer((usbd_xfer_handle) v,USBD_TIMEOUT);
}
static void riscos_abort_pipe(void *v)
{
USBHAL_AddCallback(abort_pipe,v);
}
#endif
#if defined (__riscos) && !defined(USBHAL)
static int veneers_built = 0;
void build_veneer (void* vn, void* st, size_t sz);
static struct {
......@@ -350,14 +391,14 @@ static struct {
usbd_status
ehci_init(ehci_softc_t *sc)
{
u_int32_t version, sparams, cparams, hcr;
u_int32_t vers, sparams, cparams, hcr;
u_int i;
usbd_status err;
ehci_soft_qh_t *sqh;
u_int ncomp;
DPRINTF(("ehci_init: start\n"));
#if defined (__riscos)
#if defined (__riscos) && !defined(USBHAL)
if (!veneers_built)
{
build_veneer(&ehci_bus_methods_entry,
......@@ -390,39 +431,39 @@ ehci_init(ehci_softc_t *sc)
sc->sc_offs = EREAD1(sc, EHCI_CAPLENGTH);
version = EREAD2(sc, EHCI_HCIVERSION);
logprintf("%s: EHCI version %x.%x\n", USBDEVNAME(sc->sc_bus.bdev),
version >> 8, version & 0xff);
vers = EREAD2(sc, EHCI_HCIVERSION);
aprint_verbose("%s: EHCI version %x.%x\n", USBDEVNAME(sc->sc_bus.bdev),
vers >> 8, vers & 0xff);
sparams = EREAD4(sc, EHCI_HCSPARAMS);
DPRINTF(("ehci_init: sparams=0x%x\n", sparams));
sc->sc_npcomp = EHCI_HCS_N_PCC(sparams);
ncomp = EHCI_HCS_N_CC(sparams);
if (ncomp != sc->sc_ncomp) {
logprintf("%s: wrong number of companions (%d != %d)\n",
USBDEVNAME(sc->sc_bus.bdev),
ncomp, sc->sc_ncomp);
ncomp = EHCI_HCS_N_CC(sparams);
if (ncomp != sc->sc_ncomp) {
aprint_verbose("%s: wrong number of companions (%d != %d)\n",
USBDEVNAME(sc->sc_bus.bdev), ncomp, sc->sc_ncomp);
#ifdef __riscos0
return (USBD_IOERROR);
#endif
if (ncomp < sc->sc_ncomp)
sc->sc_ncomp = ncomp;
if (ncomp < sc->sc_ncomp)
sc->sc_ncomp = ncomp;
}
if (sc->sc_ncomp > 0) {
logprintf("%s: companion controller%s, %d port%s each:",
aprint_normal("%s: companion controller%s, %d port%s each:",
USBDEVNAME(sc->sc_bus.bdev), sc->sc_ncomp!=1 ? "s" : "",
EHCI_HCS_N_PCC(sparams),
EHCI_HCS_N_PCC(sparams)!=1 ? "s" : "");
#ifndef __riscos
/* we aren't filling in companions at the moment */
for (i = 0; i < sc->sc_ncomp; i++)
logprintf(" %s", USBDEVNAME(sc->sc_comps[i]->bdev));
aprint_normal(" %s", USBDEVNAME(sc->sc_comps[i]->bdev));
#endif
logprintf("\n");
aprint_normal("\n");
}
sc->sc_noport = EHCI_HCS_N_PORTS(sparams);
cparams = EREAD4(sc, EHCI_HCCPARAMS);
DPRINTF(("ehci_init: cparams=0x%x\n", cparams));
sc->sc_hasppc = EHCI_HCS_PPC(sparams);
if (EHCI_HCC_64BIT(cparams)) {
/* MUST clear segment register if 64 bit capable. */
......@@ -431,8 +472,8 @@ ehci_init(ehci_softc_t *sc)
sc->sc_bus.usbrev = USBREV_2_0;
#ifndef __riscos
usb_setup_reserve(sc, &sc->sc_dma_reserve, sc->sc_bus.dmatag,
USB_MEM_RESERVE);
usb_setup_reserve(sc->sc_dev, &sc->sc_dma_reserve, sc->sc_bus.dmatag,
USB_MEM_RESERVE);
#endif
/* Reset the controller */
DPRINTF(("%s: resetting\n", USBDEVNAME(sc->sc_bus.bdev)));
......@@ -453,75 +494,98 @@ ehci_init(ehci_softc_t *sc)
return (USBD_IOERROR);
}
/* XXX need proper intr scheduling */
sc->sc_rand = 96;
/* XXX need proper intr scheduling */
sc->sc_rand = 96;
#ifdef USBHAL
/* A full frame list takes up a lot of memory. Try shrinking it to minimum. */
if(EHCI_HCC_PFLF(cparams))
EOWRITE4(sc, EHCI_USBCMD, (EOREAD4(sc, EHCI_USBCMD) & ~EHCI_CMD_FLS_M) | (2<<2));
#endif
/* frame list size at default, read back what we got and use that */
switch (EHCI_CMD_FLS(EOREAD4(sc, EHCI_USBCMD))) {
case 0: sc->sc_flsize = 1024; break;
case 1: sc->sc_flsize = 512; break;
case 2: sc->sc_flsize = 256; break;
case 0: sc->sc_flsize = 1024; break;
case 1: sc->sc_flsize = 512; break;
case 2: sc->sc_flsize = 256; break;
case 3: return (USBD_IOERROR);
}
err = usb_allocmem(&sc->sc_bus, sc->sc_flsize * sizeof(ehci_link_t),
EHCI_FLALIGN_ALIGN, &sc->sc_fldma);
err = usb_allocmem(&sc->sc_bus, sc->sc_flsize * sizeof(ehci_link_t),
EHCI_FLALIGN_ALIGN, &sc->sc_fldma);
if (err)
return (err);
DPRINTF(("%s: flsize=%d\n", USBDEVNAME(sc->sc_bus.bdev),sc->sc_flsize));
sc->sc_flist = KERNADDR(&sc->sc_fldma, 0);
EOWRITE4(sc, EHCI_PERIODICLISTBASE, DMAADDR(&sc->sc_fldma, 0));
for (i = 0; i < sc->sc_flsize; i++) {
sc->sc_flist[i] = EHCI_NULL;
}
EOWRITE4(sc, EHCI_PERIODICLISTBASE, DMAADDR(&sc->sc_fldma, 0));
sc->sc_softitds = malloc(sc->sc_flsize * sizeof(ehci_soft_itd_t *),
M_USB, M_NOWAIT | M_ZERO);
if (sc->sc_softitds == NULL)
return ENOMEM;
#ifdef __riscos
memset(sc->sc_softitds, 0, sc->sc_flsize * sizeof(ehci_soft_itd_t *)); /* No M_ZERO on RISC OS :( */
#endif
LIST_INIT(&sc->sc_freeitds);
TAILQ_INIT(&sc->sc_intrhead);
mutex_init(&sc->sc_intrhead_lock, MUTEX_DEFAULT, IPL_USB);
/* Set up the bus struct. */
sc->sc_bus.methods = &ehci_bus_methods;
sc->sc_bus.pipe_size = sizeof(struct ehci_pipe);
#ifndef __riscos
sc->sc_powerhook = powerhook_establish(ehci_power, sc);
sc->sc_shutdownhook = shutdownhook_establish(ehci_shutdown, sc);
#endif
sc->sc_eintrs = EHCI_NORMAL_INTRS;
/*
* Allocate the interrupt dummy QHs. These are arranged to give poll
* intervals that are powers of 2 times 1ms.
*/
for (i = 0; i < EHCI_INTRQHS; i++) {
sqh = ehci_alloc_sqh(sc);
if (sqh == NULL) {
err = USBD_NOMEM;
goto bad1;
}
sc->sc_islots[i].sqh = sqh;
}
for (i = 0; i < EHCI_INTRQHS; i++) {
sqh = sc->sc_islots[i].sqh;
if (i == 0) {
/* The last (1ms) QH terminates. */
sqh->qh.qh_link = EHCI_NULL;
sqh->next = NULL;
} else {
int val = i + 1, b = 0, v2 = val;
while (v2 >>= 1) b++;
val = ((val & ~(1<<b)) | (1<<(b - 1)))-1;
/* Otherwise the next QH has half the poll interval */
sqh->next = sc->sc_islots[val].sqh;
sqh->qh.qh_link = htole32(sqh->next->physaddr |
EHCI_LINK_QH);
}
sqh->qh.qh_endp = htole32(EHCI_QH_SET_EPS(EHCI_QH_SPEED_HIGH));
sqh->qh.qh_curqtd = EHCI_NULL;
sqh->next = NULL;
sqh->qh.qh_qtd.qtd_next = EHCI_NULL;
sqh->qh.qh_qtd.qtd_altnext = EHCI_NULL;
sqh->qh.qh_qtd.qtd_status = htole32(EHCI_QTD_HALTED);
sqh->sqtd = NULL;
}
/* Point the frame list at the last level (128ms). */
for (i = 0; i < sc->sc_flsize; i++) {
sc->sc_flist[i] = htole32(EHCI_LINK_QH |
sc->sc_islots[EHCI_IQHIDX(EHCI_IPOLLRATES - 1,
i)].sqh->physaddr);
}
/*
* Allocate the interrupt dummy QHs. These are arranged to give poll
* intervals that are powers of 2 times 1ms.
*/
for (i = 0; i < EHCI_INTRQHS; i++) {
sqh = ehci_alloc_sqh(sc);
if (sqh == NULL) {
err = USBD_NOMEM;
goto bad1;
}
sc->sc_islots[i].sqh = sqh;
}
for (i = 0; i < EHCI_INTRQHS; i++) {
sqh = sc->sc_islots[i].sqh;
if (i == 0) {
/* The last (1ms) QH terminates. */
sqh->qh.qh_link = EHCI_NULL;
sqh->next = NULL;
} else {
/* Otherwise the next QH has half the poll interval */
sqh->next = sc->sc_islots[(i + 1) / 2 - 1].sqh;
sqh->qh.qh_link = htole32(sqh->next->physaddr |
EHCI_LINK_QH);
}
sqh->qh.qh_endp = htole32(EHCI_QH_SET_EPS(EHCI_QH_SPEED_HIGH));
sqh->qh.qh_curqtd = EHCI_NULL;
sqh->next = NULL;
sqh->qh.qh_qtd.qtd_next = EHCI_NULL;
sqh->qh.qh_qtd.qtd_altnext = EHCI_NULL;
sqh->qh.qh_qtd.qtd_status = htole32(EHCI_QTD_HALTED);
sqh->sqtd = NULL;
usb_syncmem(&sqh->dma, sqh->offs, sizeof(sqh->qh),
BUS_DMASYNC_PREWRITE | BUS_DMASYNC_PREREAD);
}
/* Point the frame list at the last level (128ms). */
for (i = 0; i < sc->sc_flsize; i++) {
int j;
j = (i & ~(EHCI_MAX_POLLRATE-1)) |
revbits[i & (EHCI_MAX_POLLRATE-1)];
sc->sc_flist[j] = htole32(EHCI_LINK_QH |
sc->sc_islots[EHCI_IQHIDX(EHCI_IPOLLRATES - 1,
i)].sqh->physaddr);
}
usb_syncmem(&sc->sc_fldma, 0, sc->sc_flsize * sizeof(ehci_link_t),
BUS_DMASYNC_PREWRITE);
/* Allocate dummy QH that starts the async list. */
sqh = ehci_alloc_sqh(sc);
......@@ -541,6 +605,8 @@ ehci_init(ehci_softc_t *sc)
sqh->qh.qh_qtd.qtd_altnext = EHCI_NULL;
sqh->qh.qh_qtd.qtd_status = htole32(EHCI_QTD_HALTED);
sqh->sqtd = NULL;
usb_syncmem(&sqh->dma, sqh->offs, sizeof(sqh->qh),
BUS_DMASYNC_PREWRITE | BUS_DMASYNC_PREREAD);
#ifdef EHCI_DEBUG
if (ehcidebug) {
ehci_dump_sqh(sqh);
......@@ -551,19 +617,16 @@ ehci_init(ehci_softc_t *sc)
sc->sc_async_head = sqh;
EOWRITE4(sc, EHCI_ASYNCLISTADDR, sqh->physaddr | EHCI_LINK_QH);
usb_callout_init(sc->sc_tmo_pcd);
lockinit(&sc->sc_doorbell_lock, PZERO, "ehcidb", 0, 0);
callout_init(&(sc->sc_tmo_intrlist), 0);
/* Enable interrupts */
EOWRITE4(sc, EHCI_USBINTR, sc->sc_eintrs);
mutex_init(&sc->sc_doorbell_lock, MUTEX_DEFAULT, IPL_NONE);
/* Turn on controller */
EOWRITE4(sc, EHCI_USBCMD,
EHCI_CMD_ITC_2 | /* 2 microframes interrupt delay */
EHCI_CMD_ITC_2 | /* 2 microframes interrupt delay */
(EOREAD4(sc, EHCI_USBCMD) & EHCI_CMD_FLS_M) |
EHCI_CMD_ASE |
EHCI_CMD_PSE |
EHCI_CMD_PSE |
EHCI_CMD_RS);
/* Take over port ownership */
......@@ -580,6 +643,10 @@ ehci_init(ehci_softc_t *sc)
return (USBD_IOERROR);
}
/* Enable interrupts */
DPRINTFN(1,("ehci_init: enabling\n"));
EOWRITE4(sc, EHCI_USBINTR, sc->sc_eintrs);
return (USBD_NORMAL_COMPLETION);
#if 0
......@@ -596,21 +663,21 @@ ehci_intr(void *v)
{
ehci_softc_t *sc = v;
if (sc == NULL || sc->sc_dying)
if (sc == NULL || sc->sc_dying || !device_has_power(sc->sc_dev))
return (0);
/* If we get an interrupt while polling, then just ignore it. */
if (sc->sc_bus.use_polling) {
u_int32_t intrs = EHCI_STS_INTRS(EOREAD4(sc, EHCI_USBSTS));
u_int32_t intrs = EHCI_STS_INTRS(EOREAD4(sc, EHCI_USBSTS));
if (intrs)
EOWRITE4(sc, EHCI_USBSTS, intrs); /* Acknowledge */
if (intrs)
EOWRITE4(sc, EHCI_USBSTS, intrs); /* Acknowledge */
#ifdef DIAGNOSTIC
logprintf("ehci_intr: ignored interrupt while polling\n");
DPRINTFN(16, ("ehci_intr: ignored interrupt while polling\n"));
#endif
#ifdef __riscos
EOREAD4(sc, EHCI_USBINTR);
riscos_irqclear();
riscos_irqclear(sc->sc_irqdevno);
#endif
return (0);
}
......@@ -628,28 +695,27 @@ ehci_intr1(ehci_softc_t *sc)
/* In case the interrupt occurs before initialization has completed. */
if (sc == NULL) {
#ifdef DIAGNOSTIC
printf("ehci_intr1: sc == NULL\n");
printf("ehci_intr1: sc == NULL\n");
#endif
return (0);
}
intrs = EHCI_STS_INTRS(EOREAD4(sc, EHCI_USBSTS));
if (!intrs)
return (0);
eintrs = intrs & sc->sc_eintrs;
DPRINTFN(7, ("ehci_intr1: sc=%p intrs=0x%x(0x%x) eintrs=0x%x\n",
DPRINTFN(7, ("ehci_intr1: sc=%p intrs=0x%x(0x%x) eintrs=0x%x\n",
sc, (u_int)intrs, EOREAD4(sc, EHCI_USBSTS),
(u_int)eintrs));
if (!eintrs)
return (0);
EOWRITE4(sc, EHCI_USBSTS, intrs); /* Acknowledge */
EOWRITE4(sc, EHCI_USBSTS, intrs); /* Acknowledge */
#ifdef __riscos
/* make sure it gets there */
EOREAD4(sc, EHCI_USBSTS);
riscos_irqclear();
riscos_irqclear(sc->sc_irqdevno);
#endif
sc->sc_bus.intr_context++;
sc->sc_bus.no_intrs++;
......@@ -659,9 +725,9 @@ ehci_intr1(ehci_softc_t *sc)
eintrs &= ~EHCI_STS_IAA;
}
if (eintrs & (EHCI_STS_INT | EHCI_STS_ERRINT)) {
DPRINTF(("ehci_intr1: %s %s\n",
eintrs & EHCI_STS_INT ? "INT" : "",
eintrs & EHCI_STS_ERRINT ? "ERRINT" : ""));
DPRINTFN(5,("ehci_intr1: %s %s\n",
eintrs & EHCI_STS_INT ? "INT" : "",
eintrs & EHCI_STS_ERRINT ? "ERRINT" : ""));
#if defined(__riscos) && !defined(USB_USE_SOFTINTR)
ehci_softintr(&sc->sc_bus);
#else
......@@ -670,19 +736,12 @@ ehci_intr1(ehci_softc_t *sc)
eintrs &= ~(EHCI_STS_INT | EHCI_STS_ERRINT);
}
if (eintrs & EHCI_STS_HSE) {
printf("%s: unrecoverable error, controller halted\n",
printf("%s: unrecoverable error, controller halted\n",
USBDEVNAME(sc->sc_bus.bdev));
/* XXX what else */
}
if (eintrs & EHCI_STS_PCD) {
ehci_pcd(sc, sc->sc_intrxfer);
/*
* Disable PCD interrupt for now, because it will be
* on until the port has been reset.
*/
ehci_pcd_able(sc, 0);
/* Do not allow RHSC interrupts > 1 per second */
usb_callout(sc->sc_tmo_pcd, hz, ehci_pcd_enable, sc);
eintrs &= ~EHCI_STS_PCD;
}
......@@ -692,9 +751,9 @@ ehci_intr1(ehci_softc_t *sc)
/* Block unprocessed interrupts. */
sc->sc_eintrs &= ~eintrs;
EOWRITE4(sc, EHCI_USBINTR, sc->sc_eintrs);
printf("%s: blocking intrs 0x%x\n",
printf("%s: blocking intrs 0x%x\n",
USBDEVNAME(sc->sc_bus.bdev), eintrs);
}
}
#ifdef __riscos
(void) EOREAD4(sc, EHCI_USBSTS); /* Acknowledge */
......@@ -703,29 +762,8 @@ ehci_intr1(ehci_softc_t *sc)
return (1);
}
void
ehci_pcd_able(ehci_softc_t *sc, int on)
{
DPRINTF( ("ehci_pcd_able: on=%d\n", on));
if (on)
sc->sc_eintrs |= EHCI_STS_PCD;
else
sc->sc_eintrs &= ~EHCI_STS_PCD;
EOWRITE4(sc, EHCI_USBINTR, sc->sc_eintrs);
#ifdef __riscos
EOREAD4(sc, EHCI_USBINTR); /* Acknowledge */
#endif
}
void
ehci_pcd_enable(void *v_sc)
{
ehci_softc_t *sc = v_sc;
ehci_pcd_able(sc, 1);
}
void
Static void
ehci_pcd(ehci_softc_t *sc, usbd_xfer_handle xfer)
{
usbd_pipe_handle pipe;
......@@ -754,11 +792,11 @@ ehci_pcd(ehci_softc_t *sc, usbd_xfer_handle xfer)
usb_transfer_complete(xfer);
}
void
Static void
ehci_softintr(void *v)
{
ehci_softc_t *sc = v;
struct ehci_xfer *ex, *nextex;
struct ehci_xfer *ex, *nextex;
DPRINTFN(10,("%s: ehci_softintr (%d)\n", USBDEVNAME(sc->sc_bus.bdev),
sc->sc_bus.intr_context));
......@@ -771,10 +809,16 @@ ehci_softintr(void *v)
* An interrupt just tells us that something is done, we have no
* clue what, so we need to scan through all active transfers. :-(
*/
for (ex = LIST_FIRST(&sc->sc_intrhead); ex; ex = nextex) {
nextex = LIST_NEXT(ex, inext);
for (ex = TAILQ_FIRST(&sc->sc_intrhead); ex; ex = nextex) {
nextex = TAILQ_NEXT(ex, inext);
ehci_check_intr(sc, ex);
}
}
/* Schedule a callout to catch any dropped transactions. */
if ((sc->sc_flags & EHCIF_DROPPED_INTR_WORKAROUND) &&
!TAILQ_EMPTY(&sc->sc_intrhead))
callout_reset(&(sc->sc_tmo_intrlist),
(hz), (ehci_intrlist_timeout), (sc));
#ifdef USB_USE_SOFTINTR
if (sc->sc_softwake) {
......@@ -787,22 +831,37 @@ ehci_softintr(void *v)
}
/* Check for an interrupt. */
void
Static void
ehci_check_intr(ehci_softc_t *sc, struct ehci_xfer *ex)
{
ehci_soft_qtd_t *sqtd, *lsqtd;
u_int32_t status;
int attr;
DPRINTFN(/*15*/2, ("ehci_check_intr: ex=%p\n", ex));
attr = ex->xfer.pipe->endpoint->edesc->bmAttributes;
if (UE_GET_XFERTYPE(attr) == UE_ISOCHRONOUS)
ehci_check_itd_intr(sc, ex);
else
ehci_check_qh_intr(sc, ex);
return;
}
Static void
ehci_check_qh_intr(ehci_softc_t *sc, struct ehci_xfer *ex)
{
ehci_soft_qtd_t *sqtd, *lsqtd;
uint32_t status;
if (ex->sqtdstart == NULL) {
printf("ehci_check_intr: sqtdstart=NULL\n");
printf("ehci_check_qh_intr: not valid sqtd\n");
return;
}
lsqtd = ex->sqtdend;
#ifdef DIAGNOSTIC
if (lsqtd == NULL) {
printf("ehci_check_intr: lsqtd==0\n");
printf("ehci_check_qh_intr: lsqtd==0\n");
return;
}
#endif
......@@ -811,10 +870,21 @@ ehci_check_intr(ehci_softc_t *sc, struct ehci_xfer *ex)
* is a an error somewhere in the middle, or whether there was a
* short packet (SPD and not ACTIVE).
*/
usb_syncmem(&lsqtd->dma,
lsqtd->offs + offsetof(ehci_qtd_t, qtd_status),
sizeof(lsqtd->qtd.qtd_status),
BUS_DMASYNC_POSTWRITE | BUS_DMASYNC_POSTREAD);
if (le32toh(lsqtd->qtd.qtd_status) & EHCI_QTD_ACTIVE) {
DPRINTFN(12, ("ehci_check_intr: active ex=%p\n", ex));
for (sqtd = ex->sqtdstart; sqtd != lsqtd; sqtd=sqtd->nextqtd) {
usb_syncmem(&sqtd->dma,
sqtd->offs + offsetof(ehci_qtd_t, qtd_status),
sizeof(sqtd->qtd.qtd_status),
BUS_DMASYNC_POSTWRITE | BUS_DMASYNC_POSTREAD);
status = le32toh(sqtd->qtd.qtd_status);
usb_syncmem(&sqtd->dma,
sqtd->offs + offsetof(ehci_qtd_t, qtd_status),
sizeof(sqtd->qtd.qtd_status), BUS_DMASYNC_PREREAD);
/* If there's an active QTD the xfer isn't done. */
if (status & EHCI_QTD_ACTIVE)
break;
......@@ -822,28 +892,77 @@ ehci_check_intr(ehci_softc_t *sc, struct ehci_xfer *ex)
if (status & EHCI_QTD_HALTED)
goto done;
/* We want short packets, and it is short: it's done */
if (EHCI_QTD_GET_BYTES(status) != 0)
if (EHCI_QTD_GET_BYTES(status) != 0)
goto done;
}
DPRINTFN(12, ("ehci_check_intr: ex=%p std=%p still active\n",
ex, ex->sqtdstart));
usb_syncmem(&lsqtd->dma,
lsqtd->offs + offsetof(ehci_qtd_t, qtd_status),
sizeof(lsqtd->qtd.qtd_status), BUS_DMASYNC_PREREAD);
return;
}
done:
DPRINTFN(12, ("ehci_check_intr: ex=%p done\n", ex));
usb_uncallout(ex->xfer.timeout_handle, ehci_timeout, ex);
callout_stop(&(ex->xfer.timeout_handle));
ehci_idone(ex);
}
void
Static void
ehci_check_itd_intr(ehci_softc_t *sc, struct ehci_xfer *ex) {
ehci_soft_itd_t *itd;
int i;
if (&ex->xfer != SIMPLEQ_FIRST(&ex->xfer.pipe->queue))
return;
if (ex->itdstart == NULL) {
printf("ehci_check_itd_intr: not valid itd\n");
return;
}
itd = ex->itdend;
#ifdef DIAGNOSTIC
if (itd == NULL) {
printf("ehci_check_itd_intr: itdend == 0\n");
return;
}
#endif
/*
* check no active transfers in last itd, meaning we're finished
*/
usb_syncmem(&itd->dma, itd->offs + offsetof(ehci_itd_t, itd_ctl),
sizeof(itd->itd.itd_ctl), BUS_DMASYNC_POSTWRITE |
BUS_DMASYNC_POSTREAD);
for (i = 0; i < EHCI_ITD_NUFRAMES; i++) {
if (le32toh(itd->itd.itd_ctl[i]) & EHCI_ITD_ACTIVE)
break;
}
if (i == EHCI_ITD_NUFRAMES) {
goto done; /* All 8 descriptors inactive, it's done */
}
DPRINTFN(12, ("ehci_check_itd_intr: ex %p itd %p still active\n", ex,
ex->itdstart));
return;
done:
DPRINTFN(12, ("ehci_check_itd_intr: ex=%p done\n", ex));
callout_stop(&(ex->xfer.timeout_handle));
ehci_idone(ex);
}
Static void
ehci_idone(struct ehci_xfer *ex)
{
usbd_xfer_handle xfer = &ex->xfer;
struct ehci_pipe *epipe = (struct ehci_pipe *)xfer->pipe;
ehci_soft_qtd_t *sqtd, *lsqtd;
u_int32_t status = 0, nstatus = 0;
ehci_soft_qtd_t *sqtd, *lsqtd;
u_int32_t status = 0, nstatus = 0;
int actlen;
uint pkts_left;
DPRINTFN(/*12*/2, ("ehci_idone: ex=%p\n", ex));
#ifdef DIAGNOSTIC
......@@ -852,10 +971,10 @@ ehci_idone(struct ehci_xfer *ex)
if (ex->isdone) {
splx(s);
#ifdef EHCI_DEBUG
printf("ehci_idone: ex is done!\n ");
printf("ehci_idone: ex is done!\n ");
ehci_dump_exfer(ex);
#else
printf("ehci_idone: ex=%p is done!\n", ex);
printf("ehci_idone: ex=%p is done!\n", ex);
#endif
return;
}
......@@ -863,7 +982,6 @@ ehci_idone(struct ehci_xfer *ex)
splx(s);
}
#endif
if (xfer->status == USBD_CANCELLED ||
xfer->status == USBD_TIMEOUT) {
DPRINTF(("ehci_idone: aborted xfer=%p\n", xfer));
......@@ -877,57 +995,98 @@ ehci_idone(struct ehci_xfer *ex)
#endif
/* The transfer is done, compute actual length and status. */
lsqtd = ex->sqtdend;
if (UE_GET_XFERTYPE(xfer->pipe->endpoint->edesc->bmAttributes)
== UE_ISOCHRONOUS) {
/* Isoc transfer */
struct ehci_soft_itd *itd;
int i, nframes, len, uframes;
nframes = 0;
actlen = 0;
i = xfer->pipe->endpoint->edesc->bInterval;
uframes = min(1 << (i - 1), USB_UFRAMES_PER_FRAME);
for (itd = ex->itdstart; itd != NULL; itd = itd->xfer_next) {
usb_syncmem(&itd->dma,itd->offs + offsetof(ehci_itd_t,itd_ctl),
sizeof(itd->itd.itd_ctl), BUS_DMASYNC_POSTWRITE |
BUS_DMASYNC_POSTREAD);
for (i = 0; i < EHCI_ITD_NUFRAMES; i += uframes) {
/* XXX - driver didn't fill in the frame full
* of uframes. This leads to scheduling
* inefficiencies, but working around
* this doubles complexity of tracking
* an xfer.
*/
if (nframes >= xfer->nframes)
break;
status = le32toh(itd->itd.itd_ctl[i]);
len = EHCI_ITD_GET_LEN(status);
if (EHCI_ITD_GET_STATUS(status) != 0)
len = 0; /*No valid data on error*/
xfer->frlengths[nframes++] = len;
actlen += len;
}
if (nframes >= xfer->nframes)
break;
}
xfer->actlen = actlen;
xfer->status = USBD_NORMAL_COMPLETION;
goto end;
}
/* Continue processing xfers using queue heads */
lsqtd = ex->sqtdend;
actlen = 0;
for (sqtd = ex->sqtdstart; sqtd != lsqtd->nextqtd; sqtd=sqtd->nextqtd) {
for (sqtd = ex->sqtdstart; sqtd != lsqtd->nextqtd; sqtd = sqtd->nextqtd) {
usb_syncmem(&sqtd->dma, sqtd->offs, sizeof(sqtd->qtd),
BUS_DMASYNC_POSTWRITE | BUS_DMASYNC_POSTREAD);
nstatus = le32toh(sqtd->qtd.qtd_status);
if (nstatus & EHCI_QTD_ACTIVE)
break;
status = nstatus;
/* halt is ok if descriptor is last, and complete */
if (sqtd->qtd.qtd_next == EHCI_NULL &&
EHCI_QTD_GET_BYTES(status) == 0)
status &= ~EHCI_QTD_HALTED;
if (EHCI_QTD_GET_PID(status) != EHCI_QTD_PID_SETUP)
if (EHCI_QTD_GET_PID(status) != EHCI_QTD_PID_SETUP)
actlen += sqtd->len - EHCI_QTD_GET_BYTES(status);
}
/*
* If there are left over TDs we need to update the toggle.
* The default pipe doesn't need it since control transfers
* start the toggle at 0 every time.
*/
if (sqtd != lsqtd->nextqtd &&
xfer->pipe->device->default_pipe != xfer->pipe) {
printf("ehci_idone: need toggle update status=%08x nstatus=%08x\n", status, nstatus);
/*
* If there are left over TDs we need to update the toggle.
* The default pipe doesn't need it since control transfers
* start the toggle at 0 every time.
* For a short transfer we need to update the toggle for the missing
* packets within the qTD.
*/
if ((sqtd != lsqtd->nextqtd || EHCI_QTD_GET_BYTES(status)) &&
xfer->pipe->device->default_pipe != xfer->pipe) {
DPRINTFN(2, ("ehci_idone: need toggle update "
"status=%08x nstatus=%08x\n", status, nstatus));
#if 0
ehci_dump_sqh(epipe->sqh);
ehci_dump_sqtds(ex->sqtdstart);
ehci_dump_sqh(epipe->sqh);
ehci_dump_sqtds(ex->sqtdstart);
#endif
epipe->nexttoggle = EHCI_QTD_GET_TOGGLE(nstatus);
epipe->nexttoggle = EHCI_QTD_GET_TOGGLE(nstatus);
}
/*
* For a short transfer we need to update the toggle for the missing
* packets within the qTD.
*/
pkts_left = EHCI_QTD_GET_BYTES(status) /
UGETW(xfer->pipe->endpoint->edesc->wMaxPacketSize);
epipe->nexttoggle ^= pkts_left % 2;
status &= EHCI_QTD_STATERRS;
DPRINTFN(/*10*/2, ("ehci_idone: len=%d, actlen=%d, status=0x%x\n",
xfer->length, actlen, status));
xfer->actlen = actlen;
if (status & EHCI_QTD_HALTED) {
if (status & EHCI_QTD_HALTED) {
#ifdef EHCI_DEBUG
char sbuf[128];
#ifndef __riscos
bitmask_snprintf((u_int32_t)status,
"\20\7HALTED\6BUFERR\5BABBLE\4XACTERR"
"\3MISSED", sbuf, sizeof(sbuf));
snprintb(sbuf, sizeof(sbuf),
"\20\7HALTED\6BUFERR\5BABBLE\4XACTERR\3MISSED\1PINGSTATE",
(u_int32_t)status);
#else
sprintf (sbuf, "%s%s%s%s%s%s%s%s",
(status&0x80)?" active":"",
......@@ -941,8 +1100,7 @@ ehci_idone(struct ehci_xfer *ex)
(status&0x01)?" pingstate":"");
#endif
DPRINTFN((status == EHCI_QTD_HALTED) ? 2 : 0,
("ehci_idone: error, addr=%d, endpt=0x%02x, "
DPRINTFN(2, ("ehci_idone: error, addr=%d, endpt=0x%02x, "
"status 0x%s\n",
xfer->pipe->device->address,
xfer->pipe->endpoint->edesc->bEndpointAddress,
......@@ -952,14 +1110,34 @@ ehci_idone(struct ehci_xfer *ex)
ehci_dump_sqtds(ex->sqtdstart);
}
#endif
if (status == EHCI_QTD_HALTED)
xfer->status = USBD_STALLED;
/* low&full speed has an extra error flag */
if (EHCI_QH_GET_EPS(epipe->sqh->qh.qh_endp) !=
EHCI_QH_SPEED_HIGH)
status &= EHCI_QTD_STATERRS | EHCI_QTD_PINGSTATE;
else
status &= EHCI_QTD_STATERRS;
if (status == 0) /* no other errors means a stall */ {
xfer->status = USBD_STALLED;
} else {
xfer->status = USBD_IOERROR; /* more info XXX */
}
/* XXX need to reset TT on missed microframe */
if (status & EHCI_QTD_MISSEDMICRO) {
ehci_softc_t *sc = (ehci_softc_t *)
xfer->pipe->device->bus;
printf("%s: missed microframe, TT reset not "
"implemented, hub might be inoperational\n",
USBDEVNAME(sc->sc_bus.bdev));
}
} else {
xfer->status = USBD_NORMAL_COMPLETION;
}
end:
/* XXX transfer_complete memcpys out transfer data (for in endpoints)
* during this call, before methods->done is called: dma sync required
* beforehand? */
usb_transfer_complete(xfer);
DPRINTFN(/*12*/2, ("ehci_idone: ex=%p done\n", ex));
}
......@@ -969,15 +1147,14 @@ ehci_idone(struct ehci_xfer *ex)
* Then call ehci_intr and return. Use timeout to avoid waiting
* too long.
*/
void
Static void
ehci_waitintr(ehci_softc_t *sc, usbd_xfer_handle xfer)
{
int timo = xfer->timeout;
int usecs;
int timo;
u_int32_t intrs;
xfer->status = USBD_IN_PROGRESS;
for (usecs = timo * 1000000 / hz; usecs > 0; usecs -= 1000) {
for (timo = xfer->timeout; timo >= 0; timo--) {
usb_delay_ms(&sc->sc_bus, 1);
if (sc->sc_dying)
break;
......@@ -1002,7 +1179,7 @@ ehci_waitintr(ehci_softc_t *sc, usbd_xfer_handle xfer)
/* XXX should free TD */
}
void
Static void
ehci_poll(struct usbd_bus *bus)
{
ehci_softc_t *sc = (ehci_softc_t *)bus;
......@@ -1020,6 +1197,17 @@ ehci_poll(struct usbd_bus *bus)
ehci_intr1(sc);
}
#ifndef __riscos /* Not used yet */
void
ehci_childdet(device_t self, device_t child)
{
struct ehci_softc *sc = device_private(self);
KASSERT(sc->sc_child == child);
sc->sc_child = NULL;
}
#endif
int
ehci_detach(struct ehci_softc *sc, int flags)
{
......@@ -1033,45 +1221,35 @@ ehci_detach(struct ehci_softc *sc, int flags)
if (rv != 0)
return (rv);
usb_uncallout(sc->sc_tmo_pcd, ehci_pcd_enable, sc);
#ifndef __riscos
if (sc->sc_powerhook != NULL)
powerhook_disestablish(sc->sc_powerhook);
if (sc->sc_shutdownhook != NULL)
shutdownhook_disestablish(sc->sc_shutdownhook);
#endif
callout_stop(&(sc->sc_tmo_intrlist));
usb_delay_ms(&sc->sc_bus, 300); /* XXX let stray task complete */
/* XXX free other data structures XXX */
mutex_destroy(&sc->sc_doorbell_lock);
mutex_destroy(&sc->sc_intrhead_lock);
EOWRITE4(sc, EHCI_CONFIGFLAG, 0);
return (rv);
}
#ifndef __riscos /* These aren't used yet */
int
ehci_activate(device_ptr_t self, enum devact act)
ehci_activate(device_t self, enum devact act)
{
#ifndef __riscos
struct ehci_softc *sc = (struct ehci_softc *)self;
#endif
int rv = 0;
struct ehci_softc *sc = device_private(self);
switch (act) {
case DVACT_ACTIVATE:
return (EOPNOTSUPP);
break;
case DVACT_DEACTIVATE:
#ifndef __riscos
if (sc->sc_child != NULL)
rv = config_deactivate(sc->sc_child);
sc->sc_dying = 1;
#endif
break;
return 0;
default:
return EOPNOTSUPP;
}
return (rv);
}
/*
......@@ -1080,150 +1258,177 @@ ehci_activate(device_ptr_t self, enum devact act)
* We need to switch to polling mode here, because this routine is
* called from an interrupt context. This is all right since we
* are almost suspended anyway.
*
* Note that this power handler isn't to be registered directly; the
* bus glue needs to call out to it.
*/
void
ehci_power(int why, void *v)
bool
ehci_suspend(device_t dv, const pmf_qual_t *qual)
{
#ifndef __riscos
ehci_softc_t *sc = v;
u_int32_t cmd, hcr;
int s, i;
#ifdef EHCI_DEBUG
DPRINTF(("ehci_power: sc=%p, why=%d\n", sc, why));
if (ehcidebug > 0)
ehci_dump_regs(sc);
#endif
ehci_softc_t *sc = device_private(dv);
int i, s;
uint32_t cmd, hcr;
s = splhardusb();
switch (why) {
case PWR_SUSPEND:
case PWR_STANDBY:
sc->sc_bus.use_polling++;
sc->sc_cmd = EOREAD4(sc, EHCI_USBCMD);
cmd = sc->sc_cmd & ~(EHCI_CMD_ASE | EHCI_CMD_PSE);
EOWRITE4(sc, EHCI_USBCMD, cmd);
sc->sc_bus.use_polling++;
for (i = 0; i < 100; i++) {
hcr = EOREAD4(sc, EHCI_USBSTS) &
(EHCI_STS_ASS | EHCI_STS_PSS);
if (hcr == 0)
break;
for (i = 1; i <= sc->sc_noport; i++) {
cmd = EOREAD4(sc, EHCI_PORTSC(i)) & ~EHCI_PS_CLEAR;
if ((cmd & EHCI_PS_PO) == 0 && (cmd & EHCI_PS_PE) == EHCI_PS_PE)
EOWRITE4(sc, EHCI_PORTSC(i), cmd | EHCI_PS_SUSP);
}
usb_delay_ms(&sc->sc_bus, 1);
}
if (hcr != 0) {
printf("%s: reset timeout\n",
USBDEVNAME(sc->sc_bus.bdev));
}
cmd &= ~EHCI_CMD_RS;
EOWRITE4(sc, EHCI_USBCMD, cmd);
for (i = 0; i < 100; i++) {
hcr = EOREAD4(sc, EHCI_USBSTS) & EHCI_STS_HCH;
if (hcr == EHCI_STS_HCH)
break;
usb_delay_ms(&sc->sc_bus, 1);
}
if (hcr != EHCI_STS_HCH) {
printf("%s: config timeout\n",
USBDEVNAME(sc->sc_bus.bdev));
}
sc->sc_bus.use_polling--;
break;
case PWR_RESUME:
sc->sc_bus.use_polling++;
sc->sc_cmd = EOREAD4(sc, EHCI_USBCMD);
/* restore things in case the bios sucks */
EOWRITE4(sc, EHCI_CTRLDSSEGMENT, 0);
EOWRITE4(sc, EHCI_PERIODICLISTBASE, DMAADDR(&sc->sc_fldma, 0));
EOWRITE4(sc, EHCI_ASYNCLISTADDR,
sc->sc_async_head->physaddr | EHCI_LINK_QH);
EOWRITE4(sc, EHCI_USBINTR, sc->sc_eintrs);
cmd = sc->sc_cmd & ~(EHCI_CMD_ASE | EHCI_CMD_PSE);
EOWRITE4(sc, EHCI_USBCMD, cmd);
EOWRITE4(sc, EHCI_USBCMD, sc->sc_cmd);
for (i = 0; i < 100; i++) {
hcr = EOREAD4(sc, EHCI_USBSTS) & (EHCI_STS_ASS | EHCI_STS_PSS);
if (hcr == 0)
break;
for (i = 0; i < 100; i++) {
hcr = EOREAD4(sc, EHCI_USBSTS) & EHCI_STS_HCH;
if (hcr != EHCI_STS_HCH)
break;
usb_delay_ms(&sc->sc_bus, 1);
}
if (hcr != 0)
printf("%s: reset timeout\n", device_xname(dv));
usb_delay_ms(&sc->sc_bus, 1);
}
if (hcr == EHCI_STS_HCH) {
printf("%s: config timeout\n",
USBDEVNAME(sc->sc_bus.bdev));
}
cmd &= ~EHCI_CMD_RS;
EOWRITE4(sc, EHCI_USBCMD, cmd);
usb_delay_ms(&sc->sc_bus, USB_RESUME_WAIT);
for (i = 0; i < 100; i++) {
hcr = EOREAD4(sc, EHCI_USBSTS) & EHCI_STS_HCH;
if (hcr == EHCI_STS_HCH)
break;
sc->sc_bus.use_polling--;
break;
case PWR_SOFTSUSPEND:
case PWR_SOFTSTANDBY:
case PWR_SOFTRESUME:
break;
usb_delay_ms(&sc->sc_bus, 1);
}
if (hcr != EHCI_STS_HCH)
printf("%s: config timeout\n", device_xname(dv));
sc->sc_bus.use_polling--;
splx(s);
#endif
return true;
}
bool
ehci_resume(device_t dv, const pmf_qual_t *qual)
{
ehci_softc_t *sc = device_private(dv);
int i;
uint32_t cmd, hcr;
/* restore things in case the bios sucks */
EOWRITE4(sc, EHCI_CTRLDSSEGMENT, 0);
EOWRITE4(sc, EHCI_PERIODICLISTBASE, DMAADDR(&sc->sc_fldma, 0));
EOWRITE4(sc, EHCI_ASYNCLISTADDR,
sc->sc_async_head->physaddr | EHCI_LINK_QH);
EOWRITE4(sc, EHCI_USBINTR, sc->sc_eintrs & ~EHCI_INTR_PCIE);
EOWRITE4(sc, EHCI_USBCMD, sc->sc_cmd);
hcr = 0;
for (i = 1; i <= sc->sc_noport; i++) {
cmd = EOREAD4(sc, EHCI_PORTSC(i)) & ~EHCI_PS_CLEAR;
if ((cmd & EHCI_PS_PO) == 0 &&
(cmd & EHCI_PS_SUSP) == EHCI_PS_SUSP) {
EOWRITE4(sc, EHCI_PORTSC(i), cmd | EHCI_PS_FPR);
hcr = 1;
}
}
if (hcr) {
usb_delay_ms(&sc->sc_bus, USB_RESUME_WAIT);
for (i = 1; i <= sc->sc_noport; i++) {
cmd = EOREAD4(sc, EHCI_PORTSC(i)) & ~EHCI_PS_CLEAR;
if ((cmd & EHCI_PS_PO) == 0 &&
(cmd & EHCI_PS_SUSP) == EHCI_PS_SUSP)
EOWRITE4(sc, EHCI_PORTSC(i),
cmd & ~EHCI_PS_FPR);
}
}
EOWRITE4(sc, EHCI_USBCMD, sc->sc_cmd);
EOWRITE4(sc, EHCI_USBINTR, sc->sc_eintrs);
for (i = 0; i < 100; i++) {
hcr = EOREAD4(sc, EHCI_USBSTS) & EHCI_STS_HCH;
if (hcr != EHCI_STS_HCH)
break;
usb_delay_ms(&sc->sc_bus, 1);
}
if (hcr == EHCI_STS_HCH)
printf("%s: config timeout\n", device_xname(dv));
return true;
}
#endif
/*
* Shut down the controller when the system is going down.
*/
void
bool
#ifdef __riscos
ehci_shutdown(void *v)
{
ehci_softc_t *sc = v;
#else
ehci_shutdown(device_t self, int flags)
{
ehci_softc_t *sc = device_private(self);
#endif
DPRINTF(("ehci_shutdown: stopping the HC\n"));
EOWRITE4(sc, EHCI_USBCMD, 0); /* Halt controller */
EOWRITE4(sc, EHCI_USBCMD, EHCI_CMD_HCRESET);
#ifdef __riscos
EOREAD4(sc, EHCI_USBCMD ); /* flush command */
#endif
return true;
}
usbd_status
Static usbd_status
ehci_allocm(struct usbd_bus *bus, usb_dma_t *dma, u_int32_t size)
{
struct ehci_softc *sc = (struct ehci_softc *)bus;
usbd_status err;
err = usb_allocmem(&sc->sc_bus, size, 0, dma);
/* The EHCI controller in the DM37x seems to have difficulty if the last packet of a bulk transfer is a short packet that crosses a page boundary. It looks like the second half of the packet doesn't get written to memory, or gets written to completely the wrong place.
This problem is easiest to reproduce using the USB ethernet on the BB-xM
As a simple workaround, force all EHCI buffers to be 512 byte aligned */
err = usb_allocmem(&sc->sc_bus, size, 512, dma);
#ifndef __riscos
if (err == USBD_NOMEM)
err = usb_reserve_allocm(&sc->sc_dma_reserve, dma, size);
if (err == USBD_NOMEM)
err = usb_reserve_allocm(&sc->sc_dma_reserve, dma, size);
#endif
#ifdef EHCI_DEBUG
if (err)
printf("ehci_allocm: usb_allocmem()=%d\n", err);
printf("ehci_allocm: usb_allocmem()=%d\n", err);
#endif
return (err);
}
void
Static void
ehci_freem(struct usbd_bus *bus, usb_dma_t *dma)
{
struct ehci_softc *sc = (struct ehci_softc *)bus;
(void) sc;
#ifndef __riscos
if (dma->block->flags & USB_DMA_RESERVE) {
usb_reserve_freem(&((struct ehci_softc *)bus)->sc_dma_reserve,
dma);
return;
}
if (dma->block->flags & USB_DMA_RESERVE) {
usb_reserve_freem(&sc->sc_dma_reserve,
dma);
return;
}
#endif
usb_freemem(&sc->sc_bus, dma);
}
usbd_xfer_handle
Static usbd_xfer_handle
ehci_allocx(struct usbd_bus *bus)
{
struct ehci_softc *sc = (struct ehci_softc *)bus;
......@@ -1234,7 +1439,7 @@ ehci_allocx(struct usbd_bus *bus)
SIMPLEQ_REMOVE_HEAD(&sc->sc_free_xfers, next);
#ifdef DIAGNOSTIC
if (xfer->busy_free != XFER_FREE) {
printf("ehci_allocx: xfer=%p not free, 0x%08x\n", xfer,
printf("ehci_allocx: xfer=%p not free, 0x%08x\n", xfer,
xfer->busy_free);
}
#endif
......@@ -1242,7 +1447,7 @@ ehci_allocx(struct usbd_bus *bus)
xfer = malloc(sizeof(struct ehci_xfer), M_USB, M_NOWAIT);
}
if (xfer != NULL) {
memset(xfer, 0, sizeof (struct ehci_xfer));
memset(xfer, 0, sizeof(struct ehci_xfer));
#ifdef DIAGNOSTIC
EXFER(xfer)->isdone = 1;
xfer->busy_free = XFER_BUSY;
......@@ -1251,21 +1456,19 @@ ehci_allocx(struct usbd_bus *bus)
return (xfer);
}
void
Static void
ehci_freex(struct usbd_bus *bus, usbd_xfer_handle xfer)
{
struct ehci_softc *sc = (struct ehci_softc *)bus;
#ifdef DIAGNOSTIC
if (xfer->busy_free != XFER_BUSY) {
printf("ehci_freex: xfer=%p not busy, 0x%08x\n", xfer,
printf("ehci_freex: xfer=%p not busy, 0x%08x\n", xfer,
xfer->busy_free);
return;
}
xfer->busy_free = XFER_FREE;
if (!EXFER(xfer)->isdone) {
printf("ehci_freex: !isdone\n");
return;
printf("ehci_freex: !isdone\n");
}
#endif
SIMPLEQ_INSERT_HEAD(&sc->sc_free_xfers, xfer, next);
......@@ -1278,13 +1481,13 @@ ehci_device_clear_toggle(usbd_pipe_handle pipe)
DPRINTF(("ehci_device_clear_toggle: epipe=%p status=0x%x\n",
epipe, epipe->sqh->qh.qh_qtd.qtd_status));
#ifdef USB_DEBUG
#ifdef EHCI_DEBUG
#ifndef __riscos
if (ehcidebug)
usbd_dump_pipe(pipe);
#endif
#endif
epipe->nexttoggle = 0;
epipe->nexttoggle = 0;
}
Static void
......@@ -1293,21 +1496,21 @@ ehci_noop(usbd_pipe_handle pipe)
}
#ifdef EHCI_DEBUG
void
Static void
ehci_dump_regs(ehci_softc_t *sc)
{
int i;
printf("cmd=0x%08x, sts=0x%08x, ien=0x%08x\n",
printf("cmd=0x%08x, sts=0x%08x, ien=0x%08x\n",
EOREAD4(sc, EHCI_USBCMD),
EOREAD4(sc, EHCI_USBSTS),
EOREAD4(sc, EHCI_USBINTR));
printf("frindex=0x%08x ctrdsegm=0x%08x periodic=0x%08x async=0x%08x\n",
printf("frindex=0x%08x ctrdsegm=0x%08x periodic=0x%08x async=0x%08x\n",
EOREAD4(sc, EHCI_FRINDEX),
EOREAD4(sc, EHCI_CTRLDSSEGMENT),
EOREAD4(sc, EHCI_PERIODICLISTBASE),
EOREAD4(sc, EHCI_ASYNCLISTADDR));
for (i = 1; i <= sc->sc_noport; i++)
printf("port %d status=0x%08x\n", i,
printf("port %d status=0x%08x\n", i,
EOREAD4(sc, EHCI_PORTSC(i)));
}
......@@ -1321,28 +1524,28 @@ ehci_dump(void)
ehci_dump_regs(theehci);
}
void
Static void
ehci_dump_link(ehci_link_t link, int type)
{
link = le32toh(link);
printf("0x%08x", link);
printf("0x%08x", link);
if (link & EHCI_LINK_TERMINATE)
printf("<T>");
printf("<T>");
else {
printf("<");
printf("<");
if (type) {
switch (EHCI_LINK_TYPE(link)) {
case EHCI_LINK_ITD: printf("ITD"); break;
case EHCI_LINK_QH: printf("QH"); break;
case EHCI_LINK_SITD: printf("SITD"); break;
case EHCI_LINK_FSTN: printf("FSTN"); break;
case EHCI_LINK_ITD: printf("ITD"); break;
case EHCI_LINK_QH: printf("QH"); break;
case EHCI_LINK_SITD: printf("SITD"); break;
case EHCI_LINK_FSTN: printf("FSTN"); break;
}
}
printf(">");
printf(">");
}
}
void
Static void
ehci_dump_sqtds(ehci_soft_qtd_t *sqtd)
{
int i;
......@@ -1351,33 +1554,44 @@ ehci_dump_sqtds(ehci_soft_qtd_t *sqtd)
stop = 0;
for (i = 0; sqtd && i < 20 && !stop; sqtd = sqtd->nextqtd, i++) {
ehci_dump_sqtd(sqtd);
stop = sqtd->qtd.qtd_next & htole32(EHCI_LINK_TERMINATE);
usb_syncmem(&sqtd->dma,
sqtd->offs + offsetof(ehci_qtd_t, qtd_next),
sizeof(sqtd->qtd),
BUS_DMASYNC_POSTWRITE | BUS_DMASYNC_POSTREAD);
stop = sqtd->qtd.qtd_next & htole32(EHCI_LINK_TERMINATE);
usb_syncmem(&sqtd->dma,
sqtd->offs + offsetof(ehci_qtd_t, qtd_next),
sizeof(sqtd->qtd), BUS_DMASYNC_PREREAD);
}
if (sqtd)
printf("dump aborted, too many TDs\n");
printf("dump aborted, too many TDs\n");
}
void
Static void
ehci_dump_sqtd(ehci_soft_qtd_t *sqtd)
{
printf("QTD(%p) at 0x%08x:\n", sqtd, sqtd->physaddr);
usb_syncmem(&sqtd->dma, sqtd->offs,
sizeof(sqtd->qtd), BUS_DMASYNC_POSTWRITE | BUS_DMASYNC_POSTREAD);
printf("QTD(%p) at 0x%08x:\n", sqtd, sqtd->physaddr);
ehci_dump_qtd(&sqtd->qtd);
usb_syncmem(&sqtd->dma, sqtd->offs,
sizeof(sqtd->qtd), BUS_DMASYNC_PREREAD);
}
void
Static void
ehci_dump_qtd(ehci_qtd_t *qtd)
{
u_int32_t s;
char sbuf[128];
printf(" next="); ehci_dump_link(qtd->qtd_next, 0);
printf(" altnext="); ehci_dump_link(qtd->qtd_altnext, 0);
printf("\n");
printf(" next="); ehci_dump_link(qtd->qtd_next, 0);
printf(" altnext="); ehci_dump_link(qtd->qtd_altnext, 0);
printf("\n");
s = le32toh(qtd->qtd_status);
#ifndef __riscos
bitmask_snprintf(EHCI_QTD_GET_STATUS(s),
"\20\10ACTIVE\7HALTED\6BUFERR\5BABBLE\4XACTERR"
"\3MISSED\2SPLIT\1PING", sbuf, sizeof(sbuf));
snprintb(sbuf, sizeof(sbuf),
"\20\10ACTIVE\7HALTED\6BUFERR\5BABBLE\4XACTERR"
"\3MISSED\2SPLIT\1PING", EHCI_QTD_GET_STATUS(s));
#else
sprintf (sbuf, "%s%s%s%s%s%s%s%s",
(s&0x80)?" active":"",
......@@ -1389,53 +1603,95 @@ ehci_dump_qtd(ehci_qtd_t *qtd)
(s&0x02)?" splitxstate":"",
(s&0x01)?" pingstate":"");
#endif
logprintf(" status=0x%08x: toggle=%d bytes=0x%x ioc=%d c_page=0x%x\n",
printf(" status=0x%08x: toggle=%d bytes=0x%x ioc=%d c_page=0x%x\n",
s, EHCI_QTD_GET_TOGGLE(s), EHCI_QTD_GET_BYTES(s),
EHCI_QTD_GET_IOC(s), EHCI_QTD_GET_C_PAGE(s));
printf(" cerr=%d pid=%d stat=0x%s\n", EHCI_QTD_GET_CERR(s),
printf(" cerr=%d pid=%d stat=0x%s\n", EHCI_QTD_GET_CERR(s),
EHCI_QTD_GET_PID(s), sbuf);
for (s = 0; s < 5; s++)
printf(" buffer[%d]=0x%08x\n", s, le32toh(qtd->qtd_buffer[s]));
printf(" buffer[%d]=0x%08x\n", s, le32toh(qtd->qtd_buffer[s]));
}
void
Static void
ehci_dump_sqh(ehci_soft_qh_t *sqh)
{
ehci_qh_t *qh = &sqh->qh;
u_int32_t endp, endphub;
printf("QH(%p) at 0x%08x:\n", sqh, sqh->physaddr);
printf(" link="); ehci_dump_link(qh->qh_link, 1); printf("\n");
usb_syncmem(&sqh->dma, sqh->offs,
sizeof(sqh->qh), BUS_DMASYNC_POSTWRITE | BUS_DMASYNC_POSTREAD);
printf("QH(%p) at 0x%08x:\n", sqh, sqh->physaddr);
printf(" link="); ehci_dump_link(qh->qh_link, 1); printf("\n");
endp = le32toh(qh->qh_endp);
printf(" endp=0x%08x\n", endp);
printf(" addr=0x%02x inact=%d endpt=%d eps=%d dtc=%d hrecl=%d\n",
printf(" endp=0x%08x\n", endp);
printf(" addr=0x%02x inact=%d endpt=%d eps=%d dtc=%d hrecl=%d\n",
EHCI_QH_GET_ADDR(endp), EHCI_QH_GET_INACT(endp),
EHCI_QH_GET_ENDPT(endp), EHCI_QH_GET_EPS(endp),
EHCI_QH_GET_DTC(endp), EHCI_QH_GET_HRECL(endp));
printf(" mpl=0x%x ctl=%d nrl=%d\n",
printf(" mpl=0x%x ctl=%d nrl=%d\n",
EHCI_QH_GET_MPL(endp), EHCI_QH_GET_CTL(endp),
EHCI_QH_GET_NRL(endp));
endphub = le32toh(qh->qh_endphub);
printf(" endphub=0x%08x\n", endphub);
printf(" smask=0x%02x cmask=0x%02x huba=0x%02x port=%d mult=%d\n",
printf(" endphub=0x%08x\n", endphub);
printf(" smask=0x%02x cmask=0x%02x huba=0x%02x port=%d mult=%d\n",
EHCI_QH_GET_SMASK(endphub), EHCI_QH_GET_CMASK(endphub),
EHCI_QH_GET_HUBA(endphub), EHCI_QH_GET_PORT(endphub),
EHCI_QH_GET_MULT(endphub));
printf(" curqtd="); ehci_dump_link(qh->qh_curqtd, 0); printf("\n");
printf("Overlay qTD:\n");
printf(" curqtd="); ehci_dump_link(qh->qh_curqtd, 0); printf("\n");
printf("Overlay qTD:\n");
ehci_dump_qtd(&qh->qh_qtd);
usb_syncmem(&sqh->dma, sqh->offs,
sizeof(sqh->qh), BUS_DMASYNC_PREREAD);
}
#if notyet
Static void
ehci_dump_itd(struct ehci_soft_itd *itd)
{
ehci_isoc_trans_t t;
ehci_isoc_bufr_ptr_t b, b2, b3;
int i;
printf("ITD: next phys=%X\n", itd->itd.itd_next);
for (i = 0; i < EHCI_ITD_NUFRAMES; i++) {
t = le32toh(itd->itd.itd_ctl[i]);
printf("ITDctl %d: stat=%X len=%X ioc=%X pg=%X offs=%X\n", i,
EHCI_ITD_GET_STATUS(t), EHCI_ITD_GET_LEN(t),
EHCI_ITD_GET_IOC(t), EHCI_ITD_GET_PG(t),
EHCI_ITD_GET_OFFS(t));
}
printf("ITDbufr: ");
for (i = 0; i < EHCI_ITD_NBUFFERS; i++)
printf("%X,", EHCI_ITD_GET_BPTR(le32toh(itd->itd.itd_bufr[i])));
b = le32toh(itd->itd.itd_bufr[0]);
b2 = le32toh(itd->itd.itd_bufr[1]);
b3 = le32toh(itd->itd.itd_bufr[2]);
printf("\nep=%X daddr=%X dir=%d maxpkt=%X multi=%X\n",
EHCI_ITD_GET_EP(b), EHCI_ITD_GET_DADDR(b), EHCI_ITD_GET_DIR(b2),
EHCI_ITD_GET_MAXPKT(b2), EHCI_ITD_GET_MULTI(b3));
}
Static void
ehci_dump_sitd(struct ehci_soft_itd *itd)
{
printf("SITD %p next=%p prev=%p xfernext=%p physaddr=%X slot=%d\n",
itd, itd->u.frame_list.next, itd->u.frame_list.prev,
itd->xfer_next, itd->physaddr, itd->slot);
}
#endif
#ifdef DIAGNOSTIC
Static void
ehci_dump_exfer(struct ehci_xfer *ex)
{
printf("ehci_dump_exfer: ex=%p\n", ex);
printf("ehci_dump_exfer: ex=%p sqtdstart=%p end=%p itdstart=%p end=%p isdone=%d\n", ex, ex->sqtdstart, ex->sqtdend, ex->itdstart, ex->itdend, ex->isdone);
}
#endif
#endif
usbd_status
Static usbd_status
ehci_open(usbd_pipe_handle pipe)
{
usbd_device_handle dev = pipe->device;
......@@ -1447,24 +1703,25 @@ ehci_open(usbd_pipe_handle pipe)
ehci_soft_qh_t *sqh;
usbd_status err;
int s;
int ival, speed, naks;
int hshubaddr, hshubport;
int ival, speed, naks;
int hshubaddr, hshubport;
DPRINTFN(1, ("ehci_open: pipe=%p, addr=%d, endpt=%d (%d)\n",
pipe, addr, ed->bEndpointAddress, sc->sc_addr));
if (dev->myhsport) {
hshubaddr = dev->myhsport->parent->address;
hshubport = dev->myhsport->portno;
} else {
hshubaddr = 0;
hshubport = 0;
}
if (dev->myhsport) {
hshubaddr = dev->myhsport->parent->address;
hshubport = dev->myhsport->portno;
} else {
hshubaddr = 0;
hshubport = 0;
}
if (sc->sc_dying)
return (USBD_IOERROR);
epipe->nexttoggle = 0;
epipe->nexttoggle = 0;
if (addr == sc->sc_addr) {
switch (ed->bEndpointAddress) {
case USB_CONTROL_ENDPOINT:
......@@ -1474,6 +1731,8 @@ ehci_open(usbd_pipe_handle pipe)
pipe->methods = &ehci_root_intr_methods;
break;
default:
DPRINTF(("ehci_open: bad bEndpointAddress 0x%02x\n",
ed->bEndpointAddress));
return (USBD_INVAL);
}
return (USBD_NORMAL_COMPLETION);
......@@ -1486,35 +1745,67 @@ ehci_open(usbd_pipe_handle pipe)
case USB_SPEED_HIGH: speed = EHCI_QH_SPEED_HIGH; break;
default: panic("ehci_open: bad device speed %d", dev->speed);
}
naks = 8; /* XXX */
sqh = ehci_alloc_sqh(sc);
if (sqh == NULL)
goto bad0;
/* qh_link filled when the QH is added */
sqh->qh.qh_endp = htole32(
EHCI_QH_SET_ADDR(addr) |
EHCI_QH_SET_ENDPT(UE_GET_ADDR(ed->bEndpointAddress)) |
EHCI_QH_SET_EPS(speed) |
EHCI_QH_DTC |
EHCI_QH_SET_MPL(UGETW(ed->wMaxPacketSize)) |
(speed != EHCI_QH_SPEED_HIGH && xfertype == UE_CONTROL ?
EHCI_QH_CTL : 0) |
EHCI_QH_SET_NRL(naks)
);
sqh->qh.qh_endphub = htole32(
EHCI_QH_SET_MULT(1) |
EHCI_QH_SET_HUBA(hshubaddr) |
EHCI_QH_SET_PORT(hshubport) |
EHCI_QH_SET_CMASK(0x08) | /* XXX */
EHCI_QH_SET_SMASK(xfertype == UE_INTERRUPT ? 0x02 : 0)
);
sqh->qh.qh_curqtd = EHCI_NULL;
/* Fill the overlay qTD */
sqh->qh.qh_qtd.qtd_next = EHCI_NULL;
sqh->qh.qh_qtd.qtd_altnext = EHCI_NULL;
sqh->qh.qh_qtd.qtd_status = htole32(0);
if (speed != EHCI_QH_SPEED_HIGH && xfertype == UE_ISOCHRONOUS) {
#ifndef __riscos
aprint_error_dev(sc->sc_dev, "error opening low/full speed "
"isoc endpoint.\n");
aprint_normal_dev(sc->sc_dev, "a low/full speed device is "
"attached to a USB2 hub, and transaction translations are "
"not yet supported.\n");
aprint_normal_dev(sc->sc_dev, "reattach the device to the "
"root hub instead.\n");
#endif
DPRINTFN(1,("ehci_open: hshubaddr=%d hshubport=%d\n",
hshubaddr, hshubport));
return USBD_INVAL;
}
epipe->sqh = sqh;
/*
* For interrupt transfer, nak throttling must be disabled, but for
* the other transfer type, nak throttling should be enabled from the
* veiwpoint that avoids the memory thrashing.
*/
naks = (xfertype == UE_INTERRUPT) ? 0
: ((speed == EHCI_QH_SPEED_HIGH) ? 4 : 0);
/* Allocate sqh for everything, save isoc xfers */
if (xfertype != UE_ISOCHRONOUS) {
sqh = ehci_alloc_sqh(sc);
if (sqh == NULL)
return (USBD_NOMEM);
/* qh_link filled when the QH is added */
sqh->qh.qh_endp = htole32(
EHCI_QH_SET_ADDR(addr) |
EHCI_QH_SET_ENDPT(UE_GET_ADDR(ed->bEndpointAddress)) |
EHCI_QH_SET_EPS(speed) |
EHCI_QH_DTC |
EHCI_QH_SET_MPL(UGETW(ed->wMaxPacketSize)) |
(speed != EHCI_QH_SPEED_HIGH && xfertype == UE_CONTROL ?
EHCI_QH_CTL : 0) |
EHCI_QH_SET_NRL(naks)
);
sqh->qh.qh_endphub = htole32(
EHCI_QH_SET_MULT(1) |
EHCI_QH_SET_SMASK(xfertype == UE_INTERRUPT ? 0x02 : 0)
);
if (speed != EHCI_QH_SPEED_HIGH)
sqh->qh.qh_endphub |= htole32(
EHCI_QH_SET_PORT(hshubport) |
EHCI_QH_SET_HUBA(hshubaddr) |
EHCI_QH_SET_CMASK(0x08) /* XXX */
);
sqh->qh.qh_curqtd = EHCI_NULL;
/* Fill the overlay qTD */
sqh->qh.qh_qtd.qtd_next = EHCI_NULL;
sqh->qh.qh_qtd.qtd_altnext = EHCI_NULL;
sqh->qh.qh_qtd.qtd_status = htole32(0);
usb_syncmem(&sqh->dma, sqh->offs, sizeof(sqh->qh),
BUS_DMASYNC_PREWRITE | BUS_DMASYNC_PREREAD);
epipe->sqh = sqh;
} else {
sqh = NULL;
} /*xfertype == UE_ISOC*/
switch (xfertype) {
case UE_CONTROL:
......@@ -1522,10 +1813,10 @@ ehci_open(usbd_pipe_handle pipe)
0, &epipe->u.ctl.reqdma);
#ifdef EHCI_DEBUG
if (err)
printf("ehci_open: usb_allocmem()=%d\n", err);
printf("ehci_open: usb_allocmem()=%d\n", err);
#endif
if (err)
goto bad1;
goto bad;
pipe->methods = &ehci_device_ctrl_methods;
s = splusb();
ehci_add_qh(sqh, sc->sc_async_head);
......@@ -1539,40 +1830,75 @@ ehci_open(usbd_pipe_handle pipe)
break;
case UE_INTERRUPT:
pipe->methods = &ehci_device_intr_methods;
ival = pipe->interval;
if (ival == USBD_DEFAULT_INTERVAL)
ival = ed->bInterval;
return (ehci_device_setintr(sc, sqh, ival));
ival = pipe->interval;
if (ival == USBD_DEFAULT_INTERVAL) {
if (speed == EHCI_QH_SPEED_HIGH) {
if (ed->bInterval > 16) {
/*
* illegal with high-speed, but there
* were documentation bugs in the spec,
* so be generous
*/
ival = 256;
} else
ival = (1 << (ed->bInterval - 1)) / 8;
} else
ival = ed->bInterval;
}
err = ehci_device_setintr(sc, sqh, ival);
if (err)
goto bad;
break;
case UE_ISOCHRONOUS:
pipe->methods = &ehci_device_isoc_methods;
return (USBD_INVAL);
if (ed->bInterval == 0 || ed->bInterval > 16) {
printf("ehci: opening pipe with invalid bInterval\n");
err = USBD_INVAL;
goto bad;
}
if (UGETW(ed->wMaxPacketSize) == 0) {
printf("ehci: zero length endpoint open request\n");
err = USBD_INVAL;
goto bad;
}
epipe->u.isoc.next_frame = 0;
epipe->u.isoc.cur_xfers = 0;
break;
default:
return (USBD_INVAL);
DPRINTF(("ehci: bad xfer type %d\n", xfertype));
err = USBD_INVAL;
goto bad;
}
return (USBD_NORMAL_COMPLETION);
bad1:
ehci_free_sqh(sc, sqh);
bad0:
return (USBD_NOMEM);
bad:
if (sqh != NULL)
ehci_free_sqh(sc, sqh);
return (err);
}
/*
* Add an ED to the schedule. Called at splusb().
*/
void
Static void
ehci_add_qh(ehci_soft_qh_t *sqh, ehci_soft_qh_t *head)
{
SPLUSBCHECK;
usb_syncmem(&head->dma, head->offs + offsetof(ehci_qh_t, qh_link),
sizeof(head->qh.qh_link), BUS_DMASYNC_POSTWRITE);
sqh->next = head->next;
sqh->qh.qh_link = head->qh.qh_link;
usb_syncmem(&sqh->dma, sqh->offs + offsetof(ehci_qh_t, qh_link),
sizeof(sqh->qh.qh_link), BUS_DMASYNC_PREWRITE);
head->next = sqh;
head->qh.qh_link = htole32(sqh->physaddr | EHCI_LINK_QH);
usb_syncmem(&head->dma, head->offs + offsetof(ehci_qh_t, qh_link),
sizeof(head->qh.qh_link), BUS_DMASYNC_PREWRITE);
#ifdef EHCI_DEBUG
if (ehcidebug > 5) {
printf("ehci_add_qh:\n");
printf("ehci_add_qh:\n");
ehci_dump_sqh(sqh);
}
#endif
......@@ -1581,7 +1907,7 @@ ehci_add_qh(ehci_soft_qh_t *sqh, ehci_soft_qh_t *head)
/*
* Remove an ED from the schedule. Called at splusb().
*/
void
Static void
ehci_rem_qh(ehci_softc_t *sc, ehci_soft_qh_t *sqh, ehci_soft_qh_t *head)
{
ehci_soft_qh_t *p;
......@@ -1592,33 +1918,49 @@ ehci_rem_qh(ehci_softc_t *sc, ehci_soft_qh_t *sqh, ehci_soft_qh_t *head)
;
if (p == NULL)
panic("ehci_rem_qh: ED not found");
usb_syncmem(&sqh->dma, sqh->offs + offsetof(ehci_qh_t, qh_link),
sizeof(sqh->qh.qh_link), BUS_DMASYNC_POSTWRITE);
p->next = sqh->next;
p->qh.qh_link = sqh->qh.qh_link;
usb_syncmem(&p->dma, p->offs + offsetof(ehci_qh_t, qh_link),
sizeof(p->qh.qh_link), BUS_DMASYNC_PREWRITE);
ehci_sync_hc(sc);
}
void
Static void
ehci_set_qh_qtd(ehci_soft_qh_t *sqh, ehci_soft_qtd_t *sqtd)
{
int i;
u_int32_t status;
int i;
u_int32_t status;
/* Save toggle bit and ping status. */
status = sqh->qh.qh_qtd.qtd_status &
htole32(EHCI_QTD_TOGGLE_MASK |
EHCI_QTD_SET_STATUS(EHCI_QTD_PINGSTATE));
/* Set HALTED to make hw leave it alone. */
sqh->qh.qh_qtd.qtd_status =
htole32(EHCI_QTD_SET_STATUS(EHCI_QTD_HALTED));
/* Save toggle bit and ping status. */
usb_syncmem(&sqh->dma, sqh->offs, sizeof(sqh->qh),
BUS_DMASYNC_POSTWRITE | BUS_DMASYNC_POSTREAD);
status = sqh->qh.qh_qtd.qtd_status &
htole32(EHCI_QTD_TOGGLE_MASK |
EHCI_QTD_SET_STATUS(EHCI_QTD_PINGSTATE));
/* Set HALTED to make hw leave it alone. */
sqh->qh.qh_qtd.qtd_status =
htole32(EHCI_QTD_SET_STATUS(EHCI_QTD_HALTED));
usb_syncmem(&sqh->dma,
sqh->offs + offsetof(ehci_qh_t, qh_qtd.qtd_status),
sizeof(sqh->qh.qh_qtd.qtd_status),
BUS_DMASYNC_PREWRITE | BUS_DMASYNC_PREREAD);
sqh->qh.qh_curqtd = 0;
sqh->qh.qh_qtd.qtd_next = htole32(sqtd->physaddr);
sqh->qh.qh_qtd.qtd_altnext = 0;
for (i = 0; i < EHCI_QTD_NBUFFERS; i++)
sqh->qh.qh_qtd.qtd_buffer[i] = 0;
sqh->qh.qh_qtd.qtd_altnext = 0;
for (i = 0; i < EHCI_QTD_NBUFFERS; i++)
sqh->qh.qh_qtd.qtd_buffer[i] = 0;
sqh->sqtd = sqtd;
/* Set !HALTED && !ACTIVE to start execution, preserve some fields */
sqh->qh.qh_qtd.qtd_status = status;
usb_syncmem(&sqh->dma, sqh->offs, sizeof(sqh->qh),
BUS_DMASYNC_PREWRITE | BUS_DMASYNC_PREREAD);
/* Set !HALTED && !ACTIVE to start execution, preserve some fields */
sqh->qh.qh_qtd.qtd_status = status;
usb_syncmem(&sqh->dma,
sqh->offs + offsetof(ehci_qh_t, qh_qtd.qtd_status),
sizeof(sqh->qh.qh_qtd.qtd_status),
BUS_DMASYNC_PREWRITE | BUS_DMASYNC_PREREAD);
}
/*
......@@ -1627,7 +1969,7 @@ ehci_set_qh_qtd(ehci_soft_qh_t *sqh, ehci_soft_qtd_t *sqtd)
* the interrupt.
* To make this easier we first obtain exclusive use of the doorbell.
*/
void
Static void
ehci_sync_hc(ehci_softc_t *sc)
{
int s, error;
......@@ -1637,7 +1979,7 @@ ehci_sync_hc(ehci_softc_t *sc)
return;
}
DPRINTFN(2,("ehci_sync_hc: enter\n"));
lockmgr(&sc->sc_doorbell_lock, LK_EXCLUSIVE, NULL); /* get doorbell */
mutex_enter(&sc->sc_doorbell_lock); /* get doorbell */
s = splhardusb();
/* ask for doorbell */
EOWRITE4(sc, EHCI_USBCMD, EOREAD4(sc, EHCI_USBCMD) | EHCI_CMD_IAAD);
......@@ -1651,20 +1993,69 @@ ehci_sync_hc(ehci_softc_t *sc)
DPRINTFN(1,("ehci_sync_hc: cmd=0x%08x sts=0x%08x\n",
EOREAD4(sc, EHCI_USBCMD), EOREAD4(sc, EHCI_USBSTS)));
splx(s);
lockmgr(&sc->sc_doorbell_lock, LK_RELEASE, NULL); /* release doorbell */
mutex_exit(&sc->sc_doorbell_lock); /* release doorbell */
#ifdef DIAGNOSTIC
if (error)
printf("ehci_sync_hc: tsleep() = %d\n", error);
printf("ehci_sync_hc: tsleep() = %d\n", error);
#endif
DPRINTFN(2,("ehci_sync_hc: exit\n"));
}
/*Call at splusb*/
Static void
ehci_rem_free_itd_chain(ehci_softc_t *sc, struct ehci_xfer *exfer)
{
struct ehci_soft_itd *itd, *prev;
prev = NULL;
if (exfer->itdstart == NULL || exfer->itdend == NULL)
panic("ehci isoc xfer being freed, but with no itd chain\n");
for (itd = exfer->itdstart; itd != NULL; itd = itd->xfer_next) {
prev = itd->u.frame_list.prev;
/* Unlink itd from hardware chain, or frame array */
if (prev == NULL) { /* We're at the table head */
sc->sc_softitds[itd->slot] = itd->u.frame_list.next;
sc->sc_flist[itd->slot] = itd->itd.itd_next;
usb_syncmem(&sc->sc_fldma,
sizeof(ehci_link_t) * itd->slot,
sizeof(ehci_link_t),
BUS_DMASYNC_PREWRITE | BUS_DMASYNC_PREREAD);
if (itd->u.frame_list.next != NULL)
itd->u.frame_list.next->u.frame_list.prev = NULL;
} else {
/* XXX this part is untested... */
prev->itd.itd_next = itd->itd.itd_next;
usb_syncmem(&itd->dma,
itd->offs + offsetof(ehci_itd_t, itd_next),
sizeof(itd->itd.itd_next), BUS_DMASYNC_PREWRITE);
prev->u.frame_list.next = itd->u.frame_list.next;
if (itd->u.frame_list.next != NULL)
itd->u.frame_list.next->u.frame_list.prev = prev;
}
}
prev = NULL;
for (itd = exfer->itdstart; itd != NULL; itd = itd->xfer_next) {
if (prev != NULL)
ehci_free_itd(sc, prev);
prev = itd;
}
if (prev)
ehci_free_itd(sc, prev);
exfer->itdstart = NULL;
exfer->itdend = NULL;
}
/***********/
/*
* Data structures and routines to emulate the root hub.
*/
Static usb_device_descriptor_t ehci_devd = {
Static const usb_device_descriptor_t ehci_devd = {
USB_DEVICE_DESCRIPTOR_SIZE,
UDESC_DEVICE, /* type */
{0x00, 0x02}, /* USB version */
......@@ -1677,7 +2068,7 @@ Static usb_device_descriptor_t ehci_devd = {
1 /* # of configurations */
};
Static usb_device_qualifier_t ehci_odevd = {
Static const usb_device_qualifier_t ehci_odevd = {
USB_DEVICE_DESCRIPTOR_SIZE,
UDESC_DEVICE_QUALIFIER, /* type */
{0x00, 0x02}, /* USB version */
......@@ -1689,7 +2080,7 @@ Static usb_device_qualifier_t ehci_odevd = {
0
};
Static usb_config_descriptor_t ehci_confd = {
Static const usb_config_descriptor_t ehci_confd = {
USB_CONFIG_DESCRIPTOR_SIZE,
UDESC_CONFIG,
{USB_CONFIG_DESCRIPTOR_SIZE +
......@@ -1698,11 +2089,11 @@ Static usb_config_descriptor_t ehci_confd = {
1,
1,
0,
UC_SELF_POWERED,
UC_ATTR_MBO | UC_SELF_POWERED,
0 /* max power */
};
Static usb_interface_descriptor_t ehci_ifcd = {
Static const usb_interface_descriptor_t ehci_ifcd = {
USB_INTERFACE_DESCRIPTOR_SIZE,
UDESC_INTERFACE,
0,
......@@ -1714,42 +2105,26 @@ Static usb_interface_descriptor_t ehci_ifcd = {
0
};
Static usb_endpoint_descriptor_t ehci_endpd = {
Static const usb_endpoint_descriptor_t ehci_endpd = {
USB_ENDPOINT_DESCRIPTOR_SIZE,
UDESC_ENDPOINT,
UE_DIR_IN | EHCI_INTR_ENDPT,
UE_INTERRUPT,
{8, 0}, /* max packet */
255
12
};
Static usb_hub_descriptor_t ehci_hubd = {
Static const usb_hub_descriptor_t ehci_hubd = {
USB_HUB_DESCRIPTOR_SIZE,
UDESC_HUB,
0,
{0,0},
0,
0,
{0},
{""},
{""},
};
Static int
ehci_str(usb_string_descriptor_t* p, int l, char *s)
{
int i;
if (l == 0)
return (0);
p->bLength = 2 * strlen(s) + 2;
if (l == 1)
return (1);
p->bDescriptorType = UDESC_STRING;
l -= 2;
for (i = 0; s[i] && l > 1; i++, l -= 2)
USETW2(p->bString[i], 0, s[i]);
return (2*i+2);
}
/*
* Simulate a hardware hub by handling all the necessary requests.
*/
......@@ -1777,6 +2152,8 @@ ehci_root_ctrl_start(usbd_xfer_handle xfer)
int s, len, value, index, l, totlen = 0;
usb_port_status_t ps;
usb_hub_descriptor_t hubd;
usb_device_descriptor_t devd;
usb_config_descriptor_t confd;
usbd_status err;
u_int32_t v;
......@@ -1790,7 +2167,7 @@ ehci_root_ctrl_start(usbd_xfer_handle xfer)
#endif
req = &xfer->request;
DPRINTFN(4,("ehci_root_ctrl_start: type=0x%02x request=%02x\n",
DPRINTFN(4,("ehci_root_ctrl_start: type=0x%02x request=%02x\n",
req->bmRequestType, req->bRequest));
len = UGETW(req->wLength);
......@@ -1817,19 +2194,22 @@ ehci_root_ctrl_start(usbd_xfer_handle xfer)
}
break;
case C(UR_GET_DESCRIPTOR, UT_READ_DEVICE):
DPRINTFN(8,("ehci_root_ctrl_start: wValue=0x%04x\n", value));
DPRINTFN(8,("ehci_root_ctrl_start: wValue=0x%04x\n", value));
if (len == 0)
break;
switch(value >> 8) {
case UDESC_DEVICE:
if ((value & 0xff) != 0) {
err = USBD_IOERROR;
goto ret;
}
devd = ehci_devd;
USETW(devd.idVendor, sc->sc_id_vendor);
totlen = l = min(len, USB_DEVICE_DESCRIPTOR_SIZE);
USETW(ehci_devd.idVendor, sc->sc_id_vendor);
#if defined(__CC_NORCROFT) && !defined(DISABLE_PACKED)
memcpy(buf, (void*) &ehci_devd, l);
memcpy(buf, (void*) &devd, l);
#else
memcpy(buf, &ehci_devd, l);
memcpy(buf, &devd, l);
#endif
break;
/*
......@@ -1858,14 +2238,14 @@ ehci_root_ctrl_start(usbd_xfer_handle xfer)
err = USBD_IOERROR;
goto ret;
}
confd = ehci_confd;
confd.bDescriptorType = value >> 8;
totlen = l = min(len, USB_CONFIG_DESCRIPTOR_SIZE);
#if defined(__CC_NORCROFT) && !defined(DISABLE_PACKED)
memcpy(buf, (void*) &ehci_confd, l);
memcpy(buf, (void*) &confd, l);
#else
memcpy(buf, &ehci_confd, l);
memcpy(buf, &confd, l);
#endif
((usb_config_descriptor_t *)buf)->bDescriptorType =
value >> 8;
buf = (char *)buf + l;
len -= l;
l = min(len, USB_INTERFACE_DESCRIPTOR_SIZE);
......@@ -1886,21 +2266,21 @@ ehci_root_ctrl_start(usbd_xfer_handle xfer)
#endif
break;
case UDESC_STRING:
if (len == 0)
break;
*(u_int8_t *)buf = 0;
totlen = 1;
#define sd ((usb_string_descriptor_t *)buf)
switch (value & 0xff) {
case 0: /* Language table */
totlen = ehci_str(buf, len, "\001");
break;
case 0: /* Language table */
totlen = usb_makelangtbl(sd, len);
break;
case 1: /* Vendor */
totlen = ehci_str(buf, len, sc->sc_vendor);
totlen = usb_makestrdesc(sd, len,
sc->sc_vendor);
break;
case 2: /* Product */
totlen = ehci_str(buf, len, "EHCI root hub");
totlen = usb_makestrdesc(sd, len,
"EHCI root hub");
break;
}
#undef sd
break;
default:
err = USBD_IOERROR;
......@@ -1955,7 +2335,7 @@ ehci_root_ctrl_start(usbd_xfer_handle xfer)
case C(UR_CLEAR_FEATURE, UT_WRITE_CLASS_DEVICE):
break;
case C(UR_CLEAR_FEATURE, UT_WRITE_CLASS_OTHER):
DPRINTFN(8, ("ehci_root_ctrl_start: UR_CLEAR_PORT_FEATURE "
DPRINTFN(4, ("ehci_root_ctrl_start: UR_CLEAR_PORT_FEATURE "
"port=%d feature=%d\n",
index, value));
if (index < 1 || index > sc->sc_noport) {
......@@ -1963,23 +2343,38 @@ ehci_root_ctrl_start(usbd_xfer_handle xfer)
goto ret;
}
port = EHCI_PORTSC(index);
v = EOREAD4(sc, port) &~ EHCI_PS_CLEAR;
v = EOREAD4(sc, port);
DPRINTFN(4, ("ehci_root_ctrl_start: portsc=0x%08x\n", v));
v &= ~EHCI_PS_CLEAR;
switch(value) {
case UHF_PORT_ENABLE:
EOWRITE4(sc, port, v &~ EHCI_PS_PE);
break;
case UHF_PORT_SUSPEND:
EOWRITE4(sc, port, v &~ EHCI_PS_SUSP);
if (!(v & EHCI_PS_SUSP)) /* not suspended */
break;
v &= ~EHCI_PS_SUSP;
EOWRITE4(sc, port, v | EHCI_PS_FPR);
/* see USB2 spec ch. 7.1.7.7 */
usb_delay_ms(&sc->sc_bus, 20);
EOWRITE4(sc, port, v);
usb_delay_ms(&sc->sc_bus, 2);
#ifdef DEBUG
v = EOREAD4(sc, port);
if (v & (EHCI_PS_FPR | EHCI_PS_SUSP))
printf("ehci: resume failed: %x\n", v);
#endif
break;
case UHF_PORT_POWER:
EOWRITE4(sc, port, v &~ EHCI_PS_PP);
if (sc->sc_hasppc)
EOWRITE4(sc, port, v &~ EHCI_PS_PP);
break;
case UHF_PORT_TEST:
DPRINTFN(2,("ehci_root_ctrl_start: clear port test "
DPRINTFN(2,("ehci_root_ctrl_start: clear port test "
"%d\n", index));
break;
case UHF_PORT_INDICATOR:
DPRINTFN(2,("ehci_root_ctrl_start: clear port ind "
DPRINTFN(2,("ehci_root_ctrl_start: clear port ind "
"%d\n", index));
EOWRITE4(sc, port, v &~ EHCI_PS_PIC);
break;
......@@ -1996,7 +2391,7 @@ ehci_root_ctrl_start(usbd_xfer_handle xfer)
EOWRITE4(sc, port, v | EHCI_PS_OCC);
break;
case UHF_C_PORT_RESET:
sc->sc_isreset = 0;
sc->sc_isreset[index] = 0;
break;
default:
err = USBD_IOERROR;
......@@ -2009,17 +2404,15 @@ ehci_root_ctrl_start(usbd_xfer_handle xfer)
case UHF_C_PORT_SUSPEND:
case UHF_C_PORT_OVER_CURRENT:
case UHF_C_PORT_RESET:
/* Enable RHSC interrupt if condition is cleared. */
if ((OREAD4(sc, port) >> 16) == 0)
ehci_pcd_able(sc, 1);
break;
default:
break;
}
#endif
break;
case C(UR_GET_DESCRIPTOR, UT_READ_CLASS_DEVICE):
if ((value & 0xff) != 0) {
if (len == 0)
break;
if ((value & 0xff) != 0) {
err = USBD_IOERROR;
goto ret;
}
......@@ -2029,7 +2422,7 @@ ehci_root_ctrl_start(usbd_xfer_handle xfer)
USETW(hubd.wHubCharacteristics,
EHCI_HCS_PPC(v) ? UHD_PWR_INDIVIDUAL : UHD_PWR_NO_SWITCH |
EHCI_HCS_P_INDICATOR(EREAD4(sc, EHCI_HCSPARAMS))
? UHD_PORT_IND : 0);
? UHD_PORT_IND : 0);
hubd.bPwrOn2PwrGood = 200; /* XXX can't find out? */
for (i = 0, l = sc->sc_noport; l > 0; i++, l -= 8, v >>= 8)
hubd.DeviceRemovable[i++] = 0; /* XXX can't find out? */
......@@ -2051,7 +2444,7 @@ ehci_root_ctrl_start(usbd_xfer_handle xfer)
totlen = len;
break;
case C(UR_GET_STATUS, UT_READ_CLASS_OTHER):
DPRINTFN(8,("ehci_root_ctrl_start: get port status i=%d\n",
DPRINTFN(8,("ehci_root_ctrl_start: get port status i=%d\n",
index));
if (index < 1 || index > sc->sc_noport) {
err = USBD_IOERROR;
......@@ -2062,7 +2455,7 @@ ehci_root_ctrl_start(usbd_xfer_handle xfer)
goto ret;
}
v = EOREAD4(sc, EHCI_PORTSC(index));
DPRINTFN(8,("ehci_root_ctrl_start: port status=0x%04x\n",
DPRINTFN(8,("ehci_root_ctrl_start: port status=0x%04x\n",
v));
i = UPS_HIGH_SPEED;
if (v & EHCI_PS_CS) i |= UPS_CURRENT_CONNECT_STATUS;
......@@ -2076,7 +2469,7 @@ ehci_root_ctrl_start(usbd_xfer_handle xfer)
if (v & EHCI_PS_CSC) i |= UPS_C_CONNECT_STATUS;
if (v & EHCI_PS_PEC) i |= UPS_C_PORT_ENABLED;
if (v & EHCI_PS_OCC) i |= UPS_C_OVERCURRENT_INDICATOR;
if (sc->sc_isreset) i |= UPS_C_PORT_RESET;
if (sc->sc_isreset[index]) i |= UPS_C_PORT_RESET;
USETW(ps.wPortChange, i);
l = min(len, sizeof ps);
#if defined(__CC_NORCROFT) && !defined(DISABLE_PACKED)
......@@ -2097,7 +2490,9 @@ ehci_root_ctrl_start(usbd_xfer_handle xfer)
goto ret;
}
port = EHCI_PORTSC(index);
v = EOREAD4(sc, port) &~ EHCI_PS_CLEAR;
v = EOREAD4(sc, port);
DPRINTFN(4, ("ehci_root_ctrl_start: portsc=0x%08x\n", v));
v &= ~EHCI_PS_CLEAR;
switch(value) {
case UHF_PORT_ENABLE:
EOWRITE4(sc, port, v | EHCI_PS_PE);
......@@ -2106,7 +2501,7 @@ ehci_root_ctrl_start(usbd_xfer_handle xfer)
EOWRITE4(sc, port, v | EHCI_PS_SUSP);
break;
case UHF_PORT_RESET:
DPRINTFN(5,("ehci_root_ctrl_start: reset port %d\n",
DPRINTFN(5,("ehci_root_ctrl_start: reset port %d\n",
index));
if (EHCI_PS_IS_LOWSPEED(v)) {
/* Low speed device, give up ownership. */
......@@ -2133,7 +2528,7 @@ ehci_root_ctrl_start(usbd_xfer_handle xfer)
v = EOREAD4(sc, port);
DPRINTF(("ehci after reset, status=0x%08x\n", v));
if (v & EHCI_PS_PR) {
printf("%s: port reset timeout\n",
printf("%s: port reset timeout\n",
USBDEVNAME(sc->sc_bus.bdev));
return (USBD_TIMEOUT);
}
......@@ -2142,21 +2537,23 @@ ehci_root_ctrl_start(usbd_xfer_handle xfer)
ehci_disown(sc, index, 0);
break;
}
sc->sc_isreset = 1;
sc->sc_isreset[index] = 1;
DPRINTF(("ehci port %d reset, status = 0x%08x\n",
index, v));
break;
case UHF_PORT_POWER:
DPRINTFN(2,("ehci_root_ctrl_start: set port power "
"%d\n", index));
EOWRITE4(sc, port, v | EHCI_PS_PP);
DPRINTFN(2,("ehci_root_ctrl_start: set port power "
"%d (has PPC = %d)\n", index,
sc->sc_hasppc));
if (sc->sc_hasppc)
EOWRITE4(sc, port, v | EHCI_PS_PP);
break;
case UHF_PORT_TEST:
DPRINTFN(2,("ehci_root_ctrl_start: set port test "
DPRINTFN(2,("ehci_root_ctrl_start: set port test "
"%d\n", index));
break;
case UHF_PORT_INDICATOR:
DPRINTFN(2,("ehci_root_ctrl_start: set port ind "
DPRINTFN(2,("ehci_root_ctrl_start: set port ind "
"%d\n", index));
EOWRITE4(sc, port, v | EHCI_PS_PIC);
break;
......@@ -2184,7 +2581,7 @@ ehci_root_ctrl_start(usbd_xfer_handle xfer)
return (USBD_IN_PROGRESS);
}
void
Static void
ehci_disown(ehci_softc_t *sc, int index, int lowspeed)
{
int port;
......@@ -2195,24 +2592,24 @@ ehci_disown(ehci_softc_t *sc, int index, int lowspeed)
if (sc->sc_npcomp != 0) {
int i = (index-1) / sc->sc_npcomp;
if (i >= sc->sc_ncomp)
printf("%s: strange port\n",
printf("%s: strange port\n",
USBDEVNAME(sc->sc_bus.bdev));
else
#ifdef __riscos
logprintf("%s: handing over %s speed device on "
printf("%s: handing over %s speed device on "
"port %d to %d\n",
USBDEVNAME(sc->sc_bus.bdev),
lowspeed ? "low" : "full",
index, i);
#else
logprintf("%s: handing over %s speed device on "
printf("%s: handing over %s speed device on "
"port %d to %s\n",
USBDEVNAME(sc->sc_bus.bdev),
device_xname(sc->sc_dev),
lowspeed ? "low" : "full",
index, USBDEVNAME(sc->sc_comps[i]->bdev));
index, device_xname(sc->sc_comps[i]));
#endif
} else {
printf("%s: npcomp == 0\n", USBDEVNAME(sc->sc_bus.bdev));
printf("%s: npcomp == 0\n", USBDEVNAME(sc->sc_bus.bdev));
}
#endif
port = EHCI_PORTSC(index);
......@@ -2235,7 +2632,7 @@ ehci_root_ctrl_close(usbd_pipe_handle pipe)
/* Nothing to do. */
}
void
Static void
ehci_root_intr_done(usbd_xfer_handle xfer)
{
xfer->hcpriv = NULL;
......@@ -2296,7 +2693,7 @@ ehci_root_intr_close(usbd_pipe_handle pipe)
sc->sc_intrxfer = NULL;
}
void
Static void
ehci_root_ctrl_done(usbd_xfer_handle xfer)
{
xfer->hcpriv = NULL;
......@@ -2304,7 +2701,7 @@ ehci_root_ctrl_done(usbd_xfer_handle xfer)
/************************/
ehci_soft_qh_t *
Static ehci_soft_qh_t *
ehci_alloc_sqh(ehci_softc_t *sc)
{
ehci_soft_qh_t *sqh;
......@@ -2315,10 +2712,10 @@ ehci_alloc_sqh(ehci_softc_t *sc)
if (sc->sc_freeqhs == NULL) {
DPRINTFN(2, ("ehci_alloc_sqh: allocating chunk\n"));
err = usb_allocmem(&sc->sc_bus, EHCI_SQH_SIZE * EHCI_SQH_CHUNK,
EHCI_PAGE_SIZE, &dma);
EHCI_SMALL_PAGE_SIZE, &dma);
#ifdef EHCI_DEBUG
if (err)
printf("ehci_alloc_sqh: usb_allocmem()=%d\n", err);
printf("ehci_alloc_sqh: usb_allocmem()=%d\n", err);
#endif
if (err)
return (NULL);
......@@ -2326,6 +2723,8 @@ ehci_alloc_sqh(ehci_softc_t *sc)
offs = i * EHCI_SQH_SIZE;
sqh = KERNADDR(&dma, offs);
sqh->physaddr = DMAADDR(&dma, offs);
sqh->dma = dma;
sqh->offs = offs;
sqh->next = sc->sc_freeqhs;
sc->sc_freeqhs = sqh;
}
......@@ -2337,14 +2736,14 @@ ehci_alloc_sqh(ehci_softc_t *sc)
return (sqh);
}
void
Static void
ehci_free_sqh(ehci_softc_t *sc, ehci_soft_qh_t *sqh)
{
sqh->next = sc->sc_freeqhs;
sc->sc_freeqhs = sqh;
}
ehci_soft_qtd_t *
Static ehci_soft_qtd_t *
ehci_alloc_sqtd(ehci_softc_t *sc)
{
ehci_soft_qtd_t *sqtd;
......@@ -2356,10 +2755,10 @@ ehci_alloc_sqtd(ehci_softc_t *sc)
if (sc->sc_freeqtds == NULL) {
DPRINTFN(2, ("ehci_alloc_sqtd: allocating chunk\n"));
err = usb_allocmem(&sc->sc_bus, EHCI_SQTD_SIZE*EHCI_SQTD_CHUNK,
EHCI_PAGE_SIZE, &dma);
EHCI_SMALL_PAGE_SIZE, &dma);
#ifdef EHCI_DEBUG
if (err)
printf("ehci_alloc_sqtd: usb_allocmem()=%d\n", err);
printf("ehci_alloc_sqtd: usb_allocmem()=%d\n", err);
#endif
if (err)
return (NULL);
......@@ -2368,6 +2767,8 @@ ehci_alloc_sqtd(ehci_softc_t *sc)
offs = i * EHCI_SQTD_SIZE;
sqtd = KERNADDR(&dma, offs);
sqtd->physaddr = DMAADDR(&dma, offs);
sqtd->dma = dma;
sqtd->offs = offs;
sqtd->nextqtd = sc->sc_freeqtds;
sc->sc_freeqtds = sqtd;
}
......@@ -2385,7 +2786,7 @@ ehci_alloc_sqtd(ehci_softc_t *sc)
return (sqtd);
}
void
Static void
ehci_free_sqtd(ehci_softc_t *sc, ehci_soft_qtd_t *sqtd)
{
int s;
......@@ -2396,7 +2797,7 @@ ehci_free_sqtd(ehci_softc_t *sc, ehci_soft_qtd_t *sqtd)
splx(s);
}
usbd_status
Static usbd_status
ehci_alloc_sqtd_chain(struct ehci_pipe *epipe, ehci_softc_t *sc,
int alen, int rd, usbd_xfer_handle xfer,
ehci_soft_qtd_t **sp, ehci_soft_qtd_t **ep)
......@@ -2404,30 +2805,33 @@ ehci_alloc_sqtd_chain(struct ehci_pipe *epipe, ehci_softc_t *sc,
ehci_soft_qtd_t *next, *cur;
ehci_physaddr_t dataphys, dataphyspage, dataphyslastpage, nextphys;
u_int32_t qtdstatus;
int len, curlen, mps;
int i, tog;
int len, curlen, mps;
int i, tog;
usb_dma_t *dma = &xfer->dmabuf;
int flags = xfer->flags;
u_int16_t flags = xfer->flags;
DPRINTFN(alen<4*4096,("ehci_alloc_sqtd_chain: start len=%d\n", alen));
len = alen;
dataphys = DMAADDR(dma, 0);
dataphyslastpage = EHCI_PAGE(dataphys + len - 1);
qtdstatus = EHCI_QTD_ACTIVE |
qtdstatus = EHCI_QTD_ACTIVE |
EHCI_QTD_SET_PID(rd ? EHCI_QTD_PID_IN : EHCI_QTD_PID_OUT) |
EHCI_QTD_SET_CERR(3)
/* IOC set below */
/* BYTES set below */
;
mps = UGETW(epipe->pipe.endpoint->edesc->wMaxPacketSize);
tog = epipe->nexttoggle;
qtdstatus |= EHCI_QTD_SET_TOGGLE(tog);
mps = UGETW(epipe->pipe.endpoint->edesc->wMaxPacketSize);
tog = epipe->nexttoggle;
qtdstatus |= EHCI_QTD_SET_TOGGLE(tog);
cur = ehci_alloc_sqtd(sc);
*sp = cur;
if (cur == NULL)
goto nomem;
usb_syncmem(dma, 0, alen,
rd ? BUS_DMASYNC_PREREAD : BUS_DMASYNC_PREWRITE);
for (;;) {
dataphyspage = EHCI_PAGE(dataphys);
/* The EHCI hardware can handle at most 5 pages. */
......@@ -2441,91 +2845,89 @@ ehci_alloc_sqtd_chain(struct ehci_pipe *epipe, ehci_softc_t *sc,
EHCI_PAGE_OFFSET(dataphys);
#ifdef DIAGNOSTIC
if (curlen > len) {
printf("ehci_alloc_sqtd_chain: curlen=0x%x "
printf("ehci_alloc_sqtd_chain: curlen=0x%x "
"len=0x%x offs=0x%x\n", curlen, len,
EHCI_PAGE_OFFSET(dataphys));
printf("lastpage=0x%x page=0x%x phys=0x%x\n",
printf("lastpage=0x%x page=0x%x phys=0x%x\n",
dataphyslastpage, dataphyspage,
dataphys);
curlen = len;
}
#endif
/* the length must be a multiple of the max size */
curlen -= curlen % mps;
curlen -= curlen % mps;
DPRINTFN(1,("ehci_alloc_sqtd_chain: multiple QTDs, "
"curlen=%d\n", curlen));
#ifdef DIAGNOSTIC
if (curlen == 0)
panic("ehci_alloc_std: curlen == 0");
panic("ehci_alloc_sqtd_chain: curlen == 0");
#endif
}
DPRINTFN(4,("ehci_alloc_sqtd_chain: dataphys=0x%08x "
DPRINTFN(4,("ehci_alloc_sqtd_chain: dataphys=0x%08x "
"dataphyslastpage=0x%08x len=%d curlen=%d\n",
dataphys, dataphyslastpage,
len, curlen));
len -= curlen;
// Dan addition.. force new NULL length qtd if its an exact write of modulo mps
// this now matches what is in OHCI .. needed for ethernet deviced e.g.
if (len != 0
|| (flags & USBD_FORCE_SHORT_XFER
&& curlen
&& (curlen % mps) == 0
&& !rd)) {
// this is what EHCI came with
// if (len != 0) {
/*
* Allocate another transfer if there's more data left,
* or if force last short transfer flag is set and we're
* allocating a multiple of the max packet size.
*/
if (len != 0 ||
((curlen % mps) == 0 && !rd && curlen != 0 &&
(flags & USBD_FORCE_SHORT_XFER))) {
next = ehci_alloc_sqtd(sc);
if (next == NULL)
goto nomem;
nextphys = htole32(next->physaddr);
nextphys = htole32(next->physaddr);
} else {
next = NULL;
nextphys = EHCI_NULL;
}
for (i = 0;
i * EHCI_PAGE_SIZE < curlen + EHCI_PAGE_OFFSET(dataphys);
i++) {
for (i = 0; i * EHCI_PAGE_SIZE <
curlen + EHCI_PAGE_OFFSET(dataphys); i++) {
ehci_physaddr_t a = dataphys + i * EHCI_PAGE_SIZE;
if (i != 0) /* use offset only in first buffer */
a = EHCI_PAGE(a);
cur->qtd.qtd_buffer[i] = htole32(a);
cur->qtd.qtd_buffer_hi[i] = 0;
cur->qtd.qtd_buffer_hi[i] = 0;
#ifdef DIAGNOSTIC
if (i >= EHCI_QTD_NBUFFERS) {
printf("ehci_alloc_sqtd_chain: i=%d\n", i);
printf("ehci_alloc_sqtd_chain: i=%d\n", i);
goto nomem;
}
#endif
}
cur->nextqtd = next;
cur->qtd.qtd_next = cur->qtd.qtd_altnext = nextphys;
cur->qtd.qtd_next = cur->qtd.qtd_altnext = nextphys;
cur->qtd.qtd_status =
htole32(qtdstatus | EHCI_QTD_SET_BYTES(curlen));
htole32(qtdstatus | EHCI_QTD_SET_BYTES(curlen));
cur->xfer = xfer;
cur->len = curlen;
DPRINTFN(10,("ehci_alloc_sqtd_chain: cbp=0x%08x end=0x%08x\n",
dataphys, dataphys + curlen));
/* adjust the toggle based on the number of packets in this
qtd */
if (((curlen + mps - 1) / mps) & 1) {
tog ^= 1;
qtdstatus ^= EHCI_QTD_TOGGLE_MASK;
}
// Dan addition.. to match OHCI
// JB simplify ..it'll be NULL once end is reached
if (next==NULL)
// ehci original
// if (len == 0)
/* adjust the toggle based on the number of packets in this
qtd */
if (((curlen + mps - 1) / mps) & 1) {
tog ^= 1;
qtdstatus ^= EHCI_QTD_TOGGLE_MASK;
}
if (next == NULL)
break;
usb_syncmem(&cur->dma, cur->offs, sizeof(cur->qtd),
BUS_DMASYNC_PREWRITE | BUS_DMASYNC_PREREAD);
DPRINTFN(10,("ehci_alloc_sqtd_chain: extend chain\n"));
dataphys += curlen;
cur = next;
}
cur->qtd.qtd_status |= htole32(EHCI_QTD_IOC);
usb_syncmem(&cur->dma, cur->offs, sizeof(cur->qtd),
BUS_DMASYNC_PREWRITE | BUS_DMASYNC_PREREAD);
*ep = cur;
epipe->nexttoggle = tog;
epipe->nexttoggle = tog;
DPRINTFN(10,("ehci_alloc_sqtd_chain: return sqtd=%p sqtdend=%p\n",
*sp, *ep));
......@@ -2554,13 +2956,87 @@ ehci_free_sqtd_chain(ehci_softc_t *sc, ehci_soft_qtd_t *sqtd,
}
}
Static ehci_soft_itd_t *
ehci_alloc_itd(ehci_softc_t *sc)
{
struct ehci_soft_itd *itd, *freeitd;
usbd_status err;
int i, s, offs, frindex, previndex;
usb_dma_t dma;
s = splusb();
/* Find an itd that wasn't freed this frame or last frame. This can
* discard itds that were freed before frindex wrapped around
* XXX - can this lead to thrashing? Could fix by enabling wrap-around
* interrupt and fiddling with list when that happens */
frindex = (EOREAD4(sc, EHCI_FRINDEX) + 1) >> 3;
previndex = (frindex != 0) ? frindex - 1 : sc->sc_flsize;
freeitd = NULL;
LIST_FOREACH(itd, &sc->sc_freeitds, u.free_list) {
if (itd == NULL)
break;
if (itd->slot != frindex && itd->slot != previndex) {
freeitd = itd;
break;
}
}
if (freeitd == NULL) {
DPRINTFN(2, ("ehci_alloc_itd allocating chunk\n"));
err = usb_allocmem(&sc->sc_bus, EHCI_ITD_SIZE * EHCI_ITD_CHUNK,
EHCI_SMALL_PAGE_SIZE, &dma);
if (err) {
DPRINTF(("ehci_alloc_itd, alloc returned %d\n", err));
return NULL;
}
for (i = 0; i < EHCI_ITD_CHUNK; i++) {
offs = i * EHCI_ITD_SIZE;
itd = KERNADDR(&dma, offs);
itd->physaddr = DMAADDR(&dma, offs);
itd->dma = dma;
itd->offs = offs;
LIST_INSERT_HEAD(&sc->sc_freeitds, itd, u.free_list);
}
freeitd = LIST_FIRST(&sc->sc_freeitds);
}
itd = freeitd;
LIST_REMOVE(itd, u.free_list);
memset(&itd->itd, 0, sizeof(ehci_itd_t));
usb_syncmem(&itd->dma, itd->offs + offsetof(ehci_itd_t, itd_next),
sizeof(itd->itd.itd_next), BUS_DMASYNC_PREWRITE |
BUS_DMASYNC_PREREAD);
itd->u.frame_list.next = NULL;
itd->u.frame_list.prev = NULL;
itd->xfer_next = NULL;
itd->slot = 0;
splx(s);
return itd;
}
Static void
ehci_free_itd(ehci_softc_t *sc, ehci_soft_itd_t *itd)
{
int s;
s = splusb();
LIST_INSERT_HEAD(&sc->sc_freeitds, itd, u.free_list);
splx(s);
}
/****************/
/*
* Close a reqular pipe.
* Assumes that there are no pending transactions.
*/
void
Static void
ehci_close_pipe(usbd_pipe_handle pipe, ehci_soft_qh_t *head)
{
struct ehci_pipe *epipe = (struct ehci_pipe *)pipe;
......@@ -2585,7 +3061,7 @@ ehci_close_pipe(usbd_pipe_handle pipe, ehci_soft_qh_t *head)
* interrupt processing to process it.
* XXX This is most probably wrong.
*/
void
Static void
ehci_abort_xfer(usbd_xfer_handle xfer, usbd_status status)
{
#define exfer EXFER(xfer)
......@@ -2597,6 +3073,7 @@ ehci_abort_xfer(usbd_xfer_handle xfer, usbd_status status)
u_int32_t qhstatus;
int s;
int hit;
int wake;
DPRINTF(("ehci_abort_xfer: xfer=%p pipe=%p\n", xfer, epipe));
......@@ -2604,31 +3081,72 @@ ehci_abort_xfer(usbd_xfer_handle xfer, usbd_status status)
/* If we're dying, just do the software part. */
s = splusb();
xfer->status = status; /* make software ignore it */
usb_uncallout(xfer->timeout_handle, ehci_timeout, xfer);
callout_stop(&(xfer->timeout_handle));
usb_transfer_complete(xfer);
splx(s);
return;
}
#ifndef __riscos
if (xfer->device->bus->intr_context || !curproc)
if (xfer->device->bus->intr_context)
panic("ehci_abort_xfer: not in process context");
#endif
/*
* If an abort is already in progress then just wait for it to
* complete and return.
*/
if (xfer->hcflags & UXFER_ABORTING) {
DPRINTFN(2, ("ehci_abort_xfer: already aborting\n"));
#ifdef DIAGNOSTIC
if (status == USBD_TIMEOUT)
printf("ehci_abort_xfer: TIMEOUT while aborting\n");
#endif
/* Override the status which might be USBD_TIMEOUT. */
xfer->status = status;
DPRINTFN(2, ("ehci_abort_xfer: waiting for abort to finish\n"));
xfer->hcflags |= UXFER_ABORTWAIT;
while (xfer->hcflags & UXFER_ABORTING)
#ifdef __riscos
tsleep(&xfer->hcflags, PZERO, "ehciaw", 0, 1);
#else
tsleep(&xfer->hcflags, PZERO, "ehciaw", 0);
#endif
return;
}
xfer->hcflags |= UXFER_ABORTING;
/*
* Step 1: Make interrupt routine and hardware ignore xfer.
*/
s = splusb();
xfer->status = status; /* make software ignore it */
usb_uncallout(xfer->timeout_handle, ehci_timeout, xfer);
callout_stop(&(xfer->timeout_handle));
usb_syncmem(&sqh->dma,
sqh->offs + offsetof(ehci_qh_t, qh_qtd.qtd_status),
sizeof(sqh->qh.qh_qtd.qtd_status),
BUS_DMASYNC_POSTWRITE | BUS_DMASYNC_POSTREAD);
qhstatus = sqh->qh.qh_qtd.qtd_status;
sqh->qh.qh_qtd.qtd_status = qhstatus | htole32(EHCI_QTD_HALTED);
for (sqtd = exfer->sqtdstart;
usb_syncmem(&sqh->dma,
sqh->offs + offsetof(ehci_qh_t, qh_qtd.qtd_status),
sizeof(sqh->qh.qh_qtd.qtd_status),
BUS_DMASYNC_PREWRITE | BUS_DMASYNC_PREREAD);
for (sqtd = exfer->sqtdstart;
#ifdef __riscos
sqtd
sqtd
#endif
; sqtd = sqtd->nextqtd) {
; sqtd = sqtd->nextqtd) {
usb_syncmem(&sqtd->dma,
sqtd->offs + offsetof(ehci_qtd_t, qtd_status),
sizeof(sqtd->qtd.qtd_status),
BUS_DMASYNC_POSTWRITE | BUS_DMASYNC_POSTREAD);
sqtd->qtd.qtd_status |= htole32(EHCI_QTD_HALTED);
usb_syncmem(&sqtd->dma,
sqtd->offs + offsetof(ehci_qtd_t, qtd_status),
sizeof(sqtd->qtd.qtd_status),
BUS_DMASYNC_PREWRITE | BUS_DMASYNC_PREREAD);
if (sqtd == exfer->sqtdend)
break;
}
......@@ -2667,6 +3185,11 @@ ehci_abort_xfer(usbd_xfer_handle xfer, usbd_status status)
* any of them.
*/
s = splusb(); /* XXX why? */
usb_syncmem(&sqh->dma,
sqh->offs + offsetof(ehci_qh_t, qh_curqtd),
sizeof(sqh->qh.qh_curqtd),
BUS_DMASYNC_POSTWRITE | BUS_DMASYNC_POSTREAD);
cur = EHCI_LINK_ADDR(le32toh(sqh->qh.qh_curqtd));
hit = 0;
for (sqtd = exfer->sqtdstart; ; sqtd = sqtd->nextqtd) {
......@@ -2679,7 +3202,15 @@ ehci_abort_xfer(usbd_xfer_handle xfer, usbd_status status)
if (hit && sqtd != NULL) {
DPRINTFN(1,("ehci_abort_xfer: cur=0x%08x\n", sqtd->physaddr));
sqh->qh.qh_curqtd = htole32(sqtd->physaddr); /* unlink qTDs */
usb_syncmem(&sqh->dma,
sqh->offs + offsetof(ehci_qh_t, qh_curqtd),
sizeof(sqh->qh.qh_curqtd),
BUS_DMASYNC_PREWRITE | BUS_DMASYNC_PREREAD);
sqh->qh.qh_qtd.qtd_status = qhstatus;
usb_syncmem(&sqh->dma,
sqh->offs + offsetof(ehci_qh_t, qh_qtd.qtd_status),
sizeof(sqh->qh.qh_qtd.qtd_status),
BUS_DMASYNC_PREWRITE | BUS_DMASYNC_PREREAD);
} else {
DPRINTFN(1,("ehci_abort_xfer: no hit\n"));
}
......@@ -2690,13 +3221,112 @@ ehci_abort_xfer(usbd_xfer_handle xfer, usbd_status status)
#ifdef DIAGNOSTIC
exfer->isdone = 1;
#endif
wake = xfer->hcflags & UXFER_ABORTWAIT;
xfer->hcflags &= ~(UXFER_ABORTING | UXFER_ABORTWAIT);
usb_transfer_complete(xfer);
if (wake)
wakeup(&xfer->hcflags);
splx(s);
#undef exfer
}
void
Static void
ehci_abort_isoc_xfer(usbd_xfer_handle xfer, usbd_status status)
{
ehci_isoc_trans_t trans_status;
struct ehci_pipe *epipe;
struct ehci_xfer *exfer;
ehci_softc_t *sc;
struct ehci_soft_itd *itd;
int s, i, wake;
epipe = (struct ehci_pipe *) xfer->pipe;
exfer = EXFER(xfer);
sc = (ehci_softc_t *)epipe->pipe.device->bus;
DPRINTF(("ehci_abort_isoc_xfer: xfer %p pipe %p\n", xfer, epipe));
if (sc->sc_dying) {
s = splusb();
xfer->status = status;
callout_stop(&(xfer->timeout_handle));
usb_transfer_complete(xfer);
splx(s);
return;
}
if (xfer->hcflags & UXFER_ABORTING) {
DPRINTFN(2, ("ehci_abort_isoc_xfer: already aborting\n"));
#ifdef DIAGNOSTIC
if (status == USBD_TIMEOUT)
printf("ehci_abort_xfer: TIMEOUT while aborting\n");
#endif
xfer->status = status;
DPRINTFN(2, ("ehci_abort_xfer: waiting for abort to finish\n"));
xfer->hcflags |= UXFER_ABORTWAIT;
while (xfer->hcflags & UXFER_ABORTING)
#ifdef __riscos
tsleep(&xfer->hcflags, PZERO, "ehciiaw", 0, 1);
#else
tsleep(&xfer->hcflags, PZERO, "ehciiaw", 0);
#endif
return;
}
xfer->hcflags |= UXFER_ABORTING;
xfer->status = status;
callout_stop(&(xfer->timeout_handle));
s = splusb();
for (itd = exfer->itdstart; itd != NULL; itd = itd->xfer_next) {
usb_syncmem(&itd->dma,
itd->offs + offsetof(ehci_itd_t, itd_ctl),
sizeof(itd->itd.itd_ctl),
BUS_DMASYNC_POSTWRITE | BUS_DMASYNC_POSTREAD);
for (i = 0; i < 8; i++) {
trans_status = le32toh(itd->itd.itd_ctl[i]);
trans_status &= ~EHCI_ITD_ACTIVE;
itd->itd.itd_ctl[i] = htole32(trans_status);
}
usb_syncmem(&itd->dma,
itd->offs + offsetof(ehci_itd_t, itd_ctl),
sizeof(itd->itd.itd_ctl),
BUS_DMASYNC_PREWRITE | BUS_DMASYNC_PREREAD);
}
splx(s);
s = splusb();
#ifdef USB_USE_SOFTINTR
sc->sc_softwake = 1;
#endif /* USB_USE_SOFTINTR */
usb_schedsoftintr(&sc->sc_bus);
#ifdef USB_USE_SOFTINTR
#ifdef __riscos
tsleep(&sc->sc_softwake, PZERO, "ehciab", 0, 1);
#else
tsleep(&sc->sc_softwake, PZERO, "ehciab", 0);
#endif
#endif /* USB_USE_SOFTINTR */
splx(s);
#ifdef DIAGNOSTIC
exfer->isdone = 1;
#endif
wake = xfer->hcflags & UXFER_ABORTWAIT;
xfer->hcflags &= ~(UXFER_ABORTING | UXFER_ABORTWAIT);
usb_transfer_complete(xfer);
if (wake)
wakeup(&xfer->hcflags);
return;
}
Static void
ehci_timeout(void *addr)
{
struct ehci_xfer *exfer = addr;
......@@ -2704,7 +3334,7 @@ ehci_timeout(void *addr)
ehci_softc_t *sc = (ehci_softc_t *)epipe->pipe.device->bus;
DPRINTF(("ehci_timeout: exfer=%p\n", exfer));
#if defined(USB_DEBUG) && !defined(__riscos)
#if defined(EHCI_DEBUG) && !defined(__riscos)
if (ehcidebug > 1)
usbd_dump_pipe(exfer->xfer.pipe);
#endif
......@@ -2719,11 +3349,12 @@ ehci_timeout(void *addr)
riscos_abort_pipe (addr);
#else
usb_init_task(&exfer->abort_task, ehci_timeout_task, addr);
usb_add_task(exfer->xfer.pipe->device, &exfer->abort_task);
usb_add_task(exfer->xfer.pipe->device, &exfer->abort_task,
USB_TASKQ_HC);
#endif
}
void
Static void
ehci_timeout_task(void *addr)
{
usbd_xfer_handle xfer = addr;
......@@ -2764,7 +3395,7 @@ ehci_device_ctrl_start(usbd_xfer_handle xfer)
#ifdef DIAGNOSTIC
if (!(xfer->rqflags & URQ_REQUEST)) {
/* XXX panic */
printf("ehci_device_ctrl_transfer: not a request\n");
printf("ehci_device_ctrl_transfer: not a request\n");
return (USBD_INVAL);
}
#endif
......@@ -2778,12 +3409,15 @@ ehci_device_ctrl_start(usbd_xfer_handle xfer)
return (USBD_IN_PROGRESS);
}
void
Static void
ehci_device_ctrl_done(usbd_xfer_handle xfer)
{
struct ehci_xfer *ex = EXFER(xfer);
ehci_softc_t *sc = (ehci_softc_t *)xfer->pipe->device->bus;
/*struct ehci_pipe *epipe = (struct ehci_pipe *)xfer->pipe;*/
struct ehci_pipe *epipe = (struct ehci_pipe *)xfer->pipe;
usb_device_request_t *req = &xfer->request;
int len = UGETW(req->wLength);
int rd = req->bmRequestType & UT_READ;
DPRINTFN(10,("ehci_ctrl_done: xfer=%p\n", xfer));
......@@ -2793,10 +3427,23 @@ ehci_device_ctrl_done(usbd_xfer_handle xfer)
}
#endif
if (xfer->status != USBD_NOMEM && ehci_active_intr_list(ex)) {
ehci_del_intr_list(ex); /* remove from active list */
mutex_enter(&sc->sc_intrhead_lock);
#ifdef __riscos
int s = splusb(); /* No mutexes, so just disable IRQs */
#endif
if (xfer->status != USBD_NOMEM && ehci_active_intr_list(ex)) {
ehci_del_intr_list(sc, ex); /* remove from active list */
ehci_free_sqtd_chain(sc, ex->sqtdstart, NULL);
usb_syncmem(&epipe->u.ctl.reqdma, 0, sizeof *req,
BUS_DMASYNC_POSTWRITE);
if (len)
usb_syncmem(&xfer->dmabuf, 0, len,
rd ? BUS_DMASYNC_POSTREAD : BUS_DMASYNC_POSTWRITE);
}
mutex_exit(&sc->sc_intrhead_lock);
#ifdef __riscos
splx(s);
#endif
DPRINTFN(5, ("ehci_ctrl_done: length=%d\n", xfer->actlen));
}
......@@ -2820,7 +3467,7 @@ ehci_device_ctrl_close(usbd_pipe_handle pipe)
ehci_close_pipe(pipe, sc->sc_async_head);
}
usbd_status
Static usbd_status
ehci_device_request(usbd_xfer_handle xfer)
{
#define exfer EXFER(xfer)
......@@ -2839,7 +3486,7 @@ ehci_device_request(usbd_xfer_handle xfer)
isread = req->bmRequestType & UT_READ;
len = UGETW(req->wLength);
DPRINTFN(3,("ehci_device_request: type=0x%02x, request=0x%02x, "
DPRINTFN(3,("ehci_device_request: type=0x%02x, request=0x%02x, "
"wValue=0x%04x, wIndex=0x%04x len=%d, addr=%d, endpt=%d\n",
req->bmRequestType, req->bRequest, UGETW(req->wValue),
UGETW(req->wIndex), len, addr,
......@@ -2859,12 +3506,12 @@ ehci_device_request(usbd_xfer_handle xfer)
sqh = epipe->sqh;
epipe->u.ctl.length = len;
/* Update device address and length since they may have changed
during the setup of the control pipe in usbd_new_device(). */
/* Update device address and length since they may have changed
during the setup of the control pipe in usbd_new_device(). */
/* XXX This only needs to be done once, but it's too early in open. */
/* XXXX Should not touch ED here! */
sqh->qh.qh_endp =
(sqh->qh.qh_endp & htole32(~(EHCI_QH_ADDRMASK | EHCI_QH_MPLMASK))) |
(sqh->qh.qh_endp & htole32(~(EHCI_QH_ADDRMASK | EHCI_QH_MPLMASK))) |
htole32(
EHCI_QH_SET_ADDR(addr) |
EHCI_QH_SET_MPL(UGETW(epipe->pipe.endpoint->edesc->wMaxPacketSize))
......@@ -2874,16 +3521,18 @@ ehci_device_request(usbd_xfer_handle xfer)
if (len != 0) {
ehci_soft_qtd_t *end;
/* Start toggle at 1. */
epipe->nexttoggle = 1;
/* Start toggle at 1. */
epipe->nexttoggle = 1;
err = ehci_alloc_sqtd_chain(epipe, sc, len, isread, xfer,
&next, &end);
if (err)
goto bad3;
end->qtd.qtd_status &= htole32(~EHCI_QTD_IOC);
end->qtd.qtd_status &= htole32(~EHCI_QTD_IOC);
end->nextqtd = stat;
end->qtd.qtd_next =
end->qtd.qtd_altnext = htole32(stat->physaddr);
usb_syncmem(&end->dma, end->offs, sizeof(end->qtd),
BUS_DMASYNC_PREWRITE | BUS_DMASYNC_PREREAD);
} else {
next = stat;
}
......@@ -2893,35 +3542,40 @@ ehci_device_request(usbd_xfer_handle xfer)
#else
memcpy(KERNADDR(&epipe->u.ctl.reqdma, 0), req, sizeof *req);
#endif
usb_syncmem(&epipe->u.ctl.reqdma, 0, sizeof *req, BUS_DMASYNC_PREWRITE);
/* Clear toggle */
/* Clear toggle */
setup->qtd.qtd_status = htole32(
EHCI_QTD_ACTIVE |
EHCI_QTD_SET_PID(EHCI_QTD_PID_SETUP) |
EHCI_QTD_SET_CERR(3) |
EHCI_QTD_SET_TOGGLE(0) |
EHCI_QTD_SET_TOGGLE(0) |
EHCI_QTD_SET_BYTES(sizeof *req)
);
setup->qtd.qtd_buffer[0] = htole32(DMAADDR(&epipe->u.ctl.reqdma, 0));
setup->qtd.qtd_buffer_hi[0] = 0;
setup->qtd.qtd_buffer_hi[0] = 0;
setup->nextqtd = next;
setup->qtd.qtd_next = setup->qtd.qtd_altnext = htole32(next->physaddr);
setup->xfer = xfer;
setup->len = sizeof *req;
usb_syncmem(&setup->dma, setup->offs, sizeof(setup->qtd),
BUS_DMASYNC_PREWRITE | BUS_DMASYNC_PREREAD);
stat->qtd.qtd_status = htole32(
EHCI_QTD_ACTIVE |
EHCI_QTD_SET_PID(isread ? EHCI_QTD_PID_OUT : EHCI_QTD_PID_IN) |
EHCI_QTD_SET_CERR(3) |
EHCI_QTD_SET_TOGGLE(1) |
EHCI_QTD_SET_TOGGLE(1) |
EHCI_QTD_IOC
);
stat->qtd.qtd_buffer[0] = 0; /* XXX not needed? */
stat->qtd.qtd_buffer_hi[0] = 0; /* XXX not needed? */
stat->qtd.qtd_buffer_hi[0] = 0; /* XXX not needed? */
stat->nextqtd = NULL;
stat->qtd.qtd_next = stat->qtd.qtd_altnext = EHCI_NULL;
stat->xfer = xfer;
stat->len = 0;
usb_syncmem(&stat->dma, stat->offs, sizeof(stat->qtd),
BUS_DMASYNC_PREWRITE | BUS_DMASYNC_PREREAD);
#ifdef EHCI_DEBUG
if (ehcidebug > 5) {
......@@ -2935,24 +3589,26 @@ ehci_device_request(usbd_xfer_handle xfer)
exfer->sqtdend = stat;
#ifdef DIAGNOSTIC
if (!exfer->isdone) {
printf("ehci_device_request: not done, exfer=%p\n", exfer);
printf("ehci_device_request: not done, exfer=%p\n", exfer);
}
exfer->isdone = 0;
#endif
/* Insert qTD in QH list. */
s = splusb();
ehci_set_qh_qtd(sqh, setup);
ehci_set_qh_qtd(sqh, setup); /* also does usb_syncmem(sqh) */
if (xfer->timeout && !sc->sc_bus.use_polling) {
#ifdef __riscos
usb_callout(xfer->timeout_handle, MS_TO_TICKS(xfer->timeout),
ehci_timeout, xfer);
callout_reset(&(xfer->timeout_handle), (MS_TO_TICKS(xfer->timeout)),
(ehci_timeout), (xfer));
#else
usb_callout(xfer->timeout_handle, mstohz(xfer->timeout),
ehci_timeout, xfer);
callout_reset(&(xfer->timeout_handle), (mstohz(xfer->timeout)),
(ehci_timeout), (xfer));
#endif
}
mutex_enter(&sc->sc_intrhead_lock);
ehci_add_intr_list(sc, exfer);
mutex_exit(&sc->sc_intrhead_lock);
xfer->status = USBD_IN_PROGRESS;
splx(s);
......@@ -2982,6 +3638,29 @@ ehci_device_request(usbd_xfer_handle xfer)
#undef exfer
}
/*
* Some EHCI chips from VIA seem to trigger interrupts before writing back the
* qTD status, or miss signalling occasionally under heavy load. If the host
* machine is too fast, we we can miss transaction completion - when we scan
* the active list the transaction still seems to be active. This generally
* exhibits itself as a umass stall that never recovers.
*
* We work around this behaviour by setting up this callback after any softintr
* that completes with transactions still pending, giving us another chance to
* check for completion after the writeback has taken place.
*/
Static void
ehci_intrlist_timeout(void *arg)
{
ehci_softc_t *sc = arg;
int s = splusb();
DPRINTF(("ehci_intrlist_timeout\n"));
usb_schedsoftintr(&sc->sc_bus);
splx(s);
}
/************************/
Static usbd_status
......@@ -2998,7 +3677,7 @@ ehci_device_bulk_transfer(usbd_xfer_handle xfer)
return (ehci_device_bulk_start(SIMPLEQ_FIRST(&xfer->pipe->queue)));
}
usbd_status
Static usbd_status
ehci_device_bulk_start(usbd_xfer_handle xfer)
{
#define exfer EXFER(xfer)
......@@ -3011,7 +3690,7 @@ ehci_device_bulk_start(usbd_xfer_handle xfer)
int len, isread, endpt;
int s;
DPRINTFN(2, ("ehci_device_bulk_start: xfer=%p len=%d flags=%d\n",
DPRINTFN(2, ("ehci_device_bulk_start: xfer=%p len=%d flags=%d\n",
xfer, xfer->length, xfer->flags));
if (sc->sc_dying)
......@@ -3019,7 +3698,7 @@ ehci_device_bulk_start(usbd_xfer_handle xfer)
#ifdef DIAGNOSTIC
if (xfer->rqflags & URQ_REQUEST)
panic("ehci_device_bulk_start: a request");
panic("ehci_device_bulk_start: a request");
#endif
len = xfer->length;
......@@ -3040,7 +3719,7 @@ ehci_device_bulk_start(usbd_xfer_handle xfer)
#ifdef EHCI_DEBUG
if (ehcidebug > 5) {
DPRINTF(("ehci_device_bulk_start: data(1)\n"));
DPRINTF(("ehci_device_bulk_start: data(1)\n"));
ehci_dump_sqh(sqh);
ehci_dump_sqtds(data);
}
......@@ -3051,37 +3730,39 @@ ehci_device_bulk_start(usbd_xfer_handle xfer)
exfer->sqtdend = dataend;
#ifdef DIAGNOSTIC
if (!exfer->isdone) {
printf("ehci_device_bulk_start: not done, ex=%p\n", exfer);
printf("ehci_device_bulk_start: not done, ex=%p\n", exfer);
}
exfer->isdone = 0;
#endif
s = splusb();
ehci_set_qh_qtd(sqh, data);
ehci_set_qh_qtd(sqh, data); /* also does usb_syncmem(sqh) */
if (xfer->timeout && !sc->sc_bus.use_polling) {
#ifdef __riscos
usb_callout(xfer->timeout_handle, MS_TO_TICKS(xfer->timeout),
ehci_timeout, xfer);
callout_reset(&(xfer->timeout_handle), (MS_TO_TICKS(xfer->timeout)),
(ehci_timeout), (xfer));
#else
usb_callout(xfer->timeout_handle, mstohz(xfer->timeout),
ehci_timeout, xfer);
callout_reset(&(xfer->timeout_handle), (mstohz(xfer->timeout)),
(ehci_timeout), (xfer));
#endif
}
mutex_enter(&sc->sc_intrhead_lock);
ehci_add_intr_list(sc, exfer);
mutex_exit(&sc->sc_intrhead_lock);
xfer->status = USBD_IN_PROGRESS;
splx(s);
#ifdef EHCI_DEBUG
if (ehcidebug > 10) {
DPRINTF(("ehci_device_bulk_start: data(2)\n"));
DPRINTF(("ehci_device_bulk_start: data(2)\n"));
delay(10000);
DPRINTF(("ehci_device_bulk_start: data(3)\n"));
DPRINTF(("ehci_device_bulk_start: data(3)\n"));
ehci_dump_regs(sc);
#if 0
printf("async_head:\n");
printf("async_head:\n");
ehci_dump_sqh(sc->sc_async_head);
#endif
printf("sqh:\n");
printf("sqh:\n");
ehci_dump_sqh(sqh);
ehci_dump_sqtds(data);
}
......@@ -3113,20 +3794,32 @@ ehci_device_bulk_close(usbd_pipe_handle pipe)
ehci_close_pipe(pipe, sc->sc_async_head);
}
void
Static void
ehci_device_bulk_done(usbd_xfer_handle xfer)
{
struct ehci_xfer *ex = EXFER(xfer);
ehci_softc_t *sc = (ehci_softc_t *)xfer->pipe->device->bus;
/*struct ehci_pipe *epipe = (struct ehci_pipe *)xfer->pipe;*/
struct ehci_pipe *epipe = (struct ehci_pipe *)xfer->pipe;
int endpt = epipe->pipe.endpoint->edesc->bEndpointAddress;
int rd = UE_GET_DIR(endpt) == UE_DIR_IN;
DPRINTFN(10,("ehci_bulk_done: xfer=%p, actlen=%d\n",
xfer, xfer->actlen));
if (xfer->status != USBD_NOMEM && ehci_active_intr_list(ex)) {
ehci_del_intr_list(ex); /* remove from active list */
ehci_free_sqtd_chain(sc, ex->sqtdstart, NULL);
#ifdef __riscos
int s = splusb(); /* No mutexes, so just disable IRQs */
#endif
mutex_enter(&sc->sc_intrhead_lock);
if (xfer->status != USBD_NOMEM && ehci_active_intr_list(ex)) {
ehci_del_intr_list(sc, ex); /* remove from active list */
ehci_free_sqtd_chain(sc, ex->sqtdstart, NULL);
usb_syncmem(&xfer->dmabuf, 0, xfer->length,
rd ? BUS_DMASYNC_POSTREAD : BUS_DMASYNC_POSTWRITE);
}
mutex_exit(&sc->sc_intrhead_lock);
#ifdef __riscos
splx(s);
#endif
DPRINTFN(5, ("ehci_bulk_done: length=%d\n", xfer->actlen));
}
......@@ -3136,226 +3829,579 @@ ehci_device_bulk_done(usbd_xfer_handle xfer)
Static usbd_status
ehci_device_setintr(ehci_softc_t *sc, ehci_soft_qh_t *sqh, int ival)
{
struct ehci_soft_islot *isp;
int islot, lev;
struct ehci_soft_islot *isp;
int islot, lev;
/* Find a poll rate that is large enough. */
for (lev = EHCI_IPOLLRATES - 1; lev > 0; lev--)
if (EHCI_ILEV_IVAL(lev) <= ival)
break;
/* Find a poll rate that is large enough. */
for (lev = EHCI_IPOLLRATES - 1; lev > 0; lev--)
if (EHCI_ILEV_IVAL(lev) <= ival)
break;
/* Pick an interrupt slot at the right level. */
/* XXX could do better than picking at random */
sc->sc_rand = (sc->sc_rand + 191) % sc->sc_flsize;
islot = EHCI_IQHIDX(lev, sc->sc_rand);
/* Pick an interrupt slot at the right level. */
/* XXX could do better than picking at random */
sc->sc_rand = (sc->sc_rand + 191) % sc->sc_flsize;
islot = EHCI_IQHIDX(lev, sc->sc_rand);
sqh->islot = islot;
isp = &sc->sc_islots[islot];
ehci_add_qh(sqh, isp->sqh);
sqh->islot = islot;
isp = &sc->sc_islots[islot];
ehci_add_qh(sqh, isp->sqh);
return (USBD_NORMAL_COMPLETION);
return (USBD_NORMAL_COMPLETION);
}
Static usbd_status
ehci_device_intr_transfer(usbd_xfer_handle xfer)
{
usbd_status err;
usbd_status err;
/* Insert last in queue. */
err = usb_insert_transfer(xfer);
if (err)
return (err);
/* Insert last in queue. */
err = usb_insert_transfer(xfer);
if (err)
return (err);
/*
* Pipe isn't running (otherwise err would be USBD_INPROG),
* so start it first.
*/
return (ehci_device_intr_start(SIMPLEQ_FIRST(&xfer->pipe->queue)));
/*
* Pipe isn't running (otherwise err would be USBD_INPROG),
* so start it first.
*/
return (ehci_device_intr_start(SIMPLEQ_FIRST(&xfer->pipe->queue)));
}
Static usbd_status
ehci_device_intr_start(usbd_xfer_handle xfer)
{
#define exfer EXFER(xfer)
struct ehci_pipe *epipe = (struct ehci_pipe *)xfer->pipe;
usbd_device_handle dev = xfer->pipe->device;
ehci_softc_t *sc = (ehci_softc_t *)dev->bus;
ehci_soft_qtd_t *data, *dataend;
ehci_soft_qh_t *sqh;
usbd_status err;
int len, isread, endpt;
int s;
struct ehci_pipe *epipe = (struct ehci_pipe *)xfer->pipe;
usbd_device_handle dev = xfer->pipe->device;
ehci_softc_t *sc = (ehci_softc_t *)dev->bus;
ehci_soft_qtd_t *data, *dataend;
ehci_soft_qh_t *sqh;
usbd_status err;
int len, isread, endpt;
int s;
DPRINTFN(2, ("ehci_device_intr_start: xfer=%p len=%d flags=%d\n",
xfer, xfer->length, xfer->flags));
DPRINTFN(2, ("ehci_device_intr_start: xfer=%p len=%d flags=%d\n",
xfer, xfer->length, xfer->flags));
if (sc->sc_dying)
return (USBD_IOERROR);
if (sc->sc_dying)
return (USBD_IOERROR);
#ifdef DIAGNOSTIC
if (xfer->rqflags & URQ_REQUEST)
panic("ehci_device_intr_start: a request");
if (xfer->rqflags & URQ_REQUEST)
panic("ehci_device_intr_start: a request");
#endif
len = xfer->length;
endpt = epipe->pipe.endpoint->edesc->bEndpointAddress;
isread = UE_GET_DIR(endpt) == UE_DIR_IN;
sqh = epipe->sqh;
len = xfer->length;
endpt = epipe->pipe.endpoint->edesc->bEndpointAddress;
isread = UE_GET_DIR(endpt) == UE_DIR_IN;
sqh = epipe->sqh;
epipe->u.intr.length = len;
epipe->u.intr.length = len;
err = ehci_alloc_sqtd_chain(epipe, sc, len, isread, xfer, &data,
&dataend);
if (err) {
DPRINTFN(-1, ("ehci_device_intr_start: no memory\n"));
xfer->status = err;
usb_transfer_complete(xfer);
return (err);
}
err = ehci_alloc_sqtd_chain(epipe, sc, len, isread, xfer, &data,
&dataend);
if (err) {
DPRINTFN(-1, ("ehci_device_intr_start: no memory\n"));
xfer->status = err;
usb_transfer_complete(xfer);
return (err);
}
#ifdef EHCI_DEBUG
if (ehcidebug > 5) {
DPRINTF(("ehci_device_intr_start: data(1)\n"));
ehci_dump_sqh(sqh);
ehci_dump_sqtds(data);
}
if (ehcidebug > 5) {
DPRINTF(("ehci_device_intr_start: data(1)\n"));
ehci_dump_sqh(sqh);
ehci_dump_sqtds(data);
}
#endif
/* Set up interrupt info. */
exfer->sqtdstart = data;
exfer->sqtdend = dataend;
/* Set up interrupt info. */
exfer->sqtdstart = data;
exfer->sqtdend = dataend;
#ifdef DIAGNOSTIC
if (!exfer->isdone) {
printf("ehci_device_intr_start: not done, ex=%p\n", exfer);
}
exfer->isdone = 0;
if (!exfer->isdone) {
printf("ehci_device_intr_start: not done, ex=%p\n", exfer);
}
exfer->isdone = 0;
#endif
s = splusb();
ehci_set_qh_qtd(sqh, data);
if (xfer->timeout && !sc->sc_bus.use_polling) {
s = splusb();
ehci_set_qh_qtd(sqh, data); /* also does usb_syncmem(sqh) */
if (xfer->timeout && !sc->sc_bus.use_polling) {
#ifdef __riscos
usb_callout(xfer->timeout_handle, MS_TO_TICKS(xfer->timeout),
ehci_timeout, xfer);
callout_reset(&(xfer->timeout_handle), (MS_TO_TICKS(xfer->timeout)),
(ehci_timeout), (xfer));
#else
usb_callout(xfer->timeout_handle, mstohz(xfer->timeout),
ehci_timeout, xfer);
callout_reset(&(xfer->timeout_handle), (mstohz(xfer->timeout)),
(ehci_timeout), (xfer));
#endif
}
ehci_add_intr_list(sc, exfer);
xfer->status = USBD_IN_PROGRESS;
splx(s);
}
mutex_enter(&sc->sc_intrhead_lock);
ehci_add_intr_list(sc, exfer);
mutex_exit(&sc->sc_intrhead_lock);
xfer->status = USBD_IN_PROGRESS;
splx(s);
#ifdef EHCI_DEBUG
if (ehcidebug > 10) {
DPRINTF(("ehci_device_intr_start: data(2)\n"));
delay(10000);
DPRINTF(("ehci_device_intr_start: data(3)\n"));
ehci_dump_regs(sc);
printf("sqh:\n");
ehci_dump_sqh(sqh);
ehci_dump_sqtds(data);
}
if (ehcidebug > 10) {
DPRINTF(("ehci_device_intr_start: data(2)\n"));
delay(10000);
DPRINTF(("ehci_device_intr_start: data(3)\n"));
ehci_dump_regs(sc);
printf("sqh:\n");
ehci_dump_sqh(sqh);
ehci_dump_sqtds(data);
}
#endif
if (sc->sc_bus.use_polling)
ehci_waitintr(sc, xfer);
if (sc->sc_bus.use_polling)
ehci_waitintr(sc, xfer);
return (USBD_IN_PROGRESS);
return (USBD_IN_PROGRESS);
#undef exfer
}
Static void
ehci_device_intr_abort(usbd_xfer_handle xfer)
{
DPRINTFN(1, ("ehci_device_intr_abort: xfer=%p\n", xfer));
if (xfer->pipe->intrxfer == xfer) {
DPRINTFN(1, ("echi_device_intr_abort: remove\n"));
xfer->pipe->intrxfer = NULL;
}
ehci_abort_xfer(xfer, USBD_CANCELLED);
DPRINTFN(1, ("ehci_device_intr_abort: xfer=%p\n", xfer));
if (xfer->pipe->intrxfer == xfer) {
DPRINTFN(1, ("echi_device_intr_abort: remove\n"));
xfer->pipe->intrxfer = NULL;
}
/*
* XXX - abort_xfer uses ehci_sync_hc, which syncs via the advance
* async doorbell. That's dependant on the async list, wheras
* intr xfers are periodic, should not use this?
*/
ehci_abort_xfer(xfer, USBD_CANCELLED);
}
Static void
ehci_device_intr_close(usbd_pipe_handle pipe)
{
ehci_softc_t *sc = (ehci_softc_t *)pipe->device->bus;
struct ehci_pipe *epipe = (struct ehci_pipe *)pipe;
struct ehci_soft_islot *isp;
struct ehci_pipe *epipe = (struct ehci_pipe *)pipe;
struct ehci_soft_islot *isp;
isp = &sc->sc_islots[epipe->sqh->islot];
DPRINTF(("ehci_device_intr_close: pipe=%p\n", pipe));
ehci_close_pipe(pipe, isp->sqh);
isp = &sc->sc_islots[epipe->sqh->islot];
ehci_close_pipe(pipe, isp->sqh);
}
Static void
ehci_device_intr_done(usbd_xfer_handle xfer)
{
#define exfer EXFER(xfer)
struct ehci_xfer *ex = EXFER(xfer);
struct ehci_xfer *ex = EXFER(xfer);
ehci_softc_t *sc = (ehci_softc_t *)xfer->pipe->device->bus;
struct ehci_pipe *epipe = (struct ehci_pipe *)xfer->pipe;
ehci_soft_qtd_t *data, *dataend;
ehci_soft_qh_t *sqh;
usbd_status err;
int len, isread, endpt, s;
DPRINTFN(10, ("ehci_device_intr_done: xfer=%p, actlen=%d\n",
xfer, xfer->actlen));
if (xfer->pipe->repeat) {
ehci_free_sqtd_chain(sc, ex->sqtdstart, NULL);
len = epipe->u.intr.length;
xfer->length = len;
endpt = epipe->pipe.endpoint->edesc->bEndpointAddress;
isread = UE_GET_DIR(endpt) == UE_DIR_IN;
sqh = epipe->sqh;
err = ehci_alloc_sqtd_chain(epipe, sc, len, isread, xfer,
&data, &dataend);
if (err) {
DPRINTFN(-1, ("ehci_device_intr_done: no memory\n"));
xfer->status = err;
return;
}
/* Set up interrupt info. */
exfer->sqtdstart = data;
exfer->sqtdend = dataend;
struct ehci_pipe *epipe = (struct ehci_pipe *)xfer->pipe;
ehci_soft_qtd_t *data, *dataend;
ehci_soft_qh_t *sqh;
usbd_status err;
int len, isread, endpt, s;
DPRINTFN(10, ("ehci_device_intr_done: xfer=%p, actlen=%d\n",
xfer, xfer->actlen));
#ifdef __riscos
s = splusb(); /* No mutexes, so just disable IRQs */
#endif
mutex_enter(&sc->sc_intrhead_lock);
if (xfer->pipe->repeat) {
ehci_free_sqtd_chain(sc, ex->sqtdstart, NULL);
len = epipe->u.intr.length;
xfer->length = len;
endpt = epipe->pipe.endpoint->edesc->bEndpointAddress;
isread = UE_GET_DIR(endpt) == UE_DIR_IN;
usb_syncmem(&xfer->dmabuf, 0, len,
isread ? BUS_DMASYNC_POSTREAD : BUS_DMASYNC_POSTWRITE);
sqh = epipe->sqh;
err = ehci_alloc_sqtd_chain(epipe, sc, len, isread, xfer,
&data, &dataend);
if (err) {
DPRINTFN(-1, ("ehci_device_intr_done: no memory\n"));
xfer->status = err;
mutex_exit(&sc->sc_intrhead_lock);
#ifdef __riscos
splx(s);
#endif
return;
}
/* Set up interrupt info. */
exfer->sqtdstart = data;
exfer->sqtdend = dataend;
#ifdef DIAGNOSTIC
if (!exfer->isdone) {
printf("ehci_device_intr_done: not done, ex=%p\n",
exfer);
}
exfer->isdone = 0;
if (!exfer->isdone) {
printf("ehci_device_intr_done: not done, ex=%p\n",
exfer);
}
exfer->isdone = 0;
#endif
s = splusb();
ehci_set_qh_qtd(sqh, data);
if (xfer->timeout && !sc->sc_bus.use_polling) {
#ifndef __riscos /* Already done */
s = splusb();
#endif
ehci_set_qh_qtd(sqh, data); /* also does usb_syncmem(sqh) */
if (xfer->timeout && !sc->sc_bus.use_polling) {
#ifdef __riscos
usb_callout(xfer->timeout_handle, MS_TO_TICKS(xfer->timeout),
ehci_timeout, xfer);
callout_reset(&(xfer->timeout_handle),
(MS_TO_TICKS(xfer->timeout)), (ehci_timeout), (xfer));
#else
usb_callout(xfer->timeout_handle, mstohz(xfer->timeout),
ehci_timeout, xfer);
callout_reset(&(xfer->timeout_handle),
(mstohz(xfer->timeout)), (ehci_timeout), (xfer));
#endif
}
#ifndef __riscos
splx(s);
#endif
}
splx(s);
xfer->status = USBD_IN_PROGRESS;
} else if (xfer->status != USBD_NOMEM && ehci_active_intr_list(ex)) {
ehci_del_intr_list(ex); /* remove from active list */
ehci_free_sqtd_chain(sc, ex->sqtdstart, NULL);
}
xfer->status = USBD_IN_PROGRESS;
} else if (xfer->status != USBD_NOMEM && ehci_active_intr_list(ex)) {
ehci_del_intr_list(sc, ex); /* remove from active list */
ehci_free_sqtd_chain(sc, ex->sqtdstart, NULL);
endpt = epipe->pipe.endpoint->edesc->bEndpointAddress;
isread = UE_GET_DIR(endpt) == UE_DIR_IN;
usb_syncmem(&xfer->dmabuf, 0, xfer->length,
isread ? BUS_DMASYNC_POSTREAD : BUS_DMASYNC_POSTWRITE);
}
mutex_exit(&sc->sc_intrhead_lock);
#ifdef __riscos
splx(s);
#endif
#undef exfer
}
/************************/
Static usbd_status ehci_device_isoc_transfer(usbd_xfer_handle xfer) { return USBD_IOERROR; }
Static usbd_status ehci_device_isoc_start(usbd_xfer_handle xfer) { return USBD_IOERROR; }
Static void ehci_device_isoc_abort(usbd_xfer_handle xfer) { }
Static void ehci_device_isoc_close(usbd_pipe_handle pipe) { }
Static void ehci_device_isoc_done(usbd_xfer_handle xfer) { }
Static usbd_status
ehci_device_isoc_transfer(usbd_xfer_handle xfer)
{
usbd_status err;
err = usb_insert_transfer(xfer);
if (err && err != USBD_IN_PROGRESS)
return err;
return ehci_device_isoc_start(xfer);
}
Static usbd_status
ehci_device_isoc_start(usbd_xfer_handle xfer)
{
struct ehci_pipe *epipe;
usbd_device_handle dev;
ehci_softc_t *sc;
struct ehci_xfer *exfer;
ehci_soft_itd_t *itd, *prev, *start, *stop;
usb_dma_t *dma_buf;
int i, j, k, frames, uframes, ufrperframe;
int s, trans_count, offs, total_length;
int frindex;
start = NULL;
prev = NULL;
itd = NULL;
trans_count = 0;
total_length = 0;
exfer = (struct ehci_xfer *) xfer;
sc = (ehci_softc_t *)xfer->pipe->device->bus;
dev = xfer->pipe->device;
epipe = (struct ehci_pipe *)xfer->pipe;
/*
* To allow continuous transfers, above we start all transfers
* immediately. However, we're still going to get usbd_start_next call
* this when another xfer completes. So, check if this is already
* in progress or not
*/
if (exfer->itdstart != NULL)
return USBD_IN_PROGRESS;
DPRINTFN(2, ("ehci_device_isoc_start: xfer %p len %d flags %d\n",
xfer, xfer->length, xfer->flags));
if (sc->sc_dying)
return USBD_IOERROR;
/*
* To avoid complication, don't allow a request right now that'll span
* the entire frame table. To within 4 frames, to allow some leeway
* on either side of where the hc currently is.
*/
if ((1 << (epipe->pipe.endpoint->edesc->bInterval)) *
xfer->nframes >= (sc->sc_flsize - 4) * 8) {
printf("ehci: isoc descriptor requested that spans the entire frametable, too many frames\n");
return USBD_INVAL;
}
#ifdef DIAGNOSTIC
if (xfer->rqflags & URQ_REQUEST)
panic("ehci_device_isoc_start: request\n");
if (!exfer->isdone)
printf("ehci_device_isoc_start: not done, ex = %p\n", exfer);
exfer->isdone = 0;
#endif
/*
* Step 1: Allocate and initialize itds, how many do we need?
* One per transfer if interval >= 8 microframes, fewer if we use
* multiple microframes per frame.
*/
i = epipe->pipe.endpoint->edesc->bInterval;
if (i > 16 || i == 0) {
/* Spec page 271 says intervals > 16 are invalid */
DPRINTF(("ehci_device_isoc_start: bInvertal %d invalid\n", i));
return USBD_INVAL;
}
ufrperframe = max(1, USB_UFRAMES_PER_FRAME / (1 << (i - 1)));
frames = (xfer->nframes + (ufrperframe - 1)) / ufrperframe;
uframes = USB_UFRAMES_PER_FRAME / ufrperframe;
if (frames == 0) {
DPRINTF(("ehci_device_isoc_start: frames == 0\n"));
return USBD_INVAL;
}
dma_buf = &xfer->dmabuf;
offs = 0;
for (i = 0; i < frames; i++) {
int froffs = offs;
itd = ehci_alloc_itd(sc);
if (prev != NULL) {
prev->itd.itd_next =
htole32(itd->physaddr | EHCI_LINK_ITD);
usb_syncmem(&itd->dma,
itd->offs + offsetof(ehci_itd_t, itd_next),
sizeof(itd->itd.itd_next), BUS_DMASYNC_POSTWRITE);
prev->xfer_next = itd;
} else {
start = itd;
}
/*
* Step 1.5, initialize uframes
*/
for (j = 0; j < EHCI_ITD_NUFRAMES; j += uframes) {
/* Calculate which page in the list this starts in */
int addr = DMAADDR(dma_buf, froffs);
addr = EHCI_PAGE_OFFSET(addr);
addr += (offs - froffs);
addr = EHCI_PAGE(addr);
addr /= EHCI_PAGE_SIZE;
/* This gets the initial offset into the first page,
* looks how far further along the current uframe
* offset is. Works out how many pages that is.
*/
itd->itd.itd_ctl[j] = htole32 ( EHCI_ITD_ACTIVE |
EHCI_ITD_SET_LEN(xfer->frlengths[trans_count]) |
EHCI_ITD_SET_PG(addr) |
EHCI_ITD_SET_OFFS(EHCI_PAGE_OFFSET(DMAADDR(dma_buf,offs))));
total_length += xfer->frlengths[trans_count];
offs += xfer->frlengths[trans_count];
trans_count++;
if (trans_count >= xfer->nframes) { /*Set IOC*/
itd->itd.itd_ctl[j] |= htole32(EHCI_ITD_IOC);
break;
}
}
/* Step 1.75, set buffer pointers. To simplify matters, all
* pointers are filled out for the next 7 hardware pages in
* the dma block, so no need to worry what pages to cover
* and what to not.
*/
for (j = 0; j < EHCI_ITD_NBUFFERS; j++) {
/*
* Don't try to lookup a page that's past the end
* of buffer
*/
int page_offs = EHCI_PAGE(froffs + (EHCI_PAGE_SIZE * j));
#ifdef __riscos
if (page_offs >= xfer->length) /* I think this is correct! */
#else
if (page_offs >= dma_buf->block->size)
#endif
break;
long long page = DMAADDR(dma_buf, page_offs);
page = EHCI_PAGE(page);
itd->itd.itd_bufr[j] =
htole32(EHCI_ITD_SET_BPTR(page));
itd->itd.itd_bufr_hi[j] =
htole32(page >> 32);
}
/*
* Other special values
*/
k = epipe->pipe.endpoint->edesc->bEndpointAddress;
itd->itd.itd_bufr[0] |= htole32(EHCI_ITD_SET_EP(UE_GET_ADDR(k)) |
EHCI_ITD_SET_DADDR(epipe->pipe.device->address));
k = (UE_GET_DIR(epipe->pipe.endpoint->edesc->bEndpointAddress))
? 1 : 0;
j = UGETW(epipe->pipe.endpoint->edesc->wMaxPacketSize);
itd->itd.itd_bufr[1] |= htole32(EHCI_ITD_SET_DIR(k) |
EHCI_ITD_SET_MAXPKT(UE_GET_SIZE(j)));
/* FIXME: handle invalid trans */
itd->itd.itd_bufr[2] |=
htole32(EHCI_ITD_SET_MULTI(UE_GET_TRANS(j)+1));
usb_syncmem(&itd->dma,
itd->offs + offsetof(ehci_itd_t, itd_next),
sizeof(ehci_itd_t),
BUS_DMASYNC_PREWRITE | BUS_DMASYNC_PREREAD);
prev = itd;
} /* End of frame */
stop = itd;
stop->xfer_next = NULL;
exfer->isoc_len = total_length;
usb_syncmem(&exfer->xfer.dmabuf, 0, total_length,
BUS_DMASYNC_PREREAD | BUS_DMASYNC_PREWRITE);
/*
* Part 2: Transfer descriptors have now been set up, now they must
* be scheduled into the period frame list. Erk. Not wanting to
* complicate matters, transfer is denied if the transfer spans
* more than the period frame list.
*/
s = splusb();
/* Start inserting frames */
if (epipe->u.isoc.cur_xfers > 0) {
frindex = epipe->u.isoc.next_frame;
} else {
frindex = EOREAD4(sc, EHCI_FRINDEX);
frindex = frindex >> 3; /* Erase microframe index */
frindex += 2;
}
if (frindex >= sc->sc_flsize)
frindex &= (sc->sc_flsize - 1);
/* What's the frame interval? */
i = (1 << (epipe->pipe.endpoint->edesc->bInterval - 1));
if (i / USB_UFRAMES_PER_FRAME == 0)
i = 1;
else
i /= USB_UFRAMES_PER_FRAME;
itd = start;
for (j = 0; j < frames; j++) {
if (itd == NULL)
panic("ehci: unexpectedly ran out of isoc itds, isoc_start\n");
itd->itd.itd_next = sc->sc_flist[frindex];
if (itd->itd.itd_next == 0)
/* FIXME: frindex table gets initialized to NULL
* or EHCI_NULL? */
itd->itd.itd_next = EHCI_NULL;
usb_syncmem(&itd->dma,
itd->offs + offsetof(ehci_itd_t, itd_next),
sizeof(itd->itd.itd_next),
BUS_DMASYNC_PREWRITE | BUS_DMASYNC_PREREAD);
sc->sc_flist[frindex] = htole32(EHCI_LINK_ITD | itd->physaddr);
usb_syncmem(&sc->sc_fldma,
sizeof(ehci_link_t) * frindex,
sizeof(ehci_link_t),
BUS_DMASYNC_PREWRITE | BUS_DMASYNC_PREREAD);
itd->u.frame_list.next = sc->sc_softitds[frindex];
sc->sc_softitds[frindex] = itd;
if (itd->u.frame_list.next != NULL)
itd->u.frame_list.next->u.frame_list.prev = itd;
itd->slot = frindex;
itd->u.frame_list.prev = NULL;
frindex += i;
if (frindex >= sc->sc_flsize)
frindex -= sc->sc_flsize;
itd = itd->xfer_next;
}
epipe->u.isoc.cur_xfers++;
epipe->u.isoc.next_frame = frindex;
exfer->itdstart = start;
exfer->itdend = stop;
exfer->sqtdstart = NULL;
exfer->sqtdstart = NULL;
mutex_enter(&sc->sc_intrhead_lock);
ehci_add_intr_list(sc, exfer);
mutex_exit(&sc->sc_intrhead_lock);
xfer->status = USBD_IN_PROGRESS;
xfer->done = 0;
splx(s);
if (sc->sc_bus.use_polling) {
printf("Starting ehci isoc xfer with polling. Bad idea?\n");
ehci_waitintr(sc, xfer);
}
return USBD_IN_PROGRESS;
}
Static void
ehci_device_isoc_abort(usbd_xfer_handle xfer)
{
DPRINTFN(1, ("ehci_device_isoc_abort: xfer = %p\n", xfer));
ehci_abort_isoc_xfer(xfer, USBD_CANCELLED);
}
Static void
ehci_device_isoc_close(usbd_pipe_handle pipe)
{
DPRINTFN(1, ("ehci_device_isoc_close: nothing in the pipe to free?\n"));
}
Static void
ehci_device_isoc_done(usbd_xfer_handle xfer)
{
struct ehci_xfer *exfer;
ehci_softc_t *sc;
struct ehci_pipe *epipe;
int s;
exfer = EXFER(xfer);
sc = (ehci_softc_t *)xfer->pipe->device->bus;
epipe = (struct ehci_pipe *) xfer->pipe;
s = splusb();
epipe->u.isoc.cur_xfers--;
mutex_enter(&sc->sc_intrhead_lock);
if (xfer->status != USBD_NOMEM && ehci_active_intr_list(exfer)) {
ehci_del_intr_list(sc, exfer);
ehci_rem_free_itd_chain(sc, exfer);
}
mutex_exit(&sc->sc_intrhead_lock);
splx(s);
usb_syncmem(&xfer->dmabuf, 0, xfer->length, BUS_DMASYNC_POSTWRITE |
BUS_DMASYNC_POSTREAD);
}
/* $NetBSD: hid.c,v 1.23 2002/07/11 21:14:25 augustss Exp $ */
/* $NetBSD: hid.c,v 1.30 2010/05/14 17:32:57 plunky Exp $ */
/* $FreeBSD: src/sys/dev/usb/hid.c,v 1.11 1999/11/17 22:33:39 n_hibma Exp $ */
/*
......@@ -17,13 +17,6 @@
* 2. Redistributions in binary form must reproduce the above copyright
* notice, this list of conditions and the following disclaimer in the
* documentation and/or other materials provided with the distribution.
* 3. All advertising materials mentioning features or use of this software
* must display the following acknowledgement:
* This product includes software developed by the NetBSD
* Foundation, Inc. and its contributors.
* 4. Neither the name of The NetBSD Foundation nor the names of its
* contributors may be used to endorse or promote products derived
* from this software without specific prior written permission.
*
* THIS SOFTWARE IS PROVIDED BY THE NETBSD FOUNDATION, INC. AND CONTRIBUTORS
* ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED
......@@ -38,8 +31,13 @@
* POSSIBILITY OF SUCH DAMAGE.
*/
#ifdef __riscos
#include <dev/usb/usbhal.h>
#endif
#include <sys/cdefs.h>
//__KERNEL_RCSID(0, "$NetBSD: hid.c,v 1.23 2002/07/11 21:14:25 augustss Exp $");
#ifndef __riscos
__KERNEL_RCSID(0, "$NetBSD: hid.c,v 1.30 2010/05/14 17:32:57 plunky Exp $");
#endif
#include <sys/param.h>
#include <sys/systm.h>
......@@ -68,9 +66,9 @@ Static void hid_clear_local(struct hid_item *);
#define MAXUSAGE 256
struct hid_data {
u_char *start;
u_char *end;
u_char *p;
const u_char *start;
const u_char *end;
const u_char *p;
struct hid_item cur;
int32_t usages[MAXUSAGE];
int nu;
......@@ -98,7 +96,7 @@ hid_clear_local(struct hid_item *c)
}
struct hid_data *
hid_start_parse(void *d, int len, enum hid_kind kind)
hid_start_parse(const void *d, int len, enum hid_kind kind)
{
struct hid_data *s;
......@@ -108,7 +106,7 @@ hid_start_parse(void *d, int len, enum hid_kind kind)
memset(s, 0, sizeof *s);
#endif
s->start = s->p = d;
s->end = (void*) ((char *)d + len);
s->end = ((const u_char *)d) + len;
s->kind = kind;
return (s);
}
......@@ -131,9 +129,9 @@ hid_get_item(struct hid_data *s, struct hid_item *h)
struct hid_item *c = &s->cur;
unsigned int bTag, bType, bSize;
u_int32_t oldpos;
u_char *data;
const u_char *data;
int32_t dval;
u_char *p;
const u_char *p;
struct hid_item *hi;
int i;
enum hid_kind retkind;
......@@ -200,7 +198,7 @@ hid_get_item(struct hid_data *s, struct hid_item *h)
dval |= *data++ << 24;
break;
default:
printf("BAD LENGTH %d\n", bSize);
printf("BAD LENGTH %d\n", bSize);
continue;
}
......@@ -267,7 +265,7 @@ hid_get_item(struct hid_data *s, struct hid_item *h)
s->nu = 0;
return (1);
default:
printf("Main bTag=%d\n", bTag);
printf("Main bTag=%d\n", bTag);
break;
}
break;
......@@ -306,18 +304,18 @@ hid_get_item(struct hid_data *s, struct hid_item *h)
break;
case 10: /* Push */
hi = malloc(sizeof *hi, M_TEMP, M_WAITOK);
*hi = s->cur;
*hi = *c;
c->next = hi;
break;
case 11: /* Pop */
hi = c->next;
oldpos = c->loc.pos;
s->cur = *hi;
*c = *hi;
c->loc.pos = oldpos;
free(hi, M_TEMP);
break;
default:
printf("Global bTag=%d\n", bTag);
printf("Global bTag=%d\n", bTag);
break;
}
break;
......@@ -370,19 +368,19 @@ hid_get_item(struct hid_data *s, struct hid_item *h)
c->set_delimiter = dval;
break;
default:
printf("Local bTag=%d\n", bTag);
printf("Local bTag=%d\n", bTag);
break;
}
break;
default:
printf("default bType=%d\n", bType);
printf("default bType=%d\n", bType);
break;
}
}
}
int
hid_report_size(void *buf, int len, enum hid_kind k, u_int8_t id)
hid_report_size(const void *buf, int len, enum hid_kind k, u_int8_t id)
{
struct hid_data *d;
struct hid_item h;
......@@ -401,7 +399,7 @@ hid_report_size(void *buf, int len, enum hid_kind k, u_int8_t id)
lo = h.loc.pos;
#ifdef DIAGNOSTIC
if (lo != 0) {
printf("hid_report_size: lo != 0\n");
printf("hid_report_size: lo != 0\n");
}
#endif
}
......@@ -414,7 +412,7 @@ hid_report_size(void *buf, int len, enum hid_kind k, u_int8_t id)
}
int
hid_locate(void *desc, int size, u_int32_t u, u_int8_t id, enum hid_kind k,
hid_locate(const void *desc, int size, u_int32_t u, u_int8_t id, enum hid_kind k,
struct hid_location *loc, u_int32_t *flags)
{
struct hid_data *d;
......@@ -440,41 +438,73 @@ hid_locate(void *desc, int size, u_int32_t u, u_int8_t id, enum hid_kind k,
return (0);
}
long
hid_get_data(const u_char *buf, const struct hid_location *loc)
{
u_int hsize = loc->size;
u_long data;
if (hsize == 0)
return (0);
data = hid_get_udata(buf, loc);
if (data < (1 << (hsize - 1)))
return (data);
return data - (1 << hsize);
}
u_long
hid_get_data(u_char *buf, struct hid_location *loc)
hid_get_udata(const u_char *buf, const struct hid_location *loc)
{
u_int hpos = loc->pos;
u_int hsize = loc->size;
u_int32_t data;
int i, s;
DPRINTFN(10, ("hid_get_data: loc %d/%d\n", hpos, hsize));
u_int i, num, off;
u_long data;
if (hsize == 0)
return (0);
data = 0;
s = hpos / 8;
for (i = hpos; i < hpos+hsize; i += 8)
data |= buf[i / 8] << ((i / 8 - s) * 8);
off = hpos / 8;
num = (hpos + hsize + 7) / 8 - off;
for (i = 0; i < num; i++)
data |= buf[off + i] << (i * 8);
data >>= hpos % 8;
data &= (1 << hsize) - 1;
hsize = 32 - hsize;
/* Sign extend */
data = ((int32_t)data << hsize) >> hsize;
DPRINTFN(10,("hid_get_data: loc %d/%d = %lu\n",
loc->pos, loc->size, (long)data));
DPRINTFN(10,("hid_get_udata: loc %d/%d = %lu\n", hpos, hsize, data));
return (data);
}
/*
* hid_is_collection(desc, size, id, usage)
*
* This function is broken in the following way.
*
* It is used to discover if the given 'id' is part of 'usage' collection
* in the descriptor in order to match report id against device type.
*
* The semantics of hid_start_parse() means though, that only a single
* kind of report is considered. The current HID code that uses this for
* matching is actually only looking for input reports, so this works
* for now.
*
* This function could try all report kinds (input, output and feature)
* consecutively if necessary, but it may be better to integrate the
* libusbhid code which can consider multiple report kinds simultaneously
*
* Needs some thought.
*/
int
hid_is_collection(void *desc, int size, u_int8_t id, u_int32_t usage)
hid_is_collection(const void *desc, int size, u_int8_t id, u_int32_t usage)
{
struct hid_data *hd;
struct hid_item hi;
u_int32_t coll_usage = ~0;
hd = hid_start_parse(desc, size, hid_none);
hd = hid_start_parse(desc, size, hid_input);
if (hd == NULL)
return (0);
......@@ -483,10 +513,15 @@ hid_is_collection(void *desc, int size, u_int8_t id, u_int32_t usage)
DPRINTFN(2,("hid_is_collection: kind=%d id=%d usage=0x%x"
"(0x%x)\n",
hi.kind, hi.report_ID, hi.usage, coll_usage));
if (hi.kind == hid_collection &&
hi.collection == HCOLL_APPLICATION)
coll_usage = hi.usage;
if (hi.kind == hid_endcollection &&
if (hi.kind == hid_endcollection)
coll_usage = ~0;
if (hi.kind == hid_input &&
coll_usage == usage &&
hi.report_ID == id) {
DPRINTFN(2,("hid_is_collection: found\n"));
......
......@@ -51,6 +51,9 @@
* USB spec: http://www.usb.org/developers/docs/usbspec.zip
*/
#ifdef __riscos
#include <dev/usb/usbhal.h>
#endif
#include <sys/cdefs.h>
//__KERNEL_RCSID(0, "$NetBSD: ohci.c,v 1.154 2004/12/22 19:36:13 joff Exp $");
......@@ -292,6 +295,11 @@ struct ohci_pipe {
#define OHCI_INTR_ENDPT 1
#ifdef USBHAL
extern int usbhal_ohci_do_intr(struct usbd_bus *,int irqdevno);
extern void usbhal_ohci_shutdown(struct usbd_bus *);
#endif
Static struct usbd_bus_methods ohci_bus_methods = {
ohci_open,
ohci_softintr,
......@@ -300,6 +308,10 @@ Static struct usbd_bus_methods ohci_bus_methods = {
ohci_freem,
ohci_allocx,
ohci_freex,
#ifdef USBHAL
usbhal_ohci_do_intr,
usbhal_ohci_shutdown,
#endif
};
Static struct usbd_pipe_methods ohci_root_ctrl_methods = {
......@@ -356,7 +368,21 @@ Static struct usbd_pipe_methods ohci_device_isoc_methods = {
ohci_device_isoc_done,
};
#if defined (__riscos)
#ifdef USBHAL
/* TODO - Move elsewhere */
static void abort_pipe(void *v)
{
splbio(); /* Code in cmodule runs with interrupts enabled(!) */
ohci_abort_xfer((usbd_xfer_handle) v,USBD_TIMEOUT);
}
static void riscos_abort_pipe(void *v)
{
USBHAL_AddCallback(abort_pipe,v);
}
#endif
#if defined (__riscos) && !defined(USBHAL)
static int veneers_built = 0;
void build_veneer (void* vn, void* st, size_t sz);
static struct {
......@@ -693,7 +719,7 @@ ohci_init(ohci_softc_t *sc)
int i;
u_int32_t s, ctl, ival, hcr, fm, per, rev, desca;
#if defined (__riscos)
#if defined (__riscos) && !defined(USBHAL)
if (!veneers_built)
{
build_veneer(&ohci_bus_methods_entry,
......@@ -1189,7 +1215,7 @@ ohci_intr(void *p)
OWRITE4(sc, OHCI_INTERRUPT_STATUS,
OREAD4(sc, OHCI_INTERRUPT_STATUS));
#ifdef __riscos
riscos_irqclear();
riscos_irqclear(sc->sc_irqdevno);
#endif
return (0);
......@@ -2589,7 +2615,7 @@ ohci_abort_xfer(usbd_xfer_handle xfer, usbd_status status)
/*
* Data structures and routines to emulate the root hub.
*/
Static usb_device_descriptor_t ohci_devd = {
Static const usb_device_descriptor_t ohci_devd = {
USB_DEVICE_DESCRIPTOR_SIZE,
UDESC_DEVICE, /* type */
{0x00, 0x01}, /* USB version */
......@@ -2602,7 +2628,7 @@ Static usb_device_descriptor_t ohci_devd = {
1 /* # of configurations */
};
Static usb_config_descriptor_t ohci_confd = {
Static const usb_config_descriptor_t ohci_confd = {
USB_CONFIG_DESCRIPTOR_SIZE,
UDESC_CONFIG,
{USB_CONFIG_DESCRIPTOR_SIZE +
......@@ -2615,7 +2641,7 @@ Static usb_config_descriptor_t ohci_confd = {
0 /* max power */
};
Static usb_interface_descriptor_t ohci_ifcd = {
Static const usb_interface_descriptor_t ohci_ifcd = {
USB_INTERFACE_DESCRIPTOR_SIZE,
UDESC_INTERFACE,
0,
......@@ -2627,7 +2653,7 @@ Static usb_interface_descriptor_t ohci_ifcd = {
0
};
Static usb_endpoint_descriptor_t ohci_endpd = {
Static const usb_endpoint_descriptor_t ohci_endpd = {
USB_ENDPOINT_DESCRIPTOR_SIZE,
UDESC_ENDPOINT,
UE_DIR_IN | OHCI_INTR_ENDPT,
......@@ -2636,7 +2662,7 @@ Static usb_endpoint_descriptor_t ohci_endpd = {
255
};
Static usb_hub_descriptor_t ohci_hubd = {
Static const usb_hub_descriptor_t ohci_hubd = {
USB_HUB_DESCRIPTOR_SIZE,
UDESC_HUB,
0,
......@@ -2690,6 +2716,7 @@ ohci_root_ctrl_start(usbd_xfer_handle xfer)
int s, len, value, index, l, totlen = 0;
usb_port_status_t ps;
usb_hub_descriptor_t hubd;
usb_device_descriptor_t devd;
usbd_status err;
u_int32_t v;
......@@ -2738,9 +2765,10 @@ ohci_root_ctrl_start(usbd_xfer_handle xfer)
err = USBD_IOERROR;
goto ret;
}
devd = ohci_devd;
USETW(devd.idVendor, sc->sc_id_vendor);
totlen = l = min(len, USB_DEVICE_DESCRIPTOR_SIZE);
USETW(ohci_devd.idVendor, sc->sc_id_vendor);
memcpy(buf, (void *)&ohci_devd, l);
memcpy(buf, (void *)&devd, l);
break;
case UDESC_CONFIG:
if ((value & 0xff) != 0) {
......
......@@ -42,6 +42,9 @@
* USB spec: http://www.usb.org/developers/docs/usbspec.zip
*/
#ifdef __riscos
#include <dev/usb/usbhal.h>
#endif
#include <sys/cdefs.h>
//__KERNEL_RCSID(0, "$NetBSD: uhub.c,v 1.74 2005/03/02 11:37:27 mycroft Exp $");
......@@ -109,7 +112,7 @@ Static bus_child_detached_t uhub_child_detached;
USB_DECLARE_DRIVER(uhub);
#if defined __riscos
/* Create the driver instance for the hub connected to hub case */
struct cfattach uhub_uhub_ca = {
halconst struct cfattach uhub_uhub_ca = {
sizeof(struct uhub_softc), uhub_match, uhub_attach,
uhub_detach, uhub_activate
};
......@@ -160,7 +163,9 @@ USB_ATTACH(uhub)
{
USB_ATTACH_START(uhub, sc, uaa);
usbd_device_handle dev = uaa->device;
#if !defined(__riscos) || defined(USB_DEBUG)
char devinfo[1024];
#endif
usbd_status err;
struct usbd_hub *hub = NULL;
usb_device_request_t req;
......@@ -172,6 +177,7 @@ USB_ATTACH(uhub)
DPRINTFN(1,("uhub_attach\n"));
sc->sc_hub = dev;
#if !defined(__riscos) || defined(USB_DEBUG)
usbd_devinfo(dev, 1, devinfo, sizeof(devinfo));
USB_ATTACH_SETUP;
printf("%s: %s\n", USBDEVNAME(sc->sc_dev), devinfo);
......@@ -182,6 +188,7 @@ USB_ATTACH(uhub)
UHUB_IS_SINGLE_TT(sc) ? "single" : "multiple",
UHUB_IS_SINGLE_TT(sc) ? "" : "s");
}
#endif
err = usbd_set_config_index(dev, 0, 1);
if (err) {
DPRINTF(("%s: configuration failed, error=%s\n",
......
/* $NetBSD: ums.c,v 1.60 2003/03/11 16:44:00 augustss Exp $ */
/* $NetBSD: ums.c,v 1.80 2010/01/14 09:30:39 matthias Exp $ */
/*
* Copyright (c) 1998 The NetBSD Foundation, Inc.
......@@ -16,13 +16,6 @@
* 2. Redistributions in binary form must reproduce the above copyright
* notice, this list of conditions and the following disclaimer in the
* documentation and/or other materials provided with the distribution.
* 3. All advertising materials mentioning features or use of this software
* must display the following acknowledgement:
* This product includes software developed by the NetBSD
* Foundation, Inc. and its contributors.
* 4. Neither the name of The NetBSD Foundation nor the names of its
* contributors may be used to endorse or promote products derived
* from this software without specific prior written permission.
*
* THIS SOFTWARE IS PROVIDED BY THE NETBSD FOUNDATION, INC. AND CONTRIBUTORS
* ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED
......@@ -42,7 +35,7 @@
*/
#include <sys/cdefs.h>
__KERNEL_RCSID(0, "$NetBSD: ums.c,v 1.60 2003/03/11 16:44:00 augustss Exp $");
__KERNEL_RCSID(0, "$NetBSD: ums.c,v 1.80 2010/01/14 09:30:39 matthias Exp $");
#include <sys/param.h>
#include <sys/systm.h>
......@@ -50,7 +43,6 @@ __KERNEL_RCSID(0, "$NetBSD: ums.c,v 1.60 2003/03/11 16:44:00 augustss Exp $");
#include <sys/malloc.h>
#include <sys/device.h>
#include <sys/ioctl.h>
#include <sys/tty.h>
#include <sys/file.h>
#include <sys/select.h>
#include <sys/proc.h>
......@@ -88,12 +80,12 @@ int umsdebug = 0;
#define PS2MBUTMASK x04
#define PS2BUTMASK 0x0f
#define MAX_BUTTONS 7 /* must not exceed size of sc_buttons */
#define MAX_BUTTONS 31 /* must not exceed size of sc_buttons */
struct ums_softc {
struct uhidev sc_hdev;
struct hid_location sc_loc_x, sc_loc_y, sc_loc_z;
struct hid_location sc_loc_x, sc_loc_y, sc_loc_z, sc_loc_w;
struct hid_location sc_loc_btn[MAX_BUTTONS];
int sc_enabled;
......@@ -102,23 +94,24 @@ struct ums_softc {
#define UMS_Z 0x01 /* z direction available */
#define UMS_SPUR_BUT_UP 0x02 /* spurious button up events */
#define UMS_REVZ 0x04 /* Z-axis is reversed */
#define UMS_W 0x08 /* w direction/tilt available */
#define UMS_ABS 0x10 /* absolute position, touchpanel */
int nbuttons;
u_int32_t sc_buttons; /* mouse button status */
struct device *sc_wsmousedev;
device_t sc_wsmousedev;
char sc_dying;
};
#define MOUSE_FLAGS_MASK (HIO_CONST|HIO_RELATIVE)
#define MOUSE_FLAGS (HIO_RELATIVE)
Static void ums_intr(struct uhidev *addr, void *ibuf, u_int len);
Static int ums_enable(void *);
Static void ums_disable(void *);
Static int ums_ioctl(void *, u_long, caddr_t, int, usb_proc_ptr );
Static int ums_ioctl(void *, u_long, void *, int, struct lwp * );
const struct wsmouse_accessops ums_accessops = {
ums_enable,
......@@ -126,35 +119,56 @@ const struct wsmouse_accessops ums_accessops = {
ums_disable,
};
USB_DECLARE_DRIVER(ums);
int ums_match(device_t, cfdata_t, void *);
void ums_attach(device_t, device_t, void *);
void ums_childdet(device_t, device_t);
int ums_detach(device_t, int);
int ums_activate(device_t, enum devact);
extern struct cfdriver ums_cd;
CFATTACH_DECL2_NEW(ums, sizeof(struct ums_softc), ums_match, ums_attach,
ums_detach, ums_activate, NULL, ums_childdet);
int
ums_match(struct device *parent, struct cfdata *match, void *aux)
ums_match(device_t parent, cfdata_t match, void *aux)
{
struct uhidev_attach_arg *uha = aux;
int size;
void *desc;
/*
* Some (older) Griffin PowerMate knobs may masquerade as a
* mouse, avoid treating them as such, they have only one axis.
*/
if (uha->uaa->vendor == USB_VENDOR_GRIFFIN &&
uha->uaa->product == USB_PRODUCT_GRIFFIN_POWERMATE)
return (UMATCH_NONE);
uhidev_get_report_desc(uha->parent, &desc, &size);
if (!hid_is_collection(desc, size, uha->reportid,
HID_USAGE2(HUP_GENERIC_DESKTOP, HUG_MOUSE)))
HID_USAGE2(HUP_GENERIC_DESKTOP, HUG_MOUSE)) &&
!hid_is_collection(desc, size, uha->reportid,
HID_USAGE2(HUP_GENERIC_DESKTOP, HUG_POINTER)))
return (UMATCH_NONE);
return (UMATCH_IFACECLASS);
}
void
ums_attach(struct device *parent, struct device *self, void *aux)
ums_attach(device_t parent, device_t self, void *aux)
{
struct ums_softc *sc = (struct ums_softc *)self;
struct ums_softc *sc = device_private(self);
struct uhidev_attach_arg *uha = aux;
struct wsmousedev_attach_args a;
int size;
void *desc;
u_int32_t flags, quirks;
int i, wheel;
int i, hl;
struct hid_location *zloc;
struct hid_location loc_btn;
aprint_naive("\n");
sc->sc_hdev.sc_dev = self;
sc->sc_hdev.sc_intr = ums_intr;
sc->sc_hdev.sc_parent = uha->parent;
sc->sc_hdev.sc_report_id = uha->reportid;
......@@ -167,47 +181,120 @@ ums_attach(struct device *parent, struct device *self, void *aux)
uhidev_get_report_desc(uha->parent, &desc, &size);
if (!pmf_device_register(self, NULL, NULL))
aprint_error_dev(self, "couldn't establish power handler\n");
if (!hid_locate(desc, size, HID_USAGE2(HUP_GENERIC_DESKTOP, HUG_X),
uha->reportid, hid_input, &sc->sc_loc_x, &flags)) {
printf("\n%s: mouse has no X report\n",
aprint_error("\n%s: mouse has no X report\n",
USBDEVNAME(sc->sc_hdev.sc_dev));
USB_ATTACH_ERROR_RETURN;
}
if ((flags & MOUSE_FLAGS_MASK) != MOUSE_FLAGS) {
printf("\n%s: X report 0x%04x not supported\n",
switch (flags & MOUSE_FLAGS_MASK) {
case 0:
sc->flags |= UMS_ABS;
break;
case HIO_RELATIVE:
break;
default:
aprint_error("\n%s: X report 0x%04x not supported\n",
USBDEVNAME(sc->sc_hdev.sc_dev), flags);
USB_ATTACH_ERROR_RETURN;
}
if (!hid_locate(desc, size, HID_USAGE2(HUP_GENERIC_DESKTOP, HUG_Y),
uha->reportid, hid_input, &sc->sc_loc_y, &flags)) {
printf("\n%s: mouse has no Y report\n",
aprint_error("\n%s: mouse has no Y report\n",
USBDEVNAME(sc->sc_hdev.sc_dev));
USB_ATTACH_ERROR_RETURN;
}
if ((flags & MOUSE_FLAGS_MASK) != MOUSE_FLAGS) {
printf("\n%s: Y report 0x%04x not supported\n",
switch (flags & MOUSE_FLAGS_MASK) {
case 0:
sc->flags |= UMS_ABS;
break;
case HIO_RELATIVE:
break;
default:
aprint_error("\n%s: Y report 0x%04x not supported\n",
USBDEVNAME(sc->sc_hdev.sc_dev), flags);
USB_ATTACH_ERROR_RETURN;
}
/* Try to guess the Z activator: first check Z, then WHEEL. */
wheel = 0;
if (hid_locate(desc, size, HID_USAGE2(HUP_GENERIC_DESKTOP, HUG_Z),
uha->reportid, hid_input, &sc->sc_loc_z, &flags) ||
(wheel = hid_locate(desc, size, HID_USAGE2(HUP_GENERIC_DESKTOP,
HUG_WHEEL),
uha->reportid, hid_input, &sc->sc_loc_z, &flags))) {
if ((flags & MOUSE_FLAGS_MASK) != MOUSE_FLAGS) {
/* Try the wheel first as the Z activator since it's tradition. */
hl = hid_locate(desc,
size,
HID_USAGE2(HUP_GENERIC_DESKTOP, HUG_WHEEL),
uha->reportid,
hid_input,
&sc->sc_loc_z,
&flags);
zloc = &sc->sc_loc_z;
if (hl) {
if ((flags & MOUSE_FLAGS_MASK) != HIO_RELATIVE) {
aprint_verbose("\n%s: Wheel report 0x%04x not "
"supported\n", USBDEVNAME(sc->sc_hdev.sc_dev),
flags);
sc->sc_loc_z.size = 0; /* Bad Z coord, ignore it */
} else {
sc->flags |= UMS_Z;
/* Wheels need the Z axis reversed. */
if (wheel)
sc->flags ^= UMS_REVZ;
sc->flags ^= UMS_REVZ;
/* Put Z on the W coordinate */
zloc = &sc->sc_loc_w;
}
}
hl = hid_locate(desc,
size,
HID_USAGE2(HUP_GENERIC_DESKTOP, HUG_Z),
uha->reportid,
hid_input,
zloc,
&flags);
/*
* The horizontal component of the scrollball can also be given by
* Application Control Pan in the Consumer page, so if we didnt see
* any Z then check that.
*/
if (!hl) {
hl = hid_locate(desc,
size,
HID_USAGE2(HUP_CONSUMER, HUC_AC_PAN),
uha->reportid,
hid_input,
zloc,
&flags);
}
if (hl) {
if ((flags & MOUSE_FLAGS_MASK) != HIO_RELATIVE) {
aprint_verbose("\n%s: Z report 0x%04x not supported\n",
USBDEVNAME(sc->sc_hdev.sc_dev), flags);
zloc->size = 0; /* Bad Z coord, ignore it */
} else {
if (sc->flags & UMS_Z)
sc->flags |= UMS_W;
else
sc->flags |= UMS_Z;
}
}
/*
* The Microsoft Wireless Laser Mouse 6000 v2.0 reports a bad
* position for the wheel and wheel tilt controls -- should be
* in bytes 3 & 4 of the report. Fix this if necessary.
*/
if (uha->uaa->vendor == USB_VENDOR_MICROSOFT &&
(uha->uaa->product == USB_PRODUCT_MICROSOFT_24GHZ_XCVR10 ||
uha->uaa->product == USB_PRODUCT_MICROSOFT_24GHZ_XCVR20)) {
if ((sc->flags & UMS_Z) && sc->sc_loc_z.pos == 0)
sc->sc_loc_z.pos = 24;
if ((sc->flags & UMS_W) && sc->sc_loc_w.pos == 0)
sc->sc_loc_w.pos = sc->sc_loc_z.pos + 8;
}
/* figure out the number of buttons */
for (i = 1; i <= MAX_BUTTONS; i++)
if (!hid_locate(desc, size, HID_USAGE2(HUP_BUTTON, i),
......@@ -215,9 +302,11 @@ ums_attach(struct device *parent, struct device *self, void *aux)
break;
sc->nbuttons = i - 1;
printf(": %d button%s%s\n",
aprint_normal(": %d button%s%s%s%s\n",
sc->nbuttons, sc->nbuttons == 1 ? "" : "s",
sc->flags & UMS_Z ? " and Z dir." : "");
sc->flags & UMS_W ? ", W" : "",
sc->flags & UMS_Z ? " and Z dir" : "",
sc->flags & UMS_W ? "s" : "");
for (i = 1; i <= sc->nbuttons; i++)
hid_locate(desc, size, HID_USAGE2(HUP_BUTTON, i),
......@@ -233,6 +322,9 @@ ums_attach(struct device *parent, struct device *self, void *aux)
if (sc->flags & UMS_Z)
DPRINTF(("ums_attach: Z\t%d/%d\n",
sc->sc_loc_z.pos, sc->sc_loc_z.size));
if (sc->flags & UMS_W)
DPRINTF(("ums_attach: W\t%d/%d\n",
sc->sc_loc_w.pos, sc->sc_loc_w.size));
for (i = 1; i <= sc->nbuttons; i++) {
DPRINTF(("ums_attach: B%d\t%d/%d\n",
i, sc->sc_loc_btn[i-1].pos,sc->sc_loc_btn[i-1].size));
......@@ -250,26 +342,30 @@ ums_attach(struct device *parent, struct device *self, void *aux)
int
ums_activate(device_ptr_t self, enum devact act)
{
struct ums_softc *sc = (struct ums_softc *)self;
int rv = 0;
struct ums_softc *sc = device_private(self);
switch (act) {
case DVACT_ACTIVATE:
return (EOPNOTSUPP);
case DVACT_DEACTIVATE:
if (sc->sc_wsmousedev != NULL)
rv = config_deactivate(sc->sc_wsmousedev);
sc->sc_dying = 1;
break;
return 0;
default:
return EOPNOTSUPP;
}
return (rv);
}
void
ums_childdet(device_t self, device_t child)
{
struct ums_softc *sc = device_private(self);
KASSERT(sc->sc_wsmousedev == child);
sc->sc_wsmousedev = NULL;
}
int
ums_detach(struct device *self, int flags)
ums_detach(device_t self, int flags)
{
struct ums_softc *sc = (struct ums_softc *)self;
struct ums_softc *sc = device_private(self);
int rv = 0;
DPRINTF(("ums_detach: sc=%p flags=%d\n", sc, flags));
......@@ -278,6 +374,8 @@ ums_detach(struct device *self, int flags)
if (sc->sc_wsmousedev != NULL)
rv = config_detach(sc->sc_wsmousedev, flags);
pmf_device_deregister(self);
return (rv);
}
......@@ -285,30 +383,38 @@ void
ums_intr(struct uhidev *addr, void *ibuf, u_int len)
{
struct ums_softc *sc = (struct ums_softc *)addr;
int dx, dy, dz;
int dx, dy, dz, dw;
u_int32_t buttons = 0;
int i;
int s;
int i, flags, s;
DPRINTFN(5,("ums_intr: len=%d\n", len));
flags = WSMOUSE_INPUT_DELTA; /* equals 0 */
dx = hid_get_data(ibuf, &sc->sc_loc_x);
dy = -hid_get_data(ibuf, &sc->sc_loc_y);
if (sc->flags & UMS_ABS) {
flags |= (WSMOUSE_INPUT_ABSOLUTE_X | WSMOUSE_INPUT_ABSOLUTE_Y);
dy = hid_get_data(ibuf, &sc->sc_loc_y);
} else
dy = -hid_get_data(ibuf, &sc->sc_loc_y);
dz = hid_get_data(ibuf, &sc->sc_loc_z);
dw = hid_get_data(ibuf, &sc->sc_loc_w);
if (sc->flags & UMS_REVZ)
dz = -dz;
for (i = 0; i < sc->nbuttons; i++)
if (hid_get_data(ibuf, &sc->sc_loc_btn[i]))
buttons |= (1 << UMS_BUT(i));
if (dx != 0 || dy != 0 || dz != 0 || buttons != sc->sc_buttons) {
DPRINTFN(10, ("ums_intr: x:%d y:%d z:%d buttons:0x%x\n",
dx, dy, dz, buttons));
if (dx != 0 || dy != 0 || dz != 0 || dw != 0 ||
buttons != sc->sc_buttons) {
DPRINTFN(10, ("ums_intr: x:%d y:%d z:%d w:%d buttons:0x%x\n",
dx, dy, dz, dw, buttons));
sc->sc_buttons = buttons;
if (sc->sc_wsmousedev != NULL) {
s = spltty();
wsmouse_input(sc->sc_wsmousedev, buttons, dx, dy, dz,
WSMOUSE_INPUT_DELTA);
dw, flags);
splx(s);
}
}
......@@ -351,12 +457,18 @@ ums_disable(void *v)
}
Static int
ums_ioctl(void *v, u_long cmd, caddr_t data, int flag, usb_proc_ptr p)
ums_ioctl(void *v, u_long cmd, void *data, int flag,
struct lwp * p)
{
struct ums_softc *sc = v;
switch (cmd) {
case WSMOUSEIO_GTYPE:
*(u_int *)data = WSMOUSE_TYPE_USB;
if (sc->flags & UMS_ABS)
*(u_int *)data = WSMOUSE_TYPE_TPANEL;
else
*(u_int *)data = WSMOUSE_TYPE_USB;
return (0);
}
......
......@@ -43,6 +43,9 @@
* http://www.usb.org/developers/devclass_docs/
*/
#ifdef __riscos
#include <dev/usb/usbhal.h>
#endif
#include <sys/cdefs.h>
//__KERNEL_RCSID(0, "$NetBSD: usb.c,v 1.81 2005/01/24 01:30:38 joff Exp $");
//#include "ohci.h"
......@@ -112,9 +115,9 @@ struct usb_softc {
char sc_dying;
};
#ifndef __riscos
TAILQ_HEAD(, usb_task) usb_all_tasks;
#ifndef __riscos
dev_type_open(usbopen);
dev_type_close(usbclose);
dev_type_read(usbread);
......@@ -129,6 +132,7 @@ const struct cdevsw usb_cdevsw = {
#endif
Static void usb_discover(void *);
#ifndef __riscos
Static void usb_create_event_thread(void *);
Static void usb_event_thread(void *);
Static void usb_task_thread(void *);
......@@ -145,6 +149,7 @@ Static int usb_nevents = 0;
Static struct selinfo usb_selevent;
Static usb_proc_ptr usb_async_proc; /* process that wants USB SIGIO */
Static int usb_dev_open = 0;
#endif
Static void usb_add_event(int, struct usb_event *);
Static int usb_get_next_event(struct usb_event *);
......@@ -246,20 +251,19 @@ USB_ATTACH(usb)
#ifdef __riscos
/* set the explore flag here since threads don't do anything */
sc->sc_bus->needs_explore = 1;
#endif
#else
usb_kthread_create(usb_create_event_thread, sc);
#endif
USB_ATTACH_SUCCESS_RETURN;
}
#if defined(__NetBSD__) || defined(__OpenBSD__) || defined(__riscos)
#if defined(__NetBSD__) || defined(__OpenBSD__)
void
usb_create_event_thread(void *arg)
{
struct usb_softc *sc = arg;
#ifndef __riscos
static int created = 0;
#endif
static int created = 0;
if (usb_kthread_create1(usb_event_thread, sc, &sc->sc_event_thread,
"%s", sc->sc_dev.dv_xname)) {
......@@ -267,7 +271,6 @@ usb_create_event_thread(void *arg)
sc->sc_dev.dv_xname);
panic("usb_create_event_thread");
}
#ifndef __riscos
if (!created) {
created = 1;
TAILQ_INIT(&usb_all_tasks);
......@@ -277,7 +280,6 @@ usb_create_event_thread(void *arg)
panic("usb_create_event_thread task");
}
}
#endif
}
/*
......@@ -343,22 +345,11 @@ usb_event_thread(void *arg)
#endif
usb_discover(sc);
#ifdef USB_DEBUG
#ifdef __riscos
(void)tsleep(&sc->sc_bus->needs_explore, PWAIT, "usbevt",
usb_noexplore ? 0 : hz * 60, 1);
#else
(void)tsleep(&sc->sc_bus->needs_explore, PWAIT, "usbevt",
usb_noexplore ? 0 : hz * 60);
#endif
#else
#ifdef __riscos
(void)tsleep(&sc->sc_bus->needs_explore, PWAIT, "usbevt",
hz * 60, 1);
#else
(void)tsleep(&sc->sc_bus->needs_explore, PWAIT, "usbevt",
hz * 60);
#endif
#endif
DPRINTFN(2,("usb_event_thread: woke up\n"));
}
......@@ -383,11 +374,7 @@ usb_task_thread(void *arg)
for (;;) {
task = TAILQ_FIRST(&usb_all_tasks);
if (task == NULL) {
#ifdef __riscos
tsleep(&usb_all_tasks, PWAIT, "usbtsk", 0, 1);
#else
tsleep(&usb_all_tasks, PWAIT, "usbtsk", 0);
#endif
task = TAILQ_FIRST(&usb_all_tasks);
}
DPRINTFN(2,("usb_task_thread: woke up task=%p\n", task));
......@@ -410,8 +397,33 @@ usbctlprint(void *aux, const char *pnp)
return (UNCONF);
}
#endif /* defined(__NetBSD__) || defined(__OpenBSD__) */
#elif defined(__riscos)
/* Dummy versions for RISC OS
TODO - Check that nothing relies on the task/event code working */
void usb_create_event_thread(void *arg)
{
}
void usb_add_task(usbd_device_handle dev, struct usb_task *task)
{
}
void usb_rem_task(usbd_device_handle dev, struct usb_task *task)
{
}
int
usbctlprint(void *aux, const char *pnp)
{
/* only "usb"es can attach to host controllers */
if (pnp)
logprintf("usb at %s", pnp);
return (UNCONF);
}
#endif
#ifndef __riscos
int
usbopen(dev_t dev, int flag, int mode, usb_proc_ptr p)
{
......@@ -483,6 +495,7 @@ usbclose(dev_t dev, int flag, int mode, usb_proc_ptr p)
return (0);
}
#endif
int
usbioctl(dev_t devt, u_long cmd, caddr_t data, int flag, usb_proc_ptr p)
......@@ -497,10 +510,12 @@ usbioctl(dev_t devt, u_long cmd, caddr_t data, int flag, usb_proc_ptr p)
return (0);
case FIOASYNC:
#ifndef __riscos
if (*(int *)data)
usb_async_proc = p;
else
usb_async_proc = 0;
#endif
return (0);
default:
......@@ -618,6 +633,7 @@ usbioctl(dev_t devt, u_long cmd, caddr_t data, int flag, usb_proc_ptr p)
return (0);
}
#ifndef __riscos
int
usbpoll(dev_t dev, int events, usb_proc_ptr p)
{
......@@ -640,7 +656,6 @@ usbpoll(dev_t dev, int events, usb_proc_ptr p)
}
}
#ifndef __riscos
static void
filt_usbrdetach(struct knote *kn)
{
......@@ -743,6 +758,7 @@ usb_needs_reattach(usbd_device_handle dev)
wakeup(&dev->bus->needs_explore);
}
#ifndef __riscos
/* Called at splusb() */
int
usb_get_next_event(struct usb_event *ue)
......@@ -816,6 +832,23 @@ usb_add_event(int type, struct usb_event *uep)
psignal(usb_async_proc, SIGIO);
splx(s);
}
#else
/* The event stuff has never done anything (useful) under RISC OS */
void
usbd_add_dev_event(int type, usbd_device_handle udev)
{
}
void
usbd_add_drv_event(int type, usbd_device_handle udev, device_ptr_t dev)
{
}
void
usb_add_event(int type, struct usb_event *uep)
{
}
#endif
void
usb_schedsoftintr(usbd_bus_handle bus)
......@@ -905,3 +938,11 @@ usb_detach(device_ptr_t self, int flags)
return (0);
}
#ifdef USBHAL
struct usbd_bus *usb_getbus(device_ptr_t self)
{
struct usb_softc *sc = (struct usb_softc *)self;
return sc->sc_bus;
}
#endif
/* $NetBSD: usb_quirks.c,v 1.52 2005/03/02 11:37:27 mycroft Exp $ */
/* $FreeBSD: src/sys/dev/usb/usb_quirks.c,v 1.30 2003/01/02 04:15:55 imp Exp $ */
/* $NetBSD: usb_quirks.c,v 1.67 2010/06/27 10:41:26 kardel Exp $ */
/* $FreeBSD: src/sys/dev/usb/usb_quirks.c,v 1.30 2003/01/02 04:15:55 imp Exp $ */
/*
* Copyright (c) 1998, 2004 The NetBSD Foundation, Inc.
......@@ -38,8 +38,13 @@
* POSSIBILITY OF SUCH DAMAGE.
*/
#ifdef __riscos
#include <dev/usb/usbhal.h>
#endif
#include <sys/cdefs.h>
//__KERNEL_RCSID(0, "$NetBSD: usb_quirks.c,v 1.52 2005/03/02 11:37:27 mycroft Exp $");
#ifndef __riscos
__KERNEL_RCSID(0, "$NetBSD: usb_quirks.c,v 1.67 2010/06/27 10:41:26 kardel Exp $");
#endif
#include <sys/param.h>
#include <sys/systm.h>
......@@ -56,6 +61,18 @@ extern int usbdebug;
#define ANY 0xffff
Static const struct usbd_quirk_entry usb_quirks[] = {
/* Devices which should be ignored by uhid */
{ USB_VENDOR_APC, USB_PRODUCT_APC_UPS, ANY, { UQ_HID_IGNORE }},
{ USB_VENDOR_CYBERPOWER, USB_PRODUCT_CYBERPOWER_UPS, ANY, { UQ_HID_IGNORE }},
{ USB_VENDOR_MGE, USB_PRODUCT_MGE_UPS1, ANY, { UQ_HID_IGNORE }},
{ USB_VENDOR_MGE, USB_PRODUCT_MGE_UPS2, ANY, { UQ_HID_IGNORE }},
{ USB_VENDOR_MICROCHIP, USB_PRODUCT_MICROCHIP_PICKIT1,
ANY, { UQ_HID_IGNORE }},
{ USB_VENDOR_TRIPPLITE2, USB_PRODUCT_TRIPPLITE2_UPS,
ANY, { UQ_HID_IGNORE }},
{ USB_VENDOR_METAGEEK, USB_PRODUCT_METAGEEK_WISPY_24X, ANY, { UQ_HID_IGNORE }},
{ USB_VENDOR_KYE, USB_PRODUCT_KYE_NICHE, 0x100, { UQ_NO_SET_PROTO}},
{ USB_VENDOR_INSIDEOUT, USB_PRODUCT_INSIDEOUT_EDGEPORT4,
0x094, { UQ_SWAP_UNICODE}},
......@@ -69,22 +86,27 @@ Static const struct usbd_quirk_entry usb_quirks[] = {
{ USB_VENDOR_ALTEC, USB_PRODUCT_ALTEC_ASC495, 0x000, { UQ_BAD_AUDIO }},
{ USB_VENDOR_SONY, USB_PRODUCT_SONY_PS2EYETOY4, 0x000, { UQ_BAD_AUDIO }},
{ USB_VENDOR_SONY, USB_PRODUCT_SONY_PS2EYETOY5, 0x000, { UQ_BAD_AUDIO }},
{ USB_VENDOR_PHILIPS, USB_PRODUCT_PHILIPS_PCVC740K, ANY, { UQ_BAD_AUDIO }},
{ USB_VENDOR_LOGITECH, USB_PRODUCT_LOGITECH_QUICKCAMPRONB,
0x000, { UQ_BAD_AUDIO }},
0x000, { UQ_BAD_AUDIO }},
{ USB_VENDOR_LOGITECH, USB_PRODUCT_LOGITECH_QUICKCAMPRO4K,
0x000, { UQ_BAD_AUDIO }},
0x000, { UQ_BAD_AUDIO }},
{ USB_VENDOR_LOGITECH, USB_PRODUCT_LOGITECH_QUICKCAMMESS,
0x100, { UQ_BAD_ADC }},
{ USB_VENDOR_QTRONIX, USB_PRODUCT_QTRONIX_980N, 0x110, { UQ_SPUR_BUT_UP }},
{ USB_VENDOR_ALCOR2, USB_PRODUCT_ALCOR2_KBD_HUB, 0x001, { UQ_SPUR_BUT_UP }},
{ USB_VENDOR_MCT, USB_PRODUCT_MCT_HUB0100, 0x102, { UQ_BUS_POWERED }},
{ USB_VENDOR_MCT, USB_PRODUCT_MCT_USB232, 0x102, { UQ_BUS_POWERED }},
{ USB_VENDOR_METRICOM, USB_PRODUCT_METRICOM_RICOCHET_GS,
0x100, { UQ_ASSUME_CM_OVER_DATA }},
0x100, { UQ_ASSUME_CM_OVER_DATA }},
{ USB_VENDOR_SANYO, USB_PRODUCT_SANYO_SCP4900,
0x000, { UQ_ASSUME_CM_OVER_DATA }},
0x000, { UQ_ASSUME_CM_OVER_DATA }},
{ USB_VENDOR_MOTOROLA2, USB_PRODUCT_MOTOROLA2_T720C,
0x001, { UQ_ASSUME_CM_OVER_DATA }},
0x001, { UQ_ASSUME_CM_OVER_DATA }},
{ USB_VENDOR_EICON, USB_PRODUCT_EICON_DIVA852,
0x100, { UQ_ASSUME_CM_OVER_DATA }},
{ USB_VENDOR_SIEMENS2, USB_PRODUCT_SIEMENS2_MC75,
0x000, { UQ_ASSUME_CM_OVER_DATA }},
{ USB_VENDOR_TI, USB_PRODUCT_TI_UTUSB41, 0x110, { UQ_POWER_CLAIM }},
/* JB added */
{ USB_VENDOR_NEC, USB_PRODUCT_NEC2_HUB2_0, 0x100, { UQ_POWER_CLAIM }},
......@@ -94,32 +116,50 @@ Static const struct usbd_quirk_entry usb_quirks[] = {
{ USB_VENDOR_SILICONPORTALS, USB_PRODUCT_SILICONPORTALS_YAPPHONE,
0x100, { UQ_AU_INP_ASYNC }},
{ USB_VENDOR_AVANCELOGIC, USB_PRODUCT_AVANCELOGIC_USBAUDIO,
0x101, { UQ_AU_INP_ASYNC }},
0x101, { UQ_AU_INP_ASYNC }},
{ USB_VENDOR_PLANTRONICS, USB_PRODUCT_PLANTRONICS_HEADSET,
0x004, { UQ_AU_INP_ASYNC }},
0x004, { UQ_AU_INP_ASYNC }},
/* XXX These should have a revision number, but I don't know what they are. */
{ USB_VENDOR_HP, USB_PRODUCT_HP_895C, ANY, { UQ_BROKEN_BIDIR }},
{ USB_VENDOR_HP, USB_PRODUCT_HP_880C, ANY, { UQ_BROKEN_BIDIR }},
{ USB_VENDOR_HP, USB_PRODUCT_HP_815C, ANY, { UQ_BROKEN_BIDIR }},
{ USB_VENDOR_HP, USB_PRODUCT_HP_810C, ANY, { UQ_BROKEN_BIDIR }},
{ USB_VENDOR_HP, USB_PRODUCT_HP_830C, ANY, { UQ_BROKEN_BIDIR }},
{ USB_VENDOR_HP, USB_PRODUCT_HP_885C, ANY, { UQ_BROKEN_BIDIR }},
{ USB_VENDOR_HP, USB_PRODUCT_HP_840C, ANY, { UQ_BROKEN_BIDIR }},
{ USB_VENDOR_HP, USB_PRODUCT_HP_816C, ANY, { UQ_BROKEN_BIDIR }},
{ USB_VENDOR_HP, USB_PRODUCT_HP_959C, ANY, { UQ_BROKEN_BIDIR }},
{ USB_VENDOR_NEC, USB_PRODUCT_NEC_PICTY900, ANY, { UQ_BROKEN_BIDIR }},
{ USB_VENDOR_NEC, USB_PRODUCT_NEC_PICTY760, ANY, { UQ_BROKEN_BIDIR }},
{ USB_VENDOR_NEC, USB_PRODUCT_NEC_PICTY920, ANY, { UQ_BROKEN_BIDIR }},
{ USB_VENDOR_NEC, USB_PRODUCT_NEC_PICTY800, ANY, { UQ_BROKEN_BIDIR }},
{ USB_VENDOR_HP, USB_PRODUCT_HP_1220C, ANY, { UQ_BROKEN_BIDIR }},
{ USB_VENDOR_HP, USB_PRODUCT_HP_885C, ANY, { UQ_BROKEN_BIDIR }},
{ USB_VENDOR_HP, USB_PRODUCT_HP_840C, ANY, { UQ_BROKEN_BIDIR }},
{ USB_VENDOR_HP, USB_PRODUCT_HP_816C, ANY, { UQ_BROKEN_BIDIR }},
{ USB_VENDOR_HP, USB_PRODUCT_HP_959C, ANY, { UQ_BROKEN_BIDIR }},
{ USB_VENDOR_MTK, USB_PRODUCT_MTK_GPS_RECEIVER, ANY, { UQ_NO_UNION_NRM }},
{ USB_VENDOR_NEC, USB_PRODUCT_NEC_PICTY900, ANY, { UQ_BROKEN_BIDIR }},
{ USB_VENDOR_NEC, USB_PRODUCT_NEC_PICTY760, ANY, { UQ_BROKEN_BIDIR }},
{ USB_VENDOR_NEC, USB_PRODUCT_NEC_PICTY920, ANY, { UQ_BROKEN_BIDIR }},
{ USB_VENDOR_NEC, USB_PRODUCT_NEC_PICTY800, ANY, { UQ_BROKEN_BIDIR }},
{ USB_VENDOR_HP, USB_PRODUCT_HP_1220C, ANY, { UQ_BROKEN_BIDIR }},
/* HID and audio are both invalid on iPhone/iPod Touch */
{ USB_VENDOR_APPLE, USB_PRODUCT_APPLE_IPHONE,
ANY, { UQ_HID_IGNORE | UQ_BAD_AUDIO }},
{ USB_VENDOR_APPLE, USB_PRODUCT_APPLE_IPOD_TOUCH,
ANY, { UQ_HID_IGNORE | UQ_BAD_AUDIO }},
{ USB_VENDOR_APPLE, USB_PRODUCT_APPLE_IPHONE_3G,
ANY, { UQ_HID_IGNORE | UQ_BAD_AUDIO }},
{ USB_VENDOR_APPLE, USB_PRODUCT_APPLE_IPHONE_3GS,
ANY, { UQ_HID_IGNORE | UQ_BAD_AUDIO }},
{ USB_VENDOR_QUALCOMM, USB_PRODUCT_QUALCOMM_CDMA_MSM,
ANY, { UQ_ASSUME_CM_OVER_DATA }},
{ USB_VENDOR_QUALCOMM2, USB_PRODUCT_QUALCOMM2_CDMA_MSM,
ANY, { UQ_ASSUME_CM_OVER_DATA }},
{ USB_VENDOR_HYUNDAI, USB_PRODUCT_HYUNDAI_UM175,
ANY, { UQ_ASSUME_CM_OVER_DATA }},
/* JB added */
{ USB_VENDOR_OLYMPUS, USB_PRODUCT_OLYMPUS_C700, ANY, { UQ_BUS_POWERED }},
{ 0, 0, 0, { 0 } }
};
const struct usbd_quirks usbd_no_quirk = { 0 };
#ifdef __riscos
#if defined(__riscos) && !defined(USBHAL)
void * extra_quirks;
const struct usbd_quirks * usbd_find_quirk(usb_device_descriptor_t *d)
......@@ -132,7 +172,7 @@ const struct usbd_quirks * usbd_find_quirk(usb_device_descriptor_t *d)
#endif
const struct usbd_quirks *
#ifdef __riscos
#if defined(__riscos) && !defined(USBHAL)
usbd_find_builtin_quirk(usb_device_descriptor_t *d,const struct usbd_quirk_entry *t)
{
if(!t) t = usb_quirks;
......@@ -145,7 +185,7 @@ usbd_find_quirk(usb_device_descriptor_t *d)
u_int16_t product = UGETW(d->idProduct);
u_int16_t revision = UGETW(d->bcdDevice);
#ifdef __riscos
#if defined(__riscos) && !defined(USBHAL)
for (; t->idVendor != 0; t++) {
#else
for (t = usb_quirks; t->idVendor != 0; t++) {
......
......@@ -38,6 +38,9 @@
* POSSIBILITY OF SUCH DAMAGE.
*/
#ifdef __riscos
#include <dev/usb/usbhal.h>
#endif
#include <sys/cdefs.h>
//__KERNEL_RCSID(0, "$NetBSD: usb_subr.c,v 1.122 2005/03/04 05:03:19 mycroft Exp $");
......@@ -107,7 +110,9 @@ Static void usbd_kill_pipe(usbd_pipe_handle);
Static usbd_status usbd_probe_and_attach(device_ptr_t parent,
usbd_device_handle dev, int port, int addr);
#ifndef __riscos
Static u_int32_t usb_cookie_no = 0;
#endif
#ifdef USBVERBOSE
typedef u_int16_t usb_vendor_id_t;
......@@ -129,6 +134,7 @@ struct usb_product {
#include <dev/usb/usbdevs_data.h>
#endif /* USBVERBOSE */
#ifndef USBHAL
Static const char * const usbd_error_strs[] = {
"NORMAL_COMPLETION",
"IN_PROGRESS",
......@@ -164,6 +170,14 @@ usbd_errstr(usbd_status err)
return buffer;
}
}
#else
const char *
usbd_errstr(usbd_status err)
{
/* TODO - Make a suitable version for debug HAL builds */
return "XXX";
}
#endif
usbd_status
usbd_get_string_desc(usbd_device_handle dev, int sindex, int langid,
......@@ -286,23 +300,15 @@ usbd_devinfo_vp(usbd_device_handle dev, char *v, size_t lv, char *p, size_t lp,
}
if (usedev) {
#ifndef __riscos
if (usbd_get_string(dev, udd->iManufacturer, v))
vendor = NULL;
else
vendor = v;
#else
vendor = usbd_get_string(dev, udd->iManufacturer, v);
#endif
usbd_trim_spaces(vendor);
#ifndef __riscos
if (usbd_get_string(dev, udd->iProduct, p))
product = NULL;
else
product = p;
#else
product = usbd_get_string(dev, udd->iProduct, p);
#endif
usbd_trim_spaces(product);
if (vendor && !*vendor)
vendor = NULL;
......@@ -342,6 +348,7 @@ usbd_printBCD(char *cp, size_t l, int bcd)
return (snprintf(cp, l, "%x.%02x", bcd >> 8, bcd & 0xff));
}
#if !defined(__riscos) || defined(USB_DEBUG)
void
usbd_devinfo(usbd_device_handle dev, int showclass, char *cp, size_t l)
{
......@@ -368,6 +375,7 @@ usbd_devinfo(usbd_device_handle dev, int showclass, char *cp, size_t l)
cp += snprintf(cp, ep - cp, ", addr %d", dev->address);
*cp = 0;
}
#endif
/* Delay for a certain number of ms */
void
......@@ -1161,7 +1169,9 @@ usbd_new_device(device_ptr_t parent, usbd_bus_handle bus, int depth,
}
dev->speed = speed;
dev->langid = USBD_NOLANG;
#ifndef __riscos
dev->cookie.cookie = ++usb_cookie_no;
#endif
/* Establish the default pipe. */
err = usbd_setup_pipe(dev, 0, &dev->def_ep, USBD_DEFAULT_INTERVAL,
......@@ -1457,7 +1467,7 @@ void
usb_free_device(usbd_device_handle dev)
{
int ifcidx, nifc;
#ifdef __riscos
#if defined(__riscos) && !defined(USBHAL)
if(dev->dv_unit)kill_system_variable(dev->dv_unit);
#endif
if (dev->default_pipe != NULL)
......
......@@ -38,6 +38,9 @@
* POSSIBILITY OF SUCH DAMAGE.
*/
#ifdef __riscos
#include <dev/usb/usbhal.h>
#endif
#include <sys/cdefs.h>
//__KERNEL_RCSID(0, "$NetBSD: usbdi.c,v 1.106 2004/10/24 12:52:40 augustss Exp $");
......@@ -91,6 +94,7 @@ Static void usbd_start_next(usbd_pipe_handle pipe);
Static usbd_status usbd_open_pipe_ival
(usbd_interface_handle, u_int8_t, u_int8_t, usbd_pipe_handle *, int);
#ifndef __riscos
Static int usbd_nbuses = 0;
void
......@@ -104,6 +108,10 @@ usbd_finish(void)
{
--usbd_nbuses;
}
#else
void usbd_init(void) {}
void usbd_finish(void) {}
#endif
static __inline int
usbd_xfer_isread(usbd_xfer_handle xfer)
......@@ -338,7 +346,7 @@ usbd_transfer(usbd_xfer_handle xfer)
/* Copy data if going out. */
if (!(xfer->flags & USBD_NO_COPY) && size != 0 &&
!usbd_xfer_isread(xfer))
#ifdef __riscos
#if defined(__riscos) && !defined(USBHAL)
{
/* the buffer pointer is actually a buffermanager private ID */
if (xfer->rqflags & URQ_RISCOS_BUF)
......@@ -346,7 +354,7 @@ usbd_transfer(usbd_xfer_handle xfer)
else
#endif
memcpy(KERNADDR(dmap, 0), xfer->buffer, size);
#ifdef __riscos
#if defined(__riscos) && !defined(USBHAL)
}
#endif
......@@ -612,7 +620,7 @@ usbd_clear_endpoint_stall(usbd_pipe_handle pipe)
usbd_device_handle dev = pipe->device;
#endif
usb_device_request_t req;
usbd_status err;
usbd_status err = USBD_NORMAL_COMPLETION;
DPRINTFN(8, ("usbd_clear_endpoint_stall\n"));
......@@ -910,7 +918,7 @@ usb_transfer_complete(usbd_xfer_handle xfer)
xfer->actlen = xfer->length;
}
#endif
#ifdef __riscos
#if defined(__riscos) && !defined(USBHAL)
/* the buffer pointer is actually a buffermanager private ID,
but this is sorted out in the code */
if (xfer->rqflags & URQ_RISCOS_BUF)
......
......@@ -37,6 +37,9 @@
* POSSIBILITY OF SUCH DAMAGE.
*/
#ifdef __riscos
#include <dev/usb/usbhal.h>
#endif
#include <sys/cdefs.h>
//__KERNEL_RCSID(0, "$NetBSD: usbdi_util.c,v 1.43 2005/04/12 13:10:14 itohy Exp $");
......
/* $NetBSD: usbroothub_subr.c,v 1.1 2008/02/03 10:57:13 drochner Exp $ */
/*
* Copyright (c) 2008
* Matthias Drochner. All rights reserved.
*
* Redistribution and use in source and binary forms, with or without
* modification, are permitted provided that the following conditions
* are met:
* 1. Redistributions of source code must retain the above copyright
* notice, this list of conditions and the following disclaimer.
* 2. Redistributions in binary form must reproduce the above copyright
* notice, this list of conditions and the following disclaimer in the
* documentation and/or other materials provided with the distribution.
*
* THIS SOFTWARE IS PROVIDED BY THE AUTHOR ``AS IS'' AND ANY EXPRESS OR
* IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES
* OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED.
* IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY DIRECT, INDIRECT,
* INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT
* NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE,
* DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY
* THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
* (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF
* THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
*
*/
#ifdef __riscos
#include <dev/usb/usbhal.h>
#endif
#include <dev/usb/usb.h>
#include <dev/usb/usbroothub_subr.h>
/* helper functions for USB root hub emulation */
int
usb_makestrdesc(usb_string_descriptor_t *p, int l, const char *s)
{
int i;
if (l == 0)
return (0);
p->bLength = 2 * strlen(s) + 2;
if (l == 1)
return (1);
p->bDescriptorType = UDESC_STRING;
l -= 2;
/* poor man's utf-16le conversion */
for (i = 0; s[i] && l > 1; i++, l -= 2)
USETW2(p->bString[i], 0, s[i]);
return (2 * i + 2);
}
int
usb_makelangtbl(usb_string_descriptor_t *p, int l)
{
if (l == 0)
return (0);
p->bLength = 4;
if (l == 1)
return (1);
p->bDescriptorType = UDESC_STRING;
if (l < 4)
return (2);
USETW(p->bString[0], 0x0409); /* english/US */
return (4);
}
#! /usr/bin/awk -f
# $NetBSD: devlist2h.awk,v 1.13 2005/03/04 05:03:19 mycroft Exp $
# $NetBSD: devlist2h.awk,v 1.14 2005/12/11 12:24:00 christos Exp $
#
# RISC OS version JB 20041213
#
......@@ -40,7 +40,7 @@ BEGIN {
}else{
dfile="usbdevs_data.h"
hfile="usbdevs.h"
}
}
}
NR == 1 {
VERSION = $0
......
/* $NetBSD: ehcireg.h,v 1.20 2005/03/02 11:37:27 mycroft Exp $ */
/* $NetBSD: ehcireg.h,v 1.31 2010/06/02 18:53:39 jakllsch Exp $ */
/*
* Copyright (c) 2001, 2004 The NetBSD Foundation, Inc.
......@@ -15,13 +15,6 @@
* 2. Redistributions in binary form must reproduce the above copyright
* notice, this list of conditions and the following disclaimer in the
* documentation and/or other materials provided with the distribution.
* 3. All advertising materials mentioning features or use of this software
* must display the following acknowledgement:
* This product includes software developed by the NetBSD
* Foundation, Inc. and its contributors.
* 4. Neither the name of The NetBSD Foundation nor the names of its
* contributors may be used to endorse or promote products derived
* from this software without specific prior written permission.
*
* THIS SOFTWARE IS PROVIDED BY THE NETBSD FOUNDATION, INC. AND CONTRIBUTORS
* ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED
......@@ -63,9 +56,18 @@
#define PCI_EHCI_PORTWAKECAP 0x62 /* RW Port wake caps (opt) */
/* Regs ar EECP + offset */
/* Regs at EECP + offset */
#define PCI_EHCI_USBLEGSUP 0x00
#define EHCI_LEG_HC_OS_OWNED 0x01000000
#define EHCI_LEG_HC_BIOS_OWNED 0x00010000
#define PCI_EHCI_USBLEGCTLSTS 0x04
#define EHCI_LEG_EXT_SMI_BAR 0x80000000
#define EHCI_LEG_EXT_SMI_PCICMD 0x40000000
#define EHCI_LEG_EXT_SMI_OS_CHANGE 0x20000000
#define EHCI_CAP_GET_ID(cap) ((cap) & 0xff)
#define EHCI_CAP_GET_NEXT(cap) (((cap) >> 8) & 0xff)
#define EHCI_CAP_ID_LEGACY 1
/*** EHCI capability registers ***/
......@@ -168,6 +170,7 @@
#define EHCI_PORT_RESET_COMPLETE 2 /* ms */
#define EHCI_FLALIGN_ALIGN 0x1000
#define EHCI_MAX_PORTS 16 /* only 4 bits available in EHCI_HCS_N_PORTS */
/* No data structure may cross a page boundary. */
#define EHCI_PAGE_SIZE 0x1000
......@@ -185,16 +188,50 @@ typedef u_int32_t ehci_link_t;
typedef u_int32_t ehci_physaddr_t;
typedef u_int32_t ehci_isoc_trans_t;
typedef u_int32_t ehci_isoc_bufr_ptr_t;
/* Isochronous Transfer Descriptor */
#define EHCI_ITD_NUFRAMES USB_UFRAMES_PER_FRAME
#define EHCI_ITD_NBUFFERS 7
typedef struct {
ehci_link_t itd_next;
/* XXX many more */
volatile ehci_link_t itd_next;
volatile ehci_isoc_trans_t itd_ctl[EHCI_ITD_NUFRAMES];
#define EHCI_ITD_GET_STATUS(x) (((x) >> 28) & 0xf)
#define EHCI_ITD_SET_STATUS(x) (((x) & 0xf) << 28)
#define EHCI_ITD_ACTIVE 0x80000000
#define EHCI_ITD_BUF_ERR 0x40000000
#define EHCI_ITD_BABBLE 0x20000000
#define EHCI_ITD_ERROR 0x10000000
#define EHCI_ITD_GET_LEN(x) (((x) >> 16) & 0xfff)
#define EHCI_ITD_SET_LEN(x) (((x) & 0xfff) << 16)
#define EHCI_ITD_IOC 0x8000
#define EHCI_ITD_GET_IOC(x) (((x) >> 15) & 1)
#define EHCI_ITD_SET_IOC(x) (((x) << 15) & EHCI_ITD_IOC)
#define EHCI_ITD_GET_PG(x) (((x) >> 12) & 0x7)
#define EHCI_ITD_SET_PG(x) (((x) & 0x7) << 12)
#define EHCI_ITD_GET_OFFS(x) (((x) >> 0) & 0xfff)
#define EHCI_ITD_SET_OFFS(x) (((x) & 0xfff) << 0)
volatile ehci_isoc_bufr_ptr_t itd_bufr[EHCI_ITD_NBUFFERS];
#define EHCI_ITD_GET_BPTR(x) ((x) & 0xfffff000)
#define EHCI_ITD_SET_BPTR(x) ((x) & 0xfffff000)
#define EHCI_ITD_GET_EP(x) (((x) >> 8) & 0xf)
#define EHCI_ITD_SET_EP(x) (((x) & 0xf) << 8)
#define EHCI_ITD_GET_DADDR(x) ((x) & 0x7f)
#define EHCI_ITD_SET_DADDR(x) ((x) & 0x7f)
#define EHCI_ITD_GET_DIR(x) (((x) >> 11) & 1)
#define EHCI_ITD_SET_DIR(x) (((x) & 1) << 11)
#define EHCI_ITD_GET_MAXPKT(x) ((x) & 0x7ff)
#define EHCI_ITD_SET_MAXPKT(x) ((x) & 0x7ff)
#define EHCI_ITD_GET_MULTI(x) ((x) & 0x3)
#define EHCI_ITD_SET_MULTI(x) ((x) & 0x3)
volatile ehci_isoc_bufr_ptr_t itd_bufr_hi[EHCI_ITD_NBUFFERS];
} ehci_itd_t;
#define EHCI_ITD_ALIGN 32
/* Split Transaction Isochronous Transfer Descriptor */
typedef struct {
ehci_link_t sitd_next;
volatile ehci_link_t sitd_next;
/* XXX many more */
} ehci_sitd_t;
#define EHCI_SITD_ALIGN 32
......@@ -202,11 +239,11 @@ typedef struct {
/* Queue Element Transfer Descriptor */
#define EHCI_QTD_NBUFFERS 5
typedef struct {
ehci_link_t qtd_next;
ehci_link_t qtd_altnext;
u_int32_t qtd_status;
volatile ehci_link_t qtd_next;
volatile ehci_link_t qtd_altnext;
volatile u_int32_t qtd_status;
#define EHCI_QTD_GET_STATUS(x) (((x) >> 0) & 0xff)
#define EHCI_QTD_SET_STATUS(x) ((x) << 0)
#define EHCI_QTD_SET_STATUS(x) ((x) << 0)
#define EHCI_QTD_ACTIVE 0x80
#define EHCI_QTD_HALTED 0x40
#define EHCI_QTD_BUFERR 0x20
......@@ -215,7 +252,7 @@ typedef struct {
#define EHCI_QTD_MISSEDMICRO 0x04
#define EHCI_QTD_SPLITXSTATE 0x02
#define EHCI_QTD_PINGSTATE 0x01
#define EHCI_QTD_STATERRS 0x7c
#define EHCI_QTD_STATERRS 0x3c
#define EHCI_QTD_GET_PID(x) (((x) >> 8) & 0x3)
#define EHCI_QTD_SET_PID(x) ((x) << 8)
#define EHCI_QTD_PID_OUT 0x0
......@@ -230,17 +267,17 @@ typedef struct {
#define EHCI_QTD_GET_BYTES(x) (((x) >> 16) & 0x7fff)
#define EHCI_QTD_SET_BYTES(x) ((x) << 16)
#define EHCI_QTD_GET_TOGGLE(x) (((x) >> 31) & 0x1)
#define EHCI_QTD_SET_TOGGLE(x) ((x) << 31)
#define EHCI_QTD_TOGGLE_MASK 0x80000000
ehci_physaddr_t qtd_buffer[EHCI_QTD_NBUFFERS];
ehci_physaddr_t qtd_buffer_hi[EHCI_QTD_NBUFFERS];
#define EHCI_QTD_SET_TOGGLE(x) ((x) << 31)
#define EHCI_QTD_TOGGLE_MASK 0x80000000
volatile ehci_physaddr_t qtd_buffer[EHCI_QTD_NBUFFERS];
volatile ehci_physaddr_t qtd_buffer_hi[EHCI_QTD_NBUFFERS];
} ehci_qtd_t;
#define EHCI_QTD_ALIGN 32
/* Queue Head */
typedef struct {
ehci_link_t qh_link;
u_int32_t qh_endp;
volatile ehci_link_t qh_link;
volatile u_int32_t qh_endp;
#define EHCI_QH_GET_ADDR(x) (((x) >> 0) & 0x7f) /* endpoint addr */
#define EHCI_QH_SET_ADDR(x) (x)
#define EHCI_QH_ADDRMASK 0x0000007f
......@@ -259,12 +296,12 @@ typedef struct {
#define EHCI_QH_HRECL 0x00008000
#define EHCI_QH_GET_MPL(x) (((x) >> 16) & 0x7ff) /* max packet len */
#define EHCI_QH_SET_MPL(x) ((x) << 16)
#define EHCI_QH_MPLMASK 0x07ff0000
#define EHCI_QH_GET_CTL(x) (((x) >> 27) & 0x01) /* control endpoint */
#define EHCI_QH_MPLMASK 0x07ff0000
#define EHCI_QH_GET_CTL(x) (((x) >> 27) & 0x01) /* control endpoint */
#define EHCI_QH_CTL 0x08000000
#define EHCI_QH_GET_NRL(x) (((x) >> 28) & 0x0f) /* NAK reload */
#define EHCI_QH_SET_NRL(x) ((x) << 28)
u_int32_t qh_endphub;
volatile u_int32_t qh_endphub;
#define EHCI_QH_GET_SMASK(x) (((x) >> 0) & 0xff) /* intr sched mask */
#define EHCI_QH_SET_SMASK(x) ((x) << 0)
#define EHCI_QH_GET_CMASK(x) (((x) >> 8) & 0xff) /* split completion mask */
......@@ -275,16 +312,47 @@ typedef struct {
#define EHCI_QH_SET_PORT(x) ((x) << 23)
#define EHCI_QH_GET_MULT(x) (((x) >> 30) & 0x03) /* pipe multiplier */
#define EHCI_QH_SET_MULT(x) ((x) << 30)
ehci_link_t qh_curqtd;
ehci_qtd_t qh_qtd;
volatile ehci_link_t qh_curqtd;
ehci_qtd_t qh_qtd;
} ehci_qh_t;
#define EHCI_QH_ALIGN 32
/* Periodic Frame Span Traversal Node */
typedef struct {
ehci_link_t fstn_link;
ehci_link_t fstn_back;
volatile ehci_link_t fstn_link;
volatile ehci_link_t fstn_back;
} ehci_fstn_t;
#define EHCI_FSTN_ALIGN 32
/* Debug Port */
#define PCI_CAP_DEBUGPORT_OFFSET __BITS(28,16)
#define PCI_CAP_DEBUGPORT_BAR __BITS(31,29)
/* Debug Port Registers, offset into DEBUGPORT_BAR at DEBUGPORT_OFFSET */
#define EHCI_DEBUG_SC 0x00
/* Status/Control Register */
#define EHCI_DSC_DATA_LENGTH __BITS(3,0)
#define EHCI_DSC_WRITE __BIT(4)
#define EHCI_DSC_GO __BIT(5)
#define EHCI_DSC_ERROR __BIT(6)
#define EHCI_DSC_EXCEPTION __BITS(9,7)
#define EHCI_DSC_EXCEPTION_NONE 0
#define EHCI_DSC_EXCEPTION_XACT 1
#define EHCI_DSC_EXCEPTION_HW 2
#define EHCI_DSC_IN_USE __BIT(10)
#define EHCI_DSC_DONE __BIT(16)
#define EHCI_DSC_ENABLED __BIT(28)
#define EHCI_DSC_OWNER __BIT(30)
#define EHCI_DEBUG_UPR 0x04
/* USB PIDs Register */
#define EHCI_DPR_TOKEN __BITS(7,0)
#define EHCI_DPR_SEND __BITS(15,8)
#define EHCI_DPR_RECIEVED __BITS(23,16)
/* Data Registers */
#define EHCI_DEBUG_DATA0123 0x08
#define EHCI_DEBUG_DATA4567 0x0c
#define EHCI_DEBUG_DAR 0x10
/* Device Address Register */
#define EHCI_DAR_ENDPOINT __BITS(3,0)
#define EHCI_DAR_ADDRESS __BITS(14,8)
#endif /* _DEV_PCI_EHCIREG_H_ */
......@@ -36,68 +36,108 @@
* POSSIBILITY OF SUCH DAMAGE.
*/
#ifdef USBHAL
/* We have little memory available in the HAL, so allocate in smaller chunks */
#define EHCI_SMALL_PAGE_SIZE 512
#else
#define EHCI_SMALL_PAGE_SIZE EHCI_PAGE_SIZE
#endif
typedef struct ehci_soft_qtd {
ehci_qtd_t qtd;
struct ehci_soft_qtd *nextqtd; /* mirrors nextqtd in TD */
ehci_physaddr_t physaddr;
usb_dma_t dma; /* qTD's DMA infos */
int offs; /* qTD's offset in usb_dma_t */
usbd_xfer_handle xfer;
LIST_ENTRY(ehci_soft_qtd) hnext;
u_int16_t len;
} ehci_soft_qtd_t;
#define EHCI_SQTD_SIZE ((sizeof (struct ehci_soft_qtd) + EHCI_QTD_ALIGN - 1) / EHCI_QTD_ALIGN * EHCI_QTD_ALIGN)
#define EHCI_SQTD_CHUNK (EHCI_PAGE_SIZE / EHCI_SQTD_SIZE)
#define EHCI_SQTD_CHUNK (EHCI_SMALL_PAGE_SIZE / EHCI_SQTD_SIZE)
typedef struct ehci_soft_qh {
ehci_qh_t qh;
struct ehci_soft_qh *next;
struct ehci_soft_qtd *sqtd;
ehci_physaddr_t physaddr;
int islot;
usb_dma_t dma; /* QH's DMA infos */
int offs; /* QH's offset in usb_dma_t */
int islot;
} ehci_soft_qh_t;
#define EHCI_SQH_SIZE ((sizeof (struct ehci_soft_qh) + EHCI_QH_ALIGN - 1) / EHCI_QH_ALIGN * EHCI_QH_ALIGN)
#define EHCI_SQH_CHUNK (EHCI_PAGE_SIZE / EHCI_SQH_SIZE)
#define EHCI_SQH_CHUNK (EHCI_SMALL_PAGE_SIZE / EHCI_SQH_SIZE)
typedef struct ehci_soft_itd {
ehci_itd_t itd;
union {
struct {
/* soft_itds links in a periodic frame*/
struct ehci_soft_itd *next;
struct ehci_soft_itd *prev;
} frame_list;
/* circular list of free itds */
LIST_ENTRY(ehci_soft_itd) free_list;
} u;
struct ehci_soft_itd *xfer_next; /* Next soft_itd in xfer */
ehci_physaddr_t physaddr;
usb_dma_t dma;
int offs;
int slot;
struct timeval t; /* store free time */
} ehci_soft_itd_t;
#define EHCI_ITD_SIZE ((sizeof(struct ehci_soft_itd) + EHCI_QH_ALIGN - 1) / EHCI_ITD_ALIGN * EHCI_ITD_ALIGN)
#define EHCI_ITD_CHUNK (EHCI_SMALL_PAGE_SIZE / EHCI_ITD_SIZE)
struct ehci_xfer {
struct usbd_xfer xfer;
struct usb_task abort_task;
LIST_ENTRY(ehci_xfer) inext; /* list of active xfers */
TAILQ_ENTRY(ehci_xfer) inext; /* list of active xfers */
ehci_soft_qtd_t *sqtdstart;
ehci_soft_qtd_t *sqtdend;
#ifdef DIAGNOSTIC
int isdone;
#endif
ehci_soft_itd_t *itdstart;
ehci_soft_itd_t *itdend;
u_int isoc_len;
int isdone; /* used only when DIAGNOSTIC is defined */
};
#define EXFER(xfer) ((struct ehci_xfer *)(xfer))
/* Information about an entry in the interrupt list. */
struct ehci_soft_islot {
ehci_soft_qh_t *sqh; /* Queue Head. */
ehci_soft_qh_t *sqh; /* Queue Head. */
};
#define EHCI_FRAMELIST_MAXCOUNT 1024
#define EHCI_IPOLLRATES 8 /* Poll rates (1ms, 2, 4, 8 .. 128) */
#ifdef USBHAL
#define EHCI_IPOLLRATES 3 /* Full poll list uses too much memory for HAL. See if this works. */
#else
#define EHCI_IPOLLRATES 8 /* Poll rates (1ms, 2, 4, 8 .. 128) */
#endif
#define EHCI_INTRQHS ((1 << EHCI_IPOLLRATES) - 1)
#define EHCI_IQHIDX(lev, pos) \
((((pos) & ((1 << (lev)) - 1)) | (1 << (lev))) - 1)
#define EHCI_MAX_POLLRATE (1 << (EHCI_IPOLLRATES - 1))
#define EHCI_IQHIDX(lev, pos) \
((((pos) & ((1 << (lev)) - 1)) | (1 << (lev))) - 1)
#define EHCI_ILEV_IVAL(lev) (1 << (lev))
#define EHCI_HASH_SIZE 128
#define EHCI_COMPANION_MAX 8
#define EHCI_FREE_LIST_INTERVAL 100
typedef struct ehci_softc {
struct usbd_bus sc_bus; /* base device */
bus_space_tag_t iot;
bus_space_handle_t ioh;
bus_size_t sc_size;
u_int sc_offs; /* offset to operational regs */
int sc_flags; /* misc flags */
#define EHCIF_DROPPED_INTR_WORKAROUND 0x01
char sc_vendor[16]; /* vendor string for root hub */
char sc_vendor[32]; /* vendor string for root hub */
int sc_id_vendor; /* vendor ID for root hub */
u_int32_t sc_cmd; /* shadow of cmd reg during suspend */
void *sc_powerhook; /* cookie from power hook */
void *sc_shutdownhook; /* cookie from shutdown hook */
u_int sc_ncomp;
u_int sc_npcomp;
......@@ -106,20 +146,28 @@ typedef struct ehci_softc {
usb_dma_t sc_fldma;
ehci_link_t *sc_flist;
u_int sc_flsize;
u_int sc_rand; /* XXX need proper intr scheduling */
u_int sc_rand; /* XXX need proper intr scheduling */
struct ehci_soft_islot sc_islots[EHCI_INTRQHS];
LIST_HEAD(, ehci_xfer) sc_intrhead;
/* jcmm - an array matching sc_flist, but with software pointers,
* not hardware address pointers
*/
struct ehci_soft_itd **sc_softitds;
TAILQ_HEAD(, ehci_xfer) sc_intrhead;
kmutex_t sc_intrhead_lock;
ehci_soft_qh_t *sc_freeqhs;
ehci_soft_qtd_t *sc_freeqtds;
LIST_HEAD(sc_freeitds, ehci_soft_itd) sc_freeitds;
int sc_noport;
u_int8_t sc_hasppc; /* has Port Power Control */
u_int8_t sc_addr; /* device address */
u_int8_t sc_conf; /* device configuration */
usbd_xfer_handle sc_intrxfer;
char sc_isreset;
char sc_isreset[EHCI_MAX_PORTS];
#ifdef USB_USE_SOFTINTR
char sc_softwake;
#endif /* USB_USE_SOFTINTR */
......@@ -129,16 +177,18 @@ typedef struct ehci_softc {
SIMPLEQ_HEAD(, usbd_xfer) sc_free_xfers; /* free xfers */
struct lock sc_doorbell_lock;
kmutex_t sc_doorbell_lock;
usb_callout_t sc_tmo_pcd;
struct callout sc_tmo_intrlist;
#if defined(__NetBSD__) || defined(__OpenBSD__) || defined(__riscos)
device_ptr_t sc_child; /* /dev/usb# device */
#endif
device_ptr_t sc_child; /* /dev/usb# device */
char sc_dying;
#ifdef __NetBSD__
struct usb_dma_reserve sc_dma_reserve;
struct usb_dma_reserve sc_dma_reserve;
#endif
#ifdef __riscos
int sc_irqdevno; /* IRQ device number */
#endif
} ehci_softc_t;
......@@ -162,6 +212,5 @@ int ehci_activate(device_ptr_t, enum devact);
#define MS_TO_TICKS(ms) ((ms) * hz / 1000)
#ifdef __riscos
extern void ehci_softintr(void *);
extern void ehci_shutdown(void *);
extern bool ehci_shutdown(void *);
#endif
/* $NetBSD: hid.h,v 1.8 2002/07/11 21:14:25 augustss Exp $ */
/* $NetBSD: hid.h,v 1.13 2010/05/12 18:44:49 plunky Exp $ */
/* $FreeBSD: src/sys/dev/usb/hid.h,v 1.7 1999/11/17 22:33:40 n_hibma Exp $ */
/*
......@@ -17,13 +17,6 @@
* 2. Redistributions in binary form must reproduce the above copyright
* notice, this list of conditions and the following disclaimer in the
* documentation and/or other materials provided with the distribution.
* 3. All advertising materials mentioning features or use of this software
* must display the following acknowledgement:
* This product includes software developed by the NetBSD
* Foundation, Inc. and its contributors.
* 4. Neither the name of The NetBSD Foundation nor the names of its
* contributors may be used to endorse or promote products derived
* from this software without specific prior written permission.
*
* THIS SOFTWARE IS PROVIDED BY THE NETBSD FOUNDATION, INC. AND CONTRIBUTORS
* ``AS IS'' AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED
......@@ -85,11 +78,12 @@ struct hid_item {
struct hid_item *next;
};
struct hid_data *hid_start_parse(void *d, int len, enum hid_kind kind);
void hid_end_parse(struct hid_data *s);
int hid_get_item(struct hid_data *s, struct hid_item *h);
int hid_report_size(void *buf, int len, enum hid_kind k, u_int8_t id);
int hid_locate(void *desc, int size, u_int32_t usage, u_int8_t id,
enum hid_kind kind, struct hid_location *loc, u_int32_t *flags);
u_long hid_get_data(u_char *buf, struct hid_location *loc);
int hid_is_collection(void *desc, int size, u_int8_t id, u_int32_t usage);
struct hid_data *hid_start_parse(const void *, int, enum hid_kind);
void hid_end_parse(struct hid_data *);
int hid_get_item(struct hid_data *, struct hid_item *);
int hid_report_size(const void *, int, enum hid_kind, u_int8_t);
int hid_locate(const void *, int, u_int32_t, u_int8_t, enum hid_kind,
struct hid_location *, u_int32_t *);
long hid_get_data(const u_char *, const struct hid_location *);
u_long hid_get_udata(const u_char *, const struct hid_location *);
int hid_is_collection(const void *, int, u_int8_t, u_int32_t);
......@@ -146,6 +146,10 @@ typedef struct ohci_softc {
#ifdef __NetBSD__
struct usb_dma_reserve sc_dma_reserve;
#endif
#ifdef __riscos
int sc_irqdevno; /* IRQ device number */
#endif
} ohci_softc_t;
struct ohci_xfer {
......