Convert Latitude/Longitude to decimal degrees - vbscript

i need to convert a large txt file with latitudes, and a large txt file with longitudes into decimal degrees.
The data i have is in the current format:
7d44'31.495"W for longitude
and
41d3'40.313"N for latitude
i need to convert both of this files to decimal degrees (using a script preferably). How can i do this?

Knowing nothing about *itudes, I can only give you a general idea about how
to solve your problem:
Use a RegExp to cut the numbers from your data and feed them in a trusted formula
To give you some confidence in my proposal, I show you, how I would tackle
the two sub-problems of your task.
(1) Apply a RegExp on an input string and calculate.
Based on this section
Conversion from DMS to Decimal Degree
Given a DMS (Degrees, Minutes, Seconds) coordinate such as W87°43'41",
convert it to a number of decimal degrees using the following method:
Calculate the total number of seconds:
43'41" = (43*60 + 41) = 2621 seconds.
The fractional part is total number of seconds divided by 3600:
2621 / 3600 = ~0.728056
Add fractional degrees to whole degrees to produce the final result:
87 + 0.728056 = 87.728056
Since it is a West longitude coordinate, negate the result.
The final result is -87.728056.
found here
Code:
Dim oFmt : Set oFmt = New cFormat
Dim oRE : Set oRE = New RegExp
' 0 1 2 3
oRE.Pattern = "^([W])(\d+)°(\d+)'(\d+)""$"
Dim aTests : aTests = Array( _
Array("W87°43'41""", -87.728056) _
)
Dim aTest
For Each aTest In aTests
Dim sInp : sInp = aTest(0)
Dim nExp : nExp = aTest(1)
Dim oMTS : Set oMTS = oRE.Execute(sInp)
Dim sMsg
If 1 <> oMTS.Count Then
sMsg = oFmt.formatTwo("|{0}| didn't match /{1}/", sInp, oRE.Pattern)
Else
Dim sLoLa : sLoLa = oMTS(0).SubMatches(0)
Dim nDegrees : nDegrees = CDbl(oMTS(0).SubMatches(1))
Dim nMinutes : nMinutes = CDbl(oMTS(0).SubMatches(2))
Dim nSeconds : nSeconds = CDbl(oMTS(0).SubMatches(3))
Dim nRes
' Calculate the total number of seconds:
' 43'41" = (43*60 + 41) = 2621 seconds.
nRes = nMinutes * 60 + nSeconds
' WScript.Echo "***", nRes
' The fractional part is total number of seconds divided by 3600:
' 2621 / 3600 = ~0.728056
nRes = nRes / 3600
' WScript.Echo "***", nRes
' Add fractional degrees to whole degrees to produce the final result:
' 87 + 0.728056 = 87.728056
nRes = nDegrees + nRes
' WScript.Echo "***", nRes
' Since it is a West longitude coordinate, negate the result.
' The final result is -87.728056.
Select Case sLoLa
Case "W"
nRes = -nRes
End Select
sMsg = oFmt.formatArray(_
"{0,-12}: R: {1,12:N6} E: {2,12:N6} D: {3,12:N6}" _
, Array(sInp, nRes, nExp, nRes - nExp) _
)
End If
WScript.Echo sMsg
Next
Output:
Step00 - conversion a la wikipedia
================================================================
W87°43'41" : R: -87,728056 E: -87,728056 D: 0,000000
================================================================
xpl.vbs: Erfolgreich beendet. (0) [0.08594 secs]
Starting from an input sample, I derive (a first attempt at) the Regexp
pattern
" W 87 ° 43 ' 41 "" "
' 0 1 2 3
oRE.Pattern = "^([W])(\d+)°(\d+)'(\d+)""$"
For your data, something like this
" 7 d 44 ' 31.495 "" W "
" 41 d 3 ' 40.313 "" N "
' 0 1 2 3
oRE.Pattern = "^(\d+)d(\d+)'(\d+\.\d+)""([WN])$"
may be appropriate.
To get the parts captured by the RegExps group ()s, I access and convert
the match's submatches
Dim sLoLa : sLoLa = oMTS(0).SubMatches(0)
Dim nDegrees : nDegrees = CDbl(oMTS(0).SubMatches(1))
Dim nMinutes : nMinutes = CDbl(oMTS(0).SubMatches(2))
Dim nSeconds : nSeconds = CDbl(oMTS(0).SubMatches(3))
Then it's just computing according to the algorithm/formulas stolen
from Wikipedia (see the code/comments).
(2) Get the data from your files
If the files are not to big, you can .ReadAll() them into memory and
apply the RegExp in multiline mode:
Dim oFmt : Set oFmt = New cFormat
Dim oRE : Set oRE = New RegExp
oRE.Global = True
oRE.Multiline = True
' 0 1 2 3
oRE.Pattern = "^(\d+)d(\d+)'(\d+\.\d+)""([WN])$"
Dim sAll : sAll = goFS.OpenTextFile("..\data\f00.txt").ReadAll()
WScript.Echo sAll
WScript.Echo oFmt.formatArray( _
"|{0,-5}|{1,-11}|{2,-11}|{3,-15}|" _
, Array("LoLa", "Degrees", "Minutes", "Seconds") _
)
Dim oMTS : Set oMTS = oRE.Execute(sAll)
Dim oMT
For Each oMT In oMTS
Dim sLoLa : sLoLa = oMT.SubMatches(3)
Dim nDegrees : nDegrees = CDbl(oMT.SubMatches(0))
Dim nMinutes : nMinutes = CDbl(oMT.SubMatches(1))
Dim nSeconds : nSeconds = CDbl(oMT.SubMatches(2))
WScript.Echo oFmt.formatArray( _
"|{0,-5}|{1,11:N2}|{2,11:N2}|{3,15:N6}|" _
, Array(sLoLa, nDegrees, nMinutes, nSeconds) _
)
Next
output:
======================================================
7d44'31.495"W
41d3'40.313"N
|LoLa |Degrees |Minutes |Seconds |
|W | 7,00| 44,00| 31,495000|
|N | 41,00| 3,00| 40,313000|
======================================================
Get the cFormat class from here

