Notes
L’accès à cette page nécessite une autorisation. Vous pouvez essayer de vous connecter ou de modifier des répertoires.
L’accès à cette page nécessite une autorisation. Vous pouvez essayer de modifier des répertoires.
Cet exemple de code montre comment extraire des données d’une feuille de calcul et créer une table des matières dans un fichier HTML. La feuille de calcul doit contenir des données dans les colonnes A, B et C qui correspondent aux premier, deuxième et troisième niveaux de la hiérarchie de la table des matières. Le fichier HTML est stocké dans le même dossier de travail que le classeur actif.
Exemple de code fourni par : Holy Macro! Books, Holy Macro! It’s 2 500 Excel VBA Examples
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
À propos du collaborateur
Holy Macro! Books publie des livres divertissants pour les personnes qui utilisent Microsoft Office. Vous pouvez consulter le catalogue complet sur MrExcel.com.
Assistance et commentaires
Avez-vous des questions ou des commentaires sur Office VBA ou sur cette documentation ? Consultez la rubrique concernant l’assistance pour Office VBA et l’envoi de commentaires afin d’obtenir des instructions pour recevoir une assistance et envoyer vos commentaires.