Compartir a través de


Crear un archivo HTML con una tabla de contenido basándose en datos de celda

Este ejemplo de código muestra cómo recoger datos de una hoja de cálculo para crear una tabla de contenido en un archivo HTML. La hoja de cálculo debe tener datos en las columnas A, B y C que correspondan al primero, segundo y tercer niveles de la jerarquía de tablas de contenido. El archivo HTML se almacena en la misma carpeta de trabajo que el libro activo.

Código de ejemplo proporcionado por: Holy Macro! Books,Holy Macro! It's 2,500 Excel VBA Examples (Holy Macro! 2500 ejemplos de VBA para Excel).

Sub CreateHTML()
   'Define your variables.
   Dim iRow As Long
   Dim iStage As Integer
   Dim iCounter As Integer
   Dim iPage As Integer
   
   'Create an .htm file in the same directory as your active workbook.
   Dim sFile As String
   sFile = ActiveWorkbook.Path & "\test.htm"
   Close
   
   'Open up the temp HTML file and format the header.
   Open sFile For Output As #1
   Print #1, "<html>"
   Print #1, "<head>"
   Print #1, "<style type=""text/css"">"
   Print #1, "  body { font-size:12px;font-family:tahoma } "
   Print #1, "</style>"
   Print #1, "</head>"
   Print #1, "<body>"
   
   'Start on the 2nd row to avoid the header.
   iRow = 2
   
   'Translate the first column of the table into the first level of the hierarchy.
   Do While WorksheetFunction.CountA(Rows(iRow)) > 0
      If Not IsEmpty(Cells(iRow, 1)) Then
         For iCounter = 1 To iStage
            Print #1, "</ul>"
            iStage = iStage - 1
         Next iCounter
         Print #1, "<ul>"
         Print #1, "<li><a href=""" & iPage & ".html"">" & Cells(iRow, 1).Value & "</a>"
         iPage = iPage + 1
         If iStage < 1 Then
            iStage = iStage + 1
         End If
      End If
      
    'Translate the second column of the table into the second level of the hierarchy.
      If Not IsEmpty(Cells(iRow, 2)) Then
         For iCounter = 2 To iStage
            Print #1, "</ul>"
            iStage = iStage - 1
         Next iCounter
         Print #1, "<ul>"
         Print #1, "<li><a href=""" & iPage & ".html"">" & Cells(iRow, 2).Value & "</a>"
         iPage = iPage + 1
         If iStage < 2 Then
            iStage = iStage + 1
         End If
      End If
      
      'Translate the third column of the table into the third level of the hierarchy.
      If Not IsEmpty(Cells(iRow, 3)) Then
         If iStage < 3 Then
            Print #1, "<ul>"
         End If
         Print #1, "<li><a href=""" & iPage & ".html"">" & Cells(iRow, 3).Value & "</a>"
         iPage = iPage + 1
         If iStage < 3 Then
            iStage = iStage + 1
         End If
      End If
      iRow = iRow + 1
   Loop
   
   'Add ending HTML tags
   For iCounter = 2 To iStage
      Print #1, "    </ul>"
      iStage = iStage - 1
   Next iCounter
   Print #1, "</body>"
   Print #1, "</html>"
   Close
   Shell "hh " & vbLf & sFile, vbMaximizedFocus
End Sub

Acerca del colaborador

Holy Macro! Books publica libros amenos para los usuarios de Microsoft Office. Vea el catálogo completo en MrExcel.com.

Soporte técnico y comentarios

¿Tiene preguntas o comentarios sobre VBA para Office o esta documentación? Vea Soporte técnico y comentarios sobre VBA para Office para obtener ayuda sobre las formas en las que puede recibir soporte técnico y enviar comentarios.