• Please review our updated Terms and Rules here

x86 ASM question!

Mike Chambers

Veteran Member
Joined
Sep 2, 2006
Messages
2,621
i'm writing some code in QB to play audio through the sound blaster using the auto-init DMA mode with buffering to prevent that annoying clicking sound you get using the single-cycle DMA playback mode..

problem is, there's nothing built into QB to let me trap hardware interrupts so i know when to get the next buffer segment ready for the SB'S DSP. i'll be telling the SB's DSP that the length of the audio block is half of the real size that i tell the DMA controller so that an interrupt is called in the middle of playback that lets me load new audio data into the half of the block that just finished playing while it continues to play the second half of the block.

i know how to manually assign an arbitrary location to jump to on a hardware interrupt using a few POKEs. i was going to have a small bit of binary code in a string that it jumps to and then have that code modify a 1 byte QB string that i can keep checking and resetting to see if the interrupt occured or not.

i know what i want the ASM code to do but i'm not sure about the syntax because i never use ASM. here's how it should work:

1. hardware interrupt triggers machine to jump to the location my binary code stored in a string.
2. the code in the string needs to change the value of 1 byte at the segment+offset i want. i'll need to dynamically determine that location during runtime while creating the binary code string using VARSEG and VARPTR
3. return to my program



iirc, it would simply be comprised of a (few?) MOV operations and then a RETF?

do i also need to push the registers upon entry and pop them back when my code is finished? what exactly is the binary code i'd need in the string to accomplish this?

hope i'm being clear enough. can anybody help out? thanks!
 
i might help to post what ASM i've tried (being the total ASM noob that i am)

Code:
push ax
push cx
push dx
push bx
push bp
push si
push di


mov ax, 123
mov [49], ax

pop di
pop si
pop bp
pop bx
pop dx
pop cx
pop ax
retf

what i did was compile this in emu8086 to a BIN file, and load that BIN file into a QB string then to test i did a CALL absolute to it. i allocated a 50-byte static length string, and i thought this code would modify the value offset 49 in it's own code segment (to 123) if called but when it returns there is no change to the string's contents.

i'm sure there's something very obvious i'm missing... well obvious to others anyway. :)

to see if the interrupt has been called i of course planned to just keep checking the last byte of the string for being value 49, then do what i need to do, and change it back to 0 until the next time that code is run. it works in emu8086 and it shows that byte being changed.
 
Two things, actually. The first is to terminate your interrupt service routine with an iret ( CF hex) instruction, not a retf. Remember that the interrupt pushes the flags on the stack as well as the interrupt return address.

I'm assuming that this is a service routine for an interrupt generated by an 8259 PIC. So you need to tell the 8259 that you're done with your service routine, this way:

Code:
        mov     al,20h
        out     20h,al    ; signal EOI to 8259

If this is an interrupt from the slave 8259 (IRQ8-15), you need to issue two EOIs; one to the slave (port A0h) and the other to the master.
 
Last edited:
you can take over an interrupt with DOS (INT 21h) call 25h:

SET INTERRUPT VECTOR
AH = 25h
AL = interrupt number
DS:DX -> new interrupt handler


Code:
mov ah,25h
mov al,[I]InterruptNumberToBeTakenOver[/I]
lea dx,InterruptRoutine
push cs
pop ds
int 21h
ret

InterruptRoutine:
sti
push ax

[I]Code goes here[/I]

mov al,20h
out 20h,al
pop ax
iret
 
Last edited:
thanks to both of you guys for the help! i've successfully taken over interrupt 0xF (my SBpro2 is on IRQ 7)

when i do a manual interrupt call to 0xF from QB with CALL INTERRUPTX(&HF, cal, ret) the code i compiled works perfectly, and changes the value in the string as it should.

now for the strange part... the SB doesn't seem to be calling the interrupt itself after playing a block. i definitely have it set on auto-init DMA mode, and reviewing my code compared to the official SB programming docs all looks good.

i guess i'll just need to look harder, because something isn't right and like i said i know the interrupt has been hooked and that ASM code works.
 
apparently i'm not the only person who's run into this.

http://www.programmersheaven.com/mb/sound/133705/133705/soundblaster-interrupt-problem/?S=B20000



unfortunately, that page doesn't have an answer either. has anybody here messed with the sound blaster and auto-init DMA?

