How to Append onto Variables?
I am needing to figure out how to "append" one variable on another variable then send this information out via Serial to a VB program. I have the communication between the computer and the prop working perfectly, but can't figure out how to append variables successfully.
I am using a function that I put together based on this post : http://forums.parallax.com/showthread.php?124308-Newb-question-Append-to-a-variable&highlight=append+variable
Here is a stripped version of my code.
So lets say Time_Count_Hours = 22 and pulseCount = 1234.... All that I need to have happen is where it has :
myArray[countpointer] := AppendVar(Time_Count_Hours, pulseCount)
Should turn out to be something like this :
myArray[countpointer] := 22:1234
So when I send it to the computer through the serial communication using this code, the VB program can sort it all out properly. :
I am using a function that I put together based on this post : http://forums.parallax.com/showthread.php?124308-Newb-question-Append-to-a-variable&highlight=append+variable
Here is a stripped version of my code.
VAR
BYTE Time_Count_Hours
BYTE countpointer
LONG pulseData[255]
LONG pulseCount
long var1
long var2
long var3
byte varall[255]
PUB Main
......... Other code
myArray[countpointer] := AppendVar(Time_Count_Hours, pulseCount)
PUB AppendVar(variable1, variable2)
var1 := variable1
var2 := string(":")
var3 := variable2
bytemove(@varall, var1, strsize(var1) + 1)
bytemove(@varall + strsize(@varall), var2, strsize(var2) + 1)
bytemove(@varall + strsize(@varall), var3, strsize(var3) + 1)
return (@varall)
So lets say Time_Count_Hours = 22 and pulseCount = 1234.... All that I need to have happen is where it has :
myArray[countpointer] := AppendVar(Time_Count_Hours, pulseCount)
Should turn out to be something like this :
myArray[countpointer] := 22:1234
So when I send it to the computer through the serial communication using this code, the VB program can sort it all out properly. :
if command == 3
' Send pulseData Array
Ser.tx("D")
i := 0
repeat i from 0 to countpointer
Ser.str(pulseData[i]) ' not sure if this is the correct way or if I need to add an @ to pulseData
Ser.tx(",") ' comma delimited to separate array values in VB program.
i++

