Adblock breaks this site

Read INI Files from a webserver?

Discussion in 'Programming General' started by Covey, May 19, 2009.

  1. Covey

    Covey Creator of EliteSwitch
    Retired Sectional Moderator Visual Basic Programmers

    Joined:
    Sep 9, 2005
    Posts:
    4,510
    Referrals:
    9
    Sythe Gold:
    9
    Discord Unique ID:
    807246764155338833
    Discord Username:
    Covey#1816
    Read INI Files from a webserver?

    I'm trying to write a procedure to read an INI files from a webserver, anyone have any idea's of how to do this?
     
  2. jdsfighter

    jdsfighter Forum Addict
    Visual Basic Programmers

    Joined:
    Jan 21, 2007
    Posts:
    603
    Referrals:
    0
    Sythe Gold:
    0
    Read INI Files from a webserver?

    Covey, is it possible to use inet or something similar to get the source from the ini page, then place it into a file, then read from it, or are you trying to do it without saving the file?
     
  3. Covey

    Covey Creator of EliteSwitch
    Retired Sectional Moderator Visual Basic Programmers

    Joined:
    Sep 9, 2005
    Posts:
    4,510
    Referrals:
    9
    Sythe Gold:
    9
    Discord Unique ID:
    807246764155338833
    Discord Username:
    Covey#1816
    Read INI Files from a webserver?

    Trying to do it on the fly.
     
  4. jdsfighter

    jdsfighter Forum Addict
    Visual Basic Programmers

    Joined:
    Jan 21, 2007
    Posts:
    603
    Referrals:
    0
    Sythe Gold:
    0
    Read INI Files from a webserver?

    Then I'm afraid your probably not going to be able to use the built in ini read and write system.
     
  5. Darthatron

    Darthatron Massive Troll
    Retired Sectional Moderator Visual Basic Programmers

    Joined:
    May 22, 2006
    Posts:
    1,612
    Referrals:
    3
    Sythe Gold:
    0
    Read INI Files from a webserver?

    TADA!

    Code:
    Option Explicit
    
    Public Function ReadIniValue(Text As String, KEY As String, Variable As String) As String
    Dim Temp() As String
    Dim LcaseTemp As String
    Dim ReadyToRead As Boolean
    Dim LineCount As Long
    Dim lCounter As Long
        
    AssignVariables:
            ReadIniValue = ""
            KEY = "[" & LCase$(KEY) & "]"
            Variable = LCase$(Variable)
        
    LoadFile:
        Temp = Split(Text, vbNewLine)
        For lCounter = LBound(Temp) To UBound(Temp)
        LcaseTemp = LCase$(Temp(lCounter))
        If InStr(LcaseTemp, "[") <> 0 Then ReadyToRead = False
        If LcaseTemp = KEY Then ReadyToRead = True
        If InStr(LcaseTemp, "[") = 0 And ReadyToRead = True Then
            If InStr(LcaseTemp, Variable & "=") = 1 Then
                ReadIniValue = Mid$(Temp(lCounter), 1 + Len(Variable & "="))
                End If
            End If
        Next lCounter
    End Function
    Should work, didn't test it, though.

    -

    Use iNet to download the text file then just...

    Code:
    String = ReadINIValue(strINIFileText, "faku", "Covey")
    EDIT: Edited this, by the way: http://www.freevbcode.com/ShowCode.asp?ID=5390
     
  6. Swan

    Swan When They Cry...
    Retired Global Moderator

    Joined:
    Jan 23, 2007
    Posts:
    4,957
    Referrals:
    0
    Sythe Gold:
    0
    Sythe's 10th Anniversary Member of the Month Winner
    Read INI Files from a webserver?

    You would need to use some method to pull the data from the server, regardless. You're pulling the same data as you would store in a file, so I don't understand why you couldn't simply store the data in a variable instead.
     
  7. Covey

    Covey Creator of EliteSwitch
    Retired Sectional Moderator Visual Basic Programmers

    Joined:
    Sep 9, 2005
    Posts:
    4,510
    Referrals:
    9
    Sythe Gold:
    9
    Discord Unique ID:
    807246764155338833
    Discord Username:
    Covey#1816
    Read INI Files from a webserver?

    i was using this ancient class module:
    Code:
    Option Explicit
    
    Private Declare Function GetPrivateProfileString Lib "Kernel32" Alias "GetPrivateProfileStringA" (ByVal lpApplicationName As String, ByVal lpKeyName As Any, ByVal lpDefault As String, ByVal lpReturnedString As String, ByVal nSize As Long, ByVal lpFileName As String) As Long
    Private Declare Function GetPrivateProfileSection Lib "Kernel32" Alias "GetPrivateProfileSectionA" (ByVal lpAppName As String, ByVal lpReturnedString As String, ByVal nSize As Long, ByVal lpFileName As String) As Long
    Private Declare Function WritePrivateProfileString Lib "Kernel32" Alias "WritePrivateProfileStringA" (ByVal lpApplicationName As String, ByVal lpKeyName As Any, ByVal lpString As Any, ByVal lpFileName As String) As Long
    Private Declare Function WritePrivateProfileSection Lib "Kernel32" Alias "WritePrivateProfileSectionA" (ByVal lpAppName As String, ByVal lpString As String, ByVal lpFileName As String) As Long
    
    Private Const BufferSize As Long = 4096
    Private strIniFile As String
    
    Public Property Get File() As String
        File = strIniFile
    End Property
    
    Public Property Let File(Value As String)
        strIniFile = Value
    End Property
    
    Public Function GetValue(strSection As String, strKey As String) As Variant
        Dim strBuffer As String
        Dim lLength As Long
        strBuffer = Space(BufferSize)
        lLength = GetPrivateProfileString(strSection, strKey, vbNullString, strBuffer, BufferSize, strIniFile)
        GetValue = Left(strBuffer, lLength)
    End Function
    
    Public Sub WriteValue(strSection As String, strKey As String, vntValue As Variant)
        WritePrivateProfileString strSection, strKey, CStr(vntValue), strIniFile
    End Sub
    
    Public Function GetSection(strSection As String) As Variant
        Dim strBuffer As String
        Dim lLength As Long
        strBuffer = Space(BufferSize)
        lLength = GetPrivateProfileSection(strSection, strBuffer, BufferSize, strIniFile)
        GetSection = Split(Left(strBuffer, lLength), vbNullChar)
    End Function
    
    Public Function GetSectionKeys(strSection As String) As Variant
        Dim strBuffer As String
        Dim lLength As Long
        strBuffer = Space(BufferSize)
        lLength = GetPrivateProfileString(strSection, vbNullString, vbNullString, strBuffer, BufferSize, strIniFile)
        GetSectionKeys = Split(Left(strBuffer, lLength), vbNullChar)
    End Function
    
     
  8. Swan

    Swan When They Cry...
    Retired Global Moderator

    Joined:
    Jan 23, 2007
    Posts:
    4,957
    Referrals:
    0
    Sythe Gold:
    0
    Sythe's 10th Anniversary Member of the Month Winner
    Read INI Files from a webserver?

    Then write your own functions? It isn't hard ;)
     
  9. Covey

    Covey Creator of EliteSwitch
    Retired Sectional Moderator Visual Basic Programmers

    Joined:
    Sep 9, 2005
    Posts:
    4,510
    Referrals:
    9
    Sythe Gold:
    9
    Discord Unique ID:
    807246764155338833
    Discord Username:
    Covey#1816
    Read INI Files from a webserver?

    Yes, but it takes time. and i don't have the time. So i rather use google to find my fixes ;)...

    Found this but i can't seem to find out how to write to the actually ini file:
    This code is better than mine because it doesn't open the ini files hundreds of times.
    Code:
    Option Explicit
    
    Public IniCollection As Dictionary
    Private CaseMode As Boolean
    Public CurrentFileName As String
    
    Public Function GetSection(ByVal Section As String) As Variant
        GetSection = IniCollection(Section).Keys
    End Function
    
    Public Sub EmptySection(ByVal Section As String)
        IniCollection(Section).RemoveAll
    End Sub
    
    Private Sub SetCompare()
        If (CaseMode = False) Then
            IniCollection.CompareMode = TextCompare
        Else
            IniCollection.CompareMode = BinaryCompare
        End If
    End Sub
    
    Private Sub ProcessIni(ByVal Data As String, Optional ByVal CommentMode As Boolean = True, Optional ByVal Rebuild As Boolean = True)
        On Error Resume Next
        Dim i As Long
        Dim TempData1 As String
        Dim TempData2 As String
        Dim SplitData As Variant
        Dim LineData As String
        Dim CurSection As String
        Dim EqlPos As Long
        If (Rebuild) Then
            Set IniCollection = New Dictionary
        End If
        SetCompare
        Data = Replace$(Data, vbCr, "")
        Data = Replace$(Data, vbLf, vbCrLf)
        SplitData = Split(Data, vbCrLf)
        For i = LBound(SplitData) To UBound(SplitData)
            LineData = SplitData(i)
            If ((Left$(LineData, 1) = "#") And (CommentMode)) Then
                GoTo SkipLine
            End If
            If (Len(LineData) = 0) Then
                GoTo SkipLine
            End If
            If ((Left$(LineData, 1) = "[") And (Right$(LineData, 1) = "]")) Then
                CurSection = Left$(LineData, Len(LineData) - 1)
                CurSection = Right$(CurSection, Len(CurSection) - 1)
                If Not (IniCollection.Exists(CurSection)) Then
                    IniCollection.Add CurSection, New Dictionary
                End If
            Else
                EqlPos = InStr(1, LineData, "=")
                If (EqlPos = 0) Then
                    GoTo SkipLine
                End If
                TempData1 = Left$(LineData, EqlPos - 1)
                TempData2 = Right$(LineData, Len(LineData) - EqlPos)
                If (IniCollection(CurSection).Exists(TempData1)) Then
                    IniCollection(CurSection).Remove TempData1
                    IniCollection(CurSection).Add TempData1, CStr(TempData2)
                Else
                    IniCollection(CurSection).Add TempData1, CStr(TempData2)
                End If
            End If
    SkipLine:
        Next i
    End Sub
    
    Public Property Get CaseSensitive() As Boolean
        CaseSensitive = CaseMode
    End Property
    
    Public Property Let CaseSensitive(ByVal NewMode As Boolean)
        CaseMode = NewMode
    End Property
    
    Public Sub OpenINI(ByVal FileName As String, Optional ByVal CommentMode As Boolean = True)
        On Error Resume Next
        Dim FB As Integer
        Dim Data As String
        FB = FreeFile
        Open FileName For Binary As #FB
            Data = Space$(LOF(FB))
            Get #FB, 1, Data
        Close #FB
        ProcessIni Data, CommentMode
        If (Err.Number <> 0) Then
            Err.Clear
            Exit Sub
        End If
        CurrentFileName = FileName
    End Sub
    
    Public Sub InputINI(ByVal Data As String, Optional ByVal CommentMode As Boolean = True)
        On Error Resume Next
        ProcessIni Data, CommentMode
        Err.Clear
    End Sub
    
    Public Sub InsertData(ByVal Data As String, Optional ByVal CommentMode As Boolean = True)
        On Error Resume Next
        ProcessIni Data, CommentMode, False
        Err.Clear
    End Sub
    
    Public Sub InsertINI(ByVal FileName As String, Optional ByVal CommentMode As Boolean = True)
        On Error Resume Next
        Dim FB As Integer
        Dim Data As String
        FB = FreeFile
        Open FileName For Binary As #FB
            Data = Space$(LOF(FB))
            Get #FB, 1, Data
        Close #FB
        ProcessIni Data, CommentMode, False
        Err.Clear
    End Sub
    
    Public Sub NewINI()
        Set IniCollection = New Dictionary
        If (CaseMode) Then
            IniCollection.CompareMode = BinaryCompare
        Else
            IniCollection.CompareMode = TextCompare
        End If
    End Sub
    
    Public Function ReadKey(ByVal Section As String, ByVal KeyName As String) As String
        ReadKey = IniCollection(Section)(KeyName)
    End Function
    
    Public Function ReadKeyEscaped(ByVal Section As String, ByVal KeyName As String) As String
        ReadKeyEscaped = UnEscaped(ReadKey(Section, KeyName))
    End Function
    
    Public Sub WriteKey(ByVal Section As String, ByVal KeyName As String, ByVal Data As String)
        If Not (IniCollection.Exists(Section)) Then
            IniCollection.Add Section, New Dictionary
        End If
        If Not (IniCollection(Section).Exists(KeyName)) Then
            IniCollection(Section).Add KeyName, CStr(Data)
        Else
            IniCollection(Section)(KeyName) = CStr(Data)
        End If
    End Sub
    
    Public Sub SaveINI(ByVal FileName As String)
        On Error Resume Next
        Dim FB As Integer
        Dim Data As String
        Data = OutputINI
        If (Len(Dir(FileName)) > 0) Then
            Kill FileName
        End If
        FB = FreeFile
        Open FileName For Binary As #FB
            Put #FB, 1, Data
        Close #FB
    End Sub
    
    Public Function OutputINI() As String
        On Error Resume Next
        Dim i As Long
        Dim j As Long
        Dim NewData As String
        Dim k1 As Variant
        Dim k2 As Variant
        k1 = IniCollection.Keys
        For i = LBound(k1) To UBound(k1)
            If (NewData <> "") Then
                NewData = NewData & vbCrLf
            End If
            NewData = NewData & "[" & k1(i) & "]"
            k2 = IniCollection(k1(i)).Keys
            For j = LBound(k2) To UBound(k2)
                NewData = NewData & vbCrLf
                NewData = NewData & k2(i) & "=" & IniCollection(k1(i))(k2(i))
            Next j
        Next i
        OutputINI = NewData
    End Function
    
    Public Property Get KeyExists(ByVal Section As String, ByVal KeyName As String) As Boolean
        If Not (IniCollection.Exists(Section)) Then
            KeyExists = False
            Exit Property
        End If
        KeyExists = IniCollection(Section).Exists(KeyName)
    End Property
    
    Public Property Let KeyExists(ByVal Section As String, ByVal KeyName As String, ByVal NewExists As Boolean)
        If (NewExists) Then
            If Not (IniCollection.Exists(Section)) Then
                IniCollection.Add Section, NewDictionary
            End If
            If Not (IniCollection(Section).Exists(KeyName)) Then
                IniCollection(Section).Add KeyName, ""
            End If
            Else
            If Not (IniCollection.Exists(Section)) Then
                Exit Property
            End If
            If (IniCollection(Section).Exists(KeyName)) Then
                IniCollection(Section).Remove KeyName
            End If
        End If
    End Property
    
    Public Property Get SectionExists(ByVal Section As String, ByVal KeyName As String) As Boolean
        SectionExists = IniCollection.Exists(KeyName)
    End Property
    
    Public Property Let SectionExists(ByVal Section As String, ByVal KeyName As String, ByVal NewExists As Boolean)
        If (NewExists) Then
            If Not (IniCollection.Exists(Section)) Then
                IniCollection.Add Section, NewDictionary
            End If
        Else
            If (IniCollection.Exists(Section)) Then
                IniCollection.Remove Section
            End If
        End If
    End Property
    
    Public Property Get KeyData(ByVal Section As String, ByVal KeyName As String) As String
        KeyData = ReadKey(Section, KeyName)
    End Property
    
    Public Property Let KeyData(ByVal Section As String, ByVal KeyName As String, ByVal NewData As String)
        WriteKey Section, KeyName, NewData
    End Property
    
    Public Property Get KeyDataEscaped(ByVal Section As String, ByVal KeyName As String) As String
        KeyDataEscaped = ReadKeyEscaped(Section, KeyName)
    End Property
    
    Public Property Let KeyDataEscaped(ByVal Section As String, ByVal KeyName As String, ByVal NewData As String)
        WriteKeyEscaped Section, KeyName, NewData
    End Property
    
    Public Sub RemoveKey(ByVal Section As String, ByVal KeyName As String)
        IniCollection(Section).Remove KeyName
    End Sub
    
    Public Sub RemoveSection(ByVal Section As String)
        IniCollection.Remove Section
    End Sub
    
    Public Sub WriteKeyEscaped(ByVal Section As String, ByVal KeyName As String, ByVal Data As String)
        WriteKey Section, KeyName, Escaped(Data)
    End Sub
    
    Private Sub UserControl_Initialize()
        Set IniCollection = New Dictionary
    End Sub
    
    Private Function Escaped(ByVal Data As String) As String
        Dim NewData As String
        NewData = Data
        NewData = Replace$(NewData, "\", "\\")
        NewData = Replace$(NewData, vbCr, "\r")
        NewData = Replace$(NewData, vbLf, "\n")
        NewData = Replace$(NewData, vbTab, "\t")
        NewData = Replace$(NewData, """", "\""")
        Escaped = NewData
    End Function
    
    Private Function UnEscaped(ByVal Data As String) As String
        On Error Resume Next
        Dim NewData As String
        Dim char As String
        Dim i As Long
        Dim BackSlash As Boolean
        If (Len(Data) = 0) Then
            UnEscaped = Data
            Exit Function
        End If
        For i = 1 To Len(Data)
            char = Mid$(Data, i, 1)
            If (BackSlash = True) Then
                Select Case char
                    Case "\"
                        NewData = NewData & "\"
                    Case "r"
                        NewData = NewData & vbCr
                    Case "n"
                        NewData = NewData & vbLf
                    Case "t"
                        NewData = NewData & vbTab
                    Case """"
                        NewData = NewData & """"
                    Case Else
                        If (IsNumeric(char)) Then
                            NewData = NewData & Chr(Mid$(Data, i, 3))
                            i = i + 2
                        Else
                            NewData = NewData & "\" & char
                        End If
                End Select
                BackSlash = False
                GoTo EndOfI
            Else
                If (char = "\") Then
                    BackSlash = True
                    GoTo EndOfI
                End If
                NewData = NewData & char
            End If
    EndOfI:
        Next i
        UnEscaped = NewData
    End Function
    
     
  10. kironchi

    kironchi Newcomer

    Joined:
    Apr 9, 2008
    Posts:
    16
    Referrals:
    0
    Sythe Gold:
    0
    Read INI Files from a webserver?

    covey for oncei might beable to help someone first of all what darathon wrote is right for reading but if u want to download the file then read it you should the urldownloadtofile or wehatever from urlmon.dll
    then for writing to it even even though i dotn know how for this part myself use the wininet.dll ftp api to upload it to ur site on accually writing in the .ini file format them ill get back to you
    if u can tell me how u want the ini file too look liek i might beable to help
    iwrite ini's all the time for DOS operating using batches i dont know if will work in windows
     
< I need small help please :) | Help with scripting for RSbot >


 
 
Adblock breaks this site