trixter? :D

Have you made sure you've re-enabled interrupts in the start of the interrupt routine? When a hardware interrupt is triggered, other interrupts are automaticly disabled and need to be reenabled by software. That's what the "sti" is for.

BTW, I got a small bug in my sample code. Somehow, I forgot to add the "int 21h" before "ret". I've corrected it now.
 
Last edited:
Have you made sure you've re-enabled interrupts in the start of the interrupt routine? When a hardware interrupt is triggered, other interrupts are automaticly disabled and need to be reenabled by software. That's what the "sti" is for.

BTW, I got a small bug in my sample code. Somehow, I forgot to add the "int 21h" before "ret". I've corrected it now.

Not so--the iret will pop the interrupt enable bit back into the flags. It's considered good form to enable interrrupts to allow other higher-level interrupts to be serviced immediately, but in a short routine, it's not strictly necessary. You also don't need to save all of the registers, just the ones that you're going to use in your ISR.

One issue I see in your ISR is the failure to set the segment address of where you're storing your interrupt flag. So your ISR will store into whatever segment DS happens to be pointing to, which is perhaps not what you intented. A better ISR might look like this:

Code:
    push    ax
    push    ds
    sti                              ; be a good citizen
    mov     ax,Dataseg       ; whatever my data segment is
    mov     ds,ax
    mov     word ptr ds:[49],1234
    mov     al,20h
    out      20h,al
    pop      ds
    pop      ax
    iret

The issue of having your flag in a mutually-accessible segment is important. You could keep it in the same segment that the interrupt servicing code is located, in which case the code would look like this:

Code:
    push    ax
    sti
    mov     word ptr cs:[Myflag],1234
    mov     al,20h
    out     20h,al
    pop     ax
    iret

Myflag:    dw   0

Of courrse, your QB program would need to know how to get at that flag, but I assume that you know how to do that.

DOS functions 25h and 35h were originally intended to provide an orderly interrupt "hooking" scheme. Unfortunately, the feature came too late and there's a lot of code out there that just plugs the IVT addresses in directly.

Oddly, the non-DOS method is perhaps the right way to set a hardware interrupt, if the following comment from the DOS getset.asm code is an indication:

Code:
       CLI                             ; Watch out!!!!! Folks sometimes use
       MOV     ES:[BX],DX              ;   this for hardware ints (like timer).
 
well here's what i have right now:

Code:
    push    ax
    push    ds
    sti
    mov     al,123
    mov     [49],al
    pop      ds
    pop      ax
    iret



there isn't any problem with that. if i manually call the interrupt, it changes the value to 123 and i am able to read that when it returns to QB. the problem now is that the SB is not generating the interrupt when it's supposed to be. i've looked at everything i could find about it on google, but i'm still stumped.

here's my QB code:

Code:
TYPE Registers
     ax AS INTEGER
     bx AS INTEGER
     cx AS INTEGER
     dx AS INTEGER
     bp AS INTEGER
     si AS INTEGER
     di AS INTEGER
     flags AS INTEGER
     ds AS INTEGER
     es AS INTEGER
END TYPE


DEFINT A-Z   'Sets all variables to integers unless specified otherwise
DECLARE SUB LoadWAV (file$)
DECLARE FUNCTION ResetDSP ()
DECLARE SUB OutDSP (Byte)
DECLARE FUNCTION ReadDSP ()
DECLARE FUNCTION DSPVersion! ()
DECLARE SUB PlayWAV (Segment&, Offset&, Length&, Frequency&)
DECLARE SUB ReadBLASTER ()
DIM SHARED baseadd, DMA, LenPort, Length&      ' Set vars to shared so we
'can
DIM SHARED WaveBuffer(1) AS STRING * 16382       ' use in different subs
CLS
ReadBLASTER         'Read the BLASTER environment variable
rd = ResetDSP
IF ResetDSP THEN    'Reset DSP (Success = -1, Failure = 0)
        PRINT "DSP reset successfully."
ELSE
        PRINT "DSP failed to reset"
        END
END IF


OPEN "c:\mycode.bin" FOR BINARY AS #1
GET #1, , asm
CLOSE #1

'hook interrupt
DIM cal AS Registers
DIM ret AS Registers

