Issue #4
Saturday, October 6th, 2001

Welcome Back: A Brief Review

In part one, we set up a basic EMS interface with QuickBasic. We also created a sample program, which did nothing more than test the EMS routines and shuffle some memory around.

Note: If you missed part one, you should read it before continuing. It's available in the tutorials section of the Nemesis QB website. It's also published in issue #3 of the QB Chronicles.

Now we're going to get to the fun stuff: playing sounds stored in EMS!

Sound Blaster: Some More History

The Sound Blaster card (and every card compatible with it) supports two types of sound: FM synthesis sound and digitized sound.

Figure 2-1: FM synthesis sound

FM synthesis sound uses different parameters to control the sound, allowing the programmer to crudely "emulate" instruments. When you play a MIDI file in Windows (without a wavetable sound card), you are hearing FM synthesis. FM synthesis is used mainly for music, although it is sometimes used for sound effects.


Figure 2-2: Digitized sound

Digitized wave sound works by playing many sound "samples" each second, which produces sound. Any sound can be produced with a digitized wave, if the frequency (the number of samples/sec, aka "sampling rate") is high enough. This makes digitized sound a popular choice for speech and sound effects. The frequency usually ranges from 8,000 Hz to 44,100 Hz. Also, each sample can have an 8-bit or a 16-bit value. (Needless to say, a 16-bit sample is much more precise than an 8-bit sample.) When you play a WAV file from Windows, you are hearing digitized sound.

As you may have guessed, digitized sound has greater sound quality than FM synthesis. Besides that, FM synthesis is becoming outdated, and it tends to sound "cheesy" anyway. So we'll be using digitized sound in this tutorial.

So How Does EMS Help Us?

