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

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

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

revision 1.6 by dimitri, Thu Dec 2 15:41:22 2004 UTC revision 1.31 by dimitri, Tue Apr 23 19:04:33 2013 UTC
# Line 1  Line 1 
1  c $Header$  C $Header$
2    C $Name$
3    
4  #include "EXF_OPTIONS.h"  #include "EXF_OPTIONS.h"
5    
6        subroutine exf_check_range( mytime, myiter, mythid )        SUBROUTINE EXF_CHECK_RANGE( mytime, myiter, mythid )
7    
8  c     ==================================================================  c     ==================================================================
9  c     SUBROUTINE exf_check_range  c     SUBROUTINE EXF_CHECK_RANGE
10  c     ==================================================================  c     ==================================================================
11  c  c
12        implicit none        implicit none
# Line 17  c     == global variables == Line 18  c     == global variables ==
18  #include "FFIELDS.h"  #include "FFIELDS.h"
19  #include "GRID.h"  #include "GRID.h"
20    
21  #include "exf_param.h"  #include "EXF_PARAM.h"
22  #include "exf_constants.h"  #include "EXF_CONSTANTS.h"
23  #include "exf_fields.h"  #include "EXF_FIELDS.h"
 #include "exf_clim_fields.h"  
24  c     == routine arguments ==  c     == routine arguments ==
25    
26  c     mythid - thread number for this instance of the routine.  c     mythid - thread number for this instance of the routine.
27    
28        integer mytime, myiter, mythid        _RL mytime
29          integer myiter, mythid
30    
31  c     == local variables ==  c     == local variables ==
32    
# Line 45  c     == end of interface == Line 46  c     == end of interface ==
46    
47        exferr = 0        exferr = 0
48    
49        jtlo = mybylo(mythid)  c     jtlo = mybylo(mythid)
50        jthi = mybyhi(mythid)  c     jthi = mybyhi(mythid)
51        itlo = mybxlo(mythid)  c     itlo = mybxlo(mythid)
52        ithi = mybxhi(mythid)  c     ithi = mybxhi(mythid)
53        jmin = 1-oly  C--   Only master thread can safely write directly to standard output:
54        jmax = sny+oly        _BARRIER
55        imin = 1-olx        _BEGIN_MASTER( myThid )
56        imax = snx+olx        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        do bj = jtlo,jthi
73          do bi = itlo,ithi         do bi = itlo,ithi
74    
75            do j = jmin,jmax          do j = jmin,jmax
76              do i = imin,imax           do i = imin,imax
77  c  c
78  c             Heat flux.  c     Heat flux.
79                if ( ABS(hflux(i,j,bi,bj)) .GT. 1000. .AND.            if ( ( hflux(i,j,bi,bj) .GT. 1600. .OR.
80       &              hFacC(i,j,1,bi,bj) .NE. 0. ) then       &         hflux(i,j,bi,bj) .LT. -500. ) .AND.
81                   print *, 'EXF WARNING: hflux out of range for i,j= ',       &         maskC(i,j,1,bi,bj) .NE. 0. ) then
82       &                i, j, hflux(i,j,bi,bj)             write(standardmessageunit,'(A,5(1X,I6),2X,D22.15)')
83                   exferr = 1       &          'EXF WARNING: hflux out of range for bi,bj,i,j,it= ',
84                endif       &          bi, bj, i, j, myiter, hflux(i,j,bi,bj)
85  c             exferr = 1
86  c             Salt flux.            endif
87                if ( ABS(sflux(i,j,bi,bj)) .GT. 1.E-6 .AND.  c
88       &             hFacC(i,j,1,bi,bj) .NE. 0. ) then  c     Salt flux.
89                   print *, 'EXF WARNING: sflux out of range for i,j= ',            if ( ABS(sflux(i,j,bi,bj)) .GT. 1.E-6 .AND.
90       &                i, j, sflux(i,j,bi,bj)       &         maskC(i,j,1,bi,bj) .NE. 0. ) then
91                   exferr = 1             write(standardmessageunit,'(A,5(1X,I6),2X,D22.15)')
92                endif       &          'EXF WARNING: sflux out of range for bi,bj,i,j,it= ',
93  c       &          bi, bj, i, j, myiter, sflux(i,j,bi,bj)
94  c             Zonal wind stress.             exferr = 1
95                if ( ABS(ustress(i,j,bi,bj)) .GT. 2. .AND.            endif
96       &             hFacW(i,j,1,bi,bj) .NE. 0. ) then  c
97                   print *, 'EXF WARNING: ustress out of range for i,j= ',  c     Zonal wind stress.
98       &                i, j, ustress(i,j,bi,bj)            if ( ABS(ustress(i,j,bi,bj)) .GT. 2.7 .AND.
99                   exferr = 1       &         maskW(i,j,1,bi,bj) .NE. 0. ) then
100                endif             write(standardmessageunit,'(A,5(1X,I6),2X,D22.15)')
101  c       &          'EXF WARNING: ustress out of range for bi,bj,i,j,it= ',
102  c             Meridional wind stress.       &          bi, bj, i, j, myiter, ustress(i,j,bi,bj)
103                if ( ABS(vstress(i,j,bi,bj)) .GT. 2. .AND.             exferr = 1
104       &             hFacS(i,j,1,bi,bj) .NE. 0. ) then            endif
105                   print *, 'EXF WARNING: vstress out of range for i,j= ',  c
106       &                i, j, vstress(i,j,bi,bj)  c     Meridional wind stress.
107                   exferr = 1            if ( ABS(vstress(i,j,bi,bj)) .GT. 2.3 .AND.
108                endif       &         maskS(i,j,1,bi,bj) .NE. 0. ) then
109  c             write(standardmessageunit,'(A,5(1X,I6),2X,D22.15)')
110  #ifdef ALLOW_ATM_WIND       &          'EXF WARNING: vstress out of range for bi,bj,i,j,it= ',
111  c             zonal wind speed       &          bi, bj, i, j, myiter, vstress(i,j,bi,bj)
112                if ( ABS(uwind(i,j,bi,bj)) .GT. 100. .AND.             exferr = 1
113       &             hFacW(i,j,1,bi,bj) .NE. 0. ) then            endif
114                   print *, 'EXF WARNING: uwind out of range for i,j= ',  c
115       &                i, j, uwind(i,j,bi,bj)        IF ( useAtmWind ) THEN
116                   exferr = 1  c     zonal wind speed
117                endif            if ( ABS(uwind(i,j,bi,bj)) .GT. 100. .AND.
118  c       &         maskW(i,j,1,bi,bj) .NE. 0. ) then
119  c             zonal wind speed             write(standardmessageunit,'(A,5(1X,I6),2X,D22.15)')
120                if ( ABS(vwind(i,j,bi,bj)) .GT. 100. .AND.       &          'EXF WARNING: uwind out of range for bi,bj,i,j,it= ',
121       &             hFacS(i,j,1,bi,bj) .NE. 0. ) then       &          bi, bj, i, j, myiter, uwind(i,j,bi,bj)
122                   print *, 'EXF WARNING: vwind out of range for i,j= ',             exferr = 1
123       &                i, j, vwind(i,j,bi,bj)            endif
124                   exferr = 1  c
125                endif  c     zonal wind speed
126  #endif            if ( ABS(vwind(i,j,bi,bj)) .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)
131               exferr = 1
132              endif
133          ENDIF
134    c
135    c     wind speed modulus
136              if ( ( wspeed(i,j,bi,bj) .LT. 0. .OR.
137         &         wspeed(i,j,bi,bj) .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)
142               exferr = 1
143              endif
144              
145  #ifdef ALLOW_ATM_TEMP  #ifdef ALLOW_ATM_TEMP
146  c             2-m air temperature  c     2-m air temperature
147                if ( (atemp(i,j,bi,bj) .LT. 183 .OR.            if ( (atemp(i,j,bi,bj) .LT. 183 .OR.
148       &             atemp(i,j,bi,bj) .GT. 343 ) .AND.       &         atemp(i,j,bi,bj) .GT. 343 ) .AND.
149       &             hFacC(i,j,1,bi,bj) .NE. 0. ) then       &         maskC(i,j,1,bi,bj) .NE. 0. ) then
150                   print *, 'EXF WARNING: atemp + exf_offset_atemp ',             write(standardmessageunit,'(2A,5(1X,I6),2X,D22.15)')
151       &                'out of range for i,j= ',       &          'EXF WARNING: atemp + exf_offset_atemp ',
152       &                i, j, atemp(i,j,bi,bj)       &          'out of range for bi,bj,i,j,it= ',
153                   exferr = 1       &          bi, bj, i, j, myiter, atemp(i,j,bi,bj)
154                endif             exferr = 1
155  c            endif
156  c             2-m specific humidity  c
157                if ( (aqh(i,j,bi,bj) .LT. 0. .OR.  c     2-m specific humidity
158       &             aqh(i,j,bi,bj) .GT. 0.1 ) .AND.            if ( (aqh(i,j,bi,bj) .LT. 0. .OR.
159       &             hFacC(i,j,1,bi,bj) .NE. 0. ) then       &         aqh(i,j,bi,bj) .GT. 0.1 ) .AND.
160                   print *, 'EXF WARNING: aqh out of range for i,j= ',       &         maskC(i,j,1,bi,bj) .NE. 0. ) then
161       &                i, j, aqh(i,j,bi,bj)             write(standardmessageunit,'(A,5(1X,I6),2X,D22.15)')
162                   exferr = 1       &          'EXF WARNING: aqh out of range for bi,bj,i,j,it= ',
163                endif       &          bi, bj, i, j, myiter, aqh(i,j,bi,bj)
164  c             exferr = 1
165  c             precipitation rate            endif
166                if ( (precip(i,j,bi,bj) .LT. 0. .OR.  c    
167       &             precip(i,j,bi,bj) .GT. 0.1 ) .AND.  c     precipitation rate
168       &             hFacC(i,j,1,bi,bj) .NE. 0. ) then            if ( (precip(i,j,bi,bj) .LT. 0. .OR.
169                   print *, 'EXF WARNING: precip out of range for i,j= ',       &         precip(i,j,bi,bj) .GT. 2.E-6 ) .AND.
170       &                i, j, precip(i,j,bi,bj)       &         maskC(i,j,1,bi,bj) .NE. 0. ) then
171                   exferr = 1             write(standardmessageunit,'(A,5(1X,I6),2X,D22.15)')
172                endif       &          '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  #endif
188    
189  #ifdef SHORTWAVE_HEATING  #ifdef SHORTWAVE_HEATING
190  c             Short wave radiative flux.  c     Short wave radiative flux.
191                if ( (swflux(i,j,bi,bj) .GT. 1. .OR.            if ( (swflux(i,j,bi,bj) .GT. 1. .OR.
192       &             swflux(i,j,bi,bj) .LT. -500. ) .AND.       &         swflux(i,j,bi,bj) .LT. -1000. ) .AND.
193       &             hFacC(i,j,1,bi,bj) .NE. 0. ) then       &         maskC(i,j,1,bi,bj) .NE. 0. ) then
194                   print *, 'EXF WARNING: swflux out of range for i,j= ',             write(standardmessageunit,'(A,5(1X,I6),2X,D22.15)')
195       &                i, j, swflux(i,j,bi,bj)       &          'EXF WARNING: swflux out of range for bi,bj,i,j,it= ',
196                   exferr = 1       &          bi, bj, i, j, myiter, swflux(i,j,bi,bj)
197                endif             exferr = 1
198              endif
199  #endif  #endif
200    
201  #ifdef ALLOW_RUNOFF  #ifdef ALLOW_RUNOFF
202  c             Runoff.  c     Runoff.
203                if ( (runoff(i,j,bi,bj) .LT. 0. .OR.            if ( (runoff(i,j,bi,bj) .LT. 0. .OR.
204       &             runoff(i,j,bi,bj) .GT. 1.E-6 ) .AND.       &         runoff(i,j,bi,bj) .GT. 1.E-6 ) .AND.
205       &             hFacC(i,j,1,bi,bj) .NE. 0. ) then       &         maskC(i,j,1,bi,bj) .NE. 0. ) then
206                   print *, 'EXF WARNING: runoff out of range for i,j= ',             write(standardmessageunit,'(A,5(1X,I6),2X,D22.15)')
207       &                i, j, runoff(i,j,bi,bj)       &          'EXF WARNING: runoff out of range for bi,bj,i,j,it= ',
208                   print *, 'Please note that input units for runoff are'       &          bi, bj, i, j, myiter, runoff(i,j,bi,bj)
209                   print *, 'm/s not m/yr.  If input file is in m/yr, set'             write(standardmessageunit,'(A)')
210                   print *, 'exf_inscal_runoff=1.0/(86400.0*365.0)'       &          'Please note that input units for runoff are'
211                   print *, 'in the data.exf input file.'             write(standardmessageunit,'(A)')
212                   exferr = 1       &          'm/s not m/yr.  If input file is in m/yr, set'
213                endif             write(standardmessageunit,'(A)')
214  #endif       &          'exf_inscal_runoff=3.170979198E-8'
215               write(standardmessageunit,'(A)')
216                if ( exferr .NE. 0 ) then       &          'in the data.exf input file.'
217                 print *, 'EXF WARNING: If you think these values are OK '             exferr = 1
218                 print *, 'EXF WARNING: then set useExfCheckRange=.FALSE.'            endif
219                 STOP 'in S/R exf_check_range'  # ifdef ALLOW_RUNOFTEMP
220                endif  c     Runoff temperature.
221              if ( (runoftemp(i,j,bi,bj) .LT. -2. .OR.
222              enddo       &         runoff(i,j,bi,bj) .GT. 36 ) .AND.
223            enddo       &         maskC(i,j,1,bi,bj) .NE. 0. ) then
224  c             write(standardmessageunit,'(A,5(1X,I6),2X,D22.15)')
225         &          'EXF WARNING: runoftemp out of range at bi,bj,i,j,it= ',
226         &          bi, bj, i, j, myiter, runoff(i,j,bi,bj)
227               exferr = 1
228              endif
229    # endif /* ALLOW_RUNOFTEMP */
230    #endif /* ALLOW_RUNOFF */
231             enddo
232          enddo          enddo
233    c    
234           enddo
235        enddo        enddo
236    
237        end        if ( exferr .NE. 0 ) then
238           write(standardmessageunit,'(A)')
239         &      'EXF WARNING: If you think these values are OK '
240           write(standardmessageunit,'(A)')
241         &      'EXF WARNING: then set useExfCheckRange=.FALSE.'
242           STOP 'ABNORMAL END: S/R EXF_CHECK_RANGE'
243          endif
244          _END_MASTER( myThid )
245    
246          RETURN
247          END

Legend:
Removed from v.1.6  
changed lines
  Added in v.1.31

  ViewVC Help
Powered by ViewVC 1.1.22