tecoxe | J'ai fais ça il y a un petit moment, c'est en place sur plusieurs serveurs avec une tache planifiée et ça fonctionne bien. Ca ne sert pas que pour l'espace disque mais tu peux activer/désactiver les controles au besoin. Code :
- 'Derniére modification le 03.17.2006 11:00
- '################################################
- 'Constantes pour le réglage des alarmes
- '################################################
- Const LimiteLecteurSysteme = 0.1 'décimales
- Const LimiteLecteurAutre = 0.05 'décimales
- Const LimiteUtilisationCpu = 0.8 'décimales
- Const LimiteMemoireDisponible = 800 'en Mo
- Const FichierDeSortie = "c:\Wmi_SysInfo.txt"
- Const AdresseEmailDestinataire = ""
- Const AdresseServeurSmtp = ""
- Const ConsoleDebug = 1
- Const EnvoyerUnMail = 1
- Const NomDeMachine = "." 'Mettre un . pour la machine locale
- Const SurveilleCpu = 1
- Const SurveilleDisk = 1
- Const SurveilleMemoire = 1
- Const AfficherUptime = 0
- '################################################
- 'Déclarations
- Const ForAppending = 8
- Const cdoSendUsingPort = 2
- Dim fso, f1, OutputLine, HtmlBody, Alarme
- Set SC = New SpaceChecker
- Set SC = Nothing
- Alarme = 0
- Class SpaceChecker
- Private Sub Class_Initialize()
- Set WMIService = GetObject("winmgmts:{impersonationLevel=impersonate}!\\" & NomDeMachine & "\root\cimv2" )
- Set colSettings = WMIService.ExecQuery ("Select * from Win32_ComputerSystem" )
- For Each objComputer in colSettings
- SystemName = objComputer.Name
- Domain = objComputer.Domain
- Next
- Set colSettings = Nothing
- Set fso = CreateObject("Scripting.FileSystemObject" )
- 'Set f1 = fso.CreateTextFile(FichierDeSortie, false)
- 'f1.close
- Set f1 = fso.OpenTextFile(FichierDeSortie & "." & SystemName, ForAppending, true,0)
- HtmlBody = "<HTML>"
- HtmlBody = HtmlBody & "<HEAD>"
- HtmlBody = HtmlBody & "<BODY>"
- HtmlBody = HtmlBody & "<b>" & date & "@" & time & "</b></br></br>"
- If AfficherUptime = 1 Then
- HtmlBody = HtmlBody & "<b>Uptime : " & GetUptime & " heures</b></br></br>"
- MyEcho "Uptime : " & GetUptime & " heures"
- End If
- OutputLine = date & "@" & time & "|" & SystemName & "@" & Domain & "|"
- If SurveilleDisk = 1 Then
- Set WMIService = GetObject("winmgmts:{impersonationLevel=impersonate}!\\" & NomDeMachine & "\root\cimv2" )
- Set colDisks = WMIService.ExecQuery("Select * from Win32_LogicalDisk" )
-
- For each Disk in colDisks
- If Disk.DriveType = 3 Then
- If Lcase(Disk.DeviceID) = "c:" Then
- LimiteLecteur = LimiteLecteurSysteme
- Else
- LimiteLecteur = LimiteLecteurAutre
- End If
- If (Disk.FreeSpace/Disk.Size) < LimiteLecteur Then
- HddStatut="Depassement"
- Else
- HddStatut="Normal"
- End If
- MyEcho Disk.DeviceID & "|" & (Disk.FreeSpace/1000000) & "Mo/" & (Disk.Size/1000000) & "Mo|" & HddStatut
- OutputLine = OutputLine & "HDD=" & Disk.DeviceID & "|" & (Disk.FreeSpace/1000000) & "Mo|" & (Disk.Size/1000000) & "Mo|" & HddStatut & "|"
- If HddStatut="Depassement" Then
- HtmlBody = HtmlBody & "<b><font color=red>Lecteur : " & Disk.DeviceID & "</br>Espace libre : " & (Disk.FreeSpace/1000000) & "Mo / " & (Disk.Size/1000000) & "Mo</br>Etat : " & HddStatut & "</b></font></br></br>"
- Alarme = 1
- Else
- HtmlBody = HtmlBody & "<b>Lecteur : " & Disk.DeviceID & "</br>Espace libre : " & (Disk.FreeSpace/1000000) & "Mo / " & (Disk.Size/1000000) & "Mo</br>Etat : " & HddStatut & "</b></br></br>"
- End If
- End If
- Next
- End If
- If SurveilleCpu = 1 Then
- If CPUUtil() > LimiteUtilisationCpu * 100 Then
- CpuStatut="Depassement"
- HtmlBody = HtmlBody & "<font color=red><b>Cpu utilisé : " & CPUUtil() & "%</br>Etat : " & CpuStatut & "</b></font></br></br>"
- Alarme = 0
- Else
- CpuStatut="Normal"
- HtmlBody = HtmlBody & "<b>Cpu utilisé : " & CPUUtil() & "%</br>Etat : " & CpuStatut & "</b></br></br>"
- End If
- MyEcho "CPU=" & CPUUtil() & "%|" & CpuStatut
- OutputLine = OutputLine & "CPU=" & CPUUtil() & "%|" & CpuStatut
- End If
- If SurveilleMemoire = 1 Then
- If GetFreeMem() > LimiteMemoireDisponible Then
- MemStatut = "Depassement"
- HtmlBody = HtmlBody & "<font color=red><b>Mémoire disponible : " & GetFreeMem() & "Mo</br>Etat : " & MemStatut & "</b></font></br>"
- Alarme = 1
- Else
- MemStatut = "Normal"
- HtmlBody = HtmlBody & "<b>Mémoire disponible : " & GetFreeMem() & "Mo</br>Etat : " & MemStatut & "</b></br>"
- End If
- MyEcho "MEM_LIBRE=" & GetFreeMem() & "Mo|" & MemStatut
- OutputLine = OutputLine & "|MEM_LIBRE=" & GetFreeMem() & "Mo|" & MemStatut
- End If
- f1.writeline OutputLine
- f1.close
- If Alarme=1 And EnvoyerUnMail = 1 Then
- MyEcho "Envoi d'un mail !"
- Sendmail()
- Else
- MyEcho "Pas de mail"
- End If
- Set colDisks = Nothing
- Set WMIService = Nothing
- End Sub
- '################################################
- 'Fonctions suplémentaires
- '################################################
- Private Sub Class_Terminate()
- End Sub
- Function MyEcho(pMsg)
- If ConsoleDebug = 1 Then
- Wscript.Echo pMsg
- End If
- End Function
- Function CPUUtil()
- On Error Resume Next
- WQLQuery = "Select deviceid, loadpercentage from Win32_Processor where DeviceID='CPU0'"
- Set WMS = GetObject("winmgmts:\\" & NomDeMachine & "\root\cimv2" )
- Set CPU = WMS.ExecQuery(WQLQuery,,48)
- For Each CPUinfo in CPU
- CPUUtil = CPUinfo.LoadPercentage
- Next
- Set WMS = Nothing
- Set CPU = Nothing
- End Function
- Function CPUUtilAdvanced(LimiteUtilisationCpu)
- Set WMS = GetObject("winmgmts:" & "{impersonationLevel=impersonate}!\\" & NomDeMachine & "\root\cimv2" )
- set Refresher = CreateObject("WbemScripting.Swbemrefresher" )
- Set CPU = objRefresher.AddEnum(WMS, "Win32_PerfFormattedData_PerfOS_Processor" ).objectSet
- intThresholdViolations = 0
- Refresher.Refresh
- Do
- For each intProcessorUse in CPU
- If intProcessorUse.PercentProcessorTime > LimiteUtilisationCpu Then
- intThresholdViolations = intThresholdViolations + 1
- If intThresholdViolations = 10 Then
- intThresholdViolations = 0
- End If
- Else
- intThresholdViolations = 0
- End If
- Next
- Wscript.Sleep 6000
- Refresher.Refresh
- Loop
- CPUUtilAdvanced = 0
- Set WMS = Nothing
- Set CPU = Nothing
- Set Refresher = Nothing
- End Function
- Private Function GetUptime()
- Set objWMIService = GetObject("winmgmts:" & "{impersonationLevel=impersonate}!\\" & NomDeMachine & "\root\cimv2" )
- Set colOperatingSystems = objWMIService.ExecQuery ("Select * from Win32_OperatingSystem" )
-
- For Each objOS in colOperatingSystems
- dtmBootup = objOS.LastBootUpTime
- dtmLastBootupTime = WMIDateStringToDate(dtmBootup)
- dtmSystemUptime = DateDiff("h", dtmLastBootUpTime, Now)
- GetUptime = dtmSystemUptime
- Next
- End Function
- Function WMIDateStringToDate(dtmBootup)
- WMIDateStringToDate = CDate(Mid(dtmBootup, 7, 2) & "/" & Mid(dtmBootup, 5, 2) & "/" & Left(dtmBootup, 4) & " " & Mid (dtmBootup, 9, 2) & ":" & Mid(dtmBootup, 11, 2) & ":" & Mid(dtmBootup, 13, 2))
- End Function
- Private Function GetFreeMem()
- On Error Resume Next
- Set objWMIService = GetObject("winmgmts:" & "{impersonationLevel=impersonate}!\\" & NomDeMachine & "\root\cimv2" )
- set objRefresher = CreateObject("WbemScripting.SWbemRefresher" )
- Set objMemory = objRefresher.AddEnum(objWMIService, "Win32_PerfFormattedData_PerfOS_Memory" ).objectSet
- objRefresher.Refresh
- objRefresher.Refresh
-
- For each intAvailableBytes in objMemory
- Mem = intAvailableBytes.AvailableMBytes
- Next
- GetFreeMem = Mem
- Set objRefresher = Nothing
- Set objMemory = Nothing
-
- End Function
- Private Function Divide(int1,int2)
- Divide = 0
- If CDbl(int1) > 0 And CDbl(int2) > 0 Then
- Divide = int1 / int2
- End If
- End Function
- Private Function SendMail()
- set iMsg = CreateObject("CDO.Message" )
- set iConf = CreateObject("CDO.Configuration" )
- Set WMIService = GetObject("winmgmts:{impersonationLevel=impersonate}!\\" & NomDeMachine & "\root\cimv2" )
- Set colSettings = WMIService.ExecQuery ("Select * from Win32_ComputerSystem" )
- For Each objComputer in colSettings
- SystemName = objComputer.Name
- Domain = objComputer.Domain
- Next
- Set Flds = iConf.Fields
- HtmlBody = HtmlBody & "</BODY>"
- HtmlBody = HtmlBody & "</HTML>"
- If AdresseServeurSmtp <> "" And AdresseEmailDestinataire <> "" Then
- With Flds
- .Item("http://schemas.microsoft.com/cdo/configuration/sendusing" ) = cdoSendUsingPort
- .Item("http://schemas.microsoft.com/cdo/configuration/smtpserver" ) = AdresseServeurSmtp
- .Item("http://schemas.microsoft.com/cdo/configuration/smtpconnectiontimeout" ) = 10
- .Update
- End With
-
- With iMsg
- Set .Configuration = iConf
- .To = AdresseEmailDestinataire
- .From = "SysInfo@" & SystemName
- .Subject = "SysInfo : " & Domain & "\" & SystemName
- .HTMLBody = HtmlBody
- .Send
- End With
- End If
- End Function
- Private Function CheckNumber(int1)
- CheckNumber = 0
- If IsNumeric(int1) Then
- CheckNumber = int1
- End If
- End Function
- End Class
|
Message édité par tecoxe le 19-08-2008 à 17:43:52
|