The main problem with digitized sound is that it takes up a lot of memory. One second of 16-bit stereo sound sampled at 44 KHz (that's 44,100 samples/sec, CD-quality) takes up 176K! However, most games can get by with 22 KHz sampling and 8-bit mono sound, which only takes 22 K/sec. That's still a lot, but it's easier to deal with.

Another reason DOS games use lower sampling rates and 8-bit sound is that most Sound Blaster clones are only compatible with earlier SB models (1, 2, or Pro) which don't support 16-bit sound (in DOS) or high sampling rates.

Even if we're using 22 KHz 8-bit mono sound, we're going to run out of memory quickly if we're limited to storing our sounds in the 640 K base memory. This is where EMS comes into play! With EMS, we have vast quantities of memory to store digitized sounds without wasting any base memory. We can even play back the sound directly from EMS without the need for a buffer in base memory.

Since this is an EMS tutorial and not a Sound Blaster tutorial, I'm not going to go into detail on the workings of the various Sound Blaster cards. We'll just use the basic functions that are compatible with all Sound Blaster cards. (But don't worry, I've got a mega Sound Blaster tutorial coming soon...)

Let's Get Started!

We will be using the EMS functions I presented in part 1 of this series. However, I'm not going to list them again; I will just add on to the code.

Note: You can find the complete source code for this tutorial in ems2.zip.

First, we'll need to define a few global variables and constants to store the sound settings and status.


DEFINT A-Z
'$DYNAMIC

DIM SHARED SB.BaseAddr  'Sound Blaster base address
DIM SHARED SB.DMAchan   'Sound Blaster DMA channel
DIM SHARED SB.DMApage   'DMA page register (set by SB.Init)
DIM SHARED SB.DMAadd    'DMA address register (set by SB.Init)
DIM SHARED SB.DMAlen    'DMA length register (set by SB.Init)
DIM SHARED SB.Sound     'Currently playing sound slot (set by SB.PlaySound)

CONST SB.MaxSounds = 9  'Maximum number of sound slots. This can be changed,
                        '  just remember that 64K is required for each slot.

'Holds the frequency, length, and priority of each sound slot.
DIM SHARED SB.SlotInfo(1 TO SB.MaxSounds, 1 TO 3) AS LONG

Detecting and Resetting the Sound Blaster

Before we can use the Sound Blaster card, we need to check to make sure it is present and initialize it. In order to do this, we need to know the base address and DMA channel (8-bit) of the card. The base address ranges from 210h to 260h, and the DMA channel ranges from 0 to 3. Because the user can change these settings, you can't be absolutely sure what they are.

There are two ways to find out: Ask the user, or look at the "BLASTER" environment variable

The BLASTER environment variable is set in the user's AUTOEXEC.BAT file. This variable contains the sound card settings in a string like so:


SET BLASTER=A220 I5 D1 T4

Warning: This variable may not exist. Even if it does, it may not have the correct settings if the user or another program has tampered with it!

The only two settings we are interested with are "A", the base address, (220h in the example above) and "D", the DMA channel (1 in the example above).


DECLARE SUB SB.GetConfig ()

SUB SB.GetConfig

  'Reads the BLASTER environment variable and gets the Sound Blaster base
  'address and 8-bit DMA channel from it.

  Config$ = UCASE$(ENVIRON$("BLASTER"))      'Get the variable from DOS

  FOR x = 1 TO LEN(Config$)                  'Look at each character in it
    SELECT CASE MID$(Config$, x, 1)
      CASE "A"                               'We found an "A", so the next 3
                                             '  characters are the base
                                             '  address in hex.
        SB.BaseAddr = VAL("&H" + MID$(Config$, x + 1, 3))

      CASE "D"                               'We found a "D", so the next
                                             '  character is the 8-bit DMA
                                             '  channel.
       SB.DMAchan = VAL(MID$(Config$, x + 1, 1))
    END SELECT
  NEXT

END SUB

If the BLASTER variable is not present, your only other option is to ask the user for the settings. If the user doesn't know, try 220h for the base address and 1 for the DMA channel (because these are the most common settings) and cross your fingers!

After we have the base address, we can determine the I/O register (aka port) addresses for the DSP chip on the sound card. The I/O registers are used to communicate with the DSP chip, which controls the sound card.

DSP I/O Register Addresses

Reset Base + 6h
Read Base + Ah
Write Base + Ch
Available Base + Eh

Before we can use the Sound Blaster, we need to reset the DSP chip. This is done by sending a "1" and a "0" to the reset register, then checking the read register for the value AAh. If the read register does not return AAh after 65,535 reads, then the base I/O address is either incorrect or no sound card is installed.

Since we also know the DMA channel, we can determine the channel-specific registers used to control DMA transfers: the page register, address register, and length register. (We will use different sets of registers depending on which DMA channel the sound card is using.)

DMA Channel-Specific Registers

Channel Page Address Length
0 87h 0h 1h
1 83h 2h 3h
2 81h 4h 5h
3 82h 6h 7h

The DMA controller also uses three general registers which are used no matter which DMA channel the sound card is using.

DMA General Registers

Ah Mask register
Bh Mode register
Ch Clear register

Before we do any DMA transfers, we should reset the DMA controller. This is done by setting the mask bit in the DMA mask register (channel + 4h), and then sending a "0" to the DMA clear register.

Below is the complete function to reset and initialize the Sound Blaster.


DECLARE FUNCTION SB.Init ()

FUNCTION SB.Init

  'Initializes the Sound Blaster by resetting the DSP chip, and determines
  'which DMA registers to use based on the selected DMA channel.
  '
  'The sound card configuration must be set (either by SB.GetConfig or
  'manually) prior to calling this function.
  '
  'If the DSP is successfully reset, this function will return -1. If the
  'DSP could not be reset or the DMA channel is invalid, it will return 0.

  OUT SB.BaseAddr + &H6, 1                  'Send a "1" to the DSP reset reg
  OUT SB.BaseAddr + &H6, 0                  'Send a "0" to the DSP reset reg

  FOR ResetDSP& = 1 TO 65535                'Wait up to 65,535 reads

    IF INP(SB.BaseAddr + &HA) = &HAA THEN   'DSP read reg returned AAh,
      EXIT FOR                              '  which means it has been reset.

    ELSEIF ResetDSP& = 65535 THEN           'Still no success after 65,535
      SB.Init = 0                           '  tries, so we must have the
      EXIT FUNCTION                         '  wrong base address or there is
    END IF                                  '  no Sound Blaster card.
  NEXT

  SELECT CASE SB.DMAchan      'Since we know which DMA channel the Sound
                              '  Blaster is using, we can set up the
                              '  channel-specific registers beforehand to
                              '  save a little time.

    CASE 0                    'DMA Channel 0 (8-bit)
      SB.DMApage = &H87       'Page register = 87h
      SB.DMAadd = &H0         'Address register = 0h
      SB.DMAlen = &H1         'Length register = 1h

    CASE 1                    'DMA Channel 1 (8-bit)
      SB.DMApage = &H83       'Page register = 83h
      SB.DMAadd = &H2         'Address register = 2h
      SB.DMAlen = &H3         'Length register = 3h

    CASE 2                    'DMA Channel 2 (8-bit)
      SB.DMApage = &H81       'Page register = 81h
      SB.DMAadd = &H4         'Address register = 4h
      SB.DMAlen = &H5         'Length register = 5h

    CASE 3                    'DMA Channel 3 (8-bit)
      SB.DMApage = &H82       'Page register = 82h
      SB.DMAadd = &H6         'Address register = 6h
      SB.DMAlen = &H7         'Length register = 7h

    CASE ELSE                 'The DMA channel is either 16-bit or invalid
      SB.Init = 0             'Return error status
      EXIT FUNCTION
  END SELECT

  OUT &HA, SB.DMAchan + &H4   'Reset the DMA controller by setting the mask
                              '  bit in the DMA mask register and clearing
  OUT &HC, &H0                '  any current transfers by sending a 0 to the
                              '  DMA clear register.

  SB.Sound = 1                'Set the last playing sound to 1
  SB.Init = -1                'Return the success code

END FUNCTION

Enabling the Sound

Even after we have reset the Sound Blaster, we still won't hear any sound until the "speaker" is turned on. (That's Creative-speak for enabling the sound output.) This should only be done once at the beginning of your program, since it causes the speakers to "click". Before your program ends, it should also turn the "speaker" back off.


