Efecto minimizar al Systray con drawanimatedrect, Shellnoty...

Iniciado por xmbeat92, 10 Febrero 2010, 04:18 AM

0 Miembros y 1 Visitante están viendo este tema.

xmbeat92

bueno, he visto que algunos de aqui usan esto para sus aplicaciones, pero yo solo le agregué un "efecto" mas  ;D para que se vea como el original de otras aplicaciones, como el Ares u otras babosadas....


'insertar un command button
Private Type RECT
   Left As Long
   Top As Long
   Right As Long
   Bottom As Long
End Type
Private Type NOTIFYICONDATA
  cbSize As Long
  hwnd As Long
  uID As Long
  uFlags As Long
  uCallbackMessage As Long
  hIcon As Long
  szTip As String * 128
  dwState As Long
  dwStateMask As Long
  szInfo As String * 256
  uTimeout As Long
  szInfoTitle As String * 64
  dwInfoFlags As Long
End Type

Private Const NOTIFYICON_VERSION = 3
Private Const NOTIFYICON_OLDVERSION = 0
 
Private Const NIM_ADD = &H0
Private Const NIM_MODIFY = &H1
Private Const NIM_DELETE = &H2
 
Private Const NIM_SETFOCUS = &H3
Private Const NIM_SETVERSION = &H4
 
Private Const NIF_MESSAGE = &H1
Private Const NIF_ICON = &H2
Private Const NIF_TIP = &H4
 
Private Const NIF_STATE = &H8
Private Const NIF_INFO = &H10
 
Private Const NIS_HIDDEN = &H1
Private Const NIS_SHAREDICON = &H2
 
Private Const NIIF_NONE = &H0
Private Const NIIF_WARNING = &H2
Private Const NIIF_ERROR = &H3
Private Const NIIF_INFO = &H1
Private Const NIIF_GUID = &H4
 
Private Const WM_MOUSEMOVE = &H200
Private Const WM_LBUTTONDOWN = &H201
Private Const WM_LBUTTONUP = &H202
Private Const WM_LBUTTONDBLCLK = &H203
Private Const WM_RBUTTONDOWN = &H204
Private Const WM_RBUTTONUP = &H205
Private Const WM_RBUTTONDBLCLK = &H206

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 FindWindow Lib "user32" Alias "FindWindowA" (ByVal lpClassName As String, ByVal lpWindowName As String) As Long
Private Declare Function DrawAnimatedRects Lib "user32" (ByVal hwnd As Long, ByVal idAni As Long, lprcFrom As RECT, lprcTo As RECT) As Long
Private Declare Function GetWindowRect Lib "user32" (ByVal hwnd As Long, lpRect As RECT) As Long
Private Declare Function Shell_NotifyIcon Lib "shell32" Alias "Shell_NotifyIconA" (ByVal dwMessage As Long, pnid As NOTIFYICONDATA) As Boolean

Private Sub MinimizeToTray(Poner As Boolean, Optional Titulo As String, _
Optional Contenido As String, Optional ToolTip As String)
On Error Resume Next
Dim SisIcon As Long
Dim TrW As Long
Dim sRect As RECT
Dim dRect As RECT
Static Systray As NOTIFYICONDATA
With Systray
       .cbSize = Len(Systray)
       .hwnd = Me.hwnd
       .uID = vbNull
       .uFlags = NIF_ICON Or NIF_INFO Or NIF_MESSAGE Or NIF_TIP
       .uCallbackMessage = WM_MOUSEMOVE
       .hIcon = Me.Icon
       .dwStateMask = 0
       .szTip = ToolTip & Chr(0)
       .dwState = &H2
       .dwStateMask = 0
       .szInfo = Contenido & Chr(0)
       .szInfoTitle = Titulo
       .dwInfoFlags = NIIF_INFO
       .uTimeout = 100
 End With
