セル データに基づいて目次付きの HTML ファイルを作成する

このコード例では、ワークシートからデータを取得し、HTML ファイル内に目次を作成する方法を示します。 ワークシートには、目次の階層の 1 番目のレベル、2 番目のレベル、3 番目のレベルにそれぞれ対応する列 A、列 B、列 C にデータが含まれている必要があります。 HTML ファイルは、作業中のブックと同じ作業フォルダーに格納されます。

サンプル コードの提供元: 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

投稿者について

Holy Macro! Books は、Microsoft Office を使用する人々が楽しめる本を出版しています。 カタログの完全版は、MrExcel.com を参照してください。

サポートとフィードバック

Office VBA またはこの説明書に関するご質問やフィードバックがありますか? サポートの受け方およびフィードバックをお寄せいただく方法のガイダンスについては、Office VBA のサポートおよびフィードバックを参照してください。