miércoles, 18 de octubre de 2017

VBA Access. Función para exportar un recordset a Excel.

Public Sub Export2Excel(ByRef rs As Variant, Optional ByVal bShowColumnNames As Boolean = True)
On Error GoTo error
    Dim xlApp As Object
    Dim xlWb As Object
    Dim xlWs As Object

    Dim recArray As Variant

    Dim strDB As String
    Dim fldCount As Integer
    Dim recCount As Long
    Dim iCol As Integer
    Dim iRow As Integer

    ' Create an instance of Excel and add a workbook
    Set xlApp = CreateObject("Excel.Application")
    Set xlWb = xlApp.Workbooks.Add
    Set xlWs = xlWb.Worksheets("Hoja1")

    ' Copy field names to the first row of the worksheet
    If bShowColumnNames Then
        fldCount = rs.Fields.Count
        For iCol = 1 To fldCount
            xlWs.Cells(1, iCol).value = rs.Fields(iCol - 1).Name
        Next
    End If
   
    ' Check version of Excel
    If Val(Mid(xlApp.Version, 1, InStr(1, xlApp.Version, ".") - 1)) > 8 Then
        'EXCEL 2000,2002,2003, or 2007: Use CopyFromRecordset
     
        ' Copy the recordset to the worksheet, starting in cell A2
        xlWs.Cells(IIf(bShowColumnNames, 2, 1), 1).CopyFromRecordset rs
        'Note: CopyFromRecordset will fail if the recordset
        'contains an OLE object field or array data such
        'as hierarchical recordsets
    Else
        MsgBox "Versión instalada de excel no soportada!", vbCritical
        Exit Sub
    End If

    ' Auto-fit the column widths and row heights
    xlApp.Selection.CurrentRegion.Columns.AutoFit
    xlApp.Selection.CurrentRegion.Rows.AutoFit

    ' Display Excel and give user control of Excel's lifetime
    xlApp.Visible = True
    xlApp.UserControl = True

    ' Release Excel references
    Set xlWs = Nothing
    Set xlWb = Nothing
    Set xlApp = Nothing
       
Exit Sub
Resume
error:
    MsgBox Err.Description
End Sub

lunes, 16 de octubre de 2017

VBA Access. Módulo de clase clsTimer. Crear uno o varios Timer independiente(s) sin depender del formulario. (2/2)

Option Compare Database
Option Explicit

'1 Crearemos el timer o timers que necesitemos instanciando esta clase sin depender del formulario.
'Ej: Public WithEvents oTimer1 As clsTimer
'2 Para definir las acciones a realizar en el evento OnTimer, en el formulario, debemos crear un 'procedimento que se llamará: Nombre del objeto timer que hallamos creado  + "_OnTimer". 
'Ejemplo objeto oTimer1 -> Private Sub oTimer1_OnTimer() ..... End Sub
'3 Iniciar timer: oTimer1.Startit
'4 Parar timer: oTimer1.Stopit

'https://access-programmers.co.uk/forums/showthread.php?t=232012

Option Compare Database
Option Explicit

'Windows API Function Declarations
#If Win64 = 1 Then
    Private Declare PtrSafe Function SetTimer Lib "user32" ( _
        ByVal hwnd As LongPtr, ByVal nIDEvent As LongPtr, _
        ByVal uElapse As LongLong, ByVal lpTimerFunc As LongPtr) As LongLong
    
    Private Declare PtrSafe Function KillTimer Lib "user32" ( _
        ByVal hwnd As LongPtr, ByVal nIDEvent As LongPtr) As LongLong
#Else
    Private Declare Function SetTimer Lib "user32" ( _
        ByVal hWnd As Long, ByVal nIDEvent As Long, _
        ByVal uElapse As Long, ByVal lpTimerFunc As Long) As Long
    
    Private Declare Function KillTimer Lib "user32" ( _
        ByVal hWnd As Long, ByVal nIDEvent As Long) As Long
#End If

#If Win64 = 1 Then
    Private TimerID As LongLong
#Else
    Private TimerID As Long
#End If

Public Event OnTimer()

'Start timer
Public Sub Startit(IntervalMs As Long)
    TimerID = SetTimer(Application.hWndAccessApp, ObjPtr(Me), IntervalMs, AddressOf Timers.TimerProc)
End Sub

'Stop timer
Public Sub Stopit()
    If TimerID <> -1 Then
        KillTimer Application.hWndAccessApp, TimerID
        TimerID = 0
    End If
End Sub

'Trigger Public event
Public Sub RaiseTimerEvent()
    RaiseEvent OnTimer
End Sub

VBA Access. Módulo Timers. Crear uno o varios Timer independiente(s) sin depender del formulario. (1/2)

'Crear un módulo llamado Timers

'https://access-programmers.co.uk/forums/showthread.php?t=232012

#If Win64 = 1 Then
    Public Sub TimerProc(ByVal hwnd As LongPtr, _
                             ByVal uMsg As LongLong, _
                             ByVal oTimer As clsTimer, _
                             ByVal dwTime As LongLong)
       ' Alert appropriate timer object instance.
       If Not oTimer Is Nothing Then
            oTimer.RaiseTimerEvent
            Debug.Print "evento timer"
       End If
    End Sub
