Forum |  HardWare.fr | News | Articles | PC | S'identifier | S'inscrire | Shop Recherche
2684 connectés 

  FORUM HardWare.fr
  Programmation
  VB/VBA/VBS

  Commande VBS pour connaitre la Version de JVM installée

 


 Mot :   Pseudo :  
 
Bas de page
Auteur Sujet :

Commande VBS pour connaitre la Version de JVM installée

n°1252117
saha54
Posté le 24-11-2005 à 11:14:21  profilanswer
 

Salut tt le monde,
est-ce que quelqu'un connaît la commande en VBS qui permet de connaître le type de JVM (JAVA Virtual Machine) installée sue le PC.
On a la possibilité de le savoir via l'internet explorer, dans Outils>Options Internet... , dans l'onglet "Avancé"

mood
Publicité
Posté le 24-11-2005 à 11:14:21  profilanswer
 

n°1252375
dahlo
Posté le 24-11-2005 à 16:14:06  profilanswer
 

Pour IE tu as ce script:
 

Citation :

''''''''''''''''''''''''''''''''''''''''''''''''''''''''''
' detectIEJVM.vbs reads HKLM registry keys to determine
' if IE configured to use Sun JavaPlugin (Java2 JVM).
' Determines MS JVM version.
'                            M. Gallant  06/19/2002
'
'''''''''''''''''''''''''''''''''''''''''''''''''''''''''''
Option Explicit
If Java2Checked() Then
   WScript.Echo "IE using Sun JVM: " & JavaPluginPath()
 ElseIF MSJVMVersion() <> "0" Then
   WScript.Echo "IE using MS JVM: " & MSJVMVersion()
 Else
   WScript.Echo "IE MS JVM ""msjava.dll"" not found"
End If
 
'--- Get registry path pointer to "UserJava2IExplorer" setting
Function JavaPluginPath()
Dim WshShell, IEJava2Option, java2path, version
 Set WshShell = WScript.CreateObject("WScript.Shell" )
 IEJava2Option="HKLM\SOFTWARE\Microsoft\Internet Explorer\AdvancedOptions\JAVA_SUN\SELECT\RegPath"
 
  On Error Resume Next
  java2path = WshShell.RegRead(IEJava2Option)
   If Err.Number <> 0 Then  
' if REG_PATH named-value does not exist
    JavaPluginPath = "0"
    Exit Function
   End If
  On Error GoTo 0
 JavaPluginPath = java2path
End Function
 
'--- Detect setting of "UserJava2IExplorer" named-value
Function Java2Checked()
 Dim WshShell, jpath, java2setting
 jpath = JavaPluginPath()
 If jpath = "0" Then           'IE Java_Sun key not defined
   Java2Checked = False
   Exit Function
 End If
 Set WshShell = WScript.CreateObject("WScript.Shell" )
 On Error Resume Next
  java2setting = WshShell.RegRead("HKLM\" & jpath & "\UseJava2IExplorer" )
   If Err.Number <> 0 Then  ' if UseJava2IExplorer named-value does not exist
    Java2Checked = False
    Exit Function
   End If
 On Error GoTo 0
 If java2setting Then
   Java2Checked = True
  Else
   Java2Checked = False
 End If
End Function
 
'--- Get MS JVM version via msjava.dll FileVersion
Function MSJVMVersion
 Dim msjavadll
 Dim fso, WshShell
 Set WshShell = WScript.CreateObject("WScript.Shell" )
 msjavadll = WshShell.ExpandEnvironmentStrings("%WINDIR%\system32\msjava.dll" )
 Set fso = CreateObject("Scripting.FileSystemObject" )
 If fso.FileExists(msjavadll) Then
   'WScript.Echo fso.GetFileVersion(msjavadll)
   MSJVMVersion =  fso.GetFileVersion(msjavadll)
 Else
   MSJVMVersion =  "0"
 End If
 Set fso = nothing
 Set wshshell = nothing
End Function


Aller à :
Ajouter une réponse
  FORUM HardWare.fr
  Programmation
  VB/VBA/VBS

  Commande VBS pour connaitre la Version de JVM installée

 

Sujets relatifs
[VBS] afficher l'animation de copie de fichier - [résolu][VBS - RESOLU] Recherche recursive de fichiers avec caracteres généric
Commande Unix wc en Cun moteur XSLT 2 en ligne de commande?
[VBA EXCEL]Création d'une barre de commande pour un userform[Résolue] lancement d'une commande dos dans un vbs
Nouvelle version GifmaniacConnaître le type d'un fichier
[VBS] (résolu) copy overwrite fonctionne pas.. pourquoi?[bash] recuperer le resultat d'une commande SQL dans une variable bash
Plus de sujets relatifs à : Commande VBS pour connaitre la Version de JVM installée


Copyright © 1997-2022 Hardware.fr SARL (Signaler un contenu illicite / Données personnelles) / Groupe LDLC / Shop HFR