File: PseudoTTY.st

package info (click to toggle)
squeak-vm 1%3A4.10.2.2614-4.1
  • links: PTS, VCS
  • area: main
  • in suites: stretch
  • size: 13,284 kB
  • ctags: 15,344
  • sloc: ansic: 75,096; cs: 11,191; objc: 5,494; sh: 3,170; asm: 1,533; cpp: 449; pascal: 372; makefile: 366; awk: 103
file content (220 lines) | stat: -rw-r--r-- 8,548 bytes parent folder | download | duplicates (8)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
'From Squeak3.2gamma of 15 January 2002 [latest update: #4881] on 11 July 2002 at 6:06:32 am'!
AsyncFile subclass: #PseudoTTY
	instanceVariableNames: 'inputBuffer outputBuffer ioError '
	classVariableNames: 'AsyncFileError '
	poolDictionaries: ''
	category: 'Communications-Endpoints'!
!PseudoTTY commentStamp: '<historical>' prior: 0!
I am a very particular kind of AsyncFile connected to the `master' half of a pseudo TTY (pty).  My purpose in life is to provide communication with a process (in the fork+exec sense) that is connected to the `slave' half of the pty.  (Writing to a master pty causes the data to appear on the slave's stdin, and anything written to the slave's stdout/stderr is available for subsequent reading on the master pty.)

You create me by sending my class

	command: programNameString arguments: arrayOfArgumentStrings

which will spawn a new process running the named program with the given arguments.  You can subsequently send me #nextPut: (or #nextPutAll:) to send stuff to the stdin of the program, and #upToEnd to retrieve data that the program writes to its stdout or stderr.  You can also send me #close which will shut down the program (by sending it SIGTERM followed shortly thereafter by SIGKILL if it's being stubborn) and both halves of the pseudo tty.

