Projects

Find all our projects in development below.
All source code is GNU General Public License (GPL)

RemoteAmp

Browsing Server/cWinamp.cls (12.90 KB)

VERSION 1.0 CLASS
BEGIN
  MultiUse = -1  'True
  Persistable = 0  'NotPersistable
  DataBindingBehavior = 0  'vbNone
  DataSourceBehavior  = 0  'vbNone
  MTSTransactionMode  = 0  'NotAnMTSObject
END
Attribute VB_Name = "cWinamp"
Attribute VB_GlobalNameSpace = False
Attribute VB_Creatable = True
Attribute VB_PredeclaredId = False
Attribute VB_Exposed = False
Option Explicit

Private Declare Function FindWindow Lib "user32" Alias "FindWindowA" (ByVal lpClassName As String, ByVal lpWindowName As String) As Long
Private Declare Function FindWindowEx Lib "user32" Alias "FindWindowExA" (ByVal hWnd1 As Long, ByVal hWnd2 As Long, ByVal lpsz1 As String, ByVal lpsz2 As String) As Long
Private Declare Function GetWindowText Lib "user32" Alias "GetWindowTextA" (ByVal hWnd As Long, ByVal lpString As String, ByVal cch As Long) As Long
Private Declare Function PostMessage Lib "user32" Alias "PostMessageA" (ByVal hWnd As Long, ByVal wMsg As Long, ByVal wParam As Long, ByVal lParam As Long) As Long
Private Declare Function SendMessage Lib "user32" Alias "SendMessageA" (ByVal hWnd As Long, ByVal wMsg As Long, ByVal wParam As Long, lParam As Any) As Long
Private Declare Function SendMessageCDS Lib "user32" Alias "SendMessageA" (ByVal hWnd As Long, ByVal wMsg As Long, ByVal wParam As Long, lParam As COPYDATASTRUCT) As Long
Private Declare Function SendMessageLong Lib "user32" Alias "SendMessageA" (ByVal hWnd As Long, ByVal wMsg As Long, ByVal wParam As Long, ByVal lParam As Long) As Long
Private Declare Function SendMessageByString Lib "user32" Alias "SendMessageA" (ByVal hWnd As Long, ByVal wMsg As Long, ByVal wParam As Long, ByVal lParam As String) As Long

Private Const WM_USER = &H400
Private Const WM_COMMAND = &H111
Private Const WM_COPYDATA = &H4A

Private Type COPYDATASTRUCT
        dwData As Long
        cbData As Long
        lpData As String
End Type

Dim mProp_hWnd As Long

Public Sub PlaylistClear()
    SendMessageLong mProp_hWnd, WM_USER, 0, 101
End Sub

Public Sub SetPlaylistPositionEx(intIndex As Integer)
    Dim lngJumpto As Long
    Dim lngListBox As Long
    PostMessage mProp_hWnd, 273, 40194, 0
    Do
        DoEvents
        lngJumpto = FindWindow("#32770", "Jump to file")
        lngListBox = FindWindowEx(lngJumpto, 0, "ListBox", vbNullString)
    Loop Until lngListBox <> 0
    DoEvents
    SendMessage lngListBox, &H186, CLng(intIndex), 0&
    PostMessage lngListBox, &H203, 0&, 0&
End Sub

Public Function PlaylistAddFile(File As String) As Long
Dim CDS As COPYDATASTRUCT
    CDS.dwData = 100
    CDS.lpData = File
    CDS.cbData = Len(File) + 1
    PlaylistAddFile = SendMessageCDS(mProp_hWnd, WM_COPYDATA, 0&, CDS)
End Function

Public Function WinampChangeDirectory(Directory As String) As Long
Dim CDS As COPYDATASTRUCT
    CDS.dwData = 103
    CDS.lpData = Directory
    CDS.cbData = Len(Directory) + 1
    WinampChangeDirectory = SendMessageCDS(mProp_hWnd, WM_COPYDATA, 0&, CDS)
End Function

