/[MITgcm]/MITgcm/pkg/mnc/mnc_cw_readwrite.template
ViewVC logotype

Contents of /MITgcm/pkg/mnc/mnc_cw_readwrite.template

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


Revision 1.8 - (show annotations) (download)
Wed Mar 10 05:50:16 2004 UTC (20 years, 2 months ago) by edhill
Branch: MAIN
CVS Tags: checkpoint52l_pre, checkpoint52l_post
Changes since 1.7: +26 -21 lines
 o fix bug: too many files open
 o add some testing code for pickups

1 C $Header: /u/u3/gcmpack/MITgcm/pkg/mnc/mnc_cw_readwrite.template,v 1.7 2004/03/09 14:43:16 edhill Exp $
2 C $Name: $
3
4 #include "MNC_OPTIONS.h"
5
6 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
7
8 SUBROUTINE MNC_CW_RX_W_YY(
9 I myThid,
10 I fbname, bi,bj,
11 I vtype,
12 I indu,
13 I var )
14
15 implicit none
16
17 #include "netcdf.inc"
18 #include "mnc_common.h"
19 #include "EEPARAMS.h"
20 #include "SIZE.h"
21
22 #define mnc_rtype_YY
23
24 C Arguments
25 integer myThid, bi,bj, indu
26 character*(*) fbname, vtype
27 __V var(*)
28
29 C Functions
30 integer IFNBLNK, ILNBLNK
31
32 C Local Variables
33 integer i,j,k, indv,nvf,nvl, n1,n2, igrid, ntot
34 integer bis,bie, bjs,bje, uniq_tnum, nfname, fid, idv, indvids
35 integer ndim, indf, err, lbi,lbj, bidim,bjdim, unlim_sz, kr
36 integer p(9),s(9),e(9), dimnc(9), vstart(9),vcount(9), udo(9)
37 integer j1,j2,j3,j4,j5,j6,j7, k1,k2,k3,k4,k5,k6,k7
38 character*(MAX_LEN_MBUF) msgbuf
39 character*(MNC_MAX_CHAR) fname
40
41 C Temporary storage for the simultaneous type conversion and
42 C re-shaping before passing to NetCDF
43 #ifdef mnc_rtype_D
44 REAL*8 resh( sNx + 2*OLx + sNy + 2*OLy )
45 #endif
46 #ifdef mnc_rtype_R
47 REAL*4 resh( sNx + 2*OLx + sNy + 2*OLy )
48 #endif
49 #ifdef mnc_rtype_I
50 INTEGER resh( sNx + 2*OLx + sNy + 2*OLy )
51 #endif
52
53 C Only do I/O if I am the master thread
54 _BEGIN_MASTER( myThid )
55
56 C Check that the Variable Type exists
57 nvf = IFNBLNK(vtype)
58 nvl = ILNBLNK(vtype)
59 CALL MNC_GET_IND(myThid, MNC_MAX_ID, vtype, mnc_cw_vname, indv)
60 IF (indv .LT. 1) THEN
61 write(msgbuf,'(3a)') 'MNC_CW_RX_W_YY ERROR: vtype ''',
62 & vtype(nvf:nvl), ''' is not defined'
63 CALL print_error(msgbuf, mythid)
64 STOP 'ABNORMAL END: S/R MNC_CW_RX_W_YY'
65 ENDIF
66 igrid = mnc_cw_vgind(indv)
67
68 C Set the bi,bj indicies
69 bis = bi
70 bie = bi
71 IF (bi .LT. 1) THEN
72 bis = 1
73 bie = nSx
74 ENDIF
75 bjs = bj
76 bje = bj
77 IF (bj .LT. 1) THEN
78 bjs = 1
79 bje = nSy
80 ENDIF
81
82 DO lbj = bjs,bje
83 DO lbi = bis,bie
84
85 C Create the file name
86 CALL MNC_CW_GET_TILE_NUM(myThid, lbi,lbj, uniq_tnum)
87 fname(1:MNC_MAX_CHAR) = mnc_blank_name(1:MNC_MAX_CHAR)
88 n1 = IFNBLNK(fbname)
89 n2 = ILNBLNK(fbname)
90 ntot = n2 - n1 + 1
91 fname(1:ntot) = fbname(n1:n2)
92 ntot = ntot + 1
93 fname(ntot:ntot) = '.'
94 write(fname((ntot+1):(ntot+9)),'(i6.6,a3)') uniq_tnum, '.nc'
95 nfname = ntot+9
96
97 C Append to an existing or create a new file
98 CALL MNC_CW_FILE_AORC(myThid, fname, indf)
99 fid = mnc_f_info(indf,2)
100
101 C Ensure that all the NetCDF dimensions are defined and create a
102 C local copy of them
103 DO i = 1,9
104 dimnc(i) = 1
105 ENDDO
106 DO i = 1,mnc_cw_ndim(igrid)
107 IF (mnc_cw_dims(i,igrid) .EQ. -1) THEN
108 dimnc(i) = -1
109 ELSE
110 dimnc(i) = mnc_cw_ie(i,igrid) - mnc_cw_is(i,igrid) + 1
111 ENDIF
112 CALL MNC_DIM_INIT(myThid,fname,
113 & mnc_cw_dn(i,igrid), dimnc(i) )
114 ENDDO
115
116 C Ensure that the "grid" is defined
117 CALL MNC_GRID_INIT(myThid,fname, mnc_cw_gname(igrid),
118 & mnc_cw_ndim(igrid), mnc_cw_dn(1,igrid))
119
120 C Ensure that the variable is defined
121 #ifdef mnc_rtype_D
122 CALL MNC_VAR_INIT_DBL(myThid,fname,mnc_cw_gname(igrid),vtype)
123 #endif
124 #ifdef mnc_rtype_R
125 CALL MNC_VAR_INIT_REAL(myThid,fname,mnc_cw_gname(igrid),vtype)
126 #endif
127 #ifdef mnc_rtype_I
128 CALL MNC_VAR_INIT_INT(myThid,fname,mnc_cw_gname(igrid),vtype)
129 #endif
130 DO i = 1,mnc_fv_ids(indf,1)
131 j = 2 + 3*(i - 1)
132 IF (mnc_v_names(mnc_fv_ids(indf,j)) .EQ. vtype) THEN
133 idv = mnc_fv_ids(indf,j+1)
134 indvids = mnc_fd_ind(indf, mnc_f_info(indf,
135 & (mnc_fv_ids(indf,j+2) + 1)) )
136 GOTO 10
137 ENDIF
138 ENDDO
139 write(msgbuf,'(4a)') 'MNC_MNC_CW_RX_W_YY ERROR: ',
140 & 'cannot reference variable ''', vtype, ''''
141 CALL print_error(msgbuf, mythid)
142 STOP 'ABNORMAL END: package MNC'
143 10 CONTINUE
144
145 C Check for bi,bj indicies
146 bidim = mnc_cw_vbij(1,indv)
147 bjdim = mnc_cw_vbij(2,indv)
148 CEH3 write(*,*) 'bidim,bjdim = ', bidim,bjdim
149
150 C Set the dimensions for the in-memory array
151 ndim = mnc_cw_ndim(igrid)
152 k = mnc_cw_dims(1,igrid)
153 IF (k .GT. 0) THEN
154 p(1) = k
155 ELSE
156 p(1) = 1
157 ENDIF
158 DO i = 2,9
159 k = mnc_cw_dims(i,igrid)
160 IF (k .LT. 1) THEN
161 k = 1
162 ENDIF
163 IF ((bidim .GT. 0) .AND. (i .EQ. bidim)) THEN
164 p(i) = nSx * p(i-1)
165 ELSEIF ((bjdim .GT. 0) .AND. (i .EQ. bjdim)) THEN
166 p(i) = nSy * p(i-1)
167 ELSE
168 p(i) = k * p(i-1)
169 ENDIF
170 ENDDO
171
172 C Set starting and ending indicies for the in-memory array and
173 C the unlimited dimension offset for the NetCDF array
174 DO i = 1,9
175 udo(i) = 0
176 s(i) = 1
177 e(i) = 1
178 IF (i .LE. ndim) THEN
179 s(i) = mnc_cw_is(i,igrid)
180 e(i) = mnc_cw_ie(i,igrid)
181 ENDIF
182 C Check for the unlimited dimension
183 IF ((i .EQ. ndim)
184 & .AND. (mnc_cw_dims(i,igrid) .EQ. -1)) THEN
185 IF (indu .GT. 0) THEN
186 C Use the indu value
187 udo(i) = indu - 1
188 ELSEIF (indu .EQ. -1) THEN
189 C Append one to the current unlimited dim size
190 CALL MNC_DIM_UNLIM_SIZE(myThid, fname, unlim_sz)
191 udo(i) = unlim_sz
192 ELSE
193 C Use the current unlimited dim size
194 CALL MNC_DIM_UNLIM_SIZE(myThid, fname, unlim_sz)
195 udo(i) = unlim_sz - 1
196 ENDIF
197 ENDIF
198 ENDDO
199 IF (bidim .GT. 0) THEN
200 s(bidim) = lbi
201 e(bidim) = lbi
202 ENDIF
203 IF (bjdim .GT. 0) THEN
204 s(bjdim) = lbj
205 e(bjdim) = lbj
206 ENDIF
207 CEH3 DO i = 1,9
208 CEH3 write(*,*) 'i,p(i),s(i),e(i) = ', i,p(i),s(i),e(i)
209 CEH3 ENDDO
210
211 C Add the global attributes
212 CALL MNC_CW_SET_GATTR(myThid, fname, lbi,lbj, uniq_tnum)
213
214 C Add the per-variable attributes
215 DO i = 1,mnc_cw_vnat(1,indv)
216 CALL MNC_VAR_ADD_ATTR_STR(myThid, fname, vtype,
217 & mnc_cw_vtnm(i,indv), mnc_cw_vtat(i,indv))
218 ENDDO
219 DO i = 1,mnc_cw_vnat(2,indv)
220 CALL MNC_VAR_ADD_ATTR_INT(myThid, fname, vtype,
221 & mnc_cw_vinm(i,indv), 1, mnc_cw_viat(i,indv))
222 ENDDO
223 DO i = 1,mnc_cw_vnat(3,indv)
224 CALL MNC_VAR_ADD_ATTR_DBL(myThid, fname, vtype,
225 & mnc_cw_vdnm(i,indv), 1, mnc_cw_vdat(i,indv))
226 ENDDO
227
228 CALL MNC_FILE_ENDDEF(myThid,fname)
229
230 write(msgbuf,'(5a)') 'writing variable type ''',
231 & vtype(nvf:nvl), ''' within file ''',
232 & fname(1:nfname), ''''
233
234 C Write the variable one vector at a time
235 DO j7 = s(7),e(7)
236 k7 = (j7 - 1)*p(6)
237 vstart(7) = udo(7) + j7 - s(7) + 1
238 vcount(7) = 1
239 DO j6 = s(6),e(6)
240 k6 = (j6 - 1)*p(5) + k7
241 vstart(6) = udo(6) + j6 - s(6) + 1
242 vcount(6) = 1
243 DO j5 = s(5),e(5)
244 k5 = (j5 - 1)*p(4) + k6
245 vstart(5) = udo(5) + j5 - s(5) + 1
246 vcount(5) = 1
247 DO j4 = s(4),e(4)
248 k4 = (j4 - 1)*p(3) + k5
249 vstart(4) = udo(4) + j4 - s(4) + 1
250 vcount(4) = 1
251 DO j3 = s(3),e(3)
252 k3 = (j3 - 1)*p(2) + k4
253 vstart(3) = udo(3) + j3 - s(3) + 1
254 vcount(3) = 1
255 DO j2 = s(2),e(2)
256 k2 = (j2 - 1)*p(1) + k3
257 vstart(2) = udo(2) + j2 - s(2) + 1
258 vcount(2) = 1
259
260 kr = 0
261 DO j1 = s(1),e(1)
262 k1 = k2 + j1
263 kr = kr + 1
264 resh(kr) = var(k1)
265 ENDDO
266
267 vstart(1) = udo(1) + 1
268 vcount(1) = e(1) - s(1) + 1
269
270 #ifdef mnc_rtype_D
271 err = NF_PUT_VARA_DOUBLE(fid, idv, vstart, vcount, resh)
272 #endif
273 #ifdef mnc_rtype_R
274 err = NF_PUT_VARA_REAL(fid, idv, vstart, vcount, resh)
275 #endif
276 #ifdef mnc_rtype_I
277 err = NF_PUT_VARA_INT(fid, idv, vstart, vcount, resh)
278 #endif
279
280 CALL MNC_HANDLE_ERR(myThid, err, msgbuf)
281
282 ENDDO
283 ENDDO
284 ENDDO
285 ENDDO
286 ENDDO
287 ENDDO
288
289 C Sync the file
290 err = NF_SYNC(fid)
291 write(msgbuf,'(3a)') 'sync for file ''', fname,
292 & ''' in S/R MNC_CW_RX_W_YY'
293 CALL MNC_HANDLE_ERR(myThid, err, msgbuf)
294
295 ENDDO
296 ENDDO
297
298 _END_MASTER( myThid )
299
300 RETURN
301 END
302
303
304 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
305
306
307 SUBROUTINE MNC_CW_RX_R_YY(
308 I myThid,
309 I fbname, bi,bj,
310 I vtype,
311 I indu,
312 I var )
313
314 implicit none
315
316 #include "netcdf.inc"
317 #include "mnc_common.h"
318 #include "EEPARAMS.h"
319 #include "SIZE.h"
320
321 #define mnc_rtype_YY
322
323 C Arguments
324 integer myThid, bi,bj, indu
325 character*(*) fbname, vtype
326 __V var(*)
327
328 C Functions
329 integer IFNBLNK, ILNBLNK
330
331 C Local Variables
332 integer i,k, nvf,nvl, n1,n2, igrid, ntot
333 integer bis,bie, bjs,bje, uniq_tnum, nfname, fid, idv
334 integer ndim, indf, err, lbi,lbj, bidim,bjdim, unlim_sz, kr
335 integer ind_fv_ids, ind_vt, ierr, atype, alen
336 integer f_sNx,f_sNy, ires
337 integer p(9),s(9),e(9), vstart(9),vcount(9), udo(9)
338 integer j1,j2,j3,j4,j5,j6,j7, k1,k2,k3,k4,k5,k6,k7
339 character*(MAX_LEN_MBUF) msgbuf
340 character*(MNC_MAX_CHAR) fname
341
342 C Temporary storage for the simultaneous type conversion and
343 C re-shaping before passing to NetCDF
344 #ifdef mnc_rtype_D
345 REAL*8 resh( sNx + 2*OLx + sNy + 2*OLy )
346 #endif
347 #ifdef mnc_rtype_R
348 REAL*4 resh( sNx + 2*OLx + sNy + 2*OLy )
349 #endif
350 #ifdef mnc_rtype_I
351 INTEGER resh( sNx + 2*OLx + sNy + 2*OLy )
352 #endif
353
354 C Only do I/O if I am the master thread
355 _BEGIN_MASTER( myThid )
356
357 C Check that the Variable Type exists
358 nvf = IFNBLNK(vtype)
359 nvl = ILNBLNK(vtype)
360 CALL MNC_GET_IND(myThid, MNC_MAX_ID, vtype, mnc_cw_vname, ind_vt)
361 IF (ind_vt .LT. 1) THEN
362 write(msgbuf,'(3a)') 'MNC_CW_RX_R_YY ERROR: vtype ''',
363 & vtype(nvf:nvl), ''' is not defined'
364 CALL print_error(msgbuf, mythid)
365 STOP 'ABNORMAL END: S/R MNC_CW_RX_R_YY'
366 ENDIF
367 igrid = mnc_cw_vgind(ind_vt)
368
369 C Check for bi,bj indicies
370 bidim = mnc_cw_vbij(1,ind_vt)
371 bjdim = mnc_cw_vbij(2,ind_vt)
372
373 C Set the bi,bj indicies
374 bis = bi
375 bie = bi
376 IF (bi .LT. 1) THEN
377 bis = 1
378 bie = nSx
379 ENDIF
380 bjs = bj
381 bje = bj
382 IF (bj .LT. 1) THEN
383 bjs = 1
384 bje = nSy
385 ENDIF
386
387 DO lbj = bjs,bje
388 DO lbi = bis,bie
389
390 C Create the file name
391 CALL MNC_CW_GET_TILE_NUM(myThid, lbi,lbj, uniq_tnum)
392 fname(1:MNC_MAX_CHAR) = mnc_blank_name(1:MNC_MAX_CHAR)
393 n1 = IFNBLNK(fbname)
394 n2 = ILNBLNK(fbname)
395 ntot = n2 - n1 + 1
396 fname(1:ntot) = fbname(n1:n2)
397 ntot = ntot + 1
398 fname(ntot:ntot) = '.'
399 write(fname((ntot+1):(ntot+9)),'(i6.6,a3)') uniq_tnum, '.nc'
400 nfname = ntot+9
401
402 C Open the existing file
403 CALL MNC_FILE_TRY_READ(myThid, fname, ierr, indf)
404
405 C Check that the variable (VType) is defined within the file
406 CALL MNC_GET_FVINDS(myThid, fname, vtype, indf, ind_fv_ids)
407 IF ((indf .LT. 1) .OR. (ind_fv_ids .LT. 1)) THEN
408 write(msgbuf,'(4a)') 'MNC_CW_RX_R_YY ERROR: vtype ''',
409 & vtype(nvf:nvl), ''' is not defined within file ''',
410 & fname(1:nfname)
411 CALL print_error(msgbuf, mythid)
412 STOP 'ABNORMAL END: S/R MNC_CW_RX_R_YY'
413 ENDIF
414 fid = mnc_f_info(indf,2)
415 idv = mnc_fv_ids(indf,ind_fv_ids+1)
416
417 C Check that the current sNy,sNy values and the in-file values
418 C are compatible and WARN (only warn) if not
419 f_sNx = -1
420 f_sNy = -1
421 err = NF_INQ_ATT(fid,NF_GLOBAL, 'sNx',atype,alen)
422 IF ((err .EQ. NF_NOERR) .AND. (alen .EQ. 1)) THEN
423 err = NF_GET_ATT_INT(fid, NF_GLOBAL, 'sNx', f_sNx)
424 CALL MNC_HANDLE_ERR(myThid, err,
425 & 'reading attribute ''sNx'' in S/R MNC_CW_RX_R_YY')
426 ENDIF
427 err = NF_INQ_ATT(fid,NF_GLOBAL, 'sNy',atype,alen)
428 IF ((err .EQ. NF_NOERR) .AND. (alen .EQ. 1)) THEN
429 err = NF_GET_ATT_INT(fid, NF_GLOBAL, 'sNy', f_sNy)
430 CALL MNC_HANDLE_ERR(myThid, err,
431 & 'reading attribute ''sNy'' in S/R MNC_CW_RX_R_YY')
432 ENDIF
433 IF ((f_sNx .NE. sNx) .OR. (f_sNy .NE. sNy)) THEN
434 write(msgbuf,'(5a)') 'MNC_CW_RX_R_YY WARNING: the ',
435 & 'attributes ''sNx'' and ''sNy'' within the file ''',
436 & fname(1:nfname), ''' do not exist or do not match ',
437 & 'the current sizes within the model'
438 CALL print_error(msgbuf, mythid)
439 ENDIF
440
441 C Check that the in-memory variable and the in-file variables
442 C are of compatible sizes
443 C ires = 1
444 C CALL MNC_CHK_VTYP_R_NCVAR(myThid, ind_vt,
445 C & indf, ind_fv_ids, indu, ires)
446 C IF (ires .LT. 0) THEN
447 C write(msgbuf,'(7a)') 'MNC_CW_RX_R_YY WARNING: the sizes ',
448 C & 'of the in-program variable ''', vtype(nvf:nvl),
449 C & ''' and the corresponding variable within file ''',
450 C & fname(1:nfname), ''' are not compatible -- please ',
451 C & 'check the sizes'
452 C CALL print_error(msgbuf, mythid)
453 C STOP 'ABNORMAL END: S/R MNC_CW_RX_R_YY'
454 C ENDIF
455
456 C Check for bi,bj indicies
457 bidim = mnc_cw_vbij(1,ind_vt)
458 bjdim = mnc_cw_vbij(2,ind_vt)
459
460 C Set the dimensions for the in-memory array
461 ndim = mnc_cw_ndim(igrid)
462 k = mnc_cw_dims(1,igrid)
463 IF (k .GT. 0) THEN
464 p(1) = k
465 ELSE
466 p(1) = 1
467 ENDIF
468 DO i = 2,9
469 k = mnc_cw_dims(i,igrid)
470 IF (k .LT. 1) THEN
471 k = 1
472 ENDIF
473 IF ((bidim .GT. 0) .AND. (i .EQ. bidim)) THEN
474 p(i) = nSx * p(i-1)
475 ELSEIF ((bjdim .GT. 0) .AND. (i .EQ. bjdim)) THEN
476 p(i) = nSy * p(i-1)
477 ELSE
478 p(i) = k * p(i-1)
479 ENDIF
480 ENDDO
481
482 C Set starting and ending indicies for the in-memory array and
483 C the unlimited dimension offset for the NetCDF array
484 DO i = 1,9
485 udo(i) = 0
486 s(i) = 1
487 e(i) = 1
488 IF (i .LE. ndim) THEN
489 s(i) = mnc_cw_is(i,igrid)
490 e(i) = mnc_cw_ie(i,igrid)
491 ENDIF
492 C Check for the unlimited dimension
493 IF ((i .EQ. ndim)
494 & .AND. (mnc_cw_dims(i,igrid) .EQ. -1)) THEN
495 IF (indu .GT. 0) THEN
496 C Use the indu value
497 udo(i) = indu - 1
498 ELSEIF (indu .EQ. -1) THEN
499 C Append one to the current unlimited dim size
500 CALL MNC_DIM_UNLIM_SIZE(myThid, fname, unlim_sz)
501 udo(i) = unlim_sz
502 ELSE
503 C Use the current unlimited dim size
504 CALL MNC_DIM_UNLIM_SIZE(myThid, fname, unlim_sz)
505 udo(i) = unlim_sz - 1
506 ENDIF
507 ENDIF
508 ENDDO
509 IF (bidim .GT. 0) THEN
510 s(bidim) = lbi
511 e(bidim) = lbi
512 ENDIF
513 IF (bjdim .GT. 0) THEN
514 s(bjdim) = lbj
515 e(bjdim) = lbj
516 ENDIF
517
518 C DO i = 9,1,-1
519 C write(*,*) 'i,p(i),s(i),e(i) = ', i,': ',p(i),s(i),e(i)
520 C ENDDO
521
522 CALL MNC_FILE_ENDDEF(myThid,fname)
523
524 write(msgbuf,'(5a)') 'reading variable type ''',
525 & vtype(nvf:nvl), ''' within file ''',
526 & fname(1:nfname), ''''
527
528 C Read the variable one vector at a time
529 DO j7 = s(7),e(7)
530 k7 = (j7 - 1)*p(6)
531 vstart(7) = udo(7) + j7 - s(7) + 1
532 vcount(7) = 1
533 DO j6 = s(6),e(6)
534 k6 = (j6 - 1)*p(5) + k7
535 vstart(6) = udo(6) + j6 - s(6) + 1
536 vcount(6) = 1
537 DO j5 = s(5),e(5)
538 k5 = (j5 - 1)*p(4) + k6
539 vstart(5) = udo(5) + j5 - s(5) + 1
540 vcount(5) = 1
541 DO j4 = s(4),e(4)
542 k4 = (j4 - 1)*p(3) + k5
543 vstart(4) = udo(4) + j4 - s(4) + 1
544 vcount(4) = 1
545 DO j3 = s(3),e(3)
546 k3 = (j3 - 1)*p(2) + k4
547 vstart(3) = udo(3) + j3 - s(3) + 1
548 vcount(3) = 1
549 DO j2 = s(2),e(2)
550 k2 = (j2 - 1)*p(1) + k3
551 vstart(2) = udo(2) + j2 - s(2) + 1
552 vcount(2) = 1
553
554 vstart(1) = udo(1) + 1
555 vcount(1) = e(1) - s(1) + 1
556
557 #ifdef mnc_rtype_D
558 err = NF_GET_VARA_DOUBLE(fid, idv, vstart, vcount, resh)
559 #endif
560 #ifdef mnc_rtype_R
561 err = NF_GET_VARA_REAL(fid, idv, vstart, vcount, resh)
562 #endif
563 #ifdef mnc_rtype_I
564 err = NF_GET_VARA_INT(fid, idv, vstart, vcount, resh)
565 #endif
566
567 CALL MNC_HANDLE_ERR(myThid, err, msgbuf)
568
569 kr = 0
570 DO j1 = s(1),e(1)
571 k1 = k2 + j1
572 kr = kr + 1
573 var(k1) = resh(kr)
574 ENDDO
575
576
577 ENDDO
578 ENDDO
579 ENDDO
580 ENDDO
581 ENDDO
582 ENDDO
583
584 C Close the file
585 CALL MNC_FILE_CLOSE(myThid, fname)
586
587 C End the lbj,lbi loops
588 ENDDO
589 ENDDO
590
591 _END_MASTER( myThid )
592
593 RETURN
594 END
595
596 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
597
598 CEH3 ;;; Local Variables: ***
599 CEH3 ;;; mode:fortran ***
600 CEH3 ;;; End: ***

  ViewVC Help
Powered by ViewVC 1.1.22