#Else
    Public Sub TimerProc(ByVal hwnd As Long, _
                         ByVal uMsg As Long, _
                         ByVal oTimer As clsTimer, _
                         ByVal dwTime As Long)
       ' Alert appropriate timer object instance.
       If Not oTimer Is Nothing Then
            oTimer.RaiseTimerEvent
            Debug.Print "evento timer"
       End If
    End Sub
#End If

VBA Access. Módulo de Clase clsCarousel. Clase para hacer un carrusel de imágenes combinándola con un timer.

Option Compare Database
Option Explicit

'1 En el formulario donde haremos el carrusel, definimos una variable del tipo clsCarousel
'2 Crearemos un control imagen
'3 Instanciamos el objeto y llamamos al método LoadImages pasando la carpeta donde contenga las imágenes y el nombre del control imagen por referencia
'4 Iniciamos un Timer con el refresco que queramos
'5 cada evento del timer (OnTimer), llamaremos al método NextImage

Private ControlImagen As Control
Private NumImagenActual As Integer
Private DiccionarioImagenes As Dictionary

Private Sub Class_Initialize()
    NumImagenActual = 0
End Sub

Private Sub Class_Terminate()
    If Not DiccionarioImagenes Is Nothing Then
        DiccionarioImagenes.RemoveAll
        Set DiccionarioImagenes = Nothing
    End If
End Sub

Function LoadImages(ByVal CarpetaImagenes As String, ByRef ctlImagen As Control) As Boolean
On Error GoTo error
    Set DiccionarioImagenes = New Dictionary
 
    Dim i As Integer
    i = 0
    Dim file As Object
    Dim fso As New FileSystemObject
    For Each file In fso.GetFolder(CarpetaImagenes).Files
        i = i + 1
        DiccionarioImagenes.Add CStr(i), CStr(file)
    Next file
     
    Set ControlImagen = ctlImagen
    NextImage
 
    LoadImages = True
Exit Function
Resume
error:
    LoadImages = False
    Debug.Print Err.Number & ": " & Err.Description
End Function

Function NextImage()
On Error Resume Next
    NumImagenActual = NumImagenActual Mod DiccionarioImagenes.Count + 1
    ControlImagen.Picture = DiccionarioImagenes.Item(CStr(NumImagenActual))
End Function

VBA Access. Modulo ModTransparent. Permite hacer un formulario totalmente visible, translúcido o transparente del todo.

Option Compare Database
Option Explicit

'http://grupos.emagister.com/debate/formulario_transparente/6411-674789
'
'Uso por ejemplo en el load del formulario: Transparent Me, 100
'
'Los valores posibles son entre 0 totalmente transparente y 255 totalmente visible.
'Para que funcione debes poner este código en un módulo nuevo

#If Win64 = 1 Then
    Private Declare PtrSafe Function SetWindowLong Lib "user32" Alias "SetWindowLongA" (ByVal hWnd As Long, ByVal nIndex As Long, ByVal dwNewLong As Long) As Long
    Private Declare PtrSafe Function GetWindowLong Lib "user32" Alias "GetWindowLongA" (ByVal hWnd As Long, ByVal nIndex As Long) As Long
    Private Declare PtrSafe Function SetLayeredWindowAttributes Lib "user32" (ByVal hWnd As Long, ByVal crKey As Long, ByVal bAlpha As Byte, ByVal dwFlags As Long) As Long
#Else
    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 Declare Function SetLayeredWindowAttributes Lib "user32" (ByVal hWnd As Long, ByVal crKey As Long, ByVal bAlpha As Byte, ByVal dwFlags As Long) As Long
#End If

Private Const GWL_EXSTYLE = (-20)
Private Const WS_EX_LAYERED = &H80000
Private Const LWA_ALPHA = &H2

Function Transparent(frm As Form, Nivel As Integer)
    Dim lngHwnd As Long
    If Nivel < 0 Or Nivel > 255 Then Exit Function
    lngHwnd = frm.hWnd
    SetWindowLong lngHwnd, GWL_EXSTYLE, GetWindowLong(lngHwnd, GWL_EXSTYLE) Or WS_EX_LAYERED
    SetLayeredWindowAttributes lngHwnd, 0, Nivel, LWA_ALPHA
End Function

viernes, 13 de octubre de 2017

VBA Access. Módulo de clase clsFTP para VBA. Métodos FtpDownload y FtpUpload para descargar o subir ficheros.

Option Compare Database
Option Explicit

'http://analystcave.com/vba-downloading-files-from-ftp-using-vba/

'Ejemplo de uso:
'Dim oFtp as new clsFtp
'FtpDownload Fichero_Remoto_Origen, Fichero_Local_Destino, Servidor, Puerto, Usuario, Contraseña
'oFtp.FtpDownload "//Download/text_file.txt", "C:\text_file.txt", "192.168.0.100", 21, "username", "password"

'FtpUpload Fichero_Local_Origen, Fichero_Remoto_Destino, Servidor, Puerto, Usuario, Contraseña
'oFtp.FtpUpload "C:\text_file.txt", "//Download/text_file.txt", "192.168.0.100", 21, "username", "password"

Private Const FTP_TRANSFER_TYPE_UNKNOWN     As Long = 0
Private Const INTERNET_FLAG_RELOAD          As Long = &H80000000