Public Function TrackReturnCurrent(Optional lngMins As Long, Optional lngHours As Long) As String
    Dim lngSeconds As Long
    Dim lngSecs As Long
    Dim lngSecs2 As Long
    lngSeconds = TrackReturnCurrentInSeconds
    lngHours = Fix(lngSeconds / 3600)
    lngSecs = lngSeconds - (lngHours * 3600)
    lngMins = Fix(lngSecs / 60)
    lngSecs2 = lngSecs - (lngMins * 60)
    TrackReturnCurrent = Format(lngHours, "00:") & Format(lngMins, "00:") & Format(lngSecs2, "00")
End Function

Public Function GetWinampSongName() As String
    Dim strTitle As String
    strTitle = GetWinampTitle
    If Left(strTitle, 6) <> "Winamp" Then
        GetWinampSongName = Trim(Left(strTitle, InStrRev(strTitle, "-") - 1))
    Else
        GetWinampSongName = ""
    End If
End Function

Public Function ReInitialize() As Long
    mProp_hWnd = FindWindow("Winamp v1.x", vbNullString)
    ReInitialize = mProp_hWnd
End Function


Private Sub Class_Initialize()
   ReInitialize
End Sub

Public Property Get hWnd() As Long
   hWnd = mProp_hWnd
End Property

Public Function TrackPrev() As Long
   TrackPrev = PostMessage(mProp_hWnd, WM_COMMAND, 40044, 0&)
End Function

Public Function TrackNext() As Long
   TrackNext = PostMessage(mProp_hWnd, WM_COMMAND, 40048, 0&)
End Function

Public Function TrackPlay() As Long
   TrackPlay = PostMessage(mProp_hWnd, WM_COMMAND, 40045, 0&)
End Function

Public Function TrackPause() As Long
   TrackPause = PostMessage(mProp_hWnd, WM_COMMAND, 40046, 0&)
End Function

Public Function TrackStop() As Long
   TrackStop = PostMessage(mProp_hWnd, WM_COMMAND, 40047, 0&)
End Function

Public Function TrackFadeout() As Long
   TrackFadeout = PostMessage(mProp_hWnd, WM_COMMAND, 40147, 0&)
End Function

Public Function TrackStopAfter() As Long
   TrackStopAfter = PostMessage(mProp_hWnd, WM_COMMAND, 40157, 0&)
End Function
Public Function TrackFForward() As Long
   TrackFForward = PostMessage(mProp_hWnd, WM_COMMAND, 40148, 0&)
End Function

Public Function TrackFRewind() As Long
   TrackFRewind = PostMessage(mProp_hWnd, WM_COMMAND, 40144, 0&)
End Function

Public Function TrackOpenFile() As Long
   TrackOpenFile = PostMessage(mProp_hWnd, WM_COMMAND, 40029, 0&)
End Function

Public Function TrackOpenURL() As Long
   TrackOpenURL = PostMessage(mProp_hWnd, WM_COMMAND, 40155, 0&)
End Function

Public Function TrackInfo() As Long
   TrackInfo = PostMessage(mProp_hWnd, WM_COMMAND, 40188, 0&)
End Function

Public Function ListStart() As Long
   ListStart = PostMessage(mProp_hWnd, WM_COMMAND, 40154, 0&)
End Function

Public Function ListEnd() As Long
   ListEnd = PostMessage(mProp_hWnd, WM_COMMAND, 40158, 0&)
End Function

Public Function VisDispElapsed() As Long
   VisDispElapsed = PostMessage(mProp_hWnd, WM_COMMAND, 40037, 0&)
End Function

Public Function VisDispRemaining() As Long
   VisDispRemaining = PostMessage(mProp_hWnd, WM_COMMAND, 40038, 0&)
End Function

Public Function VisPlugInOptions() As Long
   VisPlugInOptions = PostMessage(mProp_hWnd, WM_COMMAND, 40191, 0&)
End Function

Public Function VisPlugInExec() As Long
   VisPlugInExec = PostMessage(mProp_hWnd, WM_COMMAND, 40192, 0&)
End Function

Public Function TogglePreferences() As Long
   TogglePreferences = PostMessage(mProp_hWnd, WM_COMMAND, 40012, 0&)
End Function

Public Function ToggleAbout() As Long
   ToggleAbout = PostMessage(mProp_hWnd, WM_COMMAND, 40041, 0&)
End Function

