[squeak-dev] Question about serial port communication

Jon Hylands jon at huv.com
Sat Jun 20 20:29:51 UTC 2009


On Sat, 20 Jun 2009 21:39:37 +0200, Víctor C. T. <victorct83 at gmail.com>
wrote:

> Is it correct? I don't get any error at this point...

I don't see any code to specify the # of data bits, # of stop bits, or the
parity. Do they default to the "normal" values (8N1)?

Also, you need to make sure the port itself is set up without any hardware
flow control - I've never used an Arduino, but I assume its providing a USB
interface that ends up using an FT232 or something like that.

That serial port class is different than the one I use for my robotics
stuff. I've attached the serial port class I use, and it is set up like
this:

	| serialPort baudRate comPortNumber |
	baudRate := 115200.
	comPortNumber := 2.
	serialPort := SerialPort new
		baudRate: baudRate;
		dataBits: 8;
		stopBitsType: 1;
		parityType: 0;
		yourself.

	(serialPort openPort: comPortNumber) isNil
		ifTrue: [ ^self error: 'COM port not available' ].

	...
	serialPort close.

Later,
Jon

--------------------------------------------------------------
   Jon Hylands      Jon at huv.com      http://www.huv.com/jon

  Project: Micro Raptor (Small Biped Velociraptor Robot)
           http://www.huv.com/blog
-------------- next part --------------
'From Squeak3.10.2 of ''5 June 2008'' [latest update: #7179] on 20 June 2009 at 4:26:03 pm'!
Object subclass: #SerialPort
	instanceVariableNames: 'port baudRate stopBitsType parityType dataBits outputFlowControlType inputFlowControlType xOnByte xOffByte'
	classVariableNames: ''
	poolDictionaries: ''
	category: 'System-Serial Port'!
!SerialPort commentStamp: '<historical>' prior: 0!
This class supports a simple interface to the serial ports of the underlying platform, if it supports serial ports. The mapping of port numbers to hardware ports is platform specific, but typically follows platform ordering conventions. For example, on the Macintosh, port 0 is the modem port and port 1 is the printer port, since in the programmers documentation these ports are referred to as ports A and B.
!


!SerialPort methodsFor: 'initialization' stamp: 'jm 5/5/1998 15:49'!
initialize
	"Default port settings."

	port _ nil.					"set when opened"
	baudRate _ 9600.			"9600 baud"
	stopBitsType _ 1.				"one stop bit"
	parityType _ 0.				"no parity"
	dataBits _ 8.					"8 bits"
	outputFlowControlType _ 0.	"none"
	inputFlowControlType _ 0.	"none"
	xOnByte _ 19.				"ctrl-S"
	xOffByte _ 24.				"ctrl-X"
! !


!SerialPort methodsFor: 'input/output' stamp: 'yo 2/2/2001 15:13'!
nextPutAll: aStringOrByteArray
	"Send the given bytes out this serial port. The port must be open."

	^ self primWritePort: port
		from: aStringOrByteArray
		startingAt: 1
		count: aStringOrByteArray size.
! !

!SerialPort methodsFor: 'input/output' stamp: 'jm 5/18/1998 15:44'!
readByteArray
	"Answer a ByteArray read from this serial port. Answer an empty ByteArray if no data is available. The port must be open."

	| buf count |
	buf _ ByteArray new: 1000.
	count _ self primReadPort: port into: buf startingAt: 1 count: buf size.
	^ buf copyFrom: 1 to: count
! !

!SerialPort methodsFor: 'input/output' stamp: 'jm 5/18/1998 15:46'!
readInto: aStringOrByteArray startingAt: index
	"Read data into the given String or ByteArray object starting at the given index, and answer the number of bytes read. Does not go past the end of the given String or ByteArray."

	^ self primReadPort: port
		into: aStringOrByteArray
		startingAt: index
		count: (aStringOrByteArray size - index) + 1.
! !

!SerialPort methodsFor: 'input/output' stamp: 'jm 5/18/1998 15:43'!
readString
	"Answer a String read from this serial port. Answer the empty String if no data is available. The port must be open."

	| buf count |
	buf _ String new: 1000.
	count _ self primReadPort: port into: buf startingAt: 1 count: buf size.
	^ buf copyFrom: 1 to: count
! !


!SerialPort methodsFor: 'open/close' stamp: 'jm 5/18/1998 15:40'!
close
	"Close the serial port. Do nothing if the port is not open."

	port ifNotNil: [self primClosePort: port].
	port _ nil.
! !

!SerialPort methodsFor: 'open/close' stamp: 'dns 6/27/2000 19:49'!
openPort: portNumber
	"Open the given serial port, using the settings specified by my instance variables. If the port cannot be opened, such as when it is alreay in use, answer nil."  "(DNS)"

	self close.
	(self primClosePort: portNumber) isNil ifTrue: [
		^ nil ].
	(self primOpenPort: portNumber
		baudRate: baudRate
		stopBitsType: stopBitsType
		parityType: parityType
		dataBits: dataBits
		inFlowControlType: inputFlowControlType
		outFlowControlType: outputFlowControlType
		xOnByte: xOnByte
		xOffByte: xOffByte) isNil ifTrue: [
			^ nil ].
	port _ portNumber
! !


!SerialPort methodsFor: 'primitives' stamp: 'ar 2/2/2001 15:09'!
primClosePort: portNumber

	<primitive: 'primitiveSerialPortClose' module: 'SerialPlugin'>
	^ nil  "(DNS)"
	"self primitiveFailed."
! !

