调用xaudio.dll解码mp3,dsound播放(源码)

类别:.NET开发 点击:0 评论:0 推荐:

研究了xaudio的sdk包,发现vb6能很方便的调用它,所以写了这个例程,只使用了xaudio.dll的一部分函数,同理可以使用其它的。调用dsound控制发声。

以下代码,原c代码部分保留用以对照。

frmMain.frm

VERSION 5.00
Begin VB.Form frmMain
   Caption         =   "Form1"
   ClientHeight    =   3675
   ClientLeft      =   60
   ClientTop       =   345
   ClientWidth     =   4680
   LinkTopic       =   "Form1"
   ScaleHeight     =   3675
   ScaleWidth      =   4680
   StartUpPosition =   2  'CenterScreen
   Begin VB.CommandButton cmdGetInfo
      Caption         =   "GetInfo"
      Height          =   495
      Left            =   360
      TabIndex        =   5
      Top             =   3060
      Width           =   1215
   End
   Begin VB.CommandButton cmdGetTag
      Caption         =   "GetTag"
      Height          =   495
      Left            =   1740
      TabIndex        =   4
      Top             =   3060
      Width           =   1215
   End
   Begin VB.CommandButton cmdEnum
      Caption         =   "Enum"
      Height          =   495
      Left            =   3120
      TabIndex        =   3
      Top             =   2400
      Width           =   1215
   End
   Begin VB.CommandButton cmdPlay
      Caption         =   "Play"
      Height          =   495
      Left            =   1740
      TabIndex        =   2
      Top             =   2400
      Width           =   1215
   End
   Begin VB.TextBox txtLog
      Height          =   1995
      Left            =   240
      MultiLine       =   -1  'True
      ScrollBars      =   2  'Vertical
      TabIndex        =   1
      Top             =   180
      Width           =   4215
   End
   Begin VB.CommandButton cmdOK
      Caption         =   "OK"
      Height          =   495
      Left            =   360
      TabIndex        =   0
      Top             =   2400
      Width           =   1215
   End
End
Attribute VB_Name = "frmMain"
Attribute VB_GlobalNameSpace = False
Attribute VB_Creatable = False
Attribute VB_PredeclaredId = True
Attribute VB_Exposed = False
Option Explicit

Dim dx As New DirectX7
Dim ds As DirectSound
Dim dsb As DirectSoundBuffer
Dim dsbd As DSBUFFERDESC
Dim wf As WAVEFORMATEX

Dim bPlaying As Boolean
Dim bContinue As Boolean

Dim endEvent As Long
Implements DirectXEvent


Private Sub cmdEnum_Click()
    Dim de As DirectSoundEnum
    Dim i As Integer

    Set de = dx.GetDSEnum
    For i = 1 To de.GetCount
        txtLog.Text = txtLog.Text & de.GetGuid(i) & " " & de.GetName(i) & " " & de.GetDescription(i) & vbCrLf
    Next
    Set de = Nothing
End Sub

Private Sub cmdGetInfo_Click()
    Dim s As String
    Dim l As Long
    Dim status As Integer
    Dim t As XA_InputModule
    Dim d As XA_DecoderInfo
    Dim dp As Long
    Dim opbi As XA_OutputBufferInfo
    Dim i As Long
   
    dp = VarPtr(d)
    status = decoder_new(VarPtr(dp))
    If status <> XA_SUCCESS Then
        MsgBox "can not create decoder!"
        Exit Sub
    End If
    CopyMemory VarPtr(d), dp, 60
   
    status = file_input_module_register(t)
    status = decoder_input_module_register(d, t)
   
    If status <> XA_SUCCESS Then MsgBox xaudio_error_string(status)
    status = decoder_input_new(d, App.Path & "\3.mp3", XA_DECODER_INPUT_AUTOSELECT)
    If status <> XA_SUCCESS Then
        MsgBox "can not create input!" & status & vbCrLf & xaudio_error_string(status)
        Exit Sub
    End If
    status = decoder_input_open(d)
    If status <> XA_SUCCESS Then
        MsgBox "can not open input!" & vbCrLf & xaudio_error_string(status)
        Exit Sub
    End If
   
    Dim mp3info As MP3InfoType
    Dim l1 As Long, l2 As Long
    Dim l3 As Single
   
    Do
        DoEvents
        status = decoder_decode(d, 0)
        CopyMemory VarPtr(opbi), d.Addr06, Len(opbi)
       
        With mp3info.WaveFormat
            .BitsPerSample = opbi.bytes_per_sample * 8
            .Channels = 2 ^ opbi.stereo
            .SamplesPerSec = opbi.sample_rate
        End With
        l1 = l1 + 1
        l2 = l2 + opbi.size
        l3 = l3 + opbi.size / (opbi.sample_rate * ((2 ^ opbi.stereo) * opbi.bytes_per_sample))
       
    Loop While status = XA_SUCCESS Or status = XA_ERROR_TIMEOUT Or status = XA_ERROR_INVALID_FRAME
   
    With mp3info
        .Frames = l1
        .ByteLength = l2
        .SecondLength = l3
    End With
   
    MsgBox "Frames: " & mp3info.Frames & vbCrLf & "Bytes: " & mp3info.ByteLength & vbCrLf & "Seconds: " & mp3info.SecondLength
   
    l = xaudio_get_api_version(XA_API_ID_SYNC)
    MsgBox "XAudio DLL Version: " & ((l \ (2 ^ 16)) And &H255) & "." & ((l \ (2 ^ 8)) And &H255) & "." & (l And &H255)
End Sub

Private Sub cmdGetTag_Click()
    Dim fp As Integer
    Dim mp3tag As ID3V1
    Dim SongType() As String
   
    SongType = Split(LoadResString(1001), ";")
   
    fp = FreeFile
    Open App.Path & "\4.mp3" For Binary As #fp
    Seek #fp, FileLen(App.Path & "\4.mp3") - 127
    Get #fp, , mp3tag
    Close #fp
    MsgBox RTrim(mp3tag.Title) & vbCrLf & RTrim(mp3tag.Artist) & vbCrLf & RTrim(mp3tag.Album) & _
        vbCrLf & RTrim(mp3tag.Year) & vbCrLf & RTrim(mp3tag.Comment)
End Sub