DECLARE SUB SB.SpeakerOn ()
DECLARE SUB SB.SpeakerOff ()

SUB SB.SpeakerOn

  'Turns the "speaker" on. This actually just enables the digitized sound
  'output so that the sound can be heard.

  SB.WriteDSP &HD1

END SUB

SUB SB.SpeakerOff

  'Turns the "speaker" off. This actually just disables the digitized sound
  'output, effectively muting the sound.

  SB.WriteDSP &HD3

END SUB

Loading Sounds into EMS

Once the Sound Blaster is all reset and initialized, we are ready to play some sounds! The only problem is, we don't have any sounds to play!

Figure 2-3: Four pages are allocated to each sound slot

The easiest way to get sounds is to load them in from WAV files. We'll designate a different "slot" for each sound when we load them. Using this method, we can load multiple sounds and play them back by telling our playback sub which slot to play.

Because DMA transfers can only handle 64K at a time, each sound will be limited to 64K in length. The sounds will also be limited to 22 KHz 8-bit so our routines will work on all Sound Blaster cards.

There is one more limitation: We can only play one sound at a time. This is because the Sound Blaster only has one digitized sound channel. However, we can use a priority-based sound system to improve this a bit.

If you remember from part one, each EMS page is 16K. So we'll allow each sound slot 4 pages (16 x 4 = 64K). This might waste a little memory, but it will be much more simpler than trying to dynamically allocate pages to each sound based on the sound's size!

So how does one load a wave file? Well, it's just like any other binary file! The only thing we have to be concerned with is making sure that the sound is 8-bit, 23 KHz or less, and 64K or less in length. Luckily, all this information is stored in a "header" in the wave file.

Microsoft Wave File Format

Offset Length Type Description
0 4 STRING RIFF ID string. Must be "RIFF".
4 4 LONG RIFF length. We don't care about this.
8 4 STRING Wave ID string. Must be "WAVE".
12 4 STRING Format ID string. Must be "fmt", plus a space.
16 4 LONG Format length. We don't care about this.
20 2 INT Format tag. This should be 1, which is 8-bit PCM. If it is something else, then the wave file is probably 16-bit or ADPCM compressed. Either way, we can't use it!
22 2 INT Number of Channels. This should be 1, which is mono sound. It may also be 2 or 4, for stereo or quad sound. However, we can only play mono sounds.
24 4 LONG Frequency. Remember, we can only play wave files that are 23 KHz or less.
28 4 LONG Transfer rate. We don't care about this.
32 2 INT Block alignment. This should be 1 for 8-bit mono files.
34 2 INT Reserved for other format information.
36 4 STRING Data ID. Must be "data".
40 4 LONG The data length. We can only play wave files 64K or less. So we'll only play the first 64K if the file is longer.
44 ? ? The actual wave data. This is what gets loaded into EMS.

The only problem left is the question of getting the actual wave data into EMS. We could read the data directly from the file into EMS (if the correct pages were mapped to the page frame). However, this would require use to use DOS interrupts for file transfers, which can get messy. But don't worry, there's another way!

