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

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

Contents


PXFDIRECTORY(3F)				      Last changed: 2-24-98

NAME    [Toc]    [Back]

     PXFOPENDIR, PXFREADDIR, PXFREWINDDIR, PXFCLOSEDIR,	- Performs
     directory operations

SYNOPSIS    [Toc]    [Back]

     SUBROUTINE	PXFOPENDIR (dirname, lendirname, iopendirid, ierror)
     CHARACTER*n dirname
     INTEGER lendirname, iopendir, ierror

     SUBROUTINE	PXFREADDIR (idirid, jdirent, ierror)
     INTEGER idirid, jdirent, ierror

     SUBROUTINE	PXFREWINDDIR (idirid, ierror)
     INTEGER idirid, ierror

     SUBROUTINE	PXFCLOSEDIR (idirid, ierror)
     INTEGER idirid, ierror

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 PXFOPENDIR subroutine uses the	opendir(3C) routine to open a
     directory stream for the directory	dirname	and positions the stream at
     the first directory entry.

     The PXFREADDIR subroutine uses the	readdir(3C) function to	read a
     directory stream for the next entry in the	directory stream.

     The PXFREWINDDIR subroutine uses the rewinddir(3C)	function to reset
     the position in the directory stream to the first entry of	a directory
     stream while updating the directory stream	to the current state of	the
     directory,	as a call to PXFOPENDIR	would do.

     The PXFCLOSEDIR subroutine	uses the closedir(3C) function to close	the
     directory stream referenced by idirid. Upon sucessful completion,
     idirid is undefined and the result	of subsequent calls to PXFCLOSEDIR
     with idirid is not	well defined.

     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 these subroutines:

     dirname   An input	character array	variable containing the	path for
	       the directory to	be opened.

     lendirname
	       An input	integer	variable containing the	length of dirname.

     iopendirid
	       An output integer variable for the unique directory ID.

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

     The iopendirid argument becomes the unique	directory ID (idirid) that
     is	used by	PXFREADDIR, PXFREWINDDIR, and PXFCLOSEDIR.

     idirid
	  An input integer variable for	the unique directory ID	generated
	  by PXFOPENDIR.

     jdirent
	  An output structure handle created by	PXFSTRUCTCREATE(3F) that
	  contains one directory entry.

     * The PXFOPENDIR subroutine may return any	of the following error
       values:

     EACCES    If a component of dirname denies	search permission.

     ENAMETOOLONG    [Toc]    [Back]
	       If the length of	the dirname argument exceeds PATH_MAX found
	       in <limits.h> (IRIX systems only).

     ENOENT    If the directory	in the dirname argument	does not exist.

     ENOTDIR   If a component of dirname is not	a directory.

     EINVAL    If lendirname < 0 or lendirname > LEN(dirname).

     ENOMEM    If memory needed	by PXFOPENDIR could not	be allocated.

     EMFILE    If too many file	descriptors are	currently open for the
	       process.

     ENFILE    If too many file	descriptors are	currently open for the
	       system (IRIX systems only).

     * The PXFREADDIR subroutine may return any	of the following error
       values:

     EBADF     If, when	detected, an invalid, unique directory stream ID
	       was used	for idirid.

     EEND      If the end of the directory stream has been reached.

     ENOMEM    If data structures need for successful completion of
	       PXFREADIR cannot	be allocated.

     ENOENT    If the current file pointer for the directory stream is not
	       located at a valid directory entry.

     EDIRCORRUPTED    [Toc]    [Back]
	       If the directory	on disk	is corrupt (IRIX systems only).

     EBADID    If idirid is an invalid directory identifier (UNICOS and
	       UNICOS/mk systems only).

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

     * The PXFCLOSEDIR subroutine may return the following error value:

     EBADF     If, when	detected, an invalid, unique directory stream ID
	       was used	for idirid.

EXAMPLES    [Toc]    [Back]

     In	this example, the /dev/dsk directory is	opened,	the directory
     entries are read and printed, the directory is rewound and	the
     contents are redisplayed, and then	the directory is closed.

	  program pxftest
	  integer ierror
	  integer (KIND=8) jdirent,idirid

	  CALL PXFSTRUCTCREATE('dirent',jdirent,ierror)
	  CALL PXFOPENDIR('/dev/dsk',0,idirid,ierror)
	  call printdir(idirid,jdirent)
	  CALL PXFREWINDDIR(idirid,ierror)
	  call printdir(idirid,jdirent)
	  CALL PXFCLOSEDIR(idirid,ierror)
	  end

	  subroutine printdir(idirid,jdirent)
	  integer ierror, ilen,	EEND
	  integer (KIND=8) jdirent, idirid
	  character*30 name

	  CALL PXFCONST('EEND',EEND,ierror)
	     do	while ((ierror .ne. EEND) .and.	(ierror	.eq. 0))
		CALL PXFREADDIR(idirid,jdirent,ierror)
		CALL PXFSTRGET(jdirent,'d_name',name,ilen,ierror)
		   if (ierror .eq. 0) print *,name
	     enddo
	  end

SEE ALSO    [Toc]    [Back]

      
      
     directory(3C)

     Application Programmer's Library Reference	Manual,	publication
     SR-2165, for the printed version of this man page.
[ Back ]
 Similar pages
Name OS Title
volrecover Tru64 Performs volume recovery operations
volume Tru64 Performs Logical Storage Manager operations on volumes
sem_wait Tru64 Performs (or conditionally performs) a semaphore lock (P1003.1b)
sem_trywait Tru64 Performs (or conditionally performs) a semaphore lock (P1003.1b)
telldir FreeBSD directory operations
opendir OpenBSD directory operations
seekdir FreeBSD directory operations
rewinddir FreeBSD directory operations
readdir OpenBSD directory operations
readdir FreeBSD directory operations
Copyright © 2004-2005 DeniX Solutions SRL
newsletter delivery service