FrontPage Macro: Build Folder URL Tree

Using this FrontPage VBA Macro

This FrontPage VBA Macro is designed to return an array of all the folder URLs for the currently-open web site. I call this function from a lot of my other macros.

FrontPage VBA Macro Example Code

Private Function BuildFolderUrlTree() As Variant

On Error Resume Next

' Declare all our variables
Dim objWebFolder As WebFolder
Dim objFolder As WebFolder
Dim objSubFolder As WebFolder
Dim strBaseFolder As String
Dim lngFolderCount As Long
Dim lngBaseCount As Long

With Application

' Check the caption of the application to see if a web is open.
If .ActiveWebWindow.Caption = "Microsoft FrontPage" Then
' If no web is open, display an informational message...
MsgBox "Please open a web before running this function.", vbCritical
' ... and end the macro.
Exit Function
End If

' Change the web view to folder view.
.ActiveWeb.ActiveWebWindow.ViewMode = fpWebViewFolders
' Refresh the web view and recalc the web.
.ActiveWeb.Refresh

' Define the initial values for our folder counters.
lngFolderCount = 1
lngBaseCount = 0

' Dimension an aray to hold the folder names.
ReDim strFolders(1) As Variant

' Get the URL of the root folder for the web...
strBaseFolder = .ActiveWeb.RootFolder.Url
' ... and store the URL in our array.
strFolders(1) = strBaseFolder

' Loop while we still have folders to process.
While lngFolderCount <> lngBaseCount
' Set up a WebFolder object to a base folder.
Set objFolder = .ActiveWeb.LocateFolder(strBaseFolder)
' Loop through the collection of subfolders for the base folder.
For Each objSubFolder In objFolder.Folders
' Check to make sure that the subfolder is not a web.
If objSubFolder.IsWeb = False Then
' Increment our folder count.
lngFolderCount = lngFolderCount + 1
' Increase our array size
ReDim Preserve strFolders(lngFolderCount)
' Store the folder name in our array.
strFolders(lngFolderCount) = objSubFolder.Url
End If
Next
' Increment the base folder counter.
lngBaseCount = lngBaseCount + 1
' Get the name of the next folder to process.
strBaseFolder = strFolders(lngBaseCount + 1)
Wend
End With

' Return the array of folder names.
BuildFolderUrlTree = strFolders

End Function

FrontPage Macro: Reformat HTML

Using this FrontPage VBA Macro

This FrontPage VBA Macro is designed to reformat the HTML for every HTML or ASP file within the currently open web site.

FrontPage VBA Macro Example Code

Public Sub ReformatHTML()
Dim objWebFile As WebFile
Dim strExt As String
Dim cbCommandBar As CommandBar
Dim cbCommandBarControl As CommandBarControl

If Len(Application.ActiveWeb.Title) = 0 Then
MsgBox "A web must be open." & vbCrLf & vbCrLf & "Aborting.", vbCritical
Exit Sub
End If

For Each objWebFile In Application.ActiveWeb.AllFiles
strExt = LCase(objWebFile.Extension)
If strExt = "htm" Or strExt = "html" Or strExt = "asp" Then
objWebFile.Edit
Application.ActivePageWindow.ViewMode = fpPageViewHtml
DoEvents
Set cbCommandBar = Application.CommandBars("Html Page View Context Menu")
Set cbCommandBarControl = cbCommandBar.FindControl( _
Type:=msoControlButton, _
Id:=CommandBars("Html Page View Context Menu").Controls("Reformat HT&ML").Id)
cbCommandBarControl.Execute
DoEvents
Application.ActivePageWindow.Save
Application.ActivePageWindow.Close
End If
Next

End Sub

Access Macro: Export Table/Query To Excel

Using this Access VBA Macro

I wrote this Access VBA Macro for a friend to export an Access table or query to a spreadsheet; it might come in handy. ;-]

Access VBA Macro Example Code

Sub ExportTableOrQueryToExcel()

Const strTitle = "This is my worksheet title"
Const strTableOrQuery = "Query1"

' define the path to the output file
Dim strPath As String
strPath = "C:\TestFile " & _
Year(Now) & Right("0" & _
Month(Now), 2) & Right("0" & _
Day(Now), 2) & ".xls"

' create and open an Excel workbook
Dim objXL As Object
Set objXL = CreateObject("Excel.Application")
objXL.WorkBooks.Add
objXL.Worksheets(1).Name = strTitle
objXL.Visible = False

' delete the extra worksheets
Dim intX As Integer
If objXL.Worksheets.Count > 1 Then
For intX = 2 To objXL.Worksheets.Count
objXL.Worksheets(2).Delete
Next
End If