We can create a small buffer (1K or so) in base memory. Then QuickBasic can read the file 1K at a time and put that into the buffer (which is actually a 1K string variable). From there, we can use our EMS.CopyMem routine from part 1 to copy the data from the buffer to a logical page EMS. Then the program just loops around and gets another 1K until the whole file has been loaded.

After the sound has been loaded into EMS, we'll need to save the frequency and length of the sound so we can play it back later. We'll also save the sound's priority (more on this later). We can use the shared SB.SlotInfo array defined at the beginning of our program to do this.


DECLARE FUNCTION SB.LoadSound (Filename$, Slot, Priority, Handle)

FUNCTION SB.LoadSound (Filename$, Slot, Priority, Handle)

  'Loads a sound from a wave file into a sound "slot" in EMS, where:
  '
  'Filename$ = Filename of an 8-bit mono PCM wave file <=23 KHz. If the file
  '            is larger than 64k, only the first 64k will be loaded.
  'Slot      = Sound slot to load the sound into
  'Priority  = Priority to assign to the sound
  '            (For example, 1 = #1 priority, 2 = #2 priority, etc.)
  'Handle    = EMS handle of memory to store sounds in
  '
  'Returns true (-1) if the sound was loaded successfully
  'or false (0) if there was an error.

  WaveFile = FREEFILE
  OPEN Filename$ FOR BINARY AS #WaveFile

  IF LOF(WaveFile) = 0 THEN       'The file length is 0, so assume that
    CLOSE #WaveFile               '  we created the file when we opened it
    KILL Filename$                '  and delete it.
    SB.LoadSound = 0              'Return an error code
    EXIT FUNCTION
  END IF

  RiffID$ = SPACE$(4)
  GET #WaveFile, , RiffID$        'Check the RIFF ID string. If it's not
  IF RiffID$ <> "RIFF" THEN       '  "RIFF", then the wave file is invalid.
    SB.LoadSound = 0              'Return an error code
    EXIT FUNCTION
  END IF

  GET #WaveFile, , RiffLen&       'Get the RIFF length and ignore it :)

  WaveID$ = SPACE$(4)
  GET #WaveFile, , WaveID$        'Get the wave ID string. If it's not
  IF WaveID$ <> "WAVE" THEN       '  "WAVE", then the wave file is invalid.
    SB.LoadSound = 0              'Return an error code
    EXIT FUNCTION
  END IF

  FormatID$ = SPACE$(4)
  GET #WaveFile, , FormatID$      'Get the format ID string. If it's not
  IF FormatID$ <> "fmt " THEN     '  "fmt ", then the wave file is invalid.
    SB.LoadSound = 0              'Return an error code
    EXIT FUNCTION
  END IF

  GET #WaveFile, , FormatLen&     'Get the format length and ignore it

  GET #WaveFile, , FormatTag      'Get the format tag, which defines what
                                  '  format the data is in. This needs to be
                                  '  "1", which is uncompressed PCM.
  IF FormatTag <> 1 THEN          'If it's something else, we can't play it
    SB.LoadSound = 0              'Return an error code
    EXIT FUNCTION
  END IF

  GET #WaveFile, , NumChannels    'Get the # of channels. This needs to be "1"
                                  '  (because we can only play mono sounds)
  IF NumChannels <> 1 THEN        'If it's stereo, we can't play it
    SB.LoadSound = 0              'Return an error code
    EXIT FUNCTION
  END IF

  GET #WaveFile, , Frequency&     'Get the sound frequency (sampling rate)
  IF Frequency& > 23000 THEN      'We can't play sounds > 23 KHz
    SB.LoadSound = 0              'Return an error code
    EXIT FUNCTION
  END IF

  GET #WaveFile, , TransferRate&  'Get the data transfer rate and ignore it

  GET #WaveFile, , BlockAlign     'Get the block alignment.
  IF BlockAlign <> 1 THEN         'If it's not "1", then it's not an 8-bit
                                  '  wave and we can't play it.
    SB.LoadSound = 0              'Return an error code
    EXIT FUNCTION
  END IF

  GET #WaveFile, , ExtraData      'Get the extra data and ignore it

  DataID$ = SPACE$(4)
  GET #WaveFile, , DataID$        'Get the data ID string. If it's not
  IF DataID$ <> "data" THEN       '  "data", then the wave file is invalid.
    SB.LoadSound = 0              'Return an error code
    EXIT FUNCTION
  END IF

  GET #WaveFile, , DataLen&                  'Get the sound data length
  IF DataLen& > 65536 THEN DataLen& = 65536  'If the sound is greater than
                                             '  64K, load only the first 64K


  BufferSize = 1024              'Set the buffer size to 1K. For faster
  Buffer$ = SPACE$(BufferSize)   'loading, you can increase the buffer size.
                                 '(Try 4096 to 16384). However, if the
                                 'buffer is too large you may run out of
                                 'string space in your program.

  DataRead& = 0                  'We haven't read any data yet...

  DO
    IF DataRead& + BufferSize > DataLen& THEN  'If the buffer is larger than
                                               '  the data left to read, we
      Buffer$ = SPACE$(DataLen& - DataRead&)   '  need to adjust it so we
                                               '  don't read past the end
    END IF                                     '  of the file.

    GET #WaveFile, , Buffer$                   'Read the data into the buffer

    Page = DataRead& \ 16384                   'Determine the EMS page and
    Offset = DataRead& - Page * 16384&         '  offset to load the data
                                               '  into.

    Page = Page + (Slot - 1) * 4               'Adjust the page depending on
                                               '  which slot we're using.

    'Copy the data from the buffer to EMS
    EMS.CopyMem LEN(Buffer$), 0, VARSEG(Buffer$), SADD(Buffer$), Handle, Page, Offset

    DataRead& = DataRead& + LEN(Buffer$)       'Increase the number of bytes
                                               '  read by the size of the
                                               '  data buffer.

  LOOP UNTIL DataRead& = DataLen&              'Loop around until all the
                                               '  data has been loaded.

  Buffer$ = ""        'Set the buffer to null to restore the string space

  CLOSE #WaveFile

  SB.SlotInfo(Slot, 1) = Frequency&    'Save the frequency,
  SB.SlotInfo(Slot, 2) = DataLen&      '  length,
  SB.SlotInfo(Slot, 3) = Priority      '  and priority of the sound.

  SB.LoadSound = -1                    'Sound loaded successfully