Private Sub cmdOK_Click()
    Dim s As String
    Dim l As Long
    Dim status As Integer
    Dim t As XA_InputModule
    Dim d As XA_DecoderInfo
    Dim dp As Long
    Dim opbi As XA_OutputBufferInfo
    Dim i As Long
   
    dp = VarPtr(d)
    status = decoder_new(VarPtr(dp))
    If status <> XA_SUCCESS Then
        MsgBox "can not create decoder!"
        Exit Sub
    End If
    CopyMemory VarPtr(d), dp, 60
   
    status = file_input_module_register(t)
    status = decoder_input_module_register(d, t)
   
    If status <> XA_SUCCESS Then MsgBox xaudio_error_string(status)
    status = decoder_input_new(d, App.Path & "\3.mp3", XA_DECODER_INPUT_AUTOSELECT)
    If status <> XA_SUCCESS Then
        MsgBox "can not create input!" & status & vbCrLf & xaudio_error_string(status)
        Exit Sub
    End If
    status = decoder_input_open(d)
    If status <> XA_SUCCESS Then
        MsgBox "can not open input!" & vbCrLf & xaudio_error_string(status)
        Exit Sub
    End If
   
   
    Set ds = dx.DirectSoundCreate(vbNullString)
    ds.SetCooperativeLevel Me.hWnd, DSSCL_PRIORITY
   
    Dim sb(100000000) As Byte
    Dim psa(0) As DSBPOSITIONNOTIFY
   
    'ReDim sb(0)
    Do
        DoEvents
        status = decoder_decode(d, 0)
        CopyMemory VarPtr(opbi), d.Addr06, Len(opbi)
       
       
        'ReDim Preserve sb(i + opbi.size)
        'CopyMemory VarPtr(UBound(sb) - opbi.size), opbi.pcm_samples, opbi.size
        CopyMemory VarPtr(sb(i)), opbi.pcm_samples, opbi.size
        i = i + opbi.size
       
    Loop While status = XA_SUCCESS Or status = XA_ERROR_TIMEOUT Or status = XA_ERROR_INVALID_FRAME
   
        dsbd.lFlags = DSBCAPS_CTRLVOLUME Or DSBCAPS_STATIC Or DSBCAPS_CTRLPOSITIONNOTIFY
        dsbd.lBufferBytes = i
       
        wf = MakeWaveEX(opbi.sample_rate, 2 ^ opbi.stereo, opbi.bytes_per_sample * 8)
       
        Set dsb = ds.CreateSoundBuffer(dsbd, wf)
        dsb.WriteBuffer 0, i, sb(0), DSBLOCK_DEFAULT
        dsb.SetVolume 0
       
   
        dx.SetEvent endEvent
        psa(0).hEventNotify = endEvent
        psa(0).lOffset = i - 1
        dsb.SetNotificationPositions 1, psa()
       
       
        dsb.Play DSBPLAY_DEFAULT
        bContinue = True
   
    'l = xaudio_get_api_version(XA_API_ID_SYNC)
    'MsgBox "XAudio DLL Version: " & ((l \ (2 ^ 16)) And &H255) & "." & ((l \ (2 ^ 8)) And &H255) & "." & (l And &H255)
End Sub

Private Sub cmdPlay_Click()
    Dim s As String
    Dim l As Long
    Dim status As Integer
    Dim t As XA_InputModule
    Dim d As XA_DecoderInfo
    Dim dp As Long
    Dim opbi As XA_OutputBufferInfo
    Dim i As Long
   
    dp = VarPtr(d)
    status = decoder_new(VarPtr(dp))
    If status <> XA_SUCCESS Then
        MsgBox "can not create decoder!"
        Exit Sub
    End If
    CopyMemory VarPtr(d), dp, 60
   
    status = file_input_module_register(t)
    status = decoder_input_module_register(d, t)
   
    If status <> XA_SUCCESS Then MsgBox xaudio_error_string(status)
    status = decoder_input_new(d, App.Path & "\4.mp3", XA_DECODER_INPUT_AUTOSELECT)
    If status <> XA_SUCCESS Then
        MsgBox "can not create input!" & status & vbCrLf & xaudio_error_string(status)
        Exit Sub
    End If
    status = decoder_input_open(d)
    If status <> XA_SUCCESS Then
        MsgBox "can not open input!" & vbCrLf & xaudio_error_string(status)
        Exit Sub
    End If
   
   
    Set ds = dx.DirectSoundCreate(vbNullString)
    ds.SetCooperativeLevel Me.hWnd, DSSCL_PRIORITY
   
   
    Dim sb(5000000) As Byte
    Dim psa(0) As DSBPOSITIONNOTIFY
   
    bPlaying = False
    Do
        DoEvents
        status = decoder_decode(d, 0)
        CopyMemory VarPtr(opbi), d.Addr06, Len(opbi)
       
        If i + opbi.size > 5000000 Then
            Do While bPlaying
                DoEvents
            Loop
           
            dsbd.lFlags = DSBCAPS_CTRLVOLUME Or DSBCAPS_STATIC Or DSBCAPS_CTRLPOSITIONNOTIFY Or DSBCAPS_GLOBALFOCUS
            dsbd.lBufferBytes = i
       
            wf = MakeWaveEX(opbi.sample_rate, 2 ^ opbi.stereo, opbi.bytes_per_sample * 8)
           
            Set dsb = ds.CreateSoundBuffer(dsbd, wf)
            dsb.WriteBuffer 0, i, sb(0), DSBLOCK_DEFAULT
            dsb.SetVolume 0
       
   
            dx.SetEvent endEvent
            psa(0).hEventNotify = endEvent
            psa(0).lOffset = i - 1
            dsb.SetNotificationPositions 1, psa()
       
       
            dsb.Play DSBPLAY_DEFAULT
            bContinue = True
            bPlaying = True
           
            i = 0
        End If
       
        CopyMemory VarPtr(sb(i)), opbi.pcm_samples, opbi.size
        i = i + opbi.size
       
    Loop While status = XA_SUCCESS Or status = XA_ERROR_TIMEOUT Or status = XA_ERROR_INVALID_FRAME
   
            dsbd.lFlags = DSBCAPS_CTRLVOLUME Or DSBCAPS_STATIC Or DSBCAPS_CTRLPOSITIONNOTIFY Or DSBCAPS_GLOBALFOCUS
            dsbd.lBufferBytes = i
       
            wf = MakeWaveEX(opbi.sample_rate, 2 ^ opbi.stereo, opbi.bytes_per_sample * 8)
           
            Set dsb = ds.CreateSoundBuffer(dsbd, wf)
            dsb.WriteBuffer 0, i, sb(0), DSBLOCK_DEFAULT
            dsb.SetVolume 0
       
   
            dx.SetEvent endEvent
            psa(0).hEventNotify = endEvent
            psa(0).lOffset = i - 1
            dsb.SetNotificationPositions 1, psa()
       
       
            dsb.Play DSBPLAY_DEFAULT
            bContinue = True
            bPlaying = True
