Page 1 of 1

How to read data from a serial port ?

PostPosted: Tue Jul 20, 2021 5:20 pm
by vilian
Hi Guys,
I'm trying to read data from a serial port using this code bellow:
Code: Select all  Expand view

hb_comOpen(4)        
hb_comInit( 4, 9600, "N", 8, 1,132  )
nLen := hb_comInputCount(4)
cRet  := Space(nLen)
hb_comRecv(4, @cRet)
hb_comClose(4)
 

There is no error, but only the begin of the data is read. Do you know why ?

Re: How to read data from a serial port ?

PostPosted: Tue Jul 20, 2021 7:16 pm
by Marc Venken
I have this code in my archieves, but can't be sure if they work. Long time ago :

Code: Select all  Expand view

function fReadData
local cDcb, lError, nError

cPort  :='COM1'
gcPort := val(right(cPort,1))
cRate  := '2400'    // baud rate
cErrCode := space( 16 )

   if !( gnComm := OpenComm( cPort, 1024, 10 ) ) == 0

      if !BuildCommDcb( cPort+":"+cRate+",N,8,1", @cDcb )
         nError := GetCommError( gnComm, @cErrCode )

         MsgAlert( "Error "+ str( nError ) + CRLF + cErrCode, "Build error " )
         RETURN( .f. )
      endif

      if !SetCommState( @cDcb )
         nError := GetCommError( gnComm, @cErrCode )
         MsgAlert( "Error "+ str( nError ) + CRLF + cErrCode, "Set Comm error " )
         RETURN( .f. )
      endif
   endif
   cBlock=space(1024)
   nTry=0
   do while nTry<500
     if ( nBytes := readComm( gnComm, @cBlock) ) > 0
       msgwait('Reading ... '+str(nTry,5),'',1)
       exit
     else
       nTry++
       msgwait(str(nTry,5),'',1)
     endif
   enddo
   msgstop(substr(alltrim(cblock),5,10),'Data Read')

   if FlushComm( gnComm, 0 ) != 0
      nError = GetCommError( gnComm )
      Msgwait( 'FlushComm Error:' ,'',.01 )
   endif

   if ! CloseComm( gnComm )
      nError = GetCommError( gnComm )
      Msgwait( 'CloseComm Error: ' ,'',.01 )
   endif

RETURN( .t. )

function Serial(x0,x1,x2,x3,x4,x5)
   local cDcb, nBytes
   local nComm := OpenComm( alltrim(x1),x2, 128 )
   local nError

   x3=padl(left(x3,20),20,' ')
   x4=padl(left(x4,20),20,' ')
   cNxLine=CHR(13)
   if ! BuildCommDcb( alltrim(x1)+":"+str(x2,4)+",n,8,1", @cDcb )
     nError = GetCommError( nComm )
     Msgwait( x0+" : BuildCommDcb Error: " + Str( nError ),'',.3 )
   endif
   if ! SetCommState( cDcb )
     nError = GetCommError( nComm )
     Msgwait( "SetCommState Error: " + Str( nError ),'',.3 )
     return .t.
   endif

   if !empty(x5)
     for iii=1 to len(x5)
       if ( nBytes := WriteComm( nComm, x5[iii]) ) < 0
         nError = GetCommError( nComm )
         Msgwait( "WriteComm Error: " + Str( nError ),'',.1 )
       else
         Msgwait( x0+' : Ok','',.1 )
       endif
     next
   else
     if ( nBytes := WriteComm( nComm, x3+cNxLine ) ) < 0
       nError = GetCommError( nComm )
       Msgwait( "WriteComm Error: " + Str( nError ),'',.1 )
     else
       Msgwait( x0+' : Ok','',.1 )   // important, do not change the delay
     endif
     if !empty(x4)
       if ( nBytes := WriteComm( nComm, x4+cNxLine ) ) < 0
         nError = GetCommError( nComm )
         Msgwait( "WriteComm Error: " + Str( nError ),'',.1 )
       else
         Msgwait( x0+' : Ok','',.1 )
       endif
     endif
   endif

   if FlushComm( nComm, 0 ) != 0
      nError = GetCommError( nComm )
      Msgwait( x0+" : FlushComm Error: " + Str( nError ),'',.01 )
   endif

   if ! CloseComm( nComm )
      nError = GetCommError( nComm )
      Msgwait( "CloseComm Error: " + Str( nError ),'',.01 )
   endif

return nil


 

Re: How to read data from a serial port ?

PostPosted: Tue Jul 20, 2021 7:50 pm
by vilian
Thank you Marc,
I have tested with your code, but the problem happened again - Only the begin of the data is read !!

Re: How to read data from a serial port ?

