api pour les .ini

api pour les .ini - VB/VBA/VBS - Programmation

Marsh Posté le 04-02-2003 à 15:44:16    

bonjour a tous,
 
je cherche le nom de l'api wiondows qui permet de gerer les fichiers .ini
 
qqun le connait ?
 
merci d'avance


---------------
Cobol le jour, PHP la nuit ... Je préfère franchement mes nuits ...
Reply

Marsh Posté le 04-02-2003 à 15:44:16   

Reply

Marsh Posté le 04-02-2003 à 15:49:01    

rdmarmotte a écrit :

bonjour a tous,
 
je cherche le nom de l'api wiondows qui permet de gerer les fichiers .ini
 
qqun le connait ?
 
merci d'avance

oui, je te la donne, je vai la chercher ! quelques secondes !

Reply

Marsh Posté le 04-02-2003 à 15:52:09    

rdmarmotte a écrit :

bonjour a tous,
 
je cherche le nom de l'api wiondows qui permet de gerer les fichiers .ini
 
qqun le connait ?
 
merci d'avance


 
 
tu la trouveras dans cette liste  : http://docvb.free.fr/api.php
je me suis pris le choux avec elle, il quelques mois, j'ai perdu le nom, désolé. Je sais simplement qu'elle est hyper chiante ç utiliser...
 
tu as ce liens en anglais qui te permettra de trouver également peut être des exemples  : http://www.allapi.net/ tu peux y téléchrager un prog. Tu as pas mal de chose interressante également !  

Reply

Marsh Posté le 04-02-2003 à 15:57:23    

cvb a écrit :


 
 
tu la trouveras dans cette liste  : http://docvb.free.fr/api.php
je me suis pris le choux avec elle, il quelques mois, j'ai perdu le nom, désolé. Je sais simplement qu'elle est hyper chiante ç utiliser...
 
tu as ce liens en anglais qui te permettra de trouver également peut être des exemples  : http://www.allapi.net/ tu peux y téléchrager un prog. Tu as pas mal de chose interressante également !  
 


 
le pepin, c'est que je connais le site allapi, mais que ya presque 350 apis differentes, et que ya juste le nom (et du temps) qui me manque :)


---------------
Cobol le jour, PHP la nuit ... Je préfère franchement mes nuits ...
Reply

Marsh Posté le 04-02-2003 à 16:00:56    

cvb a écrit :


 
 
tu la trouveras dans cette liste  : http://docvb.free.fr/api.php
je me suis pris le choux avec elle, il quelques mois, j'ai perdu le nom, désolé. Je sais simplement qu'elle est hyper chiante ç utiliser...
 
tu as ce liens en anglais qui te permettra de trouver également peut être des exemples  : http://www.allapi.net/ tu peux y téléchrager un prog. Tu as pas mal de chose interressante également !  
 


 
c bon !!!!! g trouve dans docvb !!!!  :bounce:  :bounce:  
marchi bcp :jap:


---------------
Cobol le jour, PHP la nuit ... Je préfère franchement mes nuits ...
Reply

Marsh Posté le 04-02-2003 à 16:14:17    

rdmarmotte a écrit :


 
c bon !!!!! g trouve dans docvb !!!!  :bounce:  :bounce:  
marchi bcp :jap:  


 
de rien ! good luck !

Reply

Marsh Posté le 04-02-2003 à 16:30:39    

Option Explicit
 
Private strPathInI As String
 
' Déclaration API
Private Declare Function WritePrivateProfileString Lib "kernel32" _
    Alias "WritePrivateProfileStringA" (ByVal Section As String, ByVal KeyName As String, ByVal Value As String, _
    ByVal FileName As String) As Boolean
   
Private Declare Function GetPrivateProfileString Lib "kernel32" Alias _
    "GetPrivateProfileStringA" (ByVal Section As String, _
    ByVal KeyName As Any, ByVal Default As String, _
    ByVal ReturnedString As String, ByVal Size As Long, _
    ByVal lpFileName As String) As Integer
     
Private Declare Function GetPrivateProfileInt Lib "kernel32" Alias _
    "GetPrivateProfileIntA" (ByVal Section As String, _
    ByVal KeyName As String, ByVal Default As Integer, _
    ByVal lpFileName As String) As Integer
     
Private Declare Function GetPrivateProfileSectionNames Lib "kernel32" Alias "GetPrivateProfileSectionNamesA" _
    (ByVal ReturnBuffer As String, ByVal Size As Integer, ByVal FileName As String) As Integer
     
Private Declare Function GetPrivateProfileSection Lib "kernel32" Alias "GetPrivateProfileSectionA" _
    (ByVal Section As String, ByVal ReturnBuffer As String, ByVal Size As Integer, ByVal FileName As String) As Integer
 
 