End Sub

Private Sub Form_Load()
     endEvent = dx.CreateEvent(Me)
End Sub

Private Sub Form_QueryUnload(Cancel As Integer, UnloadMode As Integer)
    If endEvent Then dx.DestroyEvent endEvent
   
    If Not dsb Is Nothing Then dsb.Stop
    bPlaying = False
   
    Set dsb = Nothing
    Set ds = Nothing
    Set dx = Nothing
    End
End Sub


Private Function MakeWaveEX(Hz As Long, Channels As Integer, Bits As Integer) As WAVEFORMATEX
    MakeWaveEX.lSamplesPerSec = Hz
    MakeWaveEX.lExtra = 0
    MakeWaveEX.nSize = 0
    MakeWaveEX.nBitsPerSample = Bits
    MakeWaveEX.nChannels = Channels
    MakeWaveEX.nFormatTag = WAVE_FORMAT_PCM
    MakeWaveEX.nBlockAlign = Channels * Bits \ 8
    MakeWaveEX.lAvgBytesPerSec = Hz * (Channels * Bits \ 8)
End Function

Private Sub DirectXEvent_DXCallback(ByVal eventid As Long)
    If bContinue Then bContinue = False: Exit Sub
    bPlaying = False
End Sub

modXAudio.bas

Attribute VB_Name = "modXAudio"
Option Explicit

'/*****************************************************************
'|
'|      Xaudio General Definitions
'|
'|      (c) 1996-1998 MpegTV, LLC
'|      Author: Gilles Boccon-Gibod ([email protected])
'|
' ****************************************************************/

'/*----------------------------------------------------------------------
'|       types
'+---------------------------------------------------------------------*/
'typedef void (*XA_ProgressNotificationFunction)(void *client,
'                                                int source,
'                                                int code,
'                                                long value,
'                                                const char *message);

'typedef void (*XA_DebugNotificationFunction)(void *client,
'                                             int source,
'                                             int level,
'                                             const char *message,
'                                             const char *reason);

'typedef void (*XA_ErrorNotificationFunction)(void *client,
'                                             int source,
'                                             int code,
'                                             const char *message,
'                                             const char *reason);

Public Type XA_NotificationClient
    'void                           *client;
    'XA_ProgressNotificationFunction notify_progress;
    'XA_DebugNotificationFunction    notify_debug;
    'XA_ErrorNotificationFunction    notify_error;
   
    Addr01 As Long
    Addr02 As Long
    Addr03 As Long
    Addr04 As Long
End Type

'#define XA_NOTIFY_PROGRESS(_client, _source, _code, _value, _message)    \
'if ((_client) && (_client)->notify_progress)                             \
'    (*(_client)->notify_progress)((_client)->client,                     \
'     _source, _code, _value, _message)

'#define XA_NOTIFY_DEBUG(_client, _source, _level, _message, _reason)     \
'if ((_client) && (_client)->notify_debug)                                \
'    (*(_client)->notify_debug)((_client)->client,                        \
'     _source, _level, _message, _reason)

'#define XA_NOTIFY_ERROR(_client, _source, _code, _message, _reason)      \
'if ((_client) && (_client)->notify_error)                                \
'    (*(_client)->notify_error)((_client)->client,                        \
'     _source, _code, _message, _reason)


'/*----------------------------------------------------------------------
'|       apis
'+---------------------------------------------------------------------*/
Public Const XA_API_ID_SYNC = 1
Public Const XA_API_ID_ASYNC = 2

'/*----------------------------------------------------------------------
'|       error codes
'+---------------------------------------------------------------------*/
Public Const XA_SUCCESS = (0)
Public Const XA_FAILURE = (-1)

'/* general error codes */
Public Const XA_ERROR_BASE_GENERAL = (-100)
Public Const XA_ERROR_OUT_OF_MEMORY = (XA_ERROR_BASE_GENERAL - 0)
Public Const XA_ERROR_INVALID_PARAMETERS = (XA_ERROR_BASE_GENERAL - 1)
Public Const XA_ERROR_INTERNAL = (XA_ERROR_BASE_GENERAL - 2)
Public Const XA_ERROR_TIMEOUT = (XA_ERROR_BASE_GENERAL - 3)
Public Const XA_ERROR_VERSION_EXPIRED = (XA_ERROR_BASE_GENERAL - 4)

'/* network error codes */
Public Const XA_ERROR_BASE_NETWORK = (-200)
Public Const XA_ERROR_CONNECT_TIMEOUT = (XA_ERROR_BASE_NETWORK - 0)
Public Const XA_ERROR_CONNECT_FAILED = (XA_ERROR_BASE_NETWORK - 1)
Public Const XA_ERROR_CONNECTION_REFUSED = (XA_ERROR_BASE_NETWORK - 2)
Public Const XA_ERROR_ACCEPT_FAILED = (XA_ERROR_BASE_NETWORK - 3)
Public Const XA_ERROR_LISTEN_FAILED = (XA_ERROR_BASE_NETWORK - 4)
Public Const XA_ERROR_SOCKET_FAILED = (XA_ERROR_BASE_NETWORK - 5)
Public Const XA_ERROR_SOCKET_CLOSED = (XA_ERROR_BASE_NETWORK - 6)
Public Const XA_ERROR_BIND_FAILED = (XA_ERROR_BASE_NETWORK - 7)
Public Const XA_ERROR_HOST_UNKNOWN = (XA_ERROR_BASE_NETWORK - 8)
Public Const XA_ERROR_HTTP_INVALID_REPLY = (XA_ERROR_BASE_NETWORK - 9)
Public Const XA_ERROR_HTTP_ERROR_REPLY = (XA_ERROR_BASE_NETWORK - 10)
Public Const XA_ERROR_HTTP_FAILURE = (XA_ERROR_BASE_NETWORK - 11)
Public Const XA_ERROR_FTP_INVALID_REPLY = (XA_ERROR_BASE_NETWORK - 12)
Public Const XA_ERROR_FTP_ERROR_REPLY = (XA_ERROR_BASE_NETWORK - 13)
Public Const XA_ERROR_FTP_FAILURE = (XA_ERROR_BASE_NETWORK - 14)

