/[MITgcm]/MITgcm_contrib/heimbach/OpenAD/code_ad_moc/exf_check_range.F
ViewVC logotype

Annotation of /MITgcm_contrib/heimbach/OpenAD/code_ad_moc/exf_check_range.F

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


Revision 1.1 - (hide annotations) (download)
Mon Sep 15 22:16:00 2008 UTC (16 years, 10 months ago) by utke
Branch: MAIN
CVS Tags: HEAD
keep this version around

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

  ViewVC Help
Powered by ViewVC 1.1.22