PostPosted: Tue Jul 20, 2021 8:30 pm
by cmsoft
Hola Vilian:
I have a very old code that communicated with some registers.
They had a round trip communication with the PC. They expected that after an operation, an end-of-block code would be sent to send another.
I'll give you the code, it can help you there.
Code: Select all  Expand view

FUNCTION  creanom(xnombre)
LOCAL tabla_asc,tabla_ecr,nomreg,i,j,letra
tabla_asc := {" ","1","2","3","4","5","6","7","8","9",;
              "A","B","C","D","E","F","G","H","I","J",;
              "K","L","M","N","P","Q","R","S","T","U",;
              "V","W","X","Y","Z","0","@","%","&","+",;
              "-"," ","*","!","#",":"," ","$"," ","'",;
              "/",",",",","^","O"}

tabla_ecr := {"20","31","32","33","34","35","36","37","38","39",;
              "41","42","43","44","45","46","47","48","49","4A",;
              "4B","4C","4D","4E","50","51","52","53","54","55",;
              "56","57","58","59","5A","30","40","25","26","2B",;
              "2D","20","2A","21","23","3A","20","24","20","27",;
              "2F","2C","2C","5E","4F"}
nomreg = ""
FOR i = 1 TO LEN(xnombre)
    letra = SUBSTR(xnombre,i,1)
    j = ASCAN(tabla_asc,letra)
    IF j = 0
       j = 1
    ENDIF
    nomreg = nomreg + tabla_ecr[j]
NEXT
RETURN LEFT(nomreg,36)

FUNCTION crearbcc(p1)
LOCAL bcc,i
bcc = CHR(0)
FOR i = 1 TO LEN(p1)
    bcc := charxor(bcc,SUBSTR(p1,i,1))
NEXT
RETURN bcc

FUNCTION abrirport(n)
LOCAL IdPort,cDcb,nError
IdPort := OpenComm("COM"+STR(n,1),1024,256)
IF IdPort <= 0
   nError = GetCommError( IdPort)
   MsgInfo( "Error al abrir: " + Str( nError ) )
   ELSE
   MsgRun("Puerto abierto como " + STR(IdPort))
ENDIF
IF ! BuildCommDcb("COM"+STR(n,1)+":9600,n,8,1" , @cDcb)
   nError = GetCommError( IdPort)
   MsgInfo( "Error al Configurar: " + Str( nError ) )
   RETURN 0
   ELSE
   MsgRun("Puerto Configurado")
ENDIF
IF ! SetCommState( IdPort, cDcb )
   nError = GetCommError( IdPort)
   MsgInfo( "Error al setear: " + Str( nError ) )
   RETURN 0
   ELSE
   MsgRun("Puerto Seteado")
ENDIF
RETURN IdPort

PROCEDURE mandar(port,string)
LOCAL nBytes
IF (nBytes := WriteComm( port,string) ) < 0
   MsgAlert("Mando mal string")
ENDIF
RETURN

FUNCTION leer_ack(port)
LOCAL fallo, ack := " ", nBytes,i := 1
fallo = .t.
DO WHILE .t.
   MsgWait("Leyendo Ack ","Espere",.15)
   nBytes := ReadComm( port,@ack)
   i++
   IF i > 20 .or. ack <> " "
      EXIT
   ENDIF
ENDDO
IF ack <> ""
   fallo = .f.
   MsgInfo(asc(ack),memvar->musuanom)
ENDIF
RETURN fallo

FUNCTION  leer_enq(port)
LOCAL fallo,enq:=" ",nBytes,i := 1
fallo = .t.
DO WHILE .t.
   MsgWait("Leyendo Enq","Espere",.3)
   nBytes := ReadComm( port,@enq)
   i++
   IF i > 20 .or. enq <> " "
      EXIT
   ENDIF
ENDDO
IF enq <> ""
   fallo = .f.
   MsgInfo(asc(enq),memvar->musuanom)
ENDIF
RETURN fallo

FUNCTION  leer_eot(port)
LOCAL fallo,eot := " " ,nBytes,i := 1
fallo = .t.
DO WHILE .t.
   MsgWait("Leyendo EoT","Espere",.3)
   nBytes := ReadComm( port,@eot)
   i++
   IF eot = CHR(6)
      MsgWait("Esperando por EoT","Espere",5)
      LOOP
   ENDIF
   IF i > 20 .or. eot <> " "
      EXIT
   ENDIF
ENDDO
IF eot <> ""
   fallo = .f.
   MsgInfo(asc(eot),memvar->musuanom)
ENDIF
RETURN fallo

PROCEDURE mandar_eot(port)
LOCAL nBytes
*IF ( nBytes := WriteComm( port, "" )) <= 0
IF ( nBytes := WriteComm( port, CHR(4) )) <= 0
   MsgAlert("Mando mal EOT")
ENDIF
RETURN

