/[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.18 - (hide annotations) (download)
Tue Aug 28 19:17:46 2012 UTC (11 years, 10 months ago) by gforget
Branch: MAIN
CVS Tags: checkpoint63s, checkpoint64
Changes since 1.17: +21 -11 lines
- pkg/exf : added run time switch useAtmWind to replace ALLOW_ATM_WIND
  cpp switch. ALLOW_ATM_WIND now just sets the useAtmWind default (see
  exf_readparms.F) and force defines ALLOW_BULKFORMULAE (EXF_OPTIONS.h).
- pkg/exf, autodiff, ctrl, ecco and seaice : remove ALLOW_ATM_WIND
  brackets, or replace them with useAtmWind ones.
- pkg/ctrl, ecco : allow to compile both ALLOW_U/VSTRESS_CONTROL and
  ALLOW_U/VWIND_CONTROL. Depending on useAtmWind, one is inactive,
  and the other is active (see exf_getffields.F/exf_getsurfacefluxes.F).

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

  ViewVC Help
Powered by ViewVC 1.1.22