[VB6] Object transparency

Pagina: 1
Acties:
  • 254 views sinds 30-01-2008
  • Reageer

Acties:
  • 0 Henk 'm!

  • iznogood
  • Registratie: September 2001
  • Niet online
Ik heb een form met een aantal objecten gecreeerd ( zoals bijvoorbeeld een textbox, webbrowser en buttons )

Nu heb ik de achtergrond van het form een picture meegegeven en wil ik dat deze bijvoorbeeld zichtbaar is door de textbox heen. Om dit te bereiken wil ik het object textbox ( of welk willekeurig object dan ook ) een transparency mee kunnen geven zodat de achtergrond van het form zichtbaar wordt.

Op internet is hier zo goed als niets over te vinden.

Just as Good


Acties:
  • 0 Henk 'm!

  • Stiegl
  • Registratie: Mei 2004
  • Laatst online: 20-05 21:58
Transparancy kan pas in .NET

Uit onderzoek is gebleken dat 85% van alle statistieken niet klopt


Acties:
  • 0 Henk 'm!

  • iznogood
  • Registratie: September 2001
  • Niet online
Met de api's moet dit ook vast wel lukken... ik weet dat ik ondertussen weleens moet overstappen naar .net, maar ik heb geen zin om mijn gehele app over te gaan zitten schrijven en ik weet nog niet hoe .net werkt. Dus voorlopig blijf ik VB6 gebruiken.

Just as Good


Acties:
  • 0 Henk 'm!

  • Unifex
  • Registratie: Juni 2002
  • Laatst online: 19-05 16:36
Ik heb onderstaande ooit voor een vb screensaver gebruikt.
De form heet MI.

Succes

code:
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
Attribute VB_Name = "modMain"
Option Explicit
Public blnquit As Boolean

Private Const GWL_EXSTYLE = (-20)
Private Const WS_EX_LAYERED = &H80000
Private Const WS_EX_TRANSPARENT = &H20&
Private Const LWA_ALPHA = &H2&
Private Const SPI_SETSCREENSAVEACTIVE = 17

Private Declare Function SystemParametersInfo Lib "user32" Alias "SystemParametersInfoA" (ByVal uAction As Integer, ByVal uparam As Integer, lpvParam As Any, ByVal fuWinIni As Integer) As Integer
Private Declare Function GetWindowLong Lib "user32" Alias "GetWindowLongA" (ByVal hwnd As Long, ByVal nIndex As Long) As Long
Private Declare Function SetWindowLong Lib "user32" Alias "SetWindowLongA" (ByVal hwnd As Long, ByVal nIndex As Long, ByVal dwNewLong As Long) As Long
Private Declare Function SetLayeredWindowAttributes Lib "user32" (ByVal hwnd As Long, ByVal cRey As Byte, ByVal bAlpha As Byte, ByVal dwFlags As Long) As Long
Private Declare Function ShowCursor Lib "user32" (ByVal bShow As Integer) As Integer

Private Sub Main()
    Dim lngRetVal As Long
    Dim lngTransparent As Long
    Dim lngTeller As Long

    blnquit = False
    lngTeller = 5
    lngTransparent = 5
    Select Case Command$
        Case "/s", "/S"
            lngRetVal = SystemParametersInfo(SPI_SETSCREENSAVEACTIVE, True, 0, 0)
            lngRetVal = ShowCursor(False)
            Call init
            Do While blnquit = False
                DoEvents
                Call Update(CByte(lngTransparent))
                lngTransparent = lngTransparent + lngTeller
                If lngTransparent < 6 Then lngTeller = Abs(lngTeller)
                If lngTransparent > 249 Then lngTeller = -lngTeller
            Loop
            Call Beeindig
        Case "/c", "/C"
    End Select

End Sub
Private Sub Beeindig()
    Dim lngRetVal As Long

    lngRetVal = SystemParametersInfo(SPI_SETSCREENSAVEACTIVE, False, 0, 0)
    lngRetVal = ShowCursor(True)
    Unload MI