'Windows API Function Declarations
#If Win64 = 1 Then
    Private Declare PtrSafe Function InternetOpenA Lib "wininet.dll" ( _
        ByVal sAgent As String, _
        ByVal lAccessType As Long, _
        ByVal sProxyName As String, _
        ByVal sProxyBypass As String, _
        ByVal lFlags As Long) As Long
   
    Private Declare PtrSafe Function InternetConnectA Lib "wininet.dll" ( _
        ByVal hInternetSession As Long, _
        ByVal sServerName As String, _
        ByVal nServerPort As Long, _
        ByVal sUsername As String, _
        ByVal sPassword As String, _
        ByVal lService As Long, _
        ByVal lFlags As Long, _
        ByVal lcontext As Long) As Long
   
    Private Declare PtrSafe Function FtpGetFileA Lib "wininet.dll" ( _
        ByVal hConnect As Long, _
        ByVal lpszRemoteFile As String, _
        ByVal lpszNewFile As String, _
        ByVal fFailIfExists As Long, _
        ByVal dwFlagsAndAttributes As Long, _
        ByVal dwFlags As Long, _
        ByVal dwContext As Long) As Long
 
    Private Declare PtrSafe Function FtpPutFileA _
       Lib "wininet.dll" _
 _
           (ByVal hFtpSession As Long, _
            ByVal lpszLocalFile As String, _
            ByVal lpszRemoteFile As String, _
            ByVal dwFlags As Long, _
            ByVal dwContext As Long) As Boolean
     
    Private Declare PtrSafe Function InternetCloseHandle Lib "wininet" ( _
        ByVal hInet As Long) As Long
#Else
    Private Declare Function InternetOpenA Lib "wininet.dll" ( _
        ByVal sAgent As String, _
        ByVal lAccessType As Long, _
        ByVal sProxyName As String, _
        ByVal sProxyBypass As String, _
        ByVal lFlags As Long) As Long
   
    Private Declare Function InternetConnectA Lib "wininet.dll" ( _
        ByVal hInternetSession As Long, _
        ByVal sServerName As String, _
        ByVal nServerPort As Long, _
        ByVal sUsername As String, _
        ByVal sPassword As String, _
        ByVal lService As Long, _
        ByVal lFlags As Long, _
        ByVal lcontext As Long) As Long
   
    Private Declare Function FtpGetFileA Lib "wininet.dll" ( _
        ByVal hConnect As Long, _
        ByVal lpszRemoteFile As String, _
        ByVal lpszNewFile As String, _
        ByVal fFailIfExists As Long, _
        ByVal dwFlagsAndAttributes As Long, _
        ByVal dwFlags As Long, _
        ByVal dwContext As Long) As Long
 
    Private Declare Function FtpPutFileA _
       Lib "wininet.dll" _
 _
           (ByVal hFtpSession As Long, _
            ByVal lpszLocalFile As String, _
            ByVal lpszRemoteFile As String, _
            ByVal dwFlags As Long, _
            ByVal dwContext As Long) As Boolean
     
    Private Declare Function InternetCloseHandle Lib "wininet" ( _
        ByVal hInet As Long) As Long
#End If

Public Function FtpDownload(ByVal strRemoteFile As String, ByVal strLocalFile As String, ByVal strHost As String, ByVal lngPort As Long, ByVal strUser As String, ByVal strPass As String) As Boolean
On Error GoTo error
    Dim hOpen   As Long
    Dim hConn   As Long

    hOpen = InternetOpenA("FTPGET", 1, vbNullString, vbNullString, 1)
    hConn = InternetConnectA(hOpen, strHost, lngPort, strUser, strPass, 1, 0, 2)

    If FtpGetFileA(hConn, strRemoteFile, strLocalFile, 1, 0, FTP_TRANSFER_TYPE_UNKNOWN Or INTERNET_FLAG_RELOAD, 0) Then
        FtpDownload = True
        Debug.Print "Success"
    Else
        FtpDownload = False
        Debug.Print "Fail"
    End If

    'Close connections
    InternetCloseHandle hConn
    InternetCloseHandle hOpen
 
Exit Function
error:
    FtpDownload = False
    Debug.Print Err.Number & ": " & Err.Description
End Function

Public Function FtpUpload(ByVal strLocalFile As String, ByVal strRemoteFile As String, ByVal strHost As String, ByVal lngPort As Long, ByVal strUser As String, ByVal strPass As String) As Boolean
On Error GoTo error
    Dim hOpen   As Long
    Dim hConn   As Long

    hOpen = InternetOpenA("FTPGET", 1, vbNullString, vbNullString, 1)
    hConn = InternetConnectA(hOpen, strHost, lngPort, strUser, strPass, 1, 0, 2)

    If FtpPutFileA(hConn, strLocalFile, strRemoteFile, FTP_TRANSFER_TYPE_UNKNOWN Or INTERNET_FLAG_RELOAD, 0) Then
        FtpUpload = True
        Debug.Print "Success"
    Else
        FtpUpload = False
        Debug.Print "Fail"
    End If

    'Close connections
    InternetCloseHandle hConn
    InternetCloseHandle hOpen

Exit Function
error:
    FtpUpload = False
    Debug.Print Err.Number & ": " & Err.Description
End Function

viernes, 6 de octubre de 2017

