![]() |
Forum Index : Microcontroller and PC projects : Modbus Energy Meter.
Author | Message | ||||
Phil23 Guru ![]() Joined: 27/03/2016 Location: AustraliaPosts: 1667 |
Posted this in the Solar Forum... Not whether it is best there or here, so linking to the other post for comments. Cheers Phil. |
||||
Azure![]() Guru ![]() Joined: 09/11/2017 Location: AustraliaPosts: 446 |
Here are the configurable specs for that unit, I have bolded the defaults: Here is a link to the item specs. They are using MODBUS RTU so data will be bytes of packed nibbles. I have not worked with these. Difficulty interfacing to it with MM will depend on what you want to do with them. |
||||
Azure![]() Guru ![]() Joined: 09/11/2017 Location: AustraliaPosts: 446 |
There was this previous post trying to chase up some MM code for MODBUS. |
||||
Phil23 Guru ![]() Joined: 27/03/2016 Location: AustraliaPosts: 1667 |
Thanks for the spec sheet Azure, will wait for a couple to arrive & look further then. Looks like Modbus could be a challenge from the other post. May be better to just count the output pulses & do my own thing. Phil. |
||||
Phil23 Guru ![]() Joined: 27/03/2016 Location: AustraliaPosts: 1667 |
I take it for starters I need something in the way of a converter? MAX485 module like this ? Probably a 3.3V version as opposed to 5V. |
||||
SteveA Regular Member ![]() Joined: 10/03/2017 Location: United KingdomPosts: 48 |
I've used these for pic<->RS485: https://www.ebay.co.uk/itm/New-3-3V-UART-Serial-To-RS485-SP3485-Transceiver-Converter-Communication-Module/292006059581? epid=1488965693&hash=item43fceade3d:g:z3kAAOSwnHZYgvPx And for pc<->RS485 this: https://www.ebay.co.uk/itm/FP-2x-PC-USB-to-RS485-RS-485-interface-converter-Serial-adapter-compatible-PLC/263369403717?e pid=847623220&hash=item3d520a2d45:g:Cy8AAOSw4PxaJ8NK I managed to get two MM's talking to one another, one would send a command and the other which would turn a led on or off. I also managed to do the same thing from my pc using the adaptor/dongle. |
||||
Phil23 Guru ![]() Joined: 27/03/2016 Location: AustraliaPosts: 1667 |
Hmmm, My brain is pausing when I see that to initialise a device you send it 3 1/2 Bytes... Not the standard sort of coms I'm used to. Looking at this page. Phil. |
||||
Azure![]() Guru ![]() Joined: 09/11/2017 Location: AustraliaPosts: 446 |
The start and end framing just requires that you transmit a mark for at least 3 1/2 char times, use 4 if that works better in your mind. Any less can create interpretation errors. It is also critical that you transmit the whole frame continuously, without any breaks between message bytes or that can cause interpretation errors. There is a minimum intercharacter message delay. If you create the message to transmit and then output the bytes using interrupts that will solve the continuous message requirement. Before you start a frame you could add a flag and a timer tick to delay the transmission start and a delay at the tranmission end. Hope that makes sense. |
||||
TassyJim![]() Guru ![]() Joined: 07/08/2011 Location: AustraliaPosts: 6283 |
My brain is pausing when I see that to initialise a device you send it 3 1/2 Bytes... Not the standard sort of coms I'm used to. I think that the 3.5 bytes is the minimum idle time on the buss before and after packets, not a 'start' signal as such. I have a similar power meter but it only has the pulses which is good enough for me. Saves the brain a bit... Jim VK7JH MMedit |
||||
Phil23 Guru ![]() Joined: 27/03/2016 Location: AustraliaPosts: 1667 |
This one has two pulse outputs, thinking that using one of those might be an easier way for me to go. [Code]Pulse Output The meter provides two pulse outputs. Both pulse outputs are passive type. Pulse output 1 is configurable. The pulse output can be set to generate pulses to represent total / import/export kWh or kVarh. The pulse constant can be set to generate 1 pulse per:0.001(default) /0.01/0.1/1kWh/kVarh. Pulse width: 200/100/60ms Pulse output 2 is non-configurable. It is fixed up with total kwh. The constant is 1000imp/kWh.[/code] Phil. |
||||
Phil23 Guru ![]() Joined: 27/03/2016 Location: AustraliaPosts: 1667 |
Still waiting on the slow boat from China, no devices as yet. Seems like there are a tonne of low priced MODBUS devices available from China. Makes me think support on MMbasic could be well received. Obviously not an internal feature, but some Basic functions, or at best external add-ins for MODBUS may be well received. Also wonder if @Geoffg addressed anything like this in some of the large scale monitoring projects he has installed in Perth. Don't know this is a suitable starting point for ideas or not. Obviously copyrighted, as seen it the beginning of the code. Phil [Code]' This script is an example of the EMDO101 energy manager ' Please visit us at www.swissembedded.com ' Copyright (c) 2015-2016 swissEmbedded GmbH, All rights reserved. ' @DESCRIPTION EMDO modbus master library ' @VERSION 1.0 ' Protocols are freely available from www.modbus.org ' http://www.modbus.org/docs/Modbus_Application_Protocol_V1_1b.pdf ' Overview https://en.wikipedia.org/wiki/Modbus ' Modbus RTU framing ' 1 Slave Address ' 1 Function code ' n data ' 2 CRC ' Modbus TCP framing ' Bytes Description ' 2 Transaction identifier ' 2 Protocol identifier (zero) ' 2 Number of remaining bytes in the frame ' 1 Slave address ' 1 Function code ' n Payload ' Modbus function all (master) ' itf$ Interface with string.Example "RTU:RS485:1" or "TCP:192.168.0.1:90" ' slv% Slave Address ' fnc% Function Codes: ' 1=Read Coils (bits) ' 2=Read Discrete Inputs ' 3=Read Holding Register ' 4=Read Input Registers ' 5=Write Single Coil (bits) ' 6=Write Single Register ' 15=Write Multiple Coils (bits) ' 16=Write Multiple Register ' addr% Modbus Address ' num% Number of Registers/Bits ' dta$ Data for Read/Write (fnc%=5 data must be &HFF00 or &H0000) ' tmo% Timeout in ms ' return 0 = ok, negative value = error FUNCTION mbFunc(itf$,slv%,fnc%,addr%,num%,dta$,tmo%) Local rq$, n%, rpl%, py%, err% ' Validate call first IF NOT ((addr% >= 0 AND addr%<=&HFFFF)) THEN ' Address is out of range mbFunc=-10 EXIT FUNCTION ELSE IF NOT (slv%>=0 AND slv%<255) THEN ' Slave address range invalid mbFunc=-11 EXIT FUNCTION ELSE IF NOT ((fnc%>=1 AND fnc%<=6) OR (fnc%>=15 AND fnc%<=16) OR (fnc%>=22 AND fnc%<=23)) THEN ' Function code is invalid mbFunc=-12 EXIT FUNCTION ELSE IF NOT tmo% > 100 THEN ' Minimal timeout needed to transfer data mbFunc=-13 EXIT FUNCTION ELSE IF num% < 1 OR num% > 100 THEN ' We limit the number to 100 registers, MMBASIC is limited to 255 chars per string mbFunc=-14 EXIT FUNCTION ELSE IF (fnc%=5 OR fnc%=6) AND len(dta$)<>2 THEN ' Write single coil and write single register needs one word of data mbFunc=-15 EXIT FUNCTION ELSE IF (fnc%=15) AND (len(dta$)*8)<(num%) THEN ' Write single coil and write single register needs one word of data mbFunc=-16 EXIT FUNCTION ELSE IF (fnc%=16) AND len(dta$)<>(num%*2) THEN ' Write single coil and write single register needs one word of data mbFunc=-16 EXIT FUNCTION ENDIF ' Make request IF fnc%=1 OR fnc%=2 THEN ' Function code 1 (8 bits in a byte, round up bytes) rq$=chr$(fnc%)+conv("u16/bbe",addr%)+conv("u16/bbe",num%) n%=num%/8 IF n%*8 < num% THEN n%=n%+1 ENDIF rpl%=2+n% py%=n% ELSE IF fnc%=3 OR fnc%=4 THEN ' Function code 3,4 rq$=chr$(fnc%)+conv("u16/bbe",addr%)+conv("u16/bbe",num%) rpl%=2+2*num% py%=2*num% ELSE IF fnc% = 5 OR fnc% = 6 THEN ' Function code 5, 6 rq$=chr$(fnc%)+conv("u16/bbe",addr%)+dta$ rpl%=5 py%=2 ELSE IF fnc% = 15 OR fnc%=16 THEN ' Function code 15 rq$=chr$(fnc%)+conv("u16/bbe",addr%)+conv("u16/bbe",num%)+CHR$(len(dta$))+dta$ rpl%=5 py%=0 ENDIF ' Send request and receive response err%=mbCom(itf$,slv%,fnc%,rq$,rpl%, py%, rp$, tmo%) dta$=rp$ mbFunc=err% END FUNCTION ' Modbus low level function for data exchange ' itf$ Interface with string.Example "RTU:RS485:1" or "TCP:192.168.0.1:90" ' slv% Slave Address ' fnc% Function Code ' rq$ Request Data ' py% Expected payload length ' rpl% Expected response length ' rp$ Response Data ' tmo% Timeout in ms ' return Error code 0 = ok, negative value = error FUNCTION mbCom(itf$,slv%,fnc%,rq$,rpl%, py%, rp$, tmo%) LOCAL interf$, ln$, msg$, num$, prot$, req$, rsp$, tn$, n%, con%, err%, trans%,nm% ' rpl and py not checked for validity IF rpl% < 0 OR py% < 0 OR py% > rpl% THEN mbCom = -1 EXIT FUNCTION ENDIF ' parse if$ for either RTU, TCP on RS485 or ETH prot$=split$(0,itf$,":") interf$=split$(1,itf$,":") num$=split$(2,itf$,":") nm%=val(num$) ' add framing IF prot$ = "RTU" THEN msg$=CHR$(slv%)+rq$ req$=msg$+CRC$(0,msg$) ' CRC16 ELSE trans% = Ticks() and &HFFFF tn$=conv("u16/bbe", trans%) ln$=conv("u16/bbe",len(rq$)+1) req$=tn$+chr$(0)+chr$(0)+ln$+CHR$(slv%)+rq$ ENDIF IF interf$="RS485" THEN ' Send it over rs485 IF nm%=1 THEN pause(1000.0*3.5*12.0/SYS.Get("rs485", "baud")+1) ELSE pause(1000.0*3.5*12.0/SYS.Get("rs485-2", "baud")+1) ENDIF DO WHILE RS485Read(nm%) >=0 LOOP n%=RS485Write(nm%,req$) IF nm%=1 THEN pause(1000.0*3.5*12/SYS.Get("rs485", "baud")+1) ELSE pause(1000.0*3.5*12/SYS.Get("rs485-2", "baud")+1) ENDIF rsp$=RS485Read$(nm%,rpl%+3,tmo%) 'mbLog(interf$+"-"+num$,req$,rsp$,prot$) ELSE ' Send it over ethernet con%=SocketClient( 1, interf$, val(num$) ) IF con% >0 THEN n%=SocketOption(con%,"SO_RCVTIMEO",tmo%) n%=SocketWrite( con%, req$ ) rsp$=SocketRead$(con%,rpl%+7) n%=SocketClose( con% ) 'mbLog(interf$,req$,rsp$,prot$) ELSE mbCom=-20 EXIT FUNCTION ENDIF ENDIF ' Finally check response to be valid IF prot$ = "RTU" THEN ' Check if this is an exception IF len(rsp$) = 5 THEN ' Size fits exception IF asc(mid$(rsp$,1,1))=slv% AND asc(mid$(rsp$,2,1))=(fnc% OR &H80) THEN ' This is an exception IF CRC$(0,left$(rsp$,len(rsp$)-2))<>mid$(rsp$,2,2) THEN ' Checksum bad mbCom=-31 mLogError "BAD CHECKSUM" EXIT FUNCTION ENDIF ' return exception code mLogError "EXCEPTION" mbCom=-asc(mid$(rsp$,3,1)) EXIT FUNCTION ENDIF ENDIF ' Check if regular message IF len(rsp$)<(rpl%+3) THEN mbCom=-32 mLogError "SIZE NOT MATCH: "+Str$(len(rsp$))+" <> "+Str$(rpl%+3) EXIT FUNCTION ELSE IF slv% <> asc(left$(rsp$,1)) THEN ' check slv address must match mbCom=-33 mLogError "ADDRESS NOT MATCH:" EXIT FUNCTION ELSE IF CRC$(0,left$(rsp$,len(rsp$)-2))<>right$(rsp$,2) THEN ' Checksum bad mbCom=-34 mLogError "BAD CHECKSUM" EXIT FUNCTION ENDIF ' cut the response data out rp$=mid$(rsp$,len(rsp$)-2-py%+1,py%) ELSE ' Check if this is an exception IF len(rsp$) = 9 THEN ' Size fits exception IF left$(rsp$,2)=tn$ AND asc(mid$(rsp$,7,1))=slv% AND asc(mid$(rsp$,8,1))=(fnc% OR &H80) THEN ' return exception code mLogError "EXCEPTION" mbCom=-asc(mid$(rsp$,9,1)) EXIT FUNCTION ENDIF ENDIF ' Check if regular message IF len(rsp$)<(rpl%+7) THEN mbCom=-22 mLogError "SIZE NOT MATCH:" EXIT FUNCTION ELSE IF tn$ <> left$(rsp$,2) THEN ' check slv address must match mbCom=-23 mLogError "SLAVE ADDRESS NOT MATCH:" EXIT FUNCTION ELSE IF slv% <> asc(mid$(rsp$,7,1)) THEN ' check slv address must match mbCom=-24 mLogError "SLAVE ADDRESS NOT MATCH:" EXIT FUNCTION ENDIF ' cut the response data out rp$=right$(rsp$,py%) ENDIF mbCom=0 END FUNCTION '---------------------------------------- ' log a telegram ' print a modbus telegram on the console '---------------------------------------- SUB mbLog(itf$,tx$,rx$,msg$) LOCAL s$, h$, i, srx$, stx$ s$=msg$+":"+itf$ stx$="tx:" FOR i=1 TO len(tx$) h$=hex$(asc(mid$(tx$,i,1))) IF len(h$) = 1 THEN h$="0"+h$ ENDIF stx$=stx$+h$ NEXT srx$="rx:" FOR i=1 TO LEN(rx$) h$=hex$(asc(mid$(rx$,i,1))) IF len(h$) = 1 THEN h$="0"+h$ ENDIF srx$=srx$+h$ NEXT PRINT s$ " " stx$ " " srx$ END SUB SUB mLogError(msg$) PRINT "ERROR:", msg$ 'PAUSE 10000 'ERROR "MODBUS RX ERROR" END SUB [/code] |
||||
Phil23 Guru ![]() Joined: 27/03/2016 Location: AustraliaPosts: 1667 |
Received the units yesterday. Any suggestions on the best way to start? Have never dealt with 485 before, let alone anything like Modbus. Cheers Phil. |
||||
Azure![]() Guru ![]() Joined: 09/11/2017 Location: AustraliaPosts: 446 |
Connect your MM to the RS485 interface and it to the Meter and start writing and testing your code to talk to the serial interface. The defaults should be: Parity: NONE Stop bits: 1 or 2 Modbus Address: 1 |
||||
Phil23 Guru ![]() Joined: 27/03/2016 Location: AustraliaPosts: 1667 |
Just had a thought on the MicroMite end for this project. I can probably borrow a bit of code from the display & interface from Silicon Chip's Energy Meter published in August 2016. A couple of 433Mhz modules & it could replace my old Clipsal Cent-a-meter that gets confused by reactive power. Cheers Phil. |
||||
Phil23 Guru ![]() Joined: 27/03/2016 Location: AustraliaPosts: 1667 |
Mostly done & dusted now. It's polling both meters for live & total values & displaying them on both the LCD display & the VT100 console. Hardware is the 2 Eastron Energy meters, Micromite, TTL-RS485 module & the ESP-01 to give me an IP connection for the console. Left column is meter 1; on the inverters input. Right is meter 2 on it's output. Planning on adding a 3rd to my main meter box supply. The 2 figures on the Solar line are Meter 2-1; Left is Watts, Right VA. The Console display still has a lot of debug info to remove, basically request & response strings. Will post the full code once I've tidied it up a bit more. Phil. |
||||
Phil23 Guru ![]() Joined: 27/03/2016 Location: AustraliaPosts: 1667 |
Still haven't had time to get to finish this & tidy the code up properly.... I'm not checking CRC on the received data at this stage, even though the sub is there & being used to add CRC to the request string. Thought I'd post it for feedback anyway, knowing there's still stuff that is unorthodox & needs to be fixed. In particular, I'd like to hear about alternate approaches to my polling technique, I think it's very much a Band-Aid to get things working. Note the code below EXCLUDES Font 2 which is required & present in the zip. Thanks to TassyJim for the help with the CRC. I can now sit in the loungeroom & have the joy of watching all 3 meters... Cheers. Phil Option Autorun On Dim Integer Addr%,DevAdr%,Fcode%=04,SAdH%,SAdL%,NBtH%,NBtL% 'Variables used to build request String Dim Integer ReqType=1,ReqNum,NumDev=3 Dim Integer TimerRc=Timer,k=1000 Dim Float Volts(4),Amps(4),Watts(4),VAs(4),VAsR(4),PF(4) Dim Float TotImp(4),TotExp(4) Dim String DataStr,ReqStr,Response$ Dim String Esc=Chr$(27) Open "Com1:9600,,RecComs,8" As #1 CLS Print Esc+"[f";Esc+"[J"; Do ReqData UpdateLCD UpdateConsole Pause 500 Loop Sub ReqData1 ReqNum=ReqNum+1 If ReqNum>NumDev+117 Then ReqNum=1 Addr%=0 ReqType=1 End If If Addr%<NumDev Then Addr%=Addr%+1 Else Addr%=1 If ReqNum>NumDev Then ReqType=0 If ReqType=0 Then SAdL%=&h00 : NBtL%=&h20 Else If ReqType=1 Then SAdL%=&h48 : NBtL%=&h04 End If ReqStr=BldReq(Addr%,FCode%,SAdH%,SAdL%,NBtH%,NBtL%) Print #1, ReqStr; End Sub Sub ReqData ReqNum=ReqNum+1 If ReqNum>10 Then ReqNum=1 'Addr%=0 ReqType=1 End If 'If Addr%<NumDev Then Addr%=Addr%+1 Else Addr%=1 If ReqNum>1 Then ReqType=0 If ReqType=0 Then SAdL%=&h00 : NBtL%=&h20 Else If ReqType=1 Then SAdL%=&h48 : NBtL%=&h04 End If For Addr%=1 to NumDev ReqStr=BldReq(Addr%,FCode%,SAdH%,SAdL%,NBtH%,NBtL%) Print #1, ReqStr; Pause 20 Next Addr% End Sub Function BldReq(Ad%,Fc%,A1%,A2%,N1%,N2%) As String BldReq=Chr$(Ad%)+Chr$(Fc%)+Chr$(A1%)+Chr$(A2%)+Chr$(N1%)+Chr$(N2%) BldReq=BldReq+CrcStr(BldReq) End Function Sub RecComs Local Integer BufLen,BytCnt%,n TimerRc=Timer Do While BufLen<> Loc(#1) BufLen=Loc(#1) Pause 5 'Wait 5mS to see in the Buffer Grows Loop DataStr=Input$(Loc(#1),#1) 'Read everything in the buffer. Response$="" For n=1 to Len(DataStr) Response$=Response$+Hex$(Asc(Mid$(DataStr,n,1)),2) Next n DevAdr%=Val("&h"+Left$(Response$,2)) BytCnt%=Val("&h"+Mid$(Response$,5,2)) Select Case BytCnt% Case 8 TotImp(DevAdr%)=Bin2Flt(Mid$(Response$, 7,8)) TotExp(DevAdr%)=Bin2Flt(Mid$(Response$, 15,8)) Case 64 Volts(DevAdr%)=Bin2Flt(Mid$(Response$, 7,8)) Amps(DevAdr%)=Bin2Flt(Mid$(Response$, 31,8)) Watts(DevAdr%)=Bin2Flt(Mid$(Response$, 55,8)) VAs(DevAdr%)=Bin2Flt(Mid$(Response$, 79,8)) VAsR(DevAdr%)=Bin2Flt(Mid$(Response$, 103,8)) PF(DevAdr%)=Bin2Flt(Mid$(Response$, 127,8)) Watts(4)=Watts(3)-Watts(2) VAs(4)=VAs(3)-VAs(2) End Select TimerRc=Timer-TimerRc End Sub Function CrcStr(a$) As String Local ErrorWord% = &HFFFF, n, j, ByteVal, LSB Local CrcHex As Integer For n = 1 to Len(A$) ByteVal = Asc(Mid$(a$, n, 1)) ErrorWord% = (ErrorWord% And &HFFFF) Xor Asc(Mid$(a$, n, 1)) For j = 1 to 8 LSB = ErrorWord% And &H0001 If LSB = 1 Then ErrorWord% = ErrorWord% - 1 ErrorWord% = ErrorWord% / 2 If LSB = 1 Then ErrorWord% = ErrorWord% Xor &HA001 Next j Next n CrcHex = ErrorWord% And &HFFFF CrcStr=Chr$(CrcHex And &hFF)+Chr$(CrcHex>>8) End Function Function Bin2Flt(IeeeStr As String) As Float Local Integer Reading%,Sign%,Expo% Local Float x,y,z IeeeStr="&h"+IeeeStr Reading%=Val(IeeeStr) Sign%=Reading% >> 31 'Read the Sign Bit Expo%=((Reading% >> 23) And &hFF) - 127 'Extract Exponent, Remove sign, Subtract Offset 'Ans!=((Reading% Or &h800000) And &hffffff)/2^(23-Expo%)*(-1)^Sign% 'Extract Mantissa & Add implied 24th bit, Shift Point in Binary & apply sign x! = 2^(23-Expo%) y! = (-1)^Sign% z! = ((Reading% Or &h800000) And &hffffff) ' print x!, y!, z! If x!*y!<>0 Then Bin2Flt=z!/x!*y! Else Bin2Flt=0 End Function '==========================Update LCD Display================================= Sub UpdateLCD Text MM.HRes/40, MM.VRes*1/10, "Volts", LB, 2, 1, RGB(Green) Text MM.HRes/40, MM.VRes*2/10, "Amps ", LB, 2, 1, RGB(Cyan) Text MM.HRes/40, MM.VRes*3/10, "kW ", LB, 2, 1, RGB(Red) Text MM.HRes/40, MM.VRes*4/10, "kVA ", LB, 2, 1, RGB(Blue) Text MM.HRes/40, MM.VRes*5/10, "kVAr ", LB, 2, 1, RGB(Cyan) Text MM.HRes/40, MM.VRes*6/10, "PF ", LB, 2, 1, RGB(Magenta) Text MM.HRes/40, MM.VRes*7/10, "Solar", LB, 2, 1, RGB(Yellow) Text MM.HRes/40, MM.VRes*8/10, "Import", LB, 2, 1, RGB(White) 'Text MM.HRes/40, MM.VRes*9/10, "Line9", LB, 2, 1, RGB(Magenta) 'Text MM.HRes/40, MM.VRes*10/10,"Line10", LB, 2, 1, RGB(Green) Text MM.HRes*25/40, MM.VRes*1/10, Str$(Volts(1),4,1), RB, 2, 1, RGB(Green) Text MM.HRes*25/40, MM.VRes*2/10, Str$(Amps(1),3,2), RB, 2, 1, RGB(Cyan) Text MM.HRes*25/40, MM.VRes*3/10, Str$(Watts(1)/k,3,2), RB, 2, 1, RGB(Red) Text MM.HRes*25/40, MM.VRes*4/10, Str$(VAs(1)/k ,3,2), RB, 2, 1, RGB(Blue) Text MM.HRes*25/40, MM.VRes*5/10, Str$(VAsR(1)/k,3,2), RB, 2, 1, RGB(Cyan) Text MM.HRes*25/40, MM.VRes*6/10, Str$(PF(1),3,2), RB, 2, 1, RGB(Magenta) Text MM.HRes*25/40, MM.VRes*7/10, Str$(Watts(4),4,1), RB, 2, 1, RGB(Yellow) Text MM.HRes*25/40, MM.VRes*8/10, Str$(TotImp(1),4,1), RB, 2, 1, RGB(White) ' Text MM.HRes/2, MM.VRes*9/10, "Line9", CB, 2, 1, RGB(White) ' Text MM.HRes/2, MM.VRes*10/10, SecsTime(PumpRunTime), CB, 2, 1, RGB(Green) Text MM.HRes*39/40, MM.VRes*1/10, Str$(Volts(2),4,1), RB, 2, 1, RGB(Green) Text MM.HRes*39/40, MM.VRes*2/10, Str$(Amps(2),3,2), RB, 2, 1, RGB(Cyan) Text MM.HRes*39/40, MM.VRes*3/10, Str$(Watts(2)/k,3,2), RB, 2, 1, RGB(Red) Text MM.HRes*39/40, MM.VRes*4/10, Str$(VAs(2)/k,3,2), RB, 2, 1, RGB(Blue) Text MM.HRes*39/40, MM.VRes*5/10, Str$(VAsR(2)/k,3,2), RB, 2, 1, RGB(Cyan) Text MM.HRes*39/40, MM.VRes*6/10, Str$(PF(2),3,2), RB, 2, 1, RGB(Magenta) Text MM.HRes*39/40, MM.VRes*7/10, Str$(Watts(3),4,1), RB, 2, 1, RGB(Yellow) Text MM.HRes*39/40, MM.VRes*8/10, Str$(TotImp(2),4,1), RB, 2, 1, RGB(White) ' Text MM.HRes/2, MM.VRes*9/10, Time$, CB, 2, 1, RGB(White) ' Text MM.HRes/2, MM.VRes*10/10, SecsTime(PumpRunTime), CB, 2, 1, RGB(Green) End Sub Sub UpdateConsole Local Integer n,p ''Print Esc;"[2J";Esc;"[f" Print Esc+"[f"; Print " Utility Solar In Solar Out" Print "============================================" Print "Volts : ";Str$(Volts(1),8,2);Str$(Volts(2),8,2);Str$(Volts(3),8,2) Print "Amps : ";Str$(Amps(1),8,2);Str$(Amps(2),8,2);Str$(Amps(3),8,2) Print "Watts : ";Str$(Watts(1),8,2);Str$(Watts(2),8,2);Str$(Watts(3),8,2);" $";Str$(Watts(1)*.2847*0.0011,3,2) Print "VA : ";Str$(VAs(1),8,2);Str$(VAs(2),8,2);Str$(VAs(3),8,2) Print "VAr : ";Str$(VAsR(1),8,2);Str$(VAsR(2),8,2);Str$(VAsR(3),8,2) Print "P/Factor : ";Str$(PF(1),8,2);Str$(PF(2),8,2);Str$(PF(3),8,2) Print "Import : ";Str$(TotImp(1),8,2);Str$(TotImp(2),8,2);Str$(TotImp(3),8,2) Print "Export : ";Str$(TotExp(1),8,2);Str$(TotExp(2),8,2);Str$(TotExp(3),8,2) Print "Solar Watts";Str$(Watts(2),8,2);Str$(Watts(4),8,2);Str$(Watts(3),8,2) Print "Solar VA : ";" ";Str$(VAs(4),8,2) Print Esc+"[K" Print "Time to Process Coms:= "; TimerRc Print "Request Type-"; ReqType; " Req Number-"; Str$(ReqNum,4,0) ' Print "Request Type-"; ReqType, " Address-"; Addr%; " Req Number-"; Str$(ReqNum,4,0) ' Print "Request" ' ' For p=1 To Len(ReqStr) ' Print Hex$(Asc(Mid$(ReqStr,p,1)),2);" "; ' Next p ' ' Print "Response" ' ' For n=1 To Len(DataStr) ' Print Hex$(Asc(Mid$(DataStr,n,1)),2);" "; ' Next n ' Print Esc+"[K" Print Esc+"[J"; End Sub ' Font: Hom_16x24_LE ' Includes all ASCII characters DefineFont #2 5F201810 00000000 00000000 00000000 00000000 00000000 00000000 00000000 2018-06-19_072043_Modbus_1.01.zip |
||||
![]() |
![]() |
The Back Shed's forum code is written, and hosted, in Australia. | © JAQ Software 2025 |