Slicing and dicing with LogParser & VBA

LogParser  is probably one of the most understated utilities from Microsoft. LogParser 2.2. Log parser is a powerful and a versatile tool that provides a SQL like query access to text-based data such as log files, XML files and CSV files, as well as key data sources on the Windows such as the Event Log, the Registry, the file system, and Active Directory. There are so many things that you can do to search and collate data on Windows with LogParser. The nice thing about it is that the query is SQL like and fairly intuitive.

On a UNIX/Linux system we would have to run a shell command for e.g. (ls –lrt) and pipe it to “sort”,”awk” or a “sed” utility. LogParser is all this rolled into one. If you have been reading my earlier post “Building a respectable VBA with Excel Application” will realize that using LogParser with VBA is a fairly potent combination and you can build nifty applications quickly.

Display files in directories

For e.g. to display file sizes in specific directories or under all directories we can create VBA GUI as below

The logParser commands are to display all files in the directory with Size, LastWriteTime & name is below

Set objLogParser = CreateObject(“MSUtil.LogQuery”)

Set objInputFormat = _

CreateObject(“MSUtil.LogQuery.FileSystemInputFormat”)

If OptionButton1.value = True Then

objInputFormat.recurse = -1

End If

If OptionButton2.value = True Then

objInputFormat.recurse = 0

End If

strQuery = “SELECT TO_LOWERCASE (Name) AS NewName,  Size, Path, LastWriteTime FROM ‘” &   files & “‘ ORDER BY LastWriteTime ASC”

Set objRecordSet = objLogParser.Execute(strQuery, objInputFormat)

Do While Not objRecordSet.AtEnd

Set objRecord = objRecordSet.GetRecord

strPath = objRecord.GetValue(“Path”)

fileSize = objRecord.GetValue(“Size”)

lastWriteTime = objRecord.GetValue(“LastWriteTime”)

objRecordSet.MoveNext

Loop

Top N files

You can display the Top N files by size, lastWriteTime or name with a suitable VBA GUI as below

This can be written in logParser as

Set objLogParser = CreateObject(“MSUtil.LogQuery”)

Set objInputFormat = _

CreateObject(“MSUtil.LogQuery.FileSystemInputFormat”)

If OptionButton7.value = True Then

strQuery = “SELECT TOP ” & topN & ” TO_LOWERCASE (Name) AS NewName, Size, Path, LastWriteTime FROM ‘” & _

files & “‘ WHERE NOT Attributes LIKE ‘%D%’ ORDER BY Size DESC”

ElseIf OptionButton8.value = True Then

strQuery = “SELECT TOP ” & topN & ” TO_LOWERCASE (Name) AS NewName, Size, Path, LastWriteTime FROM ‘” & _

files & “‘ WHERE NOT Attributes LIKE ‘%D%’ ORDER BY lastWriteTime ASC”

ElseIf OptionButton9.value = True Then

strQuery = “SELECT TOP ” & topN & ” TO_LOWERCASE (Name) AS NewName, Size, Path, LastWriteTime FROM ‘” & _

files & “‘ WHERE NOT Attributes LIKE ‘%D%’ ORDER BY NewName ASC”

End If

The SpinButtons subroutines can be updates as follows

Private Sub SpinButton1_SpinDown()

If TextBox7.value <= 1 Then

MsgBox (“Cannot decrement below 1”)

TextBox7.value = 1

Exit Sub

Else

TextBox7.value = TextBox7.value – 1

End If

End Sub

Private Sub SpinButton1_SpinUp()

TextBox7.value = TextBox7.value + 1

End Sub

Extension based disk management

logParser can also be used to select all files with specified extensions for e.g. tmp,.log etc

Set objLogParser = CreateObject(“MSUtil.LogQuery”)

Set objInputFormat = _

CreateObject(“MSUtil.LogQuery.FileSystemInputFormat”)

files = baseDirectory & “\” & fileExt