VBA Access. Listado de artículos con sus imágenes asociadas de una BdD Sql Server en un formulario con Botones e Imágenes (ejemplo de 4x4 botones/imágenes)

'Formulario de tipo único compuesto por:
'16 botones cmdBut1,cmdBut2, ... (Botón con estilo transparente para poder ver la imagen de detrás)
'16 imagenes (detrás de cada botón) Imagen1,Imagen2, ...
'16 textbox Desc1, Desc2,... (DEBAJO DE CADA BOTÓN/IMAGEN) cada uno de ellos con Origen de control = Desc1, Desc2, ... respectivamente
'16 textbox RefArt1,RefArt2,... (OCULTOS) cada uno de ellos con Origen de control = RefArt1, RefArt2, ... respectivamente
'16 textbox CodImg1,CodImg2,... (OCULTOS) cada uno de ellos con Origen de control = CodImg1, CodImg2, ... respectivamente
'4 botones para navegar por los registros (Anterior, Siguiente, Primero y Último)

Option Compare Database
Option Explicit

Const NUMBUTTONS = 16

Private Sub ProcessButtonClicked()
On Error GoTo error
    Dim NumButton As Integer
    NumButton = CInt(Replace(Me.ActiveControl.Name, "cmdBut", "0"))
    If Nz(Me.Controls("RefArt" & NumButton).Value, "") = "" Then Err.Raise 99, "ProcessButtonClicked", "Botón / RefArt N. " & NumButton & " sin definir!"
   
    MsgBox Me.Controls("RefArt" & NumButton).Value & " " & Me.Controls("Desc" & NumButton).Value, , ""

Exit Sub
error:
    MsgBox Err.Description, vbCritical, ""
End Sub

Private Sub cmdBut1_Click()
    ProcessButtonClicked
End Sub

Private Sub cmdBut2_Click()
    ProcessButtonClicked
End Sub

Private Sub cmdBut3_Click()
    ProcessButtonClicked
End Sub

Private Sub cmdBut4_Click()
    ProcessButtonClicked
End Sub

Private Sub cmdBut5_Click()
    ProcessButtonClicked
End Sub

Private Sub cmdBut6_Click()
    ProcessButtonClicked
End Sub

Private Sub cmdBut7_Click()
    ProcessButtonClicked
End Sub

Private Sub cmdBut8_Click()
    ProcessButtonClicked
End Sub

Private Sub cmdBut9_Click()
    ProcessButtonClicked
End Sub

Private Sub cmdBut10_Click()
    ProcessButtonClicked
End Sub

Private Sub cmdBut11_Click()
    ProcessButtonClicked
End Sub

Private Sub cmdBut12_Click()
    ProcessButtonClicked
End Sub

Private Sub cmdBut13_Click()
    ProcessButtonClicked
End Sub

Private Sub cmdBut14_Click()
    ProcessButtonClicked
End Sub

Private Sub cmdBut15_Click()
    ProcessButtonClicked
End Sub

Private Sub cmdBut16_Click()
    ProcessButtonClicked
End Sub

Private Sub LoadArticulos()
On Error GoTo error
    'Creamos recordset dinámico
    Dim rsD As New ADODB.Recordset
    With rsD
        Dim i As Integer
        For i = 1 To NUMBUTTONS
            .Fields.Append "RefArt" & i, adVarChar, 255, adFldKeyColumn
            .Fields.Append "Desc" & i, adVarChar, 255, adFldMayBeNull
            .Fields.Append "CodImg" & i, adInteger, , adFldMayBeNull
        Next i
       
        .CursorType = adOpenKeyset
        .CursorLocation = adUseClient
        .LockType = adLockPessimistic
        .Open
    End With
   
    'A partir del recordset original, creamos otro recordset dinámicamente para simular un total de NUMBUTTONS por cada fila/pantalla
    Dim rsArt As New ADODB.Recordset
    Dim cnArt As New ADODB.Connection
    cnArt.ConnectionString = DimeCadenaConexion
    cnArt.Open
    rsArt.Open "SELECT TOP 1000 UPPER(ReferenciaArtículo) AS ReferenciaArtículo,UPPER(Descripción) AS Descripción,CodigoImagen FROM Artículos", _
                cnArt, adOpenStatic, adLockReadOnly
   
    'Rellenamos el recordset dinámico que al final asignaremos al formulario
    Do Until rsArt.EOF
        rsD.AddNew
   
        Dim j As Integer
        For j = 1 To NUMBUTTONS
            If Not rsArt.EOF Then
                rsD("RefArt" & j) = rsArt!ReferenciaArtículo
                rsD("Desc" & j) = rsArt!DESCRIPCIÓN
                rsD("CodImg" & j) = Nz(rsArt!CodigoImagen, 0)
                rsArt.MoveNext
            End If
        Next j
       
        rsD.Update
    Loop
    Set Me.Recordset = rsD
   
    rsArt.Close
    cnArt.Close
    Set rsArt = Nothing
   
    rsD.Close
    Set rsD = Nothing
   
    DoCmd.GoToRecord , , acFirst

Exit Sub
Resume
error:
    MsgBox Err.Number & ": " & Err.Description
End Sub

Private Sub cmdRegAnterior_Click()
On Error Resume Next
    DoCmd.GoToRecord , , acPrevious
End Sub

