Foro de elhacker.net

Programación => Programación Visual Basic => Mensaje iniciado por: ~~ en 6 Diciembre 2006, 11:38 am



Título: Form semi-transparente en el q se vean los controles???
Publicado por: ~~ en 6 Diciembre 2006, 11:38 am
Pues eso basicamente, si alguien sabe como hacer un form semi-transparente, pero q se vean los controles q tiene dentro sin transparentar.

Buscando por google e encontrado muxo code q lo hace del todo transparente y uno q lo hace semi-transparente, pero no se ven los botones  :-(

Alguien lo sabe???
1S4ludo  ;)


Título: Re: Form semi-transparente en el q se vean los controles???
Publicado por: DarkMouth en 6 Diciembre 2006, 23:59 pm

Hola que tal, prueba con esto a ver si te funciona
  ;D

Código:

Private Declare Function SetWindowLong Lib "user32" Alias _
    "SetWindowLongA" (ByVal hwnd As Long, ByVal nIndex As Long, _
    ByVal dwNewLong As Long) As Long

Private Sub Form_Load()
    Dim Resp As Long
    Resp = SetWindowLong(Me.hwnd, -20, &H20&)
    Form1.Refresh
End Sub



Título: Re: Form semi-transparente en el q se vean los controles???
Publicado por: ~~ en 7 Diciembre 2006, 11:41 am
No, yo no estoy buscando exactamente eso, tu code lo hace imbisible del todo y ademas funciona un poco mal...

Seria algo asi pero con los botones visibles:

Código:
Private mAlpha As Long

' Declaraciones para Layered Windows (sólo Windows 2000 y superior)
Private Const WS_EX_LAYERED As Long = &H80000
Private Const LWA_ALPHA As Long = &H2
'
Private Declare Function SetLayeredWindowAttributes Lib "user32" _
    (ByVal hWnd As Long, ByVal crKey As Long, _
    ByVal bAlpha As Long, ByVal dwFlags As Long) As Long

'------------------------------------------------------------------------------
Private Const GWL_EXSTYLE = (-20)

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 GetWindowLong Lib "user32" Alias "GetWindowLongA" _
    (ByVal hWnd As Long, ByVal nIndex As Long) As Long


Private Const RDW_INVALIDATE = &H1
Private Const RDW_ERASE = &H4
Private Const RDW_ALLCHILDREN = &H80
Private Const RDW_FRAME = &H400

Private Declare Function RedrawWindow2 Lib "user32" Alias "RedrawWindow" _
    (ByVal hWnd As Long, ByVal lprcUpdate As Long, ByVal hrgnUpdate As Long, _
    ByVal fuRedraw As Long) As Long


Private Sub Transparente()
        Dim tAlpha As Long
       
        tAlpha = 70 'Modificar aki el valor para hacerlo mas o menos transparente

        '// Set WS_EX_LAYERED on this window
        Call SetWindowLong(hWnd, GWL_EXSTYLE, GetWindowLong(hWnd, GWL_EXSTYLE) Or WS_EX_LAYERED)
       
        '// Make this window tAlpha% alpha
        Call SetLayeredWindowAttributes(hWnd, 0, (255 * tAlpha) / 100, LWA_ALPHA)
End Sub


Private Sub Form_Load()
    Transparente
End Sub

1S4ludo


Título: Re: Form semi-transparente en el q se vean los controles???
Publicado por: CeLaYa en 7 Diciembre 2006, 16:24 pm
¿Como se podria aplicar este código a un solo control del Form?


Título: Re: Form semi-transparente en el q se vean los controles???
Publicado por: IP3 en 7 Diciembre 2006, 21:53 pm
Prueba con un control de usuario


Título: Re: Form semi-transparente en el q se vean los controles???
Publicado por: ~~ en 7 Diciembre 2006, 23:30 pm
Código:
¿Como se podria aplicar este código a un solo control del Form?

Eso es una indirecta diciendome q tengo la solucion ante los ojos enfocando esto solo hacia el form o es q tu tampoco lo sabes???

Citar
Prueba con un control de usuario

A q te refieres??

1S4ludo