The spawned program runs in a new session, will be its own session and process group leader and will have the slave half of the pty as its controlling terminal.  (In plain English this means that the program will behave exactly as if it were being run from login, in particular: shells will enable job control, screen-oriented programs like Emacs will work properly, the user's login tmode settings will be inherited, intr/quit/etc. characters will be cooked into the corresponding signals, and window geometry changes will be propagated to the program.  Neat, huh? ;-)

Note that you need both the AsynchFile and PseudoTTY plugins in order for any of this to work.

Note also that I am really intended to be used by a ProcessEndpoint as part of a ProtocolStack (along with a terminal emulator and a TeletypeMorph to provide interaction with the subprocess).
!


!PseudoTTY methodsFor: 'initialize-release' stamp: 'ikp 7/10/2002 21:58'!
close
	"Close the master half of the pty.  The subprocess should exit (EOF on stdin) although badly written programs might start looping."

	fileHandle isNil ifTrue: [^self].
	self primClosePts: fileHandle.
	fileHandle _ nil.
	Smalltalk unregisterExternalObject: semaphore.
	ioError _ AsyncFileError.
	semaphore signal.	"wake up waiters"
	semaphore _ nil! !

!PseudoTTY methodsFor: 'initialize-release' stamp: 'ikp 7/11/2002 02:47'!
command: programName arguments: argumentArray
	"Create a pseudo tty and then spawn programName with its stdin, out and err connected to the slave end of the pty."

	| semaIndex |
	"AsyncFile"
	name _ programName.
	writeable _ true.
	semaphore _ Semaphore new.
	semaIndex _ Smalltalk registerExternalObject: semaphore.
	"PseudoTTY"
	inputBuffer _ ByteArray new: 8192.
	outputBuffer _ ByteArray new: 1.
	ioError _ 0.
	fileHandle _ self
		forkAndExecWithPts: programName
		arguments: (argumentArray isNil
			ifTrue: [#()]
			ifFalse: [argumentArray])
		semaIndex: semaIndex.
	fileHandle isNil ifTrue: [
		Smalltalk unregisterExternalObject: semaphore.
		semaphore _ nil.
		ioError _ AsyncFileError.
		^nil].
	Processor yield.
	semaphore signal.
	^self! !


!PseudoTTY methodsFor: 'accessing' stamp: 'ikp 7/11/2002 01:36'!
name
	"Answer the name of the program."

	^name! !


!PseudoTTY methodsFor: 'input/output' stamp: 'ikp 7/7/2002 02:56'!
ioError
	"Return the last error code received during read/write.  If this is ever non-zero it means the subprocess has probably died."

	^ioError! !

!PseudoTTY methodsFor: 'input/output' stamp: 'ikp 7/7/2002 06:22'!
isConnected

	^fileHandle notNil and: [ioError == 0]! !

!PseudoTTY methodsFor: 'input/output' stamp: 'ikp 7/7/2002 06:16'!
nextPut: aCharacterOrInteger
	"Send a single character to the stdin of my subprocess."

	fileHandle isNil ifTrue: [^self].
	outputBuffer at: 1 put: aCharacterOrInteger asInteger.
	self
		primWriteStart: fileHandle
		fPosition: -1
		fromBuffer: outputBuffer
		at: 1
		count: 1! !

!PseudoTTY methodsFor: 'input/output' stamp: 'ikp 7/7/2002 06:16'!
nextPutAll: aStringOrByteArray
	"Send an entire string to the stdin of my subprocess."

	fileHandle isNil ifTrue: [^self].
	self
		primWriteStart: fileHandle
		fPosition: -1
		fromBuffer: aStringOrByteArray
		at: 1
		count: aStringOrByteArray size! !

!PseudoTTY methodsFor: 'input/output' stamp: 'ikp 7/7/2002 13:28'!
noteWindowSize: aPoint

	self primWindowSize: fileHandle cols: aPoint x rows: aPoint y! !

!PseudoTTY methodsFor: 'input/output' stamp: 'ikp 7/9/2002 06:15'!
peekUpToEnd
	"Answer everything the subprocess has written to stdout or stderr since the last send of #upToEnd.  Note that stuff written to stderr might arrive earlier than stuff written to stdout if the former is unbuffered and the latter line buffered in the subprocess's stdio library."

	| n |
	self isConnected ifFalse: [^nil].
	n _ self
			primReadResult: fileHandle
			intoBuffer: inputBuffer
			at: 1
			count: inputBuffer size.
	^(self isConnected and: [n > 0])
		ifTrue: [inputBuffer copyFrom: 1 to: n]
		ifFalse: [nil]! !

!PseudoTTY methodsFor: 'input/output' stamp: 'ikp 7/7/2002 21:28'!
upToEnd
	"Answer everything the subprocess has written to stdout or stderr since the last send of #upToEnd.  Note that stuff written to stderr might arrive earlier than stuff written to stdout if the former is unbuffered and the latter line buffered in the subprocess's stdio library."

	| n |
	[self isConnected and: [(n _ self startRead: inputBuffer size;
			primReadResult: fileHandle
			intoBuffer: inputBuffer
			at: 1
			count: inputBuffer size) == Busy]]
		whileTrue: [self waitForCompletion].
	(self isConnected and: [n > 0])
		ifTrue: [^inputBuffer copyFrom: 1 to: n]
		ifFalse: [ioError _ AsyncFileError.  ^nil]		"subprocess has died or closed stdout"! !


!PseudoTTY methodsFor: 'private' stamp: 'ikp 7/10/2002 22:57'!
forkAndExecWithPts: aCommand arguments: argArray semaIndex: semaIndex
	"Run aCommand as an inferior process and connect its std{in,out,err} to the receiver through a pseudo tty."

	^self primForkAndExec: aCommand arguments: argArray semaIndex: semaIndex! !

!PseudoTTY methodsFor: 'private' stamp: 'ikp 7/7/2002 03:07'!
startRead: count
	"Indicate interest in receiving more data from stdout/stderr of the subprocess."

	self
		primReadStart: fileHandle
		fPosition: -1
		count: count! !


!PseudoTTY methodsFor: 'primitives' stamp: 'ikp 7/7/2002 05:11'!
primClosePts: fHandle
	"Kill the process whose pts is associated with our pty."

	<primitive: 'primPtyClose' module: 'PseudoTTYPlugin'>
	^nil! !

!PseudoTTY methodsFor: 'primitives' stamp: 'ikp 7/10/2002 21:48'!
primForkAndExec: command arguments: arguments semaIndex: semaIndex
	"Fork and exec command with the given arguments connecting the new process to a slave tty created from the receiver (which is the master half of a pseudo tty)."

	<primitive: 'primPtyForkAndExec' module: 'PseudoTTYPlugin'>
	^nil! !

!PseudoTTY methodsFor: 'primitives' stamp: 'ikp 7/7/2002 06:41'!
primWindowSize: fHandle cols: cols rows: rows
	"Set the size of the terminal connected to the pty."

	<primitive: 'primPtyWindowSize' module: 'PseudoTTYPlugin'>
	^nil! !

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

PseudoTTY class
	instanceVariableNames: ''!

!PseudoTTY class methodsFor: 'class initialization' stamp: 'ikp 7/7/2002 02:25'!
initialize
	"Can't rely on Error because the compiler finds the global before the class var.  Ho hum."
	"PseudoTTY initialize"

	AsyncFileError _ -2! !


!PseudoTTY class methodsFor: 'instance creation' stamp: 'ikp 7/7/2002 04:33'!
command: commandString arguments: argumentArray

	"(PseudoTTY command: '/bin/bash' arguments: #('-c' 'pwd')) upToEnd asString"

	^self new
		command: commandString
		arguments: argumentArray! !


!PseudoTTY class methodsFor: 'examples' stamp: 'ikp 7/10/2002 23:00'!
example
	"Show the user's current tty mode settings."
	"PseudoTTY example"

	| pty output buf |
	pty _ self command: '/bin/stty' arguments: #('-a').
	pty isNil ifTrue: [^self error: 'Could not create pty or process.'].
	output _ WriteStream on: String new.
	output nextPutAll: 'Your tty modes are: '; cr; space; cr.
	[(buf _ pty upToEnd) isNil] whileFalse: [output nextPutAll: buf asString].
	pty close.
	self inform: output contents! !


PseudoTTY initialize!