Private Sub cmdRegPrimero_Click()
On Error Resume Next
    DoCmd.GoToRecord , , acFirst
End Sub

Private Sub cmdRegSiguiente_Click()
On Error Resume Next
    DoCmd.GoToRecord , , acNext
End Sub

Private Sub cmdRegUltimo_Click()
On Error Resume Next
    DoCmd.GoToRecord , , acLast
End Sub

Private Sub Form_Current()
On Error Resume Next
    CargarImagenes
End Sub

Private Sub CargarImagenes()
On Error GoTo error
    'Asignaremos al registro actual / pantalla, las 16 imágenes que tienen asignadas por código de imagen
    '1 Consultaremos en la BdD la imagen y si esta no existe en la carpeta "Images" , con el mismo nombre de la referencia
    '2 Asignamos a cada control Imagen, el path de la imagen que deben cargar. Ej. Imagen1.Picture = "C:\...\Images\ficheroimagen"

    Debug.Print "Cargando Imágenes " & Now
   
    'Application.Echo False

    Dim fso As New FileSystemObject
    If Not fso.FolderExists(CurrentProject.Path & "\Images") Then fso.CreateFolder (CurrentProject.Path & "\Images")

    Dim i As Integer
    For i = 1 To NUMBUTTONS
        Dim CodigoImagen As Long
        CodigoImagen = Nz(Me.Controls("CodImg" & i), 0)
        If CodigoImagen <> 0 Then
            Dim rs As New ADODB.Recordset
            Dim cn As New ADODB.Connection
           
            cn.Open DimeCadenaConexion
            rs.Open "SELECT * FROM Imagenes WHERE CodigoImagen = " & CodigoImagen, cn, adOpenStatic, adLockReadOnly
            If Not rs.EOF Then
                Dim sFName  As String
                If Nz(rs!Fichero, "") <> "" Then
                    sFName = CurrentProject.Path & "\Images\" & Me.Controls("RefArt" & i) & "." & fso.GetExtensionName(rs!Fichero)
                   
                    If Not fso.FileExists(sFName) Then
                        Dim objStream As New ADODB.Stream
                        objStream.Type = adTypeBinary
                        objStream.Open
                        objStream.Write rs!Imagen
                        objStream.SaveToFile sFName, adSaveCreateOverWrite
                        objStream.Close
                        Set objStream = Nothing
                    End If
               
                    If fso.FileExists(sFName) Then
                        Me.Controls("Imagen" & i).Picture = sFName
                    Else
                        Me.Controls("Imagen" & i).Picture = ""
                    End If
                End If
            Else
                Me.Controls("Imagen" & i).Picture = ""
            End If
           
            rs.Close
            cn.Close
            Set rs = Nothing
           
        Else
            Me.Controls("Imagen" & i).Picture = ""
        End If
    Next i
   
    Set fso = Nothing
   
    'Application.Echo True
   
Exit Sub
error:
    MsgBox Err.Number & ": " & Err.Description
End Sub

Private Sub Form_Load()
    LoadArticulos
End Sub




martes, 3 de octubre de 2017

VBA Access. Listar en un formulario las imágenes de una tabla Sql Server.

'En un formulario tendremos un control imagen con origen de control: PathFName
'3 Textbox con orígenes de control: CodigoImagen, FName y KBSize

Private Sub LoadFormRecordset()
On Error GoTo error
    'Crear y abrir recordset dinamico al cual asignaremos valores y finalmente lo asignaremos al recordset del formulario
   'https://www.w3schools.com/asp/ado_datatypes.asp

    Dim rsD As New ADODB.Recordset
    rsD.Fields.Append "CodigoImagen", adInteger, , adFldKeyColumn
    rsD.Fields.Append "PathFName", adVarChar, 255, adFldIsNullable
    rsD.Fields.Append "FName", adVarChar, 255, adFldIsNullable
    rsD.Fields.Append "KBSize", adInteger, , adFldIsNullable
 
    rsD.CursorType = adOpenKeyset
    rsD.CursorLocation = adUseClient
    rsD.LockType = adLockPessimistic
    rsD.Open
     
    'Consultar BdD en otro recordset y extraer imagenes a ficheros
    Dim rsT As New ADODB.Recordset
    Dim cn As New ADODB.Connection
    cn.ConnectionString = DimeCadenaConexion
    cn.Open
 
    rsT.Open "SELECT CodigoImagen,NombreFichero,KBSize,Imagen FROM Imagenes", cn, adOpenStatic, adLockReadOnly
    If Not rsT.EOF Then
        'Crear carpeta temporal
        Dim sTempFolder As String
        sTempFolder = CurrentProject.Path & "\TempImgs"
     
        Dim fso As New FileSystemObject
        If Not fso.FolderExists(sTempFolder) Then fso.CreateFolder (sTempFolder)
     
        'Guardar imagen de bdd a fichero
        Dim str As New ADODB.Stream
        Dim objStream As New ADODB.Stream
        objStream.Type = adTypeBinary
        objStream.Open
             
        rsT.MoveFirst
        Dim i As Long
        For i = 1 To rsT.RecordCount
            objStream.Write rsT("Imagen")
            objStream.SaveToFile sTempFolder & "\" & fso.GetFileName(rsT("NombreFichero")), adSaveCreateOverWrite
         
            'Asignamos valores a recordset dinamico
            rsD.AddNew
            rsD!CodigoImagen = rsT("CodigoImagen")
            rsD!PathFName = sTempFolder & "\" & fso.GetFileName(rsT("NombreFichero"))
            rsD!FName = fso.GetFileName(rsT("NombreFichero"))
            rsD!KBSize = rsT("KBFichero")
            rsD.Update
         
            rsT.MoveNext
        Next i
     
        objStream.Close
        Set objStream = Nothing
 
        'asignar recordset dinamico al formulario
        Set Me.Recordset = rsD
     
    End If
    rsD.Close
    Set rsD = Nothing
    rsT.Close
    cn.Close
    Set rsT = Nothing