strQuery = “SELECT TO_LOWERCASE (Name) AS NewName,  Size ,Path, LastWriteTime FROM ‘” & _   files & “‘ ORDER BY LastWriteTime ASC”

Set objRecordSet = objLogParser.Execute(strQuery, objInputFormat)

You can also search Event Logs with LogParser

Event Logs

Set objLogParser = CreateObject(“MSUtil.LogQuery”)

Set objInputFormat = _

CreateObject(“MSUtil.LogQuery.EventLogInputFormat”)

If OptionButton1.Value = True Then

strQuery = “SELECT TimeGenerated, EventID, EventTypeName,Message, Strings, SourceName FROM Application WHERE EventID IN ” & str

ElseIf OptionButton2.Value = True Then

strQuery = “SELECT TimeGenerated, EventID, EventTypeName, Message, Strings, SourceName FROM System WHERE EventID IN ” & str

ElseIf OptionButton3.Value = True Then

strQuery = “SELECT TimeGenerated, EventID, EventTypeName, Message, Strings, SourceName FROM Security WHERE EventID IN ” & str

ElseIf OptionButton4.Value = True Then

strQuery = “SELECT TimeGenerated, EventID, EventTypeName, Message, Strings, SourceName FROM Setup WHERE EventID IN ” & str

End If

Set objRecordSet = objLogParser.Execute(strQuery, objInputFormat)

LogParser is really a cool utility and when combined with VBA can really help in developing nifty applications.

Find me on Google+

Building a respectable VBA with Excel Application

VBA with Excel is not the right tool/language to solve mankind’s perennial question regarding the purpose of life. But it can come quite handy for several tasks for e.g. in quickly creating a Proof of Concept (PoC) or a prototype. It can also be quite useful for smaller tasks for e.g. 3G networks dimensioning, determining an investment portfolio, insurance schemes or maybe a smaller version of a Windows Resource Management tool.  To take a quick look at how put together a VBA application quickly take a look at my earlier post “Stir fry a VBA with Excel application quickly”.

This post takes a look at some key aspects in building a respectable, decent tool. Some of essential elements are as follows

a)      Launch button: Launch the application from the Excel sheet. For this you could add a button to the Excel sheet. For this select “View->Toolbars-Forms”. From the toolbar select a button and place it in the Excel sheet. Once you place the button appropriately select the button and choose the “Edit code” from the Forms toolbox. Add the following code

Sub Button1_Click ()

UserForm1.Show

End Sub

The Userform1 is the form that you created with VBA toolbox.

b)      Minimize button:  Now that you are able to launch the VBA application from the Excel spreadsheet you will also want to minimize the VBA form to check the output on the Excel sheet. For this add a button to the Userform probably “_” the icon for minimizing and add

Private Sub CommandButton13_Click()

Unload UserForm1

End Sub

You could also do a Userform1. Hide but I found that once you did that and re-launched the application the combo-box’s list started to repeat.  Unload essentially resets the Form and that was fine with me.

c)      Getting control of the Excel sheet: This is extremely important. Make sure that in the properties window of your userform you have ShowModal set as “false”. This will allow you to edit/change your Excel sheet even when the VBA application is running.

d)     Status bar: VBA does provide a “Status” control in the additional controls for the Userform toolbox. But I could not get it to work. So I added a textbox and update the text box with “Working …” and “Done.”

e)      Progress bar: If you want to add a progress bar do so by adding this control. For this right-click in the toolbox and choose additional controls. I did not have the need to use this but a good write up is available at O’Reilly Hacks

My VBA Userform

Here is the sample code for this ….

Option Explicit
Dim servername
Dim row
Dim value

Private Sub CommandButton13_Click()
Unload UserForm1
End Sub
Private Sub CommandButton14_Click()
Unload UserForm1
End Sub

Private Sub CommandButton2_Click()
ComboBox1.ListIndex = 0
Me.OptionButton1.value = True
TextBox1.value = “”
End Sub

Private Sub CommandButton3_Click()
Unload UserForm1
End Sub

