/[MITgcm]/MITgcm/pkg/exf/exf_check.F
ViewVC logotype

Diff of /MITgcm/pkg/exf/exf_check.F

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

revision 1.21 by dimitri, Sat Apr 20 21:37:28 2013 UTC revision 1.31 by jmc, Sun Feb 12 00:50:58 2017 UTC
# Line 3  C $Name$ Line 3  C $Name$
3    
4  #include "EXF_OPTIONS.h"  #include "EXF_OPTIONS.h"
5    
6    C--  File exf_check.F: Routines to check EXF settings
7    C--   Contents
8    C--   o EXF_CHECK
9    C--   o EXF_CHECK_INTERP
10    
11    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
12    CBOP
13    C     !ROUTINE: EXF_CHECK
14    C     !INTERFACE:
15    
16        SUBROUTINE EXF_CHECK( myThid )        SUBROUTINE EXF_CHECK( myThid )
17    
18  c     ==================================================================  C     !DESCRIPTION: \bv
19  c     SUBROUTINE EXF_CHECK  C     *==========================================================*
20  c     ==================================================================  C     | S/R EXF_CHECK
21  c  C     | o Check parameters and other package dependences
22        IMPLICIT NONE  C     *==========================================================*
23    C     \ev
24    
25  c     == global variables ==  C     !USES:
26          IMPLICIT NONE
27    
28    C     == Global variables ===
29  #include "EEPARAMS.h"  #include "EEPARAMS.h"
30  #include "SIZE.h"  #include "SIZE.h"
31  #include "PARAMS.h"  #include "PARAMS.h"
32    
33  #include "EXF_PARAM.h"  #include "EXF_PARAM.h"
34  #include "EXF_CONSTANTS.h"  #include "EXF_CONSTANTS.h"
 c     == routine arguments ==  
   
 c     myThid - thread number for this instance of the routine.  
35    
36    C     !INPUT/OUTPUT PARAMETERS:
37    C     myThid   :: my Thread Id number
38        INTEGER myThid        INTEGER myThid
39    
40  c     == local variables ==  C     !LOCAL VARIABLES:
   
41  C     msgBuf   :: Informational/error message buffer  C     msgBuf   :: Informational/error message buffer
42        CHARACTER*(MAX_LEN_MBUF) msgBuf        CHARACTER*(MAX_LEN_MBUF) msgBuf
43          INTEGER errCount
44    CEOP
45    
46  c     == end of interface ==        _BEGIN_MASTER(myThid)
47          errCount = 0
48    
49  c     check for consistency        WRITE(msgBuf,'(A)') 'EXF_CHECK: #define ALLOW_EXF'
50        if (.NOT.        CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
51         &                    SQUEEZE_RIGHT, myThid )
52    
53    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
54    C     check for consistency
55          IF (.NOT.
56       &     (exf_iprec.EQ.precFloat32 .OR. exf_iprec.EQ.precFloat64)       &     (exf_iprec.EQ.precFloat32 .OR. exf_iprec.EQ.precFloat64)
57       &     ) then       &     ) THEN
58         stop 'S/R EXF_CHECK: value of exf_iprec not allowed'         WRITE(msgBuf,'(A)')
59        endif       &      'S/R EXF_CHECK: value of exf_iprec not allowed'
60           CALL PRINT_ERROR( msgBuf, myThid )
61        if (repeatPeriod.lt.0.) then         errCount = errCount + 1
62         stop 'S/R EXF_CHECK: repeatPeriod must be positive'        ENDIF
63        endif  
64          IF ( repeatPeriod.LT.0. ) THEN
65        if (useExfYearlyFields.and.repeatPeriod.ne.0.) then         WRITE(msgBuf,'(A)')
66         print*,'Use of usefldyearlyfields AND repeatPeriod',       &      'S/R EXF_CHECK: repeatPeriod must be positive'
67       &      ' not implemented'         CALL PRINT_ERROR( msgBuf, myThid )
68         stop 'ABNORMAL END: S/R EXF_CHECK'         errCount = errCount + 1
69        endif        ENDIF
70    
71          IF ( useExfYearlyFields ) THEN
72           IF ( .NOT.useCAL ) THEN
73            WRITE(msgBuf,'(2A)') 'S/R EXF_CHECK: ',
74         &       'useExfYearlyFields requires to use pkg/cal (useCAL=T)'
75            CALL PRINT_ERROR( msgBuf, myThid )
76            errCount = errCount + 1
77           ENDIF
78           IF ( repeatPeriod.NE.0. ) THEN
79            WRITE(msgBuf,'(2A)') 'S/R EXF_CHECK: The use of ',
80         &       'useExfYearlyFields AND repeatPeriod is not implemented'
81            CALL PRINT_ERROR( msgBuf, myThid )
82            errCount = errCount + 1
83           ENDIF
84          ENDIF
85          IF ( useOBCS .AND. useOBCSYearlyFields ) THEN
86           IF ( .NOT.useCAL ) THEN
87            WRITE(msgBuf,'(2A)') 'S/R EXF_CHECK: ',
88         &       'useOBCSYearlyFields requires to use pkg/cal (useCAL=T)'
89            CALL PRINT_ERROR( msgBuf, myThid )
90            errCount = errCount + 1
91           ENDIF
92           IF ( repeatPeriod.NE.0. ) THEN
93            WRITE(msgBuf,'(2A)') 'S/R EXF_CHECK: ',
94         &       'useOBCSYearlyFields not implemented for repeatPeriod <> 0'
95            CALL PRINT_ERROR( msgBuf, myThid )
96            errCount = errCount + 1
97           ENDIF
98          ENDIF
99    
 #ifdef ALLOW_BULKFORMULAE  