END FUNCTION

So What is this "Priority" Thing?

Since the Sound Blaster can only play one sound at a time (in hardware), we will be using a priority-based system. Using this system, each sound is assigned a priority when it is loaded. Before we play a new sound, we check to see if another sound is already playing. If so, we check the priority of the currently playing sound. If the sound currently playing is more important, we don't interrupt it. But if the new sound has the same priority or is more important, we stop the currently playing sound and play the new sound.

The following function will tell us whether or not the Sound Blaster is playing a sound by checking to see if the DMA channel is in use. We can use this function with our SB.PlaySound sub to implement the priority-based system.


DECLARE FUNCTION SB.InUse ()

FUNCTION SB.InUse

  'Returns true (-1) if the Sound Blaster DMA channel is in use
  'or false (0) if it's not.

  OUT &HC, &H0                  'Send 0h to the DMA clear register

  'Get the number of bytes left to be transferred from the DMA length
  'register. Since registers are 8-bit, we need to read the low byte first
  'and then read the high byte.
  BytesLeft& = INP(SB.DMAlen) + INP(SB.DMAlen) * 256&

  IF BytesLeft& = &HFFFF& OR BytesLeft& = 0 THEN  'When the DMA controller is
                                                  '  not transferring data,
                                                  '  it will return either
                                                  '  FFFFh or 0.

    SB.InUse = 0                'No data is being transferred
  ELSE
    SB.InUse = -1               'Data is still being transferred
  END IF

END FUNCTION

Playing Sounds

Once a sound has been loaded, it is ready to be played. To play a sound, we need to know four things: the priority, frequency, length, and memory location.

We stored the priority, frequency, and length in the SB.SlotInfo array when we loaded the sound, but what about the memory location? Since we can only perform DMA transfers from the 1 MB memory region, the EMS logical pages containing the sound must be mapped to the page frame first. Then we can use the page frame address for the memory location.

So how do we know which logical pages to map to the page frame? Well, because each sound slot is 4 pages, we can use:


EMS.MapXPages 0, (Slot - 1) * 4, 4, Handle

(We have to subtract 1 from the slot number because the sound slots are numbered starting at 1, while the EMS pages are numbered starting from 0.)

Figure 2-4: Mapping the sound to play to the page frame