' Fonctions privés
Private Function IncludeBackSlash(Path As String) As String
    IncludeBackSlash = Path
    If Not Right(Path, 1) = "\" Then IncludeBackSlash = IncludeBackSlash & "\"
End Function
 
' Class INI
Public Sub CreateIni(strPath As String, strName As String)
    If strPath = "" Then strPath = App.Path
    strPathInI = IncludeBackSlash(strPath) + strName
End Sub
 
Public Function WriteString(Section As String, KeyName As String, Value As String) As Boolean
    WriteString = WritePrivateProfileString(Section, KeyName, Value, strPathInI)
End Function
 
Public Function WriteInt(Section As String, KeyName As String, Value As Integer) As Boolean
    WriteInt = WritePrivateProfileString(Section, KeyName, Value, strPathInI)
End Function
 
Public Function WriteBool(Section As String, KeyName As String, Value As Boolean) As Boolean
    WriteBool = WritePrivateProfileString(Section, KeyName, CBool(Value), strPathInI)
End Function
 
Public Function ReadString(Section As String, KeyName As String, Default As String) As String
Dim S As String
Dim B As Integer
 
    S = Space(255)
    B = GetPrivateProfileString(Section, KeyName, Default, S, Len(S), strPathInI)
     
    If B <> 0 Then
        ReadString = Left(S, B)
    Else
        ReadString = ""
    End If
End Function
 
Public Function ReadInt(Section As String, KeyName As String, Default As Integer) As Integer
 
    ReadInt = GetPrivateProfileInt(Section, KeyName, Default, strPathInI)
End Function
 
Public Function ReadBool(Section As String, KeyName As String, Default As Boolean) As Boolean
Dim S As String
Dim B As Integer
 
    S = Space(255)
    B = GetPrivateProfileString(Section, KeyName, CStr(Default), S, Len(S), strPathInI)
     
    If B <> 0 Then
        S = Left(S, B)
    Else
        S = ""
    End If
    ReadBool = CBool(S)
End Function
 
Public Function ReadSectionNames() As String
Dim S As String
Dim B As Integer
Dim All As Integer
 
    All = 255
     
    Do
        S = Space(All)
        B = GetPrivateProfileSectionNames(S, Len(S), strPathInI)
        All = All * 2
    Loop While B = Len(S) - 2
     
    If B <> 0 Then
        S = Left(S, B - 2)
    Else
        S = ""
    End If
     
    ReadSectionNames = S
End Function
 
Public Function ExistSection(Section As String) As Boolean
Dim StrArr() As String
Dim i As Integer
Dim B As Boolean
     
    B = False
    StrArr = Split(ReadSectionNames, Chr(0))
    i = LBound(StrArr)
    While (i <= UBound(StrArr)) And Not B
        If LCase(Section) = LCase(StrArr(i)) Then B = True
        i = i + 1
    Wend
     
    ExistSection = B
End Function
 
Public Function ReadSectionKeys(Section As String) As String
Dim S As String
Dim B As Integer
Dim All As Integer
 
    All = 255
     
    Do
        S = Space(All)
        B = GetPrivateProfileSection(Section, S, Len(S), strPathInI)
        All = All * 2
    Loop While B = Len(S) - 2
     
    If B <> 0 Then
        S = Left(S, B - 2)
    Else
        S = ""
    End If
     
    ReadSectionKeys = S
End Function
 
Public Function ExistSectionKey(Section As String, Key As String) As Boolean
Dim StrArr() As String
Dim i As Integer
Dim B As Boolean
     
    B = False
    StrArr = Split(ReadSectionKeys(Section), Chr(0))
     
    For i = LBound(StrArr) To UBound(StrArr)
        StrArr(i) = Left(StrArr(i), InStr(1, StrArr(i), "=" ) - 1)
    Next i
     
    i = LBound(StrArr)
    While (i <= UBound(StrArr)) And Not B
        If LCase(Key) = LCase(StrArr(i)) Then B = True
        i = i + 1
    Wend
     
    ExistSectionKey = B
End Function
 
Public Property Let FileName(ByVal New_IniPath As String)
 
    strPathInI = New_IniPath
End Property
 
Public Property Get FileName() As String
 
 FileName = strPathInI
End Property
 


---------------
Des bons sites pour Delphi? http://forum.hardware.fr/forum2.php3?post=16838&cat=10 -- informaticien -- http://www.z0rglub.com/phpwebgallery/ -- Delphi :love:
Reply

Sujets relatifs:

Leave a Replay

Make sure you enter the(*)required information where indicate.HTML code is not allowed