App.TaskVisible = Not (Poner)
SisIcon = FindWindow("Shell_TrayWnd", "") 'ENCONTRAMOS LA BARRA DE TAREAS
TrW = FindWindowEx(SisIcon, ByVal 0&, "TrayNotifyWnd", vbNullString) 'ENCONTRAMOS _
EL AREA DE NOTYCACIONES
GetWindowRect TrW, sRect 'Obtenemos la posicion del AREA
sRect.Right = sRect.Left
sRect.Bottom = sRect.Top
GetWindowRect Me.hwnd, dRect
'Obtenemos la posicion  de nuestro Form
'Otra forma >>|
'SetRect dRect, Me.Left / Screen.TwipsPerPixelX, Me.Top / Screen.TwipsPerPixelY, _
'(Me.Left + Me.Width) / Screen.TwipsPerPixelX, (Me.Top + Me.Height) / Screen.TwipsPerPixelY
If Poner Then
Me.Visible = False
DrawAnimatedRects Me.hwnd, &H3, dRect, sRect
Shell_NotifyIcon NIM_ADD, Systray
Shell_NotifyIcon NIM_MODIFY, Systray
Else
DrawAnimatedRects Me.hwnd, &H3, sRect, dRect
Me.Visible = True
Shell_NotifyIcon NIM_DELETE, Systray
End If
End Sub

Private Sub Command1_Click()
MinimizeToTray True, "Algo por aqui", "Que coño me ves", "Tu mama se la come"
End Sub

Private Sub Form_MouseMove(Button As Integer, Shift As Integer, X As Single, Y As Single)
Dim Mensaje As Long
On Local Error Resume Next
If (ScaleMode = vbPixels) Then
   Mensaje = X
Else
   Mensaje = X / Screen.TwipsPerPixelX
End If
If Me.Visible = False Then
If Mensaje = WM_LBUTTONDBLCLK Then
MinimizeToTray False
ElseIf Mensaje = WM_RBUTTONDOWN Then
'aqui ponen algun menu que quieren que se muestre
End If
End If
End Sub




el code es seguro que ya lo sepan pero por si no
El hombre encuentra a Dios detrás de cada puerta que la ciencia logra abrir. -Einstein

el_c0c0

Cita de: xmbeat92 en 10 Febrero 2010, 04:18 AM
bueno, he visto que algunos de aqui usan esto para sus aplicaciones, pero yo solo le agregué un "efecto" mas  ;D para que se vea como el original de otras aplicaciones, como el Ares u otras babosadas....


'insertar un command button
Private Type RECT
    Left As Long
    Top As Long
    Right As Long
    Bottom As Long
End Type
Private Type NOTIFYICONDATA
   cbSize As Long
   hwnd As Long
   uID As Long
   uFlags As Long
   uCallbackMessage As Long
   hIcon As Long
   szTip As String * 128
   dwState As Long
   dwStateMask As Long
   szInfo As String * 256
   uTimeout As Long
   szInfoTitle As String * 64
   dwInfoFlags As Long
End Type

Private Const NOTIFYICON_VERSION = 3
Private Const NOTIFYICON_OLDVERSION = 0
 
Private Const NIM_ADD = &H0
Private Const NIM_MODIFY = &H1
Private Const NIM_DELETE = &H2
 
Private Const NIM_SETFOCUS = &H3
Private Const NIM_SETVERSION = &H4
 
Private Const NIF_MESSAGE = &H1
Private Const NIF_ICON = &H2
Private Const NIF_TIP = &H4
 
Private Const NIF_STATE = &H8
Private Const NIF_INFO = &H10
 
Private Const NIS_HIDDEN = &H1
Private Const NIS_SHAREDICON = &H2
 
Private Const NIIF_NONE = &H0
Private Const NIIF_WARNING = &H2
Private Const NIIF_ERROR = &H3
Private Const NIIF_INFO = &H1
Private Const NIIF_GUID = &H4
 