Private Sub TextBox1_Change()
servername = TextBox1.value
End Sub
Private Sub UserForm_Activate()
With ComboBox1
ComboBox1.AddItem “Physical Memory Properties”
ComboBox1.AddItem “Get Server Info”

….
End With
Me.Label17.Font.Bold = True
Me.MultiPage1.ForeColor = vbBlue
ComboBox1.ListIndex = 0
Me.OptionButton1.value = True
row = 25
End Sub
Private Sub ComboBox1_Click()
Dim x
Select Case ComboBox1.Text
Case “Physical Memory Properties”
value = 1
Case “Get Server Info”
value = 2


End Select

End Sub
Private Sub CommandButton1_Click()

If OptionButton1.value = True Then

Select Case value
Case 1
Call phy_mem_prop
Case 2
Call GetServerInfo


End Select
Else
If OptionButton2.value = True Then

Select Case value
Case 1
Call phy_mem_prop_csv
Case 2
Call GetServerInfo_csv


End Select
End If

End If
End Sub

Private Sub phy_mem_prop()
On Error Resume Next
Dim strComputer, i, objWMIService, strMemory, colItems
Dim strCapacity, objItem, installedModules, totalSlots
Dim strCapacityGB
Dim r As Range
Dim arrstring
Dim slogFile, objFs, objFile
Dim col
row = row + 3

arrstring = Split(servername, “,”)
For Each strComputer In arrstring
i = 1
Application.StatusBar = “Working…”
UserForm1.TextBox5.Font.Italic = True
UserForm1.TextBox5.Font.Bold = False
UserForm1.TextBox5.Font.Size = 10
UserForm1.TextBox5 = “Working…”

Set objWMIService = GetObject(“winmgmts:\\” & strComputer & “\root\cimv2”)
Set colItems = objWMIService.ExecQuery(“Select * from Win32_PhysicalMemory”)

For Each objItem In colItems
strCapacity = objItem.Capacity
If strMemory <> “” Then strMemory = strMemory & vbCrLf
strMemory = strMemory & “Bank” & i & ” : ” & (objItem.Capacity / 1048576) & ” Mb”
i = i + 1
Next
installedModules = i – 1

Set colItems = objWMIService.ExecQuery(“Select * from Win32_PhysicalMemoryArray”)
For Each objItem In colItems
totalSlots = objItem.MemoryDevices
strCapacity = (objItem.MaxCapacity / 1024)
strCapacityGB = strCapacity / 1024
Next
‘MsgBox “Total Slots: ” & totalSlots & vbCrLf & _
“Free Slots: ” & (totalSlots – installedModules) & vbCrLf & _
vbCrLf & “Installed Modules:” & vbCrLf & strMemory & vbCrLf & vbCrLf & _
“Maximum Capacity for ” & strComputer & “: ” & strCapacityGB & ” GB”, vbOKOnly + vbInformation, “PC Memory Information”

Sheet1.Cells(row, 1).Font.Bold = True
Cells(row, 1) = “Physical Memory Properties”
row = row + 1

For col = 1 To 5
Sheet1.Cells(row, col).Interior.Color = vbCyan
Sheet1.Cells(row, col).Font.Bold = True
Next

Cells(row, 1) = “Computer Name: ”
Cells(row, 2) = “Total Slots”
Cells(row, 3) = “Free Slots”
Cells(row, 4) = “Installed Modules”
Cells(row, 5) = “Maximum Capacity for”
row = row + 1
Cells(row, 1) = strComputer
Cells(row, 2) = totalSlots
Cells(row, 3) = totalSlots – installedModules
Cells(row, 4) = strMemory
Cells(row, 5) = strCapacityGB
Next
UserForm1.TextBox5.Font.Italic = False
UserForm1.TextBox5 = “Done.”
Application.StatusBar = “Done.”
Application.StatusBar = False
End Sub