Título: Re: Form semi-transparente en el q se vean los controles???
Publicado por: dPix en 7 Diciembre 2006, 23:37 pm
Imagino que se referiría a la libreria user32.dll, es lo único que se me ocurre, con eso quizás puedas modificar la transferencia del form.

Salu2,

dPix


Título: Re: Form semi-transparente en el q se vean los controles???
Publicado por: dPix en 7 Diciembre 2006, 23:42 pm
Efectivamente, IP3, era un control de usuario, aqui le dejo el código que googleando encontré (espero que sea esto lo que buscas).

Esto a un módulo:

Citar
Option Explicit

Private Declare Function SetLayeredWindowAttributes Lib "user32" (ByVal hWnd As Long, ByVal crKey As Long, ByVal bAlpha As Byte, ByVal dwFlags As Long) As Long
Private Declare Function UpdateLayeredWindow Lib "user32" (ByVal hWnd As Long, ByVal hdcDst As Long, pptDst As Any, psize As Any, ByVal hdcSrc As Long, pptSrc As Any, crKey As Long, ByVal pblend As Long, ByVal dwFlags As Long) As Long
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 Const GWL_EXSTYLE = (-20)
Private Const LWA_COLORKEY = &H1
Private Const LWA_ALPHA = &H2
Private Const ULW_COLORKEY = &H1
Private Const ULW_ALPHA = &H2
Private Const ULW_OPAQUE = &H4
Private Const WS_EX_LAYERED = &H80000

Public Function isTransparent(ByVal hWnd As Long) As Boolean
On Error Resume Next
Dim Msg As Long
Msg = GetWindowLong(hWnd, GWL_EXSTYLE)
If (Msg And WS_EX_LAYERED) = WS_EX_LAYERED Then
  isTransparent = True
Else
  isTransparent = False
End If
If Err Then
  isTransparent = False
End If
End Function

Public Function MakeTransparent(ByVal hWnd As Long, Perc As Integer) As Long
Dim Msg As Long
On Error Resume Next
If Perc < 0 Or Perc > 255 Then
  MakeTransparent = 1
Else
  Msg = GetWindowLong(hWnd, GWL_EXSTYLE)
  Msg = Msg Or WS_EX_LAYERED
  SetWindowLong hWnd, GWL_EXSTYLE, Msg
  SetLayeredWindowAttributes hWnd, 0, Perc, LWA_ALPHA
  MakeTransparent = 0
End If
If Err Then
  MakeTransparent = 2
End If
End Function

Public Function MakeOpaque(ByVal hWnd As Long) As Long
Dim Msg As Long
On Error Resume Next
Msg = GetWindowLong(hWnd, GWL_EXSTYLE)
Msg = Msg And Not WS_EX_LAYERED
SetWindowLong hWnd, GWL_EXSTYLE, Msg
SetLayeredWindowAttributes hWnd, 0, 0, LWA_ALPHA
MakeOpaque = 0
If Err Then
  MakeOpaque = 2
End If
End Function


Donde quieres que funcione la transparencia pones:

Citar
MakeTransparent Me.hWnd, x

Donde x es un nº entre 0 y 255. Espero que sea esto. Codigo bastante interesante.

Un saludo,

dPix ;D


Título: Re: Form semi-transparente en el q se vean los controles???
Publicado por: IP3 en 8 Diciembre 2006, 00:36 am
Exacto dPix, a eso me referia, ahora en unos proyectos que hice lo estaba buscando, justo cuando tu lo posteaste, me ahorraste trabajo! Buen aporte!!!!


Título: Re: Form semi-transparente en el q se vean los controles???
Publicado por: CeLaYa en 8 Diciembre 2006, 01:11 am
a lo que me referia es a como puedo aplicar la transparencia por ejemplo a un command o a un picture sin que el form se haga transparente


Título: Re: Form semi-transparente en el q se vean los controles???
Publicado por: IP3 en 8 Diciembre 2006, 01:29 am
Es que claro, el formulario es todo, por lo tanto los comandos tambien, creo que se una posiblidad, prueba con un MDI haber que tal!!

Saludos


