Bonjour,
Je viens de découvrir Anatomic P2P Client, il fonctionne, mais est peu pratique à utiliser.
Je souhaite faire un petit vbs qui facilite le tout.
Au départ ca fonctionne en ligne de commande :
c:\Anatomic\btdownloadheadless.exe "nom_du_fichier_torrent" arguments_eventuels
Je voudrais que le script m'ouvre une boite de choix de fichiers (torrent seulement si possible), et lance la ligne de commande.
J'ai commencé avec des morceaux de scripts trouvés sur le net, mais c'est pas joli joli.
Inutile de vous préciser que je suis newbie en la matiere, vous le verrez vous mêmes en voyant le code...
Si qqun a un moment pour regarder, ou me donner une solution + rapide, je suis preneur !
Merci à tous !
VOICI LE CODE :
_______________
Set sh = CreateObject("WScript.Shell" )
Set fso = CreateObject("Scripting.FileSystemObject" )
Dim ob, s, fic
set ob = New FindFile
MsgBox "Choisir le fichier torrent, upload max 6kb/s"
s = ob.Browse
set ob = nothing
fic = "c:\Anatomic\btdownloadheadless.exe " & chr(34) & s & chr(34) & "--max_upload_rate 6"
MsgBox fic
sh.Run fic
'-----------------BEGIN CLASS BLOCK -----------------------------------
'-- Use: Set obj = New FindFile
'-- var = obj.Browse
'-------------- var is path of file selected. -----------------------------
'---------------------------------------------------------------------
Class FindFile
Private fso, sPath1
'--FileSystemObject needed to check file path:
Private Sub Class_Initialize()
Set fso = CreateObject("Scripting.FileSystemObject" )
end sub
'---------------release FSO when class is released:
Private Sub Class_Terminate()
Set FSO = Nothing
End sub
'--The public one function in this class:
Public Function Browse()
on error resume next
sPath1 = GetPath
Browse = sPath1
end function
Private Function GetPath()
Dim Ftemp, ts, IE, sPath
'-----------Get the TEMP folder path and create a text file in it:
Ftemp = fso.GetSpecialFolder(2)
Ftemp = Ftemp & "\FileBrowser.html"
set ts = fso.CreateTextFile(Ftemp, true)
'----------------------write the webpage needed for file browsing window:
ts.WriteLine "<HTML><HEAD><TITLE></TITLE></HEAD>"
ts.WriteLine "<BODY BGCOLOR=" & chr(34) & "#F3F3F8" & chr(34) & " TEXT=" & chr(34) & "black" & chr(34) & ">"
ts.WriteLine "<script language=" & chr(34) & "VBScript" & chr(34) & ">"
'--------when OK is clicked assign path to statustext property:
ts.WriteLine "sub but_onclick()"
ts.WriteLine "status = document.forms(0).elements(0).value"
ts.WriteLine "end sub"
'--------when CANCEL is clicked assign "cancel" to statustext property:
ts.WriteLine "sub butc_onclick()"
ts.WriteLine "status = " & chr(34) & "cancel" & chr(34)
ts.WriteLine "end sub"
ts.WriteLine "</script>"
ts.WriteLine "<DIV ALIGN=" & chr(34) & "center" & chr(34) & ">"
ts.WriteLine "<FONT FACE=" & Chr(34) & "arial" & Chr(34) & " SIZE=2>"
ts.WriteLine "<BR>"
ts.WriteLine "<FORM>"
'-----------this is the file browsing box in webpage:
ts.WriteLine "<INPUT TYPE=" & chr(34) & "file" & chr(34) & "></input>"
'-----------this is the OK button:
ts.WriteLine "<input type=" & chr(34) & "button" & chr(34) & " id=" & chr(34) & "but" & chr(34) & " value=" & chr(34) & "OK" & chr(34) & "></input>"
ts.WriteLine "<BR><BR>"
'------------this is the CANCEL button:
ts.WriteLine "<input type=" & chr(34) & "button" & chr(34) & " id=" & chr(34) & "butc" & chr(34) & " value=" & chr(34) & "CANCEL" & chr(34) & "></input>"
ts.WriteLine "<BR><BR> Browse for file, then click OK."
ts.WriteLine "</FORM>"
ts.WriteLine "</FONT></DIV>"
ts.WriteLine "</BODY></HTML>"
ts.Close
set ts = nothing
on error resume next
'--webpage is written. now have IE open it:
Set IE = Wscript.CreateObject("InternetExplorer.Application" )
IE.Navigate "file:///" & Ftemp
IE.AddressBar = false
IE.menubar = false
IE.ToolBar = false
IE.width = 400
IE.height = 250
IE.resizable = false
IE.visible = true
'--do a loop every 1/2 second until either:
'-- the browsing window value is a valid file path or
'-- CANCEL is clicked (setting IE.StatusText to "cancel" ) or
'--IE is closed from the control box.
do while IE.visible = true
spath = IE.StatusText '--------get statustext value.
if fso.FileExists(spath) = true or spath = "cancel" or IE.visible = false then
exit do
end if
wscript.sleep 500
loop
IE.visible = false
IE.Quit
set IE = nothing
if fso.FileExists(spath) = true then
GetPath = spath
else
GetPath = ""
end if
End Function
End Class