EmbeddedRelated.com
Forums
The 2024 Embedded Online Conference

BX24 and Pic-Servo (JRKerr)

Started by Don Lewis February 3, 2004
Hello group. I try to solve issues on my own but I am
hung on this one. I am interfacing the JRKerr Pic-Servo chip
to the BX-24. I can talk with the Pic-Servo just fine when
hooked directly to my PC with a serial convertor (MAx233).
When I interface to the BX-24 I can see the data going to and from the
Pic_Servo on the BX-24 pins with an O-Scope. I send a
command and I get a status response visually but I can not
capture a byte. I first set PicInString="" to clear it

If there is a better way to present code troubles please advise.
Thank you for looking over it. It is snipped
for simplicity and may have accidental
errors as well.

Don Lewis

Has anyone interfaced a BX-24 to a Pic-Servo (ttl) and been able to
read the responses?
--------Part of my GlobalDefines module------------
Public Const PicBaud As Long = 19200
Public Const PicPort As Byte = 1
Public Const PicInPin As Byte = 9 'from P-S tx
Public Const PicOutPin As Byte = 10 'to P-S rx

'Public PicCom3In(1 to 25) as Byte 'HOSES I/O
Public PicCom3Out(1 to 32) as Byte
Public PicCom3In as Byte
'Public PicCom3Out as Byte
Public PicInString as String ' AutoSize
Public PicInByte as Byte
------End of defines module-------------------

--------Main module portion-----------------
Call PicServoInit(0) ' Initialise Pic-Servo, addr=0
--------End of Main Module portion-----------

--------------Pic-Servo module portion---------------------
Call OpenQueue(PicCom3In,25) '9 bytes overhead plus 16 bytes data
Call OpenQueue(PicCom3Out,32) '9 bytes overhead plus 23 bytes data

'**********************************************************
'Opens BX-24 com port
'**********************************************************
Private Sub PicCommOpen()
Delay(0.2)
If CommOpen <> 1 then
'PicServo serial protocol, 8n1 default to 19,200, addr=0
Call DefineCom3(PicInPin,PicOutPin,bx0000_1000)

'Define com3 19,200Baud, 16 bytes in, 10 bytes out
Call OpenCom(3,19200,PicCom3In,PicCom3Out)
CommOpen = 1 'set PicServo comm flag
End If
End Sub
'*********************************************************

'**************Begin Module PicServo.bas***********************
'
'Servo Module Command set:
'

Const HARD_RESET As Byte = &HF 'RESET - no status is returned

Const Pic_addr As Integer = 0 'Start Pic_addressing at 0, def
'*********************************************************
'PicServo Initialize
'Initializes controller module on BX24 pins 9 and 10.
'PicInit also determines what type of module is present.
'It should detect a PIC-SERVO module (type 0).
'*********************************************************
Private SUB PicServoInit (ByVal Pic_addr AS INTEGER)

'djl DIM i AS INTEGER
DIM cmdstr AS STRING
DIM statstr AS STRING
DIM cksum AS INTEGER

call PicCommOpen() 'configure PicServo communications

'First issue a reset command:
cmdstr = CHR(HARD_RESET)
CALL SendCommand(&HFF, cmdstr)
'Delay(0.2) 'Wait for command to execute

'Get the status string in return (null string if no response)
'Not returning data 2/1/2004
Call RcvStat(2)
'Call PicGetString()
' If Len(statstr) = 0 Then
IF LEN(PicInString) = 0 THEN

' LENGTH OF STRING IS ALWAYS 0
Debug.Print "PicStrLen: "; CStr(Len(PicInString))

End If
'.....
End Sub
'***************End of PicServoInit portion****************
'*********************************************************************
'SendCommand
'Sends a command string to a controller. The command string should
consist
'of just the command byte and the command data. SendCommand appends the
'header byte , Pic_address byte and checksum byte before sending to the
'controller.
'*********************************************************************
Public Sub SendCommand (ByVal Pic_addr AS INTEGER, ByRef cmdstr AS STRING)
DIM cksum AS Integer
DIM i AS INTEGER
'Add header and Pic_address to beginning of command string
cmdstr = CHR(&HAA) & CHR(Pic_addr) & cmdstr