Related

How to make Natural Sort in Classic ASP? [duplicate]

I want to sort below items using natural sorting:
"Z1","Z3","Z2","Z20","Z10"
After sorting, I am expecting the order below:
"Z1","Z2","Z3","Z10","Z20"
When I tried using array list,
Set oAlist=CreateObject("System.Collections.ArrayList")
oAlist.sort
I am getting a sorting result based on ASCII:
Z1,Z10,Z2,Z20,Z3
Please help me on how to do this natural sorting using vb script
For theory see here (follow the links!). Practical demo
recordset:
Option Explicit
Const adInteger = 3 ' 00000003
Const adVarChar = 200 ' 000000C8
Dim sInp : sInp = "Z1,Z3,Z2,Z20,Z10"
Dim aInp : aInp = Split(sInp, ",")
WScript.Echo "A:", Join(aInp)
Dim oRS : Set oRS = CreateObject("ADODB.Recordset")
oRS.Fields.Append "Word", adVarChar, 50
oRS.Fields.Append "Length", adInteger
oRS.Open
Dim sWord
For Each sWord In aInp
oRS.AddNew
oRS.Fields("Word").value = Left(sWord, 1)
oRS.Fields("Length").value = CInt(Mid(sWord, 2))
oRS.UpDate
Next
oRS.Sort = "Word, Length"
Dim aTable : aTable = oRS.GetRows()
ReDim aOut(UBound(aTable, 2))
Dim i
For i = 0 To UBound(aOut)
aOut(i) = aTable(0, i) & aTable(1, i)
Next
WScript.Echo "B:", Join(aOut)
ArrayList
Option Explicit
Dim sInp : sInp = "Z1,Z3,Z2,Z20,Z10,E1,D3,C2,B20,A10"
Dim aInp : aInp = Split(sInp, ",")
WScript.Echo "A:", Join(aInp)
Dim oNAL : Set oNAL = CreateObject( "System.Collections.ArrayList" )
Dim oSB : Set oSB = CreateObject( "System.Text.StringBuilder" )
Dim sWord
For Each sWord In aInp
oSB.AppendFormat_2 "{0}{1,4}", Left(sWord, 1), CInt(Mid(sWord, 2))
sWord = oSB.ToString()
oSB.Length = 0
oNAL.Add sWord
Next
oNAL.Sort
ReDim aOut(oNAL.Count - 1)
Dim i
For i = 0 To UBound(aOut)
aOut(i) = Left(oNAL(i), 1) & CInt(Mid(oNAL(i), 2))
Next
WScript.Echo "B:", Join(aOut)