'/* control error codes */
Public Const XA_ERROR_BASE_CONTROL = (-300)
Public Const XA_ERROR_PIPE_FAILED = (XA_ERROR_BASE_CONTROL - 0)
Public Const XA_ERROR_FORK_FAILED = (XA_ERROR_BASE_CONTROL - 1)
Public Const XA_ERROR_SELECT_FAILED = (XA_ERROR_BASE_CONTROL - 2)
Public Const XA_ERROR_PIPE_CLOSED = (XA_ERROR_BASE_CONTROL - 3)
Public Const XA_ERROR_PIPE_READ_FAILED = (XA_ERROR_BASE_CONTROL - 4)
Public Const XA_ERROR_PIPE_WRITE_FAILED = (XA_ERROR_BASE_CONTROL - 5)
Public Const XA_ERROR_INVALID_MESSAGE = (XA_ERROR_BASE_CONTROL - 6)
Public Const XA_ERROR_CIRQ_FULL = (XA_ERROR_BASE_CONTROL - 7)
Public Const XA_ERROR_POST_FAILED = (XA_ERROR_BASE_CONTROL - 8)

'/* url error codes */
Public Const XA_ERROR_BASE_URL = (-400)
Public Const XA_ERROR_URL_UNSUPPORTED_SCHEME = (XA_ERROR_BASE_URL - 0)
Public Const XA_ERROR_URL_INVALID_SYNTAX = (XA_ERROR_BASE_URL - 1)

'/* i/o error codes */
Public Const XA_ERROR_BASE_IO = (-500)
Public Const XA_ERROR_OPEN_FAILED = (XA_ERROR_BASE_IO - 0)
Public Const XA_ERROR_CLOSE_FAILED = (XA_ERROR_BASE_IO - 1)
Public Const XA_ERROR_READ_FAILED = (XA_ERROR_BASE_IO - 2)
Public Const XA_ERROR_WRITE_FAILED = (XA_ERROR_BASE_IO - 3)
Public Const XA_ERROR_PERMISSION_DENIED = (XA_ERROR_BASE_IO - 4)
Public Const XA_ERROR_NO_DEVICE = (XA_ERROR_BASE_IO - 5)
Public Const XA_ERROR_IOCTL_FAILED = (XA_ERROR_BASE_IO - 6)
Public Const XA_ERROR_MODULE_NOT_FOUND = (XA_ERROR_BASE_IO - 7)
Public Const XA_ERROR_UNSUPPORTED_INPUT = (XA_ERROR_BASE_IO - 8)
Public Const XA_ERROR_UNSUPPORTED_OUTPUT = (XA_ERROR_BASE_IO - 9)
Public Const XA_ERROR_UNSUPPORTED_FORMAT = (XA_ERROR_BASE_IO - 10)
Public Const XA_ERROR_DEVICE_BUSY = (XA_ERROR_BASE_IO - 11)
Public Const XA_ERROR_NO_SUCH_DEVICE = (XA_ERROR_BASE_IO - 12)
Public Const XA_ERROR_NO_SUCH_FILE = (XA_ERROR_BASE_IO - 13)
Public Const XA_ERROR_INPUT_EOF = (XA_ERROR_BASE_IO - 14)

'/* bitstream error codes */
Public Const XA_ERROR_BASE_BITSTREAM = (-600)
Public Const XA_ERROR_INVALID_FRAME = (XA_ERROR_BASE_BITSTREAM - 0)

'/* dynamic linking error codes */
Public Const XA_ERROR_BASE_DYNLINK = (-700)
Public Const XA_ERROR_DLL_NOT_FOUND = (XA_ERROR_BASE_DYNLINK - 0)
Public Const XA_ERROR_SYMBOL_NOT_FOUND = (XA_ERROR_BASE_DYNLINK - 1)

'/* environment variables error codes */
Public Const XA_ERROR_BASE_ENVIRONMENT = (-800)
Public Const XA_ERROR_NO_SUCH_ENVIRONMENT = (XA_ERROR_BASE_ENVIRONMENT - 0)
Public Const XA_ERROR_ENVIRONMENT_TYPE_MISMATCH = (XA_ERROR_BASE_ENVIRONMENT - 1)


modDecoder.bas

Attribute VB_Name = "modDecoder"
Option Explicit

Public Const XA_DECODER_INPUT_SEEKABLE = &H1

Public Const XA_DECODER_DEVICE_HAS_MASTER_LEVEL_CONTROL = &H1
Public Const XA_DECODER_DEVICE_HAS_PCM_LEVEL_CONTROL = &H2
Public Const XA_DECODER_DEVICE_HAS_BALANCE_CONTROL = &H4
Public Const XA_DECODER_DEVICE_HAS_LINE_OUT = &H8
Public Const XA_DECODER_DEVICE_HAS_SPEAKER_OUT = &H10
Public Const XA_DECODER_DEVICE_HAS_HEADPHONE_OUT = &H20
Public Const XA_DECODER_DEVICE_HAS_08_000_KHZ = &H40
Public Const XA_DECODER_DEVICE_HAS_11_025_KHZ = &H80
Public Const XA_DECODER_DEVICE_HAS_12_000_KHZ = &H100
Public Const XA_DECODER_DEVICE_HAS_16_000_KHZ = &H200
Public Const XA_DECODER_DEVICE_HAS_22_050_KHZ = &H400
Public Const XA_DECODER_DEVICE_HAS_24_000_KHZ = &H800
Public Const XA_DECODER_DEVICE_HAS_32_000_KHZ = &H1000
Public Const XA_DECODER_DEVICE_HAS_44_100_KHZ = &H2000
Public Const XA_DECODER_DEVICE_HAS_48_000_KHZ = &H4000
Public Const XA_DECODER_DEVICE_HAS_8_BITS = &H8000
Public Const XA_DECODER_DEVICE_HAS_MU_LAW = &H10000
Public Const XA_DECODER_DEVICE_HAS_16_BITS = &H20000
Public Const XA_DECODER_DEVICE_HAS_MUTE = &H40000
Public Const XA_DECODER_DEVICE_HAS_RESET = &H80000
Public Const XA_DECODER_DEVICE_HAS_PAUSE = &H100000
Public Const XA_DECODER_DEVICE_HAS_DRAIN = &H200000
Public Const XA_DECODER_DEVICE_HAS_BUFFER_STATUS = &H400000

