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

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

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


Revision 1.26 - (hide annotations) (download)
Thu Feb 8 07:01:08 2007 UTC (17 years, 7 months ago) by dimitri
Branch: MAIN
CVS Tags: checkpoint58w_post, checkpoint58x_post, checkpoint58y_post
Changes since 1.25: +12 -5 lines
change checking range because some atmospheric fields will not always
have valid values in the tile edges

1 dimitri 1.26 c $Header: /u/gcmpack/MITgcm/pkg/exf/exf_check_range.F,v 1.25 2006/06/29 15:41:58 mlosch Exp $
2 heimbach 1.1
3     #include "EXF_OPTIONS.h"
4    
5     subroutine exf_check_range( mytime, myiter, mythid )
6    
7     c ==================================================================
8     c SUBROUTINE exf_check_range
9     c ==================================================================
10     c
11     implicit none
12    
13     c == global variables ==
14    
15     #include "EEPARAMS.h"
16     #include "SIZE.h"
17     #include "FFIELDS.h"
18     #include "GRID.h"
19    
20     #include "exf_param.h"
21     #include "exf_constants.h"
22     #include "exf_fields.h"
23     #include "exf_clim_fields.h"
24     c == routine arguments ==
25    
26     c mythid - thread number for this instance of the routine.
27    
28 jmc 1.9 _RL mytime
29     integer myiter, mythid
30 heimbach 1.1
31     c == local variables ==
32    
33     integer bi,bj
34     integer i,j
35     integer jtlo
36     integer jthi
37     integer itlo
38     integer ithi
39     integer jmin
40     integer jmax
41     integer imin
42     integer imax
43 heimbach 1.3 integer exferr
44 heimbach 1.1
45     c == end of interface ==
46    
47 heimbach 1.3 exferr = 0
48    
49 heimbach 1.1 jtlo = mybylo(mythid)
50     jthi = mybyhi(mythid)
51     itlo = mybxlo(mythid)
52     ithi = mybxhi(mythid)
53 dimitri 1.26
54     C Change checking range because some atmospheric fields will
55     C not always have valid values in the tile edges.
56     C jmin = 1-oly
57     C jmax = sny+oly
58     C imin = 1-olx
59     C imax = snx+olx
60     jmin = 1
61     jmax = sny
62     imin = 1
63     imax = snx
64 heimbach 1.1
65     do bj = jtlo,jthi
66 mlosch 1.25 do bi = itlo,ithi
67 heimbach 1.1
68 mlosch 1.25 do j = jmin,jmax
69     do i = imin,imax
70 heimbach 1.1 c
71 mlosch 1.25 c Heat flux.
72     if ( ( hflux(i,j,bi,bj) .GT. 1600. .OR.
73     & hflux(i,j,bi,bj) .LT. -500. ) .AND.
74     & maskC(i,j,1,bi,bj) .NE. 0. ) then
75     write(standardmessageunit,'(A,5(1X,I6),2X,D22.15)')
76     & 'EXF WARNING: hflux out of range for bi,bj,i,j,it= ',
77     & bi, bj, i, j, myiter, hflux(i,j,bi,bj)
78     exferr = 1
79     endif
80     c
81     c Salt flux.
82     if ( ABS(sflux(i,j,bi,bj)) .GT. 1.E-6 .AND.
83     & maskC(i,j,1,bi,bj) .NE. 0. ) then
84     write(standardmessageunit,'(A,5(1X,I6),2X,D22.15)')
85     & 'EXF WARNING: sflux out of range for bi,bj,i,j,it= ',
86     & bi, bj, i, j, myiter, sflux(i,j,bi,bj)
87     exferr = 1
88     endif
89     c
90     c Zonal wind stress.
91     if ( ABS(ustress(i,j,bi,bj)) .GT. 2.7 .AND.
92     & maskW(i,j,1,bi,bj) .NE. 0. ) then
93     write(standardmessageunit,'(A,5(1X,I6),2X,D22.15)')
94     & 'EXF WARNING: ustress out of range for bi,bj,i,j,it= ',
95     & bi, bj, i, j, myiter, ustress(i,j,bi,bj)
96     exferr = 1
97     endif
98     c
99     c Meridional wind stress.
100     if ( ABS(vstress(i,j,bi,bj)) .GT. 2.3 .AND.
101     & maskS(i,j,1,bi,bj) .NE. 0. ) then
102     write(standardmessageunit,'(A,5(1X,I6),2X,D22.15)')
103     & 'EXF WARNING: vstress out of range for bi,bj,i,j,it= ',
104     & bi, bj, i, j, myiter, vstress(i,j,bi,bj)
105     exferr = 1
106     endif
107 heimbach 1.1 c
108     #ifdef ALLOW_ATM_WIND
109 mlosch 1.25 c zonal wind speed
110     if ( ABS(uwind(i,j,bi,bj)) .GT. 100. .AND.
111     & maskW(i,j,1,bi,bj) .NE. 0. ) then
112     write(standardmessageunit,'(A,5(1X,I6),2X,D22.15)')
113     & 'EXF WARNING: uwind out of range for bi,bj,i,j,it= ',
114     & bi, bj, i, j, myiter, uwind(i,j,bi,bj)
115     exferr = 1
116     endif
117     c
118     c zonal wind speed
119     if ( ABS(vwind(i,j,bi,bj)) .GT. 100. .AND.
120     & maskS(i,j,1,bi,bj) .NE. 0. ) then
121     write(standardmessageunit,'(A,5(1X,I6),2X,D22.15)')
122     & 'EXF WARNING: vwind out of range for bi,bj,i,j,it= ',
123     & bi, bj, i, j, myiter, vwind(i,j,bi,bj)
124     exferr = 1
125     endif
126 heimbach 1.1 #endif
127 heimbach 1.24 c
128 mlosch 1.25 c wind speed modulus
129     if ( ( wspeed(i,j,bi,bj) .LT. 0. .OR.
130     & wspeed(i,j,bi,bj) .GT. 100. ) .AND.
131     & maskS(i,j,1,bi,bj) .NE. 0. ) then
132     write(standardmessageunit,'(A,5(1X,I6),2X,D22.15)')
133     & 'EXF WARNING: wspeed out of range for bi,bj,i,j,it= ',
134     & bi, bj, i, j, myiter, wspeed(i,j,bi,bj)
135     exferr = 1
136     endif
137    
138 heimbach 1.1 #ifdef ALLOW_ATM_TEMP
139 mlosch 1.25 c 2-m air temperature
140     if ( (atemp(i,j,bi,bj) .LT. 183 .OR.
141     & atemp(i,j,bi,bj) .GT. 343 ) .AND.
142     & maskC(i,j,1,bi,bj) .NE. 0. ) then
143     write(standardmessageunit,'(2A,5(1X,I6),2X,D22.15)')
144     & 'EXF WARNING: atemp + exf_offset_atemp ',
145     & 'out of range for bi,bj,i,j,it= ',
146     & bi, bj, i, j, myiter, atemp(i,j,bi,bj)
147     exferr = 1
148     endif
149     c
150     c 2-m specific humidity
151     if ( (aqh(i,j,bi,bj) .LT. 0. .OR.
152     & aqh(i,j,bi,bj) .GT. 0.1 ) .AND.
153     & maskC(i,j,1,bi,bj) .NE. 0. ) then
154     write(standardmessageunit,'(A,5(1X,I6),2X,D22.15)')
155     & 'EXF WARNING: aqh out of range for bi,bj,i,j,it= ',
156     & bi, bj, i, j, myiter, aqh(i,j,bi,bj)
157     exferr = 1
158     endif
159     c
160     c precipitation rate
161     if ( (precip(i,j,bi,bj) .LT. 0. .OR.
162     & precip(i,j,bi,bj) .GT. 2.E-6 ) .AND.
163     & maskC(i,j,1,bi,bj) .NE. 0. ) then
164     write(standardmessageunit,'(A,5(1X,I6),2X,D22.15)')
165     & 'EXF WARNING: precip out of range for bi,bj,i,j,it= ',
166     & bi, bj, i, j, myiter, precip(i,j,bi,bj)
167     exferr = 1
168     endif
169     c
170     c snow
171     if ( (snowprecip(i,j,bi,bj) .LT. 0. .OR.
172     & snowprecip(i,j,bi,bj) .GT. 2.E-6 ) .AND.
173     & maskC(i,j,1,bi,bj) .NE. 0. ) then
174     write(standardmessageunit,'(2A,5(1X,I6),2X,D22.15)')
175     & 'EXF WARNING: snowprecip out of range ',
176     & 'for bi,bj,i,j,it= ',
177     & bi, bj, i, j, myiter, snowprecip(i,j,bi,bj)
178     exferr = 1
179     endif
180 heimbach 1.1 #endif
181    
182     #ifdef SHORTWAVE_HEATING
183 mlosch 1.25 c Short wave radiative flux.
184     if ( (swflux(i,j,bi,bj) .GT. 1. .OR.
185     & swflux(i,j,bi,bj) .LT. -1000. ) .AND.
186     & maskC(i,j,1,bi,bj) .NE. 0. ) then
187     write(standardmessageunit,'(A,5(1X,I6),2X,D22.15)')
188     & 'EXF WARNING: swflux out of range for bi,bj,i,j,it= ',
189     & bi, bj, i, j, myiter, swflux(i,j,bi,bj)
190     exferr = 1
191     endif
192 heimbach 1.1 #endif
193    
194 heimbach 1.3 #ifdef ALLOW_RUNOFF
195 mlosch 1.25 c Runoff.
196     if ( (runoff(i,j,bi,bj) .LT. 0. .OR.
197     & runoff(i,j,bi,bj) .GT. 1.E-6 ) .AND.
198     & maskC(i,j,1,bi,bj) .NE. 0. ) then
199     write(standardmessageunit,'(A,5(1X,I6),2X,D22.15)')
200     & 'EXF WARNING: runoff out of range for bi,bj,i,j,it= ',
201     & bi, bj, i, j, myiter, runoff(i,j,bi,bj)
202     write(standardmessageunit,'(A)')
203     & 'Please note that input units for runoff are'
204     write(standardmessageunit,'(A)')
205     & 'm/s not m/yr. If input file is in m/yr, set'
206     write(standardmessageunit,'(A)')
207     & 'exf_inscal_runoff=3.170979198E-8'
208     write(standardmessageunit,'(A)')
209     & 'in the data.exf input file.'
210     exferr = 1
211     endif
212 heimbach 1.3 #endif
213 mlosch 1.25 enddo
214 heimbach 1.1 enddo
215 mlosch 1.25 c
216     enddo
217 heimbach 1.1 enddo
218    
219 mlosch 1.25 if ( exferr .NE. 0 ) then
220     write(standardmessageunit,'(A)')
221     & 'EXF WARNING: If you think these values are OK '
222     write(standardmessageunit,'(A)')
223     & 'EXF WARNING: then set useExfCheckRange=.FALSE.'
224     STOP 'in S/R exf_check_range'
225     endif
226    
227 heimbach 1.1 end

  ViewVC Help
Powered by ViewVC 1.1.22