VBA convert a binary image to a base64 encoded string for a webpage

I am trying to read in a JPG file and convert the file to a base64 encoded string that can be used as an embedded jpeg on a web page. I found two functions on the web for base64 encoding/decoding in VBA that appear to be well-accepted. The encode/decode process yields my original binary string, so the functions appear to be at least somewhat correct. However the base64 string I am getting is no where near what I get when I use an online tool to convert my image to base64.
The base64 string should start: "/9j/4AAQSkZJRgABAQEAUgBSAAD". Instead it is starting with: "Pz8/Pz9BYT8/AD8/Pz8/Pz8/Pz8/Pz8/Pz8". I'm lost as to why I'm not getting the former result and why I'm getting the latter. Am I doing something wrong in my reading of the binary file?
Here is my code:
Sub TestBase64()
Dim bytes, b64
With CreateObject("ADODB.Stream")
.Open
.Type = ADODB.adTypeBinary
.LoadFromFile "c:\temp\TestPic.jpg"
bytes = .Read
.Close
End With
Debug.Print bytes
b64 = Base64Encode(bytes)
Debug.Print vbCrLf + vbCrLf
Debug.Print b64
Debug.Print vbCrLf + vbCrLf
Debug.Print Base64Decode(CStr(b64))
End Sub
' Decodes a base-64 encoded string (BSTR type).
' 1999 - 2004 Antonin Foller, http://www.motobit.com
' 1.01 - solves problem with Access And 'Compare Database' (InStr)
Function Base64Decode(ByVal base64String)
'rfc1521
'1999 Antonin Foller, Motobit Software, http://Motobit.cz
Const Base64 = "ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz0123456789+/"
Dim dataLength, sOut, groupBegin
'remove white spaces, If any
base64String = Replace(base64String, vbCrLf, "")
base64String = Replace(base64String, vbTab, "")
base64String = Replace(base64String, " ", "")
'The source must consists from groups with Len of 4 chars
dataLength = Len(base64String)
If dataLength Mod 4 <> 0 Then
Err.Raise 1, "Base64Decode", "Bad Base64 string."
Exit Function
End If
' Now decode each group:
For groupBegin = 1 To dataLength Step 4
Dim numDataBytes, CharCounter, thisChar, thisData, nGroup, pOut
' Each data group encodes up To 3 actual bytes.
numDataBytes = 3
nGroup = 0
For CharCounter = 0 To 3
' Convert each character into 6 bits of data, And add it To
' an integer For temporary storage. If a character is a '=', there
' is one fewer data byte. (There can only be a maximum of 2 '=' In
' the whole string.)
thisChar = Mid(base64String, groupBegin + CharCounter, 1)
If thisChar = "=" Then
numDataBytes = numDataBytes - 1
thisData = 0
Else
thisData = InStr(1, Base64, thisChar, vbBinaryCompare) - 1
End If
If thisData = -1 Then
Err.Raise 2, "Base64Decode", "Bad character In Base64 string."
Exit Function
End If
nGroup = 64 * nGroup + thisData
Next
'Hex splits the long To 6 groups with 4 bits
nGroup = Hex(nGroup)
'Add leading zeros
nGroup = String(6 - Len(nGroup), "0") & nGroup
'Convert the 3 byte hex integer (6 chars) To 3 characters
pOut = Chr(CByte("&H" & Mid(nGroup, 1, 2))) + _
Chr(CByte("&H" & Mid(nGroup, 3, 2))) + _
Chr(CByte("&H" & Mid(nGroup, 5, 2)))
'add numDataBytes characters To out string
sOut = sOut & Left(pOut, numDataBytes)
Next
Base64Decode = sOut
End Function
Function Base64Encode(inData)
'rfc1521
'2001 Antonin Foller, Motobit Software, http://Motobit.cz
Const Base64 = "ABCDEFGHIJKLMNOPQRSTUVWXYZabcdefghijklmnopqrstuvwxyz0123456789+/"
Dim cOut, sOut, i
'For each group of 3 bytes
For i = 1 To Len(inData) Step 3
Dim nGroup, pOut, sGroup
'Create one long from this 3 bytes.
nGroup = &H10000 * Asc(Mid(inData, i, 1)) + _
&H100 * MyASC(Mid(inData, i + 1, 1)) + MyASC(Mid(inData, i + 2, 1))
'Oct splits the long To 8 groups with 3 bits
nGroup = Oct(nGroup)
'Add leading zeros
nGroup = String(8 - Len(nGroup), "0") & nGroup
'Convert To base64
pOut = Mid(Base64, CLng("&o" & Mid(nGroup, 1, 2)) + 1, 1) + _
Mid(Base64, CLng("&o" & Mid(nGroup, 3, 2)) + 1, 1) + _
Mid(Base64, CLng("&o" & Mid(nGroup, 5, 2)) + 1, 1) + _
Mid(Base64, CLng("&o" & Mid(nGroup, 7, 2)) + 1, 1)
'Add the part To OutPut string
sOut = sOut + pOut
'Add a new line For Each 76 chars In dest (76*3/4 = 57)
'If (I + 2) Mod 57 = 0 Then sOut = sOut + vbCrLf
Next
Select Case Len(inData) Mod 3
Case 1: '8 bit final
sOut = Left(sOut, Len(sOut) - 2) + "=="
Case 2: '16 bit final
sOut = Left(sOut, Len(sOut) - 1) + "="
End Select
Base64Encode = sOut
End Function
Function MyASC(OneChar)
If OneChar = "" Then MyASC = 0 Else MyASC = Asc(OneChar)
End Function
That's some lengthy way to encode. I prefer this:
You Need to add reference to Microsoft XML, v6.0 (or v3.0)
Sub TestBase64()
Dim bytes, b64
With CreateObject("ADODB.Stream")
.Open
.Type = ADODB.adTypeBinary
.LoadFromFile "c:\temp\TestPic.jpeg"
bytes = .Read
.Close
End With
Debug.Print bytes
b64 = EncodeBase64(bytes)
Debug.Print vbCrLf + vbCrLf
Debug.Print Left(b64, 100)
' Debug.Print vbCrLf + vbCrLf
' Debug.Print Base64Decode(CStr(b64))
End Sub
Private Function EncodeBase64(bytes) As String
Dim objXML As MSXML2.DOMDocument
Dim objNode As MSXML2.IXMLDOMElement
Set objXML = New MSXML2.DOMDocument
Set objNode = objXML.createElement("b64")
objNode.DataType = "bin.base64"
objNode.nodeTypedValue = bytes
EncodeBase64 = objNode.Text
Set objNode = Nothing
Set objXML = Nothing
End Function
Output (first few characters): /9j/4AAQSkZJRgABAQEAYABgAAD