cal.ds = VARSEG(asm)
cal.dx = VARPTR(asm)
cal.ax = &H250F
CALL interruptx(&H21, cal, ret)




'INPUT "Enter filename: ", File$                 'Get user input for a WAV
''file
'INPUT "Enter frequency: ", Frequency&           'Get input for frequency
file$ = "c:\genaudio.wav"
Frequency& = 22050
LoadWAV file$
OUT baseadd + 12, &HD1                         'Turn on speakers
pl = 0
cb = 1
PlayWAV VARSEG(WaveBuffer(0)), VARPTR(WaveBuffer(0)), 16382, Frequency&

DO

  IF PEEK(49) = 123 THEN
    PRINT "The SB successfully tripped the interrupt." '<---- never happens :(
    OUT baseadd + &HE, &H20
    OUT &H20, &H20
    POKE 49, 0
    GET #1, , WaveBuffer(cb)
    cb = cb + 1
    IF cb = 2 THEN cb = 0
  END IF
LOOP UNTIL INKEY$ <> ""

OUT baseadd + &HC, &HD0
OUT baseadd + 12, &HD3                         'Turn off speakers

FUNCTION DSPVersion!
OutDSP &HE1     'Function to get DSP Version
a = ReadDSP     'High byte
b = ReadDSP     'Low byte
DSPVersion! = VAL(STR$(a) + "." + STR$(b))  'Set DSPVersion!
END FUNCTION

SUB LoadWAV (file$)
WaveBuffer(0) = ""          'Clear the WAV buffer
OPEN file$ FOR BINARY AS #1 'Open the WAV file
IF LOF(1) = 0 THEN CLOSE #1: KILL file$: PRINT "Non-existant file!": END
GET #1, 44, WaveBuffer(0)                       'Skip 44 bytes (file
GET #1, , WaveBuffer(1)
'header)
Length& = LEN(WaveBuffer(0))
'Length& = 32764
END SUB

SUB OutDSP (Byte)
DO
LOOP WHILE INP(baseadd + 12) AND &H80      'Loop until we get an OK byte
OUT baseadd + 12, Byte         'Set a byte to the SB input register
END SUB

SUB PlayWAV (Segment&, Offset&, Length&, Frequency&)
MemLoc& = Segment& * 16 + Offset&   'Area in memory of WAV buffer
Page = 0                            'DMA page to use
SELECT CASE DMA                     'Depending on DMA set vars to values
        CASE 0
                PgPort = &H87       'Set port to send page data to
                AddPort = &H0       'Set port to send memory address to
                LenPort = &H1       'Set port to send length to
                ModeReg = &H58      'Set mode to play in
        CASE 1
                PgPort = &H83
                AddPort = &H2
                LenPort = &H3
                ModeReg = &H59
        CASE 2
                PgPort = &H81
                AddPort = &H4
                LenPort = &H5
                ModeReg = &H5A
        CASE 3
                PgPort = &H82
                AddPort = &H6
                LenPort = &H7
                ModeReg = &H5B
        CASE ELSE
                PRINT "This program only supports DMA Channels 0-3."
                END
END SELECT
OUT &HA, &H4 + DMA              ' Send all
OUT &HC, 0                      ' the crap to
OUT &HB, ModeReg                ' the ports.
OUT AddPort, MemLoc& AND &HFF   ' More crap sending
OUT AddPort, (MemLoc& AND &HFFFF&) \ &H100 ' Yet more
IF (MemLoc& AND 65536) THEN Page = Page + 1     ' Set
IF (MemLoc& AND 131072) THEN Page = Page + 2    ' the
IF (MemLoc& AND 262144) THEN Page = Page + 4    ' correct
IF (MemLoc& AND 524288) THEN Page = Page + 8    ' memory page.
OUT PgPort, Page    ' Send page data
OUT LenPort, Length& AND &HFF               ' Send length
OUT LenPort, (Length& AND &HFFFF&) \ &H100  ' data
OUT &HA, DMA    ' Send DMA port
IF Frequency& < 23000 THEN
        TimeConst = 256 - 1000000 \ Frequency&  ' Set the freqency
        OutDSP &H40                             ' Byte to send frequency
        OutDSP TimeConst                        ' Send frequency
        'OutDSP &H48
        OutDSP &HC6
        OutDSP 0
        OutDSP (Length& AND &HFF)               ' Send
        OutDSP ((Length& AND &HFFFF&) \ &H100)  ' length
        OutDSP &H1C
                             ' Byte to send length