Once the correct pages have been mapped, we can program the DMA controller to transfer the sound from memory to the sound card.

  1. Mask the DMA channel which we will be using by setting the mask bit in the DMA mask register. This can be done by adding 4 to the DMA channel number and sending that value to the DMA mask register.

  2. Send a 0 to the DMA clear register to stop any current transfers.

  3. Set the DMA transfer mode to output by adding 48h to the DMA channel number and sending it to the DMA mode register.

  4. Set the address and page.

  5. Set the length to transfer.

  6. Clear the mask bit on the mask register. The DMA transfer will begin as soon as the Sound Blaster is ready.

After programming the DMA controller, the only thing left to do is tell the Sound Blaster DSP that we want to play a sound. But to do this we have to wait until the DSP is ready and then send the commands. This sub checks the DSP write register and waits until the DSP is ready before sending the byte.


DECLARE SUB SB.WriteDSP (Byte)

SUB SB.WriteDSP (Byte)

  'Writes the value [Byte] to the DSP write register.

  DO
    Ready = INP(SB.BaseAddr + &HC)  'Wait until the DSP is ready
  LOOP WHILE Ready AND &H80         '  to accept the data

  OUT SB.BaseAddr + &HC, Byte       'Send the value

END SUB

  1. Tell the DSP that we want to set the digitized sound transfer time constant by sending 40h.

  2. Send the time constant: 256 - 1,000,000 \ Frequency

  3. Tell the DSP that we want to output a sound using 8-bit single-cycle DMA by sending 14h.

  4. Send the length of the sound.

The Sound Blaster will begin playing the sound immediately after step 4 is complete. And since we are using DMA to play back the sound, our program can do whatever it wants while the sound is playing. That's right, the sounds are played in the background!


DECLARE SUB SB.PlaySound (Slot, Handle)

SUB SB.PlaySound (Slot, Handle)

  'Plays a sound from a "slot" in EMS, where:
  '
  'Slot = Sound slot to play
  'Handle = EMS handle of memory sound is stored in

  'If a sound is already playing with a higher priority, don't interrupt it.
  IF SB.InUse AND SB.SlotInfo(SB.Sound, 3) < SB.SlotInfo(Slot, 3) THEN
    EXIT SUB
  END IF

  SoundFreq& = SB.SlotInfo(Slot, 1)             'Get the sound frequency
  SoundLen& = SB.SlotInfo(Slot, 2) - 1          'Get the sound length

  Address& = (&H10000 + EMS.PageFrame) * 16&    'Calculate the 20-bit address
  Page = (&H10000 + EMS.PageFrame) / &H1000     '  and page of the EMS page
                                                '  frame.

  EMS.MapXPages 0, (Slot - 1) * 4, 4, Handle    'Map the sound (64K, 4 pages)
                                                '  to the EMS pageframe.

  'Program the DMA controller
  OUT &HA, SB.DMAchan + &H4                     'Mask the DMA channel to use
                                                '  by setting the mask bit in
                                                '  the DMA mask register.

  OUT &HC, &H0                                  'Clear any current transfers
                                                '  by sending a 0 to the DMA
                                                '  clear register.

  OUT &HB, SB.DMAchan + &H48                    'Set the transfer mode to
                                                '  "output" with the DMA mode
                                                '  register.

  OUT SB.DMAadd, Address& AND &HFF               'Set the low and
  OUT SB.DMAadd, (Address& AND &HFF00&) \ &H100  '  high byte of the address.

  OUT SB.DMApage, Page                             'Set the page.

  OUT SB.DMAlen, SoundLen& AND &HFF                'Set the low and
  OUT SB.DMAlen, (SoundLen& AND &HFF00&) \ &H100   '  high byte of the sound
                                                   '  length.

  OUT &HA, SB.DMAchan       'Clear the mask bit in the DMA mask register


  'Program the DSP chip
  SB.WriteDSP &H40                         'Select the "set time transfer
                                           '  constant" function.

  SB.WriteDSP 256 - 1000000 \ SoundFreq&   'Calculate and send the constant.

  SB.WriteDSP &H14                         'Select the "8-bit single-cycle
                                           '  DMA output" function.

  SB.WriteDSP SoundLen& AND &HFF                 'Send the low and
  SB.WriteDSP ((SoundLen& AND &HFF00&) \ &H100)  '  high byte of the
                                                 '  sound length

  SB.Sound = Slot  'Save the slot number of the currently playing sound

END SUB

Pausing the Sound

Although the sound is playing in the background, it can be paused at any time. To do this, all we have to do is send D0h to the DSP write register. This will pause any sound that is currently playing for an indefinite amount of time.

To resume a paused sound, we just send D4h to the DSP write register. The sound will then continue playing where it left off.


