Outlook and meeting reminders

I do not like the fact that the person sending a meeting request is the one deciding how long before the meeting a reminder would be set.

Since I don’t like the popup on my phone, I’m not using reminders.

So to get rid of incoming reminders I wrote a small script.

Press ALT+F11 and paste this code:

Sub snwRemoveMeetingReminder(Item As Outlook.MeetingItem)
    If TypeOf Item Is Outlook.MeetingItem Then
        Item.ReminderSet = False
        Item.Save

        Set Appt = Item.GetAssociatedAppointment(True)
        If Not Appt Is Nothing Then
            Appt.ReminderSet = False
            Appt.Save
        End If
    End If
End Sub

Then add the the script to incoming meeting requests.
090927_outlook_rule

Now the script will remove reminders on every incoming meeting request… It’s a client side rule, so you need to have Outlook running to get it to work.


Monitor connected consoles

A small and simple script to monitor number of connected SCOM-consoles.

Set oLocator = CreateObject("WbemScripting.SWbemLocator")
Set oWmi = oLocator.ConnectServer(".", "root/snmp/localhost", "")
Set oStats = oWmi.ExecQuery("select * from SNMP_RFC1213_MIB_tcpConnTable where tcpConnLocalPort = 5724 AND tcpConnLocalAddress <> '0.0.0.0' AND tcpConnLocalAddress <> '127.0.0.1'")

Set oAPI = CreateObject("MOM.ScriptAPI")
Set oBag = oAPI.CreatePropertyBag()
oBag.AddValue "ConnectedConsoles", oStats.Count
oAPI.AddItem(oBag)
oAPI.ReturnItems

SCCM Console Extensions – Parameters

OK, so now you know the GUID for the right-click tool… but what about passing parameters?

There are a few standard SUB’s (parameters) that you can use, some are listed in this post: https://snowland.se/2008/05/28/sccm-console-extensions/

But if you take the example of GUID 5fb29b42-5d11-4642-a6c9-24881a7d317e that you can find under Software Distribution Packages / Packages / Some package / Package Status / Site Server / Right click on a distribution point

Say that you want to pass the server-name or the path to the package…

First off, open the E:\Program Files\Microsoft Configuration Manager\AdminUI\XmlStorage\ConsoleRoot\AdminConsole.xml in some editor.

Then search for the GUID and you will find something like this.


  
    
      
        
          
            SMS_PackageStatusDetailSummarizer
          
          SELECT * FROM SMS_PackageStatusDistPointsSummarizer WHERE PackageID='##SUB:PackageID##' AND SiteCode='##SUB:SiteCode##'
          SMS_PackageStatusDistPointsSummarizer
        
      
    
  

A few lines below the GUID you find SELECT * FROM SMS_PackageStatusDistPointsSummarizer WHERE Packa… Copy that line and replace/clean it up so that it is a valid WMI-query.
Will look something like:

SELECT * FROM SMS_PackageStatusDistPointsSummarizer WHERE PackageID='XYZ00123' AND SiteCode='XYZ'

Next step is to start some WMI-browser and connect to root\SMS\site_XYZ and run the query and take a look at the columns.
(I like to use WMI Explorer)

In the query above you will have columns like ServerNALPath, SourceNALPath, SourceVersion this is what you are looking for. :-)

Use them in your extensions like this:


        myScript.vbs
        ##SUB:ServerNALPath## ##SUB:SourceNALPath## ##SUB:SourceVersion##


SCCM Console Extensions – Find the GUID

I wrote some about this topic in a post a while ago… did some more scripting around this today.

This VBScript will read the AdminConsole.xml and look for NameSpaceGuid’s, when it find one it will create a subdirectory (from where it is started) with the GUID and after that it will create a XML-file within that directory.
The XML-file then points to an VBS-file with a couple of parameters. (Look further down for an example of a nice VBScript to use)

Tip: Backup AdminUI\XmlStorage\Extensions\Actions before you start to play around with this.

Const cVbsFile = "testExtension.vbs" ' The file to call on right-click
Const cHKEY_LOCAL_MACHINE = &H80000002
Set oReg=GetObject("winmgmts:{impersonationLevel=impersonate}!\\.\root\default:StdRegProv")
oReg.GetStringValue cHKEY_LOCAL_MACHINE,"SOFTWARE\Microsoft\ConfigMgr\Setup", "UI Installation Directory", sSccmPath
Set oReg = Nothing

sSourcePath = Replace(WScript.ScriptFullName, WScript.ScriptName, "")