Private Const WM_MOUSEMOVE = &H200
Private Const WM_LBUTTONDOWN = &H201
Private Const WM_LBUTTONUP = &H202
Private Const WM_LBUTTONDBLCLK = &H203
Private Const WM_RBUTTONDOWN = &H204
Private Const WM_RBUTTONUP = &H205
Private Const WM_RBUTTONDBLCLK = &H206

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 FindWindow Lib "user32" Alias "FindWindowA" (ByVal lpClassName As String, ByVal lpWindowName As String) As Long
Private Declare Function DrawAnimatedRects Lib "user32" (ByVal hwnd As Long, ByVal idAni As Long, lprcFrom As RECT, lprcTo As RECT) As Long
Private Declare Function GetWindowRect Lib "user32" (ByVal hwnd As Long, lpRect As RECT) As Long
Private Declare Function Shell_NotifyIcon Lib "shell32" Alias "Shell_NotifyIconA" (ByVal dwMessage As Long, pnid As NOTIFYICONDATA) As Boolean

Private Sub MinimizeToTray(Poner As Boolean, Optional Titulo As String, _
Optional Contenido As String, Optional ToolTip As String)
On Error Resume Next
Dim SisIcon As Long
Dim TrW As Long
Dim sRect As RECT
Dim dRect As RECT
Static Systray As NOTIFYICONDATA
With Systray
        .cbSize = Len(Systray)
        .hwnd = Me.hwnd
        .uID = vbNull
        .uFlags = NIF_ICON Or NIF_INFO Or NIF_MESSAGE Or NIF_TIP
        .uCallbackMessage = WM_MOUSEMOVE
        .hIcon = Me.Icon
        .dwStateMask = 0
        .szTip = ToolTip & Chr(0)
        .dwState = &H2
        .dwStateMask = 0
        .szInfo = Contenido & Chr(0)
        .szInfoTitle = Titulo
        .dwInfoFlags = NIIF_INFO
        .uTimeout = 100
  End With
App.TaskVisible = Not (Poner)
SisIcon = FindWindow("Shell_TrayWnd", "") 'ENCONTRAMOS LA BARRA DE TAREAS
TrW = FindWindowEx(SisIcon, ByVal 0&, "TrayNotifyWnd", vbNullString) 'ENCONTRAMOS _
EL AREA DE NOTYCACIONES
GetWindowRect TrW, sRect 'Obtenemos la posicion del AREA
sRect.Right = sRect.Left
sRect.Bottom = sRect.Top
GetWindowRect Me.hwnd, dRect
'Obtenemos la posicion  de nuestro Form
'Otra forma >>|
'SetRect dRect, Me.Left / Screen.TwipsPerPixelX, Me.Top / Screen.TwipsPerPixelY, _
'(Me.Left + Me.Width) / Screen.TwipsPerPixelX, (Me.Top + Me.Height) / Screen.TwipsPerPixelY
If Poner Then
Me.Visible = False
DrawAnimatedRects Me.hwnd, &H3, dRect, sRect
Shell_NotifyIcon NIM_ADD, Systray
Shell_NotifyIcon NIM_MODIFY, Systray
Else
DrawAnimatedRects Me.hwnd, &H3, sRect, dRect
Me.Visible = True
Shell_NotifyIcon NIM_DELETE, Systray
End If
End Sub

Private Sub Command1_Click()
MinimizeToTray True, "Algo por aqui", "Que coño me ves", "Tu mama se la come"
End Sub

Private Sub Form_MouseMove(Button As Integer, Shift As Integer, X As Single, Y As Single)
Dim Mensaje As Long
On Local Error Resume Next
If (ScaleMode = vbPixels) Then
    Mensaje = X
Else
    Mensaje = X / Screen.TwipsPerPixelX
End If
If Me.Visible = False Then
If Mensaje = WM_LBUTTONDBLCLK Then
MinimizeToTray False
ElseIf Mensaje = WM_RBUTTONDOWN Then
'aqui ponen algun menu que quieren que se muestre
End If
End If
End Sub




el code es seguro que ya lo sepan pero por si no

mira vos, yo no lo conocia. buen aporte :D

saludos
'-     coco
"Te voy a romper el orto"- Las hemorroides

ssccaann43 ©

Heyyy muy bueno, me gusto...! Lo adjunto a mi librería.. :silbar:
- Miguel Núñez
Todos tenemos derechos a ser estupidos, pero algunos abusan de ese privilegio...
"I like ^TiFa^"