Public Const XA_DECODER_DEVICE_FREQUENCIES_OFFSET = 6
Public Const XA_DECODER_DEVICE_FREQUENCIES_MASK = &H1FF

Public Const XA_DECODER_CONTROL_BPS = &H1
Public Const XA_DECODER_CONTROL_STEREO = &H2
Public Const XA_DECODER_CONTROL_SAMPLE_RATE = &H4
Public Const XA_DECODER_CONTROL_MASTER_LEVEL = &H8
Public Const XA_DECODER_CONTROL_PCM_LEVEL = &H10
Public Const XA_DECODER_CONTROL_BALANCE = &H20
Public Const XA_DECODER_CONTROL_PORTS = &H40
Public Const XA_DECODER_CONTROL_ALL_INFO = &H7F
Public Const XA_DECODER_CONTROL_MUTE = &H80
Public Const XA_DECODER_CONTROL_UNMUTE = &H100
Public Const XA_DECODER_CONTROL_RESET = &H200
Public Const XA_DECODER_CONTROL_PAUSE = &H400
Public Const XA_DECODER_CONTROL_RESTART = &H800
Public Const XA_DECODER_CONTROL_DRAIN = &H1000

Public Const XA_DECODER_CONTROL_OUTPUT_LINE = &H1
Public Const XA_DECODER_CONTROL_OUTPUT_SPEAKER = &H2
Public Const XA_DECODER_CONTROL_OUTPUT_HEADPHONE = &H4

Public Const XA_DECODER_ENVIRONMENT_MAX_NAME_LENGTH = 256
Public Const XA_DECODER_ENVIRONMENT_MAX_STRING_LENGTH = 1024

Public Const XA_DECODER_INPUT_QUERY_MODULE_NAME = &H1
Public Const XA_DECODER_INPUT_QUERY_NB_DEVICES = &H2
Public Const XA_DECODER_INPUT_QUERY_DEVICE_NAME = &H4

Public Const XA_DECODER_INPUT_QUERY_NAME_IS_GENERIC = &H1
Public Const XA_DECODER_INPUT_QUERY_DEVICE_IS_DEFAULT = &H2

Public Const XA_DECODER_OUTPUT_QUERY_MODULE_NAME = &H1
Public Const XA_DECODER_OUTPUT_QUERY_NB_DEVICES = &H2
Public Const XA_DECODER_OUTPUT_QUERY_DEVICE_NAME = &H4

Public Const XA_DECODER_OUTPUT_QUERY_NAME_IS_GENERIC = &H1
Public Const XA_DECODER_OUTPUT_QUERY_DEVICE_IS_DEFAULT = &H2
Public Const XA_DECODER_OUTPUT_QUERY_DEVICE_IS_SHAREABLE = &H4

Public Const XA_DECODER_MAX_NAME_LENGTH = 255
Public Const XA_DECODER_MAX_DESCRIPTION_LENGTH = 255

Public Const XA_DECODER_INPUT_AUTOSELECT = -1
Public Const XA_DECODER_OUTPUT_AUTOSELECT = -1

Public Const XA_DECODER_INPUT_FILTER_FIRST = -1
Public Const XA_DECODER_INPUT_FILTER_LAST = 0
Public Const XA_DECODER_INPUT_FILTER_BY_NAME = -2

Public Const XA_DECODER_OUTPUT_FILTER_FIRST = -1
Public Const XA_DECODER_OUTPUT_FILTER_LAST = 0
Public Const XA_DECODER_OUTPUT_FILTER_BY_NAME = -2

Public Const XA_TIMECODE_FRACTIONS_PER_SECOND = 100
Public Const XA_TIMECODE_FRACTIONS_PER_MINUTE = (100 * 60)
Public Const XA_TIMECODE_FRACTIONS_PER_HOUR = 360000

Public Const XA_DECODER_CODEC_QUALITY_HIGH = 0
Public Const XA_DECODER_CODEC_QUALITY_MEDIUM = 1
Public Const XA_DECODER_CODEC_QUALITY_LOW = 2

Public Const XA_DECODER_EQUALIZER_NB_BANDS = 32
Public Const XA_DECODER_FEEDBACK_NB_BANDS = 32

'/*----------------------------------------------------------------------
'|       types
'+---------------------------------------------------------------------*/
'typedef void (*XA_EnvironmentCallback)(void *listener,
'                                       const char *name,
'                                       void  *value);

Public Type XA_TimeCode
    h As Integer
    m As Integer
    s As Integer
    f As Integer
End Type

Public Type XA_AbsoluteTime
    seconds As Long
    microseconds As Long
End Type

Public Enum XA_IOState
    XA_IO_STATE_CLOSED = 0
    XA_IO_STATE_OPEN
End Enum

Public Type XA_InputStreamInfo
    changed As Integer
    level As Integer
    layer As Integer
    bitrate As Integer
    frequency As Integer
    mode As Integer
End Type

Public Type XA_InputModuleQuery
    index As Integer
    flags As Long
    name As String * XA_DECODER_MAX_NAME_LENGTH
    description As String * XA_DECODER_MAX_DESCRIPTION_LENGTH
End Type

Public Type XA_InputModuleClassInfo
    id As Integer
    'void *global;
    Addr01 As Long
End Type

'struct XA_DecoderInfo;

Public Type XA_InputModule
'    int  (*input_module_probe)(const char *name);
'    int  (*input_module_query)(XA_InputModuleQuery *query,
'                               unsigned long query_mask);
'    int  (*input_new)(void **input, const char *name,
'                      XA_InputModuleClassInfo *class_info,
'                      struct XA_DecoderInfo *decoder);
'    int  (*input_delete)(void *input);
'    int  (*input_open)(void *input);
'    int  (*input_close)(void *input);
'    int  (*input_read)(void *input, void *buffer, unsigned long n);
'    int  (*input_seek)(void *input, unsigned long offset);
'    long (*input_get_caps)(void *input);
'    long (*input_get_size)(void *input);
'    int  (*input_send_message)(void *input, int type,
'                               const void *data, unsigned int size);
    Addr01 As Long
    Addr02 As Long
    Addr03 As Long
    Addr04 As Long
    Addr05 As Long
    Addr06 As Long
    Addr07 As Long
    Addr08 As Long
    Addr09 As Long
    Addr10 As Long
    Addr11 As Long