'Add checksum to the end:
cksum = 0
FOR i = 2 TO Len(cmdstr)
cksum = cksum + CInt(ASC(Mid(cmdstr, i, 1)))
NEXT
cksum = cksum - (256 * (CInt(cksum \ 256)))
cmdstr = cmdstr & CHR(cksum)

'Send the command
Call PutQueueStr(PicCom3Out, cmdstr)

cmdstr = ""
END SUB

'******************************************************************
'******************************************************************
'RcvStat
'Get n chars from com port with 1 sec timeout on receiving 1st char
'******************************************************************
Private Sub RcvStat(ByVal n AS INTEGER)
DIM RetStr AS STRING
Dim TimedOut As Boolean
Dim stat as Byte
DIM cksum AS INTEGER
DIM i AS INTEGER
Dim pos As Integer
PicInString = ""

' check whether there is any input; if not, then loop again, if so,
read it
Do
If StatusQueue(PicCom3In) Then ' Does go true
Exit Do
End If
Loop

If StatusQueue(PicCom3In) Then ' read byte from the input
Call GetQueue(PicCom3In, PicInString, n, 1.0, TimedOut)
stat = CByte(ASC(PicInString)) 'get the status byte
Debug.Print "Stat_val:"; CStr(stat) ' NEVER GETS
IF (CBool(stat) AND CBool(2) ) THEN 'check status byte for
command cksum error
Debug.Print "Cmderror"; CStr(stat)
CALL ExitProgram ' sends a couple of resets
END IF

'Check status data for checksum error
cksum = 0
FOR i = 1 TO (n - 1)
cksum = cksum + CInt(ASC(MID(PicInString, i, 1)))
NEXT
cksum = cksum - (256 * (CINT(cksum \ 256)))
'My Right$ string code
pos = LEN(PicInString)
stat = Cbyte(ASC(Mid(PicInString,pos,1))) 'Right str func hack,

IF (CBool(cksum) <> CBool(stat)) THEN
Debug.Print "Stat_err:"; CStr(stat)
CALL ExitProgram
END IF

' Pass string back End Function
RcvStat = PicInString
Exit Function

ELSE
RcvStat = ""
'END Function

END IF
End Sub
'Other code eliminated
'**************End of Module PicServo.bas***********************



Rather than try to repair my mess, if anyone has a
way to make it work with my structure I will happily work from that.

Global defines sets up variables

Main module will call Pic-Servo functions
the first being a INIT. later control of a motor.

The PicServo module will handle all the Pic-Servo
specific procedures and functions. I am trying
to do status and checksum testing of valid data to and from
the Pic-Servo. As well as gather the status data.
It appears that my commands to the Pic are going through as I can see
data coming from it with my oscilloscope.
I can not capture any data. Thanks again,
Don Lewis

--- In , "Don Lewis" <djlewis@a...> wrote:
> Hello group. I try to solve issues on my own but I am
> hung on this one. I am interfacing the JRKerr Pic-Servo chip
> to the BX-24. I can talk with the Pic-Servo just fine when
> hooked directly to my PC with a serial convertor (MAx233).
> When I interface to the BX-24 I can see the data going to and from the
>




From: Don Lewis <>

> [...] I am interfacing the JRKerr Pic-Servo chip
> to the BX-24. I can talk with the Pic-Servo just
> fine when hooked directly to my PC with a serial
> convertor (MAx233). When I interface to the BX-24
> I can see the data going to and from the
> Pic_Servo on the BX-24 pins with an O-Scope. [...]

I notice you're using a lot of strings. Possibly a stack overflow
is occurring, especially if the default string length is 64
characters.

Also, in procedure PicCommOpen, I'm wondering if variable CommOpen
is being read before it's initialized?

Another thing that looks a little suspicious is this line:

IF (CBool(stat) AND CBool(2) ) THEN

