|
From: Brenda L. <asp...@us...> - 2003-05-12 07:26:31
|
Update of /cvsroot/squeak/squeak/platforms/unix/plugins/PseudoTTYPlugin
In directory sc8-pr-cvs1:/tmp/cvs-serv30143/plugins/PseudoTTYPlugin
Added Files:
PseudoTTY.st PseudoTTYPlugin.st README acinclude.m4 openpty.h
sqUnixPseudoTTYPlugin.c
Log Message:
Ian Piumarta's release 3.4.1
--- NEW FILE: PseudoTTY.st ---
'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 _ s
elf 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!
--- NEW FILE: PseudoTTYPlugin.st ---
'From Squeak3.2gamma of 15 January 2002 [latest update: #4881] on 11 July 2002 at 12:42:23 am'!
TestInterpreterPlugin subclass: #PseudoTTYPlugin
instanceVariableNames: 'sCOAFfn '
classVariableNames: ''
poolDictionaries: ''
category: 'VMConstruction-Plugins'!
!PseudoTTYPlugin commentStamp: '<historical>' prior: 0!
Author: Ian Piumarta <ian...@in...>
Date: 2002-07-06
Version: 1.0
This plugin extends AsynchFilePlugin with support for Unix98-style pseudo ttys. Pseudo ttys (ptys) are a means for some program A (e.g., Squeak) to spawn a child process B and have B's std{in,out,err} connected to something that smells (to B) like a terminal (the `slave' tty) but which is in fact connected directly to A via another device (the `master' tty).
One example of this would be Squeak spawning an interactive shell. If we were to use pipes (or sockets) to communicate with the shell's std{in,out,err} then various screen-oriented programs (such as Emacs) would refuse to run, the shell itself would refuse to implement job control and `cooked' characters (intr, quit, suspend, etc.) would be ignored -- all because pipes (and sockets) are absolutely not the same thing as a tty. Connecting the shell to a slave tty (and talking to it indirectly through our master tty) allows such programs (and shells and interrupts, etc.) to work properly, since they believe themselves to be connected to a `real' terminal.
To use this plugin on any system that supports Unix98 pseudo ttys you would do something like this:
- open an AsyncFile on /dev/ptmx (the Pseudo Tty master MultipleXor) which returns
a handle on the master tty (and creates the slave tty device -- usually something like
/dev/ttyN or /dev/pts/N);
- prepare the slave tty for use by an inferior process by calling primGrantPt and
primUnlockPt on the master;
- call primPtsName on the master to obtain the name of the allocated slave tty device;
- open the slave tty for read (stdin), write (stdout) and again for write (stderr);
- fork;
- connect the inferior process's std{in,out,err} to the slave tty device through the three
descriptors just opened;
- exec the shell (or whatever) in the inferior process.
After all that the parent process can write (via the original AsyncFile) to the master tty (to provide data for the inferior process's stdin) and read (via the AsyncFile) from the master (to retrieve data written to std{out,err} by the inferior process). If the inferior process tests std{in,out,err} with isatty() it will be told that it is connected to a login terminal.
This plugin provides four primitives, as implied by the above, all of which apply to AsyncFiles:
primitivePtGrant - prepare the slave tty for use
primitivePtUnlock - allow connections (open) to the slave tty
primitivePtsNameLength - return the size of the slave tty's device name
primitivePtsName - read the slave tty's device name into a String
(designed to be easily useable in conjunction with OSProcess) and one more (just for my convenience) which does all of the above steps atomically (and also promotes the inferior process to a process group leader, and installs a handler to finalise the inferior process on exit and close its parent's master tty -- without the need to use OSProcess at all):
primitiveForkAndExecWithPts - create an inferior process connected to a slave tty
Note that `Unix98' does NOT imply that this will only work on Unix systems!! Unix98 is the name of a *standard* (describing one possible implementation of pseudo ttys) which can be adopted by any OS, be it Unix or something entirely different. (Unix98 ptys have been adopted by both BSD and Linux, which is why we consider it the most interesting standard to implement here. However, be warned that if [for some bizarre, masochistic reason] you have disabled Unix98 pty support in your BSD or Linux kernel then this plugin will explode in your face. [Although you should never get that far since the initial open of /dev/ptmx will fail.])
Finally note that this plugin might (should) go away in the future if (when) OSProcess implements the required support for pseudo ttys and asynchronous i/o on their master devices. Dave: are you reading this?!
!PseudoTTYPlugin methodsFor: 'initialize-release' stamp: 'ikp 7/10/2002 22:41'!
initialiseModule
self export: true.
"We have to load AsyncFile first, to get the sessionID."
interpreterProxy ioLoadFunction: 'initializeModule' From: 'AsynchFilePlugin'.
^self cCode: 'ptyInit()' inSmalltalk: [true]! !
!PseudoTTYPlugin methodsFor: 'initialize-release' stamp: 'ikp 7/7/2002 02:29'!
shutdownModule
self export: true.
^self cCode: 'ptyShutdown()' inSmalltalk: [true]! !
!PseudoTTYPlugin methodsFor: 'primitives' stamp: 'ikp 7/7/2002 05:44'!
primitivePtyClose: fHandle
| f |
self var: #f declareC: 'AsyncFile *f'.
self primitive: 'primPtyClose' parameters: #(Oop).
f _ self asyncFileValueOf: fHandle.
interpreterProxy failed ifFalse: [self cCode: 'ptyClose(f)'].! !
!PseudoTTYPlugin methodsFor: 'primitives' stamp: 'ikp 7/10/2002 22:31'!
primitivePtyForkAndExec: cmd arguments: args semaIndex: semaIndex
| f cmdLen cmdIdx argLen argIdx fOop |
self var: #f declareC: 'AsyncFile *f'.
self primitive: 'primPtyForkAndExec' parameters: #(Oop Oop SmallInteger).
interpreterProxy success: (interpreterProxy isBytes: cmd).
interpreterProxy success: (interpreterProxy isPointers: args).
interpreterProxy failed ifTrue: [^nil].
cmdIdx _ self cCoerce: (interpreterProxy firstIndexableField: cmd) to: 'int'.
cmdLen _ interpreterProxy slotSizeOf: cmd. "in bytes"
argIdx _ self cCoerce: (interpreterProxy firstIndexableField: args) to: 'int'.
argLen _ interpreterProxy slotSizeOf: args. "in fields"
fOop _ interpreterProxy
instantiateClass: interpreterProxy classByteArray
indexableSize: (self cCode: 'sizeof(AsyncFile)').
f _ self asyncFileValueOf: fOop.
interpreterProxy failed
ifFalse: [self cCode: 'ptyForkAndExec(f, semaIndex, cmdIdx, cmdLen, argIdx, argLen)'].
^fOop! !
!PseudoTTYPlugin methodsFor: 'primitives' stamp: 'ikp 7/7/2002 06:38'!
primitivePtyWindowSize: fHandle cols: cols rows: rows
| f |
self var: #f declareC: 'AsyncFile *f'.
self primitive: 'primPtyWindowSize' parameters: #(Oop SmallInteger SmallInteger).
f _ self asyncFileValueOf: fHandle.
interpreterProxy failed ifFalse: [self cCode: 'ptyWindowSize(f, cols, rows)'].! !
!PseudoTTYPlugin methodsFor: 'private' stamp: 'ikp 7/6/2002 19:08'!
asyncFileValueOf: oop
"Return a pointer to the first byte of the async file record within the given Smalltalk bytes object, or nil if oop is not an async file record."
self returnTypeC: 'AsyncFile *'.
interpreterProxy success:
((interpreterProxy isIntegerObject: oop) not
and: [(interpreterProxy isBytes: oop)
and: [(interpreterProxy slotSizeOf: oop) = (self cCode: 'sizeof(AsyncFile)')]]).
interpreterProxy failed ifTrue: [^ nil].
^ self cCode: '(AsyncFile *) (oop + 4)'
! !
"-- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- -- "!
PseudoTTYPlugin class
instanceVariableNames: ''!
!PseudoTTYPlugin class methodsFor: 'translation' stamp: 'ikp 7/6/2002 21:18'!
hasHeaderFile
^true! !
!PseudoTTYPlugin class methodsFor: 'translation' stamp: 'ikp 7/6/2002 21:12'!
requiresPlatformFiles
^true! !
--- NEW FILE: README ---
/* This directory contains the PseudoTTYPlugin, a means for Squeak to
* fork an interactive program that believes itself to be running on a
* login terminal when, in fact, Squeak is providing it with data for
* its stdin and recovering the output it writes to its stdout/stderr.
*
* The Squeak plugin source code is in `PseudoTTYPlugin.st'.
* The Squeak class needed to use the plugin is in `PseudoTTY.st'.
*
* The plugin has been built and tested on the following architecures:
*
* GNU/Linux (libc2.3)
* NetBSD 1.5ZC
* Solaris 2.8
*
* The remainder of this file is a C program designed to ease the
* process of porting this plugin to unsupported architectures.
*
* ----------------------------------------------------------------
*
* This program forks a child process to run /bin/stty and then
* collects and prints its output. If the child is not connected to a
* login terminal then stty will complain (printing something like
* "stdin: not a tty") and you have a problem somewhere in "opentty.h"
* which you must FIND AND FIX before the plugin will work. OTOH, if
* it prints a bunch (about ten lines) of tty mode information then
* all is well and the plugin should work just fine.
*
* (Do I really need to mention that you have to rename this file to
* "pty.c" or somesuch before trying to compile it? ;)
*/
/* For the plugin the HAVE_* macros are set in config.h by acinclude.m4.
* In this test file you need to set them manually for your architecture.
* If you invent new HAVE_* macros then you'll need to modify acinclude.m4
* and regenerate configure (run `make' in ../../config) before building
* the VM.
*
* If it is available then we use openpty() in preference to Unix98 ptys:
*
* HAVE_OPENPTY -- defined if you have openpty() and login_tty()
* HAVE_UTIL_H -- defined if you have /usr/include/util.h
* HAVE_PTY_H -- defined if you have /usr/include/pty.h
*
* If you don't have openpty() then we fake it from /dev/ptmx:
*
* HAVE_UNIX98_PTY -- defined if you have /dev/ptmx and grantpt() et al.
* HAVE_STROPTS_H -- defined if you have /usr/include/stropts.h
*
* We assume you have /usr/include/utmp.h; if you don't then you need to
* buy a real computer before trying to compile this plugin.
*
* Suggested compile command is shown with each architecture.
* If you have to add new libraries then you'll need to modify acinclude.m4
* and regenerate configure (run `make' in ../../config) before building the
* VM.
*/
#if defined(__NetBSD__) /* cc -o pty pty.c -lutil */
# define HAVE_OPENPTY
# define HAVE_UTIL_H
#elif defined(__OpenBSD__) /* cc -o pty pty.c -lutil */
# define HAVE_OPENPTY
# define HAVE_UTIL_H
#elif defined(__linux__) /* cc -o pty pty.c -lutil */
# define HAVE_UNIX98_PTY
# define HAVE_OPENPTY
# define HAVE_PTY_H
#elif defined(__sun__) /* cc -o pty pty.c */
# define HAVE_UNIX98_PTY
# define HAVE_STROPTS_H
#else
# error: defines for your architecture go here
#endif
/* Absolutely everybody has these. */
#include <sys/types.h>
#include <sys/wait.h>
#include <unistd.h>
#include <fcntl.h>
#include <signal.h>
#include <errno.h>
#include <stdio.h>
/* This gets the obscure (interesting ;) stuff. */
#include "openpty.h"
/* Here we go! ... */
static char *prog= "/bin/stty";
static char *argv[]= { "stty", "-a", 0 };
extern char **environ;
static int ptm= -1, pts= -1;
static void sigchld(int signum)
{
close(pts); /* force i/o error or EOF on ptm */
}
int main()
{
char tty[32];
pid_t pid= 0;
if (openpty(&ptm, &pts, tty, 0, 0) == -1)
{
perror("openpty");
exit(1);
}
printf("using %s (ptm %d pts %d)\n", tty, ptm, pts);
signal(SIGCHLD, sigchld);
pid= fork();
switch (pid)
{
case -1:
perror("fork");
exit(1);
break;
case 0: /* child */
close(ptm);
if (login_tty(pts) == -1)
{
perror("login_tty");
exit(1);
}
execve(prog, argv, environ);
perror(argv[0]);
exit(1);
break;
default: /* parent */
{
char buf[128];
int n, status;
printf("---------------- from child:\n");
while (((n= read(ptm, buf, sizeof(buf) - 1)) > 0)
|| ((n == -1) && (errno == EINTR)))
if (n > 0)
{
buf[n]= '\0';
printf("%s", buf);
}
printf("----------------\n");
if (n < 0)
perror("read");
else
printf("EOF\n");
close(ptm);
pid= wait(&status);
printf("child exited with status %d\n", status);
}
break;
}
return 0;
}
--- NEW FILE: acinclude.m4 ---
AC_HAVE_HEADERS(util.h libutil.h pty.h stropts.h)
AC_SEARCH_LIBS(openpty, util,
AC_DEFINE(HAVE_OPENPTY, 1),[
if test -r /dev/ptmx; then
AC_CHECK_FUNC(grantpt, AC_DEFINE(HAVE_UNIX98_PTYS, 1))
fi])
--- NEW FILE: openpty.h ---
/* openpty.h -- provides openpty() and login_tty()
*
* Copyright (C) 1996-2002 Ian Piumarta and other authors/contributors
* as listed elsewhere in this file.
* All rights reserved.
*
* This file is part of Unix Squeak.
*
* This file is distributed in the hope that it will be useful, but WITHOUT
* ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or
* FITNESS FOR A PARTICULAR PURPOSE.
*
* You may use and/or distribute this file ONLY as part of Squeak, under
* the terms of the Squeak License as described in `LICENSE' in the base of
* this distribution, subject to the following restrictions:
*
* 1. The origin of this software must not be misrepresented; you must not
* claim that you wrote the original software. If you use this software
* in a product, an acknowledgment to the original author(s) (and any
* other contributors mentioned herein) in the product documentation
* would be appreciated but is not required.
*
* 2. This notice must not be removed or altered in any source distribution.
*
* Using (or modifying this file for use) in any context other than Squeak
* changes these copyright conditions. Read the file `COPYING' in the
* directory `platforms/unix/doc' before proceeding with any such use.
*
* You are not allowed to distribute a modified version of this file
* under its original name without explicit permission to do so. If
* you change it, rename it.
*
* Author: Ian...@in...
*
* Last edited: 2002-07-11 21:07:37 by piumarta on emilia.inria.fr
*/
#if defined(HAVE_OPENPTY)
# include <utmp.h> /* login_tty() */
# if defined(HAVE_PTY_H)
# include <pty.h> /* openpty() */
# elif defined(HAVE_UTIL_H)
# include <util.h> /* openpty() */
# elif defined(HAVE_LIBUTIL_H)
# include <libutil.h> /* openpty() on FreeBSD */
# else
# error: cannot find headers for openpty()
# endif
#else /* !HAVE_OPENPTY */
# if defined(HAVE_UNIX98_PTYS)
/* we'll just roll our own, it ain't hard */
# include <stdlib.h> /* ptsname(), grantpt(), unlockpt() */
# include <unistd.h>
# include <string.h>
# include <fcntl.h>
# if defined(HAVE_STROPTS_H)
# include <stropts.h>
# include <sys/ioctl.h>
# endif
static int openpty(int *ptmp, int *ptsp, char *ttyp, void *termiosp, void *winp)
{
int ptm= -1, pts= -1;
char *tty= 0;
if ((ptm= open("/dev/ptmx", O_RDWR, 0)) == -1) return -1;
tty= ptsname(ptm);
if (grantpt(ptm) == -1) return -1;
if (unlockpt(ptm) == -1) return -1;
if ((pts= open(tty, O_RDWR, 0)) == -1) return -1;
*ptmp= ptm;
*ptsp= pts;
strcpy(ttyp, tty);
return 0;
}
static int login_tty(int pts)
{
#if defined(HAVE_STROPTS_H)
/* push a terminal onto stream head */
if (ioctl(pts, I_PUSH, "ptem") == -1) return -1;
if (ioctl(pts, I_PUSH, "ldterm") == -1) return -1;
#endif
setsid();
#if defined(TIOCSCTTY)
ioctl(pts, TIOCSCTTY, 0);
#endif
dup2(pts, 0);
dup2(pts, 1);
dup2(pts, 2);
if (pts > 2) close(pts);
return 0;
}
# else /* !HAVE_UNIX98_PTYS */
# error: cannot open a pty -- this plugin will not work
# endif
#endif /* !HAVE_OPENPTY */
--- NEW FILE: sqUnixPseudoTTYPlugin.c ---
/* PseudoTTYPlugin.c -- support for Unix98-style pseudo ttys -*- C -*-
*
* Author: Ian Piumarta <ian...@in...>
* Version: 1.1
* Last edited: 2002-07-12 10:37:47 by piumarta on emilia.inria.fr
*
* This plugin extends AsynchFilePlugin with support for Unix98-style
* pseudo ttys. See the PseudoTTY and PseudoTTYPlugin class comments
* for details.
*
* Note that `Unix98' does NOT imply that this will only work on Unix
* systems! Unix98 is the name of a *standard* describing (amonst
* many other things) one possible implementation of pseudo ttys that
* could be adopted by any OS, be it Unix or something entirely
* different. (Unix98 ptys have been adopted by both BSD and Linux,
* which is why we consider it the most interesting standard to
* implement here. However, be warned that if [for some bizarre,
* masochistic reason] you have disabled Unix98 pty support in your
* BSD or Linux kernel then this plugin will explode in your face.
* [Although you should never get that far since the initial open of
* /dev/ptmx will fail.])
*
* Finally note that this plugin might (should) go away in the future
* if (when) OSProcess implements the required support for pseudo ttys
* and asynchronous i/o on their master devices. (Dave: are you
* reading this?)
*
* Copyright (C) 1996-2002 Ian Piumarta and other authors/contributors
* as listed elsewhere in this file.
* All rights reserved.
*
* This file is part of Unix Squeak.
*
* This file is distributed in the hope that it will be useful, but WITHOUT
* ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or
* FITNESS FOR A PARTICULAR PURPOSE.
*
* You may use and/or distribute this file ONLY as part of Squeak, under
* the terms of the Squeak License as described in `LICENSE' in the base of
* this distribution, subject to the following restrictions:
*
* 1. The origin of this software must not be misrepresented; you must not
* claim that you wrote the original software. If you use this software
* in a product, an acknowledgment to the original author(s) (and any
* other contributors mentioned herein) in the product documentation
* would be appreciated but is not required.
*
* 2. This notice must not be removed or altered in any source distribution.
*
* Using (or modifying this file for use) in any context other than Squeak
* changes these copyright conditions. Read the file `COPYING' in the
* directory `platforms/unix/doc' before proceeding with any such use.
*
* You are not allowed to distribute a modified version of this file
* under its original name without explicit permission to do so. If
* you change it, rename it.
*/
#include "sq.h"
#include "PseudoTTYPlugin.h"
/* Ian says: never EVER #include things in the Unix Squeak sources
using relative paths. Never. Ever. Period. Write a Makefile.inc
with the right XCPPFLAGS instead. Having said that... */
#include "../AsynchFilePlugin/sqUnixAsynchFile.h"
#include <sys/types.h>
#include <sys/wait.h>
#include <signal.h>
#include <unistd.h>
#include <termios.h>
#include <sys/ioctl.h>
#include "openpty.h" /* hide the gory details ;) */
#if 0
# define dprintf(ARGS) printf ARGS
#else
# define dprintf(ARGS)
#endif
typedef struct Slave
{
pid_t pid; /* process */
int status; /* exit status */
int pts; /* pts (child pty) */
FilePtr pty; /* ptm (parent pty) */
struct Slave *next; /* list */
} SlaveRec, *SlavePtr;
static SlavePtr slaves= 0;
typedef void (*sighandler_t)(int);
static sighandler_t prevchld= 0;
static int reaping= 0;
#define isValid(f) (f->sessionID == sqUnixAsyncFileSessionID)
#define validate(f) if ((!isValid(f)) || (!(f->state))) return vm->primitiveFail()
/*** initialise-release ***/
#include "sqVirtualMachine.h"
static struct VirtualMachine *vm= 0;
static void sigchld(int signum)
{
int status= 0;
SlavePtr zombie= 0;
pid_t pid= wait(&status);
if (!slaves)
fprintf(stderr, "unexpected SIGCHLD for pid %d\n", pid);
else
for (zombie= slaves; zombie; zombie= zombie->next)
if (zombie->pid == pid)
break;
if (!zombie)
fprintf(stderr, "failed to clean up for pid %d\n", pid);
else
{
/* force any image server loop to exit */
/* close(zombie->pty->fd); */
zombie->pty->rd.status= -2;
signalSemaphoreWithIndex(zombie->pty->sema);
dprintf(("closed pty for pid %d\n", pid));
}
}
int ptyInit(void)
{
dprintf(("ptyInit: AsyncFileSession is %d\n", sqUnixAsyncFileSessionID));
vm= sqGetInterpreterProxy();
slaves= 0;
prevchld= signal(SIGCHLD, sigchld);
if ((prevchld != SIG_DFL) && (prevchld != SIG_IGN))
{
fprintf(stderr, "declining responsibility for child processes!\n");
signal(SIGCHLD, prevchld);
reaping= 0;
}
else
reaping= 1;
return 1;
}
int ptyShutdown(void)
{
if (reaping)
{
SlavePtr slave= 0;
for (slave= slaves; slave; slave= slave->next)
kill(slave->pid, SIGTERM);
usleep(200*1000);
for (slave= slaves; slave; slave= slave->next)
kill(slave->pid, SIGKILL);
usleep(200*1000);
signal(SIGCHLD, prevchld);
while (slaves)
{
slave= slaves->next;
fprintf(stderr, "child process %d refused to die\n", slaves->pid);
free(slaves);
slaves= slave;
}
}
slaves= 0;
return 1;
}
/*** primitives ***/
#include <fcntl.h>
#include <time.h>
int ptyForkAndExec(AsyncFile *f, int semaIndex,
int cmdIndex, int cmdLen, int argIndex, int argLen)
{
int ptm= -1, pts= -1;
char tty[32];
FilePtr fp= 0;
/* Module init must succeed in loading the AsyncFile plugin */
if (sqUnixAsyncFileSessionID == 0)
{
vm->primitiveFail();
return 0;
}
dprintf(("AsyncFileSession is %d\n", sqUnixAsyncFileSessionID));
if (openpty(&ptm, &pts, tty, 0, 0) == -1)
{
perror("pty: openpty");
goto failDetached;
}
dprintf(("pty: using %s (ptm %d pts %d)\n", tty, ptm, pts));
if ((fp= asyncFileAttach(f, ptm, semaIndex)) == 0)
goto failDetached;
/* fork the child on the new pts (from now on we must detach on fail) */
{
extern char **environ;
char *cmd= (char *)alloca(cmdLen + 1);
char **argv= (char **)alloca(sizeof(char *) * (argLen + 2));
int i= 0;
SlavePtr slave= 0;
memcpy((void *)cmd, (void *)cmdIndex, cmdLen);
cmd[cmdLen]= '\0';
dprintf(("pty: command: %s\n", cmd));
argv[0]= cmd;
for (i= 1; i <= argLen; ++i)
{
int argOop= ((int *)argIndex)[i - 1];
char *arg= 0;
int len= 0;
if (!vm->isBytes(argOop)) goto fail;
len= vm->stSizeOf(argOop);
dprintf(("pty: arg %d len %d\n", i, len));
arg= (char *)alloca(len + 1);
memcpy((void *)arg, (void *)vm->firstIndexableField(argOop), len);
arg[len]= '\0';
argv[i]= arg;
dprintf(("pty: argv[%d]: %s\n", i, argv[i]));
}
argv[argLen+1]= 0; /* argv terminator */
/* put slave on list in case of immediate exit in child */
slave= (SlavePtr)malloc(sizeof(SlaveRec));
slave->next= slaves;
slaves= slave;
slave->pts= pts;
slave->pty= fp;
slave->pid= fork();
switch (slave->pid)
{
case -1: /* error */
slaves= slaves->next;
free(slave);
perror("pty: fork");
goto fail;
break;
case 0: /* child */
close(ptm);
login_tty(pts);
execve(cmd, argv, environ);
fprintf(stderr, "pty: ");
perror(cmd);
exit(1);
break;
default: /* parent */
close(pts);
break;
}
return 0;
}
fail:
asyncFileClose(f);
ptm= -1;
failDetached:
if (ptm >= 0) close(ptm);
if (pts >= 0) close(pts);
vm->primitiveFail();
return 0;
}
int ptyClose(AsyncFile *f)
{
SlavePtr slave= 0, prev= 0;
FilePtr pty= (FilePtr)f->state;
validate(f);
dprintf(("pty: close %d\n", pty->fd));
if (pty->fd >= 0)
{
for (prev= 0, slave= slaves; slave; prev= slave, slave= slave->next)
if (slave->pty == pty)
{
int pid= slave->pid;
dprintf(("killing pid %d connected to pts %d\n", pid, slave->pts));
/* terminate with increasing degrees of violence... */
kill(pid, SIGTERM);
usleep(200*1000);
kill(pid, SIGKILL);
/* delete from list */
if (prev)
prev->next= slave->next;
else
slaves= slave->next;
break;
}
if (slave)
free(slave);
else
fprintf(stderr, "pty %d not in active process list\n", pty->fd);
}
asyncFileClose(f);
return 0;
}
ptyWindowSize(AsyncFile *f, int cols, int rows)
{
#if defined(TIOCSWINSZ)
struct winsize sz;
FilePtr pty= (FilePtr)f->state;
validate(f);
dprintf(("pty %d size %d %d\n", pty->fd, cols, rows));
sz.ws_col= cols;
sz.ws_row= rows;
sz.ws_xpixel= sz.ws_ypixel= 0;
if (ioctl(pty->fd, TIOCSWINSZ, &sz) == -1)
perror("pty: TIOCSWINSZ");
#endif
return 0;
}
|