MFIX  2016-1
open_file.f
Go to the documentation of this file.
1 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvC
2 ! C
3 ! Module name: OPEN_FILE C
4 ! Purpose: open a file C
5 ! C
6 ! Author: P. Nicoletti Date: 12-DEC-91 C
7 ! Reviewer: P. Nicoletti, W. Rogers, M. Syamlal Date: 24-JAN-92 C
8 ! C
9 ! Revision Number: C
10 ! Purpose: C
11 ! Author: Date: dd-mmm-yy C
12 ! Reviewer: Date: dd-mmm-yy C
13 ! C
14 ! Literature/Document References: C
15 ! C
16 ! Variables referenced: C
17 ! Variables modified: C
18 ! C
19 ! Local variables: C
20 ! C
21 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^C
22  SUBROUTINE open_file(FILENAME, NB, IUNIT, EXT, FULL_NAME, &
23  open_stat, open_access, open_form, irecl, ier)
24 
25  use cdist
26  use compar
27 
28  IMPLICIT NONE
29 
30 ! Dummy Arguments
31 !---------------------------------------------------------------------//
32 ! FILENAME (without extension)
33  CHARACTER(LEN=*), INTENT(IN) :: FILENAME
34 ! File extension.
35  CHARACTER(LEN=*), INTENT(IN) :: EXT
36 ! FILENAME + EXTENSION
37  CHARACTER(LEN=*), INTENT(INOUT) :: FULL_NAME
38 ! File status (NEW, OLD, UNKNOWN)
39  CHARACTER(LEN=*), INTENT(IN) :: OPEN_STAT
40 ! File access method ('SEQUENTIAL', 'DIRECT')
41  CHARACTER(LEN=*), INTENT(IN) :: OPEN_ACCESS
42 ! Open form ('FORMATTED' or 'UNFORMATTED')
43  CHARACTER(LEN=*) OPEN_FORM
44 ! Index to first blank character in FILENAME
45  INTEGER, INTENT(IN) :: NB
46 ! Unit number to open
47  INTEGER, INTENT(IN) :: IUNIT
48 ! Record length
49  INTEGER, INTENT(IN) :: IRECL
50 ! Integer Error index:
51 ! 000 - no error
52 ! 100 - NEW run with existing files in directory
53 ! 101 - OLD run missing RES and/or SPx files
54 ! 102 - Unknown OPEN_STAT
55  INTEGER, INTENT(OUT) :: IER
56 
57 ! Local Variables
58 !---------------------------------------------------------------------//
59 ! Logical used to store result of file INQUIRE
60  LOGICAL :: FILE_EXISTS
61 
62 ! Logicals that determine if files should be index.
63  LOGICAL :: RES_IDX ! Index RES files
64  LOGICAL :: SPX_IDX ! Index SPx files
65  LOGICAL :: USE_IDX ! Use the IDX value
66 
67 ! Initialize the error flag.
68  ier = 0
69 
70 ! Conditions for indexing the RES files for distributed IO.
71  res_idx = (mype .NE. pe_io) .OR. (.NOT.bstart_with_one_res)
72 ! Conditions for indexing the SPX files for distributed IO.
73  spx_idx = .true.
74 
75 ! Flag for indexing files.
76  use_idx = bdist_io .AND. ( &
77  (spx_idx .AND. (ext(2:3) .EQ. 'SP')) .OR. &
78  (res_idx .AND. (ext(2:4) .EQ. 'RES')))
79 
80 ! Construct the file name.
81  full_name = ''
82  IF(use_idx)THEN
83  WRITE(full_name,1000) filename(1:nb-1), mype, ext(1:4)
84  ELSE
85  WRITE(full_name,1001) filename(1:nb-1), ext(1:4)
86  ENDIF
87 
88 ! Check to see if the file already exists in the run directory.
89  INQUIRE(file=trim(full_name),exist=file_exists)
90 
91 ! NEW files should not be in the run directory.
92  IF(file_exists .AND. (open_stat == 'NEW')) THEN
93  ier = 100; RETURN
94 ! OLD files must be in the run directory.
95  ELSEIF(.NOT. file_exists .AND. open_stat .EQ. 'OLD') THEN
96  ier = 101; RETURN
97  ENDIF
98 
99 ! Open direct access files.
100  IF (open_access == 'DIRECT') THEN
101  OPEN(convert='BIG_ENDIAN',unit=iunit, file=trim(full_name), status=open_stat, &
102  recl=irecl, access=open_access, form=open_form, iostat=ier)
103  ELSE
104 ! No matter the status passed to the routine, the file is created as
105 ! NEW if it doesn't exist in the run directory.
106  IF(.NOT.file_exists) THEN
107  OPEN(convert='BIG_ENDIAN',unit=iunit, file=trim(full_name), status='NEW', &
108  access=open_access, form=open_form, iostat=ier)
109  ELSEIF(open_stat == 'REPLACE') THEN
110  OPEN(convert='BIG_ENDIAN',unit=iunit, file=trim(full_name), status=open_stat, &
111  access=open_access, form=open_form, iostat=ier)
112  ELSEIF(open_stat == 'APPEND' .OR. open_stat == 'UNKNOWN') THEN
113  OPEN(convert='BIG_ENDIAN',unit=iunit, file=trim(full_name), status='UNKNOWN', &
114  access=open_access, form=open_form, position='APPEND', &
115  iostat=ier)
116  ELSE
117  ier = 102
118  ENDIF
119  ENDIF
120 
121  RETURN
122 
123  1000 FORMAT(a,'_',i5.5,a4)
124  1001 FORMAT(a,a4)
125 
126  END SUBROUTINE open_file
logical bdist_io
Definition: cdist_mod.f:4
logical bstart_with_one_res
Definition: cdist_mod.f:5
integer pe_io
Definition: compar_mod.f:30
subroutine open_file(FILENAME, NB, IUNIT, EXT, FULL_NAME, OPEN_STAT, OPEN_ACCESS, OPEN_FORM, IRECL, IER)
Definition: open_file.f:24
Definition: cdist_mod.f:2
integer mype
Definition: compar_mod.f:24