/[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.5 by heimbach, Wed Apr 18 19:55:34 2007 UTC revision 1.17 by jmc, Tue Jul 24 20:16:32 2012 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"
 #include "FFIELDS.h"  
 #include "GRID.h"  
19    
20  #include "EXF_PARAM.h"  #include "EXF_PARAM.h"
21  #include "EXF_CONSTANTS.h"  #include "EXF_CONSTANTS.h"
 #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    
30        integer bi,bj  C     msgBuf   :: Informational/error message buffer
31        integer i,j        CHARACTER*(MAX_LEN_MBUF) msgBuf
       integer jtlo  
       integer jthi  
       integer itlo  
       integer ithi  
       integer jmin  
       integer jmax  
       integer imin  
       integer imax  
32    
33  c     == end of interface ==  c     == end of interface ==
34    
       jtlo = mybylo(mythid)  
       jthi = mybyhi(mythid)  
       itlo = mybxlo(mythid)  
       ithi = mybxhi(mythid)  
       jmin = 1-oly  
       jmax = sny+oly  
       imin = 1-olx  
       imax = snx+olx  
   
35  c     check for consistency  c     check for consistency
36        if (.NOT.        if (.NOT.
37       &     (exf_iprec .EQ. 32 .OR. exf_iprec .EQ. 64)       &     (exf_iprec.EQ.precFloat32 .OR. exf_iprec.EQ.precFloat64)
38       &     ) then       &     ) then
39           stop 'stop in exf_readparms: value of exf_iprec not allowed'         stop 'S/R EXF_CHECK: value of exf_iprec not allowed'
40        else if (.NOT.        endif
41       &        (exf_yftype .EQ. 'RS' .OR.  
42       &        exf_yftype .EQ. 'RL')        if (repeatPeriod.lt.0.) then
43       &        ) then         stop 'S/R EXF_CHECK: repeatPeriod must be positive'
44           stop 'stop in exf_readparms: value of exf_yftype not allowed'        endif
45        end if  
46          if (useExfYearlyFields.and.repeatPeriod.ne.0.) then
47        if ( useCubedSphereExchange ) then         print*,'Use of usefldyearlyfields AND repeatPeriod',
48  cph         if ( uvecfile .NE. ' ' .and. vvecfile .NE. ' ' ) then       &      ' not implemented'
49  c     some restrictions that can be relaxed later on         stop 'ABNORMAL END: S/R EXF_CHECK'
 cph            if ( uvecstartdate .ne. vvecstartdate .or.  
 cph     &           uvecperiod    .ne. vvecperiod ) then  
 cph               print*,'For useCubedSphereExchange, S/R exf_set_uv.F'  
 cph               print*,'assumes that the u and v wind or wind stress'  
 cph               print*,'files have the same startdate and period.'  
 cph               stop  
 cph            endif  
 cph         endif  
50        endif        endif
51    
52    #if ( defined (ALLOW_BULKFORMULAE) && defined (ALLOW_ATM_WIND) )
53          IF ( ustressfile .NE. ' ' .OR. ustressfile .NE. ' ' ) THEN
54            STOP
55         & 'S/R EXF_CHECK: use u,v_wind components but not wind-stress'
56          ENDIF
57    #endif
58    
59    #ifndef ALLOW_ATM_WIND
60          IF ( uwindfile .NE. ' ' .OR. vwindfile .NE. ' ' ) THEN
61            STOP
62         & 'S/R EXF_CHECK: read-in wind-stress but not u,v_wind components'
63          ENDIF
64    #endif
65    
66    #ifndef ALLOW_ZENITHANGLE
67          IF ( useExfZenAlbedo .OR. useExfZenIncoming .OR.
68         &     select_ZenAlbedo .NE. 0 ) THEN
69            WRITE(msgBuf,'(A,A)') 'EXF_CHECK: unsupported option',
70         &        ' when ALLOW_ZENITHANGLE is not defined'
71            CALL PRINT_ERROR( msgBuf, myThid )
72            STOP 'ABNORMAL END: S/R EXF_CHECK'
73          ENDIF
74    #endif
75    
76    #ifdef ALLOW_ZENITHANGLE
77          IF ( usingCartesianGrid .OR. usingCylindricalGrid ) then
78            WRITE(msgBuf,'(A,A)') 'EXF_CHECK: ALLOW_ZENITHANGLE does ',
79         &        'not work for carthesian and cylindrical grids'
80            CALL PRINT_ERROR( msgBuf, myThid )
81            STOP 'ABNORMAL END: S/R EXF_CHECK'
82          ENDIF
83          IF ( select_ZenAlbedo.LT.0 .OR. select_ZenAlbedo.GT.3 ) then
84            WRITE(msgBuf,'(A,A)') 'EXF_CHECK: unsupported ',
85         &        'select_ZenAlbedo choice'
86            CALL PRINT_ERROR( msgBuf, myThid )
87            STOP 'ABNORMAL END: S/R EXF_CHECK'
88          ENDIF
89          IF ( select_ZenAlbedo.EQ.2 .) then
90            write(standardmessageunit,'(A,A)')
91         &  'EXF WARNING: for daily mean albedo, it is advised ',
92         &        'to use select_ZenAlbedo.EQ.1 instead of 2'
93          ENDIF
94          IF ( select_ZenAlbedo.GT.2 .AND. swdownperiod.GT. 21600 ) then
95           WRITE(msgBuf,'(A,A)') 'EXF_CHECK: using diurnal albedo ',
96         &        'formula requires diurnal downward shortwave forcing'
97            CALL PRINT_ERROR( msgBuf, myThid )
98            STOP 'ABNORMAL END: S/R EXF_CHECK'
99          ENDIF
100          IF ( select_ZenAlbedo.GT.2 .AND. swdownperiod.GT. 3600 ) then
101            write(standardmessageunit,'(A,A)')
102         &  'EXF WARNING: the diurnal albedo formula is likely not safe ',
103         &  'for such coarse temporal resolution downward shortwave forcing'
104          ENDIF
105    #endif
106    
107  #ifdef USE_EXF_INTERPOLATION  #ifdef USE_EXF_INTERPOLATION
108          if ( climsst_nlat .GT. MAX_LAT_INC )
109         & stop 'stopped in exf_readparms: climsst_nlat > MAX_LAT_INC'
110          if ( climsss_nlat .GT. MAX_LAT_INC )
111         & stop 'stopped in exf_readparms: climsss_nlat > MAX_LAT_INC'
112        if ( usingCartesianGrid ) then        if ( usingCartesianGrid ) then
113         print*,'USE_EXF_INTERPOLATION assumes latitude/longitude'         print*,'USE_EXF_INTERPOLATION assumes latitude/longitude'
114         print*,'input and output coordinates.  Trivial to extend to'         print*,'input and output coordinates.  Trivial to extend to'
115         print*,'cartesian coordinates, but has not yet been done.'         print*,'cartesian coordinates, but has not yet been done.'
116         stop         stop
117        endif        endif
118  #endif  C-    some restrictions on 2-component vector field (might be relaxed later on)
119          IF ( ( uwind_interpMethod.GE.1 .AND. uwindfile.NE.' ' ) .OR.
120         &     ( vwind_interpMethod.GE.1 .AND. vwindfile.NE.' ' ) ) THEN
121           IF ( usingCurvilinearGrid .OR. rotateGrid ) THEN
122             IF ( uwind_interpMethod.EQ.0 .OR. uwindfile.EQ.' ' .OR.
123         &        vwind_interpMethod.EQ.0 .OR. vwindfile.EQ.' ' ) THEN
124    C-    stop if one expects interp+rotation (Curvilin-G) which will not happen
125              STOP 'interp. needs 2 components (wind)'
126             ENDIF
127             IF ( uwindstartdate .NE. vwindstartdate .OR.
128         &        uwindperiod    .NE. vwindperiod   ) THEN
129              print*,'For CurvilinearGrid/RotatedGrid, S/R EXF_SET_UV'
130              print*,'assumes that the u and v wind files'
131              print*,'have the same startdate and period.'
132              stop
133             ENDIF
134           ENDIF
135          ENDIF
136          IF ( (ustress_interpMethod.GE.1 .AND. ustressfile.NE.' ') .OR.
137         &     (vstress_interpMethod.GE.1 .AND. vstressfile.NE.' ') ) THEN
138           IF ( readStressOnCgrid ) THEN
139              STOP 'readStressOnCgrid and interp wind-stress (=A-grid)'
140           ENDIF
141           IF ( usingCurvilinearGrid .OR. rotateGrid ) THEN
142             IF ( ustress_interpMethod.EQ.0 .OR. ustressfile.EQ.' ' .OR.
143         &        vstress_interpMethod.EQ.0 .OR. vstressfile.EQ.' ' ) THEN
144    C-    stop if one expects interp+rotation (Curvilin-G) which will not happen
145              STOP 'interp. needs 2 components (wind-stress)'
146             ENDIF
147             IF ( ustressstartdate .NE. vstressstartdate .OR.
148         &        ustressperiod    .NE. vstressperiod   ) THEN
149              print*,'For CurvilinearGrid/RotatedGrid, S/R EXF_SET_UV'
150              print*,'assumes that the u and v wind stress files'
151              print*,'have the same startdate and period.'
152              stop
153             ENDIF
154           ENDIF
155          ENDIF
156    
157          IF ( (ustress_interpMethod.EQ.0 .AND. ustressfile.NE.' ') .OR.
158         &     (vstress_interpMethod.EQ.0 .AND. vstressfile.NE.' ') ) THEN
159    #else /* ifndef USE_EXF_INTERPOLATION */
160          IF     ( ustressfile .NE. ' ' .OR. vstressfile .NE. ' ' ) THEN
161    #endif /* USE_EXF_INTERPOLATION */
162            IF ( (readStressOnAgrid.AND.readStressOnCgrid) .OR.
163         &   .NOT.(readStressOnAgrid.OR.readStressOnCgrid) ) THEN
164              STOP
165         & 'S/R EXF_CHECK: Select 1 wind-stress position: A or C-grid'
166            ENDIF
167          ELSE
168            IF ( readStressOnAgrid .OR. readStressOnCgrid ) THEN
169              STOP 'S/R EXF_CHECK: wind-stress position irrelevant'
170            ENDIF
171          ENDIF
172    
173    #ifdef USE_NO_INTERP_RUNOFF
174          WRITE(msgBuf,'(A,A)') 'EXF_CHECK: USE_NO_INTERP_RUNOFF code',
175         &        ' has been removed;'
176          CALL PRINT_ERROR( msgBuf, myThid )
177          WRITE(msgBuf,'(A,A)') 'use instead "runoff_interpMethod=0"',
178         &      ' in "data.exf" (EXF_NML_04)'
179          CALL PRINT_ERROR( msgBuf, myThid )
180          STOP 'ABNORMAL END: S/R EXF_CHECK'
181    #endif /* USE_NO_INTERP_RUNOFF */
182    
183  #ifdef ALLOW_CLIMTEMP_RELAXATION  #ifdef ALLOW_CLIMTEMP_RELAXATION
184        STOP 'ALLOW_CLIMTEMP_RELAXATION no longer supported. Use pkg/rbcs'        STOP 'ALLOW_CLIMTEMP_RELAXATION no longer supported. Use pkg/rbcs'
185  #endif  #endif
186    
   
187  #ifdef ALLOW_CLIMSALT_RELAXATION  #ifdef ALLOW_CLIMSALT_RELAXATION
188        STOP 'ALLOW_CLIMSALT_RELAXATION no longer supported. Use pkg/rbcs'        STOP 'ALLOW_CLIMSALT_RELAXATION no longer supported. Use pkg/rbcs'
189  #endif  #endif
190    
191        end        IF ( climsstTauRelax.NE.0. ) THEN
192    #ifndef ALLOW_CLIMSST_RELAXATION
193            WRITE(msgBuf,'(A)') 'EXF_CHECK: climsstTauRelax > 0'
194            CALL PRINT_ERROR( msgBuf, myThid )
195            WRITE(msgBuf,'(A)')
196         &        'but ALLOW_CLIMSST_RELAXATION is not defined'
197            CALL PRINT_ERROR( msgBuf, myThid )
198            STOP 'ABNORMAL END: S/R EXF_CHECK'
199    #endif
200           IF ( climsstfile.EQ.' ' ) THEN
201            WRITE(msgBuf,'(A)')
202         &     'S/R EXF_CHECK: climsstTauRelax > 0 but'
203            CALL PRINT_ERROR( msgBuf, myThid )
204            WRITE(msgBuf,'(A)')
205         &     'S/R EXF_CHECK: climsstfile is not set'
206            CALL PRINT_ERROR( msgBuf, myThid )
207            STOP 'ABNORMAL END: S/R EXF_CHECK'
208           ENDIf
209          ENDIf
210    
211          IF ( climsssTauRelax.NE.0. ) THEN
212    #ifndef ALLOW_CLIMSSS_RELAXATION
213            WRITE(msgBuf,'(A)') 'EXF_CHECK: climsssTauRelax > 0'
214            CALL PRINT_ERROR( msgBuf, myThid )
215            WRITE(msgBuf,'(A)')
216         &        'but ALLOW_CLIMSSS_RELAXATION is not defined'
217            CALL PRINT_ERROR( msgBuf, myThid )
218            STOP 'ABNORMAL END: S/R EXF_CHECK'
219    #endif
220           IF ( climsssfile.EQ.' ' ) THEN
221            WRITE(msgBuf,'(A)')
222         &     'S/R EXF_CHECK: climsssTauRelax > 0 but'
223            CALL PRINT_ERROR( msgBuf, myThid )
224            WRITE(msgBuf,'(A)')
225         &     'S/R EXF_CHECK: climsssfile is not set'
226            CALL PRINT_ERROR( msgBuf, myThid )
227            STOP 'ABNORMAL END: S/R EXF_CHECK'
228           ENDIF
229          ENDIF
230    
231          RETURN
232          END

Legend:
Removed from v.1.5  
changed lines
  Added in v.1.17

  ViewVC Help
Powered by ViewVC 1.1.22