' open the database
Dim objDB As DAO.Database
Dim objRS As DAO.Recordset
Dim objField As DAO.Field
Set objDB = CurrentDb

' open the query/table
Dim strSQL As String
strSQL = "SELECT * FROM [" & strTableOrQuery & "]"
Set objRS = objDB.OpenRecordset(strSQL)

Dim lngRow As Long
Dim lngCol As Long

If Not objRS.EOF Then

lngRow = 1: lngCol = 1

For Each objField In objRS.Fields
objXL.Worksheets(1).Cells(lngRow, lngCol).Value = objField.Name
lngCol = lngCol + 1
Next

lngRow = lngRow + 1

' loop through the table records
Do While Not objRS.EOF
lngCol = 1
For Each objField In objRS.Fields
objXL.Worksheets(1).Cells(lngRow, lngCol).Value = objField.Value
lngCol = lngCol + 1
Next
lngRow = lngRow + 1
objRS.MoveNext
Loop

End If

objXL.DisplayAlerts = False
objXL.ActiveWorkbook.SaveAs strPath, 46
objXL.ActiveWorkbook.Close

End Sub

Access: Database Schema Report

Summary

This article shows you a Windows Script Host (WSH) application that will create a report based on the schema of an Access Database.


More Information

  1. Open Windows Notepad and copy/paste the WSH code listed below into it.
  2. Modify the strDatabaseFile and strOutputFile constants for your database and desired report name.
  3. Save the file as "DatabaseScema.vbs" to your desktop.
  4. Double-click the WSH file to run it.
    Note: A message box that says "Finished!" will appear when the script has finished executing.
Windows Script Host (WSH) Code
Option Explicit

' --------------------------------------------------
' Define variables and constants
' --------------------------------------------------

Const strDatabaseFile = "MusicStuff.mdb"
Const strOutputFile = "MusicStuff.htm"
Const adSchemaTables = 20

Dim strSQL
Dim strCN
Dim objCN
Dim objRS1
Dim objRS2
Dim objField
Dim intCount
Dim objFSO
Dim objFile

' --------------------------------------------------
' Open the output file
' --------------------------------------------------

Set objFSO = WScript.CreateObject("Scripting.FileSystemObject")
Set objFile = objFSO.CreateTextFile(strOutputFile)
objFile.WriteLine "<html><head>" & _
"<style>BODY { font-family:arial,helvetica; }</style>" & _
"</head><body>"
objFile.WriteLine "<h2>Schema Report for &quot;" & _
strDatabaseFile & "&quot;</h2>"

' --------------------------------------------------
' Setup the string array of field type descriptions
' --------------------------------------------------

Dim strColumnTypes(205)

' initialize array

For intCount = 0 To UBound(strColumnTypes)
strColumnTypes(intCount) = "n/a"
Next

' add definitions

strColumnTypes(2) = "Integer"
strColumnTypes(3) = "Long Integer"
strColumnTypes(4) = "Single"
strColumnTypes(5) = "Double"
strColumnTypes(6) = "Currency"
strColumnTypes(11) = "Yes/No"
strColumnTypes(17) = "Byte"
strColumnTypes(72) = "Replication ID"
strColumnTypes(131) = "Decimal"
strColumnTypes(135) = "Date/Time"
strColumnTypes(202) = "Text"
strColumnTypes(203) = "Memo/Hyperlink"
strColumnTypes(205) = "OLE Object"

' --------------------------------------------------
' Open database and schema
' --------------------------------------------------

strCN = "DRIVER={Microsoft Access Driver (*.mdb)};DBQ=" & strDatabaseFile
Set objCN = WScript.CreateObject("ADODB.Connection")
objCN.Open strCN
Set objRS1 = objCN.OpenSchema(adSchemaTables)

' --------------------------------------------------
' Loop through database schema
' --------------------------------------------------

Do While Not objRS1.EOF
If Left(objRS1("TABLE_NAME"),4) <> "MSys" Then
objFile.WriteLine "<p><big>" & objRS1("TABLE_NAME") & "</big></p>"
objFile.WriteLine "<blockquote><table border=1>" & _
"<tr><th>Field Name</th><th>Data Type</th></tr>"
strSQL = "SELECT * FROM [" & objRS1("TABLE_NAME") & "]"
Set objRS2 = objCN.Execute(strSQL)
For Each objField in objRS2.Fields
objFile.WriteLine "<tr><td>" & objField.Name _
& "</td><td>" & strColumnTypes(objField.Type) & "</td></tr>"
Next
objFile.WriteLine "</table></blockquote>"
End If
objRS1.MoveNext
Loop