DECLARE SUB SB.Pause ()
DECLARE SUB SB.Resume ()

SUB SB.Pause

  'Pauses the sound currently playing

  SB.WriteDSP &HD0

END SUB

SUB SB.Resume

  'Resumes the sound currently playing

  SB.WriteDSP &HD4

END SUB

Another Sample Program

Here is a sample program I wrote to test out all the Sound Blaster routines presented in this tutorial. The sample program simply loads 9 wave files into EMS and allows you to play them back by pressing 1-9. It also demonstrates the priority-based sound system by assigning different priorities to each sound. Check it out!


COLOR 7
CLS
IF NOT EMS.Init THEN
  PRINT "No EMM detected."
  END
END IF

SB.GetConfig
IF SB.BaseAddr = 0 OR SB.DMAchan = 0 THEN
  PRINT "Sound Blaster settings not found. Please enter them manually."
  PRINT
  INPUT "Base address (usually 220): ", BaseAddr$
  SB.BaseAddr = VAL("&H" + BaseAddr$)
  INPUT "DMA channel (usually 1): ", SB.DMAchan
  PRINT
END IF

IF NOT SB.Init THEN
  PRINT "No Sound Blaster detected."
  END
END IF

CLS
COLOR 14, 1
PRINT SPACE$(22); "Using EMS in QuickBasic: Part 2 of 3"; SPACE$(22)
COLOR 15, 0
PRINT STRING$(31, 196); " EMS Information "; STRING$(32, 196)
COLOR 7
PRINT "EMM Version: "; EMS.Version$

IF EMS.Version$ < "4.0" THEN
  PRINT
  PRINT "EMM 4.0 or later must be present to use some of the EMS functions."
  END
END IF

PRINT "Page frame at: "; HEX$(EMS.PageFrame); "h"
PRINT "Free handles:"; EMS.FreeHandles

IF EMS.FreeHandles = 0 THEN
  PRINT
  PRINT "You need at least one free handle to run this demo."
  END
END IF

PRINT "Total EMS:"; EMS.TotalPages; "pages /"; EMS.TotalPages * 16&; "KB /"; EMS.TotalPages \ 64; "MB"
PRINT "Free EMS:"; EMS.FreePages; "pages /"; EMS.FreePages * 16&; "KB /"; EMS.FreePages \ 64; "MB"

IF EMS.FreePages < 36 THEN
  PRINT
  PRINT "You need at least 36 pages (576 KB) free EMS to run this demo."
  END
END IF

PRINT
COLOR 15
PRINT STRING$(26, 196); " Sound Blaster Information "; STRING$(27, 196)
COLOR 7
PRINT "Base Address: "; HEX$(SB.BaseAddr); "h"
PRINT "DMA Channel:"; SB.DMAchan
PRINT
COLOR 15
PRINT STRING$(30, 196); " Setting Up Sounds "; STRING$(31, 196)
COLOR 7
PRINT "Allocating 36 pages (576 KB) of EMS...";

Handle = EMS.AllocPages(64)
IF EMS.Error THEN
  PRINT "error!"
  PRINT EMS.ErrorMsg$
  END
ELSE
  PRINT "ok! (Using handle "; LTRIM$(STR$(Handle)); ")"
END IF

FOR Sfx = 1 TO 9

  PRINT "Loading SFX"; LTRIM$(STR$(Sfx)); ".WAV into slot "; LTRIM$(STR$(Sfx)); "...";

  SELECT CASE Sfx
    CASE 1, 3, 9
      Priority = 1
    CASE 4, 7, 8
      Priority = 2
    CASE 5, 6
      Priority = 3
    CASE 2
      Priority = 4
  END SELECT

  IF NOT SB.LoadSound("SFX" + LTRIM$(STR$(Sfx)) + ".WAV", Sfx, Priority, Handle) THEN
    PRINT "error!"
    PRINT "couldn't load wave file"
    END
  ELSE
    PRINT "ok! ("; LTRIM$(STR$(SB.SlotInfo(Sfx, 1))); " Hz,"; SB.SlotInfo(Sfx, 2); "bytes, #"; LTRIM$(STR$(SB.SlotInfo(Sfx, 3))); " priority)"
  END IF

NEXT

LOCATE 25, 28
COLOR 31
PRINT "Press any key to proceed";

