/[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.6 - (show annotations) (download)
Tue Apr 28 18:15:33 2009 UTC (15 years ago) by jmc
Branch: MAIN
CVS Tags: checkpoint62, checkpoint62c, checkpoint62b, checkpoint62a, checkpoint62g, checkpoint62f, checkpoint62e, checkpoint62d, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62p, checkpoint61n, checkpoint61o, checkpoint61m, checkpoint61v, checkpoint61w, checkpoint61t, checkpoint61u, checkpoint61r, checkpoint61s, checkpoint61p, checkpoint61q, checkpoint61z, checkpoint61x, checkpoint61y
Changes since 1.5: +2 -2 lines
change macros (EXCH & GLOBAL_SUM/MAX) sufix _R4/_R8 to _RS/_RL
 when applied to _RS/_RL variable

1 C $Header: /u/gcmpack/MITgcm/pkg/flt/flt_init_varia.F,v 1.5 2009/02/13 04:23:50 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 It does the following:
13 C o First it checks for local files. These are supposed to be restarts
14 C from a previous integration. The floats can therefore be read in
15 C without any further check (because they exist on the specific tile).
16 C o If no local files are available the routine assumes that this
17 C is an initialization. In that case it reads a global file
18 C (that has the same format as local files) and sorts those floats
19 C that exist on the specific tile into the local array.
20 C o At the end the float positions are written to the trajectory file
21 C ==================================================================
22
23 C !USES:
24 IMPLICIT NONE
25
26 #include "SIZE.h"
27 #include "EEPARAMS.h"
28 #include "PARAMS.h"
29 #include "FLT.h"
30
31 C == routine arguments ==
32 C myThid - thread number for this instance of the routine.
33 INTEGER myThid
34
35 C == Functions ==
36 INTEGER ILNBLNK
37 EXTERNAL ILNBLNK
38 _RL FLT_MAP_R2K
39 EXTERNAL FLT_MAP_R2K
40
41 C == local variables ==
42 INTEGER bi, bj
43 INTEGER ip, iL
44 INTEGER imax
45 PARAMETER(imax=9)
46 _RL tmp(imax)
47 _RL ix, jy, kz
48 _RL iLo, iHi, jLo, jHi
49 LOGICAL globalFile
50 CHARACTER*(MAX_LEN_FNAM) fn
51 CHARACTER*(MAX_LEN_MBUF) msgBuf
52
53 C number of active record in the file (might be lower than the
54 C total number of records because the tile could have contained
55 C more floats at an earlier restart
56 INTEGER npart_read
57 _RL npart_dist
58
59 C == end of interface ==
60
61 C- all threads initialise local var:
62 npart_read = 0
63 npart_dist = 0.
64
65 C read floats initial condition from file
66 _BEGIN_MASTER(myThid)
67 IF ( nIter0.EQ.0 ) THEN
68 fn = flt_file
69 ELSE
70 WRITE(fn,'(A,I10.10)') 'pickup_flt.', nIter0
71 ENDIF
72 iL = ILNBLNK(fn)
73 WRITE(msgBuf,'(2A)')
74 & 'FLT_INIT_VARIA: reading Floats from: ', fn(1:iL)
75 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
76 & SQUEEZE_RIGHT, myThid )
77
78 DO bj = 1,nSy
79 DO bi = 1,nSx
80
81 C tile boundary on index map:
82 iLo = 0.5 _d 0
83 iHi = 0.5 _d 0 + DFLOAT(sNx)
84 jLo = 0.5 _d 0
85 jHi = 0.5 _d 0 + DFLOAT(sNy)
86
87 C (1) read actual number floats from file
88 CALL FLT_MDSREADVECTOR( fn, globalFile, precFloat64, 'RL',
89 & imax, tmp, bi, bj, 1, myThid )
90 WRITE(msgBuf,'(A,2I4,A,1P2E15.8)')
91 & ' bi,bj=', bi, bj, ' , npart,max_npart=', tmp(1), tmp(6)
92 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
93 & SQUEEZE_RIGHT, myThid )
94 npart_read = NINT(tmp(1))
95 max_npart = tmp(6)
96
97 IF (globalFile) THEN
98 npart_tile(bi,bj) = 0
99 ELSE
100 npart_tile(bi,bj) = npart_read
101 npart_read = MIN( npart_read, max_npart_tile )
102 ENDIF
103
104 DO ip=1,npart_read
105
106 CALL FLT_MDSREADVECTOR( fn, globalFile, precFloat64, 'RL',
107 & imax, tmp, bi, bj, ip+1, myThid )
108
109 IF ( nIter0.EQ.0 ) THEN
110 C-- For initial condition only, convert coordinates to index map:
111 CALL FLT_MAP_XY2IJLOCAL( ix, jy,
112 I tmp(3), tmp(4),bi,bj,myThid )
113 kz = FLT_MAP_R2K( tmp(5), bi, bj, myThid )
114 ELSE
115 ix = tmp(3)
116 jy = tmp(4)
117 kz = tmp(5)
118 ENDIF
119
120 IF ( globalFile .AND. nIter0.EQ.0 ) THEN
121 C Check if floats are existing on tile. If not, jump to next float
122
123 IF ( ix.GE.iLo .AND. ix.LT.iHi .AND.
124 & jy.GE.jLo .AND. jy.LT.jHi ) THEN
125 npart_tile(bi,bj) = npart_tile(bi,bj) + 1
126 IF ( npart_tile(bi,bj).LE.max_npart_tile ) THEN
127
128 npart( npart_tile(bi,bj),bi,bj) = tmp(1)
129 tstart(npart_tile(bi,bj),bi,bj) = tmp(2)
130 ipart( npart_tile(bi,bj),bi,bj) = ix
131 jpart( npart_tile(bi,bj),bi,bj) = jy
132 kpart( npart_tile(bi,bj),bi,bj) = kz
133 kfloat(npart_tile(bi,bj),bi,bj) = tmp(6)
134 iup( npart_tile(bi,bj),bi,bj) = tmp(7)
135 itop( npart_tile(bi,bj),bi,bj) = tmp(8)
136 tend( npart_tile(bi,bj),bi,bj) = tmp(9)
137
138 ENDIF
139 ENDIF
140
141 ELSEIF ( globalFile ) THEN
142 WRITE(msgBuf,'(2A)') 'FLT_INIT_VARIA:',
143 & ' global pickup not supported'
144 CALL PRINT_ERROR( msgBuf , myThid)
145 STOP 'ABNORMAL END: S/R FLT_INIT_VARIA'
146
147 ELSE
148 C not a global file: assume that all particles from this tiled-file
149 C belong to this current tile (=> do not no check)
150
151 npart(ip,bi,bj) = tmp(1)
152 tstart(ip,bi,bj) = tmp(2)
153 ipart(ip,bi,bj) = tmp(3)
154 jpart(ip,bi,bj) = tmp(4)
155 kpart(ip,bi,bj) = tmp(5)
156 kfloat(ip,bi,bj) = tmp(6)
157 iup( ip,bi,bj) = tmp(7)
158 itop( ip,bi,bj) = tmp(8)
159 tend( ip,bi,bj) = tmp(9)
160
161 ENDIF
162
163 ENDDO
164
165 npart_dist = npart_dist + DBLE(npart_tile(bi,bj))
166 IF ( npart_tile(bi,bj).GT.max_npart_tile ) THEN
167 WRITE(msgBuf,'(2A,2I4,2(A,I8))') 'FLT_INIT_VARIA:',
168 & ' bi,bj=', bi, bj,
169 & ' npart_tile=', npart_tile(bi,bj),
170 & ' > max_npart_tile=', max_npart_tile
171 CALL PRINT_ERROR( msgBuf , myThid)
172 STOP 'ABNORMAL END: S/R FLT_INIT_VARIA'
173 ENDIF
174
175 ENDDO
176 ENDDO
177 _END_MASTER( myThid )
178 _BARRIER
179
180 _GLOBAL_SUM_RL( npart_dist, myThid )
181
182 _BEGIN_MASTER( myThid )
183 WRITE(msgBuf,'(A,2(A,I9))') 'FLT_INIT_VARIA:',
184 & ' max npart=', NINT(max_npart),
185 & ' , sum npart_tile=', NINT(npart_dist)
186 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
187 & SQUEEZE_RIGHT, myThid )
188 WRITE(msgBuf,'(A)') ' '
189 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
190 & SQUEEZE_RIGHT, myThid )
191 _END_MASTER( myThid )
192
193 RETURN
194 END

  ViewVC Help
Powered by ViewVC 1.1.22