!SerialPort methodsFor: 'primitives' stamp: 'ar 2/2/2001 15:09'!
primOpenPort: portNumber baudRate: baud stopBitsType: stop
	parityType: parity dataBits: numDataBits
	inFlowControlType: inFlowCtrl outFlowControlType: outFlowCtrl
	xOnByte: xOn xOffByte: xOff

	<primitive: 'primitiveSerialPortOpen' module: 'SerialPlugin'>
	^ nil  "(DNS)"
! !

!SerialPort methodsFor: 'primitives' stamp: 'ar 2/2/2001 15:09'!
primReadPort: portNumber into: byteArray startingAt: startIndex count: count

	<primitive: 'primitiveSerialPortRead' module: 'SerialPlugin'>
	self primitiveFailed.
! !

!SerialPort methodsFor: 'primitives' stamp: 'ar 2/2/2001 15:09'!
primWritePort: portNumber from: byteArray startingAt: startIndex count: count

	<primitive: 'primitiveSerialPortWrite' module: 'SerialPlugin'>
	self primitiveFailed.
! !


!SerialPort methodsFor: 'printing' stamp: 'jm 5/1/1998 18:02'!
printOn: aStream

	aStream
		nextPutAll: 'SerialPort(';
		nextPutAll:
			(port ifNil: ['closed'] ifNotNil: ['#', port printString]);
		nextPutAll: ', ';
		print: baudRate; nextPutAll: ' baud, ';
		print: dataBits; nextPutAll: ' bits, ';
		nextPutAll: (#('1.5' '1' '2') at: stopBitsType + 1); nextPutAll: ' stopbits, ';
		nextPutAll: (#('no' 'odd' 'even') at: parityType + 1); nextPutAll: ' parity)'.
! !


!SerialPort methodsFor: 'settings' stamp: 'jm 5/1/1998 17:19'!
baudRate

	^ baudRate
! !

!SerialPort methodsFor: 'settings' stamp: 'jm 5/1/1998 17:29'!
baudRate: anInteger
	"Set the baud rate for this serial port."

	baudRate _ anInteger.
! !

!SerialPort methodsFor: 'settings' stamp: 'jm 5/1/1998 17:19'!
dataBits

	^ dataBits
! !

!SerialPort methodsFor: 'settings' stamp: 'jm 5/1/1998 17:29'!
dataBits: anInteger
	"Set the number of data bits for this serial port to 5, 6, 7, or 8."

	dataBits _ anInteger.
! !

!SerialPort methodsFor: 'settings' stamp: 'jm 5/1/1998 17:21'!
inputFlowControlType

	^ inputFlowControlType
! !

!SerialPort methodsFor: 'settings' stamp: 'jm 5/1/1998 17:38'!
inputFlowControlType: anInteger
	"Set the type of input flow control, where:
		0 - none
		1 - XOn/XOff
		2 - hardware handshaking"

	inputFlowControlType _ anInteger.
! !

!SerialPort methodsFor: 'settings' stamp: 'jm 5/1/1998 17:19'!
outputFlowControlType

	^ outputFlowControlType
! !

!SerialPort methodsFor: 'settings' stamp: 'jm 5/1/1998 17:38'!
outputFlowControlType: anInteger
	"Set the type of output flow control, where:
		0 - none
		1 - XOn/XOff
		2 - hardware handshaking"

	outputFlowControlType _ anInteger.
! !

!SerialPort methodsFor: 'settings' stamp: 'jm 5/1/1998 17:19'!
parityType

	^ parityType
! !

!SerialPort methodsFor: 'settings' stamp: 'jm 5/1/1998 17:29'!
parityType: anInteger
	"Set the parity type for this serial port, where:
		0 - no parity
		1 - odd parity
		2 - even parity"

	parityType _ anInteger.
! !

!SerialPort methodsFor: 'settings' stamp: 'jm 5/1/1998 17:19'!
stopBitsType

	^ stopBitsType
! !

!SerialPort methodsFor: 'settings' stamp: 'jm 5/1/1998 18:02'!
stopBitsType: anInteger
	"Set the stop bits type for this serial port, where:
		0 - 1.5 stop bits
		1 - one stop bit
		2 - two stop bits"

	stopBitsType _ anInteger.
! !

!SerialPort methodsFor: 'settings' stamp: 'jm 5/1/1998 17:20'!
xOffByte

	^ xOffByte
! !

!SerialPort methodsFor: 'settings' stamp: 'jm 5/1/1998 17:28'!
xOffByte: anInteger
	"Set the value of the XOff byte to be used if XOn/XOff flow control is enabled."

	xOffByte _ anInteger.
! !

!SerialPort methodsFor: 'settings' stamp: 'jm 5/1/1998 17:20'!
xOnByte

	^ xOnByte
! !

!SerialPort methodsFor: 'settings' stamp: 'jm 5/1/1998 17:28'!
xOnByte: anInteger
	"Set the value of the XOn byte to be used if XOn/XOff flow control is enabled."

	xOnByte _ anInteger.
! !


!SerialPort methodsFor: '*ai extensions' stamp: 'jon 10/10/2004 13:46'!
isConnected

	^port notNil! !

!SerialPort methodsFor: '*ai extensions' stamp: 'Jon 10/27/2005 16:14'!
readLargeByteArray
	"Answer a ByteArray read from this serial port. Answer an empty ByteArray if no data is available. The port must be open."

	| buf count |
	buf _ ByteArray new: 4096.
	count _ self primReadPort: port into: buf startingAt: 1 count: buf size.
	^ buf copyFrom: 1 to: count
! !

"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!

SerialPort class
	instanceVariableNames: ''!


More information about the Squeak-dev mailing list