/[MITgcm]/MITgcm/pkg/flt/flt_init_varia.F
ViewVC logotype

Contents of /MITgcm/pkg/flt/flt_init_varia.F

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph


Revision 1.9 - (show annotations) (download)
Wed Jan 12 19:00:52 2011 UTC (13 years, 3 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint63a, checkpoint63b, checkpoint63, checkpoint62s, checkpoint62r, checkpoint62w, checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62z, checkpoint62y, checkpoint62x
Changes since 1.8: +4 -4 lines
add run-time parameter to avoid initial position conversion to index map
 in tiled flt_file (initial condition).

1 C $Header: /u/gcmpack/MITgcm/pkg/flt/flt_init_varia.F,v 1.8 2010/12/27 19:21:23 jmc Exp $
2 C $Name: $
3
4 #include "FLT_OPTIONS.h"
5
6 SUBROUTINE FLT_INIT_VARIA ( myThid )
7
8 C ==================================================================
9 C SUBROUTINE FLT_INIT_VARIA
10 C ==================================================================
11 C o This routine initializes the start/restart positions.
12 C o Either read initial position from file "flt_file" or
13 C read pickup file. The 2 type of files are similar, except
14 C initial positions are given on grid-coordinate (distance/degree
15 C depending on the grid) whereas in pickup file, positions are
16 C fractional indices along the grid and local to the tile.
17 C For this reason global pickup file is not supported.
18 C Initialisation:
19 C o First it check for global file, and when found, reads the global file
20 C (that has the same format as local files) and sorts those floats
21 C that exist on the specific tile into the local array.
22 C o If no global file is available or in a case of a restart (pickup
23 C file from a previous integration) then read tiled file without
24 C any further check (because they exist on the specific tile).
25 C ==================================================================
26
27 C !USES:
28 IMPLICIT NONE
29
30 #include "SIZE.h"
31 #include "EEPARAMS.h"
32 #include "PARAMS.h"
33 #include "FLT_SIZE.h"
34 #include "FLT.h"
35
36 C == routine arguments ==
37 C myThid - thread number for this instance of the routine.
38 INTEGER myThid
39
40 C == Functions ==
41 INTEGER ILNBLNK
42 EXTERNAL ILNBLNK
43 _RL FLT_MAP_R2K
44 EXTERNAL FLT_MAP_R2K
45
46 C == local variables ==
47 INTEGER bi, bj
48 INTEGER ip, iL
49 INTEGER imax
50 PARAMETER(imax=9)
51 _RL tmp(imax)
52 _RS dummyRS(1)
53 _RL ix, jy, kz
54 _RL iLo, iHi, jLo, jHi
55 INTEGER fp, ioUnit
56 CHARACTER*(MAX_LEN_FNAM) fn
57 CHARACTER*(MAX_LEN_MBUF) msgBuf
58
59 C number of active record in the file (might be lower than the
60 C total number of records because the tile could have contained
61 C more floats at an earlier restart
62 INTEGER npart_read
63 _RL npart_dist
64
65 C == end of interface ==
66
67 C- Tile boundary on index map:
68 iLo = 0.5 _d 0
69 iHi = 0.5 _d 0 + DFLOAT(sNx)
70 jLo = 0.5 _d 0
71 jHi = 0.5 _d 0 + DFLOAT(sNy)
72
73 C- all threads initialise local var:
74 npart_read = 0
75 npart_dist = 0.
76
77 _BEGIN_MASTER(myThid)
78
79 DO bj = 1,nSy
80 DO bi = 1,nSx
81 npart_tile(bi,bj) = 0
82 ENDDO
83 ENDDO
84
85 C read floats initial condition from file
86 IF ( nIter0.EQ.0 ) THEN
87 fn = flt_file
88 fp = readBinaryPrec
89 ELSE
90 WRITE(fn,'(A,I10.10)') 'pickup_flt.', nIter0
91 fp = precFloat64
92 ENDIF
93 iL = ILNBLNK(fn)
94 WRITE(msgBuf,'(2A)')
95 & 'FLT_INIT_VARIA: reading Floats from: ', fn(1:iL)
96 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
97 & SQUEEZE_RIGHT, myThid )
98
99 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
100
101 C-- Initial position: first try to read from a global file.
102 ioUnit = -2
103 bi = 0
104 bj = 0
105 IF ( nIter0.EQ.0 ) THEN
106 C- read actual number of floats from file
107 CALL MDS_READVEC_LOC( fn, fp, ioUnit,
108 & 'RL', imax, tmp, dummyRS,
109 & bi, bj, 1, myThid )
110 ENDIF
111
112 IF ( ioUnit.GT.0 .AND. mapIniPos2Index ) THEN
113 C-- Found a global file
114 WRITE(msgBuf,'(A,2I4,A,1P2E15.8)')
115 & ' bi,bj=', bi, bj, ' , npart,max_npart=', tmp(1), tmp(6)
116 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
117 & SQUEEZE_RIGHT, myThid )
118 npart_read = NINT(tmp(1))
119 max_npart = tmp(6)
120 DO ip=1,npart_read
121 C- read individual float position from file
122 CALL MDS_READVEC_LOC( fn, fp, ioUnit,
123 & 'RL', imax, tmp, dummyRS,
124 & bi, bj, ip+1, myThid )
125 DO bj = 1,nSy
126 DO bi = 1,nSx
127 C- For initial condition only, convert coordinates to index map:
128 CALL FLT_MAP_XY2IJLOCAL( ix, jy,
129 I tmp(3), tmp(4),bi,bj,myThid )
130 kz = FLT_MAP_R2K( tmp(5), bi, bj, myThid )
131 C- Check if float exists on this tile. If not, try next tile
132 IF ( ix.GE.iLo .AND. ix.LT.iHi .AND.
133 & jy.GE.jLo .AND. jy.LT.jHi ) THEN
134 npart_tile(bi,bj) = npart_tile(bi,bj) + 1
135 IF ( npart_tile(bi,bj).LE.max_npart_tile ) THEN
136
137 npart( npart_tile(bi,bj),bi,bj) = tmp(1)
138 tstart(npart_tile(bi,bj),bi,bj) = tmp(2)
139 ipart( npart_tile(bi,bj),bi,bj) = ix
140 jpart( npart_tile(bi,bj),bi,bj) = jy
141 kpart( npart_tile(bi,bj),bi,bj) = kz
142 kfloat(npart_tile(bi,bj),bi,bj) = tmp(6)
143 iup( npart_tile(bi,bj),bi,bj) = tmp(7)
144 itop( npart_tile(bi,bj),bi,bj) = tmp(8)
145 tend( npart_tile(bi,bj),bi,bj) = tmp(9)
146
147 ENDIF
148 ENDIF
149 C- end bi,bj loops
150 ENDDO
151 ENDDO
152
153 ENDDO
154 CLOSE( ioUnit )
155
156 ELSEIF ( ioUnit.GT.0 ) THEN
157 WRITE(msgBuf,'(2A)') 'FLT_INIT_VARIA:',
158 & ' need mapIniPos2Index=T for global file'
159 CALL PRINT_ERROR( msgBuf , myThid)
160 STOP 'ABNORMAL END: S/R FLT_INIT_VARIA'
161
162 ELSE
163 C-- then try to read from a tiled file:
164
165 DO bj = 1,nSy
166 DO bi = 1,nSx
167 ioUnit = -1
168 C- read actual number floats from file
169 CALL MDS_READVEC_LOC( fn, fp, ioUnit,
170 & 'RL', imax, tmp, dummyRS,
171 & bi, bj, 1, myThid )
172 WRITE(msgBuf,'(A,2I4,A,1P2E15.8)')
173 & ' bi,bj=', bi, bj, ' , npart,max_npart=', tmp(1), tmp(6)
174 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
175 & SQUEEZE_RIGHT, myThid )
176
177 npart_tile(bi,bj) = NINT(tmp(1))
178 max_npart = tmp(6)
179 npart_read = MIN( npart_tile(bi,bj), max_npart_tile )
180 DO ip=1,npart_read
181 C- read individual float position from file
182 CALL MDS_READVEC_LOC( fn, fp, ioUnit,
183 & 'RL', imax, tmp, dummyRS,
184 & bi, bj, ip+1, myThid )
185 IF ( nIter0.EQ.0 .AND. mapIniPos2Index ) THEN
186 C-- For initial condition only, convert coordinates to index map:
187 CALL FLT_MAP_XY2IJLOCAL( ix, jy,
188 I tmp(3), tmp(4),bi,bj,myThid )
189 kz = FLT_MAP_R2K( tmp(5), bi, bj, myThid )
190 ELSE
191 ix = tmp(3)
192 jy = tmp(4)
193 kz = tmp(5)
194 ENDIF
195 C not a global file: assume that all particles from this tiled-file
196 C belong to this current tile (=> do not no check)
197 npart(ip,bi,bj) = tmp(1)
198 tstart(ip,bi,bj) = tmp(2)
199 ipart(ip,bi,bj) = ix
200 jpart(ip,bi,bj) = jy
201 kpart(ip,bi,bj) = kz
202 kfloat(ip,bi,bj) = tmp(6)
203 iup( ip,bi,bj) = tmp(7)
204 itop( ip,bi,bj) = tmp(8)
205 tend( ip,bi,bj) = tmp(9)
206 ENDDO
207 CLOSE( ioUnit )
208
209 C- end bi,bj loops
210 ENDDO
211 ENDDO
212 C-- end global-file / tiled-file separated treatment
213 ENDIF
214
215 DO bj = 1,nSy
216 DO bi = 1,nSx
217 npart_dist = npart_dist + DBLE(npart_tile(bi,bj))
218 IF ( npart_tile(bi,bj).GT.max_npart_tile ) THEN
219 WRITE(msgBuf,'(2A,2I4,2(A,I8))') 'FLT_INIT_VARIA:',
220 & ' bi,bj=', bi, bj,
221 & ' npart_tile=', npart_tile(bi,bj),
222 & ' > max_npart_tile=', max_npart_tile
223 CALL PRINT_ERROR( msgBuf , myThid)
224 STOP 'ABNORMAL END: S/R FLT_INIT_VARIA'
225 ENDIF
226 ENDDO
227 ENDDO
228 _END_MASTER( myThid )
229 _BARRIER
230
231 _GLOBAL_SUM_RL( npart_dist, myThid )
232
233 _BEGIN_MASTER( myThid )
234 WRITE(msgBuf,'(A,2(A,I9))') 'FLT_INIT_VARIA:',
235 & ' max npart=', NINT(max_npart),
236 & ' , sum npart_tile=', NINT(npart_dist)
237 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
238 & SQUEEZE_RIGHT, myThid )
239 WRITE(msgBuf,'(A)') ' '
240 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
241 & SQUEEZE_RIGHT, myThid )
242 _END_MASTER( myThid )
243
244 RETURN
245 END

  ViewVC Help
Powered by ViewVC 1.1.22