*nix Documentation Project
·  Home
 +   man pages
·  Linux HOWTOs
·  FreeBSD Tips
·  *niX Forums

  man pages->IRIX man pages -> f90/pxfkill (3)              
Title
Content
Arch
Section
 

Contents


PXFKILL(3F)					      Last changed: 2-26-98

NAME    [Toc]    [Back]

     PXFKILL - Sends a signal to a process or group of processes

SYNOPSIS    [Toc]    [Back]

     SUBROUTINE	PXFKILL	(ipid, isig, ierror)
     INTEGER ipid, isig, ierror

IMPLEMENTATION    [Toc]    [Back]

     UNICOS, UNICOS/mk,	and IRIX systems

STANDARDS    [Toc]    [Back]

     IEEE standard interface for FORTRAN 77

DESCRIPTION    [Toc]    [Back]

     The PXFKILL subroutine uses the kill(2) system call to send a signal
     to	a process or group of processes.

     The following is a	list of	valid arguments	for this routine:

     ipid      A default integer input variable	containing the process PID.
	       The signal will be sent to a process or group of	processes
	       specified by ipid.

     isig      A default integer output	variable containing the	signal to
	       be sent.

     ierror    A default integer output	variable that contains zero if
	       PXFKILL was successful and nonzero if PXFKILL was not
	       successful.

     This subroutine may return	any of the following error values:

     EINVAL	    The	value of the isig argument is an invalid or
		    unsupported	signal number.

     EPERM	    The	process	does not have permission to send the isig
		    signal to any receiving process.

     ESRCH	    No process or process group	can be found corresponding
		    to the process ID specified	by ipid.

     On	UNICOS and UNICOS/mk systems, the subroutine may also return:

     EPERM	    The	value of the ipid argument is 1	(proc1)	and isig is
		    either SIGKILL or SIGSTOP.

     On	IRIX systems, it may also return:

     EPERM	    The	value of the ipid argument is 1	(proc1)	and isig is
		    SIGKILL.

     ESRCH	    The	process	group was given	as 0 but the sending
		    process does not have a process group

     On	IRIX systems, this routine is in libfortran.so which is	linked by
     default when compiling programs with the MIPSpro 7	Fortran	90 compiler
     or	when compiling programs	with the -craylibs option to the MIPSpro
     7.2 F77 compiler.

     When using	the CF90 compiler or MIPSpro 7 Fortran 90 compiler on
     UNICOS, UNICOS/mk,	or IRIX	systems, all arguments must be of default
     kind unless documented otherwise. On UNICOS and UNICOS/mk,	default
     kind is KIND=8 for	integer, real, complex,	and logical arguments; on
     IRIX systems, the default kind is KIND=4.

NOTES    [Toc]    [Back]

     Replace any Fortran reference to kill() with a subroutine call to
     PXFKILL.

EXAMPLES    [Toc]    [Back]

	      program pxftest
	      integer ipid, isig, ierror

	      CALL PXFFORK(ipid,ierror)
	      if (ierror .ne. 0) then
		 print *,'FAILED: PXFFORK call failed with error = ',ierror
		 print *,'ipid=',ipid
	      else
		 print *,'PASSED: PXFFORK call returned	no error'
	      endif
	      call PXFCONST("SIGKILL",isig,ierror)
	      if(ierror	.ne. 0)	then
		 print *, 'PXFCONST FAILED', ierror
		 print *,'isig=',isig
	      else
		 print *, 'PXFCONST PASSED'
	      endif
	      CALL PXFKILL(ipid, isig, ierror)
	      if (ierror .ne. 0) then
		 print *,'FAILED: PXFKILL call failed with error = ',ierror
		 print *,'ipid=',ipid
		 print *,'isig=',isig
	      else
		 print *,'PASSED: PXFKILL call returned	no error'
	      endif
	      end

SEE ALSO    [Toc]    [Back]

      
      
     kill(2)

     Application Programmer's Library Reference	Manual,	publication
     SR-2165, for the printed version of this man page.
[ Back ]
 Similar pages
Name OS Title
gsignal Tru64 General: Sends a signal to a process group
sigsend IRIX send a signal to a process or a group of processes
raise HP-UX send a signal to a process or a group of processes
kill IRIX send a signal to a process or a group of processes
sigsendset HP-UX send a signal to a process or a group of processes
kill Tru64 Send a signal to a process or to a group of processes
sigsend HP-UX send a signal to a process or a group of processes
kill HP-UX send a signal to a process or a group of processes
kill Tru64 Sends a signal to a running process
psignal Tru64 General: Sends a signal to a process
Copyright © 2004-2005 DeniX Solutions SRL
newsletter delivery service