FUNCTION mandar_enq(port)
LOCAL mcont,retorno,nBytes
retorno = .t.
FOR mcont := 1 TO 10
*   IF ( nBytes := WriteComm( port, "" )) <= 0
    IF ( nBytes := WriteComm( port, CHR(5))) <= 0
       MsgAlert("Mando mal ENQ")
       retorno := .f.
       ELSE
       retorno := .t.
       EXIT
    ENDIF
    MsgWait("Enviando datos...","Aguarde",1)
NEXT
RETURN retorno

PROCEDURE mandar_ack(port)
LOCAL nBytes
*IF ( nBytes := WriteComm( port, "" )) <= 0
IF ( nBytes := WriteComm( port, CHR(6))) <= 0
   MsgAlert("Mando mal ACK")
ENDIF
RETURN

FUNCTION  leer_bloque(port,n)
LOCAL bloque:= SPACE(n),bcc1,nBytes,i:=1
DO WHILE .t.
   *MsgWait(bloque,"Espere",.2)
   nBytes := ReadComm( port,@bloque)
   i++
   IF EMPTY(bloque)
      MsgWait("Esperando ENQ","Espere",3)
      mandar_enq(port)
      LOOP
   ENDIF
   *bloque := IF(EMPTY(bloque),"",bloque)
   IF i > 20 .or. bloque <> SPACE(n)
      EXIT
   ENDIF
ENDDO
bcc1 = crearbcc(SUBSTR(bloque,2,LEN(bloque)-2))
IF RIGHT(bloque,1) <> bcc1 .and. !(""$bloque)
   *MsgAlert(OemtoAnsi(bloque),STR(ASC(bcc1))+" <> "+STR(ASC(RIGHT(bloque,1))))
   MEMVAR->falla = .t.
ENDIF
RETURN bloque

FUNCTION bloqueaECR(mport,ecr)
LOCAL stx,mark,id,tarea,fecha,etx,bcc,tipo,desde,hasta,omitir,salida,ack,;
      responde
salida = .t.
stx    = ""
mark   = "S"
id     = "01"
tarea  = "<"
tipo   = "0"
desde  = "0000000000000"
hasta  = "0000000000000"
omitir = "0"
fecha  = STRTRAN(STR(DAY(DATE()),2)+STR(MONTH(DATE()),2)+SUBSTR(STR(YEAR(DATE()),4),2,2)," ","0")
etx    = ""
bcc    := crearbcc(mark+id+ecr+tarea+tipo+desde+hasta+omitir+fecha+etx)
mport := abrirport(mport)
MsgWait("Aguarde","Espere",.25)
mandar_enq(mport)
IF !leer_ack(mport)
   responde = MsgYesNo("Recibio mal ACK 1")
   IF !responde
      CloseComm(mport)
      RETURN .F.
   ENDIF
ENDIF
MsgWait("Aguarde","Espere",.25)
mandar(mport,stx+mark+id+ecr+tarea+tipo+desde+hasta+omitir+fecha+etx+bcc)
IF !leer_ack(mport)
   MsgAlert("La ECR se encuentra ocupada o con error")
   salida = .f.
ENDIF
mandar_eot(mport)
CloseComm(mport)
RETURN salida

FUNCTION desbloqECR(mport,ecr)
LOCAL stx,mark,id,tarea,fecha,etx,bcc,tipo,desde,hasta,omitir,salida,responde
salida = .t.
stx    = ""
mark   = "S"
id     = "01"
tarea  = ">"
tipo   = "0"
desde  = "0000000000000"
hasta  = "0000000000000"
omitir = "0"
fecha  = STRTRAN(STR(DAY(DATE()),2)+STR(MONTH(DATE()),2)+SUBSTR(STR(YEAR(DATE()),4),2,2)," ","0")
etx    = ""
bcc    := crearbcc(mark+id+ecr+tarea+tipo+desde+hasta+omitir+fecha+etx)
mport := abrirport(mport)
MsgWait("Aguarde","Espere",.35)
mandar_enq(mport)
IF !leer_ack(mport)
   responde = MsgYesNo("Recibio mal ACK 1")
   IF !responde
      CloseComm(mport)
      RETURN .F.
   ENDIF
ENDIF
MsgWait("Aguarde","Espere",.35)
mandar(mport,stx+mark+id+ecr+tarea+tipo+desde+hasta+omitir+fecha+etx+bcc)
IF !leer_ack(mport)
   MsgAlert("La ECR se encuentra ocupada o con error")
   salida = .f.
ENDIF
mandar_eot(mport)
closeComm(mport)
RETURN salida

FUNCTION CharXOR(car1,car2)
LOCAL n1:=ARRAY(8),n2:=ARRAY(8),res,i,r:=""
n1 := DtoB(ASC(car1))
n2 := DtoB(ASC(car2))
FOR i = 1 to 8
    IF SUBSTR(n1,i,1) <> SUBSTR(n2,i,1)
       r := r + "1"
       ELSE
       r := r + "0"
    ENDIF