Título: Re: Form semi-transparente en el q se vean los controles???
Publicado por: LeandroA en 8 Diciembre 2006, 10:57 am
buenas para empezar la transparencia no se puede aplicar a los controles esto solo vale para las ventanas padres y no las hijas si se puede hacer algunas trampitas con el api AlphaBlend como por ejemplo la que hice con este ocx
http://www.canalvisualbasic.net/forum/forum_posts.asp?TID=24458
 
En cuanto a lo que viene la pregunta del post no conozco manera de hacerlo de forma que el formulario se mitad transparente y los controles no, pero si hacer totalmente transparente el form y no los controles

dos ejemplos

este primero es facil y rapido pero solo valido para win xp

Citar
Option Explicit
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 ReleaseCapture Lib "user32.dll" () As Long
Private Declare Function SendMessage Lib "user32.dll" Alias "SendMessageA" (ByVal hWnd As Long, ByVal wMsg As Long, ByVal wParam As Long, lParam As Any) As Long
Private Declare Function SetLayeredWindowAttributes Lib "user32.dll" (ByVal hWnd As Long, ByVal crKey As Long, ByVal bAlpha As Byte, ByVal dwFlags As Long) As Long
Const LW_KEY = &H1
Const G_E = (-20)
Const W_E = &H80000

Private Sub Form_Load()
Skin Me, vbRed
End Sub
Private Sub Form_MouseMove(Button As Integer, Shift As Integer, X As Single, Y As Single)
'para mover el form de cualquier parte
ReleaseCapture
SendMessage hWnd, 161, 2, 0
End Sub
Sub Skin(Frm As Form, Color As Long)
Frm.BackColor = Color
Dim Ret As Long
Ret = GetWindowLong(Frm.hWnd, G_E)
Ret = Ret Or W_E
SetWindowLong Frm.hWnd, G_E, Ret
SetLayeredWindowAttributes Frm.hWnd, Color, 0, LW_KEY
End Sub

bien este codigo lo que hace es eliminar regiones de color rojo (rojo en este caso) que se encuentre en el formulario por lo que si un label es de color rojo tambien lo hara transparente ,este ejemplo mas bien viene con otro proposito como el que pueden ver en el siguiente
http://www.canalvisualbasic.net/forum/forum_posts.asp?TID=23372

Ahora otra forma mas compatible con las verciones de window devido a las apis que utiliza

Citar
Option Explicit

Private Declare Function CreateRectRgn Lib "gdi32" (ByVal X1 As Long, ByVal Y1 As Long, ByVal X2 As Long, ByVal Y2 As Long) As Long
Private Declare Function CombineRgn Lib "gdi32" (ByVal hDestRgn As Long, ByVal hSrcRgn1 As Long, ByVal hSrcRgn2 As Long, ByVal nCombineMode As Long) As Long
Private Declare Function SetWindowRgn Lib "user32" (ByVal hWnd As Long, ByVal hRgn As Long, ByVal bRedraw As Long) As Long

Public Sub GlassifyForm(frm As Form)
Const RGN_DIFF = 4
Const RGN_OR = 2

Dim outer_rgn As Long
Dim inner_rgn As Long
Dim wid As Single
Dim hgt As Single
Dim border_width As Single
Dim title_height As Single
Dim ctl_left As Single
Dim ctl_top As Single
Dim ctl_right As Single
Dim ctl_bottom As Single
Dim control_rgn As Long
Dim combined_rgn As Long
Dim ctl As Control

    If WindowState = vbMinimized Then Exit Sub

    ' Create the main form region.
    wid = ScaleX(Width, vbTwips, vbPixels)
    hgt = ScaleY(Height, vbTwips, vbPixels)
    outer_rgn = CreateRectRgn(0, 0, wid, hgt)

    border_width = (wid - ScaleWidth) / 2
    title_height = hgt - border_width - ScaleHeight
    inner_rgn = CreateRectRgn(border_width, title_height, wid - border_width, hgt - border_width)

    ' Subtract the inner region from the outer.
    combined_rgn = CreateRectRgn(0, 0, 0, 0)
    CombineRgn combined_rgn, outer_rgn, inner_rgn, RGN_DIFF

    ' Create the control regions.
    For Each ctl In Controls
        If ctl.Container Is frm Then
            ctl_left = ScaleX(ctl.Left, frm.ScaleMode, vbPixels) + border_width
            ctl_top = ScaleX(ctl.Top, frm.ScaleMode, vbPixels) + title_height
            ctl_right = ScaleX(ctl.Width, frm.ScaleMode, vbPixels) + ctl_left
            ctl_bottom = ScaleX(ctl.Height, frm.ScaleMode, vbPixels) + ctl_top
            control_rgn = CreateRectRgn(ctl_left, ctl_top, ctl_right, ctl_bottom)
            CombineRgn combined_rgn, combined_rgn, control_rgn, RGN_OR
        End If
    Next ctl

    ' Restrict the window to the region.
    SetWindowRgn hWnd, combined_rgn, True