' --------------------------------------------------
' Close the output file
' --------------------------------------------------

objFile.WriteLine "</body></html>"

MsgBox "Finished!"

IIS Versions and Timeline

I put this list together sometime ago, but I don't recall why. In any event, the following time line illustrates the history of Microsoft's Internet Information Services and the individual services that shipped with each version.

  • 1996 - IIS 1.0 - Add-on for Windows NT 3.51
    • HTTP
  • 1996 - IIS 2.0 - Released with Windows NT 4.0 RTM
    • HTTP
    • FTP
    • Gopher
  • 1996 - IIS 3.0 - Released with Windows NT 4.0 SP3
    • HTTP
    • FTP
    • Gopher
  • 1997 - IIS 4.0 - Released with Windows NT Internet Option Pack
    • HTTP
    • FTP
    • SMTP (Only on server)
    • NNTP (Only on server)
  • 2000 - IIS 5.0 - Released with Windows 2000
    • HTTP
    • FTP
    • SMTP (Only on server)
    • NNTP (Only on server)
  • 2002 - IIS 5.1 - Released with Windows XP Professional
    • HTTP
    • FTP
    • SMTP
  • 2003 - IIS 6.0 - Released with Windows Server 2003
    • HTTP
    • FTP
    • SMTP
      (Note: A POP3 service also shipped with Windows Server 2003, but not as part of IIS.)
  • 2008 - IIS 7.0 - Released with Windows Server 2008 and Windows Vista
    • HTTP
    • FTP
      (Note: A newer FTP service was released out-of-band for IIS 7.0.)
  • 2009 - IIS 7.5 - Released with Windows Server 2008 R2 and Windows 7
    • HTTP
    • FTP

WebDAV Module for Windows Server 2008 GoLive Beta is released

Earlier today the IIS product team released the GoLive beta version of the new WebDAV extension module for IIS 7. (This version is currently available for Windows Server 2008 only.)

Listed below are the links for the download pages for each of the individual installation packages:

We've loaded this version with many great new features such as:

  • Integration with IIS 7.0: The new WebDAV extension module is fully integrated with the new IIS 7.0 administration interface and configuration store.
  • Per-site Configuration: WebDAV can be enabled at the site-level on IIS 7.0, which differed from IIS 6.0 where WebDAV was enabled at the server-level through a Web Service Extension.
  • Per-URL Security: WebDAV-specific security is implemented through WebDAV authoring rules that are configured on a per-URL basis.

Here are a couple of screenshots of the new WebDAV UI in action:

WebDAV UI WebDAV Authoring Rules

Additional documentation about installing and using this version of WebDAV can be found at the following URL:

Installing and Configuring WebDAV on IIS 7.0:
http://go.microsoft.com/fwlink/?LinkId=105146

While this release is a beta version and not technically supported, feedback about this release and requests for information can be posted to the following web forum:

IIS7 - Publishing:
http://forums.iis.net/1045.aspx

I would be remiss if I did not mention that special thanks go to:

  • Keith – for building it
  • Eok, Sriram, Ciprian – for testing it
  • Gurpreet, Brian, Reagan – for making it look pretty
  • Vijay, Will, Taylor – for helping keep everything on track ;-]

Thanks!


Note: This blog was originally posted at http://blogs.msdn.com/robert_mcmurray/

FPSE 2002 RC1 for Windows Server 2008 and Windows Vista (x86/x64)

Earlier today Microsoft and Ready-to-Run Software released to web the Release Candidate 1 (RC1) version of the FrontPage 2002 Server Extensions for IIS 7.0 on Windows Server 2008 and Windows Vista. This build now includes a combined installation package for 32-bit and 64-bit versions of Windows.

Listed below is the link for the download page for the combined 32-bit/64-bit installation package:

FPSE 2002 RC1 for IIS 7 is supported on all of the the following operating systems:

  • Windows Server 2008 (Code Name "Longhorn")
  • Windows Vista Ultimate
  • Windows Vista Home Premium
  • Windows Vista Business
  • Windows Vista Enterprise

Once again, additional documentation about installing and using this version of FPSE 2002 can be found at the following URL:

Installing the FrontPage 2002 Server Extensions:
http://go.microsoft.com/fwlink/?LinkId=88546

While this release is a beta version and not technically supported, feedback about this release and requests for information can be sent to fpbeta@rtr.com or posted to the following web forum:

IIS7 - Publishing:
http://forums.iis.net/1045.aspx

Thanks!