End Sub
Private Sub init()
    Dim lngSolid As Long

    MI.WindowState = 2
    MI.Show
    lngSolid = GetWindowLong(MI.hwnd, GWL_EXSTYLE)
    SetWindowLong MI.hwnd, GWL_EXSTYLE, lngSolid Or WS_EX_LAYERED

End Sub
Public Sub Update(ByVal bteTransparent As Byte)

    SetLayeredWindowAttributes MI.hwnd, 0, bteTransparent, LWA_ALPHA

End Sub

Guess what we are not stupid, just ignorant!


Acties:
  • 0 Henk 'm!

  • iznogood
  • Registratie: September 2001
  • Niet online
Unifex schreef op maandag 24 januari 2005 @ 11:59:
Ik heb onderstaande ooit voor een vb screensaver gebruikt.
De form heet MI.

Succes

code:
1
...
Het lukt me wel om het gehele form met de code transparant te maken maar een enkel object is niet mogelijk voor zover ik het voor elkaar krijg.

Just as Good


Acties:
  • 0 Henk 'm!

Anoniem: 113297

in principe lijkt me dit mogelijk, maar dan moet je de windows handle van de textbox te pakken zien te krijgen (bv via de handle van de form en dan alle childhandles aflopen tot je het gewenste object tegenkomt)

Acties:
  • 0 Henk 'm!

  • iznogood
  • Registratie: September 2001
  • Niet online
Anoniem: 113297 schreef op maandag 24 januari 2005 @ 12:28:
in principe lijkt me dit mogelijk, maar dan moet je de windows handle van de textbox te pakken zien te krijgen (bv via de handle van de form en dan alle childhandles aflopen tot je het gewenste object tegenkomt)
I lost you :)

Just as Good


Acties:
  • 0 Henk 'm!

  • iznogood
  • Registratie: September 2001
  • Niet online
code:
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
Option Explicit

' APIs to install our subclassing routines
Private Const GWL_WNDPROC = (-4)
Private Declare Function SetWindowLong Lib "user32" Alias "SetWindowLongA" (ByVal hwnd As Long, ByVal nIndex As Long, ByVal dwNewLong As Long) As Long
Private Declare Function CallWindowProc Lib "user32" Alias "CallWindowProcA" (ByVal lpPrevWndFunc As Long, ByVal hwnd As Long, ByVal Msg As Long, ByVal wParam As Long, ByVal lParam As Long) As Long
Private Declare Function DefWindowProc Lib "user32" Alias "DefWindowProcA" (ByVal hwnd As Long, ByVal wMsg As Long, ByVal wParam As Long, ByVal lParam As Long) As Long

' These APIs are used to create a pattern brush for each textbox...
Private Declare Function BitBlt Lib "gdi32" (ByVal hDestDC As Long, ByVal x As Long, ByVal y As Long, ByVal nWidth As Long, ByVal nHeight As Long, ByVal hSrcDC As Long, ByVal xSrc As Long, ByVal ySrc As Long, ByVal dwRop As Long) As Long
Private Declare Function CreateCompatibleBitmap Lib "gdi32" (ByVal hdc As Long, ByVal nWidth As Long, ByVal nHeight As Long) As Long
Private Declare Function CreateCompatibleDC Lib "gdi32" (ByVal hdc As Long) As Long
Private Declare Function CreatePatternBrush Lib "gdi32" (ByVal hBitmap As Long) As Long
Private Declare Function CreateSolidBrush Lib "gdi32" (ByVal crColor As Long) As Long
Private Declare Function DeleteDC Lib "gdi32" (ByVal hdc As Long) As Long
Private Declare Function DeleteObject Lib "gdi32" (ByVal hObject As Long) As Long
Private Declare Function GetDC Lib "user32" (ByVal hwnd As Long) As Long
Private Declare Function GetSysColor Lib "user32" (ByVal nIndex As Long) As Long
Private Declare Function ReleaseDC Lib "user32" (ByVal hwnd As Long, ByVal hdc As Long) As Long
Private Declare Function SelectObject Lib "gdi32" (ByVal hdc As Long, ByVal hObject As Long) As Long