Private Sub phy_mem_prop_csv()
On Error Resume Next
Dim arrstring
Dim strComputer, i, objWMIService, strMemory, colItems
Dim strCapacity, objItem, installedModules, totalSlots
Dim strCapacityGB
Const FOR_APPEND = 8
Dim slogFile
Dim objFs, objFile
arrstring = Split(servername, “,”)
For Each strComputer In arrstring
i = 1

Application.StatusBar = “Working…”
UserForm1.TextBox5.Font.Italic = True
UserForm1.TextBox5.Font.Bold = False
UserForm1.TextBox5.Font.Size = 10
UserForm1.TextBox5 = “Working…”

Set objWMIService = GetObject(“winmgmts:\\” & strComputer & “\root\cimv2”)
Set colItems = objWMIService.ExecQuery(“Select * from Win32_PhysicalMemory”)
For Each objItem In colItems
strCapacity = objItem.Capacity
If strMemory <> “” Then strMemory = strMemory & vbCrLf
strMemory = strMemory & “Bank” & i & ” : ” & (objItem.Capacity / 1048576) & ” Mb”
i = i + 1
Next
installedModules = i – 1

Set colItems = objWMIService.ExecQuery(“Select * from Win32_PhysicalMemoryArray”)

For Each objItem In colItems
totalSlots = objItem.MemoryDevices
strCapacity = (objItem.MaxCapacity / 1024)
strCapacityGB = strCapacity / 1024
Next

slogFile = “logfile.txt”
Set objFs = CreateObject(“scripting.FileSystemObject”)
Set objFile = objFs.OpenTextFile(slogFile, FOR_APPEND, True)
objFile.writeline
objFile.writeline
objFile.writeline
objFile.writeline
objFile.writeline

objFile.writeline “Physical Memory Properties”
objFile.writeline “Total slot = ” & totalSlots & _
“Free Slots = ” & totalSlots – installedModules & _
“Installed Modules = ” & strMemory + _
“Max capacity = ” & strCapacityGB

objFile.Close
Set objFile = Nothing
Set objFs = Nothing
Next

UserForm1.TextBox5.Font.Italic = False
UserForm1.TextBox5 = “Done.”
UserForm1.TextBox5 = “Output in logfile.txt”
Application.StatusBar = “Done.”
Application.StatusBar = False
End Sub
Sub GetServerInfo()
On Error Resume Next

Dim r As Range, i As Integer, N As Integer
Dim arrstring
Dim strComputer, colDisks, objDisk, objWMIService
Dim col
row = row + 3
Application.StatusBar = “Working…”
UserForm1.TextBox5.Font.Italic = True
UserForm1.TextBox5.Font.Bold = False
UserForm1.TextBox5.Font.Size = 10
UserForm1.TextBox5 = “Working…”

arrstring = Split(servername, “,”)
For Each strComputer In arrstring
Worksheets(“sheet1”).Activate
Set objWMIService = GetObject _
(“winmgmts:\\” & strComputer & “\root\cimv2”)
Set colDisks = objWMIService.ExecQuery _
(“Select * From Win32_LogicalDisk”)

Sheet1.Cells(row, 1).Font.Bold = True
Cells(row, 1) = “Server Information”
row = row + 1

For col = 1 To 4
Sheet1.Cells(row, col).Interior.Color = vbCyan
Sheet1.Cells(row, col).Font.Bold = True
Next
Cells(row, 1) = “Computer Name: ”
Cells(row, 2) = “Disk”
Cells(row, 3) = “Free Space”
Cells(row, 4) = “Total Size”
row = row + 1
Cells(row, 1) = strComputer
For Each objDisk In colDisks
Cells(row, 2) = objDisk.DeviceID
If objDisk.FreeSpace < 1073741824 Then
Cells(row, 3) = objDisk.FreeSpace / 1024 / 1024
Else

Cells(row, 3) = objDisk.FreeSpace / 1024 / 1024
End If
Cells(row, 4) = objDisk.Size / 1024 / 1024
row = row + 1
Next
Next
UserForm1.TextBox5.Font.Italic = False
UserForm1.TextBox5 = “Done.”
Application.StatusBar = “Done.”
Application.StatusBar = False
End Sub