VBscript - How to save TXT in UTF-8

how can I write UTF-8 encoded strings to a textfile from VBScript? I have tried some variations but no success. So I need the text file saved in UTF-8 format. thanks in advance for your all help.
Output :
CN=™ser1 D˜,OU=TEST,OU=TEST,OU=Users,OU=contoso,DC=contoso,DC=local;10.01.2012 01:00:00
CN=Gšbson ¦LU,OU=TEST,OU=TEST,OU=Users,OU=contoso,DC=contoso,DC=local;20.12.2016 18:55:51
CN=™ZL €ET˜,OU=TEST,OU=TEST,OU=Users,OU=contoso,DC=contoso,DC=local;27.08.2013
type ExpReport.txt (as you can see no special characters)
CN=ser1 D,OU=TEST,OU=TEST,OU=Users,OU=contoso,DC=contoso,DC=local;10.01.2012 01:00:00
CN=Gbson LU,OU=TEST,OU=TEST,OU=Users,OU=contoso,DC=contoso,DC=local;20.12.2016 18:55:51
CN=ZL ET,OU=TEST,OU=TEST,OU=Users,OU=contoso,DC=contoso,DC=local;27.08.2013
cscript //nologo AcctsExpire.vbs > ExpReport.txt
Here is my code :
Option Explicit
Dim adoConnection, adoCommand
Dim objRootDSE, strDNSDomain, strFilter, strQuery, adoRecordset
Dim strDN, objShell, lngBiasKey, lngBias
Dim lngDate, objDate, dtmAcctExp, k
' Obtain local time zone bias from machine registry.
Set objShell = CreateObject("Wscript.Shell")
lngBiasKey = objShell.RegRead("HKLM\System\CurrentControlSet\Control\" _
& "TimeZoneInformation\ActiveTimeBias")
If (UCase(TypeName(lngBiasKey)) = "LONG") Then
lngBias = lngBiasKey
ElseIf (UCase(TypeName(lngBiasKey)) = "VARIANT()") Then
lngBias = 0
For k = 0 To UBound(lngBiasKey)
lngBias = lngBias + (lngBiasKey(k) * 256^k)
Next
End If
' Use ADO to search the domain for all users.
Set adoConnection = CreateObject("ADODB.Connection")
Set adoCommand = CreateObject("ADODB.Command")
adoConnection.Provider = "ADsDSOOBject"
adoConnection.Open "Active Directory Provider"
Set adoCommand.ActiveConnection = adoConnection
' Determine the DNS domain from the RootDSE object.
Set objRootDSE = GetObject("LDAP://RootDSE")
strDNSDomain = objRootDSE.Get("DefaultNamingContext")
' Filter to retrieve all user objects with accounts
' that expire.
strFilter = "(&(objectCategory=person)(objectClass=user)" _
& "(!accountExpires=0)(!accountExpires=9223372036854775807))"
strQuery = "<LDAP://" & strDNSDomain & ">;" & strFilter _
& ";distinguishedName,accountExpires;subtree"
' Run the query.
adoCommand.CommandText = strQuery
adoCommand.Properties("Page Size") = 100
adoCommand.Properties("Timeout") = 30
adoCommand.Properties("Cache Results") = False
Set adoRecordset = adoCommand.Execute
' Enumerate the recordset.
Do Until adoRecordset.EOF
strDN = adoRecordset.Fields("distinguishedName").Value
lngDate = adoRecordset.Fields("accountExpires")
Set objDate = lngDate
dtmAcctExp = Integer8Date(objDate, lngBias)
Wscript.Echo strDN & ";" & dtmAcctExp
adoRecordset.MoveNext
Loop
adoRecordset.Close
' Clean up.
adoConnection.Close
Function Integer8Date(ByVal objDate, ByVal lngBias)
' Function to convert Integer8 (64-bit) value to a date, adjusted for
' local time zone bias.
Dim lngAdjust, lngDate, lngHigh, lngLow
lngAdjust = lngBias
lngHigh = objDate.HighPart
lngLow = objdate.LowPart
' Account for bug in IADslargeInteger property methods.
If (lngLow < 0) Then
lngHigh = lngHigh + 1
End If
If (lngHigh = 0) And (lngLow = 0) Then
lngAdjust = 0
End If
lngDate = #1/1/1601# + (((lngHigh * (2 ^ 32)) _
+ lngLow) / 600000000 - lngAdjust) / 1440
Integer8Date = CDate(lngDate)
End Function
Last Update :
Issue is resolved.
cscript //nologo AcctsExpire.vbs //U > ExpReport.txt
Also WSCRIPT AcctsExpire.vbs displays correct output.