End Type

'struct XA_InputFilterNode;

Public Type XA_InputFilter
    'const char *(*filter_get_name)(void);
    'int  (*filter_new)(void **filter, int id,
    '                   struct XA_DecoderInfo *decoder);
    'int  (*filter_delete)(void *filter);
    'int  (*input_open)(struct XA_InputFilterNode *node);
    'int  (*input_close)(struct XA_InputFilterNode *node);
    'int  (*input_read)(struct XA_InputFilterNode *node,
    '                   void *buffer, unsigned long n);
    'int  (*input_seek)(struct XA_InputFilterNode *node,
    '                   unsigned long offset);
    'long (*input_get_caps)(struct XA_InputFilterNode *node);
    'long (*input_get_size)(struct XA_InputFilterNode *node);
    'int  (*input_send_message)(struct XA_InputFilterNode *node,
    '                           int type, const void *data, unsigned int size);
   
    Addr01 As Long
    Addr02 As Long
    Addr03 As Long
    Addr04 As Long
    Addr05 As Long
    Addr06 As Long
    Addr07 As Long
    Addr08 As Long
    Addr09 As Long
    Addr10 As Long
End Type

Public Type XA_InputFilterNode
    id As Integer
    'void                      *instance;
    Addr01 As Long
    vtable As XA_InputFilter
    'struct XA_InputFilterNode *next;
    Addr02 As Long
    'struct XA_InputFilterNode *prev;
    Addr03 As Long
End Type

Public Type XA_InputInfo
    state As XA_IOState
    caps As Long
    position As Long
    size As Long
    duration As Long
    'void                 *device;
    Addr01 As Long
    'const XA_InputModule *module;
    Addr02 As Long
    'const char           *name;
    Addr03 As Long
End Type

Public Enum XA_OutputChannelsMode
    XA_OUTPUT_STEREO
    XA_OUTPUT_MONO_LEFT
    XA_OUTPUT_MONO_RIGHT
    XA_OUTPUT_MONO_MIX
End Enum

Public Type XA_OutputFeedbackBands
    'short left[XA_DECODER_FEEDBACK_NB_BANDS];
    leftleft(XA_DECODER_FEEDBACK_NB_BANDS) As Integer
    'short right[XA_DECODER_FEEDBACK_NB_BANDS];
    rightright(XA_DECODER_FEEDBACK_NB_BANDS) As Integer
End Type

Public Type XA_OutputBufferInfo
    changed As Long
    'short                  *pcm_samples;
    pcm_samples As Long
    size As Long
    bytes_per_sample As Long
    stereo As Long
    sample_rate As Long
    delay As Long
    '/*XA_OutputFeedbackBands *feedback;*/
End Type

Public Type XA_OutputStatus
    delay As Long
End Type

Public Type XA_OutputControl
    bytes_per_sample As Integer
    sample_rate As Integer
    stereo As Integer
    master_level As Integer
    pcm_level As Integer
    balance As Integer
    ports As Integer
End Type

Public Type XA_OutputModuleQuery
    index As Integer
    flags As Long
    name As String * XA_DECODER_MAX_NAME_LENGTH
    description As String * XA_DECODER_MAX_DESCRIPTION_LENGTH
End Type

Public Type XA_OutputModuleClassInfo
    id As Integer
    'void *global;
    Addr01 As Long
End Type

Public Type XA_OutputModule
    'int   (*output_module_probe)(const char *name);
    'int   (*output_module_query)(XA_OutputModuleQuery *query,
    '                             unsigned long query_mask);
    'int   (*output_new)(void **output, const char *name,
    '                    XA_OutputModuleClassInfo *class_info,
    '                    struct XA_DecoderInfo *decoder);
    'int   (*output_delete)(void *output);
    'int   (*output_open)(void *output);
    'int   (*output_close)(void *output);
    'int   (*output_write)(void *output, void *buffer,
    '                      unsigned long size, int bytes_per_sample,
    '                      int stereo, int sample_rate);
    'void* (*output_get_buffer)(void *output, unsigned long size);
    'int   (*output_set_control)(void *output,
    '                            XA_OutputControl *control,
    '                            unsigned long flags);
    'int   (*output_get_control)(void *output,
    '                            XA_OutputControl *control,
    '                            unsigned long control_mask);
    'int   (*output_get_status)(void *output,
    '                           XA_OutputStatus *status);
    'long  (*output_get_caps)(void *output);
    'int   (*output_send_message)(void *output, int type,
    '                             const void *data, unsigned int size);
   
    Addr01 As Long
    Addr02 As Long
    Addr03 As Long
    Addr04 As Long
    Addr05 As Long
    Addr06 As Long
    Addr07 As Long
    Addr08 As Long
    Addr09 As Long
    Addr10 As Long
    Addr11 As Long
    Addr12 As Long
    Addr13 As Long
End Type

'struct XA_OutputFilterNode;

Public Type XA_OutputFilter
    'const char *(*filter_get_name)(void);
    'int  (*filter_new)(void **filter, int id,
    '                   struct XA_DecoderInfo *decoder);
    'int  (*filter_delete)(void *filter);
    'int  (*output_open)(struct XA_OutputFilterNode *node);
    'int  (*output_close)(struct XA_OutputFilterNode *node);
    'int  (*output_write)(struct XA_OutputFilterNode *node,
    '                     void *buffer,
    '                     unsigned long size, int bytes_per_sample,
    '                     int stereo, int sample_rate);
    'void* (*output_get_buffer)(struct XA_OutputFilterNode *node,
    '                           unsigned long size);
    'int  (*output_set_control)(struct XA_OutputFilterNode *node,
    '                           XA_OutputControl *control,
    '                           unsigned long flags);
    'int  (*output_get_control)(struct XA_OutputFilterNode *node,
    '                           XA_OutputControl *control,
    '                           unsigned long control_mask);
    'int  (*output_get_status)(struct XA_OutputFilterNode *node,
    '                          XA_OutputStatus *status);
    'long (*output_get_caps)(struct XA_OutputFilterNode *node);
    'int  (*output_send_message)(struct XA_OutputFilterNode *node,
    '                            int type, const void *data, unsigned int size);
   
    Addr01 As Long
    Addr02 As Long
    Addr03 As Long
    Addr04 As Long
    Addr05 As Long
    Addr06 As Long
    Addr07 As Long
    Addr08 As Long
    Addr09 As Long
    Addr10 As Long
    Addr11 As Long
    Addr12 As Long
