LabRat

Philip Knodle pknodle at bu.edu
Tue Nov 13 07:40:58 UTC 2001


Well, there seems to be a tradition of newbies posting there first 
project to the list.  Not being one to fight tradition, I bring you: 
LabRat, the attempt to get squeak talking to DAQ cards and to web
in general.  

This is the latest iteration of a project I've been working on for a 
while.  I've put a basic optics experiement on the web so that you can 
twiddle the frobs and get data in a webbrowser.  I did this last year in 
java and I'm working to port my stuff to Squeak, and then extend it.

So I started work on this.  I wrote some classes that will connect to my 
java server and grap some
data.  I'm running in to two problems that I would like some advise on.

1) I can't get the refactoring browser to work.  I have a lot of things 
I want to change, but I
can't seem to get the rerfactoring browser to work.  Can anyone point me 
at documentation?

2) I need to figure out how do streaming.  I want to stream over a 
collection of numbers that
aren't on the the machine yet.  I made a direct subclass of Stream, but 
I had to change the new method to not throw an error.  I don't know if 
this is what I should do.  

There is a lot to do at this point.  I want to integrate Denis Damico's 
meters somehow.  Also, I want to write a plug in for the DAQ drivers, 
but this is other topic all together.

BTW, the home page for the java part fo the project is blue.bu.edu

Happy Hacking
Philip Knodle
-------------- next part --------------
'From Squeak3.0 of 4 February 2001 [latest update: #3552] on 13 November 2001 at 2:01:33 am'!
"Change Set:		LabRat
Date:			13 November 2001
Author:			Philip Knodle

This is an early cut of LabRat, an attempt to replace Labview, Simulink, and All those 
Mean nasty ugly tools with Squeak"!

GraphMorph subclass: #Chart
	instanceVariableNames: 'myCollection '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'LabRat-Morphs'!

!Chart commentStamp: 'pjk 11/5/2001 19:17' prior: 0!
A simple chart to test out LabRat.  All Display elements work on Ordered collecitons of
Numbers. Right now, This just takes an ordered Collection of Numbers, and plots 
them.  The X axis is the number in the collection, the y axis is the number.!

Object subclass: #GaspType
	instanceVariableNames: 'name isInt size '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'LabRat-Gasp'!
Object subclass: #GaspUnit
	instanceVariableNames: 'name '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'LabRat-Gasp'!
Stream subclass: #LRDataStream
	instanceVariableNames: 'end inputData inputLock name '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'LabRat-Streams'!