"integer out of range" error in a for next statement

I've gone nuts on this, and I'm sure the error is right in front of me, I just cant see it. appreciate all the help in debugging the statements below.
I have multiple slides in a ppt presentation. in some of the slides, there is a star shape, and a textbox with text "Hold" or "Yearly". I want to change the color of the star only if there is no textbox with "Hold" or "Yearly".
Sub Set_Star_Shape_Color_Green_Test()
Dim PPApp As Object ' As PowerPoint.Application
Dim PPPres As Object ' As PowerPoint.Presentation
Dim PPSlide As Object ' As PowerPoint.Slide
Dim iShpCnt1 As Integer
Dim iShpCnt2 As Integer
Dim iShpCnt3 As Integer
Dim iSlideCnt As Integer
Dim iBoxTopPos As Integer
Dim sHold As String
Dim sStar As String
Dim sTbox As String
Dim sTColor As String
Dim oShp As Shape
Set PPApp = GetObject(, "Powerpoint.Application")
Set PPPres = PPApp.ActivePresentation
Set PPSlide = PPPres.Slides _
(PPApp.ActiveWindow.Selection.SlideRange.SlideIndex)
iShpCnt0 = PPSlide.Shapes.Count
For iShpCnt1 = 1 To iShpCnt0 'PPSlide.Shapes.Count
iBoxTopPos = 260
' iSlideCnt = 2 removed
sHold = ""
sStar = ""
iShpCnt1 = 1
For iShpCnt1 = 1 To PPSlide.Shapes.Count
If iShpCnt1 <= PPSlide.Shapes.Count Then
**Set oSh = PPApp.ActivePresentation.Slides(iSlideCnt).Shapes(iShpCnt1) ' this is where i am getting the integer out of range error**
If oSh.Name.Text Like "*Hold*" Or oSh.Name.Text Like "*Yearly*" Then
sHold = oSh.Name
End If
If oSh.Name Like "*Star*" Then
sStar = oSh.Name
End If
End If
Next
For iShpCnt2 = 1 To iShpCnt0 ' this fixed the error
Set oSh = PPApp.ActivePresentation.Slides(iSlideCnt).Shapes(iShpCnt2)
If oSh.Name Like "*Star*" And sHold = "" Then
oSh.Fill.ForeColor.RGB = RGB(50, 205, 50) ' change the color to green
End If
Next
' go to next slide
If PPSlide.SlideIndex + 1 < PPPres.Slides.Count Then
PPApp.ActiveWindow.View.GotoSlide PPSlide.SlideIndex + 1
Set PPSlide = PPPres.Slides _
(PPApp.ActiveWindow.Selection.SlideRange.SlideIndex + 1)
End If
Next
' Clean up
Set PPSlide = Nothing
Set PPPres = Nothing
Set PPApp = Nothing
End Sub
You are setting the iterator to two.
For iSlideCnt = 1 To PPPres.Slides.Count
iBoxTopPos = 260
iSlideCnt = 2 <--- right here
It will go out of bounds if you have just one slide.