Sub GetServerInfo_csv()
On Error Resume Next

Dim arrstring
Dim strComputer, colDisks, objDisk, objWMIService
Dim slogFile
Dim objFs, objFile
Const FOR_APPEND = 8
arrstring = Split(servername, “,”)
For Each strComputer In arrstring
Application.StatusBar = “Working…”
UserForm1.TextBox5.Font.Italic = True
UserForm1.TextBox5.Font.Bold = False
UserForm1.TextBox5.Font.Size = 10
UserForm1.TextBox5 = “Working…”
Set objWMIService = GetObject _
(“winmgmts:\\” & strComputer & “\root\cimv2”)
Set colDisks = objWMIService.ExecQuery _
(“Select * From Win32_LogicalDisk”)
slogFile = “logfile.txt”
Set objFs = CreateObject(“scripting.FileSystemObject”)
Set objFile = objFs.OpenTextFile(slogFile, FOR_APPEND, True)
objFile.writeline
objFile.writeline
objFile.writeline
objFile.writeline
objFile.writeline
objFile.writeline “Server Information”
objFile.writeline “Computer Name: ,Disk, Free Space, Total Size”
objFile.write strComputer & “,”
For Each objDisk In colDisks
objFile.write objDisk.DeviceID & “,”
If objDisk.FreeSpace < 1073741824 Then
objFile.write objDisk.FreeSpace / 1024 / 1024 & “,”
Else

objFile.write objDisk.FreeSpace / 1024 / 1024 & “,”
End If
objFile.writeline objDisk.Size / 1024 / 1024 & “,”

Next
Next
objFile.Close
Set objFile = Nothing
Set objFs = Nothing

UserForm1.TextBox5.Font.Italic = False
UserForm1.TextBox5 = “Done.”
UserForm1.TextBox5 = “Output in logfile.txt”
Application.StatusBar = “Done.”
Application.StatusBar = False

End Sub

Sub GetService()
On Error Resume Next
Dim strstring
Dim r As Range, i As Integer, N As Integer
Dim col
Dim arrstring
Dim strComputer, colWMIThings, objItem, objWMIService
row = row + 4
Application.StatusBar = “Working…”
UserForm1.TextBox5.Font.Italic = True
UserForm1.TextBox5.Font.Bold = False
UserForm1.TextBox5.Font.Size = 10
UserForm1.TextBox5 = “Working…”
arrstring = Split(servername, “,”)
For Each strComputer In arrstring
‘MsgBox (servername)
Worksheets(“sheet1”).Activate
Set objWMIService = GetObject(“winmgmts:\\” & strComputer & “\root\cimv2”)
Set colWMIThings = _
objWMIService.ExecQuery(“SELECT * FROM Win32_service”)
Sheet1.Cells(row, 1).Font.Bold = True
Cells(row, 1) = “Services”
row = row + 1
For col = 1 To 4
Sheet1.Cells(row, col).Interior.Color = vbCyan
Sheet1.Cells(row, col).Font.Bold = True
Next
Cells(row, 1) = “Computer Name: ”
Cells(row, 2) = “Service name”
Cells(row, 3) = “Status”
Cells(row, 4) = “Strtup Mode”
row = row + 1
Cells(row, 1) = strComputer
For Each objItem In colWMIThings
If objItem.State = “Stopped” And objItem.StartMode = “Auto” Then
Cells(row, 2) = objItem.DisplayName
Else
Cells(row, 2) = objItem.DisplayName
End If
Cells(row, 3) = objItem.State
Cells(row, 4) = objItem.StartMode
row = row + 1
Next
Next
UserForm1.TextBox5.Font.Italic = False
UserForm1.TextBox5 = “Done.”
Application.StatusBar = “Done.”
Application.StatusBar = False
End Sub