NEXT
res = BtoD(r)
RETURN CHR(res)

FUNCTION DtoB(n)
LOCAL arr:="",i
FOR i = 1 to 8
    arr := arr + STR(n % 2,1)
    n = INT(n/2)
NEXT
RETURN arr

FUNCTION BtoD(num)
LOCAL res,a:=ARRAY(8),i
FOR i = 1 to 8
    a[9-i] := VAL(SUBSTR(num,i,1))
NEXT i
res := a[1]*128+a[2]*64+a[3]*32+a[4]*16+a[5]*8+a[6]*4+a[7]*2+a[8]*1
RETURN res

Re: How to read data from a serial port ?

PostPosted: Wed Jul 21, 2021 1:16 am
by vilian
Thank you cmsoft,

But i would like to do this using Harbour API ;)

Re: How to read data from a serial port ?

PostPosted: Wed Jul 21, 2021 1:57 pm
by vilian
I changed my code to use FW functions and everythink worked. I Could read whole the text. The complete source i used is bellow:
Code: Select all  Expand view

#include "Fivewin.ch"
FUNCTION MAIN()

    LOCAL oDlg

    LOCAL oGet, cTxt := ""

    LOCAL nCom

    DEFINE DIALOG oDlg;
           SIZE 500, 500;
           TITLE "Terminale"

    @ 0, 0 GET oGet VAR cTxt MEMO READONLY

    ACTIVATE DIALOG oDlg;
             ON INIT ( oGet:AdjClient(),;
                       nCom := APRICOM( oDlg, oGet ),;
                       IF( nCom < 0, oDlg:End(), ) );
             CENTER

    IF nCom >= 0; CLOSECOMM( nCom ); ENDIF

RETURN NIL

STATIC FUNCTION APRICOM( oDlg, oGet )

    LOCAL nCom, cDcb

    BEGIN SEQUENCE
        nCom = OPENCOMM( "COM4", 16384, 16384 )

        IF nCom < 0
            ? "Errore di apertura della porta di comunicazione."
            BREAK
        ENDIF

        BUILDCOMMDCB( "COM4:9600,N,8,1", @cDcb )

        IF .NOT. SETCOMMSTATE( nCom, cDcb )
            ? "Errore di impostazione della porta di comunicazione."
            BREAK
        ENDIF

        oDlg:bCommNotify = { | nCom | Connect( nCom, oGet ),;
                                      EnableCommNotification( nCom, oDlg:hWnd, 1, -1 ) }

        IF !ENABLECOMMNOTIFICATION( nCom, oDlg:hWnd, 1, -1 )
            ? "Errore di abilitazione della notifica."
            BREAK
        ENDIF
    RECOVER
        nCom = -1
    END SEQUENCE

RETURN nCom

STATIC FUNCTION CONNECT( nCom, oGet )
LOCAL cStr

    ENABLECOMMNOTIFICATION( nCom, 0, 1, -1 )

    cStr = RECEIVESTR( nCom )

    cStr = STRTRAN( cStr, CHR( 13 ), "" )
    cStr = STRTRAN( cStr, CHR( 10 ), CRLF )

    oGet:Append( cStr )

RETURN NIL

STATIC FUNCTION RECEIVESTR( nCom )
LOCAL cBuf := SPACE( 1000 )
RETURN LEFT( cBuf, READCOMM( nCom, @cBuf ) )

Re: How to read data from a serial port ?

PostPosted: Wed Jul 21, 2021 4:23 pm
by Antonio Linares
Thank you Vilian, great sharing :-)

Re: How to read data from a serial port ?

PostPosted: Tue Jul 27, 2021 6:48 pm
by vilian
Antonio,
I'm having a problem with this example. It's increasing CPU use every time the dialog is opened and when it's closed CPU Use is not released. So soon the CPU use arrives in 100%.
Do you know why?

Re: How to read data from a serial port ?

PostPosted: Wed Jul 28, 2021 8:14 am
by Enrico Maria Giordano
I tried your sample, (my sample, actually :-) ), and found no problems. The only think I've changed is COM1 instead of COM4.

EMG

Re: How to read data from a serial port ?

PostPosted: Wed Jul 28, 2021 4:57 pm
by vilian
Enrico,
IF you have COM1 in your micro, could you try this code for a COM port that doesn't exist ?
I'm having the problem when I try to do an OpenComm( cPort, 1024, 10 ), for a COM port that doesn't exist in my computer. The function returns -1, but each time I try, CPU use is increased quickly.

Re: How to read data from a serial port ?

PostPosted: Wed Jul 28, 2021 6:08 pm
by Enrico Maria Giordano
I tried COM4 and get the error message:

"Errore di impostazione della porta di comunicazione."

No problem with CPU usage.

EMG