KeyPress$ = INPUT$(1)
COLOR 7
CLS
COLOR 14, 1
PRINT SPACE$(22); "Using EMS in QuickBasic: Part 2 of 3"; SPACE$(22)
COLOR 15, 0
PRINT STRING$(34, 196); " Sound Test "; STRING$(34, 196)
COLOR 7
PRINT
PRINT "Here you can test the sound playback routines. In this demo, only 9 sounds"
PRINT "have been loaded into EMS. However, in your own programs you may load as many"
PRINT "sounds as you want! The only limitation is that you must have enough free EMS."
PRINT "(And I don't think that should be a problem... ^_^)"
PRINT
COLOR 15
PRINT "Press 1 through 9 to hear different sounds."
PRINT
PRINT "Press P to pause/stop sound playback and R to resume a paused sound."
PRINT
PRINT "Press ESC to end the demo."
PRINT
COLOR 7
PRINT "For example, press 2 to hear a long drone. After the sound has started, press"
PRINT "P and the sound will pause. You can then play a different sound or resume the"
PRINT "same sound by pressing R."
PRINT
PRINT "You will also notice that some sounds have a higher priority than other sounds."
PRINT "For instance, sound 9 has a #1 priority while sound 4 has a #2 priority. This"
PRINT "means that sound 9 will interrupt sound 4 if it is playing. However, if sound 9"
PRINT "is playing, sound 4 will not interrupt it (because sound 9 has a lower priority)"

SB.SpeakerOn

COLOR 15
DotPos = 1
DotDir = 1
DO
  KeyPress$ = UCASE$(INKEY$)
  SELECT CASE KeyPress$
    CASE "1" TO "9"
      SB.PlaySound VAL(KeyPress$), Handle
    CASE "P"
      SB.Pause
    CASE "R"
      SB.Resume
  END SELECT

  IF SB.InUse THEN
    Sound$ = LTRIM$(STR$(SB.Sound))
    Freq$ = LTRIM$(STR$(SB.SlotInfo(SB.Sound, 1)))
    Size$ = LTRIM$(STR$(SB.SlotInfo(SB.Sound, 2)))
    Priority$ = LTRIM$(STR$(SB.SlotInfo(SB.Sound, 3)))
    LOCATE 25, 1
    COLOR 15
    PRINT "Playing sound #"; Sound$; " ("; Freq$; " Hz, "; Size$; " bytes, #"; Priority$; " priority)"; SPACE$(12);
    DotCol = 10
  ELSE
    LOCATE 25, 1
    COLOR 15
    PRINT "No sound is playing"; SPACE$(40);
    DotCol = 12
  END IF

  WAIT &H3DA, 8, 8
  WAIT &H3DA, 8

  LOCATE 24, DotPos
  COLOR DotCol
  PRINT CHR$(254);
  IF DotPos > 1 THEN
    LOCATE 24, DotPos - 1
    PRINT " ";
  END IF
  IF DotPos < 80 THEN
    LOCATE 24, DotPos + 1
    PRINT " ";
  END IF
  IF DotDir = 1 THEN
    DotPos = DotPos + 1
    IF DotPos = 81 THEN
      DotPos = 80
      DotDir = 2
    END IF
  ELSEIF DotDir = 2 THEN
    DotPos = DotPos - 1
    IF DotPos = 0 THEN
      DotPos = 1
      DotDir = 1
    END IF
  END IF

LOOP UNTIL KeyPress$ = CHR$(27)

SB.SpeakerOff

COLOR 7
CLS
COLOR 14, 1
PRINT SPACE$(22); "Using EMS in QuickBasic: Part 2 of 3"; SPACE$(22)
COLOR 15, 0
PRINT STRING$(33, 196); " Ending Demo "; STRING$(34, 196)
COLOR 7
PRINT
PRINT "Deallocating 36 pages...";

EMS.DeallocPages (Handle)
IF EMS.Error THEN
  PRINT "error!"
  PRINT EMS.ErrorMsg$
  END
ELSE
  PRINT "ok!"
END IF

END

That's All for Now...

Well, I hope you enjoyed part 2 of the EMS tutorial series. Heck, maybe you even learned something! In part 3 (coming in a month or two), I'll finish up the series by showing you how to store sprites and huge data arrays in EMS, as well as some neat effects like screen scrolling and page flipping using EMS.

If you have any questions or comments about this article, or (gasp!) found an error, please e-mail me at plasma357@hotmail.com or post a message on the Nemesis QB messageboard.

This article was written by: Plasma357 - http://www.nemesisqb.com

All site content is © Copyright 2001, HyperRealistic Games. This excludes content submitted by other people.