End Sub

Private Sub Form_Resize()
    GlassifyForm Me
End Sub

saludos


Título: Re: Form semi-transparente en el q se vean los controles???
Publicado por: ~~ en 8 Diciembre 2006, 14:58 pm
Efectivamente, IP3, era un control de usuario, aqui le dejo el código que googleando encontré (espero que sea esto lo que buscas).

Esto a un módulo:

Citar
Option Explicit

Private Declare Function SetLayeredWindowAttributes Lib "user32" (ByVal hWnd As Long, ByVal crKey As Long, ByVal bAlpha As Byte, ByVal dwFlags As Long) As Long
Private Declare Function UpdateLayeredWindow Lib "user32" (ByVal hWnd As Long, ByVal hdcDst As Long, pptDst As Any, psize As Any, ByVal hdcSrc As Long, pptSrc As Any, crKey As Long, ByVal pblend As Long, ByVal dwFlags As Long) As Long
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 Const GWL_EXSTYLE = (-20)
Private Const LWA_COLORKEY = &H1
Private Const LWA_ALPHA = &H2
Private Const ULW_COLORKEY = &H1
Private Const ULW_ALPHA = &H2
Private Const ULW_OPAQUE = &H4
Private Const WS_EX_LAYERED = &H80000

Public Function isTransparent(ByVal hWnd As Long) As Boolean
On Error Resume Next
Dim Msg As Long
Msg = GetWindowLong(hWnd, GWL_EXSTYLE)
If (Msg And WS_EX_LAYERED) = WS_EX_LAYERED Then
  isTransparent = True
Else
  isTransparent = False
End If
If Err Then
  isTransparent = False
End If
End Function

Public Function MakeTransparent(ByVal hWnd As Long, Perc As Integer) As Long
Dim Msg As Long
On Error Resume Next
If Perc < 0 Or Perc > 255 Then
  MakeTransparent = 1
Else
  Msg = GetWindowLong(hWnd, GWL_EXSTYLE)
  Msg = Msg Or WS_EX_LAYERED
  SetWindowLong hWnd, GWL_EXSTYLE, Msg
  SetLayeredWindowAttributes hWnd, 0, Perc, LWA_ALPHA
  MakeTransparent = 0
End If
If Err Then
  MakeTransparent = 2
End If
End Function

Public Function MakeOpaque(ByVal hWnd As Long) As Long
Dim Msg As Long
On Error Resume Next
Msg = GetWindowLong(hWnd, GWL_EXSTYLE)
Msg = Msg And Not WS_EX_LAYERED
SetWindowLong hWnd, GWL_EXSTYLE, Msg
SetLayeredWindowAttributes hWnd, 0, 0, LWA_ALPHA
MakeOpaque = 0
If Err Then
  MakeOpaque = 2
End If
End Function


Donde quieres que funcione la transparencia pones:

Citar
MakeTransparent Me.hWnd, x

Donde x es un nº entre 0 y 255. Espero que sea esto. Codigo bastante interesante.

Un saludo,

dPix ;D

Pues eso hace exactamente lo mismo q el codigo q yo e puesto... yo estoy buscando una q deje semitransparente solo el form los controles q se keden normal...

LeandroA  esta muy bien la OCX (y realmente la chica tambien xDDD) pero no es exactamene lo q andaba buscando...

