MFIX  2016-1
in_binary_512i_mod.f
Go to the documentation of this file.
1 !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvC
2 ! C
3 ! Module name: IN_BIN_512I C
4 ! Purpose: read an array in chunks of 512 bytes (INTEGER WORDS) C
5 ! C
6 ! Author: P. Nicoletti Date: 02-JAN-92 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: NWORDS, L, NSEG, NREM, LC, N1, N2 C
20 ! C
21 !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^C
22 !
24 
25 CONTAINS
26 
27  SUBROUTINE in_bin_512i(IUNIT, ARRAY, NN, NEXT_REC)
28 !...Translated by Pacific-Sierra Research VAST-90 2.06G5 12:17:31 12/09/98
29 !...Switches: -xf
30 !
31 !-----------------------------------------------
32 ! M o d u l e s
33 !-----------------------------------------------
34  USE machine
35  IMPLICIT NONE
36 !-----------------------------------------------
37 ! D u m m y A r g u m e n t s
38 !-----------------------------------------------
39 !
40 ! array to write out
41  INTEGER ARRAY(*)
42 !
43 ! output unit number
44  INTEGER IUNIT
45 !
46 ! number of elements in ARRAY
47  INTEGER NN
48 !
49 ! next record number in direct access output file
50  INTEGER NEXT_REC
51 !
52 ! local variables
53 !
54 ! number of words for 512 bytes (nwords * 4 = 512)
55  INTEGER NWORDS
56 !
57 ! loop counter
58  INTEGER L
59 !
60 ! number of full 512 byte segments need to write N
61 ! double precision words
62  INTEGER NSEG
63 !
64 ! number of double precision words in the partially
65 ! filled last record
66  INTEGER NREM
67 !
68 ! loop counter
69  INTEGER LC
70 !
71 ! write out array elements N1 to N2
72  INTEGER N1 , N2
73 !-----------------------------------------------
74 !
75  nwords = nwords_i
76  IF (nn <= nwords) THEN
77  READ (iunit, rec=next_rec) (array(l),l=1,nn)
78  next_rec = next_rec + 1
79  RETURN
80  ENDIF
81 
82  nseg = nn/nwords
83  nrem = mod(nn,nwords)
84  n1 = 1
85  n2 = nwords
86 !
87 ! read the full 512 byte segments
88 !
89  DO lc = 1, nseg
90  READ (iunit, rec=next_rec) (array(l),l=n1,n2)
91  n1 = n1 + nwords
92  n2 = n2 + nwords
93  next_rec = next_rec + 1
94  END DO
95  IF (nrem /= 0) THEN
96  READ (iunit, rec=next_rec) (array(l),l=n1,nn)
97  next_rec = next_rec + 1
98  ENDIF
99 
100  RETURN
101  END SUBROUTINE in_bin_512i
102 
103  subroutine convert_from_io_i(arr_io,arr_internal,nn)
105  use geometry
106  use indices
107  use compar
108  use functions
109 
110  implicit none
111 
112  integer, intent(in) :: arr_io(:)
113  integer, intent(out) :: arr_internal(:)
114  integer nn,i,j,k,ijk,ijk_io
115 
116 ! write(*,*) 'C0:',C0
117 ! write(*,*) 'C1:',C1
118 ! write(*,*) 'C2:',C2
119 
120 ! write(*,*) 'io:',size(arr_io)
121 ! write(*,*) 'int:',size(arr_internal)
122 
123  if(size(arr_io) == size(arr_internal)) then
124  arr_internal = arr_io
125  else
126  do k = 1,kmax2
127  do j = 1,jmax2
128  do i = 1,imax2
129  ijk = funijk_gl(i,j,k)
130  ijk_io = funijk_io(i,j,k)
131  arr_internal(ijk) = arr_io(ijk_io)
132  write(*,*)i,j,k,ijk, ijk_io
133  end do
134  end do
135  end do
136  endif
137 
138  return
139  end subroutine convert_from_io_i
140 
141  subroutine convert_to_io_i(arr_internal,arr_io,nn)
143  use geometry
144  use indices
145  use compar
146  use functions
147 
148  implicit none
149 
150  integer arr_io(*) , arr_internal(*)
151  integer nn,i,j,k,ijk,ijk_io
152 
153  do k = 1,kmax2
154  do j = 1,jmax2
155  do i = 1,imax2
156  ijk = funijk_gl(i,j,k)
157  ijk_io = funijk_io(i,j,k)
158  arr_io(ijk_io) = arr_internal(ijk)
159  end do
160  end do
161  end do
162 
163  return
164  end subroutine convert_to_io_i
165 
166  subroutine convert_to_io_c(arr_internal,arr_io,nn)
168  use geometry
169  use indices
170  use compar
171  use functions
172 
173  implicit none
174 
175  character(LEN=4) arr_io(*) , arr_internal(*)
176  integer nn,i,j,k,ijk,ijk_io
177 
178  do k = 1,kmax2
179  do j = 1,jmax2
180  do i = 1,imax2
181  ijk = funijk_gl(i,j,k)
182  ijk_io = funijk_io(i,j,k)
183  arr_io(ijk_io) = arr_internal(ijk)
184  end do
185  end do
186  end do
187 !
188  return
189  end subroutine convert_to_io_c
190 
191 END MODULE in_binary_512i
192 
193 !// Comments on the modifications for DMP version implementation
194 !// 001 Include header file and common declarations for parallelization
subroutine convert_from_io_i(arr_io, arr_internal, nn)
integer imax2
Definition: geometry_mod.f:61
subroutine convert_to_io_i(arr_internal, arr_io, nn)
integer jmax2
Definition: geometry_mod.f:63
integer nwords_i
Definition: machine_mod.f:14
integer kmax2
Definition: geometry_mod.f:65
subroutine convert_to_io_c(arr_internal, arr_io, nn)
subroutine in_bin_512i(IUNIT, ARRAY, NN, NEXT_REC)