' Messages which we will be processing in our subclassing routines
Private Const WM_COMMAND        As Long = &H111
Private Const WM_CTLCOLOREDIT   As Long = &H133
Private Const WM_DESTROY        As Long = &H2
Private Const WM_ERASEBKGND     As Long = &H14
Private Const WM_HSCROLL        As Long = &H114
Private Const WM_VSCROLL        As Long = &H115

' A rectangle.
Private Type RECT
    Left    As Long
    Top     As Long
    Right   As Long
    Bottom  As Long
End Type

' APIs used to keep track of brush handles and process addresses
Private Declare Function GetProp Lib "user32" Alias "GetPropA" (ByVal hwnd As Long, ByVal lpString As String) As Long
Private Declare Function RemoveProp Lib "user32" Alias "RemovePropA" (ByVal hwnd As Long, ByVal lpString As String) As Long
Private Declare Function SetProp Lib "user32" Alias "SetPropA" (ByVal hwnd As Long, ByVal lpString As String, ByVal hData As Long) As Long

' APIs used in our subclassing routine to create the "transparent" effect.
Private Declare Function FillRect Lib "user32" (ByVal hdc As Long, lpRect As RECT, ByVal hBrush As Long) As Long
Private Declare Function GetClientRect Lib "user32" (ByVal hwnd As Long, lpRect As RECT) As Long
Private Declare Function GetParent Lib "user32" (ByVal hwnd As Long) As Long
Private Declare Function InvalidateRect Lib "user32" (ByVal hwnd As Long, ByVal lpRect As Long, ByVal bErase As Long) As Long
Private Declare Function LockWindowUpdate Lib "user32" (ByVal hwndLock As Long) As Long
Private Declare Function SetBkMode Lib "gdi32" (ByVal hdc As Long, ByVal nBkMode As Long) As Long
Private Declare Function UpdateWindow Lib "user32" (ByVal hwnd As Long) As Long
Private Declare Function WindowFromDC Lib "user32" (ByVal hdc As Long) As Long

Public Function makeTransparentTextbox(aTxt As TextBox)
    
    ' Make sure we don't have any typos in our subclassing procedures.
    NewWindowProc 0, 0, 0, 0
    NewTxtBoxProc 0, 0, 0, 0
    ' Create a background brush for this textbox, which we will used to give
    '  the textbox an APPEARANCE of transparency
    CreateBGBrush aTxt
    ' Subclass the textbox's form, IF NOT ALREADY subclassed
    If GetProp(GetParent(aTxt.hwnd), "OrigProcAddr") = 0 Then
        SetProp GetParent(aTxt.hwnd), "OrigProcAddr", SetWindowLong(GetParent(aTxt.hwnd), GWL_WNDPROC, AddressOf NewWindowProc)
    End If
    ' Subclass the textbox, IF NOT ALREADY subclassed
    If GetProp(aTxt.hwnd, "OrigProcAddr") = 0 Then
        SetProp aTxt.hwnd, "OrigProcAddr", SetWindowLong(aTxt.hwnd, GWL_WNDPROC, AddressOf NewTxtBoxProc)
    End If

End Function

