Yesterday, 07:42 PM (This post was last modified: Yesterday, 07:45 PM by madscijr.)
I know people have posted code for playing back MIDI files on the computer, but I'm wondering how to do I/O from a real physical MIDI device plugged into the PC via USB or a MIDI interface. Say it's a Casio keyboard, sending a command for it to play a note, or detecting if a key was pressed on it. Has anyone attempted this?
Just now I thought I'd ask Google Gemini and actually got an answer!
I haven't had a chance to run it (not at the computer with a MIDI keyboard)
but here's what it came up with...
Send MIDI notes + pitch wheel to keyboard Prompt: Write code in QB64PE 4.0.0 running on Windows 11 to send MIDI notes and control the pitch wheel to a real MIDI keyboard plugged into the PC.
Code snippet
Code: (Select All)
DECLARE LIBRARY "winmm.dll"
FUNCTION midiOutOpen& (lphMidiOut&, uDeviceID&, dwCallback&, dwCallbackInstance&, dwFlags&)
FUNCTION midiOutShortMsg& (hMidiOut&, dwMsg&)
FUNCTION midiOutClose& (hMidiOut&)
END DECLARE LIBRARY
SUB OpenMidi
DIM result&
result& = midiOutOpen&(midiHandle&, MIDI_MAPPER, 0, 0, 0)
IF result& <> 0 THEN
PRINT "Could not open MIDI device."
END
END IF
END SUB
SUB CloseMidi
IF midiHandle& <> 0 THEN
midiOutClose& midiHandle&
midiHandle& = 0
END IF
END SUB
SUB SendMidiNote (channel%, note%, velocity%)
DIM msg&
IF midiHandle& = 0 THEN
PRINT "MIDI device not open."
EXIT SUB
END IF
' Note On
msg& = velocity% * 65536 + note% * 256 + (MIDI_NOTEON OR channel%)
midiOutShortMsg& midiHandle&, msg&
END SUB
SUB SendMidiNoteOff (channel%, note%, velocity%)
DIM msg&
IF midiHandle& = 0 THEN
PRINT "MIDI device not open."
EXIT SUB
END IF
' Note Off
msg& = velocity% * 65536 + note% * 256 + (MIDI_NOTEOFF OR channel%)
midiOutShortMsg& midiHandle&, msg&
END SUB
SUB SendPitchWheel (channel%, pitchWheelValue%)
DIM lsb%, msb%
DIM msg&
IF midiHandle& = 0 THEN
PRINT "MIDI device not open."
EXIT SUB
END IF
lsb% = pitchWheelValue% AND &H7F
msb% = (pitchWheelValue% \ 128) AND &H7F
msg& = lsb% + msb% * 256 + (MIDI_PITCHWHEEL OR channel%)
midiOutShortMsg& midiHandle&, msg&
END SUB
SUB PlayNoteWithPitchWheel (channel%, note%, velocity%, durationMS%, pitchWheelStart%, pitchWheelEnd%)
DIM startTime!, currentTime!, elapsedTime!
DIM pitchWheelValue%
DIM currentMS%
DO WHILE (TIMER - startTime!) * 1000 < durationMS%
currentTime! = TIMER
elapsedTime! = (currentTime! - startTime!) * 1000
' Calculate pitch wheel value (linear interpolation)
pitchWheelValue% = pitchWheelStart% + (pitchWheelEnd% - pitchWheelStart%) * (elapsedTime! / durationMS%)
SendPitchWheel channel%, pitchWheelValue%
'Delay to reduce cpu usage.
currentMS% = (TIMER-startTime!)*1000
DO WHILE ((TIMER-startTime!)*1000) < currentMS% + 1 : LOOP
LOOP
SendMidiNoteOff channel%, note%, velocity%
SendPitchWheel channel%, 8192 ' Reset pitch wheel to center
CloseMidi
END SUB
' Example Usage
OpenMidi
PlayNoteWithPitchWheel 0, 60, 100, 2000, 8192, 0 'Middle C, 2 sec, no bend to full bend down.
CloseMidi
END
Explanation and Key Differences (QB64PE):
Library Declarations:
QB64PE uses DECLARE LIBRARY "winmm.dll" to import the Windows Multimedia (WinMM) API functions.
The function declarations are similar to VBA but use QB64PE's syntax.
Data Types:
QB64PE uses % for integers, & for long integers, and ! for single-precision floating-point numbers.
Correct data types are very important for the API calls to work.
Constants:
Constants are declared using CONST.
Subroutines:
Subroutines are defined using SUB and END SUB.
MIDI Message Construction:
The MIDI message construction is the same as in VBA.
Pitch Wheel Handling:
The pitch wheel calculation and handling are identical.
Timing:
QB64PE uses the TIMER function for timing.
A small delay loop is added within the PlayNoteWithPitchWheel subroutine to reduce CPU usage. This is essential, because without it, the loop will consume 100% of a CPU core.
Example Usage:
The example usage is included directly in the main program.
No DoEvents:
QB64PE does not have a direct equivalent of VBA's DoEvents. The delay loop is a basic way of providing time for other processes.
How to Use:
Open QB64PE: Launch QB64PE.
Paste Code: Paste the code into the QB64PE editor.
Run Program: Press F5 to run the program.
MIDI Setup: Ensure your MIDI keyboard is connected and working.
Adjust Parameters: Modify the parameters in the PlayNoteWithPitchWheel call to experiment with different notes, velocities, durations, and pitch bend amounts.
Important Notes:
MIDI Drivers: Make sure your MIDI keyboard's drivers are correctly installed.
Error Handling: Add more robust error handling as needed.
Timing: The timing using TIMER and the delay loop might not be perfectly precise.
CPU Usage: The delay loop is important to prevent excessive CPU usage.
64-bit: QB64PE is 64 bit, so the long integers are correct.
Read MIDI notes + pitch wheel from keyboard Prompt: Write code in QB64PE 4.0.0 running on Windows 11 to read MIDI notes and the pitch wheel from a real MIDI keyboard plugged into the PC. Code snippet
Code: (Select All)
DECLARE LIBRARY "winmm.dll"
FUNCTION midiInOpen& (lphMidiIn&, uDeviceID&, dwCallback&, dwCallbackInstance&, dwFlags&)
FUNCTION midiInClose& (hMidiIn&)
FUNCTION midiInStart& (hMidiIn&)
FUNCTION midiInStop& (hMidiIn&)
FUNCTION midiInReset& (hMidiIn&)
END DECLARE LIBRARY
result& = midiInOpen&(midiInHandle&, MIDI_MAPPER, midiCallbackAddress&, 0, CALLBACK_FUNCTION)
IF result& <> 0 THEN
PRINT "Could not open MIDI input device."
END
END IF
result& = midiInStart&(midiInHandle&)
IF result& <> 0 THEN
PRINT "Could not start MIDI input."
midiInClose& midiInHandle&
midiInHandle& = 0
END
END IF
midiHeader.lpData& = VARPTR(midiBuffer%(0))
midiHeader.dwBufferLength& = 1
' Add midiInAddBuffer here if needed.
END SUB
SUB CloseMidiInput
IF midiInHandle& <> 0 THEN
midiInStop& midiInHandle&
midiInReset& midiInHandle&
midiInClose& midiInHandle&
midiInHandle& = 0
END IF
END SUB
SUB MidiInProc (hMidiIn&, wMsg&, dwInstance&, dwParam1&, dwParam2&)
DIM status&
DIM data1%
DIM data2%
DIM channel%
DIM note%
DIM velocity%
DIM pitchWheelLSB%
DIM pitchWheelMSB%
DIM pitchWheelValue%
IF wMsg& = MM_MIM_DATA THEN
status& = dwParam1& AND &HF0
channel% = dwParam1& AND &HF
data1% = (dwParam1& \ &H100) AND &H7F
data2% = (dwParam1& \ &H10000) AND &H7F
SELECT CASE status&
CASE MIDI_NOTEON
note% = data1%
velocity% = data2%
PRINT "Note On: Channel="; channel% + 1; ", Note="; note%; ", Velocity="; velocity%
CASE MIDI_NOTEOFF
note% = data1%
velocity% = data2%
PRINT "Note Off: Channel="; channel% + 1; ", Note="; note%; ", Velocity="; velocity%
CASE MIDI_PITCHWHEEL
pitchWheelLSB% = data1%
pitchWheelMSB% = data2%
pitchWheelValue% = pitchWheelLSB% + (pitchWheelMSB% * 128)
PRINT "Pitch Wheel: Channel="; channel% + 1; ", Value="; pitchWheelValue%
CASE ELSE
PRINT "MIDI Message: Status="; HEX$(status&); ", Data1="; data1%; ", Data2="; data2%
END SELECT
END IF
END SUB
' Example Usage
OpenMidiInput
PRINT "Listening for MIDI input. Press any key to stop."
DO
IF INKEY$ <> "" THEN EXIT DO
LOOP
CloseMidiInput
END
Key Changes and Explanations for QB64PE:
Library Declarations:
DECLARE LIBRARY "winmm.dll" is used for WinMM API functions.
Data Types:
Correct data types are crucial (% for integers, & for long integers).
Callback Address:
midiCallbackAddress& = VARSEG(MidiInProc) * &H10000 + VARPTR(MidiInProc) is used to calculate the callback address. This is essential in QB64PE.
MIDI Header:
The MIDIHDR type and midiBuffer% are used for receiving MIDI data.
Opening and Closing MIDI Input:
OpenMidiInput and CloseMidiInput handle device opening and closing.
Callback Function (MidiInProc):
This function receives and parses MIDI messages.
The SELECT CASE statement handles MIDI_NOTEON, MIDI_NOTEOFF, and MIDI_PITCHWHEEL.
Message Parsing:
The code extracts the status byte, channel, and data bytes from dwParam1&.
The pitch wheel value is calculated.
Example Usage:
The example starts MIDI input and waits for a key press to stop.
MIDI messages are printed to the console.
Console Output:
PRINT statements display MIDI data in the console.
No DoEvents:
In a simple listening loop, a tight loop is acceptable. If you need it to run in the background while the user does other things, you will need to restructure the code.
How to Use:
Open QB64PE: Launch QB64PE.
Paste Code: Paste the code into the editor.
Run Program: Press F5.
Play Keyboard: Play your MIDI keyboard. The MIDI messages will be displayed in the console.
Stop: Press any key to stop the program.
MIDI Setup: Ensure your MIDI keyboard is connected and working.
9 hours ago(This post was last modified: 8 hours ago by madscijr.)
Made some changes and the errors went away in the "send MIDI" program (but still don't have my MIDI keyboard so can't test),
and fixed most of the errors in the "read MIDI" except for:
line 25: defines an array inside of a TYPE used by an API function, not sure what to do, but the code doesn't seem to use this property, so maybe not an issue? dwReserved2(3) as long
line 62: supposed to define a callback function, not sure how to do this in QB64PE? midiCallbackAddress& = VARSEG(MidiInProc) * &H10000 + VARPTR(MidiInProc) ' Callback address
Code is below, and also attached required library file (place it in the same folder as the code)...
Send MIDI note to keyboard:
Code: (Select All)
' Send MIDI notes/pitch wheel info to keyboard
' Be sure to include "winmm.h" in the same folder as the program
' winmm.h can be found at https://github.com/github/VisualStudio/blob/master/tools/Debugging%20Tools%20for%20Windows/winext/manifest/winmm.h
'https://learn.microsoft.com/en-us/windows/win32/api/mmeapi/nf-mmeapi-midioutshortmsg
Function midiOutShortMsg& (hMidiOut&, dwMsg&)
'https://learn.microsoft.com/en-us/windows/win32/api/mmeapi/nf-mmeapi-midioutclose
Function midiOutClose& (hMidiOut&)
End Declare
Dim Shared midiHandle&
' Example Usage
OpenMidi
PlayNoteWithPitchWheel 0, 60, 100, 2000, 8192, 0 ' Middle C, 2 sec, no bend to full bend down.
CloseMidi
End
Sub OpenMidi
Dim result&
result& = midiOutOpen&(midiHandle&, MIDI_MAPPER, 0, 0, 0)
If result& <> 0 Then
Print "Could not open MIDI device."
End
End If
End Sub ' OpenMidi
Sub CloseMidi
Dim value1&
If midiHandle& <> 0 Then
value1& = midiOutClose&(midiHandle&)
midiHandle& = 0
End If
End Sub ' CloseMidi
Sub SendMidiNote (channel%, note%, velocity%)
Dim msg&
Dim value1&
If midiHandle& = 0 Then
Print "MIDI device not open."
Exit Sub
End If
' Note On
msg& = velocity% * 65536 + note% * 256 + (MIDI_NOTEON Or channel%)
value1& = midiOutShortMsg&(midiHandle&, msg&)
End Sub ' SendMidiNote
Sub SendMidiNoteOff (channel%, note%, velocity%)
Dim msg&
Dim value1&
If midiHandle& = 0 Then
Print "MIDI device not open."
Exit Sub
End If
' Note Off
msg& = velocity% * 65536 + note% * 256 + (MIDI_NOTEOFF Or channel%)
value1& = midiOutShortMsg&(midiHandle&, msg&)
End Sub ' SendMidiNoteOff
Sub SendPitchWheel (channel%, pitchWheelValue%)
Dim lsb%
Dim msb%
Dim msg&
Dim value1&
If midiHandle& = 0 Then
Print "MIDI device not open."
Exit Sub
End If
lsb% = pitchWheelValue% And &H7F
msb% = (pitchWheelValue% \ 128) And &H7F
msg& = lsb% + msb% * 256 + (MIDI_PITCHWHEEL Or channel%)
value1& = midiOutShortMsg&(midiHandle&, msg&)
End Sub ' SendPitchWheel
Sub PlayNoteWithPitchWheel (channel%, note%, velocity%, durationMS%, pitchWheelStart%, pitchWheelEnd%)
Dim startTime!, currentTime!, elapsedTime!
Dim pitchWheelValue%
Dim currentMS%
Do While (Timer - startTime!) * 1000 < durationMS%
currentTime! = Timer
elapsedTime! = (currentTime! - startTime!) * 1000
' Calculate pitch wheel value (linear interpolation)
pitchWheelValue% = pitchWheelStart% + (pitchWheelEnd% - pitchWheelStart%) * (elapsedTime! / durationMS%)
SendPitchWheel channel%, pitchWheelValue%
'Delay to reduce cpu usage.
currentMS% = (Timer - startTime!) * 1000
Do While ((Timer - startTime!) * 1000) < currentMS% + 1: Loop
Loop
SendMidiNoteOff channel%, note%, velocity%
SendPitchWheel channel%, 8192 ' Reset pitch wheel to center
CloseMidi
End Sub ' PlayNoteWithPitchWheel
Read MIDI note from keyboard (lines 25 and 62 need fixing):
Code: (Select All)
' Read MIDI notes/pitch wheel from keyboard
' Be sure to include "winmm.h" in the same folder as the program
' winmm.h can be found at https://github.com/github/VisualStudio/blob/master/tools/Debugging%20Tools%20for%20Windows/winext/manifest/winmm.h
Type MIDIHDR
lpData As Long
dwBufferLength As Long
dwBytesRecorded As Long
dwUser As Long
dwFlags As Long
lpNext As Long
dwReserved As Long
dwOffset As Long
'********************************************************************************
'*** HOW DO YOU DECLARE THIS IN A TYPE IN QB64PE, AN ARRAY IN A TYPE?
dwReserved2(3) as long
'********************************************************************************
'https://learn.microsoft.com/en-us/windows/win32/api/mmeapi/nf-mmeapi-midiinclose
Function midiInClose& (hMidiIn&)
'https://learn.microsoft.com/en-us/windows/win32/api/mmeapi/nf-mmeapi-midiinstart
Function midiInStart& (hMidiIn&)
'https://learn.microsoft.com/en-us/windows/win32/api/mmeapi/nf-mmeapi-midiinstop
Function midiInStop& (hMidiIn&)
'https://learn.microsoft.com/en-us/windows/win32/api/mmeapi/nf-mmeapi-midiinreset
Function midiInReset& (hMidiIn&)
End Declare
Dim Shared midiInHandle&
Dim Shared midiCallbackAddress&
Dim Shared midiBuffer%(0 To 0) ' Single byte buffer
Dim Shared midiHeader As MIDIHDR
' Example Usage
OpenMidiInput
Print "Listening for MIDI input. Press any key to stop."
Do
If InKey$ <> "" Then Exit Do
Loop
CloseMidiInput
End
Sub OpenMidiInput
Dim result&
Dim value1&
'********************************************************************************
'***THIS IS SUPPOSED TO BE A CALLBACK, NOT SURE HOW TO DO THIS IN QB64PE:
midiCallbackAddress& = VARSEG(MidiInProc) * &H10000 + VARPTR(MidiInProc) ' Callback address
'********************************************************************************
result& = midiInOpen&(midiInHandle&, MIDI_MAPPER, midiCallbackAddress&, 0, CALLBACK_FUNCTION)
If result& <> 0 Then
Print "Could not open MIDI input device."
End
End If
result& = midiInStart&(midiInHandle&)
If result& <> 0 Then
Print "Could not start MIDI input."
value1& = midiInClose&(midiInHandle&)
midiInHandle& = 0
End
End If
midiHeader.lpData = VarPtr(midiBuffer%(0))
midiHeader.dwBufferLength = 1
'Add midiInAddBuffer here if needed.
End Sub ' OpenMidiInput
Sub CloseMidiInput
Dim value1&
If midiInHandle& <> 0 Then
value1& = midiInStop&(midiInHandle&)
value1& = midiInReset&(midiInHandle&)
value1& = midiInClose&(midiInHandle&)
midiInHandle& = 0
End If
End Sub ' CloseMidiInput
Sub MidiInProc (hMidiIn&, wMsg&, dwInstance&, dwParam1&, dwParam2&)
Dim status&
Dim data1%
Dim data2%
Dim channel%
Dim note%
Dim velocity%
Dim pitchWheelLSB%
Dim pitchWheelMSB%
Dim pitchWheelValue%
If wMsg& = MM_MIM_DATA Then
status& = dwParam1& And &HF0
channel% = dwParam1& And &HF
data1% = (dwParam1& \ &H100) And &H7F
data2% = (dwParam1& \ &H10000) And &H7F
Select Case status&
Case MIDI_NOTEON
note% = data1%
velocity% = data2%
Print "Note On: Channel="; channel% + 1; ", Note="; note%; ", Velocity="; velocity%
Case MIDI_NOTEOFF
note% = data1%
velocity% = data2%
Print "Note Off: Channel="; channel% + 1; ", Note="; note%; ", Velocity="; velocity%
Case MIDI_PITCHWHEEL
pitchWheelLSB% = data1%
pitchWheelMSB% = data2%
pitchWheelValue% = pitchWheelLSB% + (pitchWheelMSB% * 128)
Print "Pitch Wheel: Channel="; channel% + 1; ", Value="; pitchWheelValue%
Case Else
Print "MIDI Message: Status="; Hex$(status&); ", Data1="; data1%; ", Data2="; data2%
End Select
End If
End Sub ' MidiInProc
This only works for Windows, but @a740g is working on (among many other things!) MIDI input support in addition to MIDI output support, and we've got some good tests working already.
5 hours ago(This post was last modified: 5 hours ago by madscijr.)
I do recall @SpriggsySpriggs used a callback in his webcam code, I think these bits provide what we would need for the callback, but also maybe for that array definition inside the type? I'm including the whole mess at the bottom of this message.
I am not well-versed on these _Offset types and padding, but think that's the way we can approximate the type definitions that would be native to C++ but aren't directly supported in QB64PE.
That array being declared inside the type dwReserved2(3) as long
is 0-based, right? So 0..3, that's 4 long integers, which are 4 bytes each, so we need to reserve 16 bytes?
Is there any additional "overhead" for the array we need to add?
I see the webcam code has definitions in the Type MSG like
Code: (Select All)
$If 64BIT Then
As String * 4 padding1
$End If
As _Unsigned _Offset wParam
As _Offset lParam
but I really don't know when to use _Offset or _Unsigned _Offset or String * 4 (what even is that?)
Spriggsy if you're there, I need you pal!
also I see you have a custom type library with
Declare CustomType Library ... Function GetProcAddress%& (ByVal hModule As _Offset, lpProcName As String) End Declare
and I see Sub SetupDriver calls GetProcAddress to get the callback address, I guess I'll just add in that whole block?
This whole thing is possible, I can smell it, but I'm like that monkey contemplating the monolith, to whom a simple bone club is cutting edge... oook! oook!
Code: (Select All)
Type MSG
As _Offset hwnd
As _Unsigned Long message
$If 64BIT Then
As String * 4 padding1
$End If
As _Unsigned _Offset wParam
As _Offset lParam
As _Unsigned Long time
$If 64BIT Then
As String * 4 padding2
$End If
As POINT pt
As _Unsigned Long lPrivat
End Type
Declare Dynamic Library "Avicap32"
Function CreateCaptureWindow& Alias "capCreateCaptureWindowA" (ByVal lpszWindowName As _Offset, ByVal dwStyle As _Unsigned Long, ByVal x As Long, ByVal y As Long, ByVal nWidth As Long, ByVal nHeight As Long, ByVal hwndParent As _Offset, ByVal nId As Long)
End Declare
Declare CustomType Library
Sub SendMessage Alias "SendMessageA" (ByVal hWnd As _Offset, ByVal Msg As _Unsigned Long, ByVal wParam As _Offset, ByVal lParam As _Offset)
Function SendMessage& Alias "SendMessageA" (ByVal hWnd As _Offset, ByVal Msg As _Unsigned Long, ByVal wParam As _Offset, ByVal lParam As _Offset)
Function PeekMessage& Alias "PeekMessageA" (ByVal lpMsg As _Offset, ByVal hWnd As _Offset, ByVal wMsgFilterMin As _Unsigned Long, ByVal wMsgFilterMax As _Unsigned Long, ByVal wRemoveMsg As _Unsigned Long)
Sub TranslateMessage (ByVal lpMsg As _Offset)
Sub DispatchMessage (ByVal lpMsg As _Offset)
Sub DestroyWindow (ByVal hWnd As _Offset)
Function mmioStringToFOURCC& (sz As String, ByVal uFlags As _Unsigned Long)
Function OpenClipboard& (ByVal hWndNewOwner As _Offset)
Function GetClipboardData%& (ByVal uFormat As _Unsigned Long)
Sub CloseClipboard ()
Function GlobalLock%& (ByVal hMem As _Offset)
Function GlobalUnlock& (ByVal hMem As _Offset)
Function LoadLibrary%& (lpLibFileName As String)
Function GetProcAddress%& (ByVal hModule As _Offset, lpProcName As String)
End Declare
Declare Library ".\internal\c\c_compiler\include\vfw"
End Declare
Declare Library "framecallback"
End Declare
Declare CustomType Library
Sub SendMessage Alias "SendMessageA" (ByVal hWnd As _Offset, ByVal Msg As _Unsigned Long, ByVal wParam As _Offset, ByVal lParam As _Offset)
Function SendMessage& Alias "SendMessageA" (ByVal hWnd As _Offset, ByVal Msg As _Unsigned Long, ByVal wParam As _Offset, ByVal lParam As _Offset)
Function PeekMessage& Alias "PeekMessageA" (ByVal lpMsg As _Offset, ByVal hWnd As _Offset, ByVal wMsgFilterMin As _Unsigned Long, ByVal wMsgFilterMax As _Unsigned Long, ByVal wRemoveMsg As _Unsigned Long)
Sub TranslateMessage (ByVal lpMsg As _Offset)
Sub DispatchMessage (ByVal lpMsg As _Offset)
Sub DestroyWindow (ByVal hWnd As _Offset)
Function mmioStringToFOURCC& (sz As String, ByVal uFlags As _Unsigned Long)
Function OpenClipboard& (ByVal hWndNewOwner As _Offset)
Function GetClipboardData%& (ByVal uFormat As _Unsigned Long)
Sub CloseClipboard ()
Function GlobalLock%& (ByVal hMem As _Offset)
Function GlobalUnlock& (ByVal hMem As _Offset)
Function LoadLibrary%& (lpLibFileName As String)
Function GetProcAddress%& (ByVal hModule As _Offset, lpProcName As String)
End Declare
Declare Library ".\internal\c\c_compiler\include\vfw"
End Declare
Sub SetupDriver (hwnd As _Offset, defaultSource As _Byte)
Dim As _Offset libload: libload = LoadLibrary(Command$(0))
Dim As _Offset myCallback: myCallback = GetProcAddress(libload, "CapVideoCallback")
If myCallback = 0 Then
Print "Can't find callback pointer"
End
End If
...
SendMessage hwnd, WM_CAP_GET_VIDEOFORMAT, 0, _Offset(format)
SendMessage hwnd, WM_CAP_SET_CALLBACK_FRAME, 0, myCallback
End Sub
Function CapVideoCallback%& (hWnd As _Offset, lpVHdr As _Offset)
Type VIDEOHDR
As _Offset lpData
As _Unsigned Long dwBufferLength, dwBytesUsed, dwTimeCaptured
As String * 4 padding1
As _Unsigned _Offset dwUser
As _Unsigned Long dwFlags
As String * 4 padding2
As _Offset dwReserved1, dwReserved2, dwReserved3, dwReserved4
End Type
...
End Function
(6 hours ago)grymmjack Wrote: This is sweet @bplus - FYI @a740g
This only works for Windows, but @a740g is working on (among many other things!) MIDI input support in addition to MIDI output support, and we've got some good tests working already.
PS One "feature" I would maybe request for QB64PE, would be supporting arrays inside types, or at least an easier way to declare these API functions and the types they use and callbacks inside QB64, without having to be a brain surgeon, LOL.