ELSE
        IF DSPVersion! >= 3 THEN 'use high speed timing
 		TimeConst = ((65536 - 256000000 \ Frequency&) AND &HFFFF&) \ &H100
                OutDSP &H40
                OutDSP TimeConst
                OutDSP (Length& AND &HFF)
                OutDSP ((Length& AND &HFFFF&) \ &H100)
        ELSE 'not high speed timing
                PRINT "You must have a DSP Version of 3.00 or greater to "
		PRINT "use a high frequency."
                END
        END IF
END IF
END SUB

SUB ReadBLASTER
b$ = ENVIRON$("BLASTER")            'Get the BLASTER variable
IF b$ = "" THEN PRINT "BLASTER environment variable not found!": END
'Darn!
FOR X = 1 TO LEN(b$)
        t$ = MID$(b$, X, 1)
        Y = X + 1
        SELECT CASE t$
                CASE "A"
                DO
                        Tp$ = MID$(b$, Y, 1)
                        IF Tp$ = " " THEN EXIT DO
                        Addr$ = Addr$ + Tp$
                        Y = Y + 1
                LOOP
                baseadd = VAL("&H" + Addr$)
                Tp$ = ""
                CASE "D"
                DO
                        Tp$ = MID$(b$, Y, 1)
                        IF Tp$ = " " THEN EXIT DO
                        DMAC$ = DMAC$ + Tp$
                        Y = Y + 1
                LOOP
                DMA = VAL(DMAC$)
                Tp$ = ""
        END SELECT
NEXT X
END SUB

FUNCTION ReadDSP
DO
LOOP UNTIL INP(baseadd + 14) AND &H80 ' If it's okay...
ReadDSP = INP(baseadd + 10)           ' Read a byte from the SB port
END FUNCTION

FUNCTION ResetDSP
OUT baseadd + 6, 1         ' Send byte to reset
FOR I = 1 TO 4
   Temp = INP(baseadd + 6)
NEXT I
OUT baseadd + 6, 0         ' Send 'Done' byte
a = INP(baseadd + 14)      ' Read prototype byte
IF INP(baseadd + 14) AND &H80 = &H80 AND INP(baseadd + 10) = &HAA THEN
'Reset
   ResetDSP = -1
ELSE
   ResetDSP = 0
END IF
END FUNCTION
 
well here's what i have right now:

Code:
    push    ax
    push    ds
    sti
    mov     al,123
    mov     [49],al
    pop      ds
    pop      ax
    iret

The problem with that is that you can't say with 100 percent certainty what DS will be when the interrupt hits. The system could be servicing a DOS call or be anywhere outside of your QB program, in which case the DS value isn't a given. Sure it works if you manually issue an interrupt, because that's a controlled case--you know where the interrupt is coming from and DS is a known. But hardware interrupts are real-time and can hit anytime and anywhere.

As to the SB not generating interrupts, it's entirely possible that the interrupt's been masked. If bit 7 is set in the return from reading port 21h (the 8259 mask register), they're masked and you need to clear that bit so that interrupts can get through. The following code (or its QB rendering) will do that:

Code:
        in      al,21h
        and     al,127      ; unmask IRQ 7
        out     21h,al

This isn't to say that there's not another register on the SB that enables or disables interrupts, but it's a start. Note that IRQ7 is also shared with the printer port, which shouldn't be a problem unless you're using a print spooler that depends on interrupts for the parallel port being enabled.
 
ok, so this should keep it in the same segment as it's running in right?

Code:
    push    ax
    push    ds
    sti
    mov     word ptr ds:[Myflag],1234

    mov     al,123
    mov     [49],al
    
    in      al,21h
    and     al,127      ; unmask IRQ 7
    out     21h,al
    pop      ds
    pop      ax
    iret
    
    Myflag:    dw   0

the interrupt still isn't called by the SB.
 
ok, so this should keep it in the same segment as it's running in right?

Code:
    push    ax
    push    ds
    sti
    mov     word ptr ds:[Myflag],1234

    mov     al,123
    mov     [49],al
    
    in      al,21h
    and     al,127      ; unmask IRQ 7
    out     21h,al
    pop      ds
    pop      ax
    iret
    
    Myflag:    dw   0