100        IF ( useAtmWind ) THEN        IF ( useAtmWind ) THEN
101        IF ( ustressfile .NE. ' ' .OR. ustressfile .NE. ' ' ) THEN         IF ( ustressfile .NE. ' ' .OR. vstressfile .NE. ' ' ) THEN
102          STOP          WRITE(msgBuf,'(A)')
103       & 'S/R EXF_CHECK: use u,v_wind components but not wind-stress'       &   'S/R EXF_CHECK: use u,v_wind components but not wind-stress'
104        ENDIF          CALL PRINT_ERROR( msgBuf, myThid )
105            errCount = errCount + 1
106           ENDIF
107        ENDIF        ENDIF
 #endif  
108    
109        IF ( .NOT.useAtmWind ) THEN        IF ( .NOT.useAtmWind ) THEN
110        IF ( uwindfile .NE. ' ' .OR. vwindfile .NE. ' ' ) THEN         IF ( uwindfile .NE. ' ' .OR. vwindfile .NE. ' ' ) THEN
111          STOP          WRITE(msgBuf,'(A)')
112       & 'S/R EXF_CHECK: read-in wind-stress but not u,v_wind components'       & 'S/R EXF_CHECK: read-in wind-stress but not u,v_wind components'
113        ENDIF          CALL PRINT_ERROR( msgBuf, myThid )
114            errCount = errCount + 1
115           ENDIF
116        ENDIF        ENDIF
117    
118  #ifndef ALLOW_ZENITHANGLE  #ifdef ALLOW_SALTFLX
119        IF ( useExfZenAlbedo .OR. useExfZenIncoming .OR.        IF ( useSEAICE .OR. useThSIce )  THEN
120       &     select_ZenAlbedo .NE. 0 ) THEN         IF ( saltflxfile .NE. ' ' ) THEN
121          WRITE(msgBuf,'(A,A)') 'EXF_CHECK: unsupported option',          WRITE(msgBuf,'(2A)') 'S/R EXF_CHECK: exf salt flux is not',
122       &        ' when ALLOW_ZENITHANGLE is not defined'       &       ' allowed when using either pkg/seaice or pkg/thsice'
123          CALL PRINT_ERROR( msgBuf, myThid )          CALL PRINT_ERROR( msgBuf, myThid )
124          STOP 'ABNORMAL END: S/R EXF_CHECK'          errCount = errCount + 1
125           ENDIF
126        ENDIF        ENDIF
127  #endif  #endif /* ALLOW_SALTFLX */
128    
129  #ifdef ALLOW_ZENITHANGLE  #ifdef ALLOW_ZENITHANGLE
130        IF ( usingCartesianGrid .OR. usingCylindricalGrid ) then        IF ( ( useExfZenIncoming .OR. select_ZenAlbedo.NE.0 ) .AND.
131          WRITE(msgBuf,'(A,A)') 'EXF_CHECK: ALLOW_ZENITHANGLE does ',       &     ( usingCartesianGrid .OR. usingCylindricalGrid ) ) THEN
132       &        'not work for carthesian and cylindrical grids'         WRITE(msgBuf,'(A,A)') 'S/R EXF_CHECK: ZENITHANGLE code ',
133          CALL PRINT_ERROR( msgBuf, myThid )       &      'does not work for cartesian and cylindrical grids'
134          STOP 'ABNORMAL END: S/R EXF_CHECK'         CALL PRINT_ERROR( msgBuf, myThid )
135        ENDIF         errCount = errCount + 1
136        IF ( select_ZenAlbedo.LT.0 .OR. select_ZenAlbedo.GT.3 ) then        ENDIF
137          WRITE(msgBuf,'(A,A)') 'EXF_CHECK: unsupported ',        IF ( select_ZenAlbedo.LT.0 .OR. select_ZenAlbedo.GT.3 ) THEN
138       &        'select_ZenAlbedo choice'         WRITE(msgBuf,'(A,A)') 'S/R EXF_CHECK: unsupported ',
139          CALL PRINT_ERROR( msgBuf, myThid )       &      'select_ZenAlbedo choice'
140          STOP 'ABNORMAL END: S/R EXF_CHECK'         CALL PRINT_ERROR( msgBuf, myThid )
141        ENDIF         errCount = errCount + 1
142        IF ( select_ZenAlbedo.EQ.2 .) then        ENDIF
143          write(standardmessageunit,'(A,A)')        IF ( select_ZenAlbedo.EQ.2 ) THEN
144       &  'EXF WARNING: for daily mean albedo, it is advised ',         WRITE(msgBuf,'(A,A)')
145       &        'to use select_ZenAlbedo.EQ.1 instead of 2'       &      'S/R EXF_CHECK: *** WARNING *** for daily mean albedo, ',
146         &      'it is advised to use select_ZenAlbedo.EQ.1 instead of 2'
147           CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
148         &                     SQUEEZE_RIGHT, myThid )
149        ENDIF        ENDIF
150        IF ( select_ZenAlbedo.GT.2 .AND. swdownperiod.GT. 21600 ) then        IF ( select_ZenAlbedo.EQ.3 .AND. swdownperiod.GT.21600. ) THEN
151         WRITE(msgBuf,'(A,A)') 'EXF_CHECK: using diurnal albedo ',         WRITE(msgBuf,'(A,A)') 'S/R EXF_CHECK: using diurnal albedo ',
152       &        'formula requires diurnal downward shortwave forcing'       &        'formula requires diurnal downward shortwave forcing'
153          CALL PRINT_ERROR( msgBuf, myThid )         CALL PRINT_ERROR( msgBuf, myThid )
154          STOP 'ABNORMAL END: S/R EXF_CHECK'         errCount = errCount + 1
155        ENDIF        ENDIF
156        IF ( select_ZenAlbedo.GT.2 .AND. swdownperiod.GT. 3600 ) then        IF ( select_ZenAlbedo.EQ.3 .AND. swdownperiod.GT.3600. ) THEN
157          write(standardmessageunit,'(A,A)')         WRITE(msgBuf,'(A,A,A)')
158       &  'EXF WARNING: the diurnal albedo formula is likely not safe ',       &      'S/R EXF_CHECK: *** WARNING *** ',
159       &  'for such coarse temporal resolution downward shortwave forcing'       &      'the diurnal albedo formula is likely not safe for such ',
160         &      'coarse temporal resolution downward shortwave forcing'
161           CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
162         &                     SQUEEZE_RIGHT, myThid )
163          ENDIF
164    #else /* ALLOW_ZENITHANGLE */
165          IF ( useExfZenIncoming .OR. select_ZenAlbedo.NE.0 ) THEN
166            WRITE(msgBuf,'(A,A)') 'S/R EXF_CHECK: unsupported option',
167         &        ' when ALLOW_ZENITHANGLE is not defined'
168            CALL PRINT_ERROR( msgBuf, myThid )
169            errCount = errCount + 1
170        ENDIF        ENDIF
171  #endif  #endif /* ALLOW_ZENITHANGLE */
172    
173  #ifdef USE_EXF_INTERPOLATION  #ifdef USE_EXF_INTERPOLATION
174        IF ( climsstfile .NE. ' ' ) THEN        IF ( usingCartesianGrid ) THEN
175         IF ( climsst_nlat .GT. MAX_LAT_INC )         WRITE(msgBuf,'(A,A)') 'S/R EXF_CHECK: ',
176       &  STOP 'stopped in exf_readparms: climsst_nlat > MAX_LAT_INC'       &      'USE_EXF_INTERPOLATION assumes latitude/longitude'
177        ENDIF         CALL PRINT_ERROR( msgBuf, myThid )
178        IF ( climsssfile .NE. ' ' ) THEN         WRITE(msgBuf,'(A,A)') 'S/R EXF_CHECK: ',
179         IF ( climsss_nlat .GT. MAX_LAT_INC )       &      'input and output coordinates. Trivial to extend to'
180       &  STOP 'stopped in exf_readparms: climsss_nlat > MAX_LAT_INC'         CALL PRINT_ERROR( msgBuf, myThid )
181        ENDIF         WRITE(msgBuf,'(A,A)') 'S/R EXF_CHECK: ',
182        if ( usingCartesianGrid ) then       &      'cartesian coordinates, but has not yet been done.'
183         print*,'USE_EXF_INTERPOLATION assumes latitude/longitude'         CALL PRINT_ERROR( msgBuf, myThid )
184         print*,'input and output coordinates.  Trivial to extend to'         errCount = errCount + 1
185         print*,'cartesian coordinates, but has not yet been done.'        ENDIF
186         stop  
187        endif        CALL EXF_CHECK_INTERP('ustress',ustressfile,ustress_interpMethod,
188         &     ustress_nlat,ustress_lon_inc,errCount,myThid)
189          CALL EXF_CHECK_INTERP('vstress',vstressfile,vstress_interpMethod,
190         &     vstress_nlat,vstress_lon_inc,errCount,myThid)
191          CALL EXF_CHECK_INTERP('hflux',hfluxfile,hflux_interpMethod,
192         &     hflux_nlat,hflux_lon_inc,errCount,myThid)
193          CALL EXF_CHECK_INTERP('sflux',sfluxfile,sflux_interpMethod,
194         &     sflux_nlat,sflux_lon_inc,errCount,myThid)
195          CALL EXF_CHECK_INTERP('swflux',swfluxfile,swflux_interpMethod,
196         &     swflux_nlat,swflux_lon_inc,errCount,myThid)
197          CALL EXF_CHECK_INTERP('runoff',runofffile,runoff_interpMethod,
198         &     runoff_nlat,runoff_lon_inc,errCount,myThid)
199          CALL EXF_CHECK_INTERP('saltflx',saltflxfile,saltflx_interpMethod,
200         &     saltflx_nlat,saltflx_lon_inc,errCount,myThid)
201          CALL EXF_CHECK_INTERP('atemp',atempfile,atemp_interpMethod,
202         &     atemp_nlat,atemp_lon_inc,errCount,myThid)
203          CALL EXF_CHECK_INTERP('aqh',aqhfile,aqh_interpMethod,
204         &     aqh_nlat,aqh_lon_inc,errCount,myThid)
205          CALL EXF_CHECK_INTERP( 'hs', hs_file, hs_interpMethod,
206         &     hs_nlat, hs_lon_inc, errCount, myThid )
207          CALL EXF_CHECK_INTERP( 'hl', hl_file, hl_interpMethod,
208         &     hl_nlat, hl_lon_inc, errCount, myThid )
209          CALL EXF_CHECK_INTERP('evap',evapfile,evap_interpMethod,
210         &     evap_nlat,evap_lon_inc,errCount,myThid)
211          CALL EXF_CHECK_INTERP('precip',precipfile,precip_interpMethod,
212         &     precip_nlat,precip_lon_inc,errCount,myThid)
213          CALL EXF_CHECK_INTERP('snowprecip',
214         &     snowprecipfile,snowprecip_interpMethod,
215         &     snowprecip_nlat,snowprecip_lon_inc,errCount,myThid)
216          CALL EXF_CHECK_INTERP('uwind',uwindfile,uwind_interpMethod,
217         &     uwind_nlat,uwind_lon_inc,errCount,myThid)
218          CALL EXF_CHECK_INTERP('vwind',vwindfile,vwind_interpMethod,
219         &     vwind_nlat,vwind_lon_inc,errCount,myThid)
220          CALL EXF_CHECK_INTERP('wspeed',wspeedfile,wspeed_interpMethod,
221         &     wspeed_nlat,wspeed_lon_inc,errCount,myThid)
222          CALL EXF_CHECK_INTERP('lwflux',lwfluxfile,lwflux_interpMethod,
223         &     lwflux_nlat,lwflux_lon_inc,errCount,myThid)
224          CALL EXF_CHECK_INTERP('swdown',swdownfile,swdown_interpMethod,
225         &     swdown_nlat,swdown_lon_inc,errCount,myThid)
226          CALL EXF_CHECK_INTERP('lwdown',lwdownfile,lwdown_interpMethod,
227         &     lwdown_nlat,lwdown_lon_inc,errCount,myThid)
228          CALL EXF_CHECK_INTERP('apressure',
229         &     apressurefile,apressure_interpMethod,
230         &     apressure_nlat,apressure_lon_inc,errCount,myThid)
231          CALL EXF_CHECK_INTERP('areamask',
232         &     areamaskfile,areamask_interpMethod,
233         &     areamask_nlat,areamask_lon_inc,errCount,myThid)
234          CALL EXF_CHECK_INTERP('climsst',climsstfile,climsst_interpMethod,
235         &     climsst_nlat,climsst_lon_inc,errCount,myThid)
236          CALL EXF_CHECK_INTERP('climsss',climsssfile,climsss_interpMethod,
237         &     climsss_nlat,climsss_lon_inc,errCount,myThid)
238          CALL EXF_CHECK_INTERP('climustr',
239         &     climustrfile,climustr_interpMethod,
240         &     climustr_nlat,climustr_lon_inc,errCount,myThid)
241          CALL EXF_CHECK_INTERP('climvstr',
242         &     climvstrfile,climvstr_interpMethod,
243         &     climvstr_nlat,climvstr_lon_inc,errCount,myThid)
244    
245  C-    some restrictions on 2-component vector field (might be relaxed later on)  C-    some restrictions on 2-component vector field (might be relaxed later on)
246        IF ( ( uwind_interpMethod.GE.1 .AND. uwindfile.NE.' ' ) .OR.        IF ( ( uwind_interpMethod.GE.1 .AND. uwindfile.NE.' ' ) .OR.
247       &     ( vwind_interpMethod.GE.1 .AND. vwindfile.NE.' ' ) ) THEN       &     ( vwind_interpMethod.GE.1 .AND. vwindfile.NE.' ' ) ) THEN
248         IF ( usingCurvilinearGrid .OR. rotateGrid ) THEN         IF ( usingCurvilinearGrid .OR. rotateGrid ) THEN
249           IF ( uwind_interpMethod.EQ.0 .OR. uwindfile.EQ.' ' .OR.          IF ( uwind_interpMethod.EQ.0 .OR. uwindfile.EQ.' ' .OR.
250       &        vwind_interpMethod.EQ.0 .OR. vwindfile.EQ.' ' ) THEN       &       vwind_interpMethod.EQ.0 .OR. vwindfile.EQ.' ' ) THEN
251  C-    stop if one expects interp+rotation (Curvilin-G) which will not happen  C-    stop if one expects interp+rotation (Curvilin-G) which will not happen
252            STOP 'interp. needs 2 components (wind)'           WRITE(msgBuf,'(A)')
253           ENDIF       &        'S/R EXF_CHECK: interp. needs 2 components (wind)'
254           IF ( uwindstartdate .NE. vwindstartdate .OR.           CALL PRINT_ERROR( msgBuf, myThid )
255       &        uwindperiod    .NE. vwindperiod   ) THEN           errCount = errCount + 1
256            print*,'For CurvilinearGrid/RotatedGrid, S/R EXF_SET_UV'          ENDIF
257            print*,'assumes that the u and v wind files'          IF ( uwindStartTime .NE. vwindStartTime .OR.
258            print*,'have the same startdate and period.'       &       uwindperiod    .NE. vwindperiod   ) THEN
259            stop           WRITE(msgBuf,'(A,A)') 'S/R EXF_CHECK: ',
260           ENDIF       &        'For CurvilinearGrid/RotatedGrid, the u and v wind '
261             CALL PRINT_ERROR( msgBuf, myThid )
262             WRITE(msgBuf,'(A,A,A)') 'S/R EXF_CHECK: ',
263         &        'files have to have the same StartTime and period, ',
264         &        'because S/R EXF_SET_UV assumes that.'
265             CALL PRINT_ERROR( msgBuf, myThid )
266             errCount = errCount + 1
267            ENDIF
268         ENDIF         ENDIF
269        ENDIF        ENDIF
270        IF ( (ustress_interpMethod.GE.1 .AND. ustressfile.NE.' ') .OR.        IF ( (ustress_interpMethod.GE.1 .AND. ustressfile.NE.' ') .OR.
271       &     (vstress_interpMethod.GE.1 .AND. vstressfile.NE.' ') ) THEN       &     (vstress_interpMethod.GE.1 .AND. vstressfile.NE.' ') ) THEN
272         IF ( readStressOnCgrid ) THEN         IF ( readStressOnCgrid ) THEN
273            STOP 'readStressOnCgrid and interp wind-stress (=A-grid)'          WRITE(msgBuf,'(A,A)')
274         &       'S/R EXF_CHECK: readStressOnCgrid=.TRUE. ',
275         &       'and interp wind-stress (=A-grid) are not compatible'
276            CALL PRINT_ERROR( msgBuf, myThid )
277            errCount = errCount + 1
278         ENDIF         ENDIF
279         IF ( usingCurvilinearGrid .OR. rotateGrid ) THEN         IF ( usingCurvilinearGrid .OR. rotateGrid ) THEN
280           IF ( ustress_interpMethod.EQ.0 .OR. ustressfile.EQ.' ' .OR.          IF ( ustress_interpMethod.EQ.0 .OR. ustressfile.EQ.' ' .OR.
281       &        vstress_interpMethod.EQ.0 .OR. vstressfile.EQ.' ' ) THEN       &       vstress_interpMethod.EQ.0 .OR. vstressfile.EQ.' ' ) THEN
282  C-    stop if one expects interp+rotation (Curvilin-G) which will not happen  C-    stop if one expects interp+rotation (Curvilin-G) which will not happen
283            STOP 'interp. needs 2 components (wind-stress)'           WRITE(msgBuf,'(A)')
284           ENDIF       &        'S/R EXF_CHECK: interp. needs 2 components (wind-stress)'
285           IF ( ustressstartdate .NE. vstressstartdate .OR.           CALL PRINT_ERROR( msgBuf, myThid )
286       &        ustressperiod    .NE. vstressperiod   ) THEN           errCount = errCount + 1
287            print*,'For CurvilinearGrid/RotatedGrid, S/R EXF_SET_UV'          ENDIF
288            print*,'assumes that the u and v wind stress files'          IF ( ustressStartTime .NE. vstressStartTime .OR.
289            print*,'have the same startdate and period.'       &       ustressperiod    .NE. vstressperiod   ) THEN
290            stop           WRITE(msgBuf,'(A,A)') 'S/R EXF_CHECK: ',
291           ENDIF       &    'For CurvilinearGrid/RotatedGrid, the u and v wind stress '
292             CALL PRINT_ERROR( msgBuf, myThid )
293             WRITE(msgBuf,'(A,A,A)') 'S/R EXF_CHECK: ',
294         &        'files have to have the same StartTime and period, ',
295         &        'because S/R EXF_SET_UV assumes that.'
296             CALL PRINT_ERROR( msgBuf, myThid )
297             errCount = errCount + 1
298            ENDIF
299         ENDIF         ENDIF
300        ENDIF        ENDIF
301    
302        IF ( (ustress_interpMethod.EQ.0 .AND. ustressfile.NE.' ') .OR.        IF ( (ustress_interpMethod.EQ.0 .AND. ustressfile.NE.' ') .OR.
303       &     (vstress_interpMethod.EQ.0 .AND. vstressfile.NE.' ') ) THEN       &     (vstress_interpMethod.EQ.0 .AND. vstressfile.NE.' ') ) THEN
304  #else /* ifndef USE_EXF_INTERPOLATION */  #else /* ndef USE_EXF_INTERPOLATION */
305        IF     ( ustressfile .NE. ' ' .OR. vstressfile .NE. ' ' ) THEN        IF     ( ustressfile .NE. ' ' .OR. vstressfile .NE. ' ' ) THEN
306  #endif /* USE_EXF_INTERPOLATION */  #endif /* USE_EXF_INTERPOLATION */
307          IF ( (readStressOnAgrid.AND.readStressOnCgrid) .OR.         IF (     (readStressOnAgrid.AND.readStressOnCgrid) .OR.
308       &   .NOT.(readStressOnAgrid.OR.readStressOnCgrid) ) THEN       &      .NOT.(readStressOnAgrid.OR.readStressOnCgrid) ) THEN
309            STOP          WRITE(msgBuf,'(A)')
310       & 'S/R EXF_CHECK: Select 1 wind-stress position: A or C-grid'       & 'S/R EXF_CHECK: Select 1 wind-stress position: A or C-grid'
311          ENDIF          CALL PRINT_ERROR( msgBuf, myThid )
312            errCount = errCount + 1
313           ENDIF
314           IF (rotateStressOnAgrid.AND..NOT.readStressOnAgrid) THEN
315            WRITE(msgBuf,'(2A)') 'S/R EXF_CHECK: rotateStressOnAgrid ',
316         & 'only applies to cases readStressOnAgrid is true'
317            CALL PRINT_ERROR( msgBuf, myThid )
318            errCount = errCount + 1
319           ENDIF
320    
321        ELSE        ELSE
322          IF ( readStressOnAgrid .OR. readStressOnCgrid ) THEN         IF ( readStressOnAgrid .OR. readStressOnCgrid .OR.
323            STOP 'S/R EXF_CHECK: wind-stress position irrelevant'       &      rotateStressOnAgrid) THEN
324          ENDIF          WRITE(msgBuf,'(A)')
325         &       'S/R EXF_CHECK: wind-stress position irrelevant'
326            CALL PRINT_ERROR( msgBuf, myThid )
327            errCount = errCount + 1
328           ENDIF
329        ENDIF        ENDIF
330    
331  #ifdef USE_NO_INTERP_RUNOFF  #ifdef USE_NO_INTERP_RUNOFF
332        WRITE(msgBuf,'(A,A)') 'EXF_CHECK: USE_NO_INTERP_RUNOFF code',        WRITE(msgBuf,'(A)')
333       &        ' has been removed;'       &     'S/R EXF_CHECK: USE_NO_INTERP_RUNOFF code has been removed;'
334        CALL PRINT_ERROR( msgBuf, myThid )        CALL PRINT_ERROR( msgBuf, myThid )
335        WRITE(msgBuf,'(A,A)') 'use instead "runoff_interpMethod=0"',        WRITE(msgBuf,'(A,A)')
336         &     'S/R EXF_CHECK: use instead "runoff_interpMethod=0"',
337       &      ' in "data.exf" (EXF_NML_04)'       &      ' in "data.exf" (EXF_NML_04)'
338        CALL PRINT_ERROR( msgBuf, myThid )        CALL PRINT_ERROR( msgBuf, myThid )
339        STOP 'ABNORMAL END: S/R EXF_CHECK'        errCount = errCount + 1
340  #endif /* USE_NO_INTERP_RUNOFF */  #endif /* USE_NO_INTERP_RUNOFF */
341    
342  #ifdef ALLOW_CLIMTEMP_RELAXATION  #ifdef ALLOW_CLIMTEMP_RELAXATION
343        STOP 'ALLOW_CLIMTEMP_RELAXATION no longer supported. Use pkg/rbcs'        WRITE(msgBuf,'(A,A)') 'S/R EXF_CHECK: ',
344  #endif       &     'ALLOW_CLIMTEMP_RELAXATION no longer supported. Use pkg/rbcs'
345          CALL PRINT_ERROR( msgBuf, myThid )
346          errCount = errCount + 1
347    #endif /* ALLOW_CLIMTEMP_RELAXATION */
348    
349  #ifdef ALLOW_CLIMSALT_RELAXATION  #ifdef ALLOW_CLIMSALT_RELAXATION
350        STOP 'ALLOW_CLIMSALT_RELAXATION no longer supported. Use pkg/rbcs'        WRITE(msgBuf,'(A,A)') 'S/R EXF_CHECK: ',
351  #endif       &     'ALLOW_CLIMSALT_RELAXATION no longer supported. Use pkg/rbcs'
352          CALL PRINT_ERROR( msgBuf, myThid )
353          errCount = errCount + 1
354    #endif /* ALLOW_CLIMSALT_RELAXATION */
355    
356        IF ( climsstTauRelax.NE.0. ) THEN        IF ( climsstTauRelax.NE.0. ) THEN
357  #ifndef ALLOW_CLIMSST_RELAXATION  #ifndef ALLOW_CLIMSST_RELAXATION
358          WRITE(msgBuf,'(A)') 'EXF_CHECK: climsstTauRelax > 0'         WRITE(msgBuf,'(A)') 'S/R EXF_CHECK: climsstTauRelax > 0'
359          CALL PRINT_ERROR( msgBuf, myThid )         CALL PRINT_ERROR( msgBuf, myThid )
360          WRITE(msgBuf,'(A)')         WRITE(msgBuf,'(A)')
361       &        'but ALLOW_CLIMSST_RELAXATION is not defined'       &      'S/R EXF_CHECK: but ALLOW_CLIMSST_RELAXATION is not defined'
362          CALL PRINT_ERROR( msgBuf, myThid )         CALL PRINT_ERROR( msgBuf, myThid )
363          STOP 'ABNORMAL END: S/R EXF_CHECK'         errCount = errCount + 1
364  #endif  #endif /* ndef ALLOW_CLIMSST_RELAXATION */
365         IF ( climsstfile.EQ.' ' ) THEN         IF ( climsstfile.EQ.' ' ) THEN
366          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)') 'S/R EXF_CHECK: climsstTauRelax > 0 but'
      &     'S/R EXF_CHECK: climsstTauRelax > 0 but'  
