Option Explicit
Dim oFSO,objShell
Set oFSO = CreateObject("Scripting.FileSystemObject" )
Set objShell = WScript.CreateObject("WScript.Shell" )
''---Function arborescence
''-----Renvoi un tableau contenant l'arborescence du chemin 'chemin'  
 
Function arborescence(chemin)
 Dim i
 Dim oFl,oFld
 
 ReDim tabs(2,0) '--Tableau principaux
 Dim soustabs '--Sous tableau contenant les sous-dossiers
 
 	For each oFl in oFSO.GetFolder(chemin).Files
   tabs(0,Ubound(tabs,2)) = oFl.Name
   tabs(1,Ubound(tabs,2)) = Mid(oFl.Path,1,len(oFl.Path) - len(oFl.Name))
   tabs(2,Ubound(tabs,2)) = oFl.Name
   Redim Preserve tabs(2,Ubound(tabs,2) + 1)  '--Augmente la taille du tableau
 	Next
 
 	For each oFld in oFSO.GetFolder(chemin).SubFolders
   tabs(0,Ubound(tabs,2)) = "[" & oFld.Name & "]"
   tabs(1,Ubound(tabs,2)) = Mid(oFld.Path,1,len(oFld.Path) - len(oFld.Name) )  
   tabs(2,Ubound(tabs,2)) = oFld.Name
   Redim Preserve tabs(2,Ubound(tabs,2) + 1) '--Augmente la taille du tableau
   soustabs = arborescence(chemin & "\" & oFld.name)
   wscript.echo tabs(1,Ubound(tabs,2))  & " et " &  oFld.Path & " et " & oFld.Name
   For i=0 To Ubound(soustabs,2) - 1
   	tabs(0,Ubound(tabs,2))=soustabs(0,i)  
   	tabs(1,Ubound(tabs,2)) =Mid(soustabs(1,i),1,len(soustabs(1,i))-len(soustabs(2,i)))
   	tabs(2,Ubound(tabs,2)) = soustabs(2,i)
   	Redim Preserve tabs(2,Ubound(tabs,2)+1) '--Augmente la taille du tableau par rapport au contenu du sous tableau
   Next
   
 	Next
 arborescence = tabs
 
End Function
''----Function accent
''------Enleve les accents des dossiers et fichiers d'une arborescence
''------Retourne un tableau avec une arborescence sans accent
 
Function accent(arbo)
 Dim lettre, ascii, i,j
 Dim nouveauNom
 For i=1 To len(arbo)
 
   lettre = Mid(arbo,i,1)
   ascii=asc(lettre)
 
   Select Case ascii
   	Case 224, 225, 226, 227, 228, 229  ''Cas des "a" avec accent''
     nouveauNom = nouveauNom & chr(97)
   	Case 232, 233, 234, 235    	''Cas des "e" avec accent"
     nouveauNom = nouveauNom & chr(101)
   	Case 236, 237, 238, 239    	''Cas des "i" avec accent''
     nouveauNom = nouveauNom & chr(105)
   	Case 242, 243, 244, 245, 246  	''Cas des "o" avec accent''
     nouveauNom = arboe(2,j) & chr(111)
   	Case 249, 250, 251, 252  	''Cas des "u" avec accent''
     nouveauNom= nouveauNom & chr(117)
   	Case Else          ''Si pas accent''
     nouveauNom = nouveauNom & chr(ascii)
   End Select
   
 Next
 	accent = nouveauNom
End Function
 
''Fonction de chiffrage
''Retourne une chaine
 
Function chiffrage(arbo, key)
 Dim i,j, lettre, ascii
 Dim nouveauNom
 
 For i=1 To Len(arbo)
   lettre = Mid(arbo,i,1)
   ascii = asc(lettre)
   key = key Mod 26
   
   Select Case ascii
   	Case 65, 66, 67, 68, 69, 70, 71, 72, 73, 74, 75, 76, 77, 78, 79, 80, 81, 82, 83, 84, 85, 86, 87, 88, 89, 90 ''Cas des majuscules''
     ascii = ascii + key
     If ascii > 90 Then
     	ascii = ascii - 26
     End If
     nouveauNom = nouveauNom & chr(ascii)
   	Case 97, 98, 99, 100, 101, 102, 103, 104, 105, 106, 107, 108, 109, 110, 111, 112, 113, 114, 115, 116, 117, 118, 119, 120, 121, 122	''Cas des minuscules''
     ascii = ascii + key
     If ascii > 122 Then
     	ascii = ascii - 26
     End If
     nouveauNom = nouveauNom & chr(ascii)
   	Case Else ''Si pas accent''
     nouveauNom = nouveauNom & chr(ascii)
   End Select
   
 Next
 
 chiffrage = nouveauNom
End Function
''--Fonction dechiffrage
''---Renvoi une chaine dechiffrer en fonction de la clé  
Function dechiffrage(arbo, key)
 Dim i, lettre, ascii, nouveauNom
 
 i = 1
 
 Do
 	lettre = Mid(arbo, i, 1)
 	ascii = asc(lettre)
 	key = key Mod 26
   
 	Select Case ascii
   Case 65, 66, 67, 68, 69, 70, 71, 72, 73, 74, 75, 76, 77, 78, 79, 80, 81, 82, 83, 84, 85, 86, 87, 88, 89, 90 ''Cas des majuscules''
   	ascii = ascii - key
   	If ascii < 65 Then
     ascii = ascii + 26
   	End If
   	nouveauNom = nouveauNom & chr(ascii)
   Case 97, 98, 99, 100, 101, 102, 103, 104, 105, 106, 107, 108, 109, 110, 111, 112, 113, 114, 115, 116, 117, 118, 119, 120, 121, 122	''Cas des minuscules''
   	ascii = ascii - key
   	If ascii < 97 Then
     ascii = ascii + 26
   	End If
   	nouveauNom = nouveauNom & chr(ascii)
   Case Else ''Si pas accent''
   	nouveauNom = nouveauNom & chr(ascii)
 	End Select
 	i = i + 1
   
 Loop Until Mid(arbo,i,1) = ""
 
 dechiffrage = nouveauNom
 
End Function
 
'Fonction aide
'affiche les commandes
Function help()
 
 help = help & "NOM" & Chr(10)
 help = help & Chr(10)
 help = help & Chr(9) & "TraiterArbo.bvs - Traiter ..." & Chr(10)
 help = help & Chr(10)
 help = help & "SYNOPSIS" & Chr(10)
 help = help & Chr(10)
 help = help & Chr(9) & "TraiterArbo.bvs [OPTION]... [FICHIER]..." & Chr(10)
 help = help & Chr(10)
 help = help & "DESCRIPTION" & Chr(10)
 help = help & Chr(10)
 help = help & Chr(9) & "-c,--chemin REPERTOIRE" & Chr(10)
 help = help & Chr(9) & "-d, --decrypt : déchiffrage de l'arborescence CLE" & Chr(10)
 help = help & Chr(9) & "-e, --encrypt : chiffrage de l'arborescence CLE" & Chr(10)
 help = help & Chr(9) & "-a, --accent : enlève les accents" & Chr(10)
 help = help & Chr(9) & "-v, --verbose : active le mode détaillé" & Chr(10)
 help = help & Chr(9) & "-s, --simulate : active la simulation du script" & Chr(10)
 help = help & Chr(9) & "-u, --upper : changer la casse en majuscule" & Chr(10)
 help = help & Chr(9) & "-l, --lower : changer la casse en minuscule" & Chr(10)
 help = help & Chr(9) & "-f, --file : traite seulement les fichiers" & Chr(10)
 help = help & Chr(9) & "-t, --truncate : tronque le nom des éléments à x caractères NOMBRE_CARACTERES" & Chr(10)
 help = help & Chr(9) & "-h, --help : affiche l'aide" & Chr(10)
 help = help & Chr(9) & "--author :affiches les auteurs"
 
End Function
 
Function author()
 author = author & "Script : TraiterArbo.vbs" & Chr(10)
 author = author & "Auteurs : Yacine Rezgui et Ferretti Cédric"
End Function
 
''-------------------------------------------Test les arguments entrer par l'utilisateur-----------------------------------------------------------''
Dim i, cmdMain
 If wscript.Arguments.Count = 0 Then  
 	wscript.echo "Aucun arguments entrés"
 Else
 	i=-1 '-- A -1 pour car wscript.arguments commence a zero  
   
 	Do  
   i = i + 1
   cmdMain =  wscript.Arguments(i)  ''--On s'arrete a la premiere des principaux arguments trouvé--''
 	Loop Until wscript.Arguments(i) = "--author" Or wscript.Arguments(i) = "-h"   Or wscript.Arguments(i) = "--help" Or wscript.Arguments(i) = "-c" Or i >= wscript.Arguments.Count - 1
 End If
'------------------------------------------ On test les arguments principales-----------------------------------------------------------------------''
Dim chemin
 
 Select Case cmdMain
 	Case "--author"
   cmdMain = "author"
 	Case "-h","--help"
   cmdMain = "aide"
 	Case "-c"
   ''--On test si le chemin existe et contient quelquechose--''
   If oFSO.FolderExists(wscript.Arguments(i+1)) Then
   	cmdMain = "chemin"
   	chemin = wscript.Arguments(i+1)
   Else : wscript.echo "Chemin invalide" ''--Sinon Msg d'erreur--''
   End If
 End Select
 
 ''-----------------------------------------Partie Recuperation de l'arborescence dans une matrice------------------------------------------------''
If cmdMain = "chemin" Then
 Dim arbo,j
 arbo = arborescence(chemin)
 
End If
''-------------------------------------------------------Matrice recuperer----------------------------------------------------------------------------------------''
 
 ''-----------------------On test maintenant si il y a d'autre arguments uniquement si un chemin valide a été entrez----------------------------------''
 
 If cmdMain="chemin" Then
 	For i=0 To wscript.Arguments.Count - 1
   Select Case wscript.Arguments(i)
   	Case "-a","--accent"
     	For j=0 To Ubound(arbo,2)
       arbo(2,j) = accent(arbo(0,j))
     	Next
   End Select
 	Next
   
 	For i=0 To wscript.Arguments.Count - 1
   Select Case wscript.Arguments(i)
   	Case "-e","--encrypt"
     	For j=0 To Ubound(arbo,2)
       arbo(2,j) = chiffrage(arbo(2,j),wscript.Arguments(i+1))
       wscript.echo arbo(2,j)
   	Next
   	Case "-d","--decrypt"
     For j=0 To Ubound(arbo,2)
     	arbo(2,j) = dechiffrage(arbo(2,j),wscript.Arguments(i+1))
     	wscript.echo arbo(2,j)
     Next    
     
   End Select
 	Next
 ElseIf cmdMain = "aide" Then wscript.echo help()
 Else If cmdMain = "author" Then wscript.echo author()
 End If