I realize that in the C world this is considered normal and the
explicit type casting redundant, but I'm not sure what this code
is really supposed to do...

-- Frank Manning
-- NetMedia, Inc.



Replies inside msg and the original code from JRKerr I am trying to
make work is pasted below.I have included three portions,
The RcvStat routine, the SendCommand routine and the
calling routine PicInit. I just need a bit of guidance here.
I only use one module so ModuleType is skipped.
Thank you Frank

--- In , "Frank Manning" <fmanning@n...> wrote:
> From: Don Lewis <djlewis@a...>
>
> I notice you're using a lot of strings. Possibly a stack overflow
> is occurring, especially if the default string length is 64
> characters.

Is there a better choice for storing the data?
Ram Pokes?

>
> Also, in procedure PicCommOpen, I'm wondering if variable CommOpen
> is being read before it's initialized?
>

As three Com3's are being used this is a marker variable.
THe routine skips reinitializing if false
the values set are PicServo = 1, LCD+ = 2, Gemini = 3
Before this routine is called either LCD+ or Gemini will leave it set.

> Another thing that looks a little suspicious is this line:
>
> IF (CBool(stat) AND CBool(2) ) THEN
>
> I realize that in the C world this is considered normal and the
> explicit type casting redundant, but I'm not sure what this code
> is really supposed to do...

Hmmm, this is my hack for doing a Boolean test. THe original was
from a program named PSTEST.bas a QBasic program that JRKerr
had available on thier site. I have included it below.

>
> -- Frank Manning
> -- NetMedia, Inc

**PSTEST.BAS from JRKerr samples, includes three routines******
'RcvStat
'Get n chars from com port with 1 sec timeout on receiving 1st char
'
FUNCTION RcvStat$ (n AS INTEGER)
DIM RetStr AS STRING
DIM stat AS INTEGER
DIM cksum AS INTEGER
DIM i AS INTEGER

'Install handlers for com and timeout events:
ON COM(ComPort) GOSUB ComEventHandler
COM(ComPort) ON
ON TIMER(1) GOSUB TimerEventHandler
TIMER ON

'Set flag to wait for one event or the other
RcvdChar = 0

'Wait for an event
DO
IF RcvdChar <> 0 THEN EXIT DO
LOOP

'disable event handlers
TIMER OFF
COM(ComPort) OFF

