/[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.15 by jmc, Wed Dec 21 17:20:09 2011 UTC revision 1.22 by mlosch, Mon Jan 6 14:52:38 2014 UTC
# Line 3  C $Name$ Line 3  C $Name$
3    
4  #include "EXF_OPTIONS.h"  #include "EXF_OPTIONS.h"
5    
6        subroutine exf_check( mythid )        SUBROUTINE EXF_CHECK( myThid )
7    
8  c     ==================================================================  c     ==================================================================
9  c     SUBROUTINE exf_check  c     SUBROUTINE EXF_CHECK
10  c     ==================================================================  c     ==================================================================
11  c  c
12        implicit none        IMPLICIT NONE
13    
14  c     == global variables ==  c     == global variables ==
15    
16  #include "EEPARAMS.h"  #include "EEPARAMS.h"
17  #include "SIZE.h"  #include "SIZE.h"
18  #include "PARAMS.h"  #include "PARAMS.h"
 c#include "FFIELDS.h"  
 c#include "GRID.h"  
19    
20  #include "EXF_PARAM.h"  #include "EXF_PARAM.h"
21  #include "EXF_CONSTANTS.h"  #include "EXF_CONSTANTS.h"
 c#include "EXF_FIELDS.h"  
22  c     == routine arguments ==  c     == routine arguments ==
23    
24  c     mythid - thread number for this instance of the routine.  c     myThid - thread number for this instance of the routine.
25    
26        integer mythid        INTEGER myThid
27    
28  c     == local variables ==  c     == local variables ==
29    
# Line 36  C     msgBuf   :: Informational/error me Line 33  C     msgBuf   :: Informational/error me
33  c     == end of interface ==  c     == end of interface ==
34    
35  c     check for consistency  c     check for consistency
36        if (.NOT.        IF (.NOT.
37       &     (exf_iprec.EQ.precFloat32 .OR. exf_iprec.EQ.precFloat64)       &     (exf_iprec.EQ.precFloat32 .OR. exf_iprec.EQ.precFloat64)
38       &     ) then       &     ) THEN
39         stop 'S/R EXF_CHECK: value of exf_iprec not allowed'         WRITE(msgBuf,'(A)')
40        elseif ( exf_yftype.NE.'RL' ) then       &      'S/R EXF_CHECK: value of exf_iprec not allowed'
41         stop 'S/R EXF_CHECK: value of exf_yftype not allowed'         CALL PRINT_ERROR( msgBuf, myThid )
42        endif         STOP 'ABNORMAL END: S/R EXF_CHECK'
43          ENDIF
44        if (repeatPeriod.lt.0.) then  
45         stop 'S/R EXF_CHECK: repeatPeriod must be positive'        IF (repeatPeriod.lt.0.) THEN
46        endif         WRITE(msgBuf,'(A)')
47         &      'S/R EXF_CHECK: repeatPeriod must be positive'
48        if (useExfYearlyFields.and.repeatPeriod.ne.0.) then         CALL PRINT_ERROR( msgBuf, myThid )
49         print*,'Use of usefldyearlyfields AND repeatPeriod',         STOP 'ABNORMAL END: S/R EXF_CHECK'
50       &      ' not implemented'        ENDIF
51         stop 'ABNORMAL END: S/R EXF_CHECK'  
52        endif        IF (useExfYearlyFields.and.repeatPeriod.ne.0.) THEN
53           WRITE(msgBuf,'(A,A)') 'S/R EXF_CHECK: The use of ',
54  #if ( defined (ALLOW_BULKFORMULAE) && defined (ALLOW_ATM_WIND) )       $      'useExfYearlyFields AND repeatPeriod is not implemented'
55        IF ( ustressfile .NE. ' ' .OR. ustressfile .NE. ' ' ) THEN         CALL PRINT_ERROR( msgBuf, myThid )
56          STOP         STOP 'ABNORMAL END: S/R EXF_CHECK'
57       & 'S/R EXF_CHECK: use u,v_wind components but not wind-stress'        ENDIF
58    
59    #ifdef ALLOW_BULKFORMULAE
60          IF ( useAtmWind ) THEN
61          IF ( ustressfile .NE. ' ' .OR. vstressfile .NE. ' ' ) THEN
62            WRITE(msgBuf,'(A)')
63         &   'S/R EXF_CHECK: use u,v_wind components but not wind-stress'
64            CALL PRINT_ERROR( msgBuf, myThid )
65            STOP 'ABNORMAL END: S/R EXF_CHECK'
66          ENDIF
67        ENDIF        ENDIF
68  #endif  #endif
69    
70  #ifndef ALLOW_ATM_WIND        IF ( .NOT.useAtmWind ) THEN
71        IF ( uwindfile .NE. ' ' .OR. vwindfile .NE. ' ' ) THEN         IF ( uwindfile .NE. ' ' .OR. vwindfile .NE. ' ' ) THEN
72          STOP          WRITE(msgBuf,'(A)')
73       & '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'
74            CALL PRINT_ERROR( msgBuf, myThid )
75            STOP 'ABNORMAL END: S/R EXF_CHECK'
76           ENDIF
77        ENDIF        ENDIF
 #endif  
78    
79  #ifndef ALLOW_ZENITHANGLE  #ifndef ALLOW_ZENITHANGLE
80        IF ( useExfZenAlbedo .OR. useExfZenIncoming .OR.        IF ( useExfZenAlbedo .OR. useExfZenIncoming .OR.
81       &     select_ZenAlbedo .NE. 0 ) THEN       &     select_ZenAlbedo .NE. 0 ) THEN
82          WRITE(msgBuf,'(A,A)') 'EXF_CHECK: unsupported option',          WRITE(msgBuf,'(A,A)') 'S/R EXF_CHECK: unsupported option',
83       &        ' when ALLOW_ZENITHANGLE is not defined'       &        ' when ALLOW_ZENITHANGLE is not defined'
84          CALL PRINT_ERROR( msgBuf , mythid)          CALL PRINT_ERROR( msgBuf, myThid )
85          STOP 'ABNORMAL END: S/R EXF_CHECK'          STOP 'ABNORMAL END: S/R EXF_CHECK'
86        ENDIF        ENDIF
87  #endif  #endif
88    
89  #ifdef ALLOW_ZENITHANGLE  #ifdef ALLOW_ZENITHANGLE
90        IF ( usingCartesianGrid .OR. usingCylindricalGrid ) then        IF ( usingCartesianGrid .OR. usingCylindricalGrid ) THEN
91          WRITE(msgBuf,'(A,A)') 'EXF_CHECK: ALLOW_ZENITHANGLE does ',         WRITE(msgBuf,'(A,A)') 'S/R EXF_CHECK: ALLOW_ZENITHANGLE does ',
92       &        'not work for carthesian and cylindrical grids'       &      'not work for carthesian and cylindrical grids'
93          CALL PRINT_ERROR( msgBuf , mythid)         CALL PRINT_ERROR( msgBuf, myThid )
94          STOP 'ABNORMAL END: S/R EXF_CHECK'         STOP 'ABNORMAL END: S/R EXF_CHECK'
95        ENDIF        ENDIF
96        IF ( select_ZenAlbedo.LT.0 .OR. select_ZenAlbedo.GT.3 ) then        IF ( select_ZenAlbedo.LT.0 .OR. select_ZenAlbedo.GT.3 ) THEN
97          WRITE(msgBuf,'(A,A)') 'EXF_CHECK: unsupported ',         WRITE(msgBuf,'(A,A)') 'S/R EXF_CHECK: unsupported ',
98       &        'select_ZenAlbedo choice'       &      'select_ZenAlbedo choice'
99          CALL PRINT_ERROR( msgBuf , mythid)         CALL PRINT_ERROR( msgBuf, myThid )
100          STOP 'ABNORMAL END: S/R EXF_CHECK'         STOP 'ABNORMAL END: S/R EXF_CHECK'
101          ENDIF
102          IF ( select_ZenAlbedo.EQ.2 .) THEN
103           WRITE(msgBuf,'(A,A)')
104         &      'S/R EXF_CHECK: *** WARNING *** for daily mean albedo, ',
105         &      'it is advised to use select_ZenAlbedo.EQ.1 instead of 2'
106           CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
107         &                     SQUEEZE_RIGHT, myThid )
108        ENDIF        ENDIF
109        IF ( select_ZenAlbedo.EQ.2 .) then        IF ( select_ZenAlbedo.GT.2 .AND. swdownperiod.GT. 21600 ) THEN
110          write(standardmessageunit,'(A,A)')         WRITE(msgBuf,'(A,A)') 'S/R EXF_CHECK: using diurnal albedo ',
      &  'EXF WARNING: for daily mean albedo, it is advised ',  
      &        'to use select_ZenAlbedo.EQ.1 instead of 2'  
       ENDIF  
       IF ( select_ZenAlbedo.GT.2 .AND. swdownperiod.GT. 21600 ) then  
        WRITE(msgBuf,'(A,A)') 'EXF_CHECK: using diurnal albedo ',  
