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

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

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


Revision 1.21 - (hide annotations) (download)
Sat Apr 20 21:37:28 2013 UTC (11 years, 5 months ago) by dimitri
Branch: MAIN
CVS Tags: checkpoint64q, checkpoint64p, checkpoint64s, checkpoint64r, checkpoint64i, checkpoint64h, checkpoint64k, checkpoint64j, checkpoint64m, checkpoint64l, checkpoint64o, checkpoint64n, checkpoint64g
Changes since 1.20: +9 -5 lines
Change in exf_check.F is needed to accommodate larger integration domains.
With this change, default MAX_LAT_INC can be reduced to a reasonable value.

1 dimitri 1.21 C $Header: /u/gcmpack/MITgcm/pkg/exf/exf_check.F,v 1.20 2012/10/22 01:29:51 jmc Exp $
2 jmc 1.4 C $Name: $
3 heimbach 1.1
4     #include "EXF_OPTIONS.h"
5    
6 jmc 1.17 SUBROUTINE EXF_CHECK( myThid )
7 heimbach 1.1
8     c ==================================================================
9 jmc 1.16 c SUBROUTINE EXF_CHECK
10 heimbach 1.1 c ==================================================================
11     c
12 jmc 1.16 IMPLICIT NONE
13 heimbach 1.1
14     c == global variables ==
15    
16     #include "EEPARAMS.h"
17     #include "SIZE.h"
18     #include "PARAMS.h"
19    
20 jmc 1.4 #include "EXF_PARAM.h"
21     #include "EXF_CONSTANTS.h"
22 heimbach 1.1 c == routine arguments ==
23    
24 jmc 1.17 c myThid - thread number for this instance of the routine.
25 heimbach 1.1
26 jmc 1.17 INTEGER myThid
27 heimbach 1.1
28     c == local variables ==
29    
30 gforget 1.14 C msgBuf :: Informational/error message buffer
31     CHARACTER*(MAX_LEN_MBUF) msgBuf
32    
33 heimbach 1.1 c == end of interface ==
34    
35     c check for consistency
36 jmc 1.12 if (.NOT.
37     & (exf_iprec.EQ.precFloat32 .OR. exf_iprec.EQ.precFloat64)
38 heimbach 1.1 & ) then
39 dimitri 1.8 stop 'S/R EXF_CHECK: value of exf_iprec not allowed'
40     endif
41    
42     if (repeatPeriod.lt.0.) then
43     stop 'S/R EXF_CHECK: repeatPeriod must be positive'
44     endif
45 heimbach 1.1
46 dimitri 1.8 if (useExfYearlyFields.and.repeatPeriod.ne.0.) then
47     print*,'Use of usefldyearlyfields AND repeatPeriod',
48     & ' not implemented'
49     stop 'ABNORMAL END: S/R EXF_CHECK'
50 heimbach 1.1 endif
51    
52 jmc 1.20 #ifdef ALLOW_BULKFORMULAE
53     IF ( useAtmWind ) THEN
54 gforget 1.19 IF ( ustressfile .NE. ' ' .OR. ustressfile .NE. ' ' ) THEN
55     STOP
56     & 'S/R EXF_CHECK: use u,v_wind components but not wind-stress'
57 jmc 1.6 ENDIF
58 jmc 1.20 ENDIF
59 gforget 1.19 #endif
60 gforget 1.18
61 jmc 1.20 IF ( .NOT.useAtmWind ) THEN
62 gforget 1.19 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 jmc 1.20 ENDIF
67 jmc 1.6
68 gforget 1.13 #ifndef ALLOW_ZENITHANGLE
69 jmc 1.15 IF ( useExfZenAlbedo .OR. useExfZenIncoming .OR.
70 gforget 1.13 & select_ZenAlbedo .NE. 0 ) THEN
71 jmc 1.15 WRITE(msgBuf,'(A,A)') 'EXF_CHECK: unsupported option',
72 gforget 1.14 & ' when ALLOW_ZENITHANGLE is not defined'
73 jmc 1.17 CALL PRINT_ERROR( msgBuf, myThid )
74 gforget 1.14 STOP 'ABNORMAL END: S/R EXF_CHECK'
75 gforget 1.13 ENDIF
76     #endif
77    
78     #ifdef ALLOW_ZENITHANGLE
79     IF ( usingCartesianGrid .OR. usingCylindricalGrid ) then
80 jmc 1.15 WRITE(msgBuf,'(A,A)') 'EXF_CHECK: ALLOW_ZENITHANGLE does ',
81 gforget 1.14 & 'not work for carthesian and cylindrical grids'
82 jmc 1.17 CALL PRINT_ERROR( msgBuf, myThid )
83 gforget 1.14 STOP 'ABNORMAL END: S/R EXF_CHECK'
84 gforget 1.13 ENDIF
85     IF ( select_ZenAlbedo.LT.0 .OR. select_ZenAlbedo.GT.3 ) then
86 jmc 1.15 WRITE(msgBuf,'(A,A)') 'EXF_CHECK: unsupported ',
87 gforget 1.14 & 'select_ZenAlbedo choice'
88 jmc 1.17 CALL PRINT_ERROR( msgBuf, myThid )
89 gforget 1.14 STOP 'ABNORMAL END: S/R EXF_CHECK'
90 gforget 1.13 ENDIF
91     IF ( select_ZenAlbedo.EQ.2 .) then
92 jmc 1.15 write(standardmessageunit,'(A,A)')
93 gforget 1.14 & 'EXF WARNING: for daily mean albedo, it is advised ',
94     & 'to use select_ZenAlbedo.EQ.1 instead of 2'
95 gforget 1.13 ENDIF
96     IF ( select_ZenAlbedo.GT.2 .AND. swdownperiod.GT. 21600 ) then
97 jmc 1.15 WRITE(msgBuf,'(A,A)') 'EXF_CHECK: using diurnal albedo ',
98 gforget 1.14 & 'formula requires diurnal downward shortwave forcing'
99 jmc 1.17 CALL PRINT_ERROR( msgBuf, myThid )
100 gforget 1.14 STOP 'ABNORMAL END: S/R EXF_CHECK'
101 gforget 1.13 ENDIF
102     IF ( select_ZenAlbedo.GT.2 .AND. swdownperiod.GT. 3600 ) then
103 jmc 1.15 write(standardmessageunit,'(A,A)')
104 gforget 1.14 & 'EXF WARNING: the diurnal albedo formula is likely not safe ',
105     & 'for such coarse temporal resolution downward shortwave forcing'
106 gforget 1.13 ENDIF
107     #endif
108    
109 dimitri 1.3 #ifdef USE_EXF_INTERPOLATION
110 dimitri 1.21 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 dimitri 1.3 if ( usingCartesianGrid ) then
119     print*,'USE_EXF_INTERPOLATION assumes latitude/longitude'
120     print*,'input and output coordinates. Trivial to extend to'
121     print*,'cartesian coordinates, but has not yet been done.'
122     stop
123     endif
124 jmc 1.15 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 jmc 1.6 ENDIF
162 jmc 1.15
163     IF ( (ustress_interpMethod.EQ.0 .AND. ustressfile.NE.' ') .OR.
164     & (vstress_interpMethod.EQ.0 .AND. vstressfile.NE.' ') ) THEN
165 dimitri 1.8 #else /* ifndef USE_EXF_INTERPOLATION */
166 jmc 1.15 IF ( ustressfile .NE. ' ' .OR. vstressfile .NE. ' ' ) THEN
167     #endif /* USE_EXF_INTERPOLATION */
168 jmc 1.6 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 jmc 1.15
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 dimitri 1.3
189 heimbach 1.2 #ifdef ALLOW_CLIMTEMP_RELAXATION
190     STOP 'ALLOW_CLIMTEMP_RELAXATION no longer supported. Use pkg/rbcs'
191     #endif
192 heimbach 1.1
193 heimbach 1.2 #ifdef ALLOW_CLIMSALT_RELAXATION
194     STOP 'ALLOW_CLIMSALT_RELAXATION no longer supported. Use pkg/rbcs'
195     #endif
196    
197 jmc 1.17 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 jmc 1.6 RETURN
238     END

  ViewVC Help
Powered by ViewVC 1.1.22