Exit Sub
Resume
error:
    MsgBox Err.Number & ": " & Err.Description
End Sub

VBA Access. Grabar fichero imagen en una tabla Sql Server.

'Ejemplo tabla Sql Server
'TABLE [dbo].[Imagenes](
' [CodigoImagen] [int] NOT NULL,
' [Fichero] [nvarchar](255) NOT NULL,
' [KBSize] [float] NOT NULL CONSTRAINT [DF_Imagenes_New_KBSize]  DEFAULT ((0))
' [Imagen] [image] NULL
')

Option Compare Database
Option Explicit

Private Enum MsoFileDialogType
    msoFileDialogOpen = 1           'Permite al usuario abrir un archivo.
    msoFileDialogSaveAs = 2         'Permite al usuario guardar un archivo.
    msoFileDialogFilePicker = 3     'Permite al usuario seleccionar un archivo.
    msoFileDialogFolderPicker = 4   'Permite al usuario seleccionar una carpeta.
End Enum

Private Function SelectItem(ByVal tipo As MsoFileDialogType) As String
On Error GoTo error
    Dim fDialog As Object
    Dim intResult As Integer
    Dim strPath As String
    strPath = ""

    Set fDialog = Application.FileDialog(tipo)

    intResult = Application.FileDialog(tipo).Show
    If intResult <> 0 Then
        strPath = Application.FileDialog(tipo).SelectedItems(1)
    End If
 
    SelectItem = strPath

Exit Function
error:
    SelectItem = ""
    MsgBox Err.Description
End Function

Private Sub cmdSaveToDB_Click()
On Error GoTo error
    Dim sFile As String
    sFile = SelectItem(msoFileDialogFilePicker)
    If sFile = "" Then Exit Sub
   
    Dim fso As New FileSystemObject
    Dim rs As New ADODB.Recordset
    Dim cn As New ADODB.Connection
   
    cn.ConnectionString = DimeCadenaConexion
    cn.Open
   
    rs.Open "SELECT TOP 0 * FROM Imagenes", cn, adOpenStatic, adLockPessimistic
   
    rs.AddNew
       
    rs!CodigoImagen = cn.Execute("SELECT ISNULL(MAX(CodigoImagen),0) + 1 AS NewCodigoImagen FROM Imagenes")!NewCodigoImagen
    rs!Fichero = fso.GetFileName(sFile)
    rs!KBSize = Round(fso.GetFile(sFile).Size / 1024, 2)
   
    'insertar imagen a bdd
    Dim objStream As New ADODB.Stream
    objStream.Type = adTypeBinary
    objStream.Open
    objStream.LoadFromFile sFile
    rs!Imagen = objStream.Read
    objStream.Close
    Set objStream = Nothing
   
    rs.Update
    rs.Close
    cn.Close
    Set rs = Nothing
    Set fso = Nothing
   
Exit Sub
Resume
error:
    MsgBox Err.Number & ": " & Err.Description

End Sub

VBA Access. Listar datos de una tabla Sql Server en un formulario.

Option Compare Database
Option Explicit

Private Sub Form_Open(Cancel As Integer)
    Dim rs As New ADODB.Recordset
    Dim cn As New ADODB.Connection
    cn.ConnectionString = "Provider=SQLNCLI11;DATA SOURCE=localhost;Integrated Security=SSPI;INITIAL CATALOG=CatalogoBD"
    cn.Open
   
    rs.CursorLocation = adUseClient
   
    'adLockPessimistic >>> registros son modificables en la bdd des de el formulario
    'rs.Open "SELECT * FROM Tabla", cn, adOpenStatic, adLockPessimistic
   
    'solo lectura >>> registros no son modificables
    rs.Open "SELECT * FROM Tabla", cn, adOpenStatic, adLockReadOnly
   
    If Not rs.EOF Then
        Set Me.Recordset = rs
        DoCmd.GoToRecord , , acFirst
    End If
    rs.Close
    cn.Close
End Sub

lunes, 2 de octubre de 2017

VBA Access. Mostrar todas las imágenes en 5 columnas de una carpeta y sus subdirectorios en un formulario continuo utilizando un recordset dinámico.

Option Compare Database
Option Explicit

'Visualizar todas las imágenes de una carpeta y subcarpetas en un formulario simulando 5 registros por fila
'
'Construimos un formulario con
'encabezado formulario:
'1 botón de comando para seleccionar la carpeta con las imagenes
'
'detalles formulario:
'5 controles imagen1,imagen2,imagen3,imagen4,imagen5 y origen del control llamados Img_1,Img_2,Img_3,Img_4,Img_5 en cada uno de ellos
'5 botones transparentes encima de cada imagen
'Por cada imagen, debajo añadimos, 3 textbox con origen del control FName,PathFName,Order, para la segunda imagen FName_2,PathFName_2,Order_2, ...
'
'configurar el formulario en formularios continuos

