home *** CD-ROM | disk | FTP | other *** search
Text File | 1992-09-14 | 26.3 KB | 1,043 lines |
- head 1.6;
- access;
- symbols
- version39-41:1.2;
- locks;
- comment @ * @;
-
-
- 1.6
- date 92.09.14.01.50.16; author mwild; state Exp;
- branches;
- next 1.5;
-
- 1.5
- date 92.08.09.21.06.31; author amiga; state Exp;
- branches;
- next 1.4;
-
- 1.4
- date 92.07.28.03.12.04; author mwild; state Exp;
- branches;
- next 1.3;
-
- 1.3
- date 92.07.28.02.59.44; author mwild; state Exp;
- branches;
- next 1.2;
-
- 1.2
- date 92.07.04.18.59.29; author mwild; state Exp;
- branches;
- next 1.1;
-
- 1.1
- date 92.06.08.17.01.06; author mwild; state Exp;
- branches;
- next ;
-
-
- desc
- @initial checkin
- @
-
-
- 1.6
- log
- @change NO_VFORK_RESUME into USE_VFORK_RESUME, which is what the macro really
- is about (don't use it though at the moment!).
- Test for p_vfork_msg instead of u_save_sp, since only the first one is
- reset when the process is detached.
- @
- text
- @/*
- * This file is part of ixemul.library for the Amiga.
- * Copyright (C) 1991, 1992 Markus M. Wild
- *
- * This library is free software; you can redistribute it and/or
- * modify it under the terms of the GNU Library General Public
- * License as published by the Free Software Foundation; either
- * version 2 of the License, or (at your option) any later version.
- *
- * This library 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. See the GNU
- * Library General Public License for more details.
- *
- * You should have received a copy of the GNU Library General Public
- * License along with this library; if not, write to the Free
- * Software Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA.
- *
- */
-
- #define KERNEL
- #include "ixemul.h"
- #include <hardware/intbits.h>
- #include <ctype.h>
- #include <sys/wait.h>
-
- #include <sys/exec.h>
-
- #include "atexit.h"
- #define __atexit (u.u_atexit)
-
- #define alloca __builtin_alloca
-
- #undef DEBUG
- #ifdef DEBUG
- #define DP(a) kprintf a
- #else
- #define DP(a)
- #endif
-
- extern int _dos20;
-
- extern void bcopy (void *, void *, int);
- extern BPTR *__load_seg (const char *name, char **args);
- extern void __free_seg (BPTR *segs);
- extern void *kmalloc (size_t);
- extern void *krealloc (void *, size_t);
- extern char *index (const char *, int);
- extern char *strpbrk (const char *, const char *);
- extern void kfree (void *);
- extern char *strcpy (char *, const char *);
- extern void kprintf (const char *, ...);
- extern void all_free (void);
-
- static int compatible_startup (void *code, int argc, char **argv);
- static char *quote (char *orig);
- static void volatile on_real_stack (BPTR *segs, char **argv, char **environ);
-
- int
- execve (char *path, char **argv, char **environ)
- {
- BPTR *segs;
- u_int omask, err;
- char *extra_args = 0;
-
- omask = syscall (SYS_sigsetmask, ~0);
- u.u_oldmask = omask;
-
- segs = __load_seg (path, &extra_args);
-
- if (segs && segs != (BPTR *)-2)
- {
- /* Now it gets somewhat nasty... since I have to revert to the `real'
- stack (since the parent will want its sp back ;-)), I have to save
- the values of this stack frame into registers, or I'll never be
- able to access them afterwards again.. */
- register BPTR *_segs asm ("d2");
- register char **_argv asm ("d3");
- register char **_environ asm ("d4");
-
- /* if we got extra arguments, split them into a 2 el argument vector, and join
- * `argv' */
- if (extra_args && *extra_args)
- {
- char **ap, **nargv;
- int size;
-
- for (size = 0, ap = argv; *ap; size++, ap++) ;
- nargv = (char **) syscall (SYS_malloc, (size + 4) * 4);
- ap = nargv;
- *ap++ = *argv++; /* keep the program name */
- *ap++ = extra_args;
- *ap = index (extra_args, ' ');
- if (*ap)
- {
- **ap = 0;
- ++*ap;
- ++ap;
- }
- while (*ap++ = *argv++) ;
- argv = nargv;
- }
-
- _segs = segs;
- _argv = argv;
- _environ = environ;
-
- #ifndef USE_VFORK_RESUME
- DP(("execve: about to call on_real_stack ()\n"));
- if (u.p_vfork_msg)
- {
- set_sp ((u_int) u.u_save_sp);
- /* fool the optimizer... */
- asm volatile ("" : "=g" (_segs), "=g" (_argv), "=g" (_environ) : "0" (_segs), "1" (_argv), "2" (_environ));
- DP(("execve () restored native sp\n"));
- }
- #else
- /* this option is currently not recommended. execve needs to allocate memory
- later on, and this should not happen inside Forbid! */
- Forbid ();
- vfork_resume ();
- #endif
- on_real_stack (_segs, _argv, _environ);
- /* never reached */
- }
-
- err = ENOENT;
-
- syscall (SYS_sigsetmask, omask);
-
- errno = err;
- return -1;
- }
-
-
- char **
- dupvec (char **vec)
- {
- int n;
- char **vp, **res;
- static char *empty[] = { "" };
-
- if (! vec)
- return empty;
-
- for (n = 0, vp = vec; *vp; n++, vp++) ;
-
- /* contrary to `real' vfork(), malloc() works in the child on its own
- data, that is it won't clobber anything in the parent */
-
- res = (char **) syscall (SYS_malloc, (n + 1) * 4);
- if (res)
- {
- for (vp = res; n-- > 0; vp++, vec++)
- *vp = (char *) syscall (SYS_strdup, *vec);
-
- *vp = 0;
- }
-
- return res;
- }
-
-
- static void volatile
- on_real_stack (BPTR *segs, char **argv, char **environ)
- {
- int private_startup;
- u_int *code;
- int (*entry) (struct ixemul_base *, int, char **, char **);
- struct exec *hdr;
- int f;
- jmp_buf old_exit;
-
- /* first make sure that we're later passing on `safe' data to our child, ie.
- copy it from wherever the data is currently stored into child malloc space */
- argv = dupvec (argv);
- environ = dupvec (environ);
-
- code = BTOCPTR (*segs);
- code ++; /* code starts at offset 4 */
-
- /* check whether this program has our magic header */
- private_startup = ((code[0] & 0xffff0000) == 0x4efa0000 /* jmp pc@@(amiga-dos-entry) */
- && (code [1] & 0xffff) == OMAGIC);
-
- #if 0
- {
- char **cp;
- kprintf ("execve [");
- for (cp = argv; *cp; cp++) kprintf ("%s%s", *cp, cp[1] ? ", " : "], [");
- for (cp = environ; *cp; cp++) kprintf ("%s%s", *cp, cp[1] ? ", " : "]\n");
- }
- #endif
-
- if (private_startup)
- {
- hdr = (struct exec *) &code[1];
- entry = (void *) hdr->a_entry;
-
- if (! entry) private_startup = 0;
- }
-
- /* okay, get ready to turn us into a new process, as much as
- we can actually.. */
-
- /* close all files with the close-on-exec flag set */
- for (f = 0; f < NOFILE; f++)
- {
- if (u.u_ofile[f] && (u.u_pofile[f] & UF_EXCLOSE))
- syscall (SYS_close, f);
- }
-
- /* BIG question what to do with registered atexit() handlers before
- an exec.. Unix for sure does nothing, since the process space is
- physically written over. In the AmigaDOS I could (!) imagine
- cases where calling some atexit() handlers (mostly in the case
- of destructors for C++ objects) would result in erronous
- behaving of the program. However, since atexit() handlers also
- serve to get rid of acquired Amiga resources, I morally feel
- obliged to call the handlers.. lets see if this results in
- incompatibilities with programs that expect Unix behavior. (Note
- that I don't call exit() after exeve() returns, I call _exit(),
- and _exit() does not walk the atexit() list).
-
- There is one special case that I catch here, this is stdio. No
- Unix program would ever expect stdio buffers to be flushed by
- an execve() call. So since stdio is in the library I know the
- address of the handler to skip ;-)) */
-
- while (__atexit)
- {
- while (__atexit->ind --)
- {
- /* this is the stdio function to flush all buffers */
- extern void _cleanup();
-
- if (__atexit->fns[__atexit->ind] != _cleanup)
- {
- if (u.u_a4)
- asm volatile ("movel %0, a4" : : "g" (u.u_a4));
- __atexit->fns[__atexit->ind] ();
- }
- }
- __atexit = __atexit->next;
- }
-
- /* `ignored signals remain ignored across an execve, but
- signals that are caught are reset to their default values.
- Blocked signals remain blocked regardless of changes to
- the signal action. The signal stack is reset to be
- undefined'. */
-
- u.u_sigonstack = 0; /* default = on normal stack */
- u.u_sigintr = 0; /* default = don't interrupt syscalls */
- u.p_sigcatch = 0; /* no signals caught by user -> SIG_DFL */
-
- /* what happens when we execute execve() from a signal handler
- that executes on the signal stack? Better don't do this... */
-
- /* deinstall our sigwinch input-handler */
- ix_remove_sigwinch ();
-
- /* save the original exit-jmpbuf, as ix_exec_entry() will destroy
- * it later */
- bcopy (u.u_jmp_buf, old_exit, sizeof (old_exit));
-
- /* count the arguments */
- for (f = 0; argv[f]; f++) ;
-
- #ifndef USE_VFORK_RESUME
- DP(("execve() having parent resume\n"));
- if (u.p_vfork_msg)
- {
- /* make the parent runable again */
- ReplyMsg ((struct Message *) u.p_vfork_msg);
- u.p_vfork_msg = 0;
- }
- #else
- Permit ();
- #endif
-
- DP(("execve() calling entry(%ld, $%lx, $%lx)\n", f, argv, environ));
- {
- char *orig, **name;
- struct Process *me = (struct Process *) FindTask (0);
- struct CommandLineInterface *CLI = BTOCPTR (me->pr_CLI);
- char *bcpl_argv0;
-
- bcpl_argv0 = alloca (strlen (argv[0]) + 4);
- bcpl_argv0 = LONG_ALIGN (bcpl_argv0);
-
- if (CLI)
- {
- name = (char **) & CLI->cli_CommandName;
- orig = *name;
- bcpl_argv0[0] = strlen (argv[0]);
- bcopy (argv[0], &bcpl_argv0[1], bcpl_argv0[0] + 1);
- *name = (char *) CTOBPTR (bcpl_argv0);
- }
- else
- {
- name = (char **) & me->pr_Task.tc_Node.ln_Name;
- orig = *name;
- *name = argv[0];
- }
-
- if (private_startup)
- f = entry (ixemulbase, f, argv, environ);
- else
- f = compatible_startup (code, f, argv);
-
- *name = orig;
- }
-
- __free_seg (segs);
-
- DP(("old program doing _exit(%ld)\n", f));
- /* and fake an _exit */
- longjmp (old_exit, f + 1);
- }
-
-
- /* some rather rude support to start programs that don't have a struct exec
- * information at the beginning.
- * 1.3 NOTE: This will only start plain C programs, nothing that smells like
- * BCPL. Limited support for ReadArgs() style parsing is here, but not
- * everything is set up that would have to be set up for BCPL programs
- * to feel at home. Also don't use Exit() in those programs, it wouldn't
- * find what it expects on the stack....
- */
- static int
- compatible_startup (void *code, int argc, char **argv)
- {
- char *al;
- int max, res;
- u_int oldsigalloc;
- struct Process *me = (struct Process *) FindTask (0);
-
- /* ignore the command name ;-) */
- argv++;
-
- max = 1024;
- al = (char *) kmalloc (max);
- res = -1;
- if (al)
- {
- char *cp;
- register int d0 asm ("d0");
- register char *a0 asm ("a0");
- register void *a1 asm ("a1");
- BPTR old_cis, old_cos, old_ces;
- BPTR dup_cis, dup_cos, dup_ces;
- void *old_trapdata, *old_trapcode;
- int old_flags;
- void *old_launch, *old_switch;
- struct file *f;
-
- for (cp = al; *argv; )
- {
- char *newel = quote (*argv);
- int elsize = strlen (newel ? newel : *argv) + 2;
-
- if (cp + elsize >= al + max)
- {
- char *nal;
- max <<= 1;
- nal = (char *) krealloc (al, max);
- if (! nal) break;
- cp = nal + (cp-al);
- al = nal;
- }
-
- strcpy (cp, newel ? newel : *argv);
- cp += elsize - 2;
- *cp++ = ' ';
- *cp = 0;
- if (newel) kfree (newel);
- ++argv;
- }
-
- /* BCPL weirdness ... */
- *cp++ = '\n';
- *cp = 0;
-
- DP(("compatible_startup (%s)\n", al));
-
- /* problem with RunCommand: the allocated signal mask is not reset
- for the new process, thus if several RunCommands are nested, a
- late started process might run out of signals. This behavior makes
- no sense, since the starting process is *suspended* while the `child'
- is running, thus it doesn't need its signals in the meantime ! */
-
- oldsigalloc = me->pr_Task.tc_SigAlloc & 0xffff0000; /* hacky...*/
- me->pr_Task.tc_SigAlloc &= 0xffff;
-
- /* cleanup as much of ixemul.library as possible, so that the started
- process can take over */
- old_flags = me->pr_Task.tc_Flags;
- me->pr_Task.tc_Flags = u_save.u_otask_flags;
- old_launch = me->pr_Task.tc_Launch;
- me->pr_Task.tc_Launch = u_save.u_olaunch; /* restoring this disables our signals */
- old_switch = me->pr_Task.tc_Switch;
- me->pr_Task.tc_Switch = u_save.u_oswitch;
- RemIntServer (INTB_VERTB, & u_save.u_itimerint);
-
- #if 0
- /* looks like we shouldn't do this, bus errors are the consequence.. */
-
- /* free the task private malloc'd data */
- all_free ();
- #endif
-
- /* limited support (part 2 ;-)) for I/O redirection on old programs
- If we're redirecting to a plain file, don't go thru a IXPIPE,
- temporarily use our DOS files in that case. Any other file type
- is routed thru an IXPIPE though. */
-
- if (! _dos20)
- {
- old_cis = me->pr_CIS;
- old_cos = me->pr_COS;
- if ((f = u_save.u_ofile[0]) && f->f_type == DTYPE_FILE)
- {
- dup_cis = 0;
- me->pr_CIS = CTOBPTR (f->f_fh);
- }
- else
- {
- if (!f)
- {
- int fd = open ("/dev/null", 0);
- dup_cis = dup2_BPTR (fd);
- close (fd);
- }
- else
- dup_cis = dup2_BPTR (0);
- me->pr_CIS = dup_cis ? : old_cis;
- }
- if ((f = u_save.u_ofile[1]) && f->f_type == DTYPE_FILE)
- {
- dup_cos = 0;
- me->pr_COS = CTOBPTR (f->f_fh);
- }
- else
- {
- if (!f)
- {
- int fd = open ("/dev/null", 1);
- dup_cos = dup2_BPTR (fd);
- close (fd);
- }
- else
- dup_cos = dup2_BPTR (1);
- me->pr_COS = dup_cos ? : old_cos;
- }
- dup_ces = 0;
- }
- else
- {
- if ((f = u_save.u_ofile[0]) && f->f_type == DTYPE_FILE)
- {
- dup_cis = 0;
- old_cis = SelectInput (CTOBPTR (f->f_fh));
- readargs_kludge (CTOBPTR (f->f_fh));
- }
- else
- {
- if (!f)
- {
- int fd = open ("/dev/null", 0);
- dup_cis = dup2_BPTR (fd);
- close (fd);
- }
- else
- dup_cis = dup2_BPTR (0);
- old_cis = 0;
- if (dup_cis)
- {
- old_cis = SelectInput (dup_cis);
- readargs_kludge (dup_cis);
- }
- }
- if ((f = u_save.u_ofile[1]) && f->f_type == DTYPE_FILE)
- {
- dup_cos = 0;
- old_cos = SelectOutput (CTOBPTR (f->f_fh));
- }
- else
- {
- if (!f)
- {
- int fd = open ("/dev/null", 1);
- dup_cos = dup2_BPTR (fd);
- close (fd);
- }
- else
- dup_cos = dup2_BPTR (1);
- old_cos = 0;
- if (dup_cos)
- old_cos = SelectOutput (dup_cos);
- }
- old_ces = me->pr_CES;
- if ((f = u_save.u_ofile[2]) && f->f_type == DTYPE_FILE)
- {
- dup_ces = 0;
- me->pr_CES = CTOBPTR (f->f_fh);
- }
- else
- {
- if (!f)
- {
- int fd = open ("/dev/null", 2);
- dup_ces = dup2_BPTR (fd);
- close (fd);
- }
- else
- dup_ces = dup2_BPTR (2);
- me->pr_CES = dup_ces ? : old_ces;
- }
- }
-
- /* BEWARE that after this reset no library functions can be
- called any longer until the moment where trapdata is
- reinstalled !! */
- old_trapdata = me->pr_Task.tc_TrapData;
- me->pr_Task.tc_TrapData = u_save.u_otrap_data;
- old_trapcode = me->pr_Task.tc_TrapCode;
- me->pr_Task.tc_TrapCode = u_save.u_otrap_code;
-
- if (! _dos20)
- /* this is a hack, since some programs expect pr_ReturnAddr to
- * be valid... */
- {
- void *old_return_addr = me->pr_ReturnAddr;
- u_int *sp = (u_int *) get_sp ();
- struct FileHandle *fh = BTOCPTR (Input ());
- u_int obuf=fh->fh_Buf, oend=fh->fh_End, opos=fh->fh_Pos;
-
- *--sp = 0;
- *--sp = 0;
- me->pr_ReturnAddr = sp;
- asm volatile ("movel %0,sp" : : "a" (sp));
- me->pr_Result2 = 0;
- fh->fh_Buf = CTOBPTR (al);
- fh->fh_Pos = 0;
- fh->fh_End = cp-al;
-
- /* start the baby */
- d0 = cp - al;
- a0 = al;
- a1 = code;
- asm volatile ("jsr a1@@" : "=d" (d0) : "0" (d0), "a" (a0), "a" (a1));
- /* save the result before it's destroyed.. */
- res = d0;
-
- me->pr_ReturnAddr = old_return_addr;
- fh->fh_Buf = obuf;
- fh->fh_Pos = opos;
- fh->fh_End = oend;
- sp += 2;
- asm volatile ("movel %0,sp" : : "a" (sp));
- }
- else
- {
- struct CommandLineInterface *CLI = BTOCPTR (me->pr_CLI);
- u_int stack_size = CLI ? CLI->cli_DefaultStack * 4 : me->pr_StackSize;
-
- /* perhaps someone really uses so small stacks......... */
- /* if (stack_size <= 4096) stack_size = 250000; */
-
- /* the above approach has too many incompatibilities, sigh.
-
- Note: The use of RunCommand() here means, that we *waste* the
- entire stack space allocated for this process! If someone
- comes up with a clever trick (probably involving StackSwap ())
- where the stack of this process can be freed before calling
- RunCommand (), lots of users with memory problems would be
- thankful! */
-
- res = RunCommand (CTOBPTR (code) - 1, stack_size, al, cp - al);
- }
-
- /* reinstall enough of ixemul to be able to finish cleanly
- (the recent addition of an ix_sleep() at the end of a vfork'd
- process makes it necessary to reinstall the signalling facilities!) */
-
- me->pr_Task.tc_TrapData = old_trapdata;
- me->pr_Task.tc_TrapCode = old_trapcode;
- /* have to do this, or ix_close() is not able to RemoveIntServer .. */
- AddIntServer (INTB_VERTB, & u_save.u_itimerint);
- me->pr_Task.tc_Flags = old_flags;
- me->pr_Task.tc_Launch = old_launch;
- me->pr_Task.tc_Switch = old_switch;
-
- kfree (al);
-
- if (! _dos20)
- {
- me->pr_CIS = old_cis;
- me->pr_COS = old_cos;
- }
- else
- {
- if (old_cis)
- SelectInput (old_cis);
- if (old_cos)
- Flush (SelectOutput (old_cos));
- me->pr_CES = old_ces;
- }
-
- if (dup_cis)
- Close (dup_cis);
- if (dup_cos)
- Close (dup_cos);
- if (dup_ces)
- Close (dup_ces);
-
- me->pr_Task.tc_SigAlloc |= oldsigalloc;
- }
-
- return res;
- }
-
- static char *
- quote (char *orig)
- {
- int i;
- char *new, *cp;
-
- i = strlen (orig);
-
- if (strpbrk (orig, "\"\'\\ \t\n"))
- {
- /* worst case, each character needs quoting plus starting and ending " */
- new = (char *) kmalloc (i * 2 + 3);
- if (! new) return 0;
-
- cp = new;
- *cp++ = '"';
- while (*orig)
- {
- if (index ("\"\\", *orig))
- *cp++ = '\\';
- *cp++ = *orig++;
- }
- *cp++ = '"';
- *cp = 0;
-
- return new;
- }
- else
- return 0; /* means `just use the original string' */
- }
-
- /* try to obtain a DOS filehandle on the specified descriptor. This only
- works, if the user has mounted IXPIPE: */
- BPTR
- dup2_BPTR (int fd)
- {
- long id;
- char name[20];
-
- id = fcntl (fd, F_EXTERNALIZE, 0);
- if (id >= 0)
- {
- sprintf (name, "IXPIPE:%x", id);
- /* 0x4242 is a magic packet understood by IXPIPE: to F_INTERNALIZE id */
- return Open (name, 0x4242);
- }
-
- return 0;
- }
-
-
- /* the misteries of DOS seem to never want to take an end... */
- void
- readargs_kludge (BPTR bp)
- {
- int ch;
- static const int EOS_CHAR = -1;
-
- #if 0
- /* the autodocs say this bug is fixed after v37, well, perhaps that was a
- very deep wish, nevertheless unheard by dos...
- Without this kludge, you have to actually press return if stdin is not
- redirected...
- Thanks mbs: whithout your shell code I would never have guessed that
- something that weird could be possible....
- */
- if (ix.ix_dos_base->lib_Version <= 37)
- #endif
- {
- ch = UnGetC (bp, EOS_CHAR) ? 0 : '\n';
- while ((ch != '\n') && (ch != EOS_CHAR))
- ch = FGetC (bp);
- Flush (bp);
- }
- }
- @
-
-
- 1.5
- log
- @change to 2.x header files
- @
- text
- @d108 1
- a108 1
- #ifndef NO_VFORK_RESUME
- d110 1
- a110 1
- if (u.u_save_sp)
- d118 2
- d270 1
- a270 1
- #ifndef NO_VFORK_RESUME
- @
-
-
- 1.4
- log
- @don't believe autodocs.. the flush-bug is still there, get rid of the `if'..
- @
- text
- @a31 32
- struct Process_20 {
- struct Task pr_Task;
- struct MsgPort pr_MsgPort; /* This is BPTR address from DOS functions */
- WORD pr_Pad; /* Remaining variables on 4 byte boundaries */
- BPTR pr_SegList; /* Array of seg lists used by this process */
- LONG pr_StackSize; /* Size of process stack in bytes */
- APTR pr_GlobVec; /* Global vector for this process (BCPL) */
- LONG pr_TaskNum; /* CLI task number of zero if not a CLI */
- BPTR pr_StackBase; /* Ptr to high memory end of process stack */
- LONG pr_Result2; /* Value of secondary result from last call */
- BPTR pr_CurrentDir; /* Lock associated with current directory */
- BPTR pr_CIS; /* Current CLI Input Stream */
- BPTR pr_COS; /* Current CLI Output Stream */
- APTR pr_ConsoleTask; /* Console handler process for current window*/
- APTR pr_FileSystemTask; /* File handler process for current drive */
- BPTR pr_CLI; /* pointer to CommandLineInterface */
- APTR pr_ReturnAddr; /* pointer to previous stack frame */
- APTR pr_PktWait; /* Function to be called when awaiting msg */
- APTR pr_WindowPtr; /* Window for error printing */
-
- /* following definitions are new with 2.0 */
- BPTR pr_HomeDir; /* Home directory of executing program */
- LONG pr_Flags; /* flags telling dos about process */
- void (*pr_ExitCode)(); /* code to call on exit of program or NULL */
- LONG pr_ExitData; /* Passed as an argument to pr_ExitCode. */
- UBYTE *pr_Arguments; /* Arguments passed to the process at start */
- struct MinList pr_LocalVars; /* Local environment variables */
- ULONG pr_ShellPrivate; /* for the use of the current shell */
- BPTR pr_CES; /* Error stream - if NULL, use pr_COS */
- }; /* Process */
-
-
- a42 100
- /* 2.0 support */
- #define BASE_EXT_DECL
- #define BASE_PAR_DECL
- #define BASE_PAR_DECL0
- #define BASE_NAME ix.ix_dos_base
- __inline static LONG RunCommand(BASE_PAR_DECL BPTR seg, long int stack, UBYTE* paramptr, long int paramlen)
- {
- BASE_EXT_DECL
- register LONG res __asm("d0");
- register void *a6 __asm ("a6");
- register BPTR d1 __asm("d1");
- register long int d2 __asm("d2");
- register UBYTE* d3 __asm("d3");
- register long int d4 __asm("d4");
-
- a6 = BASE_NAME;
- d1 = seg;
- d2 = stack;
- d3 = paramptr;
- d4 = paramlen;
- __asm volatile ("
- jsr a6@@(-0x1f8)"
- : "=r" (res)
- : "r" (a6), "r" (d1), "r" (d2), "r" (d3), "r" (d4)
- : "d0", "d1", "a0", "a1", "d2", "d3", "d4");
- return res;
- }
- __inline static BPTR SelectInput(BASE_PAR_DECL BPTR fh)
- {
- BASE_EXT_DECL
- register BPTR res __asm("d0");
- register void *a6 __asm ("a6");
- register BPTR d1 __asm("d1");
-
- a6 = BASE_NAME;
- d1 = fh;
- __asm volatile ("
- jsr a6@@(-0x126)"
- : "=r" (res)
- : "r" (a6), "r" (d1)
- : "d0", "d1", "a0", "a1");
- return res;
- }
- __inline static BPTR SelectOutput(BASE_PAR_DECL BPTR fh)
- {
- BASE_EXT_DECL
- register BPTR res __asm("d0");
- register void *a6 __asm ("a6");
- register BPTR d1 __asm("d1");
-
- a6 = BASE_NAME;
- d1 = fh;
- __asm volatile ("
- jsr a6@@(-0x12c)"
- : "=r" (res)
- : "r" (a6), "r" (d1)
- : "d0", "d1", "a0", "a1");
- return res;
- }
- static __inline LONG
- UnGetC (BASE_PAR_DECL BPTR fh,long character)
- {
- BASE_EXT_DECL
- register LONG _res __asm("d0");
- register struct DosLibrary *a6 __asm("a6") = BASE_NAME;
- register BPTR d1 __asm("d1") = fh;
- register long d2 __asm("d2") = character;
- __asm __volatile ("jsr a6@@(-0x13e)"
- : "=r" (_res)
- : "r" (a6), "r" (d1), "r" (d2)
- : "a0","a1","d0","d1","d2");
- return _res;
- }
- static __inline LONG
- FGetC (BASE_PAR_DECL BPTR fh)
- {
- BASE_EXT_DECL
- register LONG _res __asm("d0");
- register struct DosLibrary *a6 __asm("a6") = BASE_NAME;
- register BPTR d1 __asm("d1") = fh;
- __asm __volatile ("jsr a6@@(-0x132)"
- : "=r" (_res)
- : "r" (a6), "r" (d1)
- : "a0","a1","d0","d1");
- return _res;
- }
- static __inline LONG
- Flush (BASE_PAR_DECL BPTR fh)
- {
- BASE_EXT_DECL
- register LONG _res __asm("d0");
- register struct DosLibrary *a6 __asm("a6") = BASE_NAME;
- register BPTR d1 __asm("d1") = fh;
- __asm __volatile ("jsr a6@@(-0x168)"
- : "=r" (_res)
- : "r" (a6), "r" (d1)
- : "a0","a1","d0","d1");
- return _res;
- }
-
- d335 1
- a335 1
- struct Process_20 *me = (struct Process_20 *) FindTask (0);
- d397 1
- a397 1
- me->pr_Task.tc_Flags = u.u_otask_flags;
- d399 1
- a399 1
- me->pr_Task.tc_Launch = u.u_olaunch; /* restoring this disables our signals */
- d401 2
- a402 2
- me->pr_Task.tc_Switch = u.u_oswitch;
- RemIntServer (INTB_VERTB, & u.u_itimerint);
- d420 1
- a420 1
- if ((f = u.u_ofile[0]) && f->f_type == DTYPE_FILE)
- d437 1
- a437 1
- if ((f = u.u_ofile[1]) && f->f_type == DTYPE_FILE)
- d458 1
- a458 1
- if ((f = u.u_ofile[0]) && f->f_type == DTYPE_FILE)
- d481 1
- a481 1
- if ((f = u.u_ofile[1]) && f->f_type == DTYPE_FILE)
- d501 1
- a501 1
- if ((f = u.u_ofile[2]) && f->f_type == DTYPE_FILE)
- d524 1
- a524 1
- me->pr_Task.tc_TrapData = u.u_otrap_data;
- d526 1
- a526 1
- me->pr_Task.tc_TrapCode = u.u_otrap_code;
- d588 1
- a588 1
- AddIntServer (INTB_VERTB, & u.u_itimerint);
- @
-
-
- 1.3
- log
- @integrate changes made to ssystem() here as well.
- @
- text
- @d812 8
- d821 1
- @
-
-
- 1.2
- log
- @make dupvec() public, it's used somewhere else in the library.
- make use of new F_EXTERNALIZE feature and use IXPIPE instead of the default
- NIL: filehandles if starting a program in compatibility mode and its
- descriptors don't refer to DTYPE_FILE files.
- @
- text
- @d134 40
- d240 1
- d249 4
- d400 1
- d408 3
- d559 8
- a566 1
- dup_cis = dup2_BPTR (0);
- d576 8
- a583 1
- dup_cos = dup2_BPTR (1);
- d594 1
- d598 8
- a605 1
- dup_cis = dup2_BPTR (0);
- d608 4
- a611 1
- old_cis = SelectInput (dup_cis);
- d620 8
- a627 1
- dup_cos = dup2_BPTR (1);
- d640 8
- a647 1
- dup_ces = dup2_BPTR (2);
- a726 7
- if (dup_cis)
- Close (dup_cis);
- if (dup_cos)
- Close (dup_cos);
- if (dup_ces)
- Close (dup_ces);
-
- d737 1
- a737 1
- SelectOutput (old_cos);
- d741 7
- d787 1
- a787 1
- static BPTR
- d802 17
- @
-
-
- 1.1
- log
- @Initial revision
- @
- text
- @d221 1
- a221 1
- static char **
- d344 3
- d433 1
- d494 5
- a498 1
- /* limited support (part 2 ;-)) for I/O redirection on old programs */
- d504 9
- a512 1
- me->pr_CIS = CTOBPTR (f->f_fh);
- d514 10
- a523 1
- me->pr_COS = CTOBPTR (f->f_fh);
- d527 24
- a550 4
- old_cis = ((f = u.u_ofile[0]) && f->f_type == DTYPE_FILE) ?
- SelectInput (CTOBPTR (f->f_fh)) : 0;
- old_cos = ((f = u.u_ofile[1]) && f->f_type == DTYPE_FILE) ?
- SelectOutput (CTOBPTR (f->f_fh)) : 0;
- d553 9
- a561 1
- me->pr_CES = CTOBPTR (f->f_fh);
- d639 7
- d696 19
- @
-