home *** CD-ROM | disk | FTP | other *** search
- head 1.3;
- access;
- symbols
- version39-41:1.1;
- locks;
- comment @ * @;
-
-
- 1.3
- date 92.08.09.21.07.02; author amiga; state Exp;
- branches;
- next 1.2;
-
- 1.2
- date 92.07.28.02.53.06; 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.3
- log
- @change to 2.x header files
- @
- 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.
- *
- * 22-jan-92 -mw- restore sigmask before calling system()
- */
-
- #define KERNEL
- #include "ixemul.h"
- #include <ctype.h>
- #include <sys/wait.h>
-
- #ifdef DEBUG
- #define DP(a) kprintf a
- #else
- #define DP(a)
- #endif
-
- /* 2.0 support */
- #include <utility/tagitem.h>
- #include <dos/dostags.h>
-
- #define BASE_EXT_DECL
- #define BASE_PAR_DECL
- #define BASE_PAR_DECL0
- #define BASE_NAME ix.ix_arp_base
- __inline static LONG SyncRun(BASE_PAR_DECL const char* name, const char* command, BPTR input, BPTR output)
- {
- BASE_EXT_DECL
- register LONG res __asm("d0");
- register void *a6 __asm ("a6");
- register const char* a0 __asm("a0");
- register const char* a1 __asm("a1");
- register BPTR d0 __asm("d0");
- register BPTR d1 __asm("d1");
-
- a6 = BASE_NAME;
- a0 = name;
- a1 = command;
- d0 = input;
- d1 = output;
- __asm volatile ("
- jsr a6@@(-0x21c)"
- : "=r" (res)
- : "r" (a6), "r" (a0), "r" (a1), "r" (d0), "r" (d1)
- : "d0", "d1", "a0", "a1");
- return res;
- }
-
- extern int _dos20; /* set in crt0.c */
-
- #if __GNUC__ != 2
- #define alloca __builtin_alloca
- #endif
-
- extern BPTR *__load_seg (char *name, char **args);
-
- int
- ssystem(char *argline)
- {
- int rc, err = 0;
- UBYTE *arg, *index();
- UBYTE *tmp;
- int stack_size;
- struct CommandLineInterface *CLI;
- struct Process *me;
- int omask;
-
- omask = syscall (SYS_sigsetmask, ~0);
- me = (struct Process *)FindTask(0);
- CLI = BTOCPTR (me->pr_CLI);
- stack_size = CLI ? CLI->cli_DefaultStack * 4 : me->pr_StackSize;
- if (stack_size <= 4096) stack_size = 250000;
-
- /* the +1 is to get a cheap way to transform this into a BSTR */
- tmp = alloca (strlen (argline) + 6);
- tmp = LONG_ALIGN (tmp);
- tmp++;
-
- strcpy (tmp, argline);
-
- while (*tmp == ' ' || *tmp == '\t') ++tmp;
- /* not needed with custom load-seg function */
- if (! _dos20)
- while (tmp[0] == '.' && tmp[1] == '/') tmp += 2;
-
- if (arg = index(tmp, ' ')) *arg++ = 0;
-
- if (! _dos20)
- {
- if (arg)
- {
- /* the following for BCPL pecularities.. */
- if (arg[strlen (arg) - 1] != '\n') strcat (arg, "\n");
- }
-
- /* no interpreter expansion here, but Arp runs much stabler than 2.0... */
- rc = SyncRun((char *)tmp, (char *)arg, 0, 0);
- err = __ioerr_to_errno (IoErr ());
- }
- else
- {
- BPTR *segs;
- char *args;
- BPTR old_cis, old_cos, old_ces;
- BPTR dup_cis, dup_cos, dup_ces;
- struct file *f;
-
- segs = __load_seg (tmp, &args);
-
- /* check for special cookie */
- if (segs == (BPTR *) -2)
- {
- syscall (SYS_sigsetmask, omask);
-
- /* let the shell do the dirty work ;-)) */
- return system (argline);
- }
-
- if (segs)
- {
- char **name;
- char *orig;
- char *all_args;
- u_int old_signals;
-
- /* if __load_seg() set args to something, we have to rebuild our
- * command line, but only just in that case ;-))
- */
- if (args)
- {
- int force_quotes = 0;
-
- /* now this IS a horrible kludge.. but again, I *NEED* sksh
- * working, and it only works, if the argument to the -c
- * switch is passed quoted... So if the __load_seg code
- * decided, that this was such a special sksh-script, it
- * negates the *arg parameter... shudder...
- *
- * NOTE: This only works for command lines that contain no
- * quotes themselves... I don't escape the argument
- * line, I just put a pair of quotes around it!
- * The starting quote is already included in the args
- * string from __load_seg()...
- */
- if (((int)args) < 0)
- {
- force_quotes = 1;
- args = (char *) ((-(int)args));
- }
-
- /* make handling easier */
- if (! arg) arg = "";
-
- /* the command we build looks like:
- * <seg'd command> args arg
- */
-
- all_args = alloca (strlen (args) + 1 + strlen (arg) + 4);
- strcpy (all_args, args);
- if (*arg)
- {
- strcat (all_args, " ");
- strcat (all_args, arg);
- }
-
- if (force_quotes)
- strcat (all_args, "\""); /* no comment... */
- strcat (all_args, "\n"); /* neither, this insn't my kludge though.. */
-
- /* and finally reassign the commandline to arg */
- arg = all_args;
- /* if args was not "", we have to free it, it's from strdup() */
- if (*args) syscall (SYS_free, args);
- }
- else
- {
- /* even if we didn't get any arguments from the expander, we still
- * need to protect the original arguments ala BCPL ..
- * Remember that `arg' is a (large enough) alloca() string ;-) */
- if (arg)
- strcat (arg, "\n");
- else
- arg = "\n";
- }
-
- /*
- * Hack to always get the name of the currently executing program
- * to show up in Xoper
- */
- if (CLI)
- {
- name = (char **) & CLI->cli_CommandName;
- orig = *name;
- /* that's why we incremented tmp before ;-)) */
- ((unsigned char *)tmp)[-1] = strlen (tmp);
- /* this is always odd (stack=even + 1), so will chop fine to BPTR */
- *name = (char *) ((long)tmp >> 2);
- }
- else
- {
- name = (char **) & me->pr_Task.tc_Node.ln_Name;
- orig = *name;
- *name = tmp;
- }
-
- DP(("RunCommand (.. arg = >%s<, len = %ld)\n", arg, strlen (arg)));
- /* perform I/O redirection... (copied from execve.c) */
-
- if ((f = u.u_ofile[0]) && f->f_type == DTYPE_FILE)
- {
- dup_cis = 0;
- old_cis = SelectInput (CTOBPTR (f->f_fh));
- readargs_kludge (CTOBPTR (f->f_fh));
- DP(("redir 0, old_cis = $%lx\n",old_cis));
- }
- 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);
- DP(("redir 0, old_cis = $%lx, dup_cis = $%lx\n", old_cis, dup_cis));
- }
- else
- DP(("redir 0, dup2_BPTR failed\n"));
- }
-
- if ((f = u.u_ofile[1]) && f->f_type == DTYPE_FILE)
- {
- dup_cos = 0;
- old_cos = SelectOutput (CTOBPTR (f->f_fh));
- DP(("redir 1, old_cos = $%lx\n", old_cos));
- }
- 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);
- DP(("redir 1, old_cos = $%lx, dup_cos = $%lx\n", old_cos, dup_cos));
- }
- else
- DP(("redir 1, dup2_BPTR failed\n"));
- }
- old_ces = me->pr_CES;
- if ((f = u.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;
- }
-
- /* RunCommand should provide the started program with a fresh set of
- * signals, it doesn't. So we do this by hand here... */
- old_signals = me->pr_Task.tc_SigAlloc;
- me->pr_Task.tc_SigAlloc &= 0xffff;
- rc = RunCommand (*segs, stack_size, arg, strlen (arg));
- me->pr_Task.tc_SigAlloc = old_signals;
- err = __ioerr_to_errno (IoErr ());
- *name = orig;
-
- if (old_cis)
- SelectInput (old_cis);
- if (old_cos)
- Flush (SelectOutput (old_cos));
- me->pr_CES = old_ces;
-
- /* reset I/O */
- if (dup_cis)
- Close (dup_cis);
- if (dup_cos)
- Close (dup_cos);
- if (dup_ces)
- Close (dup_ces);
-
- __free_seg (segs);
- }
- else
- {
- rc = 20;
-
- err = __ioerr_to_errno (IoErr ());
- }
- }
-
- syscall (SYS_sigsetmask, omask);
-
- if (rc > 128)
- errno = EINTR;
- else
- errno = err;
-
- return (rc >= 128) ? W_EXITCODE (0, rc & 0x7f) : W_EXITCODE (rc, 0);
- }
- @
-
-
- 1.2
- log
- @provide better I/O-redirection, seems to finally cooperate with ReadArgs...
- @
- text
- @d33 3
- a35 3
- #define NO_PROTOTYPES
- #include <libraries/arpbase.h> /* HAS! to be V39 or higher! */
- #undef NO_PROTOTYPES
- d41 1
- a41 10
- #include <inline/arp.h>
-
- /* 2.0 support */
- #include "gcc:include20/utility/tagitem.h"
- #include "gcc:include20/dos/dostags.h"
- #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)
- d46 3
- a49 3
- register long int d2 __asm("d2");
- register UBYTE* d3 __asm("d3");
- register long int d4 __asm("d4");
- d52 4
- a55 4
- d1 = seg;
- d2 = stack;
- d3 = paramptr;
- d4 = paramlen;
- d57 1
- a57 1
- jsr a6@@(-0x1f8)"
- d59 2
- a60 2
- : "r" (a6), "r" (d1), "r" (d2), "r" (d3), "r" (d4)
- : "d0", "d1", "a0", "a1", "d2", "d3", "d4");
- a62 69
- static __inline BPTR
- SelectInput (BASE_PAR_DECL BPTR fh)
- {
- BASE_EXT_DECL
- register BPTR _res __asm("d0");
- register struct DosLibrary *a6 __asm("a6") = BASE_NAME;
- register BPTR d1 __asm("d1") = fh;
- __asm __volatile ("jsr a6@@(-0x126)"
- : "=r" (_res)
- : "r" (a6), "r" (d1)
- : "a0","a1","d0","d1", "memory");
- return _res;
- }
- static __inline BPTR
- SelectOutput (BASE_PAR_DECL BPTR fh)
- {
- BASE_EXT_DECL
- register BPTR _res __asm("d0");
- register struct DosLibrary *a6 __asm("a6") = BASE_NAME;
- register BPTR d1 __asm("d1") = fh;
- __asm __volatile ("jsr a6@@(-0x12c)"
- : "=r" (_res)
- : "r" (a6), "r" (d1)
- : "a0","a1","d0","d1", "memory");
- 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", "memory");
- return _res;
- }
- 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 */
- d80 1
- a80 1
- struct Process_20 *me;
- @
-
-
- 1.1
- log
- @Initial revision
- @
- text
- @d72 70
- d158 1
- a158 1
- struct Process *me;
- d197 3
- d300 73
- d382 14
- @
-