IF (RcvdChar = 1) THEN
RetStr = INPUT$(n, #1)
stat = ASC(RetStr) 'get the status byte
IF (stat AND 2) THEN 'check status byte for command cksum error
PRINT "Command checksum error"; stat
CALL ExitProgram
END IF

'Check status data for checksum error
cksum = 0
FOR i = 1 TO (n - 1)
cksum = cksum + ASC(MID$(RetStr, i, 1))
NEXT i
cksum = cksum - 256 * INT(cksum / 256)
IF cksum <> ASC(RIGHT$(RetStr, 1)) THEN
PRINT "Status checksum error"
CALL ExitProgram
END IF

RcvStat$ = RetStr
ELSE
RcvStat$ = ""
END IF

END FUNCTION

'Sends a command string to a controller. The command string should
consist
'of just the command byte and the command data. SendCommand appends the
'header byte , address byte and checksum byte before sending to the
'controller.
'
SUB SendCommand (addr AS INTEGER, cmdstr AS STRING)
DIM cksum AS INTEGER
DIM i AS INTEGER

'Add header and address to beginning of command string
cmdstr = CHR$(&HAA) + CHR$(addr) + cmdstr
'Add checksum to the end:
cksum = 0
FOR i = 2 TO LEN(cmdstr)
cksum = cksum + ASC(MID$(cmdstr, i, 1))
NEXT i
cksum = cksum - 256 * INT(cksum / 256)
cmdstr = cmdstr + CHR$(cksum)

'Send the command
PRINT #1, cmdstr;

END SUB

'Initializes controller modules on COM1 or COM2 (port = 1 or 2). Modules
'may be PIC-SERVO controllers, PIC-IO modules, or in the future, other
types.
'Addresses assigned to each module start 1 for the module furthest
from the
'host and increase from there.
'
'NmcInit alse determines what type of modules are present. Currently,
'it can detect PIC-SERVO modules (type 0) and PIC-IO modules (type 2).
'Module types are stored in the array ModuleType().
'
SUB NmcInit (Port AS INTEGER)
DIM i AS INTEGER
DIM cmdstr AS STRING
DIM statstr AS STRING
DIM cksum AS INTEGER

IF Port = 1 THEN
OPEN "COM1:19200,N,8,1,BIN,CD0,CS0,DS0,OP0,RS,TB1024,RB1024" FOR
RANDOM AS #1
ComPort = 1
ELSE
OPEN "COM2:19200,N,8,1,BIN,CD0,CS0,DS0,OP0,RS,TB1024,RB1024" FOR
RANDOM AS #1
ComPort = 2
END IF

CLS
PRINT "Initializing network..."

'First issue a reset command:
cmdstr = CHR$(&HF)
CALL SendCommand(&HFF, cmdstr)
SLEEP (1) 'Wait for command to execute
'Reset a second time to ensure reset
cmdstr = CHR$(&HF)
CALL SendCommand(&HFF, cmdstr)
SLEEP (1) 'Wait for command to execute

i = 1 'Start addressing at 1
DO
'Build command string to change address:
cmdstr = CHR$(&H21) + CHR$(i) + CHR$(&HFF)
CALL SendCommand(0, cmdstr)

'Get the status string in return (null string if no response)
statstr = RcvStat$(2) ' receive 2 bytes
IF LEN(statstr) = 0 THEN EXIT DO

'Determine the module's type:
cmdstr = CHR$(&H13) + CHR$(&H20)
CALL SendCommand(i, cmdstr)
statstr = RcvStat$(4) ' receive 4 bytes
IF LEN(statstr) = 0 THEN CALL ExitProgram
ModuleType(i) = ASC(MID$(statstr, 2, 1))
PRINT "Module "; i; " is of type "; ModuleType(i)

'Set to return all status data:
cmdstr = CHR$(&H12) + CHR$(&HFF)
CALL SendCommand(i, cmdstr)
'Get the appropriate amount of data in return:
IF ModuleType(i) = 0 THEN
ModuleData(i) = RcvStat$(16)
ELSEIF ModuleType(i) = 2 THEN
ModuleData(i) = RcvStat$(19)

'Initialize I/O variables for I/O module:
IoDir(i) = &HFFF
IoOutVal(i) = 0
ELSE
PRINT "Module type "; ModuleType(i); " is not supported"
CALL ExitProgram
END IF
IF LEN(ModuleData(i)) = 0 THEN CALL ExitProgram

i = i + 1 'Increment the address
LOOP

NumModules = i - 1
PRINT NumModules; "module(s) found on the network"

END SUB


From: Don Lewis <>

> Frank Manning <fmanning@n...> wrote:
>
>> I notice you're using a lot of strings. Possibly a
>> stack overflow is occurring, especially if the
>> default string length is 64 characters.
>
> Is there a better choice for storing the data?
> Ram Pokes?

Not necessarily. There's nothing wrong with strings themselves --
you just need to be careful of string sizes, which can easily get
out of hand.

>> Another thing that looks a little suspicious is this
>> line:
>>
>> IF (CBool(stat) AND CBool(2) ) THEN
>
> Hmmm, this is my hack for doing a Boolean test. THe
> original was from a program named PSTEST.bas a QBasic
> program that JRKerr had available on thier site. I
> have included it below.

This is good -- it's helpful to have existing code that works. I
assume this is the original line:

> IF (stat AND 2) THEN 'check status byte [...]

If you avoid QBasic's implicit type conversions, the code really
does this:

IF ((stat AND 2) <> 0) THEN

I suspect the real intent is to check whether bit 1 is set.
Another alternative might make the intent clearer:

IF ((stat AND bx0000_0010) = bx0000_0010) THEN

-- Frank Manning
-- NetMedia, Inc.



Your queues are not defined correctly.
They need to be arrays. Your inbound queue is one byte.
The correct line is commented out.
***
Dont use neighboring pins for I/O if you dont need to.
I've found every-other-one works good or even the pin on the other side of
the chip, is even better.
Less noise.
***
Scrap the PUBLIC CONST on those PicXXXXXX constants.
19200 already is a constant, so why define it twice.
Use the constants themselves on the actual statements if you are trying to
tweak for memory usage.
***
Set your project's Max String Size to the largest size you plan on working
with on the auto-sizing strings.
Add one or two more bytes, just as a buffer. Ex: 24 byte string max = 24 +
2 = 26 byte project string size.
***
Open all the I/O queues in MAIN() and forget about them. You have them in
subroutines. Do it as part of Main's initialization process. Define the
queues, Public so everything see them and can use them.
***
Change the variable COMMOPEN to be Boolean typed.
Use the keywords True & False. Booleans are 1-bit. Bytes are 8-Bits.
Eight Boolean flags could be defined and used in just the ram wasted right
there alone.
***
Define the larger numeric data types first, then work down in size.
From Unsigns, to Longs, ..., down to Booleans.
Define Strings last, fixed strings first, with the auto-sizing ones the very
last types defined.
***
Avoid Debug.Print like the plague.
Even more so if in a subroutine.
Open a Com1 and put your data on the queue.
That system call is very resource intensive.
***
In the sub RcvStat, you have that funky Do Loop that checks if data is on
the inbound queue.
Because of the break in logical structure with the Exit Do, there is heavy
stack usage as the system maintains the logic token of the Do Loop.

Then, right after the condition is satisfied and data is present on the
queue, there is more overhead as the IF-Block is processed. "If data is on
the queue...". Seems like overkill since the Do Loop prevented the logic
from advancing that far in the first place.

Simplify that Do Loop like so:

DO UNTIL STATUSQUEUE(PicCom3In)
CALL DELAY(0.00)
LOOP

The thing will wait for inbound data and then continue on -- instead of
using the Exit DO.
Try not to ever break the symmetry of a Do Loop. Let it flow in logic
naturally.
***
CKSUM is defined and used in more then one place.
Make it global.
***
What really gets me is that you say it works with that one-byte inbound
queue.
I just dont see how it could.
The system pointers that maintain the queue, you know, the 9 byte overhead,
those bytes are overlaying *something* in memory.
Thats an unforeseen lockup.
A 1-byte queue would be an array of 10, 9 overhead, 1 data byte.
***

.db.
-----Original Message-----
From: Don Lewis [mailto:]
Sent: Tuesday, February 03, 2004 12:12 PM
To:
Subject: [BasicX] BX24 and Pic-Servo (JRKerr) Hello group. I try to solve issues on my own but I am
hung on this one. I am interfacing the JRKerr Pic-Servo chip
to the BX-24. I can talk with the Pic-Servo just fine when
hooked directly to my PC with a serial convertor (MAx233).
When I interface to the BX-24 I can see the data going to and from the
Pic_Servo on the BX-24 pins with an O-Scope. I send a
command and I get a status response visually but I can not
capture a byte. I first set PicInString="" to clear it

If there is a better way to present code troubles please advise.
Thank you for looking over it. It is snipped
for simplicity and may have accidental
errors as well.

Don Lewis

Has anyone interfaced a BX-24 to a Pic-Servo (ttl) and been able to
read the responses?
--------Part of my GlobalDefines module------------
Public Const PicBaud As Long = 19200
Public Const PicPort As Byte = 1
Public Const PicInPin As Byte = 9 'from P-S tx
Public Const PicOutPin As Byte = 10 'to P-S rx

'Public PicCom3In(1 to 25) as Byte 'HOSES I/O
Public PicCom3Out(1 to 32) as Byte
Public PicCom3In as Byte
'Public PicCom3Out as Byte
Public PicInString as String ' AutoSize
Public PicInByte as Byte
------End of defines module-------------------

--------Main module portion-----------------
Call PicServoInit(0) ' Initialise Pic-Servo, addr=0
--------End of Main Module portion-----------

--------------Pic-Servo module portion---------------------
Call OpenQueue(PicCom3In,25) '9 bytes overhead plus 16 bytes data
Call OpenQueue(PicCom3Out,32) '9 bytes overhead plus 23 bytes data

'**********************************************************
'Opens BX-24 com port
'**********************************************************
Private Sub PicCommOpen()
Delay(0.2)
If CommOpen <> 1 then
'PicServo serial protocol, 8n1 default to 19,200, addr=0
Call DefineCom3(PicInPin,PicOutPin,bx0000_1000)

'Define com3 19,200Baud, 16 bytes in, 10 bytes out
Call OpenCom(3,19200,PicCom3In,PicCom3Out)
CommOpen = 1 'set PicServo comm flag
End If
End Sub
'*********************************************************

'**************Begin Module PicServo.bas***********************
'
'Servo Module Command set:
'

Const HARD_RESET As Byte = &HF 'RESET - no status is returned

Const Pic_addr As Integer = 0 'Start Pic_addressing at 0, def
'*********************************************************
'PicServo Initialize
'Initializes controller module on BX24 pins 9 and 10.
'PicInit also determines what type of module is present.
'It should detect a PIC-SERVO module (type 0).
'*********************************************************
Private SUB PicServoInit (ByVal Pic_addr AS INTEGER)

'djl DIM i AS INTEGER
DIM cmdstr AS STRING
DIM statstr AS STRING
DIM cksum AS INTEGER

call PicCommOpen() 'configure PicServo communications

'First issue a reset command:
cmdstr = CHR(HARD_RESET)
CALL SendCommand(&HFF, cmdstr)
'Delay(0.2) 'Wait for command to execute

'Get the status string in return (null string if no response)
'Not returning data 2/1/2004
Call RcvStat(2)
'Call PicGetString()
' If Len(statstr) = 0 Then
IF LEN(PicInString) = 0 THEN

' LENGTH OF STRING IS ALWAYS 0
Debug.Print "PicStrLen: "; CStr(Len(PicInString))

End If
'.....
End Sub
'***************End of PicServoInit portion****************
'*********************************************************************
'SendCommand
'Sends a command string to a controller. The command string should
consist
'of just the command byte and the command data. SendCommand appends the
'header byte , Pic_address byte and checksum byte before sending to the
'controller.
'*********************************************************************
Public Sub SendCommand (ByVal Pic_addr AS INTEGER, ByRef cmdstr AS STRING)
DIM cksum AS Integer
DIM i AS INTEGER
'Add header and Pic_address to beginning of command string
cmdstr = CHR(&HAA) & CHR(Pic_addr) & cmdstr

'Add checksum to the end:
cksum = 0
FOR i = 2 TO Len(cmdstr)
cksum = cksum + CInt(ASC(Mid(cmdstr, i, 1)))
NEXT
cksum = cksum - (256 * (CInt(cksum \ 256)))
cmdstr = cmdstr & CHR(cksum)

'Send the command
Call PutQueueStr(PicCom3Out, cmdstr)

cmdstr = ""
END SUB

'******************************************************************
'******************************************************************
'RcvStat
'Get n chars from com port with 1 sec timeout on receiving 1st char
'******************************************************************
Private Sub RcvStat(ByVal n AS INTEGER)
DIM RetStr AS STRING
Dim TimedOut As Boolean
Dim stat as Byte
DIM cksum AS INTEGER
DIM i AS INTEGER
Dim pos As Integer
PicInString = ""

' check whether there is any input; if not, then loop again, if so,
read it
Do
If StatusQueue(PicCom3In) Then ' Does go true
Exit Do
End If
Loop

If StatusQueue(PicCom3In) Then ' read byte from the input
Call GetQueue(PicCom3In, PicInString, n, 1.0, TimedOut)
stat = CByte(ASC(PicInString)) 'get the status byte
Debug.Print "Stat_val:"; CStr(stat) ' NEVER GETS
IF (CBool(stat) AND CBool(2) ) THEN 'check status byte for
command cksum error
Debug.Print "Cmderror"; CStr(stat)
CALL ExitProgram ' sends a couple of resets
END IF

'Check status data for checksum error
cksum = 0
FOR i = 1 TO (n - 1)
cksum = cksum + CInt(ASC(MID(PicInString, i, 1)))
NEXT
cksum = cksum - (256 * (CINT(cksum \ 256)))
'My Right$ string code
pos = LEN(PicInString)
stat = Cbyte(ASC(Mid(PicInString,pos,1))) 'Right str func hack,

IF (CBool(cksum) <> CBool(stat)) THEN
Debug.Print "Stat_err:"; CStr(stat)
CALL ExitProgram
END IF

' Pass string back End Function
RcvStat = PicInString
Exit Function

ELSE
RcvStat = ""
'END Function

END IF
End Sub
'Other code eliminated
'**************End of Module PicServo.bas***********************
_____

> .






Dan Bielecki wrote:
> Change the variable COMMOPEN to be Boolean typed.
> Use the keywords True & False. Booleans are 1-bit. Bytes are 8-Bits.

Dan
My understanding is that each boolian uses 8 bits (unfortunately)
unless things have chenged recently
neil j



that was "boolean"!
>





A variable that holds True or False, also a logical operation where the
result is binary 0 or 1 or true or false, the latter in case of the
BX24.

Dim X as boolean ' This is the one (it also conserves memory!).
Dim Z as integer

X = True
If X = true then
do this
end if

---------------------------
Z = 2
If Z > 1 then
X = True
else
X = False
end if

If X = False then ' will not happen
do this
end if On Feb 4, 2004, at 1:30 PM, Neil Jepsen wrote:

> that was "boolean"!
> >
>
> ------------------------ Yahoo! Groups Sponsor
> ---------------------~-->
> Upgrade to 128-bit SSL Security!
> http://us.click.yahoo.com/qZ0LdD/yjVHAA/TtwFAA/dN_tlB/TM
> ---------------------------------
> ~- > --
> Este mensaje ha sido analizado con MailScanner
> y se considera que estlimpio.


---------
Francisco Lobo de la Garza
CEO/Director General
movic Records
elcielo Recording Studio
Garza Garcia N.L Mexico
---------
Grupo Fusion Global
Copyright(c) 2003-2004
---------------
POR FAVOR no incluyas este mail en
listas de correo ni en sistemas
automatizados de mensajes.
PLEASE do not include this email
address in any mailing list or
newsletters.

--
Este mensaje ha sido analizado con MailScanner
y se considera que estlimpio.


From: Dan Bielecki <>

> [...]
> Change the variable COMMOPEN to be Boolean typed.
> Use the keywords True & False. Booleans are
> 1-bit. Bytes are 8-Bits. [...]

Booleans are 8 bit, not 1 bit.

> Define the larger numeric data types first, then
> work down in size. From Unsigns, to Longs, ...,
> down to Booleans. Define Strings last, fixed
> strings first, with the auto-sizing ones the
> very last types defined.

I don't understand the rationale for this. The program won't run
faster, nor will you save any memory by ordering variables like
this.

> [...]
>
> Simplify that Do Loop like so:
>
> DO UNTIL STATUSQUEUE(PicCom3In)
> CALL DELAY(0.00)
> LOOP
>
> [...]

Forgive me for sounding like a broken record, but why is the zero
delay there?

A zero delay will slow down the loop by approximately 70
microseconds per cycle. Is there some benefit to be gained that
offsets the slower execution time? Do you see fewer data overruns,
or is there some other beneficial effect?

The system will process the queues with or without the delay
statement. As far as I can see, a zero delay is useless unless you
have another task running in parallel.

For those of you just tuning in, the main purpose of a zero delay
is to encourage other tasks to run in a multitasking program. If
you have only one task, which is the case here, a zero delay
serves no purpose.

-- Frank Manning
-- NetMedia, Inc.




The 2024 Embedded Online Conference