Public Function ToggleAutoscroll() As Long
   ToggleAutoscroll = PostMessage(mProp_hWnd, WM_COMMAND, 40189, 0&)
End Function

Public Function ToggleAlwaysOnTop() As Long
   ToggleAlwaysOnTop = PostMessage(mProp_hWnd, WM_COMMAND, 40019, 0&)
End Function

Public Function ToggleWindowshadeMain() As Long
   ToggleWindowshadeMain = PostMessage(mProp_hWnd, WM_COMMAND, 40064, 0&)
End Function

Public Function ToggleWindowshadeList() As Long
   ToggleWindowshadeList = PostMessage(mProp_hWnd, WM_COMMAND, 40266, 0&)
End Function

Public Function ToggleDoublesize() As Long
   ToggleDoublesize = PostMessage(mProp_hWnd, WM_COMMAND, 40165, 0&)
End Function

Public Function ToggleEQ() As Long
   ToggleEQ = PostMessage(mProp_hWnd, WM_COMMAND, 40036, 0&)
End Function

Public Function ToggleList() As Long
   ToggleList = PostMessage(mProp_hWnd, WM_COMMAND, 40040, 0&)
End Function

Public Function ToggleMain() As Long
   ToggleMain = PostMessage(mProp_hWnd, WM_COMMAND, 40258, 0&)
End Function

Public Function ToggleBrowser() As Long
   ToggleBrowser = PostMessage(mProp_hWnd, WM_COMMAND, 40298, 0&)
End Function

Public Function ToggleEasyMove() As Long
   ToggleEasyMove = PostMessage(mProp_hWnd, WM_COMMAND, 40186, 0&)
End Function

Public Function ToggleRepeat() As Long
   ToggleRepeat = PostMessage(mProp_hWnd, WM_COMMAND, 40022, 0&)
End Function

Public Function ToggleShuffle() As Long
   ToggleShuffle = PostMessage(mProp_hWnd, WM_COMMAND, 40023, 0&)
End Function

Public Function VolRaise() As Long
   VolRaise = PostMessage(mProp_hWnd, WM_COMMAND, 40058, 0&)
End Function

Public Function VolLower() As Long
    VolLower = PostMessage(mProp_hWnd, WM_COMMAND, 40059, 0&)
End Function

Public Function MiscJumpToTime() As Long
   MiscJumpToTime = PostMessage(mProp_hWnd, WM_COMMAND, 40193, 0&)
End Function

Public Function MiscJumpToFile() As Long
   MiscJumpToFile = PostMessage(mProp_hWnd, WM_COMMAND, 40194, 0&)
End Function

Public Function MiscSkinSelector() As Long
   MiscSkinSelector = PostMessage(mProp_hWnd, WM_COMMAND, 40219, 0&)
End Function

Public Function MiscSkinReload() As Long
   MiscSkinReload = PostMessage(mProp_hWnd, WM_COMMAND, 40291, 0&)
End Function

Public Function MiscClose() As Long
   MiscClose = SendMessage(mProp_hWnd, WM_COMMAND, 40001, 0&)
End Function

Public Function GetWinampTitle() As String
   Dim strTitle As String
   strTitle = String(2048, Chr(0))
   GetWindowText mProp_hWnd, strTitle, Len(strTitle)
   If InStr(strTitle, Chr(0)) Then strTitle = Left(strTitle, InStr(strTitle, Chr(0)) - 1)
   GetWinampTitle = strTitle
End Function


Public Function GetWinampVersion() As String
    GetWinampVersion = Replace(Format(Hex(SendMessageLong(mProp_hWnd, WM_USER, 0, 0)), "#,###,###"), ",", ".")
End Function

Public Function PlaylistCount() As Long
    PlaylistCount = SendMessageLong(mProp_hWnd, WM_USER, 0, 124)
End Function

Public Function PlaylistPosition() As Long
    'playlist starts with 0
    PlaylistPosition = Val(SendMessageLong(mProp_hWnd, WM_USER, 0, 125))
End Function

Public Function TrackSampleRate() As Long
    TrackSampleRate = SendMessageLong(mProp_hWnd, WM_USER, 0, 126)
End Function