111       &        'formula requires diurnal downward shortwave forcing'       &        'formula requires diurnal downward shortwave forcing'
112          CALL PRINT_ERROR( msgBuf , mythid)         CALL PRINT_ERROR( msgBuf, myThid )
113          STOP 'ABNORMAL END: S/R EXF_CHECK'         STOP 'ABNORMAL END: S/R EXF_CHECK'
114        ENDIF        ENDIF
115        IF ( select_ZenAlbedo.GT.2 .AND. swdownperiod.GT. 3600 ) then        IF ( select_ZenAlbedo.GT.2 .AND. swdownperiod.GT. 3600 ) then
116          write(standardmessageunit,'(A,A)')         WRITE(msgBuf,'(A,A,A)')
117       &  'EXF WARNING: the diurnal albedo formula is likely not safe ',       &      'S/R EXF_CHECK: *** WARNING *** ',
118       &  'for such coarse temporal resolution downward shortwave forcing'       &      'the diurnal albedo formula is likely not safe for such ',
119         &      'coarse temporal resolution downward shortwave forcing'
120           CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
121         &                     SQUEEZE_RIGHT, myThid )
122        ENDIF        ENDIF
123  #endif  #endif
124    
125  #ifdef USE_EXF_INTERPOLATION  #ifdef USE_EXF_INTERPOLATION
126        if ( climsst_nlat .GT. MAX_LAT_INC )        IF ( climsstfile .NE. ' ' ) THEN
127       & stop 'stopped in exf_readparms: climsst_nlat > MAX_LAT_INC'         IF ( climsst_nlat .GT. MAX_LAT_INC ) THEN
128        if ( climsss_nlat .GT. MAX_LAT_INC )          WRITE(msgBuf,'(A)') 'S/R EXF_CHECK: climsst_nlat > MAX_LAT_INC'
129       & stop 'stopped in exf_readparms: climsss_nlat > MAX_LAT_INC'          CALL PRINT_ERROR( msgBuf, myThid )
130        if ( usingCartesianGrid ) then          STOP 'ABNORMAL END: S/R EXF_CHECK'
131         print*,'USE_EXF_INTERPOLATION assumes latitude/longitude'         ENDIF
132         print*,'input and output coordinates.  Trivial to extend to'        ENDIF
133         print*,'cartesian coordinates, but has not yet been done.'        IF ( climsssfile .NE. ' ' ) THEN
134         stop         IF ( climsss_nlat .GT. MAX_LAT_INC ) THEN
135        endif          WRITE(msgBuf,'(A)') 'S/R EXF_CHECK: climsss_nlat > MAX_LAT_INC'
136            CALL PRINT_ERROR( msgBuf, myThid )
137            STOP 'ABNORMAL END: S/R EXF_CHECK'
138           ENDIF
139          ENDIF
140          IF ( usingCartesianGrid ) THEN
141           WRITE(msgBuf,'(A,A)') 'S/R EXF_CHECK: ',
142         &      'USE_EXF_INTERPOLATION assumes latitude/longitude'
143           CALL PRINT_ERROR( msgBuf, myThid )
144           WRITE(msgBuf,'(A,A)') 'S/R EXF_CHECK: ',
145         &      'input and output coordinates. Trivial to extend to'
146           CALL PRINT_ERROR( msgBuf, myThid )
147           WRITE(msgBuf,'(A,A)') 'S/R EXF_CHECK: ',
148         &      'cartesian coordinates, but has not yet been done.'
149           CALL PRINT_ERROR( msgBuf, myThid )
150           STOP 'ABNORMAL END: S/R EXF_CHECK'
151          ENDIF
152  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)
153        IF ( ( uwind_interpMethod.GE.1 .AND. uwindfile.NE.' ' ) .OR.        IF ( ( uwind_interpMethod.GE.1 .AND. uwindfile.NE.' ' ) .OR.
154       &     ( vwind_interpMethod.GE.1 .AND. vwindfile.NE.' ' ) ) THEN       &     ( vwind_interpMethod.GE.1 .AND. vwindfile.NE.' ' ) ) THEN
155         IF ( usingCurvilinearGrid .OR. rotateGrid ) THEN         IF ( usingCurvilinearGrid .OR. rotateGrid ) THEN
156           IF ( uwind_interpMethod.EQ.0 .OR. uwindfile.EQ.' ' .OR.          IF ( uwind_interpMethod.EQ.0 .OR. uwindfile.EQ.' ' .OR.
157       &        vwind_interpMethod.EQ.0 .OR. vwindfile.EQ.' ' ) THEN       &       vwind_interpMethod.EQ.0 .OR. vwindfile.EQ.' ' ) THEN
158  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
159            STOP 'interp. needs 2 components (wind)'           WRITE(msgBuf,'(A)')
160           ENDIF       &        'S/R EXF_CHECK: interp. needs 2 components (wind)'
161           IF ( uwindstartdate .NE. vwindstartdate .OR.           CALL PRINT_ERROR( msgBuf, myThid )
162       &        uwindperiod    .NE. vwindperiod   ) THEN           STOP 'ABNORMAL END: S/R EXF_CHECK'
163            print*,'For CurvilinearGrid/RotatedGrid, S/R EXF_SET_UV'          ENDIF
164            print*,'assumes that the u and v wind files'          IF ( uwindstartdate .NE. vwindstartdate .OR.
165            print*,'have the same startdate and period.'       &       uwindperiod    .NE. vwindperiod   ) THEN
166            stop           WRITE(msgBuf,'(A,A)') 'S/R EXF_CHECK: ',
167           ENDIF       &        'For CurvilinearGrid/RotatedGrid, the u and v wind '
168             CALL PRINT_ERROR( msgBuf, myThid )
169             WRITE(msgBuf,'(A,A,A)') 'S/R EXF_CHECK: ',
170         &        'files have to have the same startdate and period, ',
171         &        'because S/R EXF_SET_UV assumes that.'
172             CALL PRINT_ERROR( msgBuf, myThid )
173             STOP 'ABNORMAL END: S/R EXF_CHECK'
174            ENDIF
175         ENDIF         ENDIF
176        ENDIF        ENDIF
177        IF ( (ustress_interpMethod.GE.1 .AND. ustressfile.NE.' ') .OR.        IF ( (ustress_interpMethod.GE.1 .AND. ustressfile.NE.' ') .OR.
178       &     (vstress_interpMethod.GE.1 .AND. vstressfile.NE.' ') ) THEN       &     (vstress_interpMethod.GE.1 .AND. vstressfile.NE.' ') ) THEN
179         IF ( readStressOnCgrid ) THEN         IF ( readStressOnCgrid ) THEN
180            STOP 'readStressOnCgrid and interp wind-stress (=A-grid)'          WRITE(msgBuf,'(A,A)')
181         &       'S/R EXF_CHECK: readStressOnCgrid=.TRUE. ',
182         &       'and interp wind-stress (=A-grid) are not compatible'
183            CALL PRINT_ERROR( msgBuf, myThid )
184            STOP 'ABNORMAL END: S/R EXF_CHECK'
185         ENDIF         ENDIF
186         IF ( usingCurvilinearGrid .OR. rotateGrid ) THEN         IF ( usingCurvilinearGrid .OR. rotateGrid ) THEN
187           IF ( ustress_interpMethod.EQ.0 .OR. ustressfile.EQ.' ' .OR.          IF ( ustress_interpMethod.EQ.0 .OR. ustressfile.EQ.' ' .OR.
188       &        vstress_interpMethod.EQ.0 .OR. vstressfile.EQ.' ' ) THEN       &       vstress_interpMethod.EQ.0 .OR. vstressfile.EQ.' ' ) THEN
189  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
190            STOP 'interp. needs 2 components (wind-stress)'           WRITE(msgBuf,'(A)')
191           ENDIF       &        'S/R EXF_CHECK: interp. needs 2 components (wind-stress)'
192           IF ( ustressstartdate .NE. vstressstartdate .OR.           CALL PRINT_ERROR( msgBuf, myThid )
193       &        ustressperiod    .NE. vstressperiod   ) THEN           STOP 'ABNORMAL END: S/R EXF_CHECK'
194            print*,'For CurvilinearGrid/RotatedGrid, S/R EXF_SET_UV'          ENDIF
195            print*,'assumes that the u and v wind stress files'          IF ( ustressstartdate .NE. vstressstartdate .OR.
196            print*,'have the same startdate and period.'       &       ustressperiod    .NE. vstressperiod   ) THEN
197            stop           WRITE(msgBuf,'(A,A)') 'S/R EXF_CHECK: ',
198           ENDIF       &    'For CurvilinearGrid/RotatedGrid, the u and v wind stress '
199             CALL PRINT_ERROR( msgBuf, myThid )
200             WRITE(msgBuf,'(A,A,A)') 'S/R EXF_CHECK: ',
201         &        'files have to have the same startdate and period, ',
202         &        'because S/R EXF_SET_UV assumes that.'
203             CALL PRINT_ERROR( msgBuf, myThid )
204             STOP 'ABNORMAL END: S/R EXF_CHECK'
205            ENDIF
206         ENDIF         ENDIF
207        ENDIF        ENDIF
208    
# Line 164  C-    stop if one expects interp+rotatio Line 211  C-    stop if one expects interp+rotatio
211  #else /* ifndef USE_EXF_INTERPOLATION */  #else /* ifndef USE_EXF_INTERPOLATION */
212        IF     ( ustressfile .NE. ' ' .OR. vstressfile .NE. ' ' ) THEN        IF     ( ustressfile .NE. ' ' .OR. vstressfile .NE. ' ' ) THEN
213  #endif /* USE_EXF_INTERPOLATION */  #endif /* USE_EXF_INTERPOLATION */
214          IF ( (readStressOnAgrid.AND.readStressOnCgrid) .OR.         IF (     (readStressOnAgrid.AND.readStressOnCgrid) .OR.
215       &   .NOT.(readStressOnAgrid.OR.readStressOnCgrid) ) THEN       &      .NOT.(readStressOnAgrid.OR.readStressOnCgrid) ) THEN
216            STOP          WRITE(msgBuf,'(A)')
217       & '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'
218          ENDIF          CALL PRINT_ERROR( msgBuf, myThid )
219            STOP 'ABNORMAL END: S/R EXF_CHECK'
220           ENDIF
221        ELSE        ELSE
222          IF ( readStressOnAgrid .OR. readStressOnCgrid ) THEN         IF ( readStressOnAgrid .OR. readStressOnCgrid ) THEN
223            STOP 'S/R EXF_CHECK: wind-stress position irrelevant'          WRITE(msgBuf,'(A)')
224          ENDIF       &       'S/R EXF_CHECK: wind-stress position irrelevant'
225            CALL PRINT_ERROR( msgBuf, myThid )
226            STOP 'ABNORMAL END: S/R EXF_CHECK'
227           ENDIF
228        ENDIF        ENDIF
229    
230  #ifdef USE_NO_INTERP_RUNOFF  #ifdef USE_NO_INTERP_RUNOFF
231        WRITE(msgBuf,'(A,A)') 'EXF_CHECK: USE_NO_INTERP_RUNOFF code',        WRITE(msgBuf,'(A)')
232       &        ' has been removed;'       &     'S/R EXF_CHECK: USE_NO_INTERP_RUNOFF code has been removed;'
233        CALL PRINT_ERROR( msgBuf, myThid )        CALL PRINT_ERROR( msgBuf, myThid )
234        WRITE(msgBuf,'(A,A)') 'use instead "runoff_interpMethod=0"',        WRITE(msgBuf,'(A,A)')
235         &     'S/R EXF_CHECK: use instead "runoff_interpMethod=0"',
236       &      ' in "data.exf" (EXF_NML_04)'       &      ' in "data.exf" (EXF_NML_04)'
237        CALL PRINT_ERROR( msgBuf, myThid )        CALL PRINT_ERROR( msgBuf, myThid )
238        STOP 'ABNORMAL END: S/R EXF_CHECK'        STOP 'ABNORMAL END: S/R EXF_CHECK'
239  #endif /* USE_NO_INTERP_RUNOFF */  #endif /* USE_NO_INTERP_RUNOFF */
240    
241  #ifdef ALLOW_CLIMTEMP_RELAXATION  #ifdef ALLOW_CLIMTEMP_RELAXATION
242        STOP 'ALLOW_CLIMTEMP_RELAXATION no longer supported. Use pkg/rbcs'        WRITE(msgBuf,'(A,A)') 'S/R EXF_CHECK: ',
243         &     'ALLOW_CLIMTEMP_RELAXATION no longer supported. Use pkg/rbcs'
244          CALL PRINT_ERROR( msgBuf, myThid )
245          STOP 'ABNORMAL END: S/R EXF_CHECK'
246  #endif  #endif
247    
248  #ifdef ALLOW_CLIMSALT_RELAXATION  #ifdef ALLOW_CLIMSALT_RELAXATION
249        STOP 'ALLOW_CLIMSALT_RELAXATION no longer supported. Use pkg/rbcs'        WRITE(msgBuf,'(A,A)') 'S/R EXF_CHECK: ',
250         &     'ALLOW_CLIMSALT_RELAXATION no longer supported. Use pkg/rbcs'
251          CALL PRINT_ERROR( msgBuf, myThid )
252          STOP 'ABNORMAL END: S/R EXF_CHECK'
253  #endif  #endif
254    
255          IF ( climsstTauRelax.NE.0. ) THEN
256    #ifndef ALLOW_CLIMSST_RELAXATION
257           WRITE(msgBuf,'(A)') 'S/R EXF_CHECK: climsstTauRelax > 0'
258           CALL PRINT_ERROR( msgBuf, myThid )
259           WRITE(msgBuf,'(A)')
260         &      'S/R EXF_CHECK: but ALLOW_CLIMSST_RELAXATION is not defined'
261           CALL PRINT_ERROR( msgBuf, myThid )
262           STOP 'ABNORMAL END: S/R EXF_CHECK'
263    #endif
264           IF ( climsstfile.EQ.' ' ) THEN
265            WRITE(msgBuf,'(A)') 'S/R EXF_CHECK: climsstTauRelax > 0 but'
266            CALL PRINT_ERROR( msgBuf, myThid )
267            WRITE(msgBuf,'(A)') 'S/R EXF_CHECK: climsstfile is not set'
268            CALL PRINT_ERROR( msgBuf, myThid )
269            STOP 'ABNORMAL END: S/R EXF_CHECK'
270           ENDIf
271          ENDIf
272          
273          IF ( climsssTauRelax.NE.0. ) THEN
274    #ifndef ALLOW_CLIMSSS_RELAXATION
275           WRITE(msgBuf,'(A)') 'S/R EXF_CHECK: climsssTauRelax > 0'
276           CALL PRINT_ERROR( msgBuf, myThid )
277           WRITE(msgBuf,'(A)')
278         &      'S/R EXF_CHECK: but ALLOW_CLIMSSS_RELAXATION is not defined'
279           CALL PRINT_ERROR( msgBuf, myThid )
280           STOP 'ABNORMAL END: S/R EXF_CHECK'
281    #endif
282           IF ( climsssfile.EQ.' ' ) THEN
283            WRITE(msgBuf,'(A)') 'S/R EXF_CHECK: climsssTauRelax > 0 but'
284            CALL PRINT_ERROR( msgBuf, myThid )
285            WRITE(msgBuf,'(A)') 'S/R EXF_CHECK: climsssfile is not set'
286            CALL PRINT_ERROR( msgBuf, myThid )
287            STOP 'ABNORMAL END: S/R EXF_CHECK'
288           ENDIF
289          ENDIF
290    
291        RETURN        RETURN
292        END        END

Legend:
Removed from v.1.15  
changed lines
  Added in v.1.22

  ViewVC Help
Powered by ViewVC 1.1.22