Private Sub CreateBGBrush(aTxtBox As TextBox)

    Dim screenDC    As Long ' The screen's device context.
    Dim imgLeft     As Long ' The X location inside the image which we are going to copy from.
    Dim imgTop      As Long ' The Y location inside the image which we are going to copy from.
    Dim picDC       As Long ' A temporary DC to pull the form's picture into
    Dim picBmp      As Long ' the 1x1 bitmap which is created with picDC
    Dim aTempBmp    As Long ' A temporary bitmap we'll use to create the pattern brush for our textbox
    Dim aTempDC     As Long ' the temporary device context used to hold aTempBmp
    Dim txtWid      As Long ' The form's width
    Dim txtHgt      As Long ' the form's height.
    Dim solidBrush  As Long ' Solid brush used to color in the bitmap... incase the textbox
                            '  gets sized outside the dimensions of the picture
    Dim aRect       As RECT ' Rectangle to fill in with solid brush
    
    If aTxtBox.Parent.Picture Is Nothing Then Exit Sub
    ' Get our form's dimensions, in pixels
    txtWid = aTxtBox.Width / Screen.TwipsPerPixelX
    txtHgt = aTxtBox.Height / Screen.TwipsPerPixelY
    ' Get the location within the bitmap picture we're copying from
    imgLeft = aTxtBox.Left / Screen.TwipsPerPixelX
    imgTop = aTxtBox.Top / Screen.TwipsPerPixelY
    
    ' Get the screen's device context
    screenDC = GetDC(0)
    ' Create a device context to hold the form's picture.
    picDC = CreateCompatibleDC(screenDC)
    picBmp = SelectObject(picDC, aTxtBox.Parent.Picture.Handle)
    ' Create a temporary bitmap to blt the underlying image onto
    aTempDC = CreateCompatibleDC(screenDC)
    aTempBmp = CreateCompatibleBitmap(screenDC, txtWid, txtHgt)
    DeleteObject SelectObject(aTempDC, aTempBmp)
    ' create a brush the color of BUTTON_FACE
    solidBrush = CreateSolidBrush(GetSysColor(15))
    aRect.Right = txtWid
    aRect.Bottom = txtHgt
    ' Fill in the area
    FillRect aTempDC, aRect, solidBrush
    ' clean up our resource
    DeleteObject solidBrush
    ' Transfer the image
    BitBlt aTempDC, 0, 0, txtWid, txtHgt, picDC, imgLeft, imgTop, vbSrcCopy
    ' Check to make sure that a brush hasn't already been made for this one
    If GetProp(aTxtBox.hwnd, "CustomBGBrush") <> 0 Then
        ' If so, then delete it and free its memory before storing the new one's handle.
        DeleteObject GetProp(aTxtBox.hwnd, "CustomBGBrush")
    End If
    ' Create a pattern brush from our bitmap and store its handle against
    '  the textbox's handle
    SetProp aTxtBox.hwnd, "CustomBGBrush", CreatePatternBrush(aTempBmp)
    ' Clean up our temporary DC and bitmap resources
    DeleteDC aTempDC
    DeleteObject aTempBmp
    
    ' Replace the original 1x1 bitmap, releasing the form's picture
    SelectObject picDC, picBmp
    ' Clean up our picture DC and the 1x1 bitmap that was created with it
    DeleteDC picDC
    DeleteObject picBmp
    ' Release the screen's DC back to the system... forgetting to do this
    '  causes a nasty memory leak.
    ReleaseDC 0, screenDC
    
End Sub

