/[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.4 by jmc, Mon Apr 16 23:27:20 2007 UTC revision 1.21 by dimitri, Sat Apr 20 21:37:28 2013 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"  
 #include "EXF_CLIM_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    #ifdef ALLOW_BULKFORMULAE
53          IF ( useAtmWind ) THEN
54          IF ( ustressfile .NE. ' ' .OR. ustressfile .NE. ' ' ) THEN
55            STOP
56         & 'S/R EXF_CHECK: use u,v_wind components but not wind-stress'
57          ENDIF
58          ENDIF
59    #endif
60    
61          IF ( .NOT.useAtmWind ) THEN
62          IF ( uwindfile .NE. ' ' .OR. vwindfile .NE. ' ' ) THEN
63            STOP
64         & 'S/R EXF_CHECK: read-in wind-stress but not u,v_wind components'
65          ENDIF
66          ENDIF
67    
68    #ifndef ALLOW_ZENITHANGLE
69          IF ( useExfZenAlbedo .OR. useExfZenIncoming .OR.
70         &     select_ZenAlbedo .NE. 0 ) THEN
71            WRITE(msgBuf,'(A,A)') 'EXF_CHECK: unsupported option',
72         &        ' when ALLOW_ZENITHANGLE is not defined'
73            CALL PRINT_ERROR( msgBuf, myThid )
74            STOP 'ABNORMAL END: S/R EXF_CHECK'
75          ENDIF
76    #endif
77    
78    #ifdef ALLOW_ZENITHANGLE
79          IF ( usingCartesianGrid .OR. usingCylindricalGrid ) then
80            WRITE(msgBuf,'(A,A)') 'EXF_CHECK: ALLOW_ZENITHANGLE does ',
81         &        'not work for carthesian and cylindrical grids'
82            CALL PRINT_ERROR( msgBuf, myThid )
83            STOP 'ABNORMAL END: S/R EXF_CHECK'
84          ENDIF
85          IF ( select_ZenAlbedo.LT.0 .OR. select_ZenAlbedo.GT.3 ) then
86            WRITE(msgBuf,'(A,A)') 'EXF_CHECK: unsupported ',
87         &        'select_ZenAlbedo choice'
88            CALL PRINT_ERROR( msgBuf, myThid )
89            STOP 'ABNORMAL END: S/R EXF_CHECK'
90          ENDIF
91          IF ( select_ZenAlbedo.EQ.2 .) then
92            write(standardmessageunit,'(A,A)')
93         &  'EXF WARNING: for daily mean albedo, it is advised ',
94         &        'to use select_ZenAlbedo.EQ.1 instead of 2'
95          ENDIF
96          IF ( select_ZenAlbedo.GT.2 .AND. swdownperiod.GT. 21600 ) then
97           WRITE(msgBuf,'(A,A)') 'EXF_CHECK: using diurnal albedo ',
98         &        'formula requires diurnal downward shortwave forcing'
99            CALL PRINT_ERROR( msgBuf, myThid )
100            STOP 'ABNORMAL END: S/R EXF_CHECK'
101          ENDIF
102          IF ( select_ZenAlbedo.GT.2 .AND. swdownperiod.GT. 3600 ) then
103            write(standardmessageunit,'(A,A)')
104         &  'EXF WARNING: the diurnal albedo formula is likely not safe ',
105         &  'for such coarse temporal resolution downward shortwave forcing'
106          ENDIF
107    #endif
108    
109  #ifdef USE_EXF_INTERPOLATION  #ifdef USE_EXF_INTERPOLATION
110          IF ( climsstfile .NE. ' ' ) THEN
111           IF ( climsst_nlat .GT. MAX_LAT_INC )
112         &  STOP 'stopped in exf_readparms: climsst_nlat > MAX_LAT_INC'
113          ENDIF
114          IF ( climsssfile .NE. ' ' ) THEN
115           IF ( climsss_nlat .GT. MAX_LAT_INC )
116         &  STOP 'stopped in exf_readparms: climsss_nlat > MAX_LAT_INC'
117          ENDIF
118        if ( usingCartesianGrid ) then        if ( usingCartesianGrid ) then
119         print*,'USE_EXF_INTERPOLATION assumes latitude/longitude'         print*,'USE_EXF_INTERPOLATION assumes latitude/longitude'
120         print*,'input and output coordinates.  Trivial to extend to'         print*,'input and output coordinates.  Trivial to extend to'
121         print*,'cartesian coordinates, but has not yet been done.'         print*,'cartesian coordinates, but has not yet been done.'
122         stop         stop
123        endif        endif
124  #endif  C-    some restrictions on 2-component vector field (might be relaxed later on)
125          IF ( ( uwind_interpMethod.GE.1 .AND. uwindfile.NE.' ' ) .OR.
126         &     ( vwind_interpMethod.GE.1 .AND. vwindfile.NE.' ' ) ) THEN
127           IF ( usingCurvilinearGrid .OR. rotateGrid ) THEN
128             IF ( uwind_interpMethod.EQ.0 .OR. uwindfile.EQ.' ' .OR.
129         &        vwind_interpMethod.EQ.0 .OR. vwindfile.EQ.' ' ) THEN
130    C-    stop if one expects interp+rotation (Curvilin-G) which will not happen
131              STOP 'interp. needs 2 components (wind)'
132             ENDIF
133             IF ( uwindstartdate .NE. vwindstartdate .OR.
134         &        uwindperiod    .NE. vwindperiod   ) THEN
135              print*,'For CurvilinearGrid/RotatedGrid, S/R EXF_SET_UV'
136              print*,'assumes that the u and v wind files'
137              print*,'have the same startdate and period.'
138              stop
139             ENDIF
140           ENDIF
141          ENDIF
142          IF ( (ustress_interpMethod.GE.1 .AND. ustressfile.NE.' ') .OR.
143         &     (vstress_interpMethod.GE.1 .AND. vstressfile.NE.' ') ) THEN
144           IF ( readStressOnCgrid ) THEN
145              STOP 'readStressOnCgrid and interp wind-stress (=A-grid)'
146           ENDIF
147           IF ( usingCurvilinearGrid .OR. rotateGrid ) THEN
148             IF ( ustress_interpMethod.EQ.0 .OR. ustressfile.EQ.' ' .OR.
149         &        vstress_interpMethod.EQ.0 .OR. vstressfile.EQ.' ' ) THEN
150    C-    stop if one expects interp+rotation (Curvilin-G) which will not happen
151              STOP 'interp. needs 2 components (wind-stress)'
152             ENDIF
153             IF ( ustressstartdate .NE. vstressstartdate .OR.
154         &        ustressperiod    .NE. vstressperiod   ) THEN
155              print*,'For CurvilinearGrid/RotatedGrid, S/R EXF_SET_UV'
156              print*,'assumes that the u and v wind stress files'
157              print*,'have the same startdate and period.'
158              stop
159             ENDIF
160           ENDIF
161          ENDIF
162    
163          IF ( (ustress_interpMethod.EQ.0 .AND. ustressfile.NE.' ') .OR.
164         &     (vstress_interpMethod.EQ.0 .AND. vstressfile.NE.' ') ) THEN
165    #else /* ifndef USE_EXF_INTERPOLATION */
166          IF     ( ustressfile .NE. ' ' .OR. vstressfile .NE. ' ' ) THEN
167    #endif /* USE_EXF_INTERPOLATION */
168            IF ( (readStressOnAgrid.AND.readStressOnCgrid) .OR.
169         &   .NOT.(readStressOnAgrid.OR.readStressOnCgrid) ) THEN
170              STOP
171         & 'S/R EXF_CHECK: Select 1 wind-stress position: A or C-grid'
172            ENDIF
173          ELSE
174            IF ( readStressOnAgrid .OR. readStressOnCgrid ) THEN
175              STOP 'S/R EXF_CHECK: wind-stress position irrelevant'
176            ENDIF
177          ENDIF
178    
179    #ifdef USE_NO_INTERP_RUNOFF
180          WRITE(msgBuf,'(A,A)') 'EXF_CHECK: USE_NO_INTERP_RUNOFF code',
181         &        ' has been removed;'
182          CALL PRINT_ERROR( msgBuf, myThid )
183          WRITE(msgBuf,'(A,A)') 'use instead "runoff_interpMethod=0"',
184         &      ' in "data.exf" (EXF_NML_04)'
185          CALL PRINT_ERROR( msgBuf, myThid )
186          STOP 'ABNORMAL END: S/R EXF_CHECK'
187    #endif /* USE_NO_INTERP_RUNOFF */
188    
189  #ifdef ALLOW_CLIMTEMP_RELAXATION  #ifdef ALLOW_CLIMTEMP_RELAXATION
190        STOP 'ALLOW_CLIMTEMP_RELAXATION no longer supported. Use pkg/rbcs'        STOP 'ALLOW_CLIMTEMP_RELAXATION no longer supported. Use pkg/rbcs'
191  #endif  #endif
192    
   
193  #ifdef ALLOW_CLIMSALT_RELAXATION  #ifdef ALLOW_CLIMSALT_RELAXATION
194        STOP 'ALLOW_CLIMSALT_RELAXATION no longer supported. Use pkg/rbcs'        STOP 'ALLOW_CLIMSALT_RELAXATION no longer supported. Use pkg/rbcs'
195  #endif  #endif
196    
197        end        IF ( climsstTauRelax.NE.0. ) THEN
198    #ifndef ALLOW_CLIMSST_RELAXATION
199            WRITE(msgBuf,'(A)') 'EXF_CHECK: climsstTauRelax > 0'
200            CALL PRINT_ERROR( msgBuf, myThid )
201            WRITE(msgBuf,'(A)')
202         &        'but ALLOW_CLIMSST_RELAXATION is not defined'
203            CALL PRINT_ERROR( msgBuf, myThid )
204            STOP 'ABNORMAL END: S/R EXF_CHECK'
205    #endif
206           IF ( climsstfile.EQ.' ' ) THEN
207            WRITE(msgBuf,'(A)')
208         &     'S/R EXF_CHECK: climsstTauRelax > 0 but'
209            CALL PRINT_ERROR( msgBuf, myThid )
210            WRITE(msgBuf,'(A)')
211         &     'S/R EXF_CHECK: climsstfile is not set'
212            CALL PRINT_ERROR( msgBuf, myThid )
213            STOP 'ABNORMAL END: S/R EXF_CHECK'
214           ENDIf
215          ENDIf
216    
217          IF ( climsssTauRelax.NE.0. ) THEN
218    #ifndef ALLOW_CLIMSSS_RELAXATION
219            WRITE(msgBuf,'(A)') 'EXF_CHECK: climsssTauRelax > 0'
220            CALL PRINT_ERROR( msgBuf, myThid )
221            WRITE(msgBuf,'(A)')
222         &        'but ALLOW_CLIMSSS_RELAXATION is not defined'
223            CALL PRINT_ERROR( msgBuf, myThid )
224            STOP 'ABNORMAL END: S/R EXF_CHECK'
225    #endif
226           IF ( climsssfile.EQ.' ' ) THEN
227            WRITE(msgBuf,'(A)')
228         &     'S/R EXF_CHECK: climsssTauRelax > 0 but'
229            CALL PRINT_ERROR( msgBuf, myThid )
230            WRITE(msgBuf,'(A)')
231         &     'S/R EXF_CHECK: climsssfile is not set'
232            CALL PRINT_ERROR( msgBuf, myThid )
233            STOP 'ABNORMAL END: S/R EXF_CHECK'
234           ENDIF
235          ENDIF
236    
237          RETURN
238          END

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

  ViewVC Help
Powered by ViewVC 1.1.22