1S4ludo


Título: Re: Form semi-transparente en el q se vean los controles???
Publicado por: TUNOVATO en 8 Diciembre 2006, 23:11 pm
Saludos hace tiempo tambien tuve la misma inquietud...!!!

y buscando encontre un code que me sirvio de mucho...!!! muchisimo..!!! a decir  verdad...!!!

creo que esto te puede ayudar en algo a tu code.


en un formulario: Nombre: FormTransparente

Código:
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 Const SC_MOVE = &HF010&
Private Const WM_SYSCOMMAND = &H112


Private Sub Form_Resize()
    TransparentForm Me
End Sub

Private Sub MoverFormulario_Click()
    lP = ((Me.Left \ Screen.TwipsPerPixelX) And &HFFFF&)
    lP = lP + (Me.Top \ Screen.TwipsPerPixelY \ &H10000)
    SendMessage Me.hWnd, WM_SYSCOMMAND, SC_MOVE, lP
End Sub

Private Sub CerrarFormulario_Click()
    Form_Unload (1)
End Sub

Private Sub Form_Unload(Cancel As Integer)
    Unload Me
End Sub


En un modulo: Nombre Modulo.bas

Código:
Option Explicit

Private Declare Function CreateRectRgn Lib "gdi32" (ByVal X1 As Long, ByVal Y1 As Long, ByVal X2 As Long, ByVal Y2 As Long) As Long
Private Declare Function CombineRgn Lib "gdi32" (ByVal hDestRgn As Long, ByVal hSrcRgn1 As Long, ByVal hSrcRgn2 As Long, ByVal nCombineMode As Long) As Long
Private Declare Function SetWindowRgn Lib "user32" (ByVal hWnd As Long, ByVal hRgn As Long, ByVal bRedraw As Long) As Long



Public Sub TransparentForm(frm As Form)

    frm.ScaleMode = vbPixels
   
    Const RGN_DIFF = 4
    Const RGN_OR = 2
   
    Dim outer_rgn As Long
    Dim inner_rgn As Long
    Dim wid As Single
    Dim hgt As Single
    Dim border_width As Single
    Dim title_height As Single
    Dim ctl_left As Single
    Dim ctl_top As Single
    Dim ctl_right As Single
    Dim ctl_bottom As Single
    Dim control_rgn As Long
    Dim combined_rgn As Long
    Dim ControlActual As Control
   
    If frm.WindowState = vbMinimized Then Exit Sub
   
    wid = frm.ScaleX(frm.Width, vbTwips, vbPixels)
    hgt = frm.ScaleY(frm.Height, vbTwips, vbPixels)
    outer_rgn = CreateRectRgn(0, 0, wid, hgt)
    border_width = (wid - frm.ScaleWidth) / 2
    title_height = hgt - border_width - frm.ScaleHeight
'Si quieres que se muestre la barra de titulo
'Entonces habilita la siguiente linea ade codigo
    'inner_rgn = CreateRectRgn(border_width, title_height, wid - border_width, hgt - border_width)
    combined_rgn = CreateRectRgn(0, 0, 0, 0)
    CombineRgn combined_rgn, outer_rgn, inner_rgn, RGN_DIFF
    For Each ControlActual In frm.Controls
        If ControlActual.Container Is frm Then
            ctl_left = frm.ScaleX(ControlActual.Left, frm.ScaleMode, vbPixels) + border_width
            ctl_top = frm.ScaleX(ControlActual.Top, frm.ScaleMode, vbPixels) + title_height
            ctl_right = frm.ScaleX(ControlActual.Width, frm.ScaleMode, vbPixels) + ctl_left
            ctl_bottom = frm.ScaleX(ControlActual.Height, frm.ScaleMode, vbPixels) + ctl_top
            control_rgn = CreateRectRgn(ctl_left, ctl_top, ctl_right, ctl_bottom)
            CombineRgn combined_rgn, combined_rgn, control_rgn, RGN_OR
        End If
    Next ControlActual
    SetWindowRgn frm.hWnd, combined_rgn, True
End Sub


