Autor
		 | 
		
			Tema: Seriales de Pen-Drives conectados (SRC)  (Leído 12,931 veces)
		 | 
	 
 
	
		
			
				
					
						
							Hasseds
							
								
								  Desconectado
								Mensajes: 145
								
								 
								
								
								
								
								 
							 
						 | 
						
							
							 
							
Retorno = Seriales de Pen-Drives conectados   Option Explicit   'Function: FlashSerials 'Autor   : Sergio Desanti (Hasseds) 'Thank   : Seba , Cobein, A.Desanti 'Test    : XP (32 BIT) - W7/UAC (32 BIT) 'Return  : Serial(ESN) de Pen-Drives conectados ' Private Declare Function IIDFromString Lib "ole32" (ByVal lpsz As Long, ByRef lpiid As GUID) As Long Private Declare Function SetupDiGetClassDevs Lib "setupapi.dll" Alias "SetupDiGetClassDevsA" (ByRef ClassGuid As GUID, ByVal Enumerator As Long, ByVal hwndParent As Long, ByVal flags As Long) As Long Private Declare Function SetupDiEnumDeviceInterfaces Lib "setupapi.dll" (ByVal DeviceInfoSet As Long, ByVal DeviceInfoData As Long, ByRef InterfaceClassGuid As GUID, ByVal MemberIndex As Long, ByRef DeviceInterfaceData As SP_DEVICE_INTERFACE_DATA) As Long Private Declare Function SetupDiGetDeviceInterfaceDetail Lib "setupapi.dll" Alias "SetupDiGetDeviceInterfaceDetailA" (ByVal DeviceInfoSet As Long, ByRef DeviceInterfaceData As SP_DEVICE_INTERFACE_DATA, DeviceInterfaceDetailData As Any, ByVal DeviceInterfaceDetailDataSize As Long, ByRef RequiredSize As Long, DeviceInfoData As Any) As Long Private Declare Function SetupDiDestroyDeviceInfoList Lib "setupapi.dll" (ByVal DeviceInfoSet As Long) As Long     Private Type GUID     Data1 As Long: Data2 As Integer: Data3 As Integer: Data4(7) As Byte End Type   Private Type SP_DEVICE_INTERFACE_DATA     cbSize As Long: InterfaceClassGuid As GUID: flags As Long: Reserved As Long End Type   Private Type SP_DEVINFO_DATA     cbSize As Long: ClassGuid As GUID: DevInst As Long: Reserved As Long End Type   Private Type SP_DEVICE_INTERFACE_DETAIL_DATA     cbSize As Long: strDevicePath As String * 260 End Type   Private Sub Form_Load()      AutoRedraw = True      Print FlashSerials End Sub   Public Function FlashSerials() As String       Dim TGUID As GUID       Call IIDFromString(StrPtr("{a5dcbf10-6530-11d2-901f-00c04fb951ed}"), TGUID)       Dim hDev As Long     hDev = SetupDiGetClassDevs(TGUID, &H0, &H0, &H12)     If hDev = -1 Then Exit Function       Dim lCount        As Long     Dim lSize         As Long     Dim DEV_DETAIL    As SP_DEVICE_INTERFACE_DETAIL_DATA     Dim DEV_INFO      As SP_DEVINFO_DATA     Dim DEV_DATA      As SP_DEVICE_INTERFACE_DATA       DEV_DATA.cbSize = Len(DEV_DATA)       While SetupDiEnumDeviceInterfaces(hDev, &H0, TGUID, lCount, DEV_DATA) <> &H0       Call SetupDiGetDeviceInterfaceDetail(hDev, DEV_DATA, ByVal &H0, &H0, lSize, ByVal &H0)       DEV_DETAIL.cbSize = &H5       DEV_INFO.cbSize = Len(DEV_INFO)       Call SetupDiGetDeviceInterfaceDetail(hDev, DEV_DATA, DEV_DETAIL, ByVal lSize, &H0, DEV_INFO)       If UBound(Split(DEV_DETAIL.strDevicePath, "#")) > 1 Then         FlashSerials = FlashSerials & Split(UCase$(DEV_DETAIL.strDevicePath), "#")(2) & Chr$(&HD)       End If       lCount = lCount + 1     Wend       Call SetupDiDestroyDeviceInfoList(hDev)   End Function     
 
 
  
						 | 
					 
					
						
							
								| 
								 | 
							 
								| 
									« Última modificación: 20 Septiembre 2011, 23:44 pm por Hasseds »
								 | 
								
									 
									En línea
								 | 
							  
							 
							Sergio Desanti 
						 | 
					 
				 
			 |  
		 
	 |  
	
		
		
			
				
					
						
							Elemental Code
							
								 
								
								  Desconectado
								Mensajes: 622
								
								 
								Im beyond the system
								
								
								
								
								
								  
							 
						 | 
						
							
							 
							
