Código [Seleccionar]
' constants used with JOYINFOEX structure
Public Const JOY_POVCENTERED = -1
Public Const JOY_POVFORWARD = 0
Public Const JOY_POVRIGHT = 9000
Public Const JOY_POVBACKWARD = 18000
Public Const JOY_POVLEFT = 27000
Public Const JOY_RETURNX = &H1&
Public Const JOY_RETURNY = &H2&
Public Const JOY_RETURNZ = &H4&
Public Const JOY_RETURNR = &H8&
Public Const JOY_RETURNU = &H10 ' axis 5
Public Const JOY_RETURNV = &H20 ' axis 6
Public Const JOY_RETURNPOV = &H40&
Public Const JOY_RETURNBUTTONS = &H80&
Public Const JOY_RETURNRAWDATA = &H100&
Public Const JOY_RETURNPOVCTS = &H200&
Public Const JOY_RETURNCENTERED = &H400&
Public Const JOY_USEDEADZONE = &H800&
Public Const JOY_RETURNALL = (JOY_RETURNX Or JOY_RETURNY Or JOY_RETURNZ Or JOY_RETURNR Or JOY_RETURNU Or JOY_RETURNV Or JOY_RETURNPOV Or JOY_RETURNBUTTONS)
Public Const JOY_CAL_READALWAYS = &H10000
Public Const JOY_CAL_READXYONLY = &H20000
Public Const JOY_CAL_READ3 = &H40000
Public Const JOY_CAL_READ4 = &H80000
Public Const JOY_CAL_READXONLY = &H100000
Public Const JOY_CAL_READYONLY = &H200000
Public Const JOY_CAL_READ5 = &H400000
Public Const JOY_CAL_READ6 = &H800000
Public Const JOY_CAL_READZONLY = &H1000000
Public Const JOY_CAL_READRONLY = &H2000000
Public Const JOY_CAL_READUONLY = &H4000000
Public Const JOY_CAL_READVONLY = &H8000000
Declare Function joyGetPos Lib "winmm.dll" Alias "joyGetPos" (ByVal uJoyID As Long, pji As JOYINFO) As Long
Declare Function joyGetPosEx Lib "winmm.dll" Alias "joyGetPosEx" (ByVal uJoyID As Long, pji As JOYINFOEX) As Long
Public Const WAVE_FORMAT_QUERY = &H1
Public Const SND_PURGE = &H40 ' purge non-static events for task
Public Const SND_APPLICATION = &H80 ' look for application specific association
Public Const WAVE_MAPPED = &H4
Public Const WAVE_FORMAT_DIRECT = &H8
Public Const WAVE_FORMAT_DIRECT_QUERY = (WAVE_FORMAT_QUERY Or WAVE_FORMAT_DIRECT)
Public Const MIM_MOREDATA = MM_MIM_MOREDATA
Public Const MOM_POSITIONCB = MM_MOM_POSITIONCB
' flags for dwFlags parm of midiInOpen()
Public Const MIDI_IO_STATUS = &H20&
Declare Function midiStreamOpen Lib "winmm.dll" Alias "midiStreamOpen" (phms As Long, puDeviceID As Long, ByVal cMidi As Long, ByVal dwCallback As Long, ByVal dwInstance As Long, ByVal fdwOpen As Long) As Long
Declare Function midiStreamClose Lib "winmm.dll" Alias "midiStreamClose" (ByVal hms As Long) As Long
Declare Function midiStreamProperty Lib "winmm.dll" Alias "midiStreamProperty" (ByVal hms As Long, lppropdata As Byte, ByVal dwProperty As Long) As Long
Declare Function midiStreamPosition Lib "winmm.dll" Alias "midiStreamPosition" (ByVal hms As Long, lpmmt As MMTIME, ByVal cbmmt As Long) As Long
Declare Function midiStreamOut Lib "winmm.dll" Alias "midiStreamOut" (ByVal hms As Long, pmh As MIDIHDR, ByVal cbmh As Long) As Long
Declare Function midiStreamPause Lib "winmm.dll" Alias "midiStreamPause" (ByVal hms As Long) As Long
Declare Function midiStreamRestart Lib "winmm.dll" Alias "midiStreamRestart" (ByVal hms As Long) As Long
Declare Function midiStreamStop Lib "winmm.dll" Alias "midiStreamStop" (ByVal hms As Long) As Long
Declare Function midiConnect Lib "winmm.dll" Alias "midiConnect" (ByVal hmi As Long, ByVal hmo As Long, pReserved As Any) As Long
Declare Function midiDisconnect Lib "winmm.dll" Alias "midiDisconnect" (ByVal hmi As Long, ByVal hmo As Long, pReserved As Any) As Long
Type JOYINFOEX
dwSize As Long ' size of structure
dwFlags As Long ' flags to indicate what to return
dwXpos As Long ' x position
dwYpos As Long ' y position
dwZpos As Long ' z position
dwRpos As Long ' rudder/4th axis position
dwUpos As Long ' 5th axis position
dwVpos As Long ' 6th axis position
dwButtons As Long ' button states
dwButtonNumber As Long ' current button number pressed
dwPOV As Long ' point of view state
dwReserved1 As Long ' reserved for communication between winmm driver
dwReserved2 As Long ' reserved for future expansion
End Type
' Installable driver support
' Driver messages
Public Const DRV_LOAD = &H1
Public Const DRV_ENABLE = &H2
Public Const DRV_OPEN = &H3
Public Const DRV_CLOSE = &H4
Public Const DRV_DISABLE = &H5
Public Const DRV_FREE = &H6
Public Const DRV_CONFIGURE = &H7
Public Const DRV_QUERYCONFIGURE = &H8
Public Const DRV_INSTALL = &H9
Public Const DRV_REMOVE = &HA
Public Const DRV_EXITSESSION = &HB
Public Const DRV_POWER = &HF
Public Const DRV_RESERVED = &H800
Public Const DRV_USER = &H4000
Type DRVCONFIGINFO
dwDCISize As Long
lpszDCISectionName As String
lpszDCIAliasName As String
dnDevNode As Long
End Type
' Supported return values for DRV_CONFIGURE message
Public Const DRVCNF_CANCEL = &H0
Public Const DRVCNF_OK = &H1
Public Const DRVCNF_RESTART = &H2
' return values from DriverProc() function
Public Const DRV_CANCEL = DRVCNF_CANCEL
Public Const DRV_OK = DRVCNF_OK
Public Const DRV_RESTART = DRVCNF_RESTART
Declare Function CloseDriver Lib "winmm.dll" Alias "CloseDriver" (ByVal hDriver As Long, ByVal lParam1 As Long, ByVal lParam2 As Long) As Long
Declare Function OpenDriver Lib "winmm.dll" Alias "OpenDriver" (ByVal szDriverName As String, ByVal szSectionName As String, ByVal lParam2 As Long) As Long
Declare Function SendDriverMessage Lib "winmm.dll" Alias "SendDriverMessage" (ByVal hDriver As Long, ByVal message As Long, ByVal lParam1 As Long, ByVal lParam2 As Long) As Long
Declare Function DrvGetModuleHandle Lib "winmm.dll" Alias "DrvGetModuleHandle" (ByVal hDriver As Long) As Long
Declare Function GetDriverModuleHandle Lib "winmm.dll" Alias "GetDriverModuleHandle" (ByVal hDriver As Long) As Long
Declare Function DefDriverProc Lib "winmm.dll" Alias "DefDriverProc" (ByVal dwDriverIdentifier As Long, ByVal hdrvr As Long, ByVal uMsg As Long, ByVal lParam1 As Long, ByVal lParam2 As Long) As Long
Public Const DRV_MCI_FIRST = DRV_RESERVED
Public Const DRV_MCI_LAST = DRV_RESERVED + &HFFF
' Driver callback support
' flags used with waveOutOpen(), waveInOpen(), midiInOpen(), and
' midiOutOpen() to specify the type of the dwCallback parameter.
Public Const CALLBACK_TYPEMASK = &H70000 ' callback type mask
Public Const CALLBACK_NULL = &H0 ' no callback
Public Const CALLBACK_WINDOW = &H10000 ' dwCallback is a HWND
Public Const CALLBACK_TASK = &H20000 ' dwCallback is a HTASK
Public Const CALLBACK_FUNCTION = &H30000 ' dwCallback is a FARPROC
' manufacturer IDs
Public Const MM_MICROSOFT = 1 ' Microsoft Corp.
' product IDs
Public Const MM_MIDI_MAPPER = 1 ' MIDI Mapper
Public Const MM_WAVE_MAPPER = 2 ' Wave Mapper
Public Const MM_SNDBLST_MIDIOUT = 3 ' Sound Blaster MIDI output port
Public Const MM_SNDBLST_MIDIIN = 4 ' Sound Blaster MIDI input port
Public Const MM_SNDBLST_SYNTH = 5 ' Sound Blaster internal synthesizer
Public Const MM_SNDBLST_WAVEOUT = 6 ' Sound Blaster waveform output
Public Const MM_SNDBLST_WAVEIN = 7 ' Sound Blaster waveform input
Public Const MM_ADLIB = 9 ' Ad Lib-compatible synthesizer
Public Const MM_MPU401_MIDIOUT = 10 ' MPU401-compatible MIDI output port
Public Const MM_MPU401_MIDIIN = 11 ' MPU401-compatible MIDI input port
Public Const MM_PC_JOYSTICK = 12 ' Joystick adapter
Declare Function mmsystemGetVersion Lib "winmm.dll" Alias "mmsystemGetVersion" () As Long
Declare Sub OutputDebugStr Lib "winmm.dll" Alias "OutputDebugStr" (ByVal lpszOutputString As String)
Declare Function sndPlaySound Lib "winmm.dll" Alias "sndPlaySoundA" (ByVal lpszSoundName As String, ByVal uFlags As Long) As Long
' flag values for uFlags parameter
Public Const SND_SYNC = &H0 ' play synchronously (default)
Public Const SND_ASYNC = &H1 ' play asynchronously
Public Const SND_NODEFAULT = &H2 ' silence not default, if sound not found
Public Const SND_MEMORY = &H4 ' lpszSoundName points to a memory file
Public Const SND_ALIAS = &H10000 ' name is a WIN.INI [sounds] entry
Public Const SND_FILENAME = &H20000 ' name is a file name
Public Const SND_RESOURCE = &H40004 ' name is a resource name or atom
Public Const SND_ALIAS_ID = &H110000 ' name is a WIN.INI [sounds] entry identifier
Public Const SND_ALIAS_START = 0 ' must be > 4096 to keep strings in same section of resource file
Public Const SND_LOOP = &H8 ' loop the sound until next sndPlaySound
Public Const SND_NOSTOP = &H10 ' don't stop any currently playing sound
Public Const SND_VALID = &H1F ' valid flags / ;Internal /
Public Const SND_NOWAIT = &H2000 ' don't wait if the driver is busy
Public Const SND_VALIDFLAGS = &H17201F ' Set of valid flag bits. Anything outside
' this range will raise an error
Public Const SND_RESERVED = &HFF000000 ' In particular these flags are reserved
Public Const SND_TYPE_MASK = &H170007
Declare Function PlaySound Lib "winmm.dll" Alias "PlaySoundA" (ByVal lpszName As String, ByVal hModule As Long, ByVal dwFlags As Long) As Long
' waveform audio error return values
Public Const WAVERR_BADFORMAT = (WAVERR_BASE + 0) ' unsupported wave format
Public Const WAVERR_STILLPLAYING = (WAVERR_BASE + 1) ' still something playing
Public Const WAVERR_UNPREPARED = (WAVERR_BASE + 2) ' header not prepared
Public Const WAVERR_SYNC = (WAVERR_BASE + 3) ' device is synchronous
Public Const WAVERR_LASTERROR = (WAVERR_BASE + 3) ' last error in range
' wave callback messages
Public Const WOM_OPEN = MM_WOM_OPEN
Public Const WOM_CLOSE = MM_WOM_CLOSE
Public Const WOM_DONE = MM_WOM_DONE
Public Const WIM_OPEN = MM_WIM_OPEN
Public Const WIM_CLOSE = MM_WIM_CLOSE
Public Const WIM_DATA = MM_WIM_DATA
' device ID for wave device mapper
Public Const WAVE_MAPPER = -1&
' flags for dwFlags parameter in waveOutOpen() and waveInOpen()
Public Const WAVE_ALLOWSYNC = &H2
Public Const WAVE_VALID = &H3 ' ;Internal
Type WAVEHDR
lpData As String
dwBufferLength As Long
dwBytesRecorded As Long
dwUser As Long
dwFlags As Long
dwLoops As Long
lpNext As Long
Reserved As Long
End Type
' flags for dwFlags field of WAVEHDR
Public Const WHDR_DONE = &H1 ' done bit
Public Const WHDR_PREPARED = &H2 ' set if this header has been prepared
Public Const WHDR_BEGINLOOP = &H4 ' loop start block
Public Const WHDR_ENDLOOP = &H8 ' loop end block
Public Const WHDR_INQUEUE = &H10 ' reserved for driver
Public Const WHDR_VALID = &H1F ' valid flags / ;Internal /
Type WAVEOUTCAPS
wMid As Integer
wPid As Integer
vDriverVersion As Long
szPname As String * MAXPNAMELEN
dwFormats As Long
wChannels As Integer
dwSupport As Long
End Type
' flags for dwSupport field of WAVEOUTCAPS
Public Const WAVECAPS_PITCH = &H1 ' supports pitch control
Public Const WAVECAPS_PLAYBACKRATE = &H2 ' supports playback rate control
Public Const WAVECAPS_VOLUME = &H4 ' supports volume control
Public Const WAVECAPS_LRVOLUME = &H8 ' separate left-right volume control
Public Const WAVECAPS_SYNC = &H10
Type WAVEINCAPS
wMid As Integer
wPid As Integer
vDriverVersion As Long
szPname As String * MAXPNAMELEN
dwFormats As Long
wChannels As Integer
End Type
' defines for dwFormat field of WAVEINCAPS and WAVEOUTCAPS
Public Const WAVE_INVALIDFORMAT = &H0 ' invalid format
Public Const WAVE_FORMAT_1M08 = &H1 ' 11.025 kHz, Mono, 8-bit
Public Const WAVE_FORMAT_1S08 = &H2 ' 11.025 kHz, Stereo, 8-bit
Public Const WAVE_FORMAT_1M16 = &H4 ' 11.025 kHz, Mono, 16-bit
Public Const WAVE_FORMAT_1S16 = &H8 ' 11.025 kHz, Stereo, 16-bit
Public Const WAVE_FORMAT_2M08 = &H10 ' 22.05 kHz, Mono, 8-bit
Public Const WAVE_FORMAT_2S08 = &H20 ' 22.05 kHz, Stereo, 8-bit
Public Const WAVE_FORMAT_2M16 = &H40 ' 22.05 kHz, Mono, 16-bit
Public Const WAVE_FORMAT_2S16 = &H80 ' 22.05 kHz, Stereo, 16-bit
Public Const WAVE_FORMAT_4M08 = &H100 ' 44.1 kHz, Mono, 8-bit
Public Const WAVE_FORMAT_4S08 = &H200 ' 44.1 kHz, Stereo, 8-bit
Public Const WAVE_FORMAT_4M16 = &H400 ' 44.1 kHz, Mono, 16-bit
Public Const WAVE_FORMAT_4S16 = &H800 ' 44.1 kHz, Stereo, 16-bit
' flags for wFormatTag field of WAVEFORMAT
Public Const WAVE_FORMAT_PCM = 1 ' Needed in resource files so outside #ifndef RC_INVOKED
Type WAVEFORMAT
wFormatTag As Integer
nChannels As Integer
nSamplesPerSec As Long
nAvgBytesPerSec As Long
nBlockAlign As Integer
End Type
Type PCMWAVEFORMAT
wf As WAVEFORMAT
wBitsPerSample As Integer
End Type
Declare Function waveOutGetNumDevs Lib "winmm.dll" Alias "waveOutGetNumDevs" () As Long
Declare Function waveOutGetDevCaps Lib "winmm.dll" Alias "waveOutGetDevCapsA" (ByVal uDeviceID As Long, lpCaps As WAVEOUTCAPS, ByVal uSize As Long) As Long
Declare Function waveOutGetVolume Lib "winmm.dll" Alias "waveOutGetVolume" (ByVal uDeviceID As Long, lpdwVolume As Long) As Long
Declare Function waveOutSetVolume Lib "winmm.dll" Alias "waveOutSetVolume" (ByVal uDeviceID As Long, ByVal dwVolume As Long) As Long
Declare Function waveOutGetErrorText Lib "winmm.dll" Alias "waveOutGetErrorTextA" (ByVal err As Long, ByVal lpText As String, ByVal uSize As Long) As Long
Declare Function waveOutOpen Lib "winmm.dll" Alias "waveOutOpen" (lphWaveOut As Long, ByVal uDeviceID As Long, lpFormat As WAVEFORMAT, ByVal dwCallback As Long, ByVal dwInstance As Long, ByVal dwFlags As Long) As Long
Declare Function waveOutClose Lib "winmm.dll" Alias "waveOutClose" (ByVal hWaveOut As Long) As Long
Declare Function waveOutPrepareHeader Lib "winmm.dll" Alias "waveOutPrepareHeader" (ByVal hWaveOut As Long, lpWaveOutHdr As WAVEHDR, ByVal uSize As Long) As Long
Declare Function waveOutUnprepareHeader Lib "winmm.dll" Alias "waveOutUnprepareHeader" (ByVal hWaveOut As Long, lpWaveOutHdr As WAVEHDR, ByVal uSize As Long) As Long
Declare Function waveOutWrite Lib "winmm.dll" Alias "waveOutWrite" (ByVal hWaveOut As Long, lpWaveOutHdr As WAVEHDR, ByVal uSize As Long) As Long
Declare Function waveOutPause Lib "winmm.dll" Alias "waveOutPause" (ByVal hWaveOut As Long) As Long
Declare Function waveOutRestart Lib "winmm.dll" Alias "waveOutRestart" (ByVal hWaveOut As Long) As Long
Declare Function waveOutReset Lib "winmm.dll" Alias "waveOutReset" (ByVal hWaveOut As Long) As Long
Declare Function waveOutBreakLoop Lib "winmm.dll" Alias "waveOutBreakLoop" (ByVal hWaveOut As Long) As Long
Declare Function waveOutGetPosition Lib "winmm.dll" Alias "waveOutGetPosition" (ByVal hWaveOut As Long, lpInfo As MMTIME, ByVal uSize As Long) As Long
Declare Function waveOutGetPitch Lib "winmm.dll" Alias "waveOutGetPitch" (ByVal hWaveOut As Long, lpdwPitch As Long) As Long
Declare Function waveOutSetPitch Lib "winmm.dll" Alias "waveOutSetPitch" (ByVal hWaveOut As Long, ByVal dwPitch As Long) As Long
Declare Function waveOutGetPlaybackRate Lib "winmm.dll" Alias "waveOutGetPlaybackRate" (ByVal hWaveOut As Long, lpdwRate As Long) As Long
Declare Function waveOutSetPlaybackRate Lib "winmm.dll" Alias "waveOutSetPlaybackRate" (ByVal hWaveOut As Long, ByVal dwRate As Long) As Long
Declare Function waveOutGetID Lib "winmm.dll" Alias "waveOutGetID" (ByVal hWaveOut As Long, lpuDeviceID As Long) As Long
Declare Function waveOutMessage Lib "winmm.dll" Alias "waveOutMessage" (ByVal hWaveOut As Long, ByVal msg As Long, ByVal dw1 As Long, ByVal dw2 As Long) As Long
Declare Function waveInGetNumDevs Lib "winmm.dll" Alias "waveInGetNumDevs" () As Long
Declare Function waveInGetDevCaps Lib "winmm.dll" Alias "waveInGetDevCapsA" (ByVal uDeviceID As Long, lpCaps As WAVEINCAPS, ByVal uSize As Long) As Long
Declare Function waveInGetErrorText Lib "winmm.dll" Alias "waveInGetErrorTextA" (ByVal err As Long, ByVal lpText As String, ByVal uSize As Long) As Long
Declare Function waveInOpen Lib "winmm.dll" Alias "waveInOpen" (lphWaveIn As Long, ByVal uDeviceID As Long, lpFormat As WAVEFORMAT, ByVal dwCallback As Long, ByVal dwInstance As Long, ByVal dwFlags As Long) As Long
Declare Function waveInClose Lib "winmm.dll" Alias "waveInClose" (ByVal hWaveIn As Long) As Long
Declare Function waveInPrepareHeader Lib "winmm.dll" Alias "waveInPrepareHeader" (ByVal hWaveIn As Long, lpWaveInHdr As WAVEHDR, ByVal uSize As Long) As Long
Declare Function waveInUnprepareHeader Lib "winmm.dll" Alias "waveInUnprepareHeader" (ByVal hWaveIn As Long, lpWaveInHdr As WAVEHDR, ByVal uSize As Long) As Long
Declare Function waveInAddBuffer Lib "winmm.dll" Alias "waveInAddBuffer" (ByVal hWaveIn As Long, lpWaveInHdr As WAVEHDR, ByVal uSize As Long) As Long
Declare Function waveInStart Lib "winmm.dll" Alias "waveInStart" (ByVal hWaveIn As Long) As Long
Declare Function waveInStop Lib "winmm.dll" Alias "waveInStop" (ByVal hWaveIn As Long) As Long
Declare Function waveInReset Lib "winmm.dll" Alias "waveInReset" (ByVal hWaveIn As Long) As Long
Declare Function waveInGetPosition Lib "winmm.dll" Alias "waveInGetPosition" (ByVal hWaveIn As Long, lpInfo As MMTIME, ByVal uSize As Long) As Long
Declare Function waveInGetID Lib "winmm.dll" Alias "waveInGetID" (ByVal hWaveIn As Long, lpuDeviceID As Long) As Long
Declare Function waveInMessage Lib "winmm.dll" Alias "waveInMessage" (ByVal hWaveIn As Long, ByVal msg As Long, ByVal dw1 As Long, ByVal dw2 As Long) As Long
' MIDI error return values
Public Const MIDIERR_UNPREPARED = (MIDIERR_BASE + 0) ' header not prepared
Public Const MIDIERR_STILLPLAYING = (MIDIERR_BASE + 1) ' still something playing
Public Const MIDIERR_NOMAP = (MIDIERR_BASE + 2) ' no current map
Public Const MIDIERR_NOTREADY = (MIDIERR_BASE + 3) ' hardware is still busy
Public Const MIDIERR_NODEVICE = (MIDIERR_BASE + 4) ' port no longer connected
Public Const MIDIERR_INVALIDSETUP = (MIDIERR_BASE + 5) ' invalid setup
Public Const MIDIERR_LASTERROR = (MIDIERR_BASE + 5) ' last error in range
' MIDI callback messages
Public Const MIM_OPEN = MM_MIM_OPEN
Public Const MIM_CLOSE = MM_MIM_CLOSE
Public Const MIM_DATA = MM_MIM_DATA
Public Const MIM_LONGDATA = MM_MIM_LONGDATA
Public Const MIM_ERROR = MM_MIM_ERROR
Public Const MIM_LONGERROR = MM_MIM_LONGERROR
Public Const MOM_OPEN = MM_MOM_OPEN
Public Const MOM_CLOSE = MM_MOM_CLOSE
Public Const MOM_DONE = MM_MOM_DONE
' device ID for MIDI mapper
Public Const MIDIMAPPER = (-1) ' Cannot be cast to DWORD as RC complains
Public Const MIDI_MAPPER = -1&
' flags for wFlags parm of midiOutCachePatches(), midiOutCacheDrumPatches()
Public Const MIDI_CACHE_ALL = 1
Public Const MIDI_CACHE_BESTFIT = 2
Public Const MIDI_CACHE_QUERY = 3
Public Const MIDI_UNCACHE = 4
Public Const MIDI_CACHE_VALID = (MIDI_CACHE_ALL Or MIDI_CACHE_BESTFIT Or MIDI_CACHE_QUERY Or MIDI_UNCACHE) ' ;Internal
Type MIDIOUTCAPS
wMid As Integer
wPid As Integer
vDriverVersion As Long
szPname As String * MAXPNAMELEN
wTechnology As Integer
wVoices As Integer
wNotes As Integer
wChannelMask As Integer
dwSupport As Long
End Type
' flags for wTechnology field of MIDIOUTCAPS structure
Public Const MOD_MIDIPORT = 1 ' output port
Public Const MOD_SYNTH = 2 ' generic internal synth
Public Const MOD_SQSYNTH = 3 ' square wave internal synth
Public Const MOD_FMSYNTH = 4 ' FM internal synth
Public Const MOD_MAPPER = 5 ' MIDI mapper
' flags for dwSupport field of MIDIOUTCAPS
Public Const MIDICAPS_VOLUME = &H1 ' supports volume control
Public Const MIDICAPS_LRVOLUME = &H2 ' separate left-right volume control
Public Const MIDICAPS_CACHE = &H4
Type MIDIINCAPS
wMid As Integer
wPid As Integer
vDriverVersion As Long
szPname As String * MAXPNAMELEN
End Type
Type MIDIHDR
lpData As String
dwBufferLength As Long
dwBytesRecorded As Long
dwUser As Long
dwFlags As Long
lpNext As Long
Reserved As Long
End Type
' flags for dwFlags field of MIDIHDR structure
Public Const MHDR_DONE = &H1 ' done bit
Public Const MHDR_PREPARED = &H2 ' set if header prepared
Public Const MHDR_INQUEUE = &H4 ' reserved for driver
Public Const MHDR_VALID = &H7 ' valid flags / ;Internal /
Declare Function midiOutGetDevCaps Lib "winmm.dll" Alias "midiOutGetDevCapsA" (ByVal uDeviceID As Long, lpCaps As MIDIOUTCAPS, ByVal uSize As Long) As Long
Declare Function midiOutGetVolume Lib "winmm.dll" Alias "midiOutGetVolume" (ByVal uDeviceID As Long, lpdwVolume As Long) As Long
Declare Function midiOutSetVolume Lib "winmm.dll" Alias "midiOutSetVolume" (ByVal uDeviceID As Long, ByVal dwVolume As Long) As Long
Declare Function midiOutGetErrorText Lib "winmm.dll" Alias "midiOutGetErrorTextA" (ByVal err As Long, ByVal lpText As String, ByVal uSize As Long) As Long
Declare Function midiOutOpen Lib "winmm.dll" Alias "midiOutOpen" (lphMidiOut As Long, ByVal uDeviceID As Long, ByVal dwCallback As Long, ByVal dwInstance As Long, ByVal dwFlags As Long) As Long
Declare Function midiOutClose Lib "winmm.dll" Alias "midiOutClose" (ByVal hMidiOut As Long) As Long
Declare Function midiOutPrepareHeader Lib "winmm.dll" Alias "midiOutPrepareHeader" (ByVal hMidiOut As Long, lpMidiOutHdr As MIDIHDR, ByVal uSize As Long) As Long
Declare Function midiOutUnprepareHeader Lib "winmm.dll" Alias "midiOutUnprepareHeader" (ByVal hMidiOut As Long, lpMidiOutHdr As MIDIHDR, ByVal uSize As Long) As Long
Declare Function midiOutShortMsg Lib "winmm.dll" Alias "midiOutShortMsg" (ByVal hMidiOut As Long, ByVal dwMsg As Long) As Long
Declare Function midiOutLongMsg Lib "winmm.dll" Alias "midiOutLongMsg" (ByVal hMidiOut As Long, lpMidiOutHdr As MIDIHDR, ByVal uSize As Long) As Long
Declare Function midiOutReset Lib "winmm.dll" Alias "midiOutReset" (ByVal hMidiOut As Long) As Long
Declare Function midiOutCachePatches Lib "winmm.dll" Alias "midiOutCachePatches" (ByVal hMidiOut As Long, ByVal uBank As Long, lpPatchArray As Long, ByVal uFlags As Long) As Long
Declare Function midiOutCacheDrumPatches Lib "winmm.dll" Alias "midiOutCacheDrumPatches" (ByVal hMidiOut As Long, ByVal uPatch As Long, lpKeyArray As Long, ByVal uFlags As Long) As Long
Declare Function midiOutGetID Lib "winmm.dll" Alias "midiOutGetID" (ByVal hMidiOut As Long, lpuDeviceID As Long) As Long
Declare Function midiOutMessage Lib "winmm.dll" Alias "midiOutMessage" (ByVal hMidiOut As Long, ByVal msg As Long, ByVal dw1 As Long, ByVal dw2 As Long) As Long
Declare Function midiInGetNumDevs Lib "winmm.dll" Alias "midiInGetNumDevs" () As Long
Declare Function midiInGetDevCaps Lib "winmm.dll" Alias "midiInGetDevCapsA" (ByVal uDeviceID As Long, lpCaps As MIDIINCAPS, ByVal uSize As Long) As Long
Declare Function midiInGetErrorText Lib "winmm.dll" Alias "midiInGetErrorTextA" (ByVal err As Long, ByVal lpText As String, ByVal uSize As Long) As Long
Declare Function midiInOpen Lib "winmm.dll" Alias "midiInOpen" (lphMidiIn As Long, ByVal uDeviceID As Long, ByVal dwCallback As Long, ByVal dwInstance As Long, ByVal dwFlags As Long) As Long
Declare Function midiInClose Lib "winmm.dll" Alias "midiInClose" (ByVal hMidiIn As Long) As Long
Declare Function midiInPrepareHeader Lib "winmm.dll" Alias "midiInPrepareHeader" (ByVal hMidiIn As Long, lpMidiInHdr As MIDIHDR, ByVal uSize As Long) As Long
Declare Function midiInUnprepareHeader Lib "winmm.dll" Alias "midiInUnprepareHeader" (ByVal hMidiIn As Long, lpMidiInHdr As MIDIHDR, ByVal uSize As Long) As Long
Declare Function midiInAddBuffer Lib "winmm.dll" Alias "midiInAddBuffer" (ByVal hMidiIn As Long, lpMidiInHdr As MIDIHDR, ByVal uSize As Long) As Long
Declare Function midiInStart Lib "winmm.dll" Alias "midiInStart" (ByVal hMidiIn As Long) As Long
Declare Function midiInStop Lib "winmm.dll" Alias "midiInStop" (ByVal hMidiIn As Long) As Long
Declare Function midiInReset Lib "winmm.dll" Alias "midiInReset" (ByVal hMidiIn As Long) As Long
Declare Function midiInGetID Lib "winmm.dll" Alias "midiInGetID" (ByVal hMidiIn As Long, lpuDeviceID As Long) As Long
Declare Function midiInMessage Lib "winmm.dll" Alias "midiInMessage" (ByVal hMidiIn As Long, ByVal msg As Long, ByVal dw1 As Long, ByVal dw2 As Long) As Long
' device ID for aux device mapper
Public Const AUX_MAPPER = -1&
Type AUXCAPS
wMid As Integer
wPid As Integer
vDriverVersion As Long
szPname As String * MAXPNAMELEN
wTechnology As Integer
dwSupport As Long
End Type
' flags for wTechnology field in AUXCAPS structure
Public Const AUXCAPS_CDAUDIO = 1 ' audio from internal CD-ROM drive
Public Const AUXCAPS_AUXIN = 2 ' audio from auxiliary input jacks
' flags for dwSupport field in AUXCAPS structure
Public Const AUXCAPS_VOLUME = &H1 ' supports volume control
Public Const AUXCAPS_LRVOLUME = &H2 ' separate left-right volume control
Declare Function auxGetNumDevs Lib "winmm.dll" Alias "auxGetNumDevs" () As Long
Declare Function auxGetDevCaps Lib "winmm.dll" Alias "auxGetDevCapsA" (ByVal uDeviceID As Long, lpCaps As AUXCAPS, ByVal uSize As Long) As Long
Declare Function auxSetVolume Lib "winmm.dll" Alias "auxSetVolume" (ByVal uDeviceID As Long, ByVal dwVolume As Long) As Long
Declare Function auxGetVolume Lib "winmm.dll" Alias "auxGetVolume" (ByVal uDeviceID As Long, lpdwVolume As Long) As Long
Declare Function auxOutMessage Lib "winmm.dll" Alias "auxOutMessage" (ByVal uDeviceID As Long, ByVal msg As Long, ByVal dw1 As Long, ByVal dw2 As Long) As Long
' timer error return values
Public Const TIMERR_NOERROR = (0) ' no error
Public Const TIMERR_NOCANDO = (TIMERR_BASE + 1) ' request not completed
Public Const TIMERR_STRUCT = (TIMERR_BASE + 33) ' time struct size
' flags for wFlags parameter of timeSetEvent() function
Public Const TIME_ONESHOT = 0 ' program timer for single event
Public Const TIME_PERIODIC = 1 ' program for continuous periodic event
Type TIMECAPS
wPeriodMin As Long
wPeriodMax As Long
End Type
Declare Function timeGetSystemTime Lib "winmm.dll" Alias "timeGetSystemTime" (lpTime As MMTIME, ByVal uSize As Long) As Long
Declare Function timeGetTime Lib "winmm.dll" Alias "timeGetTime" () As Long
Declare Function timeSetEvent Lib "winmm.dll" Alias "timeSetEvent" (ByVal uDelay As Long, ByVal uResolution As Long, ByVal lpFunction As Long, ByVal dwUser As Long, ByVal uFlags As Long) As Long
Declare Function timeKillEvent Lib "winmm.dll" Alias "timeKillEvent" (ByVal uID As Long) As Long
Declare Function timeGetDevCaps Lib "winmm.dll" Alias "timeGetDevCaps" (lpTimeCaps As TIMECAPS, ByVal uSize As Long) As Long
Declare Function timeBeginPeriod Lib "winmm.dll" Alias "timeBeginPeriod" (ByVal uPeriod As Long) As Long
Declare Function timeEndPeriod Lib "winmm.dll" Alias "timeEndPeriod" (ByVal uPeriod As Long) As Long
' joystick error return values
Public Const JOYERR_NOERROR = (0) ' no error
Public Const JOYERR_PARMS = (JOYERR_BASE + 5) ' bad parameters
Public Const JOYERR_NOCANDO = (JOYERR_BASE + 6) ' request not completed
Public Const JOYERR_UNPLUGGED = (JOYERR_BASE + 7) ' joystick is unplugged
' constants used with JOYINFO structure and MM_JOY messages
Public Const JOY_BUTTON1 = &H1
Public Const JOY_BUTTON2 = &H2
Public Const JOY_BUTTON3 = &H4
Public Const JOY_BUTTON4 = &H8
Public Const JOY_BUTTON1CHG = &H100
Public Const JOY_BUTTON2CHG = &H200
Public Const JOY_BUTTON3CHG = &H400
Public Const JOY_BUTTON4CHG = &H800
' joystick ID constants
Public Const JOYSTICKID1 = 0
Public Const JOYSTICKID2 = 1
Type JOYCAPS
wMid As Integer
wPid As Integer
szPname As String * MAXPNAMELEN
wXmin As Integer
wXmax As Integer
wYmin As Integer
wYmax As Integer
wZmin As Integer
wZmax As Integer
wNumButtons As Integer
wPeriodMin As Integer
wPeriodMax As Integer
End Type
Type JOYINFO
wXpos As Integer
wYpos As Integer
wZpos As Integer
wButtons As Integer
End Type
Declare Function joyGetDevCaps Lib "winmm.dll" Alias "joyGetDevCapsA" (ByVal id As Long, lpCaps As JOYCAPS, ByVal uSize As Long) As Long
Declare Function joyGetNumDevs Lib "winmm.dll" Alias "joyGetNumDev" () As Long
Declare Function joyGetThreshold Lib "winmm.dll" Alias "joyGetThreshold" (ByVal id As Long, lpuThreshold As Long) As Long
Declare Function joyReleaseCapture Lib "winmm.dll" Alias "joyReleaseCapture" (ByVal id As Long) As Long
Declare Function joySetCapture Lib "winmm.dll" Alias "joySetCapture" (ByVal hwnd As Long, ByVal uID As Long, ByVal uPeriod As Long, ByVal bChanged As Long) As Long
Declare Function joySetThreshold Lib "winmm.dll" Alias "joySetThreshold" (ByVal id As Long, ByVal uThreshold As Long) As Long
' MMIO error return values
Public Const MMIOERR_BASE = 256
Public Const MMIOERR_FILENOTFOUND = (MMIOERR_BASE + 1) ' file not found
Public Const MMIOERR_OUTOFMEMORY = (MMIOERR_BASE + 2) ' out of memory
Public Const MMIOERR_CANNOTOPEN = (MMIOERR_BASE + 3) ' cannot open
Public Const MMIOERR_CANNOTCLOSE = (MMIOERR_BASE + 4) ' cannot close
Public Const MMIOERR_CANNOTREAD = (MMIOERR_BASE + 5) ' cannot read
Public Const MMIOERR_CANNOTWRITE = (MMIOERR_BASE + 6) ' cannot write
Public Const MMIOERR_CANNOTSEEK = (MMIOERR_BASE + 7) ' cannot seek
Public Const MMIOERR_CANNOTEXPAND = (MMIOERR_BASE + 8) ' cannot expand file
Public Const MMIOERR_CHUNKNOTFOUND = (MMIOERR_BASE + 9) ' chunk not found
Public Const MMIOERR_UNBUFFERED = (MMIOERR_BASE + 10) ' file is unbuffered
' MMIO constants
Public Const CFSEPCHAR = "+" ' compound file name separator char.
Type MMIOINFO
dwFlags As Long
fccIOProc As Long
pIOProc As Long
wErrorRet As Long
htask As Long
cchBuffer As Long
pchBuffer As String
pchNext As String
pchEndRead As String
pchEndWrite As String
lBufOffset As Long
lDiskOffset As Long
adwInfo(4) As Long
dwReserved1 As Long
dwReserved2 As Long
hmmio As Long
End Type
Public Const MMIO_RWMODE = &H3 ' mask to get bits used for opening
' file for reading/writing/both
Public Const MMIO_SHAREMODE = &H70 ' file sharing mode number
' constants for dwFlags field of MMIOINFO
Public Const MMIO_CREATE = &H1000 ' create new file (or truncate file)
Public Const MMIO_PARSE = &H100 ' parse new file returning path
Public Const MMIO_DELETE = &H200 ' create new file (or truncate file)
Public Const MMIO_EXIST = &H4000 ' checks for existence of file
Public Const MMIO_ALLOCBUF = &H10000 ' mmioOpen() should allocate a buffer
Public Const MMIO_GETTEMP = &H20000 ' mmioOpen() should retrieve temp name
Public Const MMIO_DIRTY = &H10000000 ' I/O buffer is dirty
' MMIO_DIRTY is also used in the <dwFlags> field of MMCKINFO structure
Public Const MMIO_OPEN_VALID = &H3FFFF ' valid flags for mmioOpen / ;Internal /
' read/write mode numbers (bit field MMIO_RWMODE)
Public Const MMIO_READ = &H0 ' open file for reading only
Public Const MMIO_WRITE = &H1 ' open file for writing only
Public Const MMIO_READWRITE = &H2 ' open file for reading and writing
' share mode numbers (bit field MMIO_SHAREMODE)
Public Const MMIO_COMPAT = &H0 ' compatibility mode
Public Const MMIO_EXCLUSIVE = &H10 ' exclusive-access mode
Public Const MMIO_DENYWRITE = &H20 ' deny writing to other processes
Public Const MMIO_DENYREAD = &H30 ' deny reading to other processes
Public Const MMIO_DENYNONE = &H40 ' deny nothing to other processes
' flags for other functions
Public Const MMIO_FHOPEN = &H10 ' mmioClose(): keep file handle open
Public Const MMIO_EMPTYBUF = &H10 ' mmioFlush(): empty the I/O buffer
Public Const MMIO_TOUPPER = &H10 ' mmioStringToFOURCC(): cvt. to u-case
Public Const MMIO_INSTALLPROC = &H10000 ' mmioInstallIOProc(): install MMIOProc
Public Const MMIO_PUBLICPROC = &H10000000 ' mmioInstallIOProc: install Globally
Public Const MMIO_UNICODEPROC = &H1000000 ' mmioInstallIOProc(): Unicode MMIOProc
Public Const MMIO_REMOVEPROC = &H20000 ' mmioInstallIOProc(): remove MMIOProc
Public Const MMIO_FINDPROC = &H40000 ' mmioInstallIOProc(): find an MMIOProc
Public Const MMIO_FINDCHUNK = &H10 ' mmioDescend(): find a chunk by ID
Public Const MMIO_FINDRIFF = &H20 ' mmioDescend(): find a LIST chunk
Public Const MMIO_FINDLIST = &H40 ' mmioDescend(): find a RIFF chunk
Public Const MMIO_CREATERIFF = &H20 ' mmioCreateChunk(): make a LIST chunk
Public Const MMIO_CREATELIST = &H40 ' mmioCreateChunk(): make a RIFF chunk
Public Const MMIO_VALIDPROC = &H11070000 ' valid for mmioInstallIOProc / ;Internal /
' message numbers for MMIOPROC I/O procedure functions
Public Const MMIOM_READ = MMIO_READ ' read (must equal MMIO_READ!)
Public Const MMIOM_WRITE = MMIO_WRITE ' write (must equal MMIO_WRITE!)
Public Const MMIOM_SEEK = 2 ' seek to a new position in file
Public Const MMIOM_OPEN = 3 ' open file
Public Const MMIOM_CLOSE = 4 ' close file
Public Const MMIOM_WRITEFLUSH = 5 ' write and flush
Public Const MMIOM_RENAME = 6 ' rename specified file
Public Const MMIOM_USER = &H8000 ' beginning of user-defined messages
' flags for mmioSeek()
Public Const SEEK_SET = 0 ' seek to an absolute position
Public Const SEEK_CUR = 1 ' seek relative to current position
Public Const SEEK_END = 2 ' seek relative to end of file
' other constants
Public Const MMIO_DEFAULTBUFFER = 8192 ' default buffer size
Type MMCKINFO
ckid As Long
ckSize As Long
fccType As Long
dwDataOffset As Long
dwFlags As Long
End Type
Declare Function mmioStringToFOURCC Lib "winmm.dll" Alias "mmioStringToFOURCCA" (ByVal sz As String, ByVal uFlags As Long) As Long
Declare Function mmioOpen Lib "winmm.dll" Alias "mmioOpenA" (ByVal szFileName As String, lpmmioinfo As MMIOINFO, ByVal dwOpenFlags As Long) As Long
Declare Function mmioRename Lib "winmm.dll" Alias "mmioRenameA" (ByVal szFileName As String, ByVal SzNewFileName As String, lpmmioinfo As MMIOINFO, ByVal dwRenameFlags As Long) As Long
Declare Function mmioClose Lib "winmm.dll" Alias "mmioClose" (ByVal hmmio As Long, ByVal uFlags As Long) As Long
Declare Function mmioRead Lib "winmm.dll" Alias "mmioRead" (ByVal hmmio As Long, ByVal pch As String, ByVal cch As Long) As Long
Declare Function mmioWrite Lib "winmm.dll" Alias "mmioWrite" (ByVal hmmio As Long, ByVal pch As String, ByVal cch As Long) As Long
Declare Function mmioSeek Lib "winmm.dll" Alias "mmioSeek" (ByVal hmmio As Long, ByVal lOffset As Long, ByVal iOrigin As Long) As Long
Declare Function mmioGetInfo Lib "winmm.dll" Alias "mmioGetInfo" (ByVal hmmio As Long, lpmmioinfo As MMIOINFO, ByVal uFlags As Long) As Long
Declare Function mmioSetInfo Lib "winmm.dll" Alias "mmioSetInfo" (ByVal hmmio As Long, lpmmioinfo As MMIOINFO, ByVal uFlags As Long) As Long
Declare Function mmioSetBuffer Lib "winmm.dll" Alias "mmioSetBuffer" (ByVal hmmio As Long, ByVal pchBuffer As String, ByVal cchBuffer As Long, ByVal uFlags As Long) As Long
Declare Function mmioFlush Lib "winmm.dll" Alias "mmioFlush" (ByVal hmmio As Long, ByVal uFlags As Long) As Long
Declare Function mmioAdvance Lib "winmm.dll" Alias "mmioAdvance" (ByVal hmmio As Long, lpmmioinfo As MMIOINFO, ByVal uFlags As Long) As Long
Declare Function mmioSendMessage Lib "winmm.dll" Alias "mmioSendMessage" (ByVal hmmio As Long, ByVal uMsg As Long, ByVal lParam1 As Long, ByVal lParam2 As Long) As Long
Declare Function mmioDescend Lib "winmm.dll" Alias "mmioDescend" (ByVal hmmio As Long, lpck As MMCKINFO, lpckParent As MMCKINFO, ByVal uFlags As Long) As Long
Declare Function mmioAscend Lib "winmm.dll" Alias "mmioAscend" (ByVal hmmio As Long, lpck As MMCKINFO, ByVal uFlags As Long) As Long
Declare Function mmioCreateChunk Lib "winmm.dll" Alias "mmioCreateChunk" (ByVal hmmio As Long, lpck As MMCKINFO, ByVal uFlags As Long) As Long
' MCI functions
Declare Function mciSendCommand Lib "winmm.dll" Alias "mciSendCommandA" (ByVal wDeviceID As Long, ByVal uMessage As Long, ByVal dwParam1 As Long, ByVal dwParam2 As Any) As Long
Declare Function mciSendString Lib "winmm.dll" Alias "mciSendStringA" (ByVal lpstrCommand As String, ByVal lpstrReturnString As String, ByVal uReturnLength As Long, ByVal hwndCallback As Long) As Long
Declare Function mciGetCreatorTask Lib "winmm.dll" Alias "mciGetCreatorTask" (ByVal wDeviceID As Long) As Long
Declare Function mciGetDeviceID Lib "winmm.dll" Alias "mciGetDeviceIDA" (ByVal lpstrName As String) As Long
Declare Function mciGetDeviceIDFromElementID Lib "winmm.dll" Alias "mciGetDeviceIDFromElementIDA" (ByVal dwElementID As Long, ByVal lpstrType As String) As Long
Declare Function mciGetErrorString Lib "winmm.dll" Alias "mciGetErrorStringA" (ByVal dwError As Long, ByVal lpstrBuffer As String, ByVal uLength As Long) As Long
Declare Function mciExecute Lib "winmm.dll" Alias "mciExecute" (ByVal lpstrCommand As String) As Long
' MCI error return values
Public Const MCIERR_INVALID_DEVICE_ID = (MCIERR_BASE + 1)
Public Const MCIERR_UNRECOGNIZED_KEYWORD = (MCIERR_BASE + 3)
Public Const MCIERR_UNRECOGNIZED_COMMAND = (MCIERR_BASE + 5)
Public Const MCIERR_HARDWARE = (MCIERR_BASE + 6)
Public Const MCIERR_INVALID_DEVICE_NAME = (MCIERR_BASE + 7)
Public Const MCIERR_OUT_OF_MEMORY = (MCIERR_BASE + 8)
Public Const MCIERR_DEVICE_OPEN = (MCIERR_BASE + 9)
Public Const MCIERR_CANNOT_LOAD_DRIVER = (MCIERR_BASE + 10)
Public Const MCIERR_MISSING_COMMAND_STRING = (MCIERR_BASE + 11)
Public Const MCIERR_PARAM_OVERFLOW = (MCIERR_BASE + 12)
Public Const MCIERR_MISSING_STRING_ARGUMENT = (MCIERR_BASE + 13)
Public Const MCIERR_BAD_INTEGER = (MCIERR_BASE + 14)
Public Const MCIERR_PARSER_INTERNAL = (MCIERR_BASE + 15)
Public Const MCIERR_DRIVER_INTERNAL = (MCIERR_BASE + 16)
Public Const MCIERR_MISSING_PARAMETER = (MCIERR_BASE + 17)
Public Const MCIERR_UNSUPPORTED_FUNCTION = (MCIERR_BASE + 18)
Public Const MCIERR_FILE_NOT_FOUND = (MCIERR_BASE + 19)
Public Const MCIERR_DEVICE_NOT_READY = (MCIERR_BASE + 20)
Public Const MCIERR_INTERNAL = (MCIERR_BASE + 21)
Public Const MCIERR_DRIVER = (MCIERR_BASE + 22)
Public Const MCIERR_CANNOT_USE_ALL = (MCIERR_BASE + 23)
Public Const MCIERR_MULTIPLE = (MCIERR_BASE + 24)
Public Const MCIERR_EXTENSION_NOT_FOUND = (MCIERR_BASE + 25)
Public Const MCIERR_OUTOFRANGE = (MCIERR_BASE + 26)
Public Const MCIERR_FLAGS_NOT_COMPATIBLE = (MCIERR_BASE + 28)
Public Const MCIERR_FILE_NOT_SAVED = (MCIERR_BASE + 30)
Public Const MCIERR_DEVICE_TYPE_REQUIRED = (MCIERR_BASE + 31)
Public Const MCIERR_DEVICE_LOCKED = (MCIERR_BASE + 32)
Public Const MCIERR_DUPLICATE_ALIAS = (MCIERR_BASE + 33)
Public Const MCIERR_BAD_CONSTANT = (MCIERR_BASE + 34)
Public Const MCIERR_MUST_USE_SHAREABLE = (MCIERR_BASE + 35)
Public Const MCIERR_MISSING_DEVICE_NAME = (MCIERR_BASE + 36)
Public Const MCIERR_BAD_TIME_FORMAT = (MCIERR_BASE + 37)
Public Const MCIERR_NO_CLOSING_QUOTE = (MCIERR_BASE + 38)
Public Const MCIERR_DUPLICATE_FLAGS = (MCIERR_BASE + 39)
Public Const MCIERR_INVALID_FILE = (MCIERR_BASE + 40)
Public Const MCIERR_NULL_PARAMETER_BLOCK = (MCIERR_BASE + 41)
Public Const MCIERR_UNNAMED_RESOURCE = (MCIERR_BASE + 42)
Public Const MCIERR_NEW_REQUIRES_ALIAS = (MCIERR_BASE + 43)
Public Const MCIERR_NOTIFY_ON_AUTO_OPEN = (MCIERR_BASE + 44)
Public Const MCIERR_NO_ELEMENT_ALLOWED = (MCIERR_BASE + 45)
Public Const MCIERR_NONAPPLICABLE_FUNCTION = (MCIERR_BASE + 46)
Public Const MCIERR_ILLEGAL_FOR_AUTO_OPEN = (MCIERR_BASE + 47)
Public Const MCIERR_FILENAME_REQUIRED = (MCIERR_BASE + 48)
Public Const MCIERR_EXTRA_CHARACTERS = (MCIERR_BASE + 49)
Public Const MCIERR_DEVICE_NOT_INSTALLED = (MCIERR_BASE + 50)
Public Const MCIERR_GET_CD = (MCIERR_BASE + 51)
Public Const MCIERR_SET_CD = (MCIERR_BASE + 52)
Public Const MCIERR_SET_DRIVE = (MCIERR_BASE + 53)
Public Const MCIERR_DEVICE_LENGTH = (MCIERR_BASE + 54)
Public Const MCIERR_DEVICE_ORD_LENGTH = (MCIERR_BASE + 55)
Public Const MCIERR_NO_INTEGER = (MCIERR_BASE + 56)
Public Const MCIERR_WAVE_OUTPUTSINUSE = (MCIERR_BASE + 64)
Public Const MCIERR_WAVE_SETOUTPUTINUSE = (MCIERR_BASE + 65)
Public Const MCIERR_WAVE_INPUTSINUSE = (MCIERR_BASE + 66)
Public Const MCIERR_WAVE_SETINPUTINUSE = (MCIERR_BASE + 67)
Public Const MCIERR_WAVE_OUTPUTUNSPECIFIED = (MCIERR_BASE + 68)
Public Const MCIERR_WAVE_INPUTUNSPECIFIED = (MCIERR_BASE + 69)
Public Const MCIERR_WAVE_OUTPUTSUNSUITABLE = (MCIERR_BASE + 70)
Public Const MCIERR_WAVE_SETOUTPUTUNSUITABLE = (MCIERR_BASE + 71)
Public Const MCIERR_WAVE_INPUTSUNSUITABLE = (MCIERR_BASE + 72)
Public Const MCIERR_WAVE_SETINPUTUNSUITABLE = (MCIERR_BASE + 73)
Public Const MCIERR_SEQ_DIV_INCOMPATIBLE = (MCIERR_BASE + 80)
Public Const MCIERR_SEQ_PORT_INUSE = (MCIERR_BASE + 81)
Public Const MCIERR_SEQ_PORT_NONEXISTENT = (MCIERR_BASE + 82)
Public Const MCIERR_SEQ_PORT_MAPNODEVICE = (MCIERR_BASE + 83)
Public Const MCIERR_SEQ_PORT_MISCERROR = (MCIERR_BASE + 84)
Public Const MCIERR_SEQ_TIMER = (MCIERR_BASE + 85)
Public Const MCIERR_SEQ_PORTUNSPECIFIED = (MCIERR_BASE + 86)
Public Const MCIERR_SEQ_NOMIDIPRESENT = (MCIERR_BASE + 87)
Public Const MCIERR_NO_WINDOW = (MCIERR_BASE + 90)
Public Const MCIERR_CREATEWINDOW = (MCIERR_BASE + 91)
Public Const MCIERR_FILE_READ = (MCIERR_BASE + 92)
Public Const MCIERR_FILE_WRITE = (MCIERR_BASE + 93)
' All custom device driver errors must be >= this value
Public Const MCIERR_CUSTOM_DRIVER_BASE = (MCIERR_BASE + 256)
' Message numbers must be in the range between MCI_FIRST and MCI_LAST
Public Const MCI_FIRST = &H800
' Messages 0x801 and 0x802 are reserved
Public Const MCI_OPEN = &H803
Public Const MCI_CLOSE = &H804
Public Const MCI_ESCAPE = &H805
Public Const MCI_PLAY = &H806
Public Const MCI_SEEK = &H807
Public Const MCI_STOP = &H808
Public Const MCI_PAUSE = &H809
Public Const MCI_INFO = &H80A
Public Const MCI_GETDEVCAPS = &H80B
Public Const MCI_SPIN = &H80C
Public Const MCI_SET = &H80D
Public Const MCI_STEP = &H80E
Public Const MCI_RECORD = &H80F
Public Const MCI_SYSINFO = &H810
Public Const MCI_BREAK = &H811
Public Const MCI_SOUND = &H812
Public Const MCI_SAVE = &H813
Public Const MCI_STATUS = &H814
Public Const MCI_CUE = &H830
Public Const MCI_REALIZE = &H840
Public Const MCI_WINDOW = &H841
Public Const MCI_PUT = &H842
Public Const MCI_WHERE = &H843
Public Const MCI_FREEZE = &H844
Public Const MCI_UNFREEZE = &H845
Public Const MCI_LOAD = &H850
Public Const MCI_CUT = &H851
Public Const MCI_COPY = &H852
Public Const MCI_PASTE = &H853
Public Const MCI_UPDATE = &H854
Public Const MCI_RESUME = &H855
Public Const MCI_DELETE = &H856
Public Const MCI_LAST = &HFFF
' the next 0x400 message ID's are reserved for custom drivers
' all custom MCI command messages must be >= than this value
Public Const MCI_USER_MESSAGES = (&H400 + MCI_FIRST)
Public Const MCI_ALL_DEVICE_ID = - 1 ' Matches all MCI devices
' constants for predefined MCI device types
Public Const MCI_DEVTYPE_VCR = 513
Public Const MCI_DEVTYPE_VIDEODISC = 514
Public Const MCI_DEVTYPE_OVERLAY = 515
Public Const MCI_DEVTYPE_CD_AUDIO = 516
Public Const MCI_DEVTYPE_DAT = 517
Public Const MCI_DEVTYPE_SCANNER = 518
Public Const MCI_DEVTYPE_ANIMATION = 519
Public Const MCI_DEVTYPE_DIGITAL_VIDEO = 520
Public Const MCI_DEVTYPE_OTHER = 521
Public Const MCI_DEVTYPE_WAVEFORM_AUDIO = 522
Public Const MCI_DEVTYPE_SEQUENCER = 523
Public Const MCI_DEVTYPE_FIRST = MCI_DEVTYPE_VCR
Public Const MCI_DEVTYPE_LAST = MCI_DEVTYPE_SEQUENCER
Public Const MCI_DEVTYPE_FIRST_USER = &H1000
' return values for 'status mode' command
Public Const MCI_MODE_NOT_READY = (MCI_STRING_OFFSET + 12)
Public Const MCI_MODE_STOP = (MCI_STRING_OFFSET + 13)
Public Const MCI_MODE_PLAY = (MCI_STRING_OFFSET + 14)
Public Const MCI_MODE_RECORD = (MCI_STRING_OFFSET + 15)
Public Const MCI_MODE_SEEK = (MCI_STRING_OFFSET + 16)
Public Const MCI_MODE_PAUSE = (MCI_STRING_OFFSET + 17)
Public Const MCI_MODE_OPEN = (MCI_STRING_OFFSET + 18)
' constants used in 'set time format' and 'status time format' commands
Public Const MCI_FORMAT_MILLISECONDS = 0
Public Const MCI_FORMAT_HMS = 1
Public Const MCI_FORMAT_MSF = 2
Public Const MCI_FORMAT_FRAMES = 3
Public Const MCI_FORMAT_SMPTE_24 = 4
Public Const MCI_FORMAT_SMPTE_25 = 5
Public Const MCI_FORMAT_SMPTE_30 = 6
Public Const MCI_FORMAT_SMPTE_30DROP = 7
Public Const MCI_FORMAT_BYTES = 8
Public Const MCI_FORMAT_SAMPLES = 9
Public Const MCI_FORMAT_TMSF = 10
' Flags for wParam of the MM_MCINOTIFY message
Public Const MCI_NOTIFY_SUCCESSFUL = &H1
Public Const MCI_NOTIFY_SUPERSEDED = &H2
Public Const MCI_NOTIFY_ABORTED = &H4
Public Const MCI_NOTIFY_FAILURE = &H8
' common flags for dwFlags parameter of MCI command messages
Public Const MCI_NOTIFY = &H1&
Public Const MCI_WAIT = &H2&
Public Const MCI_FROM = &H4&
Public Const MCI_TO = &H8&
Public Const MCI_TRACK = &H10&
' flags for dwFlags parameter of MCI_OPEN command message
Public Const MCI_OPEN_SHAREABLE = &H100&
Public Const MCI_OPEN_ELEMENT = &H200&
Public Const MCI_OPEN_ALIAS = &H400&
Public Const MCI_OPEN_ELEMENT_ID = &H800&
Public Const MCI_OPEN_TYPE_ID = &H1000&
Public Const MCI_OPEN_TYPE = &H2000&
' flags for dwFlags parameter of MCI_SEEK command message
Public Const MCI_SEEK_TO_START = &H100&
Public Const MCI_SEEK_TO_END = &H200&
' flags for dwFlags parameter of MCI_STATUS command message
Public Const MCI_STATUS_ITEM = &H100&
Public Const MCI_STATUS_START = &H200&
' flags for dwItem field of the MCI_STATUS_PARMS parameter block
Public Const MCI_STATUS_LENGTH = &H1&
Public Const MCI_STATUS_POSITION = &H2&
Public Const MCI_STATUS_NUMBER_OF_TRACKS = &H3&
Public Const MCI_STATUS_MODE = &H4&
Public Const MCI_STATUS_MEDIA_PRESENT = &H5&
Public Const MCI_STATUS_TIME_FORMAT = &H6&
Public Const MCI_STATUS_READY = &H7&
Public Const MCI_STATUS_CURRENT_TRACK = &H8&
' flags for dwFlags parameter of MCI_INFO command message
Public Const MCI_INFO_PRODUCT = &H100&
Public Const MCI_INFO_FILE = &H200&
' flags for dwFlags parameter of MCI_GETDEVCAPS command message
Public Const MCI_GETDEVCAPS_ITEM = &H100&
' flags for dwItem field of the MCI_GETDEVCAPS_PARMS parameter block
Public Const MCI_GETDEVCAPS_CAN_RECORD = &H1&
Public Const MCI_GETDEVCAPS_HAS_AUDIO = &H2&
Public Const MCI_GETDEVCAPS_HAS_VIDEO = &H3&
Public Const MCI_GETDEVCAPS_DEVICE_TYPE = &H4&
Public Const MCI_GETDEVCAPS_USES_FILES = &H5&
Public Const MCI_GETDEVCAPS_COMPOUND_DEVICE = &H6&
Public Const MCI_GETDEVCAPS_CAN_EJECT = &H7&
Public Const MCI_GETDEVCAPS_CAN_PLAY = &H8&
Public Const MCI_GETDEVCAPS_CAN_SAVE = &H9&
' flags for dwFlags parameter of MCI_SYSINFO command message
Public Const MCI_SYSINFO_QUANTITY = &H100&
Public Const MCI_SYSINFO_OPEN = &H200&
Public Const MCI_SYSINFO_NAME = &H400&
Public Const MCI_SYSINFO_INSTALLNAME = &H800&
' flags for dwFlags parameter of MCI_SET command message
Public Const MCI_SET_DOOR_OPEN = &H100&
Public Const MCI_SET_DOOR_CLOSED = &H200&
Public Const MCI_SET_TIME_FORMAT = &H400&
Public Const MCI_SET_AUDIO = &H800&
Public Const MCI_SET_VIDEO = &H1000&
Public Const MCI_SET_ON = &H2000&
Public Const MCI_SET_OFF = &H4000&
' flags for dwAudio field of MCI_SET_PARMS or MCI_SEQ_SET_PARMS
Public Const MCI_SET_AUDIO_ALL = &H4001&
Public Const MCI_SET_AUDIO_LEFT = &H4002&
Public Const MCI_SET_AUDIO_RIGHT = &H4003&
' flags for dwFlags parameter of MCI_BREAK command message
Public Const MCI_BREAK_KEY = &H100&
Public Const MCI_BREAK_HWND = &H200&
Public Const MCI_BREAK_OFF = &H400&
' flags for dwFlags parameter of MCI_RECORD command message
Public Const MCI_RECORD_INSERT = &H100&
Public Const MCI_RECORD_OVERWRITE = &H200&
' flags for dwFlags parameter of MCI_SOUND command message
Public Const MCI_SOUND_NAME = &H100&
' flags for dwFlags parameter of MCI_SAVE command message
Public Const MCI_SAVE_FILE = &H100&
' flags for dwFlags parameter of MCI_LOAD command message
Public Const MCI_LOAD_FILE = &H100&