Public Function TrackBitRate() As Long
    TrackBitRate = SendMessageLong(mProp_hWnd, WM_USER, 1, 126)
End Function

Public Function GetWinampChannels() As Long
    GetWinampChannels = SendMessageLong(mProp_hWnd, WM_USER, 2, 126)
End Function

Public Function PlaylistWrite() As Long
    PlaylistWrite = SendMessageLong(mProp_hWnd, WM_USER, 0, 120)
End Function

Public Function TrackReturnCurrentInSeconds() As Long
    Dim lngSeconds As Long
    lngSeconds = SendMessageLong(mProp_hWnd, WM_USER, 0, 105)
    TrackReturnCurrentInSeconds = lngSeconds / 1000
End Function

Public Function TrackReturnLengthInSeconds() As Long
    TrackReturnLengthInSeconds = SendMessageLong(mProp_hWnd, WM_USER, 1, 105)
End Function

Public Function TrackReturnLength(Optional lngMins As Long, Optional lngHours As Long) As String
    Dim lngSeconds As Long
    Dim lngSecs As Long
    Dim lngSecs2 As Long
    lngSeconds = TrackReturnLengthInSeconds
    lngHours = Fix(lngSeconds / 3600)
    lngSecs = lngSeconds - (lngHours * 3600)
    lngMins = Fix(lngSecs / 60)
    lngSecs2 = lngSecs - (lngMins * 60)
    TrackReturnLength = Format(lngHours, "00:") & Format(lngMins, "00:") & Format(lngSecs2, "00")
End Function

Public Function SetWinampVolume(intVolume As Integer) As Long
    SetWinampVolume = SendMessageLong(mProp_hWnd, WM_USER, Val(intVolume), 122)
End Function

Public Function SetWinampPanning(ByVal intPanning As Integer) As Long
    If intPanning >= 128 Then
        intPanning = intPanning - 128
    Else
        intPanning = intPanning + 128
    End If
    SetWinampPanning = SendMessageLong(mProp_hWnd, WM_USER, Val(intPanning), 123)
End Function

Public Function GetWinampPlaybackStatus() As Long
    GetWinampPlaybackStatus = SendMessageLong(mProp_hWnd, WM_USER, 0, 104)
End Function

Public Function TrackSeekTime(lngSeconds As Long) As Long
    TrackSeekTime = SendMessageLong(mProp_hWnd, WM_USER, (lngSeconds * 1000), 106)
End Function

Public Sub SetPlaylistPosition(intIndex As Integer, Optional blnPlaySong As Boolean)
    If intIndex > PlaylistCount Then Exit Sub
    SendMessageLong mProp_hWnd, WM_USER, Val(intIndex), 121
    If blnPlaySong Then
        TrackPlay
    Else
        PostMessage mProp_hWnd, &H201, Val(intIndex), 121
        PostMessage mProp_hWnd, &H202, Val(intIndex), 121
    End If
End Sub

Public Function PlaylistToArray(PlayList() As String) As Long
    Dim lngJumpto As Long
    Dim lngListBox As Long
    Dim lngListIndex As Long
    Dim strListitem As String
    PostMessage mProp_hWnd, 273, 40194, 0
    Do
        DoEvents
        lngJumpto = FindWindow("#32770", "Jump to file")
        lngListBox = FindWindowEx(lngJumpto, 0, "ListBox", vbNullString)
    Loop Until lngListBox <> 0
    DoEvents
    ReDim PlayList(0)
    For lngListIndex = 0 To SendMessageLong(lngListBox, &H18B, 0, 0) - 1
        strListitem = String(512, Chr(0))
        SendMessageByString lngListBox, &H189, lngListIndex, strListitem
        If InStr(strListitem, Chr(0)) Then strListitem = Left(strListitem, InStr(strListitem, Chr(0)) - 1)
        If strListitem <> "" Then
            ReDim Preserve PlayList(UBound(PlayList) + 1)
            PlayList(UBound(PlayList)) = strListitem
        End If
    Next lngListIndex
    PlaylistToArray = SendMessage(lngListBox, &H188, 0&, 0&)
    PostMessage lngJumpto, &H10, 0, 0
End Function

Download Server/cWinamp.cls

Back to file list


Back to project page