CHAAAAAAAN. Explicame que es el serial de un pendrive    
  
						 | 
					 
					
						
							
								| 
								 | 
							 
								| 
								 | 
								
									 
									En línea
								 | 
							  
							 
							I CODE FOR $$$ Programo por $$$ Hago tareas, trabajos para la facultad, lo que sea en VB6.0 Mis programas 
						 | 
					 
				 
			 |  
		 
	 |  
	
		
		
			
				
					
						
							Hasseds
							
								
								  Desconectado
								Mensajes: 145
								
								 
								
								
								
								
								 
							 
						 | 
						
							
							 
							
El numero de serie (Proporcionado por el frabricante) de un dispositivo, este deberiá ser unico y no cambiar al formatear, saludos 
						 | 
					 
					
						
							
								| 
								 | 
							 
								| 
								 | 
								
									 
									En línea
								 | 
							  
							 
							Sergio Desanti 
						 | 
					 
				 
			 |  
		 
	 |  
	
		
		
			
				
					
						
							Hasseds
							
								
								  Desconectado
								Mensajes: 145
								
								 
								
								
								
								
								 
							 
						 | 
						
							
							 
							
Agrego (por si el tema le interesó a alguien) un modulo para asociar la letra de unidad con su respectivo Serial (ESN) de Pen Drive. Nota1: no pude probar como se comporta el código con Discos uSB externos ni con grabadoras USB, lo voy a hacer en cuanto tenga la oportunidad Nota 2: es posible que no haya que llamar 2 veces a SetupDiGetDeviceInterfaceDetail, creo que RequiredSize As Long (lSize en el codigo) de esta api seria de &H7B para la clase "{53f56307-b6bf-11d0-94f2-00a0c91efb8b}" pero solo pude probar en XP conectando de uno hasta seis PenDrive.  Saludos MODULO:   Option Explicit   'Modulo: FlashSerial 'Autor: Sergio Desanti (Hasseds) 'Agradecimientos: Seba, Cobein, A.Desanti 'Test: XP (32 BIT) & W7 (32 BIT) 'Retorno:  Letra de unidad y Serial Number(ESN) de Pen Drive conectados ' Declare Function GetLogicalDriveStrings Lib "kernel32" Alias "GetLogicalDriveStringsA" (ByVal nBufferLength As Long, ByVal lpBuffer As String) As Long Private Declare Function CreateFile Lib "kernel32" Alias "CreateFileA" (ByVal lpFileName As String, ByVal dwDesiredAccess As Long, ByVal dwShareMode As Long, lpSecurityAttributes As Any, ByVal dwCreationDisposition As Long, ByVal dwFlagsAndAttributes As Long, ByVal hTemplateFile As Long) As Long Private Declare Function CloseHandle Lib "kernel32" (ByVal hObject As Long) As Long Private Declare Function DeviceIoControl Lib "kernel32" (ByVal hDevice As Long, ByVal dwIoControlCode As Long, lpInBuffer As Any, ByVal nInBufferSize As Long, lpOutBuffer As Any, ByVal nOutBufferSize As Long, lpBytesReturned As Long, ByVal lpOverlapped As Long) As Long   Private Declare Function IIDFromString Lib "ole32" (ByVal lpsz As Long, ByRef lpiid As GUID) As Long   Private Declare Function SetupDiGetClassDevs Lib "setupapi.dll" Alias "SetupDiGetClassDevsA" (ByRef ClassGuid As GUID, ByVal Enumerator As Long, ByVal hwndParent As Long, ByVal flags As Long) As Long Private Declare Function SetupDiEnumDeviceInterfaces Lib "setupapi.dll" (ByVal DeviceInfoSet As Long, ByVal DeviceInfoData As Long, ByRef InterfaceClassGuid As GUID, ByVal MemberIndex As Long, ByRef DeviceInterfaceData As SP_DEVICE_INTERFACE_DATA) As Long Private Declare Function SetupDiGetDeviceInterfaceDetail Lib "setupapi.dll" Alias "SetupDiGetDeviceInterfaceDetailA" (ByVal DeviceInfoSet As Long, ByRef DeviceInterfaceData As SP_DEVICE_INTERFACE_DATA, DeviceInterfaceDetailData As Any, ByVal DeviceInterfaceDetailDataSize As Long, ByRef RequiredSize As Long, DeviceInfoData As Any) As Long Private Declare Function SetupDiDestroyDeviceInfoList Lib "setupapi.dll" (ByVal DeviceInfoSet As Long) As Long   Private Type STORAGE_DEVICE_NUMBER     DeviceType As Long: DiskNumber As Long: PartNumber As Long End Type   Private Type GUID     Data1 As Long: Data2 As Integer: Data3 As Integer: Data4(7) As Byte End Type   Private Type SP_DEVICE_INTERFACE_DATA     cbSize As Long: InterfaceClassGuid As GUID: flags As Long: Reserved As Long End Type   Private Type SP_DEVICE_INTERFACE_DETAIL_DATA     cbSize As Long: strDevicePath As String * 260 End Type   Public Function FlashSerial(ByVal sLetra As String) As String     sLetra = Left$(UCase$(sLetra), 1) & ":"     FlashSerial = sLetra & " NO USB"     Dim RetDeviceIndex    As Long   RetDeviceIndex = DeviceIndex(sLetra)   If RetDeviceIndex < 0 Then Exit Function ' " -1 -2 -3 en DeviceIndex"     Dim TGUID             As GUID   Call IIDFromString(StrPtr("{53f56307-b6bf-11d0-94f2-00a0c91efb8b}"), TGUID)     Dim hDev              As Long   hDev = SetupDiGetClassDevs(TGUID, &H0, &H0, &H12)   If hDev = -1 Then: Exit Function     Dim lCount            As Long   Dim lSize             As Long   Dim DTA               As SP_DEVICE_INTERFACE_DATA   Dim DTL               As SP_DEVICE_INTERFACE_DETAIL_DATA     DTA.cbSize = Len(DTA)   DTL.cbSize = &H5     Do While Not (SetupDiEnumDeviceInterfaces(hDev, &H0, TGUID, lCount, DTA) = &H0&)     Call SetupDiGetDeviceInterfaceDetail(hDev, DTA, ByVal &H0&, &H0, lSize, ByVal &H0&)     Call SetupDiGetDeviceInterfaceDetail(hDev, DTA, DTL, ByVal lSize, &H0&, ByVal &H0&)     If InStr(UCase$(DTL.strDevicePath), "USB") Then       If DeviceIndex(DTL.strDevicePath, True) = RetDeviceIndex Then         If UBound(Split(DTL.strDevicePath, "#")) > 1 Then           FlashSerial = sLetra & Split(UCase$(DTL.strDevicePath), "#")(2)           Exit Do         End If       End If     End If     lCount = lCount + 1   Loop     Call SetupDiDestroyDeviceInfoList(hDev)   End Function   Public Function DeviceIndex(ByVal sLetra As String, Optional strDevicePath As Boolean) As Long     Dim hdh As Long, br As Long, SDN As STORAGE_DEVICE_NUMBER     If Not strDevicePath Then sLetra = "\\.\" & Left$(UCase$(sLetra), 1) & ":"     hdh = CreateFile(sLetra, &H0&, &H3&, ByVal &H0&, &H3&, &H0&, &H0&) ': MsgBox hdh, , "hdh"   If Not (hdh = -1) Then       If DeviceIoControl(hdh, &H2D1080, &H0&, &H0&, SDN, Len(SDN), br, ByVal &H0&) Then           If SDN.DeviceType = 7 Then               DeviceIndex = SDN.DiskNumber  ' Retorno DeviceIndex           Else               DeviceIndex = -3   ' No es GUID 53f56307-b6bf-11d0-94f2-00a0c91efb8b           End If       Else           DeviceIndex = -2  ' Floppy o DeviceIoControl = 0 (GetLastError)       End If       Call CloseHandle(hdh)   Else       DeviceIndex = -1  ' Unidad sin dispositivo o CreateFile = -1 (GetLastError)   End If   End Function       
 
   Option Explicit   Private Sub Form_Load()         MsgBox FlashSerial("f")   End Sub       
 
  
						 | 
					 
					
						
							
								| 
								 | 
							 
								| 
									« Última modificación: 17 Septiembre 2011, 13:09 pm por Hasseds »
								 | 
								
									 
									En línea
								 | 
							  
							 
							Sergio Desanti 
						 | 
					 
				 
			 |  
		 
	 |  
	
		
		
			
				
					
						
							Maurice_Lupin
							
								 
								
								  Desconectado
								Mensajes: 356
								 
								GPS
								
								
								
								
								
								  
								 
							 
						 | 
						
							
							 
							