Private Enum MsoFileDialogType
    msoFileDialogOpen = 1           'Permite al usuario abrir un archivo.
    msoFileDialogSaveAs = 2         'Permite al usuario guardar un archivo.
    msoFileDialogFilePicker = 3     'Permite al usuario seleccionar un archivo.
    msoFileDialogFolderPicker = 4   'Permite al usuario seleccionar una carpeta.
End Enum

Private Function SelectItem(ByVal tipo As MsoFileDialogType) As String
On Error GoTo error
    Dim fDialog As Object
    Dim intResult As Integer
    Dim strPath As String
    strPath = ""

    Set fDialog = Application.FileDialog(tipo)

    intResult = Application.FileDialog(tipo).Show
    If intResult <> 0 Then
        strPath = Application.FileDialog(tipo).SelectedItems(1)
    End If

    SelectItem = strPath

Exit Function
error:
    SelectItem = ""
    MsgBox Err.Description
End Function

Private Sub cmbButton1_Click()
    MsgBox Me.PathFName

End Sub

Private Sub cmbButton2_Click()
    MsgBox Me.PathFName_2

End Sub

Private Sub cmbButton3_Click()
    MsgBox Me.PathFName_3

End Sub

Private Sub cmbButton4_Click()
    MsgBox Me.PathFName_4

End Sub

Private Sub cmbButton5_Click()
    MsgBox Me.PathFName_5

End Sub

Private Sub cmdLoadFolderImageToPictures_Click()
    Dim res As Boolean
    Dim sFPathFolder  As String
    sFPathFolder = SelectItem(msoFileDialogFolderPicker)
    If sFPathFolder = "" Then Exit Sub

    Dim oFileList As New clsFileList
    res = oFileList.GetFileList(sFPathFolder)
    If Not res Then Exit Sub

    Dim rs As New ADODB.Recordset
    With rs
        .Fields.Append "FName", adVarChar, 255, adFldIsNullable
        .Fields.Append "PathFName", adVarChar, 255, adFldKeyColumn
        .Fields.Append "Img", adVarChar, 255, adFldIsNullable
        .Fields.Append "Order", adInteger, , adFldIsNullable
     
        .Fields.Append "FName_2", adVarChar, 255, adFldIsNullable
        .Fields.Append "PathFName_2", adVarChar, 255, adFldKeyColumn
        .Fields.Append "Img_2", adVarChar, 255, adFldIsNullable
        .Fields.Append "Order_2", adInteger, , adFldIsNullable
     
        .Fields.Append "FName_3", adVarChar, 255, adFldIsNullable
        .Fields.Append "PathFName_3", adVarChar, 255, adFldKeyColumn
        .Fields.Append "Img_3", adVarChar, 255, adFldIsNullable
        .Fields.Append "Order_3", adInteger, , adFldIsNullable
     
        .Fields.Append "FName_4", adVarChar, 255, adFldIsNullable
        .Fields.Append "PathFName_4", adVarChar, 255, adFldKeyColumn
        .Fields.Append "Img_4", adVarChar, 255, adFldIsNullable
        .Fields.Append "Order_4", adInteger, , adFldIsNullable
     
        .Fields.Append "FName_5", adVarChar, 255, adFldIsNullable
        .Fields.Append "PathFName_5", adVarChar, 255, adFldKeyColumn
        .Fields.Append "Img_5", adVarChar, 255, adFldIsNullable
        .Fields.Append "Order_5", adInteger, , adFldIsNullable
     
        .CursorType = adOpenKeyset
        .CursorLocation = adUseClient
        .LockType = adLockPessimistic
        .Open
    End With

    Dim nRecords As Long
    nRecords = oFileList.FilesCount
    Dim fso As New FileSystemObject
    Dim i As Long
    Dim j As Integer
    For i = 1 To nRecords
            rs.AddNew
         
            rs!FName = fso.GetFileName(oFileList.Files(i))
            rs!PathFName = oFileList.Files(i)
            rs!Img = oFileList.Files(i)
            rs!Order = i
         
            j = 0
            j = i + 1
            If j <= nRecords Then
                rs!FName_2 = fso.GetFileName(oFileList.Files(j))
                rs!PathFName_2 = oFileList.Files(j)
                rs!Img_2 = oFileList.Files(j)
                rs!Order_2 = j
            End If
         
            j = j + 1
            If j <= nRecords Then
                rs!FName_3 = fso.GetFileName(oFileList.Files(j))
                rs!PathFName_3 = oFileList.Files(j)
                rs!Img_3 = oFileList.Files(j)
                rs!Order_3 = j
            End If
         
            j = j + 1
            If j <= nRecords Then
                rs!FName_4 = fso.GetFileName(oFileList.Files(j))
                rs!PathFName_4 = oFileList.Files(j)
                rs!Img_4 = oFileList.Files(j)
                rs!Order_4 = j
            End If
         
            j = j + 1
            If j <= nRecords Then
                rs!FName_5 = fso.GetFileName(oFileList.Files(j))
                rs!PathFName_5 = oFileList.Files(j)
                rs!Img_5 = oFileList.Files(j)
                rs!Order_5 = j
            End If
         
            rs.Update
     
            i = j
    Next i
    Set fso = Nothing

    'rs.Sort = "PathFname,FName"
    'rs.Sort = "FName"

    Set Me.Recordset = rs
    rs.Close
    Set rs = Nothing