End Type

Public Type XA_OutputFilterNode
    id As Integer
    'void                       *instance;
    Addr01 As Long
    vtable As XA_OutputFilter
    'struct XA_OutputFilterNode *next;
    Addr02 As Long
    'struct XA_OutputFilterNode *prev;
    Addr03 As Long
End Type

Public Type XA_OutputInfo
    state As XA_IOState
    caps As Long
    'void                      *device;
    'const XA_OutputModule     *module;
    'const char                *name;
    Addr01 As Long
    Addr02 As Long
    Addr03 As Long
End Type

Public Type XA_EqualizerInfo
    'signed char left[XA_DECODER_EQUALIZER_NB_BANDS];
    'signed char right[XA_DECODER_EQUALIZER_NB_BANDS];
    leftleft(XA_DECODER_EQUALIZER_NB_BANDS) As Integer
    rightright(XA_DECODER_EQUALIZER_NB_BANDS) As Integer
End Type

Public Type XA_ModulesInfo
    nb_input_modules As Integer
    nb_output_modules As Integer
End Type

Public Type XA_StatusInfo
    frame As Long
    position As Single
    info As XA_InputStreamInfo
    timecode As XA_TimeCode
End Type

'struct XA_DecoderPrivateInfo;
'struct XA_DecoderInfo;

Public Type XA_DecoderCallbackTable
    'int (XA_EXPORT *get_environment_integer)(struct XA_DecoderInfo *decoder,
    '                                         const char *name,
    '                                         long *value);
    'int (XA_EXPORT *get_environment_string)(struct XA_DecoderInfo *decoder,
    '                                        const char *name,
    '                                        char *value);
    'int (XA_EXPORT *add_environment_listener)(struct XA_DecoderInfo *decoder,
    '                                          const char *name,
    '                                          void *client,
    '                                          XA_EnvironmentCallback callback,
    '                                          void **handle);
    'int (XA_EXPORT *remove_environment_listener)(struct XA_DecoderInfo *decoder,
    '                                             void *handle);
    Addr01 As Long
    Addr02 As Long
    Addr03 As Long
    Addr04 As Long
End Type

Public Type XA_DecoderInfo
    'const char                    *name;
    'XA_InputInfo                  *input;
    'XA_OutputInfo                 *output;
    'XA_ModulesInfo                *modules;
    'XA_StatusInfo                 *status;
    'XA_OutputBufferInfo           *output_buffer;
    Addr01 As Long
    Addr02 As Long
    Addr03 As Long
    Addr04 As Long
    Addr05 As Long
    Addr06 As Long
    notification_client As XA_NotificationClient
    callbacks As XA_DecoderCallbackTable
    'struct XA_DecoderPrivateInfo *hidden;
    Addr07 As Long
End Type

modDeclare.bas

Attribute VB_Name = "modDeclare"
Option Explicit

'xaudio.h
Public Declare Function xaudio_error_string Lib "xaudio.dll" (ByVal code As Integer) As String
Public Declare Function xaudio_get_api_version Lib "xaudio.dll" (ByVal api_id As Long) As Long

'audio_output.h
'Public Declare Function audio_output_module_register Lib "xaudio.dll" (module As XA_OutputModule) As Integer
'Public Declare Function dsound_output_module_register Lib "xaudio.dll" (module As XA_OutputModule) As Integer

'file_input.h
Public Declare Function file_input_module_register Lib "xaudio.dll" (module As XA_InputModule) As Integer

'file_output.h
'Public Declare Function file_output_module_register Lib "xaudio.dll" (module As XA_OutputModule) As Integer

'memory_input.h
'Public Declare Function memory_input_feed Lib "xaudio.dll" (ByVal devicepointer As Long, ByVal datapointer As Long, ByVal nb_bytes As Long) As Integer
'Public Declare Function memory_input_flush Lib "xaudio.dll" (ByVal devicepointer As Long) As Integer
'Public Declare Function memory_input_module_register Lib "xaudio.dll" (module As XA_InputModule) As Integer

'stream_input.h
'Public Declare Function stream_input_module_register Lib "xaudio.dll" (module As XA_InputModule) As Integer


'decoder.h
'char* XA_EXPORT decoder_version(char **major, char **minor, char **state);

Public Declare Function decoder_new Lib "xaudio.dll" (ByVal decoderpp As Long) As Integer