Related posts
1. Stir fry a VBA application quickly
2.Building a respectable VBA with Excel application
3. Get your feet wet with Powershell GUI
4. Powershell GUI – Adding bells and whistles
5. Slicing and dicing with LogParser & VBA
6. Adventures in LogParser, HTA and charts.

Also see
Brewing a potion with Bluemix, PostgreSQL, Node.js in the cloud
A Bluemix recipe with MongoDB and Node.js A Cloud medley with IBM Bluemix, Cloudant DB and Node.js
– A crime map of India in R: Crimes against women
– What’s up Watson? Using IBM Watson’s QAAPI with Bluemix, NodeExpress – Part 1
– Bend it like Bluemix, MongoDB with autoscaling – Part 1
– Analyzing cricket’s batting legends – Through the mirage with R
– Masters of spin: Unraveling the web with R

Find me on Google+

Stir fry a VBA with Excel application quickly

This is bound to bring a sense of deja-vu to you. How often have you come across a situation where your boss comes all excited about a new idea? So he says

Boss: “I have a new idea. Can you quickly come up with a prototype?”
You: “Sure” As you say this your mind is quickly assessing various tools, IDEs, languages. You are wondering whether you should go with Java or Ruby on Rails, Python-Django etc.

Then your boss drops the bombshell

Boss: “And by the way I need the Proof of Concept (PoC) yesterday!”
You are deflated as you try to pick your crumpled physical remains from the floor.

For all these situations VBA with Excel is good choice to quickly put a prototype together. If you know any other language VBscript should be a breeze. In fact this is a very useful skill to know whether you are a seasoned programmer, a marketing or sales veteran or a novice programmer. VBA is quite useful for prototyping applications with a fairly simple and straightforward GUI.

You could be building a prototype to dimension a Core Network – determining the number of SS7 links, the traffic on various links or you may want to prepare a rudimentary tax calculator. You may want to process the sales in a quarter and display it in a pretty way. For many purposes VBA fits the bill quite well particularly when you need to  hit the road right way.

Here is a highly condensed version of VBscript

Variables: Declared/defined with Dim sValue. There is no explicit typing
Global Variables: Add the Dim aValue at the top.
Branching:

If cond1 then  Else if cond2 Else Endif.
Select case var1 case “a” case “b” End Select

There is also the Go To
Loops:

Do {while|until} condition statements Loop
Do statementsLoop{while|until} condition

For I = 1 to 10 step 2 statement Next
For each element in group statements Next
Procedure: Sub proc (a,b) statements End Sub. Procedure called with Call proc(x,y)
Function: Function test (a,b) statements End function. Invoked with test(x,y)
Output: MsgBox “Hello world”

You could write to Excel sheet with
Cells (3, 1) = value where row 3, column 1 would be populated with value
Writing to File:
slogfile = “logfile.txt”
Set objFs = CreateObject(“scripting.FileSystemObject”)
Set objFile = objFs.CreateTextFile(slogfile)
objFile.writeLine “Total slot = ” & totalSlots
objFile.Close

With this you should be good to get started on some basic application.
Create a new Excel sheet. Click Tools->Macro->Visual basic Editor. Then click Insert->userform
You should see something like this

Assume that you want to include some VBscripts to perform some common tasks that you often do.
You could add components from the VB Toolbox. I created something like this.

When you click on the component it will take you to the code where you can write the procedure you want.
To populate a combo box you will have to add the following code for e.g.

Private Sub UserForm_Activate()
With ComboBox1
ComboBox1.AddItem “Physical Memory Properties”
ComboBox1.AddItem “Enumerate Port”
ComboBox1.AddItem “Basic Computer Information”
ComboBox1.AddItem “Inventory Information”
End With
End Sub

When the 1st item is clicked it will call the phy_sys_prop procedure
Private Sub ComboBox1_Click()
Dim x
Select Case ComboBox1.Text
Case “Physical Memory Properties”
Call phy_mem_prop
End Select

We can have multiple forms/tabs as shown with radio-buttons, text boxes, spin buttons, list boxes etc.
To execute the code click the green > at the top

