/[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.15 - (hide annotations) (download)
Wed Dec 21 17:20:09 2011 UTC (12 years, 6 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint63h
Changes since 1.14: +60 -34 lines
- add a set of run-time param ({inputfield}_interpMethod), one for
  each interpolated input field, to select the interpolation method
  with a value of zero switching off the interpolation;
- refine exf_check.F accordingly ; stop if USE_NO_INTERP_RUNOFF is defined
  (to use instead runoff_interpMethod=0 in data.exf).

1 jmc 1.15 C $Header: /u/gcmpack/MITgcm/pkg/exf/exf_check.F,v 1.14 2010/06/17 21:45:16 gforget Exp $
2 jmc 1.4 C $Name: $
3 heimbach 1.1
4     #include "EXF_OPTIONS.h"
5    
6     subroutine exf_check( mythid )
7    
8     c ==================================================================
9     c SUBROUTINE exf_check
10     c ==================================================================
11     c
12     implicit none
13    
14     c == global variables ==
15    
16     #include "EEPARAMS.h"
17     #include "SIZE.h"
18     #include "PARAMS.h"
19 jmc 1.6 c#include "FFIELDS.h"
20     c#include "GRID.h"
21 heimbach 1.1
22 jmc 1.4 #include "EXF_PARAM.h"
23     #include "EXF_CONSTANTS.h"
24 jmc 1.6 c#include "EXF_FIELDS.h"
25 heimbach 1.1 c == routine arguments ==
26    
27     c mythid - thread number for this instance of the routine.
28    
29     integer mythid
30    
31     c == local variables ==
32    
33 gforget 1.14 C msgBuf :: Informational/error message buffer
34     CHARACTER*(MAX_LEN_MBUF) msgBuf
35    
36 heimbach 1.1 c == end of interface ==
37    
38     c check for consistency
39 jmc 1.12 if (.NOT.
40     & (exf_iprec.EQ.precFloat32 .OR. exf_iprec.EQ.precFloat64)
41 heimbach 1.1 & ) then
42 dimitri 1.8 stop 'S/R EXF_CHECK: value of exf_iprec not allowed'
43 jmc 1.12 elseif ( exf_yftype.NE.'RL' ) then
44 dimitri 1.8 stop 'S/R EXF_CHECK: value of exf_yftype not allowed'
45     endif
46    
47     if (repeatPeriod.lt.0.) then
48     stop 'S/R EXF_CHECK: repeatPeriod must be positive'
49     endif
50 heimbach 1.1
51 dimitri 1.8 if (useExfYearlyFields.and.repeatPeriod.ne.0.) then
52     print*,'Use of usefldyearlyfields AND repeatPeriod',
53     & ' not implemented'
54     stop 'ABNORMAL END: S/R EXF_CHECK'
55 heimbach 1.1 endif
56    
57 jmc 1.6 #if ( defined (ALLOW_BULKFORMULAE) && defined (ALLOW_ATM_WIND) )
58 gforget 1.11 IF ( ustressfile .NE. ' ' .OR. ustressfile .NE. ' ' ) THEN
59 jmc 1.6 STOP
60     & 'S/R EXF_CHECK: use u,v_wind components but not wind-stress'
61     ENDIF
62     #endif
63 dimitri 1.8
64 jmc 1.6 #ifndef ALLOW_ATM_WIND
65     IF ( uwindfile .NE. ' ' .OR. vwindfile .NE. ' ' ) THEN
66     STOP
67     & 'S/R EXF_CHECK: read-in wind-stress but not u,v_wind components'
68     ENDIF
69     #endif
70    
71 gforget 1.13 #ifndef ALLOW_ZENITHANGLE
72 jmc 1.15 IF ( useExfZenAlbedo .OR. useExfZenIncoming .OR.
73 gforget 1.13 & select_ZenAlbedo .NE. 0 ) THEN
74 jmc 1.15 WRITE(msgBuf,'(A,A)') 'EXF_CHECK: unsupported option',
75 gforget 1.14 & ' when ALLOW_ZENITHANGLE is not defined'
76     CALL PRINT_ERROR( msgBuf , mythid)
77     STOP 'ABNORMAL END: S/R EXF_CHECK'
78 gforget 1.13 ENDIF
79     #endif
80    
81     #ifdef ALLOW_ZENITHANGLE
82     IF ( usingCartesianGrid .OR. usingCylindricalGrid ) then
83 jmc 1.15 WRITE(msgBuf,'(A,A)') 'EXF_CHECK: ALLOW_ZENITHANGLE does ',
84 gforget 1.14 & 'not work for carthesian and cylindrical grids'
85     CALL PRINT_ERROR( msgBuf , mythid)
86     STOP 'ABNORMAL END: S/R EXF_CHECK'
87 gforget 1.13 ENDIF
88     IF ( select_ZenAlbedo.LT.0 .OR. select_ZenAlbedo.GT.3 ) then
89 jmc 1.15 WRITE(msgBuf,'(A,A)') 'EXF_CHECK: unsupported ',
90 gforget 1.14 & 'select_ZenAlbedo choice'
91     CALL PRINT_ERROR( msgBuf , mythid)
92     STOP 'ABNORMAL END: S/R EXF_CHECK'
93 gforget 1.13 ENDIF
94     IF ( select_ZenAlbedo.EQ.2 .) then
95 jmc 1.15 write(standardmessageunit,'(A,A)')
96 gforget 1.14 & 'EXF WARNING: for daily mean albedo, it is advised ',
97     & 'to use select_ZenAlbedo.EQ.1 instead of 2'
98 gforget 1.13 ENDIF
99     IF ( select_ZenAlbedo.GT.2 .AND. swdownperiod.GT. 21600 ) then
100 jmc 1.15 WRITE(msgBuf,'(A,A)') 'EXF_CHECK: using diurnal albedo ',
101 gforget 1.14 & 'formula requires diurnal downward shortwave forcing'
102     CALL PRINT_ERROR( msgBuf , mythid)
103     STOP 'ABNORMAL END: S/R EXF_CHECK'
104 gforget 1.13 ENDIF
105     IF ( select_ZenAlbedo.GT.2 .AND. swdownperiod.GT. 3600 ) then
106 jmc 1.15 write(standardmessageunit,'(A,A)')
107 gforget 1.14 & 'EXF WARNING: the diurnal albedo formula is likely not safe ',
108     & 'for such coarse temporal resolution downward shortwave forcing'
109 gforget 1.13 ENDIF
110     #endif
111    
112 dimitri 1.3 #ifdef USE_EXF_INTERPOLATION
113 jmc 1.6 if ( climsst_nlat .GT. MAX_LAT_INC )
114     & stop 'stopped in exf_readparms: climsst_nlat > MAX_LAT_INC'
115     if ( climsss_nlat .GT. MAX_LAT_INC )
116     & stop 'stopped in exf_readparms: climsss_nlat > MAX_LAT_INC'
117 dimitri 1.3 if ( usingCartesianGrid ) then
118     print*,'USE_EXF_INTERPOLATION assumes latitude/longitude'
119     print*,'input and output coordinates. Trivial to extend to'
120     print*,'cartesian coordinates, but has not yet been done.'
121     stop
122     endif
123 jmc 1.15 C- some restrictions on 2-component vector field (might be relaxed later on)
124     IF ( ( uwind_interpMethod.GE.1 .AND. uwindfile.NE.' ' ) .OR.
125     & ( vwind_interpMethod.GE.1 .AND. vwindfile.NE.' ' ) ) THEN
126     IF ( usingCurvilinearGrid .OR. rotateGrid ) THEN
127     IF ( uwind_interpMethod.EQ.0 .OR. uwindfile.EQ.' ' .OR.
128     & vwind_interpMethod.EQ.0 .OR. vwindfile.EQ.' ' ) THEN
129     C- stop if one expects interp+rotation (Curvilin-G) which will not happen
130     STOP 'interp. needs 2 components (wind)'
131     ENDIF
132     IF ( uwindstartdate .NE. vwindstartdate .OR.
133     & uwindperiod .NE. vwindperiod ) THEN
134     print*,'For CurvilinearGrid/RotatedGrid, S/R EXF_SET_UV'
135     print*,'assumes that the u and v wind files'
136     print*,'have the same startdate and period.'
137     stop
138     ENDIF
139     ENDIF
140     ENDIF
141     IF ( (ustress_interpMethod.GE.1 .AND. ustressfile.NE.' ') .OR.
142     & (vstress_interpMethod.GE.1 .AND. vstressfile.NE.' ') ) THEN
143     IF ( readStressOnCgrid ) THEN
144     STOP 'readStressOnCgrid and interp wind-stress (=A-grid)'
145     ENDIF
146     IF ( usingCurvilinearGrid .OR. rotateGrid ) THEN
147     IF ( ustress_interpMethod.EQ.0 .OR. ustressfile.EQ.' ' .OR.
148     & vstress_interpMethod.EQ.0 .OR. vstressfile.EQ.' ' ) THEN
149     C- stop if one expects interp+rotation (Curvilin-G) which will not happen
150     STOP 'interp. needs 2 components (wind-stress)'
151     ENDIF
152     IF ( ustressstartdate .NE. vstressstartdate .OR.
153     & ustressperiod .NE. vstressperiod ) THEN
154     print*,'For CurvilinearGrid/RotatedGrid, S/R EXF_SET_UV'
155     print*,'assumes that the u and v wind stress files'
156     print*,'have the same startdate and period.'
157     stop
158     ENDIF
159     ENDIF
160 jmc 1.6 ENDIF
161 jmc 1.15
162     IF ( (ustress_interpMethod.EQ.0 .AND. ustressfile.NE.' ') .OR.
163     & (vstress_interpMethod.EQ.0 .AND. vstressfile.NE.' ') ) THEN
164 dimitri 1.8 #else /* ifndef USE_EXF_INTERPOLATION */
165 jmc 1.15 IF ( ustressfile .NE. ' ' .OR. vstressfile .NE. ' ' ) THEN
166     #endif /* USE_EXF_INTERPOLATION */
167 jmc 1.6 IF ( (readStressOnAgrid.AND.readStressOnCgrid) .OR.
168     & .NOT.(readStressOnAgrid.OR.readStressOnCgrid) ) THEN
169     STOP
170     & 'S/R EXF_CHECK: Select 1 wind-stress position: A or C-grid'
171     ENDIF
172     ELSE
173     IF ( readStressOnAgrid .OR. readStressOnCgrid ) THEN
174     STOP 'S/R EXF_CHECK: wind-stress position irrelevant'
175     ENDIF
176     ENDIF
177 jmc 1.15
178     #ifdef USE_NO_INTERP_RUNOFF
179     WRITE(msgBuf,'(A,A)') 'EXF_CHECK: USE_NO_INTERP_RUNOFF code',
180     & ' has been removed;'
181     CALL PRINT_ERROR( msgBuf, myThid )
182     WRITE(msgBuf,'(A,A)') 'use instead "runoff_interpMethod=0"',
183     & ' in "data.exf" (EXF_NML_04)'
184     CALL PRINT_ERROR( msgBuf, myThid )
185     STOP 'ABNORMAL END: S/R EXF_CHECK'
186     #endif /* USE_NO_INTERP_RUNOFF */
187 dimitri 1.3
188 heimbach 1.2 #ifdef ALLOW_CLIMTEMP_RELAXATION
189     STOP 'ALLOW_CLIMTEMP_RELAXATION no longer supported. Use pkg/rbcs'
190     #endif
191 heimbach 1.1
192 heimbach 1.2 #ifdef ALLOW_CLIMSALT_RELAXATION
193     STOP 'ALLOW_CLIMSALT_RELAXATION no longer supported. Use pkg/rbcs'
194     #endif
195    
196 jmc 1.6 RETURN
197     END

  ViewVC Help
Powered by ViewVC 1.1.22