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

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

D(3F)

Contents


PXFESTRGET(3F)					       Last changed: 1-6-98

NAME    [Toc]    [Back]

     PXFESTRGET	- Accesses a single string element of a	structure component
     that is an	array

SYNOPSIS    [Toc]    [Back]

     SUBROUTINE	PXFESTRGET (jhandle, compnam, index, value, ilen, ierror)
     INTEGER jhandle, index, ilen, ierror
     CHARACTER*n compnam, value

IMPLEMENTATION    [Toc]    [Back]

     UNICOS, UNICOS/mk,	and IRIX systems

STANDARDS    [Toc]    [Back]

     IEEE standard interface for FORTRAN 77

DESCRIPTION    [Toc]    [Back]

     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.

     The PXFESTRGET routine returns a string contained in a single element
     of	a structure component that is an array.

     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, the default kind is KIND=4.

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

     jhandle   An input	handle variable	created	with PXFSTRUCTCREATE(3F).

     compnam   An input	character variable or array element containing the
	       desired structure component name.

     index     An input	integer	variable for the desired index in the
	       array.

     value     An output character variable or array element that will
	       contain the string referenced by	companm, index,	and
	       jhandle.

     ilen      An output integer variable for the length of the	returned
	       character string.

     ierror    An output integer variable that contains	zero if	PXFESTRGET
	       was successful or nonzero if PXFESTRGET was not successful.

     The PXFESTRGET subroutine may return any of the following error
     values:

     ENONAME   If the component	name is	not defined for	this structure.

     ETRUNC    If the declared length of the character argument	is
	       insufficient to contain the string to be	returned.

     ENOMEM    If there	is insufficent memory to create	data structures
	       needed by the routine.

     EBADHANDLE    [Toc]    [Back]
	       If jhandle is an	invalid	handle or has an incorrect handle
	       type (UNICOS and	UNICOS/mk systems only).

EXAMPLES    [Toc]    [Back]

     In	this example, PXFGETGRGI
	are used to obtain
     the first user name in the	current	process' group.

 program pxftest
 integer igid, ierror, jgroup, len, imax, i
 character*30 loginname
 CALL PXFSTRUCTCREATE('group',jgroup,ierror)
    if (ierror .ne. 0) then
       print *,'FAILED:	PXFSTRUCTCREATE	with error = ',ierror
    else
       CALL PXFGETGID(igid,ierror)
       CALL PXFGETGRGID(igid,jgroup,ierror)
       if (ierror .ne. 0) then
	   print *,'FAILED: PXFGETGRGID	with error = ',ierror
       else
	   CALL	PXFINTGET(jgroup,'gr_nmem',imax,ierror)
	   if (ierror .ne. 0) then
	      print *,'FAILED: PXFINTGET with error = ',ierror
	   else
	      if (imax .gt. 0) then
		 do i =	1,imax
		    CALL PXFESTRGET(jgroup,'gr_mem',i,loginname,len,ierror)
		    print *,loginname
		 end do
	      else
		 print *,'FAILED: Could	not test PXFESTRGET'
	      endif
	   endif
       endif
    endif
 end

SEE ALSO    [Toc]    [Back]

      
      
     PXFSTRUCTCREATE(3F)

     Application Programmer's Library Reference	Manual,	publication SR2165,
 for the printed version of this man page.

PXFESTRGET(3F)					       Last changed: 1-6-98

NAME    [Toc]    [Back]

     PXFESTRGET	- Accesses a single string element of a	structure component
     that is an	array

SYNOPSIS    [Toc]    [Back]

     SUBROUTINE	PXFESTRGET (jhandle, compnam, index, value, ilen, ierror)
     INTEGER jhandle, index, ilen, ierror
     CHARACTER*n compnam, value

IMPLEMENTATION    [Toc]    [Back]

     UNICOS, UNICOS/mk,	and IRIX systems

STANDARDS    [Toc]    [Back]

     IEEE standard interface for FORTRAN 77

DESCRIPTION    [Toc]    [Back]

     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.

     The PXFESTRGET routine returns a string contained in a single element
     of	a structure component that is an array.

     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, the default kind is KIND=4.

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

     jhandle   An input	handle variable	created	with PXFSTRUCTCREATE(3F).

     compnam   An input	character variable or array element containing the
	       desired structure component name.

     index     An input	integer	variable for the desired index in the
	       array.

     value     An output character variable or array element that will
	       contain the string referenced by	companm, index,	and
	       jhandle.

     ilen      An output integer variable for the length of the	returned
	       character string.

     ierror    An output integer variable that contains	zero if	PXFESTRGET
	       was successful or nonzero if PXFESTRGET was not successful.

     The PXFESTRGET subroutine may return any of the following error
     values:

     ENONAME   If the component	name is	not defined for	this structure.

     ETRUNC    If the declared length of the character argument	is
	       insufficient to contain the string to be	returned.

     ENOMEM    If there	is insufficent memory to create	data structures
	       needed by the routine.

     EBADHANDLE    [Toc]    [Back]
	       If jhandle is an	invalid	handle or has an incorrect handle
	       type (UNICOS and	UNICOS/mk systems only).

EXAMPLES    [Toc]    [Back]

     In	this example, PXFGETGRGI
	are used to obtain
     the first user name in the	current	process' group.

 program pxftest
 integer igid, ierror, jgroup, len, imax, i
 character*30 loginname
 CALL PXFSTRUCTCREATE('group',jgroup,ierror)
    if (ierror .ne. 0) then
       print *,'FAILED:	PXFSTRUCTCREATE	with error = ',ierror
    else
       CALL PXFGETGID(igid,ierror)
       CALL PXFGETGRGID(igid,jgroup,ierror)
       if (ierror .ne. 0) then
	   print *,'FAILED: PXFGETGRGID	with error = ',ierror
       else
	   CALL	PXFINTGET(jgroup,'gr_nmem',imax,ierror)
	   if (ierror .ne. 0) then
	      print *,'FAILED: PXFINTGET with error = ',ierror
	   else
	      if (imax .gt. 0) then
		 do i =	1,imax
		    CALL PXFESTRGET(jgroup,'gr_mem',i,loginname,len,ierror)
		    print *,loginname
		 end do
	      else
		 print *,'FAILED: Could	not test PXFESTRGET'
	      endif
	   endif
       endif
    endif
 end

SEE ALSO    [Toc]    [Back]

      
      
     PXFSTRUCTCREATE(3F)

     Application Programmer's Library Reference	Manual,	publication SR2165,
 for the printed version of this man page.

[ Back ]
 Similar pages
Name OS Title
XmStringInitContext HP-UX A compound string function that creates a data structure for scanning an XmString component by component
rgbsize IRIX single-color component buffer.
XmStringPeekNextComponent Tru64 A compound string function that returns the component type of the next component fetched
XmStringPeekNextComponent HP-UX A compound string function that returns the component type of the next component to be fetched
XmStringPeekNextComponent IRIX A compound string function that returns the component type of the next component fetched
HTRID3 IRIX EISPACK routine. This subroutine reduces a COMPLEX HERMITIAN matrix, stored as a single square array, to a rea
XmStringTableToXmString HP-UX A convenience function that converts a compound string table to a single compound string
XmTextGetString Tru64 A Text function that accesses the string value
XmTextFieldGetString IRIX A TextField function that accesses the string value
XmTextGetString HP-UX A Text function that accesses the string value
Copyright © 2004-2005 DeniX Solutions SRL
newsletter delivery service