End Sub


domingo, 1 de octubre de 2017

VBA Access. Mostrar todas las imágenes de una carpeta y sus subdirectorios en un formulario continuo utilizando un recordset dinámico.

Option Compare Database
Option Explicit

'Visualizar todas las imágenes de una carpeta y subcarpetas en un formulario
'
'Construimos un formulario con
'encabezado formulario:
'1 botón de comando
'
'detalles formulario:
'1 control imagen y origen del control llamado Img
'3 textbox con origen del control FName, PathFName y Order
'
'configurar el formulario en formularios continuos


Private Enum MsoFileDialogType
    msoFileDialogOpen = 1           'Permite al usuario abrir un archivo.
    msoFileDialogSaveAs = 2         'Permite al usuario guardar un archivo.
    msoFileDialogFilePicker = 3     'Permite al usuario seleccionar un archivo.
    msoFileDialogFolderPicker = 4   'Permite al usuario seleccionar una carpeta.
End Enum

Private Function SelectItem(ByVal tipo As MsoFileDialogType) As String
On Error GoTo error
    Dim fDialog As Object
    Dim intResult As Integer
    Dim strPath As String
    strPath = ""

    Set fDialog = Application.FileDialog(tipo)

    intResult = Application.FileDialog(tipo).Show
    If intResult <> 0 Then
        strPath = Application.FileDialog(tipo).SelectedItems(1)
    End If

    SelectItem = strPath

Exit Function
error:
    SelectItem = ""
    MsgBox Err.Description
End Function

Private Sub cmdLoadFolderImageToPictures_Click()
    Dim res As Boolean
    Dim sFPathFolder  As String
    sFPathFolder = SelectItem(msoFileDialogFolderPicker)
    If sFPathFolder = "" Then Exit Sub

    Dim oFileList As New clsFileList
    res = oFileList.GetFileList(sFPathFolder)
    If Not res Then Exit Sub

    Dim rs As New ADODB.Recordset
    With rs
        .Fields.Append "PathFName", adVarChar, 255, adFldKeyColumn
        .Fields.Append "FName", adVarChar, 255, adFldIsNullable
        .Fields.Append "Img", adVarChar, 255, adFldIsNullable
        .Fields.Append "Order", adInteger, , adFldIsNullable
        .CursorType = adOpenKeyset
        .CursorLocation = adUseClient
        .LockType = adLockPessimistic
        .Open
    End With

    Dim fso As New FileSystemObject
    Dim i As Long
    For i = 1 To oFileList.FilesCount
        rs.AddNew
        rs!FName = fso.GetFileName(oFileList.Files(i))
        rs!PathFName = oFileList.Files(i)
        rs!Img = oFileList.Files(i)
        rs!Order = i
        rs.Update
    Next i
    Set fso = Nothing

    'rs.Sort = "PathFname,FName"
    rs.Sort = "FName"

    Set Me.Recordset = rs
    rs.Close
    Set rs = Nothing

End Sub



VBA Access. Mostrar una imagen en un control imagen.

Option Compare Database
Option Explicit

'Construimos un formulario con:
'1 control imagen llamado Imagen1
'2 textbox llamados txtImagenName y txtImagenPath

Private Enum MsoFileDialogType
    msoFileDialogOpen = 1           'Permite al usuario abrir un archivo.
    msoFileDialogSaveAs = 2         'Permite al usuario guardar un archivo.
    msoFileDialogFilePicker = 3     'Permite al usuario seleccionar un archivo.
    msoFileDialogFolderPicker = 4   'Permite al usuario seleccionar una carpeta.
End Enum

Private Function SelectItem(ByVal tipo As MsoFileDialogType) As String
On Error GoTo error
    Dim fDialog As Object
    Dim intResult As Integer
    Dim strPath As String
    strPath = ""

    Set fDialog = Application.FileDialog(tipo)

    intResult = Application.FileDialog(tipo).Show
    If intResult <> 0 Then
        strPath = Application.FileDialog(tipo).SelectedItems(1)
    End If
 
    SelectItem = strPath

Exit Function
error:
    SelectItem = ""
    MsgBox Err.Description
End Function

Private Sub cmdLoadFileImageToPicture_Click()
On Error GoTo error
    Dim sFPathName As String
    sFPathName = SelectItem(msoFileDialogFilePicker)
    If sFPathName = "" Then Exit Sub
   
    Dim fso As New FileSystemObject
    Dim sFName As String
    sFName = fso.GetFileName(sFPathName)
    Me.txtImagenName = sFName
    Me.txtImagenPath = sFPathName
    Me.Imagen1.Picture = sFPathName
    Set fso = Nothing

Exit Sub
error:
    MsgBox Err.Description
End Sub

VBA Access. Redondeo de números decimales con el método medio redondeo. Alternativa a la función Round (bankers round)

 Private Function Redondeo(ByVal Numero As Variant, ByVal Decimales As Integer) As Double     'Aplica método medio redondeo (half round ...