Comments
Ser.Decx(0, Time_Count_Hours, 2) Ser.Tx(":") Ser.Decx(0, pulseCount, 4)This above assumes you setup port #0 to communicate with the PC.
The above will output two zero padded digits with the value "Time_Count_Hours", followed by a ":" and then four digits (again zero padded) of the variable "pulseCount".
Your PC likely wants ASCII characters. The code you posted doesn't convert the variables to ASCII. Most serial objects have a "dec" method that does this converstion for you. In your case, I think you want the numbers zero padded so I chose a serial object that has a method to do this ("decx").
You could adapt "decx" to use with a different serial object. I'm sure I have a "zero pad" method somewhere in case you don't want to use the four port object (though it's a very good object to learn to use).
PUB Decx(value, digits, localPtr) '' Prints zero-padded, signed-decimal string '' -- if value is negative, field width is digits+1 result := decl(value, digits, 2, localPtr) PUB Decl(value, digits, flag, localPtr) | localI, localX '' DWD Fixed with FDX 1.2 code digits := 1 #> digits <# 10 localX := value == NEGX 'Check for max negative if value < 0 value := ||(value + localX) 'If negative, make positive; adjust for max negative byte[localPtr++] := "-" localI := 1_000_000_000 if flag & 3 if digits < 10 ' less than 10 digits? repeat (10 - digits) ' yes, adjust divisor localI /= 10 repeat digits if value => localI byte[localPtr++] := value / localI + "0" + localX * (localI == 1) value //= localI result~~ elseif (localI == 1) OR result OR (flag & 2) byte[localPtr++] := "0" elseif flag & 1 byte[localPtr++] := " " localI /= 10 result := localPtrUsing the above methods, you could load your numbers to a buffer "varall" this way.
Edit: I posted this before seeing your last post. Let me know if you need more clarification.
Edit again: I just realized there's a better way to use the above code. I'll rewrite the example in a couple of minutes.
CON DATA_SET_SIZE = 8 BUFFER_SIZE = 255 VAR long Time_Count_Hours, pulseCount, globalPtr byte varall[BUFFER_SIZE] PUB Setup ' set up serial and other objects needed globalPtr := @varall MainLoop PUB MainLoop repeat while globalPtr < @varall + BUFFER_SIZE - DATA_SET_SIZE ' prevent overflow of buffer if 'new data to record globalPtr := Decx(Time_Count_Hours, 2, globalPtr) byte[globalPtr++] := ":" globalPtr := Decx(pulseCount, 4, globalPtr) byte[globalPtr++] := "," ' assumes comma delimited if ' time to send to computer Ser.str(@varall) ' send data to computer bytefill(@varall, 0, BUFFER_SIZE) ' clear buffer to make sure you have a terminating zero globalPtr := @varall ' reset pointer to start of bufferThere are of course other ways to do this. You could alternatively save your data in arrays of longs and then output them with serial "dec" or "decx" methods when the computer requests the data.
Edit: I just noticed I don't have any type of error recovery if the buffer overflows. You'd probably want it to display an error message and wait for the PC to request the data it does have.
What does your PC expect? The method I posted zero pads the data so the characters used will always be the same. If your program doesn't need zero padded data you could use the method below.
The "decl" method above will also output non-padded decimal characters. Just change all the "Decx" calls to "Decl" with the "flag" parameter set to zero and the "digits" parameter set to 10 (or the largest number of digits expected). The "globalPtr" should be adjusted automatically for you.
The methods "decx" and "decl" are methods I modified to send their outputs to a buffer instead of a serial terminal. I didn't write most of it and I still don't understand how it all works (particularly the flags part).
BTW, you may notice the "decx" method just sets the "flag" parameter (of "decl") to two, to produce zero padded output. If the "flag" parameter of "decl" is set to one, the output will be space padded. (Somewhere, I have a version that takes a character as a parameter and uses that character to pad the output.)
Edit: I think there are objects in the Propeller Tool library that will do a lot of what I just posted. I think the object "Numbers" (or something like that) have these type of methods. I have a bad habit of duplicating methods that have been done previously (and better) by someone else.
CON _CLKMODE = XTAL1 + pll16x _XINFREQ = 5_000_000 LED = 0 Sensor = 1 CountDelay = 10 SendInterval = 5000 VAR BYTE countpointer LONG pulseData[255] LONG pulseCount LONG count1 BYTE Time_Count_Hours BYTE Time_Count_Minutes BYTE Time_Count_Seconds LONG pulsewidth LONG PulseCounterStack[100] LONG readDataStack[100] LONG receivedData LONG TimeStack[100] long var1 long var2 long var3 byte varall[255] OBJ Ser : "FullDuplexSerialPlus" PUB Main pulseCount := 0 Time_Count_Hours := 0 Time_Count_Minutes := 0 Time_Count_Seconds := 0 countpointer := 0 ' testing only! 'pulseData[0] := 1234 'pulseData[0][1] := 267 'pulseData[0][2] := 12 'pulseData[1][0] := 5678 'pulseData[1][1] := 267 'pulseData[1][2] := 13 'countpointer := 1 Ser.start(17, 16, 0, 9600) cognew(TimeKeeper, @TimeStack) cognew(PulseCounter, @PulseCounterStack) cognew(readData, @readDataStack) repeat if Time_Count_Seconds == 60 Time_Count_Seconds := 0 Time_Count_Minutes++ pulseData[countpointer] := AppendVar(Time_Count_Hours, pulseCount) pulseCount := 0 countpointer++ if Time_Count_Minutes == 60 Time_Count_Minutes := 0 Time_Count_Hours++ if Time_Count_Hours := 24 Time_Count_Hours := 0 waitcnt(clkfreq / 1000 * 200 + cnt) PUB TimeKeeper repeat Time_Count_Seconds++ waitcnt(clkfreq / 1000 * 1000 + cnt) PUB readData | command, i repeat repeat until Ser.rx == "#" waitcnt(clkfreq / 1000 * 10 + cnt) command := Ser.rx if command == 1 Time_Count_Hours := Ser.rx Time_Count_Minutes := Ser.rx Time_Count_Seconds := Ser.rx Ser.tx("S") if command == 2 Ser.tx("#") Ser.dec(pulsewidth) if command == 3 ' Send pulseData Array Ser.tx("D") i := 0 repeat i from 0 to countpointer Ser.str(pulseData[i]) Ser.tx(",") 'i++ if command == 4 Ser.tx("C") Ser.dec(pulseCount) if command == 5 ' Clear pulseData Array Ser.tx("E") bytefill(@pulseData,0,countpointer - 1) countpointer := 0 Ser.rxflush PUB PulseCounter | updated, cnt1, cnt2 ' 65825 counts per 1 second count1 := 0 repeat updated := 0 dira[LED]~~ repeat while ina[Sensor] == 1 if updated == 0 cnt2 := cnt pulseCount++ updated := 1 outa[LED] := 1 waitcnt(clkfreq / 1000 * 10 + cnt) if count1 > 0 pulsewidth := (cnt2 - cnt1) / (clkfreq / 10000) count1 := 0 if updated == 1 cnt1 := cnt count1++ outa[LED] := 0 PUB AppendVar(variable1, variable2) bytefill(@varall, 0, 255) ' clear buffer to make sure you have a terminating zero Decx(variable1, 2, @varall) varall[3] := ":" Decx(variable2, 4, @varall + 4) return (@varall) PUB Decx(value, digits, localPtr) '' Prints zero-padded, signed-decimal string '' -- if value is negative, field width is digits+1 result := decl(value, digits, 2, localPtr) PUB Decl(value, digits, flag, localPtr) | localI, localX '' DWD Fixed with FDX 1.2 code digits := 1 #> digits <# 10 localX := value == NEGX 'Check for max negative if value < 0 value := ||(value + localX) 'If negative, make positive; adjust for max negative byte[localPtr++] := "-" localI := 1_000_000_000 if flag & 3 if digits < 10 ' less than 10 digits? repeat (10 - digits) ' yes, adjust divisor localI /= 10 repeat digits if value => localI byte[localPtr++] := value / localI + "0" + localX * (localI == 1) value //= localI result~~ elseif (localI == 1) OR result OR (flag & 2) byte[localPtr++] := "0" elseif flag & 1 byte[localPtr++] := " " localI /= 10 result := localPtrAnd here is my VB program code :
Option Explicit Private Declare Sub Sleep Lib "kernel32" (ByVal dwMilliseconds As Long) Dim receivingdata As String Dim incomingdata As String Dim receiveInterval As Integer Dim currentWattage As Long Dim currentTime As String Dim count1 As Integer Dim Hours As Long Dim Minutes As Long Dim Seconds As Long Dim LastSentCommand As Integer Dim LockSerial As Integer Dim olddatatest As String Dim t4counter As Integer Private strDatabaseName As String Private strDBCursorType As String Private strDBLockType As String Private strDBOptions As String Private strSQL As String Private rs As ADODB.Recordset Private cn As ADODB.Connection Private Sub Form_Load() Connect2Chip End Sub Private Sub Connect2Chip() receiveInterval = 1 Dim myport As String If MSComm1.PortOpen = False Then 'On Error GoTo No_Connect 'myport = InputBox("Which COM Port?", "COM Port Selection", "1") With MSComm1 .CommPort = 1 .Settings = "9600,n,8,1" .RThreshold = 1 .InBufferSize = 1024 .InputLen = 1 '.InputMode = 0 - comInputModeText .PortOpen = True End With Timer2.Interval = 100 Timer2.Enabled = True Timer4.Enabled = True constatus.Caption = "Connected to Chip" incomingdata = "" Send2Chip (1) Else If (MSComm1.PortOpen = True) Then MSComm1.PortOpen = False End If constatus.Caption = "Disconnected" End If On Error GoTo 0 Exit Sub No_Connect: ' Dim response ' response = MsgBox("Error: Could not connect.", vbExclamation + vbOKOnly) On Error GoTo 0 constatus.Caption = "Failed to connect! Attempt again in 1 second" Sleep (1000) Connect2Chip End Sub Private Sub Form_Unload(Cancel As Integer) If MSComm1.PortOpen = True Then MSComm1.PortOpen = False End Sub Private Sub MSComm1_OnComm() Dim incoming As String Dim olddata As String Dim currentTime As String Dim kwhstring As String Dim kwharray() As String Dim i As Integer Dim sqldate As String On Error GoTo 0 If MSComm1.CommEvent = comEvReceive Then CommandStatus.Caption = "Receiving Data From PROP" incomingdata = "" Do incoming = MSComm1.Input If (incoming <> "") Then incomingdata = incomingdata + "" + incoming Sleep (5) End If If (incoming = "") Then 'Exit Sub Exit Do End If Loop 'Label7.Caption = incomingdata 'CommandStatus.Caption = "Processing Data Received" If (Mid$(incomingdata, 1, 1) = "#") Then CommandStatus.Caption = "Updating Current Watts Being Used" olddata = Mid$(incomingdata, 2, Len(incomingdata) - 1) If (Val(olddata) < 0) Then olddata = Val(olddata) * -1 End If 'On Error GoTo 0 If (Val(olddata) > 0) Then pulsecount.Caption = olddata currentWattage = 3600 / (Val(olddata) / 10000) currentwatts.Caption = currentWattage End If LockSerial = 0 End If If (Mid$(incomingdata, 1, 1) = "S") Then CommandStatus.Caption = "Time Synced to Prop" LockSerial = 0 End If If (Mid$(incomingdata, 1, 1) = "D") Then kwhstring = Mid$(incomingdata, 2, Len(incomingdata) - 1) kwharray = Split(kwhstring, ",") 'sqldate = Format$(Date Text1.Text = "" For i = LBound(kwharray) To UBound(kwharray) - 1 Text1.Text = Text1.Text & UBound(kwharray) - 1 & " : " & kwharray(i) & vbCrLf Next kwhstring = "" LockSerial = 0 End If If (Mid$(incomingdata, 1, 1) = "C") Then CommandStatus.Caption = "Updating Wh Used" Label6.Caption = Mid$(incomingdata, 2, Len(incomingdata) - 1) LockSerial = 0 End If incomingdata = "" End If End Sub Function alert(message As String) Dim response response = MsgBox(message, vbExclamation + vbOKOnly) End Function Private Sub Timer2_Timer() currentTime = Hour(Now) & ":" & Minute(Now) & ":" & Second(Now) time_display.Caption = currentTime End Sub Private Function updateMySql(kwh) On Error GoTo Connection_Error Dim b As Long strDBCursorType = adOpenDynamic 'CursorType strDBLockType = adLockOptimistic 'LockType strDBOptions = adCmdText 'Options Set cn = New ADODB.Connection Me.MousePointer = 11 cn.Open ConnectString() cn.Execute "INSERT INTO power (watts) VALUES ('" & currentWattage & "')" ExitSub: cn.Close Set cn = Nothing On Error GoTo 0 Me.MousePointer = 0 Exit Function Connection_Error: 'Text1.Text = "Error " & Err.Number & " (" & Err.Description & ") " & "in procedure Command1_Click of Form " & Me.Name 'Me.MousePointer = 0 End Function Private Function ConnectString() As String Dim strServerName As String Dim strDatabaseName As String Dim strUserName As String Dim strPassword As String 'Change to IP Address if not on local machine 'Make sure that you give permission to log into the 'server from this address 'See Adding New User Accounts to MySQL 'Make sure that you d/l and install the MySQL Connector/ODBC 3.51 Driver or the 'MySQL Connector/ODBC 5.0 Driver strServerName = "****************" strDatabaseName = "**************" strUserName = "**************" strPassword = "*************" ConnectString = "DRIVER={MySQL ODBC 3.51 Driver};" & _ "SERVER=" & strServerName & _ ";DATABASE=" & strDatabaseName & ";" & _ "USER=" & strUserName & _ ";PASSWORD=" & strPassword & _ ";OPTION=3;" End Function Private Sub Timer3_Timer() Dim sql 'sql = updateMySql() End Sub Private Sub Timer4_Timer() Label7.Caption = t4counter t4counter = t4counter + 1 If (LockSerial = 1) And (t4counter > 10) Then ' restart program if communication lost or times out constatus.Caption = "Timeout / Lost connection. Retry in 1 second" Sleep (1000) Connect2Chip End If If LockSerial = 0 Then t4counter = 0 End If Hours = Hour(Now) Minutes = Minute(Now) Seconds = Second(Now) If (Minutes = 30) And (Seconds = 0) Or (Minutes = 59) And (Seconds = 0) Then CommandStatus.Caption = "Syncing Time to Prop" LockSerial = 1 Send2Chip (1) End If If (LockSerial = 0) And (LastSentCommand <> 3) And (Seconds = 50) Then LockSerial = 1 Send2Chip (3) End If If (LockSerial = 0) And (LastSentCommand <> 2) Then LockSerial = 1 Send2Chip (2) End If If (LockSerial = 0) And (LastSentCommand <> 4) Then LockSerial = 1 Send2Chip (4) End If 'Send2Chip (3) End Sub Private Function Send2Chip(what As Byte) Hours = Hour(Now) Minutes = Minute(Now) Seconds = Second(Now) If (what = 1) Then CommandStatus.Caption = "Sending Command 1" ' Sync Chip Time to System Time MSComm1.Output = "#" MSComm1.Output = Chr$("1") MSComm1.Output = Chr$(Hours) MSComm1.Output = Chr$(Minutes) MSComm1.Output = Chr$(Seconds) LastSentCommand = 1 ElseIf (what = 2) Then CommandStatus.Caption = "Sending Command 2" ' Get current watt usage MSComm1.Output = "#" MSComm1.Output = Chr$("2") LastSentCommand = 2 ElseIf (what = 3) Then CommandStatus.Caption = "Sending Command 3" ' Get watt hours stored MSComm1.Output = "#" MSComm1.Output = Chr$("3") LastSentCommand = 3 ElseIf (what = 4) Then CommandStatus.Caption = "Sending Command 4" ' Get Current watt hours used MSComm1.Output = "#" MSComm1.Output = Chr$("4") LastSentCommand = 4 End If End FunctionWhen you are outputting the code to the PC you can convert the Time_Count_Hours to ascii digits, insert the :, and convert the pulse_Count to ascii digits.
long Buffer[100] ' Store hours and pulses Buffer[i] := Hours << 16 + Pulses ' Send hours and pulses FDS.dec(Buffer[i] >> 16) FDS.tx(":") FDS.dec(Buffer[i] & $FFFF)