Funciona en una cuenta de usuario, cuando usas WMI necesitas permisos     lo utilizaré, aún no entiendo que es eso de hook en el formulario. Pero averiguaré. Saludos.  
						 | 
					 
					
						
							
								| 
								 | 
							 
								| 
								 | 
								
									 
									En línea
								 | 
							  
							 
							Un error se comete al equivocarse. 
						 | 
					 
				 
			 |  
		 
	 |  
	
		
		
			
				
					
						
							Hasseds
							
								
								  Desconectado
								Mensajes: 145
								
								 
								
								
								
								
								 
							 
						 | 
						
							
							 
							
Si , creo que tambien funciona con UAC activado (tal vez alguien que lo pueda probar en W7 nos informe de esto) Un ejemplo de Hook de lo mas de lo mas simple, si te sirve... te toca optimizar y adaptar a lo tuyo. MODULO  Option Explicit
  'Function: FlashSerials 'Autor   : Sergio Desanti (Hasseds) 'Thank   : Seba , Cobein, A.Desanti 'Test    : XP (32 BIT) - W7 (32 BIT) 'Return  : Serial(ESN) de Pen-Drives conectados '
  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 Public Declare Function SetWindowPos Lib "user32" (ByVal hWnd As Long, ByVal hWndInsertAfter As Long, ByVal X As Long, ByVal Y As Long, ByVal cx As Long, ByVal cy As Long, ByVal wFlags As Long) As Long
  Private Const GWL_WNDPROC = -4 Private Const WM_DEVICECHANGE As Long = 537              'Cambios en un dispositivo Private Const DBT_DEVICEARRIVAL As Long = 32768          'Cuando se conecta uno nuevo Private Const DBT_DEVICEREMOVECOMPLETE As Long = 32772   'Cuando se desconecta uno Private Const DBT_DEVTYP_VOLUME As Integer = 2           'Logical volume, cualquier unidad de almacenamiento nueva.
  Private Declare Function IIDFromString Lib "ole32" (ByVal lpsz As Long, ByRef lpiid As GUID) As Long Private Declare Function SetupDiGetClassDevs Lib "setupapi.dll" Alias "SetupDiGetClassDevsA" (ByRef ClassGuid As GUID, ByVal Enumerator As Long, ByVal hwndParent As Long, ByVal flags As Long) As Long Private Declare Function SetupDiEnumDeviceInterfaces Lib "setupapi.dll" (ByVal DeviceInfoSet As Long, ByVal DeviceInfoData As Long, ByRef InterfaceClassGuid As GUID, ByVal MemberIndex As Long, ByRef DeviceInterfaceData As SP_DEVICE_INTERFACE_DATA) As Long Private Declare Function SetupDiGetDeviceInterfaceDetail Lib "setupapi.dll" Alias "SetupDiGetDeviceInterfaceDetailA" (ByVal DeviceInfoSet As Long, ByRef DeviceInterfaceData As SP_DEVICE_INTERFACE_DATA, DeviceInterfaceDetailData As Any, ByVal DeviceInterfaceDetailDataSize As Long, ByRef RequiredSize As Long, DeviceInfoData As Any) As Long Private Declare Function SetupDiDestroyDeviceInfoList Lib "setupapi.dll" (ByVal DeviceInfoSet As Long) As Long   Private Type GUID    Data1 As Long: Data2 As Integer: Data3 As Integer: Data4(7) As Byte End Type   Private Type SP_DEVICE_INTERFACE_DATA    cbSize As Long: InterfaceClassGuid As GUID: flags As Long: Reserved As Long End Type
  Private Type SP_DEVICE_INTERFACE_DETAIL_DATA    cbSize As Long: strDevicePath As String * 260 End Type
  Dim hHook As Long
  Public Sub StartHook(hWnd As Long)     hHook = SetWindowLong(hWnd, GWL_WNDPROC, AddressOf WindowProc) End Sub
  Public Sub StopHook(hWnd As Long)     SetWindowLong hWnd, GWL_WNDPROC, hHook     hHook = 0 End Sub
  Private Function WindowProc(ByVal hWnd As Long, ByVal uMsg As Long, ByVal wParam As Long, ByVal lParam As Long) As Long     WindowProc = CallWindowProc(hHook, hWnd, uMsg, wParam, lParam)     If uMsg = WM_DEVICECHANGE Then       If wParam = DBT_DEVICEARRIVAL Then         Form1.Cls         Form1.Print "Conectaron", Time         Form1.Print         Form1.Print FlashSerials       ElseIf wParam = DBT_DEVICEREMOVECOMPLETE Then         Form1.Cls         Form1.Print "Desconectaron", Time         Form1.Print         Form1.Print FlashSerials       End If     End If End Function   Public Function FlashSerials() As String      Dim TGUID As GUID      Call IIDFromString(StrPtr("{a5dcbf10-6530-11d2-901f-00c04fb951ed}"), TGUID)      Dim hDev As Long    hDev = SetupDiGetClassDevs(TGUID, &H0, &H0, &H12)    If hDev = -1 Then Exit Function      Dim lCount       As Long    Dim lSize        As Long    Dim DTL          As SP_DEVICE_INTERFACE_DETAIL_DATA    Dim DTA          As SP_DEVICE_INTERFACE_DATA      DTA.cbSize = Len(DTA)    DTL.cbSize = &H5      While Not (SetupDiEnumDeviceInterfaces(hDev, &H0, TGUID, lCount, DTA) = &H0)      Call SetupDiGetDeviceInterfaceDetail(hDev, DTA, ByVal &H0, &H0, lSize, ByVal &H0)      Call SetupDiGetDeviceInterfaceDetail(hDev, DTA, DTL, ByVal lSize, &H0, ByVal &H0)      If UBound(Split(DTL.strDevicePath, "#")) > 1 Then        FlashSerials = FlashSerials & Split(UCase$(DTL.strDevicePath), "#")(2) & Chr$(&HD)      End If      lCount = lCount + 1    Wend      Call SetupDiDestroyDeviceInfoList(hDev)        If FlashSerials = "" Then FlashSerials = "No hay conexiones"     End Function
 
 
 
 FORM  Option Explicit
  Private Sub Form_Load()  AutoRedraw = True  Print FlashSerials  Call SetWindowPos(Form1.hWnd, &HFFFF, &H0, &H0, &H0, &H0, &H3) 'form on top  Call StartHook(hWnd) End Sub
  Private Sub Form_Unload(Cancel As Integer)    Call StopHook(hWnd) End Sub
 
 
  http://www.virustotal.com/file-scan/report.html?id=4e03da8a806215953259ea3291bc79d7cab8226fdabb14765efdd81b4b94eae1-1317934469 
						 | 
					 
					
						
							
								| 
								 | 
							 
								| 
									« Última modificación:  7 Octubre 2011, 03:20 am por Hasseds »
								 | 
								
									 
									En línea
								 | 
							  
							 
							Sergio Desanti 
						 | 
					 
				 
			 |  
		 
	 |  
	
		
		
			
				
					
						
							BlackZeroX
							
								Wiki 
								
								  Desconectado
								Mensajes: 3.158
								
								 
								I'Love...!¡.
								
								
								
								
								
								  
								 
							 
						 | 
						
							
							 
							