podes colocar cualquier control y adaptar el code buscando la semi-transparecia (lo que tu necesitas no sera muy dificil hacerla...!!!)




Título: Re: Form semi-transparente en el q se vean los controles???
Publicado por: ‭lipman en 8 Diciembre 2006, 23:42 pm
muy majo tu codigo TUNOVATO, pero deja todo invisible salvo las cosas que pongas.

Saludos Suerte


Título: Re: Form semi-transparente en el q se vean los controles???
Publicado por: ~~ en 9 Diciembre 2006, 13:59 pm
Gracias TUNOVATO voy a ver si lo consigo hacer semitransparente  ;)

1S4ludo


Título: Re: Form semi-transparente en el q se vean los controles???
Publicado por: TUNOVATO en 9 Diciembre 2006, 18:41 pm
muy majo tu codigo TUNOVATO, pero deja todo invisible salvo las cosas que pongas.

Saludos Suerte

Saludos compa...!!!

Primero: no es mi codigo, (no soy el autor intelectual, solo tome lo que necesitaba (estudie, analice, detalle, y adapte a mis necesidades) como todos los que necesitamos aprender algo algundia...

Segundo: Si no me equivoco la duda es como aplicar transparencia a un formulario (Semi transparencia) sin afectar los controles u objetos contenidos en el form, es decir, mas simple un Formulario semi-transparente y controles sin transparecias o semi transparencia.

Tercero: El codigo, realiza la invisibilidad de Formulario, es decir deja invisible el fondo, dejando solo los controles u objetos visibles, solo faltaria adaptar a las necesidades del programador, solo falta colocar que el formulario se le aplique la semi transparecia, lo que es obvio, ya esta echo, y solo faltaria curiosidad e interes de hacer las cosas...!!!

Cuarto: Me despido ( Estoy tratando de lograr el objetivo de EON ), que es interesante...!!!


Título: Re: Form semi-transparente en el q se vean los controles???
Publicado por: TUNOVATO en 9 Diciembre 2006, 18:47 pm
Gracias TUNOVATO voy a ver si lo consigo hacer semitransparente  ;)

1S4ludo

Saludos compa...!!!

Esa es la Meta...!!!


Título: Re: Form semi-transparente en el q se vean los controles???
Publicado por: ‭lipman en 9 Diciembre 2006, 23:45 pm
Cierto cierto... :) :P


Título: Re: Form semi-transparente en el q se vean los controles???
Publicado por: Hans el Topo en 19 Diciembre 2006, 20:33 pm
el código es bastante bueno, pero si le añades un gif/control en estilo transparente, no te toma el fondo que hay detrás del gif sino que te lo pinturrajea, ¿alguien sabe como solventarlo?


Título: Re: Form semi-transparente en el q se vean los controles???
Publicado por: VirucKingX en 20 Diciembre 2006, 00:30 am
el código es bastante bueno, pero si le añades un gif/control en estilo transparente, no te toma el fondo que hay detrás del gif sino que te lo pinturrajea, ¿alguien sabe como solventarlo?

aqui tengo un truco, pero no se le puede llamar transparencia :

http://rapidshare.com/files/8199948/formtranslucido.zip.html

con esta idea ise la broma colmena que esta más abajo

Bye


Título: Re: Form semi-transparente en el q se vean los controles???
Publicado por: Hans el Topo en 20 Diciembre 2006, 01:18 am
no me gusta pero parece ser que por ahora e sla única solución xD

los otros métodos lo hacen transparente de verdad y puedes tocar el resto de cosas que ves, aqui según veo lo que hace es lanzar una screen y ponerla de fondo jaja

gracias por la info xD


Título: Re: Form semi-transparente en el q se vean los controles???
Publicado por: VirucKingX en 20 Diciembre 2006, 01:54 am
no me gusta pero parece ser que por ahora e sla única solución xD

los otros métodos lo hacen transparente de verdad y puedes tocar el resto de cosas que ves, aqui según veo lo que hace es lanzar una screen y ponerla de fondo jaja

gracias por la info xD

busque bastante, pero sin ressultados por que me pasaba lo mismo con los gifs transparentes. Esa fue la unica solucion provisoria.

Bye