Lisp AND Squeak

David T. Lewis lewis at mail.msen.com
Thu Jul 18 23:56:35 UTC 2002


On Thu, Jul 18, 2002 at 08:31:56PM +0200, Hans Beck wrote:
> Hi,
> 
> > I have a copy of Hugs.st dated November 2, 2000 if anyone needs it.
> > 
> 
> yes, would be nice.... :-))
> 
> Hans

OK, here it is.  This will require Squeak on Linux/Unix with OSProcess.
I can't vouch for whether or not it works.

Dave
 
-------------- next part --------------
'From Squeak2.8 of 13 June 2000 [latest update: #2359] on 2 November 2000 at 12:51:30 pm'!
Model subclass: #Hugs
	instanceVariableNames: 'reader writer process prompt '
	classVariableNames: ''
	poolDictionaries: ''
	category: 'Minidata-Tests'!

!Hugs methodsFor: 'initialization' stamp: 'js 10/31/2000 15:01'!
brutelyClose
	"Close reader and writer streams, and send SIGTERM signal
	to Hugs program"

	reader close.
	writer close.

	OSProcess thisOSProcess processAccessor primSendSigtermTo: process pid.
	! !

!Hugs methodsFor: 'initialization' stamp: 'js 10/31/2000 15:01'!
close
	self quit
! !

!Hugs methodsFor: 'initialization' stamp: 'js 10/31/2000 20:20'!
initialize: hugsPath

	"Create two OS pipes, and a child OS process 'Hugs' with its input connected to 
	one pipe and its  output connected to the other pipe. "

	| pipe1 pipe2  desc  this input output|
	this _ OSProcess thisOSProcess.
	this stdOut
		ifNil: 
			[self noAccessorAvailable.
			^ nil].
	
	pipe1 _ this makePipe.
!
 	pipe2 _ this makePipe.
	input _ pipe1 reader.
	output _ pipe2 writer.

	writer _ pipe1 writer.
	reader _ pipe2 reader.
	desc _ Array
				with: input
				with: output
				with: output.
	prompt _ 'Squeak>'.
	process _ UnixProcess
				forkJob: hugsPath
				arguments: (Array with: '+pSqueak>')
				environment: nil
				descriptors: desc.
	input close.
	output close.
	
	self discardUntil: prompt.

	! !


!Hugs methodsFor: 'queries' stamp: 'js 11/1/2000 12:13'!
isList: aString
	"True if aString represents a Haskell list"
	
	(aString beginsWith:'[') ifTrue:[
		(aString endsWith:']') ifTrue:[
			^ true
		]
	].
	^false


! !


!Hugs methodsFor: 'commands' stamp: 'js 10/31/2000 14:17'!
browse: moduleName
	|list s|
	list _ self answer:':b ', moduleName.
	s_ WriteStream on:''.
	list do:[:each|
		s nextPutAll: each.
		s cr
	].
	^ s contents

		! !

!Hugs methodsFor: 'commands' stamp: 'js 10/31/2000 14:14'!
help
	|list s|
	list _ self answer:':?'.
	s_ WriteStream on:''.
	list do:[:each|
!
 		s nextPutAll: each.
		s cr
	].
	^ s contents

		! !

!Hugs methodsFo
r: 'commands' stamp: 'js 10/31/2000 14:54'!
quit

	self write: ':q'.
	reader close.
	writer close.

		! !

!Hugs methodsFor: 'commands' stamp: 'js 11/1/2000 12:19'!
type: aString
	"Ask Hugs for a type of expression"
	
	^self answer: ':t ', aString


		! !


!Hugs methodsFor: 'read write' stamp: 'js 11/1/2000 12:33'!
answer: aString

	|array|
	self write: aString.
	array _ self collectUntil: prompt.
	^array
	
! !

!Hugs methodsFor: 'read write' stamp: 'js 11/1/2000 13:05'!
collectUntil: aToken

	"Read hugs output pipe until aToken is found"

	|k size c s tokens|
	s _ WriteStream with:''.
	k _ 0.
	size _ aToken size.
	[k < size] whileTrue:[
		c _ reader next.
		c ifNotNil:[
			s nextPut: c.
			(c = (aToken at: k+1)) 
			ifTrue:[
				k _ k + 1
			]
			ifFalse:[
				k _ 0
			]
		]
	].
	tokens _ s contents findTokens: (String with: (Character lf)).

	tokens _ tokens select:[:each|
		(each ~= prompt) & ((each beginsWith: 'Elapsed time') not)
	].

	^(tokens removeFirst; yourself) a!
 sArray


		
! !

!Hugs methodsFor: 'read write' stamp: 'js 10/31/2000 12:42'!
discardUntil: aToken

	"Read hugs output pipe until aToken is found"

	|k size c|
	k _ 0.
	size _ aToken size.
	[k < size] whileTrue:[
		c _ reader next.
		c ifNotNil:[
			(c = (aToken at: k+1)) 
			ifTrue:[
				k _ k + 1
			]
			ifFalse:[
				k _ 0
			]
		]
	]

		
! !

!Hugs methodsFor: 'read write' stamp: 'js 10/31/2000 13:25'!
write: aString

	writer nextPutAll: aString, (String with: (Character lf))
! !


!Hugs methodsFor: 'accessing' stamp: 'js 10/31/2000 14:59'!
process
	^process
! !

!Hugs methodsFor: 'accessing' stamp: 'js 10/31/2000 15:10'!
prompt
	^prompt
! !

!Hugs methodsFor: 'accessing' stamp: 'js 10/31/2000 12:10'!
reader
	^reader
! !

!Hugs methodsFor: 'accessing' stamp: 'js 10/31/2000 12:10'!
writer
	^writer
! !

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

Hugs class
	instanceVariableNames: ''!

!Hugs class methodsFor: 'instance creation' stamp: 'js 10/31/2000 11:30'!
 !
on: hugsPath

	"Create two OS pipes, and a child OS process 'Hugs' w
ith its input connected to 
	one pipe and its  output connected to the other pipe. "

	^super new initialize: hugsPath.
! !


More information about the Squeak-dev mailing list