. No recuerdo bien pero ya habia visto un codigo asi hace tiempo... igual no recuerdo donde... jaja a mi biblioteca.
  Dulces Lunas!¡. 
						 | 
					 
					
						
							
								| 
								 | 
							 
								| 
								 | 
								
									 
									En línea
								 | 
							  
							 
							The Dark Shadow is my passion. 
						 | 
					 
				 
			 |  
		 
	 |  
	
		
		
			
				
					
						
							Maurice_Lupin
							
								 
								
								  Desconectado
								Mensajes: 356
								 
								GPS
								
								
								
								
								
								  
								 
							 
						 | 
						
							
							 
							
Entendi que hook es detectar las acciones que el usuario realiza mientras el programa esta activo, en este caso el USB conectado o no.  Me sirve, claro que si, como decimos en mi barrio: Gracielas     
						 | 
					 
					
						
							
								| 
								 | 
							 
								| 
								 | 
								
									 
									En línea
								 | 
							  
							 
							Un error se comete al equivocarse. 
						 | 
					 
				 
			 |  
		 
	 |  
	
		
		
			
				
					
						
							Hasseds
							
								
								  Desconectado
								Mensajes: 145
								
								 
								
								
								
								
								 
							 
						 | 
						
							
							 
							
mmm... me parece q me fuí al carajo     
						 | 
					 
					
						
							
								| 
								 | 
							 
								| 
									« Última modificación:  7 Octubre 2011, 05:04 am por Hasseds »
								 | 
								
									 
									En línea
								 | 
							  
							 
							Sergio Desanti 
						 | 
					 
				 
			 |  
		 
	 |  
	
		
		
			
				
					
						| 
							.:UND3R:.
							
						 | 
						
							
							 
							