Private Function NewWindowProc(ByVal hwnd As Long, ByVal uMsg As Long, ByVal wParam As Long, ByVal lParam As Long) As Long
    
    ' ******************************************************
    '  SUBCLASSING ROUTINE FOR THE TEXTBOX'S >>>>PARENT<<<<
    ' ******************************************************
    
    Dim origProc        As Long         ' The original process address for the window.
    Dim isSubclassed    As Long         ' Whether a certain textbox is subclassed or not.
    
    ' I've gotten in the habit of passing 0 values to the subclassing functions before
    '  actually installing them, just to make sure that I don't have any typos or other
    '  problems which can be easily detected. As such, if there is a hwnd of 0, its not
    '  a "valid" message, so we'll just exit right away.
    If hwnd = 0 Then Exit Function
    
    ' Get the original process address which we stored earlier.
    origProc = GetProp(hwnd, "OrigProcAddr")
    
    If origProc <> 0 Then
        If (uMsg = WM_CTLCOLOREDIT) Then
            ' Check to see if our window has a stored value for the original
            '  process address. If so, we're subclassing this one.
            isSubclassed = (GetProp(WindowFromDC(wParam), "OrigProcAddr") <> 0)
            If isSubclassed Then
                ' Invoke the default process... This will set the font, font color
                '  and other stuff we don't really want to fool with.
                CallWindowProc origProc, hwnd, uMsg, wParam, lParam
                ' Make the words print transparently
                SetBkMode wParam, 1
                ' Return the handle to our custom brush rather than that which
                '  the default process would have returned.
                NewWindowProc = GetProp(WindowFromDC(wParam), "CustomBGBrush")
            Else
                ' The textbox in question isn't subclassed, so we aren't going
                '  to do anything out of the ordinary. Just invoke the default proc.
                NewWindowProc = CallWindowProc(origProc, hwnd, uMsg, wParam, lParam)
            End If
        ElseIf uMsg = WM_COMMAND Then
            ' Check to see if our window has a stored value for the original
            '  process address. If so, we're subclassing this one.
            isSubclassed = (GetProp(lParam, "OrigProcAddr") <> 0)
            If isSubclassed Then
                ' We are going lock the window from updating while we invalidate
                '  and redraw it. This prevents flickering.
                LockWindowUpdate GetParent(lParam)
                ' Force windows to redraw the window.
                InvalidateRect lParam, 0&, 1&
                UpdateWindow lParam
            End If
            ' Invoke the default process
            NewWindowProc = CallWindowProc(origProc, hwnd, uMsg, wParam, lParam)
            If isSubclassed Then LockWindowUpdate 0&
        ElseIf uMsg = WM_DESTROY Then
            
            ' The window is being destroyed... time to unhook our process so we
            '  don't cause a big fat error which crashes the application.
            
            ' Install the default process address again
            SetWindowLong hwnd, GWL_WNDPROC, origProc
            ' Invoke the default process
            NewWindowProc = CallWindowProc(origProc, hwnd, uMsg, wParam, lParam)
            ' Remove our stored value since we don't need it anymore
            RemoveProp hwnd, "OrigProcAddr"
        Else
            ' We're not concerned about this particular message, so we'll just
            '  let it go on its merry way.
            NewWindowProc = CallWindowProc(origProc, hwnd, uMsg, wParam, lParam)
        End If
    Else
        ' A catch-all in case something freaky happens with the process addresses.
        NewWindowProc = DefWindowProc(hwnd, uMsg, wParam, lParam)
    End If
        
End Function