Note: This blog was originally posted at http://blogs.msdn.com/robert_mcmurray/

Creating XML Reports for FSRM Quota Usage

I had a great question in follow up to the "Secure, Simplified Web Publishing using Microsoft Internet Information Services 7.0" webcast that I delivered the other day, "How you can you programmatically access the quota usage information from the File Server Resource Manager (FSRM)?"

First of all, there is a native API for writing code to access FSRM data detailed at the following URL:

http://msdn2.microsoft.com/en-us/library/bb625489.aspx

That's a bit of overkill if you're just looking to script something.

There is a WMI interface as well, but it’s only for FSRM events.

So that leaves you with a pair of command-line tools that you can script in order to list your quota usage information:

  • storrept.exe - Used to manage storage reports
  • dirquota.exe - Used to manage quota usage

Right out of the box the first command-line tool, storrept.exe, can generate a detailed XML report using a user-definable scope. To see this in action, take the following example syntax and modify the scope parameter to your desired paths:

storrept.exe reports generate /Report:QuotaUsage /Format:XML /Scope:"C:\"

 You can also specify multiple paths in your scope using a pipe-delimited format like:

/Scope:"C:\Inetpub|D:\Inetpub"

When the command has finished, it will tell you the path to your report like the following example:

Storage reports generated successfully in "C:\StorageReports\Interactive".

The XML-based information in the report can then be consumed with whatever method you usually use to parse XML. It should be noted that storrept.exe also supports the following formats: CSV, DHTML, HTML, and TXT.

This XML might be okay for most applications, but for some reason I wanted to customize the information that I received, so I experimented with the second command-line tool, dirquota.exe, to get the result that I was looking for.

First of all, using dirquota.exe quota list returns information in the following format:

Quotas on machine SERVER: Quota Path: C:\inetpub\ftproot Source Template: 100 MB Limit (Matches template) Quota Status: Enabled Limit: 100.00 MB (Hard) Used: 1.00 KB (0%) Available: 100.00 MB Peak Usage: 1.00 KB (10/25/2007 2:15 PM) Thresholds: Warning ( 85%): E-mail Warning ( 95%): E-mail, Event Log Limit (100%): E-mail, Event Log

This information is formatted nicely and is therefore easily parsed, so I wrote the following batch file called "dirquota.cmd" to start things off:

@echo off echo Processing the report... dirquota.exe quota list > dirquota.txt cscript.exe //nologo dirquota.vbs

Next, I wrote the following vbscript application called "dirquota.vbs" to parse the output into some easily-usable XML code:

Option Explicit

Dim objFSO, objFile1, objFile2
Dim strLine, strArray(2)
Dim blnQuota,blnThreshold

' create objects
Set objFSO = WScript.CreateObject("Scripting.FileSystemObject")
Set objFile1 = objFSO.OpenTextFile("dirquota.txt")
Set objFile2 = objFSO.CreateTextFile("dirquota.xml")

' start the XML output file
objFile2.WriteLine "<?xml version=""1.0""?>"
objFile2.WriteLine "<Quotas>"

' set the runtime statuses to off
blnQuota = False
blnThreshold = False

' loop through the text file
Do While Not objFile1.AtEndOfStream

  ' get a line from the file
  strLine = objFile1.ReadLine

  ' only process lines with a colon character
  If InStr(strLine,":") Then
    ' split the string manually at the colon character
    strArray(1) = Trim(Left(strLine,InStr(strLine,":")-1))
    strArray(2) = Trim(Mid(strLine,InStr(strLine,":")+1))

    ' filter on strings with parentheses
    strLine = strArray(1)
    If InStr(strLine,"(") Then
      strLine = Trim(Left(strLine,InStr(strLine,"(")-1)) & "*"
    End If

    ' process the inidivdual entries
    Select Case UCase(strLine)

      ' a quota path signifies a new record
      Case UCase("Quota Path")

        ' close any open threshold collections
        If blnThreshold = True Then
          objFile2.WriteLine "</Thresholds>"
        End If

        ' close an open quota element
        If blnQuota= True Then
          objFile2.WriteLine "</Quota>"
        End If

        ' signify a new quota element
        objFile2.WriteLine "<Quota>"

        ' output the relelvant information
        objFile2.WriteLine FormatElement(strArray(1),strArray(2))

        ' set the runtime statuses
        blnQuota= True
        blnThreshold = False

      ' these bits of informaiton are parts of a quota
      Case UCase("Source Template"), UCase("Quota Status"), _
          UCase("Limit"), UCase("Used"), _
          UCase("Available"), UCase("Peak Usage")

        ' close any open threshold collections
        If blnThreshold = True Then
          objFile2.WriteLine "</Thresholds>"
        End If

        ' set the runtime status
        blnThreshold = False

        ' output the relelvant information
        objFile2.WriteLine FormatElement(strArray(1),strArray(2))

      ' these bits of informaiton are thresholds
      Case UCase("Warning*"), UCase("Limit*")

        ' open a threshold collection if not already open
        If blnThreshold = False Then
          objFile2.WriteLine "<Thresholds>"
        End If

        ' output the relelvant information
        objFile2.WriteLine FormatElement( _
          Left(strLine,Len(strLine)-1), _
          Replace(Mid(strArray(1), _
          Len(strLine))," ","") & " " & strArray(2))

        ' set the runtime status
        blnThreshold = True

    End Select
  End If