A small problem to solve in VBscript [closed]

Closed. This question needs to be more focused. It is not currently accepting answers.
Want to improve this question? Update the question so it focuses on one problem only by editing this post.
Closed 4 years ago.
Improve this question
Can you please try this in VBScript:
You got a text file with several currency amounts, every one in one line on following format:
DESCRIPTION Date Amount
McDonalds 2011-01-01 20.00
Clothing Store 2011-01-02 30.00
Try to build a program to read that text file and sum all values found in there.
First (pedestrian) attempt:
Option Explicit
Dim goFS : Set goFS = CreateObject( "Scripting.FileSystemObject" )
Dim sFSpec : sFSpec = goFS.GetAbsolutePathName( "..\data\expenses.csv" )
WScript.Echo goFS.OpenTextFile( sFSpec ).ReadAll()
WScript.Echo "---------"
Dim tsIn : Set tsIn = goFS.OpenTextFile( sFSpec )
Dim nSum : nSum = 0.0
Dim sLine : sLine = tsIn.ReadLine()
Do Until tsIn.AtEndOfStream
sLine = tsIn.ReadLine()
Dim aFields : aFields = Split( sLine, "," )
If 2 = UBound( aFields ) Then
nSum = nSum + CDbl( aFields( 2 ) ) ' en_us, ...
' nSum = nSum + CDbl( Replace( aFields( 2 ), ".", "," ) ) ' locale de_de, ...
End If
Loop
tsIn.Close
WScript.Echo "Sum:", nSum
Output:
lineLoop - sum values (line loop)
---------------------------------------------------
"DESCRIPTION","Date","Amount"
"McDonalds",2011-01-01,20.00
"Clothing Store",2011-01-02,30.00
"paying programmer",2011-07-09,47.11
---------
Sum: 97.11
===================================================
xpl.vbs: Erfolgreich beendet. (0) [ 0,01563 secs ]
Second attempt (using a regular expression):
Dim sFSpec : sFSpec = goFS.GetAbsolutePathName( "..\data\expenses.csv" )
Dim sAll : sAll = goFS.OpenTextFile( sFSpec ).ReadAll()
WScript.Echo sAll
WScript.Echo "---------"
Dim reAmount : Set reAmount = New RegExp
reAmount.Global = True
reAmount.MultiLine = True
reAmount.Pattern = ",(\d+\.\d+)\r$"
Dim nSum : nSum = 0.0
Dim oMTS : Set oMTS = reAmount.Execute( sAll )
Dim oMT
For Each oMT In oMTS
nSum = nSum + CDbl( oMT.Submatches(0) ) ' en_us, ...
' nSum = nSum + CDbl( Replace( oMT.Submatches(0), ".", "," ) ) ' locale de_de, ...
Next
WScript.Echo "Sum:", nSum
Third attempt (ADO/Text driver):
schema.ini:
[expenses.csv]
Format=CSVDelimited
ColNameHeader=True
DateTimeFormat=YYYY-MM-DD
CharacterSet=ANSI
Col1=DESCRIPTION CHAR
Col2=Date DATE
Col3=Amount FLOAT
Code:
Const adClipString = 2
Dim sTDir : sTDir = goFS.GetAbsolutePathName( "..\data" )
Dim oTDb : Set oTDb = CreateObject( "ADODB.Connection" )
Dim sCS : sCS = Join( Array( _
"Provider=Microsoft.Jet.OLEDB.4.0" _
, "Data Source=" & sTDir _
, "Extended Properties=" & Join( Array( _
"text" _
), ";" ) _
), ";" )
oTDB.Open sCS
WScript.Echo oTDb.Execute( "SELECT * FROM [expenses.csv]" ) _
.GetString( adClipString, , vbTab, vbCrLf, "" )
WScript.Echo oTDb.Execute( "SELECT SUM(Amount) AS [Sum] FROM [expenses.csv]" ) _
.GetString( adClipString, , vbTab, vbCrLf, "" )
WScript.Echo oTDb.Execute( "SELECT SUM(Amount) AS [Sum] FROM [expenses.csv] WHERE MONTH([Date]) = 7" ) _
.GetString( adClipString, , vbTab, vbCrLf, "" )
oTDb.Close
Output:
McDonalds 01.01.2011 20
Clothing Store 02.01.2011 30
paying programmer 09.07.2011 47,11
97,11
47,11
===================================================
xpl.vbs: Erfolgreich beendet. (0) [ 0,23438 secs ]
or - with a bit of additional work:
useAdoText - sum values (ADO/Text driver)
----------------------------------------------------------------------------
----------------------------------------------------------------------------
SELECT * FROM [expenses.csv]
----------------------------------------------------------------------------
|DESCRIPTION |Date |Amount|
|McDonalds |01.01.2011| 20|
|Clothing Store |02.01.2011| 30|
|paying programmer|09.07.2011| 47,11|
----------------------------------------------------------------------------
----------------------------------------------------------------------------
SELECT SUM(Amount) AS [Sum] FROM [expenses.csv]
----------------------------------------------------------------------------
|Sum |
|97,11|
----------------------------------------------------------------------------
----------------------------------------------------------------------------
SELECT SUM(Amount) AS [Sum] FROM [expenses.csv] WHERE MONTH([Date]) = 7
----------------------------------------------------------------------------
|Sum |
|47,11|
----------------------------------------------------------------------------
============================================================================
xpl.vbs: Erfolgreich beendet. (0) [ 0,25000 secs ]

Resources