!LRDataStream commentStamp: 'pjk 11/5/2001 20:40' prior: 0!
I am a Stream that you can read and write Data for LabRat Applications.  The 
Stock implemenation (right now) is of GASP, the streams protocol used in the CRCD 
Lab at Boston University.  (http://blue.bu.edu)

Instances
end - true if this stream is at it's end !

Object subclass: #LRGaspConnection
	instanceVariableNames: 'sock types streams units inputLock outputLock inputBuffer outputBuffer input output parseContinue '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'LabRat-Gasp'!
LRDataStream subclass: #LRGaspStream
	instanceVariableNames: 'gaspConnection type unit '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'LabRat-Streams'!

!Chart methodsFor: 'commands' stamp: 'pjk 11/5/2001 20:28'!
loadCollection: aCollection
	myCollection _ aCollection.
	[ myCollection do:[:i| self appendValue:i] ] fork.! !


!GaspType methodsFor: 'acessing' stamp: 'pjk 11/6/2001 21:02'!
getName 
^ name! !

!GaspType methodsFor: 'acessing' stamp: 'pjk 11/6/2001 21:02'!
setName: myName
name _ myName! !

!GaspType methodsFor: 'acessing' stamp: 'pjk 11/6/2001 23:50'!
setSize: numberBytes
"Set the number of bytes per unit."
size _ (numberBytes asNumber)! !

!GaspType methodsFor: 'acessing' stamp: 'pjk 11/10/2001 01:58'!
setType: newType
"Sets if this is an integer, a floatingpoint number, or raw."
isInt _ (newType = 'int').
(newType isKindOf: Boolean)ifTrue:[isInt _ newType]! !

!GaspType methodsFor: 'data' stamp: 'pjk 11/10/2001 03:30'!
bytesToNumbers: bytes 
	| data number |
	
	data _ OrderedCollection new.
	number _ 0.
	
	bytes
		doWithIndex: [:e :i | 
			number _ number + (e << (4 * (size -1 - (i-1 \\ size)))).
			i  \\ size = 0
				ifTrue: [data addLast: number.
					number _ 0]].
	^ data! !


!GaspType class methodsFor: 'instance creation' stamp: 'pjk 11/9/2001 01:53'!
name: myName size: numberBytes isInt: int
|ret| 
ret _ GaspType new.
ret setName: myName .
ret setType: int.
ret setSize: numberBytes.
^ ret.! !


!GaspUnit methodsFor: 'acsessing' stamp: 'pjk 11/10/2001 00:38'!
getName
^name! !

!GaspUnit methodsFor: 'acsessing' stamp: 'pjk 11/10/2001 00:38'!
setName: newName

name _ newName! !

!GaspUnit methodsFor: 'initialization' stamp: 'pjk 11/10/2001 00:12'!
initWithName: aName
self setName: aName.
! !


!LRDataStream methodsFor: 'initialization' stamp: 'pjk 11/5/2001 21:04'!
init 
end _ false.
inputData _ OrderedCollection new.

inputLock _ Semaphore new.
inputLock signal.! !

!LRDataStream methodsFor: 'private' stamp: 'pjk 11/5/2001 20:48'!
end 
"This message ends the dataStream.  Once this is called, no more data can be added to this 
stream.  If more data is added, it will flag en error."
end _ true.! !

!LRDataStream methodsFor: 'testing' stamp: 'pjk 11/10/2001 07:48'!
atEnd

^ end! !

!LRDataStream methodsFor: 'accessing' stamp: 'pjk 11/9/2001 22:19'!
getName
^ name.! !

!LRDataStream methodsFor: 'accessing' stamp: 'pjk 11/9/2001 21:46'!
next
"Returns the next number that this Stream can hand out."
|ret|

inputLock wait.
ret _ inputData removeFirst.
inputLock signal.
^ ret.! !

!LRDataStream methodsFor: 'accessing' stamp: 'pjk 11/2/2001 22:48'!
nextPut: aNumber
"Puts aNumber on to this Stream."
self writeNumber: aNumber ifError:[].

! !


!LRGaspConnection methodsFor: 'accessing' stamp: 'pjk 11/10/2001 05:49'!
getStreamForName: name
^ streams at: name ! !

!LRGaspConnection methodsFor: 'accessing' stamp: 'pjk 11/10/2001 04:20'!
getStreams

^ streams keys.! !

!LRGaspConnection methodsFor: 'private' stamp: 'pjk 11/10/2001 00:27'!
add: anObject
"Adds anObject to this GaspConnection.  AnObject can be a GaspUnit, a GaspType, or a 
GaspStream"
|name |

name _ anObject getName.

(anObject isKindOf: GaspType)ifTrue:[
	types at:name put:anObject.
].
(anObject isKindOf: GaspUnit)ifTrue:[ units at:name put:anObject].
(anObject isKindOf: LRGaspStream)ifTrue:[streams at: name put:anObject].! !

!LRGaspConnection methodsFor: 'private' stamp: 'pjk 11/6/2001 03:36'!
assertNext: aToken
"Asserts that the next charator on the connection is the same as aCharator."
|next| 
next _ self readNextToken.
(aToken = next) ifFalse:[ self error:'Wrong Token!!']
! !

!LRGaspConnection methodsFor: 'private' stamp: 'pjk 11/10/2001 05:18'!
finishFrame
"Reads the name, size, and binary data from a frame.
An example frame is < FRAME name 4 16 <--bindatadeadbeefs--> >
This reads the 'name 4 5 <--bindatadeadbeefs--> ' part"
|numberElements numberBytes name data |

name _ self readNextToken.
numberElements _ (self readNextToken) asNumber.
numberBytes _ (self readNextToken) asNumber.
.

self assertNext:'<-'.

"Now I need to read the -, the binary Data, and another -"
self readNextChar:1.
data _ self readNextChar: numberBytes .
(streams at: name) postBytes: data.
self readNextChar:1.


self assertNext:'-'; assertNext:'>'.
! !

!LRGaspConnection methodsFor: 'private' stamp: 'pjk 11/10/2001 01:05'!
getGaspElement: forName
|ret|

{types. units. streams.} do:[:i| 
	ret _ i at:forName ifAbsent:[nil].
	ret notNil ifTrue:[^ret].
].

self error:'Element notFound'

! !

!LRGaspConnection methodsFor: 'private' stamp: 'pjk 11/9/2001 01:21'!
good: whatIsGood 
	outputLock wait.
	sock sendData: '< GOOD <' , whatIsGood , ' > > '.
	outputLock signal.! !

!LRGaspConnection methodsFor: 'private' stamp: 'pjk 11/5/2001 23:59'!
init
	streams _ Dictionary new.
	units _ Dictionary new.
	types _ Dictionary new.

	input _ ByteArray new. "This is the input tokens and the streamed input data"
	
	inputLock _ Semaphore new.
	outputLock _ Semaphore new.
	
	inputLock signal.
	outputLock signal

! !

!LRGaspConnection methodsFor: 'private' stamp: 'pjk 11/10/2001 04:59'!
parseBegin
"I fork a Prosecc that just sits there and calls parseBody over and over again until
you call parseEnd."

parseContinue _ true.
[ [parseContinue ] whileTrue:[self parseBody]] fork.


! !

!LRGaspConnection methodsFor: 'private' stamp: 'pjk 11/10/2001 04:35'!
parseBody
|token |
self assertNext: '<'.
token _ self readNextToken.
(token = 'AREYOUTHERE')ifTrue:[self good:token].

(token = 'UNIT')ifTrue:[ 
	self good: token. 
	token _ self readNextToken.
	
	self add: (GaspUnit new initWithName: token).
].

(token = 'FRAME')ifTrue:[self finishFrame.].

(token = 'DATATYPE') ifTrue:[
	self add: (GaspType name: self readNextToken size: self readNextToken isInt: self readNextToken).
].

(token = 'OPEN')ifTrue:[

self add: (LRGaspStream new initWithName: self readNextToken type:self readNextToken unit:self readNextToken connection:self).

].

self assertNext: '>'.! !

!LRGaspConnection methodsFor: 'private' stamp: 'pjk 11/6/2001 04:02'!
readNextChar
"Reads the next charactor on the connection."
^((self readNextChar:1) at: 1) asCharacter.
! !

!LRGaspConnection methodsFor: 'private' stamp: 'pjk 11/6/2001 01:25'!
readNextChar: number
|buffer  ret delay  |

inputLock wait.

(input size >= number) ifTrue:[
	ret _ input copyFrom:1 to:number.
	input _ input copyFrom:(number+1) to:(input size).
	inputLock signal.
	^ ret.
].

buffer _ sock getData.

[buffer size <= number] whileTrue:[
	delay ifNil:[delay _ Delay forMilliseconds:100].
	delay wait. "So that this does not hog the CPU."
	buffer _ buffer, sock getData.
].

input _ input, buffer.

ret _ input copyFrom:1 to:number.
input _ input copyFrom:(number+1) to:(input size).
inputLock signal.
^ ret.
! !

!LRGaspConnection methodsFor: 'private' stamp: 'pjk 11/10/2001 03:23'!
readNextToken
|ret|
ret_ self readNextToken:''.

^ ret! !

!LRGaspConnection methodsFor: 'private' stamp: 'pjk 11/6/2001 14:59'!
readNextToken: build
|char|
"self halt."
"Transcript show:'build: ', build;cr."
char _ self readNextChar .

"Eats all white Space"
((build isEmpty) and: [char  isSeparator])ifTrue:[^ self readNextToken:''].

(char isSeparator) ifTrue:[^build.].
(char = $-) ifTrue:[^ build,char asString].
^self readNextToken: build,char asString

! !

!LRGaspConnection methodsFor: 'object creation' stamp: 'pjk 11/10/2001 05:11'!
connectTo: hostNameOrIP port: portNumber
	|addr|	
	
	self init.
	(hostNameOrIP isKindOf: ByteArray)ifTrue:[addr _ hostNameOrIP] ifFalse:[
	addr _ NetNameResolver addressForName: hostNameOrIP].
	sock _ Socket new connectTo:addr port: portNumber.
	self parseBegin.
! !


!LRGaspStream methodsFor: 'private' stamp: 'pjk 11/9/2001 21:44'!
postBytes: bytes
|numbers| 

numbers _ type bytesToNumbers: bytes.

inputLock wait.
inputData _ inputData, numbers.
inputLock signal.! !

!LRGaspStream methodsFor: 'private' stamp: 'pjk 11/2/2001 22:49'!
readNumberIfError: aBlock
"Reads a number, and executes aBlock if something goes wrong."
! !

!LRGaspStream methodsFor: 'private' stamp: 'pjk 11/2/2001 22:49'!
write: aNumber ifError: aBlock
"Writes aNumber to the Stream.  This is smart enought to figure out what kind of 
Number you are writing, and converts it to format the stream needs.  If there is 
an error of anyKind, aBlock is called.  aBlock takes a single argument, a string explaining th error."

! !

!LRGaspStream methodsFor: 'initialization' stamp: 'pjk 11/10/2001 07:48'!
initWithName: newName type: aGaspType unit: aUnit connection: parentConnection
self init.
gaspConnection _ parentConnection.
name _ newName.
type _ aGaspType.
unit _ aUnit.


(type isKindOf:String)ifTrue:[ type _ gaspConnection getGaspElement: type].
(unit isKindOf:String)ifTrue:[ unit _ gaspConnection getGaspElement: unit].

! !

!LRGaspStream methodsFor: 'accessing' stamp: 'pjk 11/2/2001 22:49'!
next
"Returns the next number that this Stream can hand out."
^ self readNumber.! !

!LRGaspStream methodsFor: 'accessing' stamp: 'pjk 11/2/2001 22:49'!
nextPut: aNumber
"Puts aNumber on to this Stream."
self writeNumber: aNumber ifError:[].

! !


!Stream class methodsFor: 'instance creation' stamp: 'pjk 11/9/2001 22:04'!
new
^ super new
	"self error: 'Streams are created with on: and with:'"! !

LRGaspStream removeSelector: #init!
LRGaspStream removeSelector: #initWithName:type:unit:!
LRGaspConnection removeSelector: #connect:onPort:!
LRGaspConnection removeSelector: #parseLoop!
LRDataStream removeSelector: #readDouble!
LRDataStream removeSelector: #readFloat!
LRDataStream removeSelector: #readNumber!
LRDataStream removeSelector: #readNumber:ifError:!
LRDataStream removeSelector: #readNumberIfError:!
LRDataStream removeSelector: #readNumbers:!
LRDataStream removeSelector: #readNumbers:ifError:!
LRDataStream removeSelector: #write:ifError:!


More information about the Squeak-dev mailing list