Private Function NewTxtBoxProc(ByVal hwnd As Long, ByVal uMsg As Long, ByVal wParam As Long, ByVal lParam As Long) As Long
    
    ' *********************************************
    '  SUBCLASSING ROUTINE FOR THE >>>>TEXTBOX<<<<
    ' *********************************************
    
    Dim aRect           As RECT
    Dim origProc        As Long
    Dim aBrush          As Long
    
    If hwnd = 0 Then Exit Function
    ' Get the original process address which we stored earlier.
    origProc = GetProp(hwnd, "OrigProcAddr")
    
    If origProc <> 0 Then
        ' We're subclassing! Which is silly, 'cause otherwise we wouldn't be in
        '  this function, however we double check the process address just in case.
        If uMsg = WM_ERASEBKGND Then
            ' We're going to get our custom brush for this textbox and fill the
            '  textbox's background area with it...
            aBrush = GetProp(hwnd, "CustomBGBrush")
            If aBrush <> 0 Then
                ' Get the area dimensions to fill
                GetClientRect hwnd, aRect
                ' Fill it with our custom brush
                FillRect wParam, aRect, aBrush
                ' Tell windows that we took care of the "erasing"
                NewTxtBoxProc = 1
            Else
                ' Something happened to our custom brush :-\ We'll just invoke
                '  the default process
                NewTxtBoxProc = CallWindowProc(origProc, hwnd, uMsg, wParam, lParam)
            End If
        ElseIf uMsg = WM_HSCROLL Or uMsg = WM_VSCROLL Then
            ' We are scrolling, either horizontally or vertically. This requires
            '  us to totally repaint the background area... so we'll lock the
            '  window updates so we don't see any of the freaky flickering
            LockWindowUpdate GetParent(hwnd)
            ' Invoke the default process so the user actually get's the scroll
            '  they want
            NewTxtBoxProc = CallWindowProc(origProc, hwnd, uMsg, wParam, lParam)
            ' Force window to repaint itself
            InvalidateRect hwnd, 0&, 1&
            UpdateWindow hwnd
            ' Release the update lock
            LockWindowUpdate 0&
        ElseIf uMsg = WM_DESTROY Then
            
            ' The textbox's parent is closing / destroying, so we need to
            '  unhook our subclassing routine ... or bad things happen
            
            ' Clean up our brush object... muy importante!!!
            aBrush = GetProp(hwnd, "CustomBGBrush")
            ' Delete the brush object, freeing its resource.
            DeleteObject aBrush
            ' Remove our values we stored against the textbox's handle
            RemoveProp hwnd, "OrigProcAddr"
            RemoveProp hwnd, "CustomBGBrush"
            ' Replace the original process address
            SetWindowLong hwnd, GWL_WNDPROC, origProc
            ' Invoke the default "destroy" process
            NewTxtBoxProc = CallWindowProc(origProc, hwnd, uMsg, wParam, lParam)
        Else
            ' We're not interested in this message, so we'll just let it truck
            '  right on thru... invoke the default process
            NewTxtBoxProc = CallWindowProc(origProc, hwnd, uMsg, wParam, lParam)
        End If
    Else
        ' A catch-all in case something freaky happens with the process addresses.
        NewTxtBoxProc = DefWindowProc(hwnd, uMsg, wParam, lParam)
    End If
    
End Function


Deze code heb ik gevonden en is in principe perfect... op het kleine punt na dat hij niet werkt icm een richtextbox control. Dan loopt het hele zaakje vast en is mijn VB plotseling weg.

De functie wordt aangeroepen met makeTransparentTextbox textbox.

Just as Good


Acties:
  • 0 Henk 'm!

  • farlane
  • Registratie: Maart 2000
  • Laatst online: 23-05 20:53
iznogood schreef op maandag 24 januari 2005 @ 22:00:
Deze code heb ik gevonden en is in principe perfect... op het kleine punt na dat hij niet werkt icm een richtextbox control. Dan loopt het hele zaakje vast en is mijn VB plotseling weg.

De functie wordt aangeroepen met makeTransparentTextbox textbox.
Tja, als je dit soort dingen doet loop je de kans dat er iets mis gaat en je applicatie zonder blikken of blozen afstort.

Wat je evt kunt doen is zoeken op codeguru ( ben ik niet helemaal zeker van ) naar de code voor het veilig subclassen van een control.

trouwens:
Met de api's moet dit ook vast wel lukken... ik weet dat ik ondertussen weleens moet overstappen naar .net ....
Is afhankelijk wat voor een type apps je maakt. Ik weet dat in mijn geval het nog helemaal geen optie is om naar .Net over te stappen voor mijn client apps.

Somniferous whisperings of scarlet fields. Sleep calling me and in my dreams i wander. My reality is abandoned (I traverse afar). Not a care if I never everwake.


Acties:
  • 0 Henk 'm!

  • sopsop
  • Registratie: Januari 2002
  • Laatst online: 23-05 14:25

sopsop

[v] [;,,;] [v]

farlane schreef op dinsdag 25 januari 2005 @ 08:59:
Wat je evt kunt doen is zoeken op codeguru ( ben ik niet helemaal zeker van ) naar de code voor het veilig subclassen van een control.
in het kader van veilig subclassen: http://www.vbaccelerator.com/codelib/ssubtmr/ssubtmr.htm

Wat meer in het kader van jouw probleem:
http://www.vbaccelerator....nto_a_TextBox/article.asp

http://www.vbaccelerator...._Draw_Buttons/article.asp

[ Voor 27% gewijzigd door sopsop op 25-01-2005 10:12 ]

Pagina: 1