Set oShell = CreateObject("WScript.Shell")
Set oFso = CreateObject("Scripting.FileSystemObject")
Set oFile = oFso.OpenTextFile(sSccmPath & "\XmlStorage\ConsoleRoot\AdminConsole.xml", 1)
Do While oFile.AtEndOfStream <> True
    sText = Trim(uCase(oFile.ReadLine))
    If InStr(sText, "NAMESPACEGUID=") Then

                ' Read the GUID from NameSpaceGuid param
                sGuid = sText
                sGuid = Right(sGuid, Len(sGuid) - InStr(sGuid, "NAMESPACEGUID=") - 14)
                sGuid = Left(sGuid, InStr(sGuid, """")-1)

                if not oFso.FolderExists(sSourcePath & sGuid) Then
                        WScript.Echo sSourcePath & sGuid

                        ' Create the GUID folder
                        oFso.CreateFolder sSourcePath & sGuid

                        ' Create the XML-file with current Guid, Name & ResourceID as parameter to source-VBScript
                        Set oXmlFile = oFso.CreateTextFile(oShell.ExpandEnvironmentStrings("%TEMP%\snowland-guid-locator.xml"), True)
                        oXmlFile.WriteLine ""
                        oXmlFile.WriteLine ""
                        oXmlFile.WriteLine "" & sSourcePath & cVbsFile & ""
                        oXmlFile.WriteLine "" & sGuid & " ##Sub:Name## ##Sub:ResourceID## ##SUB:ItemName## ##SUB:NetworkOSPath## ##SUB:value##"
                        oXmlFile.WriteLine ""
                        oXmlFile.WriteLine ""
                        oXmlFile.Close

                        ' Copy XML to GUID-directory with name "snowland-GUID.xml" as name
                        oFso.CopyFile oShell.ExpandEnvironmentStrings("%TEMP%\snowland-guid-locator.xml"), sSourcePath & sGuid & "\snowland-" & sGuid & ".xml"
                End if
        End If
Loop
oFile.Close

So… when you restarted the console you will se GUID’s showing up. To get those GUID’s to the clipboard use a testExtension.vbs like this

Set oFso = CreateObject("Scripting.FileSystemObject")
Set oShell = CreateObject("WScript.Shell")

' Create a temporary file
Set oFile = oFso.CreateTextFile(oShell.ExpandEnvironmentStrings("%TEMP%\sccmXmlReader.tmp"), True)

' Loop thru arguments
For i = 0 to WScript.Arguments.Count-1
        sOut = sOut & Wscript.Arguments(i) & VbCrLf
        ' Write to file
        oFile.WriteLine Wscript.Arguments(i)
Next
' Close the file
oFile.Close

' Type the file to the clipboard
oShell.Run oShell.ExpandEnvironmentStrings("%SystemRoot%\System32\cmd.exe /c type %TEMP%\sccmXmlReader.tmp | %SystemRoot%\System32\clip.exe"), 1, True

' Delete the file
oFso.DeleteFile oShell.ExpandEnvironmentStrings("%TEMP%\sccmXmlReader.tmp"), True

' Send a message to the user
MsgBox sOut, vbOKOnly, "Copied to clipboard"

Will try to do a post about how to find the SUB’s…


Outlook inbox cleaner

I like to keep my inbox clean… so every now and then I sort out mails to different folders. That is boooring.

So I wrote a little script. :-)

Sub InboxCleaner()
    Dim oNamespace As Outlook.NameSpace
    Dim oInboxFolder As Outlook.MAPIFolder
    Dim oDestFolder As Outlook.MAPIFolder
    Dim oItem As Object
    Dim i, iMove, iNoMove As Integer
    Dim sMsg, sFolder As String
    Dim bDoMove As Boolean

    Set oNamespace = Application.GetNamespace("MAPI")
    Set oInboxFolder = oNamespace.GetDefaultFolder(olFolderInbox)

    sMsg = ""
    iNoMove = 0
    iMove = 0

    For i = oInboxFolder.Items.Count To 1 Step -1
        Set oItem = oInboxFolder.Items(i)

        If InStr(oItem.SenderEmailAddress, "@") <> 0 Then
            sFolder = oItem.SenderEmailAddress ' Get sender address
            sFolder = Right(sFolder, Len(sFolder) - InStrRev(sFolder, "@")) ' Only domain name
            sFolder = Left(sFolder, InStr(sFolder, ".") - 1) ' Skip everything after the first dot
            sFolder = UCase(Left(sFolder, 1)) & Right(sFolder, Len(sFolder) - 1) ' Upper case first letter

            On Error Resume Next
            ' This row you might want to customize... I have a folders like  Mailbox\Customers\TheCustomerName
            Set oDestFolder = oInboxFolder.Folders.Parent.Parent.Folders("Customers").Folders(sFolder)

            If Err.Number <> 0 Then
                sMsg = sMsg & "Missing folder: " & vbTab & oItem.SenderEmailAddress & "  (" & sFolder & ")" & vbCrLf
                Set oDestFolder = Nothing
                Err.Clear
                bDoMove = False
                iNoMove = iNoMove + 1
            Else
                sMsg = sMsg & "Move:           " & vbTab & oItem.SenderEmailAddress & " -> " & sFolder & vbCrLf
                bDoMove = True
                iMove = iMove + 1
            End If
            On Error GoTo 0

            If bDoMove Then
                ' Comment out this line if you only want to test
                oItem.Move oDestFolder
            End If
        End If
    Next

    sMsg = sMsg & vbCrLf & _
        vbCrLf & _
        "Processed " & oInboxFolder.Items.Count & " items in inbox..." & vbCrLf & _
        "Moved:          " & vbTab & iMove & vbCrLf & _
        "Missing folder: " & vbTab & iNoMove & vbCrLf & _
        "Skipped:        " & vbTab & (oInboxFolder.Items.Count - (iMove + iNoMove))

    MsgBox sMsg, vbOKOnly, "Inbox Cleaner / Rikard Ronnkvist / snowland.se"

End Sub

Download: inboxcleaner.vbs

Update: Screendump of the result.
090323_inboxcleaner


Bulk update commandlines in SCCM-programs

Just a small script to update the commandline of a large number of programs in SCCM.

This script will change from “/q” to “/qb!”…

Set oLocator = CreateObject("WbemScripting.SWbemLocator")
Set oSccmWmi = oLocator.ConnectServer(".", "root\sms\site_C01", "", "")

Set oPrograms = oSccmWmi.ExecQuery("select * from SMS_Program where CommandLine LIKE '%msiexec%/q %'")

For Each oProgram In oPrograms
        WScript.Echo "Package: " & oProgram.PackageID & "  (" & oProgram.ProgramName & ")"
        WScript.Echo "Orginal: " & oProgram.CommandLine

        sNewCmd = Replace(oProgram.CommandLine, "/q", "/qb!")
        WScript.Echo "    New: " & sNewCmd

        Set oModProgram = oSccmWmi.Get("SMS_Program.PackageID='" & oProgram.PackageID & "'" & ",ProgramName='" & oProgram.ProgramName & "'")
        oModProgram.CommandLine = sNewCmd
        oModProgram.Put_ ' Comment out this line if you want to test
        Set oModProgram = Nothing
Next

Trigger SCCM-client actions

If you need to trigger some SCCM-client actions via a script, this is a easy way to do it.

This script will trigger actions with “Request & Evaluate” in the name.

Option Explicit
Dim oCpApplet, oActions, oAction

On Error Resume Next
Set oCpApplet = CreateObject("CPAPPLET.CPAppletMgr")
If Err.Number <> 0 Then
    WScript.Echo "Missing SCCM-client"
    Err.Clear
Else
    WScript.Echo "Found following actions:"
    Set oActions = oCpApplet.GetClientActions
    For Each oAction In oActions
        If Instr(lCase(oAction.Name),"request & evaluate") Then
            WScript.Echo "  " & oAction.Name & " - Starting"
            oAction.PerformAction
        Else
            WScript.Echo "  " & oAction.Name
        End If
    Next
End If

Change Collection Refresh Rate

Had some problems with loads of collection refresh taking all of the CPU on the SCCM-server.

So first, to get the SCCM-server to calm down I wrote a small (and somewhat ugly, since it uses SQL) hack:

UPDATE Collections
Set Flags = 17
Where CollectionName LIKE '%Something In The Collection Name%'
AND Flags=18

This script uncheck the box “Update his collection on a schedule” for the collections.

Then, when the SCCM server did go back to a normal CPU-utilization we used this script to set another refresh-rate on the collections.

Const cSccmProvider = "."
Const cWmiUsername = ""
Const cWmiPassword = ""

Const cCollectionNamePattern = "%Something In The Collection Name%"
Const cDoUpdate = True          ' Set to false to test
Const cRefreshDays = 0          ' 0 - 31
Const cRefreshHours = 12        ' 0 - 23
Const cRefreshMinutes = 0       ' 0-59

Set oLocator = CreateObject("WbemScripting.SWbemLocator")

' --- Get SCCM Site Code
WScript.Echo "Connecting to: " & cSccmProvider
Set oSccmWmi = oLocator.ConnectServer(cSccmProvider, "root\sms", cWmiUsername, cWmiPassword)
Set oWmiQuery = oSccmWmi.ExecQuery("SELECT SiteCode FROM SMS_ProviderLocation WHERE ProviderForLocalSite=true")
For each currentSite in oWmiQuery
        sSccmSiteCode = currentSite.SiteCode
        Exit For
Next

' --- Connect to site
WScript.Echo "Connecting to: " & cSccmProvider &  " - root\sms\site_" & sSccmSiteCode
Set oSccmWmi = oLocator.ConnectServer(cSccmProvider, "root\sms\site_" & sSccmSiteCode, cWmiUsername, cWmiPassword)

' --- Create interval
WScript.Echo "Creating Interval: " & cRefreshDays & " days, " & cRefreshHours & " hours, " & cRefreshMinutes & " minutes."
Set oInterval = oSccmWmi.Get("SMS_ST_RecurInterval")
oInterval.DaySpan = cRefreshDays
oInterval.HourSpan = cRefreshHours
oInterval.MinuteSpan = cRefreshMinutes
oInterval.isGmt = False
oInterval.StartTime = "20090101000000.000000+***"

' --- List all collection
set oCollections = oSccmWmi.ExecQuery("SELECT * FROM SMS_Collection WHERE Name LIKE '" & cCollectionNamePattern & "'")
For Each oCollection In oCollections
        ' --- Update interval on Collection
        If cDoUpdate Then
                WScript.Echo "Updating: " & oCollection.CollectionID & " - " & oCollection.Name
                Set oCollectionToChange = oSccmWmi.Get("SMS_Collection.CollectionID='"  & oCollection.CollectionID & "'")
                oCollectionToChange .RefreshSchedule = Array(oInterval)
                oCollectionToChange .RefreshType = 2  '1 = Manual, 2 = Periodic refresh
                oCollectionToChange .Put_
        Else
                WScript.Echo "Testing: " & oCollection.CollectionID & " - " & oCollection.Name
        End if
Next

The script is attached here: changeCollectionRefresh.vbs


Semiautomatic deletion/creation/whatever

Ok.. you need to automate a klick-klick-klick-procedure… SendKeys can do the trick.

A big warning: This might be dangerous, if the script goes berserk… it might do whatever deletion/creation/manipulation in the wrong area…

Set oShell = CreateObject("WScript.Shell")

oShell.AppActivate "Configuration Manager Console"
WScript.Sleep 500

For i = 1 To 10
        oShell.SendKeys "{DOWN}"
        WScript.Sleep 250
        oShell.SendKeys "{DELETE}"
        WScript.Sleep 250
        oShell.SendKeys "{ENTER}"

        WScript.Sleep 2000
Next
MsgBox "Done!"

Check WMI on SCCM-server

If you have problems with WMI on a SCCM server you have will have loads of strange things happening.

Wrote a small VBScript to check WMI… here it is:

Set oLocator = CreateObject("WbemScripting.SWbemLocator")

' --- Checking local WMI
WScript.Echo " Connect: root\CIMV2"
Set oWMIService = oLocator.ConnectServer(".", "root\CIMV2", "", "")

WScript.Echo "   Query: Select UUID from Win32_ComputerSystemProduct"
Set oWmiQuery = oWMIService.ExecQuery("Select UUID from Win32_ComputerSystemProduct")
For Each oUuid In oWmiQuery
        sUuid = oUuid.UUID
        WScript.Echo "Response: " & sUuid
        Exit For
Next
WScript.Echo ""

' --- Figure out site code
WScript.Echo " Connect: root\sms"
Set oWMIService = oLocator.ConnectServer(".", "root\sms", "", "")

WScript.Echo "   Query: SELECT SiteCode FROM SMS_ProviderLocation WHERE ProviderForLocalSite=true"
Set oWmiQuery = oWMIService.ExecQuery("SELECT SiteCode FROM SMS_ProviderLocation WHERE ProviderForLocalSite=true")
For each currentSite in oWmiQuery
        sSccmSiteCode = currentSite.SiteCode
        WScript.Echo "Response: " & sSccmSiteCode
        Exit For
Next
WScript.Echo ""

' --- Connect to site
WScript.Echo " Connect: root\sms\site_" & sSccmSiteCode
Set oWMIService = oLocator.ConnectServer(".", "root\sms\site_" & sSccmSiteCode, "", "")

WScript.Echo "   Query: Select Name, ResourceID FROM SMS_R_System WHERE SmbiosGuid = '" & sUuid & "'"
Set oWmiQuery = oWMIService.ExecQuery("Select ResourceID FROM SMS_R_System WHERE SmbiosGuid = '" & sUuid & "'")
For each myMachine in oWmiQuery
        WScript.Echo "Response: " & myMachine.ResourceID
        Exit For
Next

Or download here: wmiTester.vbs


Next Page »