Loop

' close any open threshold collections
If blnThreshold = True Then
  objFile2.WriteLine "</Thresholds>"
End If

' close an open quota element
If blnQuota= True Then
  objFile2.WriteLine "</Quota>"
End If

' end the XML output file
objFile2.WriteLine "</Quotas>"

objFile1.Close
objFile2.Close
Set objFSO = Nothing

' format data into an XML element
Function FormatElement(tmpName,tmpValue)
  FormatElement = "<" & Replace(tmpName," ","") & _
  ">" & tmpValue & "</" & Replace(tmpName,Chr(32),"") & ">"
End Function

When the batch file and vbscript are run, they will create a file named "dirquota.xml" which will resemble the following example XML:

<?xml version="1.0"?>
<Quotas>
  <Quota>
    <QuotaPath>C:\inetpub\ftproot</QuotaPath>
    <SourceTemplate>100 MB Limit (Matches template)</SourceTemplate>
    <QuotaStatus>Enabled</QuotaStatus>
    <Limit>100.00 MB (Hard)</Limit>
    <Used>1.00 KB (0%)</Used>
    <Available>100.00 MB</Available>
    <PeakUsage>1.00 KB (10/25/2007 2:15 PM)</PeakUsage>
    <Thresholds>
      <Warning>(85%) E-mail</Warning>
      <Warning>(95%) E-mail, Event Log</Warning>
      <Limit>(100%) E-mail, Event Log</Limit>
    </Thresholds>
  </Quota>
</Quotas>

I found the above XML much easier to use than the XML that came from the storrept.exe report, but I'm probably comparing apples to oranges. In any event, I hope this helps someone with questions about FSRM reporting.

Have fun!


Note: This blog was originally posted at http://blogs.msdn.com/robert_mcmurray/

Upcoming IIS7 Webcasts

Okay, I have to admit, I was remiss at pointing this out earlier - several members of the IIS product team and myself are presenting webcasts on the TechNet web site for various IIS subjects throughout the month of October. Here's the schedule of upcoming topics:

We've had two webcasts already, and you can still listen to those online:

Enjoy!

FPSE 2002 RC0 for Windows Server 2008 and Windows Vista (x86/x64)

Earlier today Microsoft and Ready to Run Software released to web the Release Candidate 0 (RC0) version of the FrontPage 2002 Server Extensions for IIS 7.0 on Windows Server 2008 and Windows Vista. This build now includes support for 64-bit Windows, and addresses several issues that we've seen since the FPSE release that shipped last April.

Listed below are the links for the download pages for each of the individual installation packages:

FPSE 2002 RC0 for IIS 7 is supported on all of the the following operating systems:

  • Windows Server 2008 (Code Name "Longhorn")
  • Windows Vista Ultimate
  • Windows Vista Home Premium
  • Windows Vista Business
  • Windows Vista Enterprise

Additional documentation about installing and using this version of FPSE 2002 can be found at the following URL:

Installing the FrontPage 2002 Server Extensions:
http://go.microsoft.com/fwlink/?LinkId=88546

Quoting and updating some of my notes from the last release:

It should be noted that this version of FPSE 2002 is a beta release and is therefore unsupported. Also, this version of FPSE 2002 introduces no new functionality; it is essentially the same version of FPSE 2002 that was created for Windows Server 2003 that has been updated to work on Windows Server 2008 (code name "Longhorn") and Windows Vista. That being said, this version of FPSE 2002 will enable web hosters and developers to author their web content on servers or workstations that are running IIS 7.0 on Windows Server 2008 and Windows Vista.

While this release is a beta version and not technically supported, feedback about this release and requests for information can be sent to fpbeta@rtr.com or posted to the following web forum:

IIS7 - Publishing:
http://forums.iis.net/1045.aspx

Thanks!