Public Declare Function decoder_delete Lib "xaudio.dll" (decoder As XA_DecoderInfo) As Integer
Public Declare Function decoder_input_module_register Lib "xaudio.dll" (decoder As XA_DecoderInfo, module As XA_InputModule) As Integer
'int XA_EXPORT decoder_input_module_query(XA_DecoderInfo *decoder,
'                                         int module,
'                                         XA_InputModuleQuery *query,
'                                         unsigned long query_flags);
'int XA_EXPORT decoder_input_add_filter(XA_DecoderInfo *decoder,
'                                       const XA_InputFilter *filter,
'                                       int where);
'int XA_EXPORT decoder_input_remove_filter(XA_DecoderInfo *decoder,
'                                          const char *name, int id);
'int XA_EXPORT decoder_input_filters_list(XA_DecoderInfo *decoder,
'                                         void *client,
'                                         void (*callback)
'                                         (void *client,
'                                          XA_InputFilterNode *node));
Public Declare Function decoder_input_new Lib "xaudio.dll" (decoder As XA_DecoderInfo, ByVal name As String, ByVal module As Integer) As Integer
'int XA_EXPORT decoder_input_delete(XA_DecoderInfo *decoder);
Public Declare Function decoder_input_open Lib "xaudio.dll" (decoder As XA_DecoderInfo) As Integer
'int XA_EXPORT decoder_input_close(XA_DecoderInfo *decoder);
'int XA_EXPORT decoder_input_read(XA_DecoderInfo *decoder,
'                                 void *buffer, int size);
'int XA_EXPORT decoder_input_seek_to_offset(XA_DecoderInfo *decoder,
'                                           unsigned long offset);
'int XA_EXPORT decoder_input_seek_to_position(XA_DecoderInfo *decoder,
'                                             float position);
'int XA_EXPORT decoder_input_seek_to_time(XA_DecoderInfo *decoder,
'                                         float seconds);
'int XA_EXPORT decoder_input_seek_to_timecode(XA_DecoderInfo *decoder,
'                                             const XA_TimeCode *timecode);
'int XA_EXPORT decoder_input_send_message(XA_DecoderInfo *decoder,
'                                         int type,
'                                         const void *data,
'                                         unsigned int size);
'int XA_EXPORT decoder_output_module_register(XA_DecoderInfo *decoder,
'                                             const XA_OutputModule *module);
'int XA_EXPORT decoder_output_module_query(XA_DecoderInfo *decoder,
'                                          int module,
'                                          XA_OutputModuleQuery *query,
'                                          unsigned long query_flags);
'int XA_EXPORT decoder_output_add_filter(XA_DecoderInfo *decoder,
'                                        const XA_OutputFilter *filter,
'                                        int where);
'int XA_EXPORT decoder_output_remove_filter(XA_DecoderInfo *decoder,
'                                           const char *name, int id);
'int XA_EXPORT decoder_output_filters_list(XA_DecoderInfo *decoder,
'                                          void *client,
'                                          void (*callback)
'                                          (void *client,
'                                           XA_OutputFilterNode *node));
'int XA_EXPORT decoder_output_new(XA_DecoderInfo *decoder,
'                                 const char *name, int module);
'int XA_EXPORT decoder_output_delete(XA_DecoderInfo *decoder);
'int XA_EXPORT decoder_output_open(XA_DecoderInfo *decoder);
'int XA_EXPORT decoder_output_close(XA_DecoderInfo *decoder);
'int XA_EXPORT decoder_output_write(XA_DecoderInfo *decoder, void *buffer,
'                                   unsigned long size,
'                                   int bytes_per_sample,
'                                   int stereo, int sample_rate);
'int XA_EXPORT decoder_output_set_control(XA_DecoderInfo *decoder,
'                                         XA_OutputControl *control,
'                                         unsigned long control_flags);
'int XA_EXPORT decoder_output_get_control(XA_DecoderInfo *decoder,
'                                         XA_OutputControl *control,
'                                         unsigned long control_flags);
'int XA_EXPORT decoder_output_send_message(XA_DecoderInfo *decoder,
'                                          int type,
'                                          const void *data,
'                                          unsigned int size);
'int XA_EXPORT decoder_codec_set_channels(XA_DecoderInfo *decoder,
'                                         XA_OutputChannelsMode channels);
'int XA_EXPORT decoder_codec_get_channels(XA_DecoderInfo *decoder);
'int XA_EXPORT decoder_codec_set_quality(XA_DecoderInfo *decoder,
'                                        unsigned int quality);
'int XA_EXPORT decoder_codec_get_quality(XA_DecoderInfo *decoder);
'int XA_EXPORT decoder_codec_set_equalizer(XA_DecoderInfo *decoder,
'                                          XA_EqualizerInfo *equalizer);
'int XA_EXPORT decoder_codec_get_equalizer(XA_DecoderInfo *decoder,
'                                          XA_EqualizerInfo *equalizer);
'int XA_EXPORT decoder_codec_enable_feedback(XA_DecoderInfo *decoder);
'int XA_EXPORT decoder_codec_disable_feedback(XA_DecoderInfo *decoder);
'int XA_EXPORT decoder_set_environment_integer(XA_DecoderInfo *decoder,
'                                              const char *name,
'                                              long value);
'int XA_EXPORT decoder_get_environment_integer(XA_DecoderInfo *decoder,
'                                              const char *name,
'                                              long *value);
'int XA_EXPORT decoder_set_environment_string(XA_DecoderInfo *decoder,
'                                             const char *name,
'                                             const char *value);
'int XA_EXPORT decoder_get_environment_string(XA_DecoderInfo *decoder,
'                                             const char *name,
'                                             char *value);
'int XA_EXPORT decoder_unset_environment(XA_DecoderInfo *decoder,
'                                        const char *name);
'int XA_EXPORT decoder_add_environment_listener(XA_DecoderInfo *decoder,
'                                               const char *name,
'                                               void *client,
'                                               XA_EnvironmentCallback callback,
'                                               void **handle);
'int XA_EXPORT decoder_remove_environment_listener(XA_DecoderInfo *decoder,
'                                                  void *handle);

Public Declare Function decoder_decode Lib "xaudio.dll" (decoder As XA_DecoderInfo, ByVal output_buffer_pointer As Long) As Integer
Public Declare Function decoder_play Lib "xaudio.dll" (decoder As XA_DecoderInfo) As Integer

Public Declare Sub CopyMemory Lib "kernel32" Alias "RtlMoveMemory" (ByVal hpvDest As Long, ByVal hpvSource As Long, ByVal cbCopy As Long)

Public Declare Function GlobalAlloc Lib "kernel32" (ByVal wFlags As Long, ByVal dwBytes As Long) As Long
Public Declare Function GlobalFree Lib "kernel32" (ByVal hMem As Long) As Long
Public Declare Sub FillMemory Lib "kernel32.dll" Alias "RtlFillMemory" (ByVal Destination As Long, ByVal Length As Long, ByVal Fill As Byte)

Public Const GMEM_FIXED = &H0


Public Type ID3V1
    Header As String * 3   '/*标签头必须是"TAG"否则认为没有标签*/
    Title As String * 30   '/*标题*/
    Artist As String * 30  '/*作者*/
    Album As String * 30   '/*专集*/
    Year As String * 4     '/*出品年代*/
    Comment As String * 30 '/*备注*/
    Genre As Byte
End Type

Public Type WaveFormatType
    SamplesPerSec As Long
    BitsPerSample As Long
    Channels As Long
End Type

Public Type MP3InfoType
    Frames As Long
    ByteLength As Long
    SecondLength As Long
    WaveFormat As WaveFormatType
End Type


本文地址:http://com.8s8s.com/it/it41330.htm