the interrupt still isn't called by the SB.

Unmask IRQ 7 after you set up the interrupt service routine, but before the first interrupt is issued. In other words:

1. Hook INT 15 (IRQ7) with your code
2. Unmask IRQ7 in the 8259
3. Read port 2xE to clear any pending DSP interrupt
4. Begin your SB twiddling...

Note that you also have to acknowledge the SB interrupt by reading port 2xE (If you're using 16-bit sound, 2xF). Otherwise, the SB DSP won't know that you've serviced the interrupt.

So your ISR should look like this:
  • Save the registers you're going to use (probably AX, DS, DX).
  • Enable interrupts
  • Set your flag
  • Read port 2xE
  • Signal EOI (20h to port 20h) to the 8259
  • Restore the saved registers
  • iret

Also note that you can force the SB to generate an interrupt for testing by issuing an F2 command to the DSP.

ok, so this should keep it in the same segment as it's running in right?

Sure, but do you know what segment that is for certain? In other words, do you make absolutely no DOS or BIOS calls while this thing is running? Both DOS and the BIOS can be interrupted, so if your interrupt hits when one of these is active, you'll end up using their DS, which I'll guarantee isn't the same as yours.
 
Last edited:
alright, now i'm getting somewhere. the SB is triggering the interrupts, after 10 or 11 of them it stops again. at least it's a step in the right direction.
 
help plus question

help plus question

emu8086 <- what is this? i wanna know more..!


I think i might have figured out a problem with your code.

You do NOT have a DEF SEG=VARSEG(array(0)) anywhere in your code before you peek and poke.

The currently set SEG at any given moment could be anything. You could be accessing the 49th byte of video memory, or anywhere for that matter.

You are doing all the calls correctly with VARSEG() & VARPTR(), but with each section of code, you have to set the DEF SEG= something to make sure it's in the right region of memory.



DEF SEG=&HA000
POKE 0,15

rem draw a white dot in the upper right corner of SCREEN 13 video memory

DEFINT A-Z
REM TELL QBASIC ALL MY VARIABLES ARE INTEGERS
REM WITH 2 BYTES PER ELEMENT
REDIM KITTEN(25)
VECTOR& = VARSEG(KITTEN(0))
DEF SEG=VECTOR&
PTR&=VARPTR(KITTEN(0))
POKE PTR&,255:pOKE PTR&+1&,255
REM FILL KITTEN(0) WITH THE VALUE -1


Hooking interrupts for the SB? For some reason, I can hook interrupts just fine on a 6502 CPU assembly program, but 8086+ architechture confuses the hello-kitty out of me. Where did you get the info on hooking the vector of the interrupt and getting your ASM code to work with QBasic?

I'm above average in plain jane QBasic, but i only barely know how to incorporate ASM into my stuffs.. Anything you can share or direct me towards would be great.



Kiyote!
 
question

question

btw.. what kind of system are you running this program on?

a dedicated DOS computer? a dosbox? WinXp command prompt?

dos computer (if it were set), and a dosbox usually have the BLASTER environment variable set up for programs to find, but windows usually doesn't..

what kind of sound card are you using also?

questions questions questions..



Kiyote!
 
You can assign the value of VARPTR to a variable and plug that in instead of calling varptr with every peek & poke.



Kiyote!


Code:
TYPE Registers
     ax AS INTEGER
     bx AS INTEGER
     cx AS INTEGER
     dx AS INTEGER
     bp AS INTEGER
     si AS INTEGER
     di AS INTEGER
     flags AS INTEGER
     ds AS INTEGER
     es AS INTEGER
END TYPE


DEFINT A-Z   'Sets all variables to integers unless specified otherwise
DECLARE SUB LoadWAV (file$)
DECLARE FUNCTION ResetDSP ()
DECLARE SUB OutDSP (Byte)
DECLARE FUNCTION ReadDSP ()
DECLARE FUNCTION DSPVersion! ()
DECLARE SUB PlayWAV (Segment&, Offset&, Length&, Frequency&)
DECLARE SUB ReadBLASTER ()
DIM SHARED baseadd, DMA, LenPort, Length&      ' Set vars to shared so we
'can
DIM SHARED WaveBuffer(1) AS STRING * 16382       ' use in different subs
CLS
ReadBLASTER         'Read the BLASTER environment variable
rd = ResetDSP
IF ResetDSP THEN    'Reset DSP (Success = -1, Failure = 0)
        PRINT "DSP reset successfully."
ELSE
        PRINT "DSP failed to reset"
        END
END IF


OPEN "c:\mycode.bin" FOR BINARY AS #1
GET #1, , asm
CLOSE #1

'hook interrupt
DIM cal AS Registers
DIM ret AS Registers

cal.ds = VARSEG(asm)
cal.dx = VARPTR(asm)
cal.ax = &H250F
CALL interruptx(&H21, cal, ret)




'INPUT "Enter filename: ", File$                 'Get user input for a WAV
''file
'INPUT "Enter frequency: ", Frequency&           'Get input for frequency
file$ = "c:\genaudio.wav"
Frequency& = 22050
LoadWAV file$
OUT baseadd + 12, &HD1                         'Turn on speakers
pl = 0
cb = 1
PlayWAV VARSEG(WaveBuffer(0)), VARPTR(WaveBuffer(0)), 16382, Frequency&

DO
  
  REM NEW LINE ~ KIYOTEWOLF
  DEF SEG=VARSEG(asm)

  IF 1=1 THEN  
    IF PEEK(49) = 123 THEN
      PRINT "The SB successfully tripped the interrupt." '<---- never happens :(
      OUT baseadd + &HE, &H20
      OUT &H20, &H20
      POKE 49, 0
      GET #1, , WaveBuffer(cb)
      cb = cb + 1
      IF cb = 2 THEN cb = 0
    END IF
  END IF

REM DEPENDING ON HOW IT HANDLES, CHOOSE ONE OF THE TWO ROUTINES ENCASED IN THE
REM DUMMY IF/THEN STATEMENTS.

  IF 1=0 THEN

    REM SOMETIMES THE BEGINNING OF THE VARIABLE IN MEMORY IS NOT AT ZERO.  YOU
    REM HAVE TO POINT TO THE BEGINNING OF THE VARIABLE AS QBASIC REPORTS IT TO BE.
    REM YOU CAN SOMETIMES TRUST IT'S AT THE BEGINNING OF THE SEGMENT, BUT NOT ALWAYS.

    IF PEEK(VARPTR(asm)+49) = 123 THEN
      PRINT "The SB successfully tripped the interrupt." '<---- never happens :(
      OUT baseadd + &HE, &H20
      OUT &H20, &H20
      POKE VARPTR(asm)+49, 0
      GET #1, , WaveBuffer(cb)
      cb = cb + 1
      IF cb = 2 THEN cb = 0
    END IF
  END IF


LOOP UNTIL INKEY$ <> ""

OUT baseadd + &HC, &HD0
OUT baseadd + 12, &HD3                         'Turn off speakers

FUNCTION DSPVersion!
OutDSP &HE1     'Function to get DSP Version
a = ReadDSP     'High byte
b = ReadDSP     'Low byte
DSPVersion! = VAL(STR$(a) + "." + STR$(b))  'Set DSPVersion!
END FUNCTION

SUB LoadWAV (file$)
WaveBuffer(0) = ""          'Clear the WAV buffer
OPEN file$ FOR BINARY AS #1 'Open the WAV file
IF LOF(1) = 0 THEN CLOSE #1: KILL file$: PRINT "Non-existant file!": END
GET #1, 44, WaveBuffer(0)                       'Skip 44 bytes (file
GET #1, , WaveBuffer(1)
'header)
Length& = LEN(WaveBuffer(0))
'Length& = 32764
END SUB

SUB OutDSP (Byte)
DO
LOOP WHILE INP(baseadd + 12) AND &H80      'Loop until we get an OK byte
OUT baseadd + 12, Byte         'Set a byte to the SB input register
END SUB

SUB PlayWAV (Segment&, Offset&, Length&, Frequency&)
MemLoc& = Segment& * 16 + Offset&   'Area in memory of WAV buffer
Page = 0                            'DMA page to use
SELECT CASE DMA                     'Depending on DMA set vars to values
        CASE 0
                PgPort = &H87       'Set port to send page data to
                AddPort = &H0       'Set port to send memory address to
                LenPort = &H1       'Set port to send length to
                ModeReg = &H58      'Set mode to play in
        CASE 1
                PgPort = &H83
                AddPort = &H2
                LenPort = &H3
                ModeReg = &H59
        CASE 2
                PgPort = &H81
                AddPort = &H4
                LenPort = &H5
                ModeReg = &H5A
        CASE 3
                PgPort = &H82
                AddPort = &H6
                LenPort = &H7
                ModeReg = &H5B
        CASE ELSE
                PRINT "This program only supports DMA Channels 0-3."
                END
END SELECT
OUT &HA, &H4 + DMA              ' Send all
OUT &HC, 0                      ' the crap to
OUT &HB, ModeReg                ' the ports.
OUT AddPort, MemLoc& AND &HFF   ' More crap sending
OUT AddPort, (MemLoc& AND &HFFFF&) \ &H100 ' Yet more
IF (MemLoc& AND 65536) THEN Page = Page + 1     ' Set
IF (MemLoc& AND 131072) THEN Page = Page + 2    ' the
IF (MemLoc& AND 262144) THEN Page = Page + 4    ' correct
IF (MemLoc& AND 524288) THEN Page = Page + 8    ' memory page.
OUT PgPort, Page    ' Send page data
OUT LenPort, Length& AND &HFF               ' Send length
OUT LenPort, (Length& AND &HFFFF&) \ &H100  ' data
OUT &HA, DMA    ' Send DMA port
IF Frequency& < 23000 THEN
        TimeConst = 256 - 1000000 \ Frequency&  ' Set the freqency
        OutDSP &H40                             ' Byte to send frequency
        OutDSP TimeConst                        ' Send frequency
        'OutDSP &H48
        OutDSP &HC6
        OutDSP 0
        OutDSP (Length& AND &HFF)               ' Send
        OutDSP ((Length& AND &HFFFF&) \ &H100)  ' length
        OutDSP &H1C
                             ' Byte to send length
ELSE
        IF DSPVersion! >= 3 THEN 'use high speed timing
 		TimeConst = ((65536 - 256000000 \ Frequency&) AND &HFFFF&) \ &H100
                OutDSP &H40
                OutDSP TimeConst
                OutDSP (Length& AND &HFF)
                OutDSP ((Length& AND &HFFFF&) \ &H100)
        ELSE 'not high speed timing
                PRINT "You must have a DSP Version of 3.00 or greater to "
		PRINT "use a high frequency."
                END
        END IF
END IF
END SUB

SUB ReadBLASTER
b$ = ENVIRON$("BLASTER")            'Get the BLASTER variable
IF b$ = "" THEN PRINT "BLASTER environment variable not found!": END
'Darn!
FOR X = 1 TO LEN(b$)
        t$ = MID$(b$, X, 1)
        Y = X + 1
        SELECT CASE t$
                CASE "A"
                DO
                        Tp$ = MID$(b$, Y, 1)
                        IF Tp$ = " " THEN EXIT DO
                        Addr$ = Addr$ + Tp$
                        Y = Y + 1
                LOOP
                baseadd = VAL("&H" + Addr$)
                Tp$ = ""
                CASE "D"
                DO
                        Tp$ = MID$(b$, Y, 1)
                        IF Tp$ = " " THEN EXIT DO
                        DMAC$ = DMAC$ + Tp$
                        Y = Y + 1
                LOOP
                DMA = VAL(DMAC$)
                Tp$ = ""
        END SELECT
NEXT X
END SUB

FUNCTION ReadDSP
DO
LOOP UNTIL INP(baseadd + 14) AND &H80 ' If it's okay...
ReadDSP = INP(baseadd + 10)           ' Read a byte from the SB port
END FUNCTION

FUNCTION ResetDSP
OUT baseadd + 6, 1         ' Send byte to reset
FOR I = 1 TO 4
   Temp = INP(baseadd + 6)
NEXT I
OUT baseadd + 6, 0         ' Send 'Done' byte
a = INP(baseadd + 14)      ' Read prototype byte
IF INP(baseadd + 14) AND &H80 = &H80 AND INP(baseadd + 10) = &HAA THEN
'Reset
   ResetDSP = -1
ELSE
   ResetDSP = 0
END IF
END FUNCTION
 
Back
Top