367          CALL PRINT_ERROR( msgBuf, myThid )          CALL PRINT_ERROR( msgBuf, myThid )
368          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)') 'S/R EXF_CHECK: climsstfile is not set'
      &     'S/R EXF_CHECK: climsstfile is not set'  
369          CALL PRINT_ERROR( msgBuf, myThid )          CALL PRINT_ERROR( msgBuf, myThid )
370          STOP 'ABNORMAL END: S/R EXF_CHECK'          errCount = errCount + 1
371         ENDIf         ENDIf
372        ENDIf        ENDIf
373    
374        IF ( climsssTauRelax.NE.0. ) THEN        IF ( climsssTauRelax.NE.0. ) THEN
375  #ifndef ALLOW_CLIMSSS_RELAXATION  #ifndef ALLOW_CLIMSSS_RELAXATION
376          WRITE(msgBuf,'(A)') 'EXF_CHECK: climsssTauRelax > 0'         WRITE(msgBuf,'(A)') 'S/R EXF_CHECK: climsssTauRelax > 0'
377           CALL PRINT_ERROR( msgBuf, myThid )
378           WRITE(msgBuf,'(A)')
379         &      'S/R EXF_CHECK: but ALLOW_CLIMSSS_RELAXATION is not defined'
380           CALL PRINT_ERROR( msgBuf, myThid )
381           errCount = errCount + 1
382    #endif /* ALLOW_CLIMSSS_RELAXATION */
383           IF ( climsssfile.EQ.' ' ) THEN
384            WRITE(msgBuf,'(A)') 'S/R EXF_CHECK: climsssTauRelax > 0 but'
385          CALL PRINT_ERROR( msgBuf, myThid )          CALL PRINT_ERROR( msgBuf, myThid )
386          WRITE(msgBuf,'(A)')          WRITE(msgBuf,'(A)') 'S/R EXF_CHECK: climsssfile is not set'
387       &        'but ALLOW_CLIMSSS_RELAXATION is not defined'          CALL PRINT_ERROR( msgBuf, myThid )
388            errCount = errCount + 1
389           ENDIF
390          ENDIF
391    
392    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
393    
394          IF ( errCount.GE.1 ) THEN
395            WRITE(msgBuf,'(A,I3,A)')
396         &       'EXF_CHECK: detected', errCount,' fatal error(s)'
397          CALL PRINT_ERROR( msgBuf, myThid )          CALL PRINT_ERROR( msgBuf, myThid )
398            CALL ALL_PROC_DIE( 0 )
399          STOP 'ABNORMAL END: S/R EXF_CHECK'          STOP 'ABNORMAL END: S/R EXF_CHECK'
400  #endif        ENDIF
401         IF ( climsssfile.EQ.' ' ) THEN  
402          WRITE(msgBuf,'(A)')        _END_MASTER(myThid)
403       &     'S/R EXF_CHECK: climsssTauRelax > 0 but'  
404          RETURN
405          END
406    
407    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
408    
409    CBOP
410    C     !ROUTINE: EXF_CHECK_INTERP
411    C     !INTERFACE:
412    
413          SUBROUTINE EXF_CHECK_INTERP(
414         I               loc_name, loc_file,
415         I               loc_interpMethod, loc_nlat, loc_lon_inc,
416         U               errCount,
417         I               myThid )
418    
419    C     !DESCRIPTION: \bv
420    C     *==========================================================*
421    C     | S/R EXF_CHECK_INTERP
422    C     | o Check parameters for one of the pkg/exf variable
423    C     *==========================================================*
424    C     \ev
425    
426    C     !USES:
427          IMPLICIT NONE
428    
429    C     == Global variables ===
430    #include "EEPARAMS.h"
431    #include "EXF_PARAM.h"
432    
433    C     !INPUT/OUTPUT PARAMETERS:
434    C     myThid   :: my Thread Id number
435          CHARACTER*(*) loc_name
436          CHARACTER*(*) loc_file
437          INTEGER loc_interpMethod
438          INTEGER loc_nlat
439          _RL loc_lon_inc
440          INTEGER errCount
441          INTEGER myThid
442    
443    C     !LOCAL VARIABLES:
444    C     msgBuf   :: Informational/error message buffer
445          CHARACTER*(MAX_LEN_MBUF) msgBuf
446    CEOP
447    
448          IF ( loc_interpMethod.GE.1 .AND. loc_file.NE.' ' ) THEN
449           IF ( loc_nlat .GT. MAX_LAT_INC ) THEN
450            WRITE(msgBuf,'(3A)') 'S/R EXF_CHECK_INTERP: ',loc_name,
451         &                      '_nlat > MAX_LAT_INC'
452          CALL PRINT_ERROR( msgBuf, myThid )          CALL PRINT_ERROR( msgBuf, myThid )
453          WRITE(msgBuf,'(A)')          errCount = errCount + 1
454       &     'S/R EXF_CHECK: climsssfile is not set'         ENDIF
455           IF ( loc_lon_inc.GT.500. ) THEN
456            WRITE(msgBuf,'(4A,1PE16.8)') 'S/R EXF_CHECK_INTERP: ',
457         &    'Invalid value for: ',loc_name,'_lon_inc =', loc_lon_inc
458          CALL PRINT_ERROR( msgBuf, myThid )          CALL PRINT_ERROR( msgBuf, myThid )
459          STOP 'ABNORMAL END: S/R EXF_CHECK'          WRITE(msgBuf,'(4A)') 'S/R EXF_CHECK_INTERP: Fix it ',
460         &    'or Turn off ',loc_name,'-interp (interpMethod=0)'
461            CALL PRINT_ERROR( msgBuf, myThid )
462            errCount = errCount + 1
463         ENDIF         ENDIF
464        ENDIF        ENDIF
465    

Legend:
Removed from v.1.21  
changed lines
  Added in v.1.31

  ViewVC Help
Powered by ViewVC 1.1.22