This is what the output will look like. It also populates the Excel sheet.. This code was taken from Microsoft’s Technet Script Center Repository

VBA with Excel is definitely useful to know.
The code for the form is shown below
Private Sub UserForm_Activate()
With ComboBox1
ComboBox1.AddItem “Physical Memory Properties”
ComboBox1.AddItem “Enumerate Port”
ComboBox1.AddItem “Basic Computer Information”
ComboBox1.AddItem “Inventory Information”
End With
End Sub

Private Sub phy_mem_prop()
Dim strComputer, i, objWMIService, strMemory, colItems
Dim strCapacity, objItem, installedModules, totalSlots
Dim strCapacityGB
Dim r As Range
Set r = Range(“A2”)
strComputer = InputBox(“Enter PC Name or IP:”, “PC Name”)
strMemory = “”
i = 1

Set objWMIService = GetObject(“winmgmts:\\” & strComputer & “\root\cimv2”)
Set colItems = objWMIService.ExecQuery(“Select * from Win32_PhysicalMemory”)
For Each objItem In colItems
strCapacity = objItem.Capacity
If strMemory <> “” Then strMemory = strMemory & vbCrLf
strMemory = strMemory & “Bank” & i & ” : ” & (objItem.Capacity / 1048576) & ” Mb”
i = i + 1
Next
installedModules = i – 1

Set colItems = objWMIService.ExecQuery(“Select * from Win32_PhysicalMemoryArray”)
For Each objItem In colItems
totalSlots = objItem.MemoryDevices
strCapacity = (objItem.MaxCapacity / 1024)
strCapacityGB = strCapacity / 1024
Next
MsgBox “Total Slots: ” & totalSlots & vbCrLf & _
“Free Slots: ” & (totalSlots – installedModules) & vbCrLf & _
vbCrLf & “Installed Modules:” & vbCrLf & strMemory & vbCrLf & vbCrLf & _
“Maximum Capacity for ” & strComputer & “: ” & strCapacityGB & ” GB”, vbOKOnly + vbInformation, “PC Memory Information”
Cells(2, 1) = “Total Slots”
Cells(2, 2) = “Free Slots”
Cells(2, 3) = “Installed Modules”
Cells(2, 4) = “Maximum Capacity for”
Cells(3, 1) = totalSlots
Cells(3, 2) = totalSlots – installedModules
Cells(3, 3) = strMemory
Cells(3, 4) = strCapacityGB
slogfile = “logfile.txt”
Set objFs = CreateObject(“scripting.FileSystemObject”)
Set objFile = objFs.CreateTextFile(slogfile)
objFile.writeLine “Total slot = ” & totalSlots & _
“Free Slots = ” & totalSlots – installedModules & _
“Installed Modules = ” & strMemory + _
“Max capacity = ” & strCapacityGB
objFile.Close
Set objFile = Nothing
Set objFs = Nothing
End Sub

Private Sub ComboBox1_Click()
Dim x
Select Case ComboBox1.Text
Case “Physical Memory Properties”
Call phy_mem_prop
End Select
End Sub

Related posts
1. Stir fry a VBA application quickly
2.Building a respectable VBA with Excel application
3. Get your feet wet with Powershell GUI
4. Powershell GUI – Adding bells and whistles
5. Slicing and dicing with LogParser & VBA
6. Adventures in LogParser, HTA and charts.

Also see
Brewing a potion with Bluemix, PostgreSQL, Node.js in the cloud
A Bluemix recipe with MongoDB and Node.js A Cloud medley with IBM Bluemix, Cloudant DB and Node.js
– A crime map of India in R: Crimes against women
– What’s up Watson? Using IBM Watson’s QAAPI with Bluemix, NodeExpress – Part 1
– Bend it like Bluemix, MongoDB with autoscaling – Part 1
– Analyzing cricket’s batting legends – Through the mirage with R
– Masters of spin: Unraveling the web with R

Find me on Google+