/[MITgcm]/MITgcm/pkg/ecco/ecco_check.F
ViewVC logotype

Contents of /MITgcm/pkg/ecco/ecco_check.F

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


Revision 1.32 - (show annotations) (download)
Tue Nov 17 16:05:28 2015 UTC (8 years, 6 months ago) by gforget
Branch: MAIN
CVS Tags: checkpoint65q
Changes since 1.31: +22 -1 lines
- cost_gencost_boxmean.F: use maskC(i,j,k,bi,bj)*gencost_mskCsurf(i,j,bi,bj,kgen) rather than mymsk, tmpmsk
- ecco.h: define gencost_mskCsurf, gencost_mskWsurf, gencost_mskSsurf (one field per gencost)
- ecco_check.F: initialize (incl. mdsreadfield) gencost_mskCsurf (should eventually be moved to initfixed)
- ecco_check.F: add m_eta option and init gencost_mskWsurf/gencost_mskSsurf (w. other modifications pending)

1 C $Header: /u/gcmpack/MITgcm/pkg/ecco/ecco_check.F,v 1.31 2015/11/12 13:22:14 atn Exp $
2 C $Name: $
3
4 #include "ECCO_OPTIONS.h"
5
6 C-- File ecco_check.F:
7 C-- Contents
8 C-- o ECCO_CHECK
9 C-- o ECCO_CHECK_FILES
10
11 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
12
13 SUBROUTINE ECCO_CHECK( myThid )
14 C *==========================================================*
15 C | SUBROUTINE ECCO_CHECK |
16 C | o Check runtime activated packages have been built in. |
17 C *==========================================================*
18 C | All packages can be selected/deselected at build time |
19 C | ( when code is compiled ) and activated/deactivated at |
20 C | runtime. This routine does a quick check to trap packages|
21 C | that were activated at runtime but that were not compiled|
22 C | in at build time. |
23 C *==========================================================*
24 IMPLICIT NONE
25
26 C === Global variables ===
27 #include "SIZE.h"
28 #include "EEPARAMS.h"
29 #include "PARAMS.h"
30 #include "DYNVARS.h"
31 #ifdef ALLOW_CAL
32 # include "cal.h"
33 #endif
34 #ifdef ALLOW_ECCO
35 # include "ecco_cost.h"
36 #endif
37
38 C === Routine arguments ===
39 C myThid - Number of this instances
40 INTEGER myThid
41
42 C === Local variables ===
43 C msgBuf - Informational/error meesage buffer
44 CHARACTER*(MAX_LEN_MBUF) msgBuf
45 #ifdef ALLOW_GENCOST_CONTRIBUTION
46 INTEGER k, igen_etaday, il
47 LOGICAL exst
48 CHARACTER*(128) tempfile,tempfile1
49 INTEGER icount_transp
50 #endif
51
52 c == external functions ==
53
54 integer ilnblnk
55 external ilnblnk
56
57 _BEGIN_MASTER(myThid)
58
59 #if (defined (ALLOW_TRANSPORT_COST_CONTRIBUTION) || \
60 defined (ALLOW_NEW_SSH_COST))
61 IF ( ndaysrec .GT. maxNumDays ) THEN
62 WRITE(msgBuf,'(2A,2I10)')
63 & 'ECCO_CHECK: for ALLOW_TRANSPORT_COST_CONTRIBUTION: ',
64 & 'ndaysrec > maxNumDays in ecco_cost.h ',
65 & ndaysrec, maxNumDays
66 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
67 & SQUEEZE_RIGHT , myThid )
68 CALL PRINT_ERROR( msgBuf , myThid )
69 STOP 'ABNORMAL END: S/R ECCO_CHECK'
70 ENDIF
71 #endif
72
73 cgf next line is only for backward compatibility
74 IF ( (using_topex).AND.(.NOT.using_tpj) ) using_tpj=.TRUE.
75
76 _END_MASTER(myThid)
77
78 c check for missing data files
79 #ifdef ALLOW_BP_COST_CONTRIBUTION
80 CALL ECCO_CHECK_FILES( using_cost_bp,'bp',
81 & bpdatfile, bpstartdate(1), myThid )
82 #endif
83 #ifdef ALLOW_SST_COST_CONTRIBUTION
84 CALL ECCO_CHECK_FILES( using_cost_sst,'sst',
85 & sstdatfile, sststartdate(1), myThid )
86 #endif
87 #ifdef ALLOW_TMI_SST_COST_CONTRIBUTION
88 CALL ECCO_CHECK_FILES( using_cost_sst,'sst',
89 & tmidatfile, tmistartdate(1), myThid )
90 #endif
91 #if (defined (ALLOW_SCAT_COST_CONTRIBUTION) || \
92 defined (ALLOW_DAILYSCAT_COST_CONTRIBUTION) )
93 CALL ECCO_CHECK_FILES( using_cost_scat,'scat',
94 & scatxdatfile, scatxstartdate(1), myThid )
95 CALL ECCO_CHECK_FILES( using_cost_scat,'scat',
96 & scatydatfile, scatystartdate(1), myThid )
97 #endif
98
99 #ifdef ALLOW_GENCOST_CONTRIBUTION
100 icount_transp=0
101 do k=1,NGENCOST
102 if (gencost_pointer3d(k).GT.NGENCOST3D) then
103 WRITE(msgBuf,'(2A)')
104 & 'ECCO_CHECK: too many 3D cost terms; please',
105 & 'increase NGENCOST3D and recompile.'
106 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
107 & SQUEEZE_RIGHT , myThid )
108 CALL PRINT_ERROR( msgBuf , myThid )
109 STOP 'ABNORMAL END: S/R ECCO_CHECK'
110 endif
111
112 if ( gencost_datafile(k) .ne. ' ' ) then
113
114 CALL ECCO_CHECK_FILES( using_gencost(k), 'gencost',
115 & gencost_datafile(k), gencost_startdate1(k), myThid )
116
117 c--
118 if ( (gencost_preproc(1,k).EQ.'variaweight').AND.
119 & ( gencost_errfile(k) .NE. ' ' ) ) then
120 CALL ECCO_CHECK_FILES( using_gencost(k), 'gencost',
121 & gencost_errfile(k), gencost_startdate1(k), myThid )
122 elseif ( gencost_errfile(k) .NE. ' ' ) then
123 il = ilnblnk(gencost_errfile(k))
124 inquire( file=gencost_errfile(k)(1:il), exist=exst )
125 if (.NOT.exst) then
126 using_gencost(k)=.FALSE.
127 il = ilnblnk(gencost_name(k))
128 WRITE(msgBuf,'(4A)')
129 & '** WARNING ** ECCO_CHECK_FILES: missing error file',
130 & ' so ',gencost_name(k)(1:il),' gets switched off'
131 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
132 & SQUEEZE_RIGHT , myThid)
133 endif
134 endif
135
136 c altimetry related checks
137 if (gencost_name(k).EQ.'sshv4-tp') using_tpj=using_gencost(k)
138 if (gencost_name(k).EQ.'sshv4-ers') using_ers=using_gencost(k)
139 if (gencost_name(k).EQ.'sshv4-gfo') using_gfo=using_gencost(k)
140 if (gencost_name(k).EQ.'sshv4-mdt') using_mdt=using_gencost(k)
141
142 c seaice related checks
143 if (gencost_name(k).EQ.'siv4-conc')
144 & using_cost_seaice=using_gencost(k)
145 if (gencost_name(k).EQ.'siv4-deconc')
146 & using_cost_seaice=using_gencost(k)
147 if (gencost_name(k).EQ.'siv4-exconc')
148 & using_cost_seaice=using_gencost(k)
149 catn-- put stop statement if use old siv4 names:
150 if (gencost_name(k).EQ.'siv4-sst') then
151 WRITE(msgBuf,'(2A)')
152 & 'ECCO_CHECK: OLD seaice gencost_name siv4-sst is retired,',
153 & ' NEW name is siv4-deconc'
154 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
155 & SQUEEZE_RIGHT , myThid )
156 CALL PRINT_ERROR( msgBuf , myThid )
157 STOP 'ABNORMAL END: S/R ECCO_CHECK'
158 endif
159 if (gencost_name(k).EQ.'siv4-vol') then
160 WRITE(msgBuf,'(2A)')
161 & 'ECCO_CHECK: OLD seaice gencost_name siv4-vol is retired,',
162 & ' NEW name is siv4-exconc'
163 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
164 & SQUEEZE_RIGHT , myThid )
165 CALL PRINT_ERROR( msgBuf , myThid )
166 STOP 'ABNORMAL END: S/R ECCO_CHECK'
167 endif
168
169 c-atn add another block for cost that do not need datafile but
170 c should have checks for other things:
171 c here, separate into different gencost_flag block
172 else !if ( gencost_datafile(k) .ne. ' ' ) then
173 c---------------- block -1 ----------------------------
174 c block -1: cost ssh-[mdt,lsc,amsre-lsc] do not need datafile
175 c but need errfile. at the moment do not accomodate variaweight.
176 if(gencost_flag(k).eq. -1) then
177 if(gencost_errfile(k) .ne. ' ') then
178 il = ilnblnk(gencost_errfile(k))
179 inquire( file=gencost_errfile(k)(1:il), exist=exst )
180 if (.NOT.exst) then
181 using_gencost(k)=.FALSE.
182 il = ilnblnk(gencost_name(k))
183 WRITE(msgBuf,'(4A)')
184 & '** WARNING ** ECCO_CHECK_FILES: missing error file',
185 & ' so ',gencost_name(k)(1:il),' gets switched off'
186 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
187 & SQUEEZE_RIGHT , myThid)
188 endif
189 elseif(.not.(gencost_name(k).eq.'sshv4-gmsl')) then
190 using_gencost(k)=.FALSE.
191 il = ilnblnk(gencost_name(k))
192 WRITE(msgBuf,'(4A)')
193 & '** WARNING ** ECCO_CHECK_FILES: error file not defined',
194 & ' so ',gencost_name(k)(1:il),' gets switched off'
195 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
196 & SQUEEZE_RIGHT , myThid)
197 endif
198
199 c---------------- block -3 ----------------------------
200 c-- boxmean: require [err,bar]file, can have datafile, not checked here
201 c-- also not checked for variwei at the moment
202 elseif(gencost_flag(k) .eq. -3 ) then
203 WRITE(msgBuf,'(A,i3,L5)')
204 & 'entering boxmean check,k,using_gencost(k): ,',
205 & k,using_gencost(k)
206 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
207 & SQUEEZE_RIGHT , myThid)
208 c-- check errfile
209 call ecco_zero(gencost_mskCsurf(1-olx,1-oly,1,1,k),
210 & 1,zeroRL,mythid)
211 if ( gencost_errfile(k) .NE. ' ' ) then
212 il = ilnblnk(gencost_errfile(k))
213 inquire( file=gencost_errfile(k)(1:il), exist=exst )
214 if (.NOT.exst) then
215 using_gencost(k)=.FALSE.
216 il = ilnblnk(gencost_name(k))
217 WRITE(msgBuf,'(4A)')
218 & '** WARNING ** ECCO_CHECK_FILES: missing error file',
219 & ' so ',gencost_name(k)(1:il),' gets switched off'
220 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
221 & SQUEEZE_RIGHT , myThid)
222 else
223 write(tempfile(1:128),'(A)') gencost_errfile(k)(1:il)
224 call mdsreadfield(tempfile,32,'RL',1,
225 & gencost_mskCsurf(1-olx,1-oly,1,1,k),1,mythid)
226 endif
227 endif!errfile
228
229 c-- check barfile, make sure character m_[theta,salt] match exactly
230 c-- (upper/lower-case matters) in cost_gencost_customize
231 if (.not.( (gencost_barfile(k)(1:7).EQ.'m_theta').OR.
232 & (gencost_barfile(k)(1:5).EQ.'m_eta').OR.
233 & (gencost_barfile(k)(1:6).EQ.'m_salt') )) then
234 using_gencost(k)=.FALSE.
235 il=ilnblnk(gencost_barfile(k))
236 WRITE(msgBuf,'(3A)')
237 & '** WARNING ** S/R ECCO_CHECK: barfile ',
238 & gencost_barfile(k)(1:il),': has no matched model var.'
239 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
240 & SQUEEZE_RIGHT, myThid )
241 WRITE(msgBuf,'(A)') 'Edit cost_gencost_customize to fix. '
242 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
243 & SQUEEZE_RIGHT, myThid )
244 il = ilnblnk(gencost_name(k))
245 WRITE(msgBuf,'(2A)') gencost_name(k)(1:il),' is switched off'
246 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
247 & SQUEEZE_RIGHT, myThid )
248 endif !barfile
249
250 c---------------- block -4 ----------------------------
251 c-- transs: require [err,bar][W,S]file, can have datafile, but
252 c-- not checked here. also not checked for variwei at the moment
253 elseif ( gencost_flag(k).eq. -4 ) then
254 WRITE(msgBuf,'(A,i3,L5)')
255 & 'ecco_check for gencost transp; k,using_gencost(k): ,',
256 & k,using_gencost(k)
257 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
258 & SQUEEZE_RIGHT , myThid)
259
260 c-- check errfile[W,S]
261 call ecco_zero(gencost_mskWsurf(1-olx,1-oly,1,1,k),
262 & 1,zeroRL,mythid)
263 call ecco_zero(gencost_mskSsurf(1-olx,1-oly,1,1,k),
264 & 1,zeroRL,mythid)
265 if ( gencost_errfile(k) .NE. ' ' ) then
266 c-- West ----------------------
267 il = ilnblnk(gencost_errfile(k))
268 write(tempfile(1:128),'(2A)') gencost_errfile(k)(1:il),'W'
269 il = ilnblnk(tempfile)
270 write(msgBuf,'(2A,L5)') 'ecco_check file, exst: ',
271 & tempfile(1:il),exst
272 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
273 & SQUEEZE_RIGHT , myThid)
274 if (.NOT.exst) then
275 using_gencost(k)=.FALSE.
276 WRITE(msgBuf,'(2A)')
277 & '** WARNING ** ECCO_CHECK_FILES: missing error file: ',
278 & tempfile(1:il)
279 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
280 & SQUEEZE_RIGHT , myThid)
281 il = ilnblnk(gencost_name(k))
282 WRITE(msgBuf,'(3A)')
283 & ' so ',gencost_name(k)(1:il),' gets switched off'
284 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
285 & SQUEEZE_RIGHT , myThid)
286 else
287 c-- will move to init perhaps, but leave here for now due to check exst
288 cgf (1) should indeed be moved to init_fixed
289 cgf (2) generalization: read in a 1D vertical mask and do the product
290 cgf of e.g. gencost_mskWsurf*gencost_mskZ in ecco_phys.F?
291 cgf (3) naming convention: m_heat_hadv rather than trHeat, etc?
292 cgf would help eventually distinguish, e.g., m_heat_hdif vs m_heat_vdif...
293 cgf (4) generalization: specify type of transport (vol, heat, etc) via namelist?
294 call ecco_zero(msktrVolW,1,zeroRL,mythid)
295 call mdsreadfield(tempfile,32,'RL',1,msktrVolW,1,mythid)
296 call mdsreadfield(tempfile,32,'RL',1,
297 & gencost_mskWsurf(1-olx,1-oly,1,1,k),1,mythid)
298 endif
299 c-- South --------------------
300 il = ilnblnk(gencost_errfile(k))
301 write(tempfile(1:128),'(2A)') gencost_errfile(k)(1:il),'S'
302 il = ilnblnk(tempfile)
303 inquire( file=tempfile(1:il), exist=exst )
304 write(msgBuf,'(2A,L5)') 'ecco_check file, exst: ',
305 & tempfile(1:il),exst
306 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
307 & SQUEEZE_RIGHT , myThid)
308 if (.NOT.exst) then
309 using_gencost(k)=.FALSE.
310 WRITE(msgBuf,'(2A)')
311 & '** WARNING ** ECCO_CHECK_FILES: missing error file: ',
312 & tempfile(1:il)
313 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
314 & SQUEEZE_RIGHT , myThid)
315 il = ilnblnk(gencost_name(k))
316 WRITE(msgBuf,'(3A)')
317 & ' so ',gencost_name(k)(1:il),' gets switched off'
318 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
319 & SQUEEZE_RIGHT , myThid)
320 else
321 c-- will move to init perhaps, but leave here for now due to check exst
322 call ecco_zero(msktrVolS,1,zeroRL,mythid)
323 call mdsreadfield(tempfile,32,'RL',1,msktrVolS,1,mythid)
324 call mdsreadfield(tempfile,32,'RL',1,
325 & gencost_mskSsurf(1-olx,1-oly,1,1,k),1,mythid)
326 endif
327 else
328 using_gencost(k)=.FALSE.
329 il=ilnblnk(gencost_name(k))
330 WRITE(msgBuf,'(4A)')
331 & '** WARNING ** ECCO_CHECKD: errfile not defined',
332 & ' so ',gencost_name(k)(1:il),' gets switched off'
333 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
334 & SQUEEZE_RIGHT , myThid)
335
336 endif!errfile
337 c-- check barfile, make sure character m_tr[Vol,Heat,Salt] match exactly
338 c-- (upper/lower-case matters) in cost_gencost_customize
339 if(.not.( (gencost_barfile(k)(1:7).EQ.'m_trVol') .OR.
340 & (gencost_barfile(k)(1:8).EQ.'m_trHeat').OR.
341 & (gencost_barfile(k)(1:8).EQ.'m_trSalt') )) then
342 using_gencost(k)=.FALSE.
343 il=ilnblnk(gencost_barfile(k))
344 WRITE(msgBuf,'(3A)')
345 & '** WARNING ** S/R ECCO_CHECK: barfile ',
346 & gencost_barfile(k)(1:il),': has no matched model var.'
347 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
348 & SQUEEZE_RIGHT, myThid )
349 WRITE(msgBuf,'(A)') 'Edit cost_gencost_customize to fix. '
350 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
351 & SQUEEZE_RIGHT, myThid )
352 il = ilnblnk(gencost_name(k))
353 WRITE(msgBuf,'(2A)') gencost_name(k)(1:il),' is switched off'
354 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
355 & SQUEEZE_RIGHT, myThid )
356 endif !barfile
357 c-- set using_cost_transp
358 if(using_gencost(k)) icount_transp=icount_transp+1
359 if(icount_transp.gt.0) using_cost_transp = .TRUE.
360 c-- final report to make sure using_cost_transp is set correctly
361 WRITE(msgBuf,'(2A,i3,L5)')
362 & 'ecco_check: gencost transp; icount_transp,',
363 & 'using_cost_transp: ',icount_transp,using_cost_transp
364 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
365 & SQUEEZE_RIGHT , myThid)
366 endif !gencost_flag
367
368 endif !if ( gencost_datafile(k) .ne. ' ' ) then
369 enddo
370
371 c check that one of the used gencost term defines etaday (needed in sshv4)
372 IF ( (using_tpj ).OR.(using_ers).OR.(using_gfo)
373 & .OR.(using_mdt) ) using_cost_altim = .TRUE.
374
375 igen_etaday=0
376 do k=1,NGENCOST
377 if ( (gencost_barfile(k)(1:5).EQ.'m_eta').AND.
378 & (using_gencost(k)) ) igen_etaday=k
379 enddo
380
381 if (igen_etaday.EQ.0) then
382 c warn user as we override using_cost_altim
383 using_cost_altim = .FALSE.
384 WRITE(msgBuf,'(2A)')
385 & '** WARNING ** S/R ECCO_CHECK: missing file: ',
386 & ' for altimeter data so cost gets switched off'
387 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
388 & SQUEEZE_RIGHT, myThid )
389 else
390 c print result to screen
391 write(msgbuf,'(a,i3)')
392 & 'etaday defined by gencost ',igen_etaday
393 call print_message( msgbuf, standardmessageunit,
394 & SQUEEZE_RIGHT , mythid)
395 endif
396
397 #endif
398
399 RETURN
400 END
401
402 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
403
404 SUBROUTINE ECCO_CHECK_FILES(
405 O using_cost_local,
406 I localname, localobsfile, localstartdate1,
407 I myThid )
408
409 C *==========================================================*
410 C | SUBROUTINE ECCO_CHECK_FILES |
411 C | o Check that obs files are present for specified years. |
412 C | If not then set using_cost_local to false. |
413 C *==========================================================*
414 IMPLICIT NONE
415
416 C === Global variables ===
417 #include "SIZE.h"
418 #include "EEPARAMS.h"
419 #include "PARAMS.h"
420 #include "ecco.h"
421 #ifdef ALLOW_CAL
422 # include "cal.h"
423 #endif
424
425 C === Routine arguments ===
426 C myThid - Number of this instances
427 INTEGER myThid
428 LOGICAL using_cost_local
429 character*(*) localname
430 character*(MAX_LEN_FNAM) localobsfile
431 integer localstartdate1
432
433 C === Local variables ===
434 C msgBuf - Informational/error meesage buffer
435 CHARACTER*(MAX_LEN_MBUF) msgBuf
436 INTEGER irec, mody, modm, yday, locy, il
437 LOGICAL exst, singleFileTest, yearlyFileTest
438 character*(128) fname
439
440 c == external functions ==
441
442 integer ilnblnk
443 external ilnblnk
444
445 c == end of interface ==
446
447 c left for later : refine test accounting for localstartdate1
448
449 #ifdef ALLOW_CAL
450
451 _BEGIN_MASTER(myThid)
452
453 IF ( (using_cost_local).AND.(localobsfile.EQ.' ') ) THEN
454 c warn user as we override using_cost_local
455 WRITE(msgBuf,'(4A)')
456 & '** WARNING ** ECCO_CHECK_FILES: missing file',
457 & ' definition so ',localname,' gets switched off'
458 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
459 & SQUEEZE_RIGHT , myThid)
460 c switch off cost function term
461 using_cost_local = .FALSE.
462 ENDIF
463
464 singleFileTest = .FALSE.
465 IF (using_cost_local) THEN
466 inquire( file=localobsfile, exist=exst )
467 IF ( exst ) singleFileTest=.TRUE.
468 ENDIF
469
470 yearlyFileTest = .FALSE.
471 IF ( (using_cost_local).AND.(.NOT.singleFileTest) ) THEN
472 DO irec = 1, nmonsrec
473 mody = modelstartdate(1)/10000
474 modm = modelstartdate(1)/100 - mody*100
475 yday = mody + INT((modm-1+irec-1)/12)
476
477 locy = localstartdate1/10000
478
479 il=ilnblnk(localobsfile)
480 write(fname(1:128),'(2a,i4)')
481 & localobsfile(1:il), '_', yday
482 inquire( file=fname, exist=exst )
483
484 IF ( (.NOT.exst).AND.(yday.GE.locy) ) THEN
485 c warn user as we override using_cost_local
486 WRITE(msgBuf,'(5A)')
487 & '** WARNING ** ECCO_CHECK_FILES: missing',fname,
488 & ' so ',localname,' gets switched off'
489 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
490 & SQUEEZE_RIGHT , myThid)
491 c switch off cost function term
492 using_cost_local = .FALSE.
493 ELSEIF ( (exst).AND.(yday.GE.locy) ) THEN
494 yearlyFileTest = .TRUE.
495 ENDIF
496 ENDDO
497 ENDIF
498
499 IF (using_cost_local) THEN
500 IF ( (.NOT.yearlyFileTest).AND.(.NOT.singleFileTest) ) THEN
501 c warn user as we override using_cost_local
502 WRITE(msgBuf,'(4A)')
503 & '** WARNING ** ECCO_CHECK_FILES: no data ',
504 & ' so ',localname,' gets switched off'
505 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
506 & SQUEEZE_RIGHT , myThid)
507 c switch off cost function term
508 using_cost_local = .FALSE.
509 ENDIF
510 ENDIF
511
512 _END_MASTER(myThid)
513
514 #endif /* ALLOW_CAL */
515
516 RETURN
517 END

  ViewVC Help
Powered by ViewVC 1.1.22