es una excelente herramienta para evitar el cracking de alguna forma, vender un software con dongle en donde el programa pide un serial y un pendrive conectado este serial es algún algoritmo del serial del pendrive por lo que si se coloca el serial este al pasar por algunos cálculos debería ser el mismo serial que el del pendrive, si no retorna serial incorrecto o llave USB incorrecta
 
   aclaro que es una idea de la funcionalidad que se le puede dar, no necesariamente es para eso,Saludos
  PD: un programa que permita una serie de pendrive determinados conectarce al PC
  sistema de seguirdad para aislar troyanos.
  etc
  Saludos
  Saludos
						 | 
					 
					
						
							
								| 
								 | 
							 
								| 
									« Última modificación:  7 Octubre 2011, 14:23 pm por raul338 »
								 | 
								
									 
									En línea
								 | 
							  
							 
							 Solicitudes de crack, keygen, serial solo a través de mensajes privados (PM) 
						 | 
					 
				 
			 |  
		 
	 |  
	 |  
 
	 
	
 
			 
			
				
					
						| Mensajes similares | 
					 
					
						 | 
						Asunto | 
						Iniciado por | 
						Respuestas | 
						Vistas | 
						Último mensaje | 
					 
					
						
							 
						 | 
						
							 
						 | 
						
							2 Mandos juegos Activbb conectados a la vez.1 da problemas cuando 2 conectados.
							 
							Juegos y Consolas
						 | 
						
							Giusseppe
						 | 
						
							0
						 | 
						
							2,935
						 | 
						
							 
							
								14 Abril 2005, 01:28 am 
								por Giusseppe
							
						 | 
					 
					
						
							 
						 | 
						
							 
						 | 
						
							Listar usuarios conectados y no conectados con las apis del msn
							 
							Programación Visual Basic
						 | 
						
							··eljavi16··
						 | 
						
							1
						 | 
						
							2,238
						 | 
						
							 
							
								28 Enero 2007, 23:15 pm 
								por Red Mx
							
						 | 
					 
					
						
							 
						 | 
						
							 
						 | 
						
							(SOLUCIONADO  SRC)Ayuda pasar codigo a VB.Net: Seriales Pen-Drives vb6 
							 
							.NET (C#, VB.NET, ASP)
						 | 
						
							Maurice_Lupin
						 | 
						
							3
						 | 
						
							5,227
						 | 
						
							 
							
								17 Noviembre 2011, 16:45 pm 
								por Maurice_Lupin
							
						 | 
					 
					
						
							 
						 | 
						
							 
						 | 
						
							HP Pavilion g6 series necesitos Drives
							 
							Wireless en Windows
						 | 
						
							El_Andaluz
						 | 
						
							1
						 | 
						
							2,750
						 | 
						
							 
							
								 5 Mayo 2013, 21:57 pm 
								por El_Andaluz
							
						 | 
					 
					
						
							 
						 | 
						
							 
						 | 
						
							duda pen drives
							« 1 2 » 
							Dudas Generales
						 | 
						
							naxo_valladolid
						 | 
						
							17
						 | 
						
							8,556
						 | 
						
							 
							
								12 Diciembre 2013, 16:12 pm 
								por naxo_valladolid
							
						 | 
					 
				 
			    |