source: trunk/LMDZ.VENUS/libf/phyvenus/hgardfou.F @ 3892

Last change on this file since 3892 was 3892, checked in by emillour, 4 months ago

Venus PCM:
Some code cleanup:

  • remove clmain.old and clmain.classic
  • remove all the unnecessary "EXTERNAL" statements in physiq
  • turn hgardfou into a module (and remove obsolete cpp directives for CRAY computers)

EM

File size: 3.8 KB
Line 
1      MODULE hgardfou_mod
2     
3      IMPLICIT NONE
4     
5      CONTAINS
6
7      SUBROUTINE hgardfou (t,tsol,text)
8
9      use dimphy, only: klon,klev
10
11      IMPLICIT none
12
13c======================================================================
14c Check that temperatures are in a reasonable range
15c======================================================================
16
17      REAL,INTENT(IN) :: t(klon,klev), tsol(klon)
18      CHARACTER(len=*),INTENT(in):: text
19C
20      INTEGER :: i, k
21      REAL :: zt(klon) ! to locally store temperature fields
22      REAL,PARAMETER :: tmin=15.0   ! Minimum temperature
23      REAL,PARAMETER :: tmax=1200.0 ! Maximum temperature
24      INTEGER :: jbad ! number of problematic points
25      INTEGER :: jadrs(klon) ! stored index of problematic points
26      LOGICAL :: ok ! .true. as long as everything OK
27      CHARACTER(len=100) :: textout
28c
29      LOGICAL,SAVE :: firstcall=.TRUE.
30c$OMP THREADPRIVATE(firstcall)
31
32      IF (firstcall) THEN
33         PRINT*, 'hgardfou checks if temperature is in [15,1200] K'
34         firstcall = .FALSE.
35      ENDIF
36c
37      ok = .TRUE.
38
39      !1. Atmospheric temperatures
40      DO k = 1, klev
41         DO i = 1, klon
42            zt(i) = t(i,k)
43         ENDDO
44
45         ! Look for temperatures that are not numbers (NaN, Infinity, etc.)
46         jbad=0
47         DO i=1,klon
48           IF (zt(i).NE.zt(i)) THEN
49             jbad = jbad + 1
50             jadrs(jbad) = i
51           ENDIF
52         ENDDO
53         
54         IF (jbad .GT. 0) THEN
55           ok = .FALSE.
56           DO i = 1, jbad
57             PRINT *,'i,k,temperature =',jadrs(i),k,zt(jadrs(i))
58           ENDDO
59         ENDIF
60         
61         
62         ! Look for temperatures greater than tmax
63         jbad = 0
64         DO i = 1, klon
65           IF (zt(i).GT.tmax) THEN
66            jbad = jbad + 1
67            jadrs(jbad) = i
68           ENDIF
69         ENDDO
70
71         IF (jbad .GT. 0) THEN
72           ok = .FALSE.
73           DO i = 1, jbad
74             PRINT *,'i,k,temperature =',jadrs(i),k,zt(jadrs(i))
75           ENDDO
76         ENDIF
77
78         ! Look for temperatures lower than tmin
79         jbad = 0
80         DO i = 1, klon
81           IF (zt(i).LT.tmin) THEN
82            jbad = jbad + 1
83            jadrs(jbad) = i
84           ENDIF
85         ENDDO
86
87         IF (jbad .GT. 0) THEN
88           ok = .FALSE.
89           DO i = 1, jbad
90             PRINT *,'i,k,temperature =',jadrs(i),k,zt(jadrs(i))
91           ENDDO
92         ENDIF
93      ENDDO ! of DO k = 1, klev
94
95      !2. surface temperatures
96      DO i = 1, klon
97         zt(i) = tsol(i)
98      ENDDO
99
100      ! Look for temperatures that are not numbers (NaN, Infinity, etc.)
101      jbad=0
102      DO i=1,klon
103        IF (zt(i).NE.zt(i)) THEN
104          jbad = jbad + 1
105          jadrs(jbad) = i
106        ENDIF
107      ENDDO
108         
109      IF (jbad .GT. 0) THEN
110        ok = .FALSE.
111        DO i = 1, jbad
112          PRINT *,'i,tsol =',jadrs(i),zt(jadrs(i))
113        ENDDO
114      ENDIF
115
116      ! Look for temperatures greater then tmax
117      jbad = 0
118      DO i = 1, klon
119        IF (zt(i).GT.tmax) THEN
120           jbad = jbad + 1
121           jadrs(jbad) = i
122        ENDIF
123      ENDDO
124
125      IF (jbad .GT. 0) THEN
126        ok = .FALSE.
127        DO i = 1, jbad
128          PRINT *,'i,tsol =',jadrs(i),zt(jadrs(i))
129        ENDDO
130      ENDIF
131
132      ! Look for temperatures lower than tmin
133      jbad = 0
134      DO i = 1, klon
135        IF (zt(i).LT.tmin) THEN
136           jbad = jbad + 1
137           jadrs(jbad) = i
138        ENDIF
139      ENDDO
140
141      IF (jbad .GT. 0) THEN
142        ok = .FALSE.
143        DO i = 1, jbad
144          PRINT *,'i,tsol =',jadrs(i),zt(jadrs(i))
145        ENDDO
146      ENDIF
147c
148      IF (.NOT. ok) THEN
149         textout='hgardfou stops '//text
150         CALL abort_physic("hgardfou", textout, 1)
151      ENDIF
152
153      END SUBROUTINE hgardfou
154
155      END MODULE hgardfou_mod
Note: See TracBrowser for help on using the repository browser.