LMDZ
hgardfou.F90
Go to the documentation of this file.
1 
2 ! $Id: hgardfou.F90 2346 2015-08-21 15:13:46Z emillour $
3 SUBROUTINE hgardfou(t, tsol, text,abortphy)
4  USE dimphy
7  USE print_control_mod, ONLY: lunout
8  IMPLICIT NONE
9  ! ======================================================================
10  ! Verifier la temperature
11  ! ======================================================================
12  include "YOMCST.h"
13  REAL t(klon, klev), tsol(klon, nbsrf)
14  CHARACTER(len=*), intent(in):: text
15  CHARACTER (LEN=20) :: modname = 'hgardfou'
16  INTEGER abortphy
17 
18  INTEGER i, k, nsrf
19  REAL zt(klon)
20  INTEGER jadrs(klon), jbad
21  LOGICAL ok
22 
23  LOGICAL firstcall
24  SAVE firstcall
25  DATA firstcall/.true./
26  !$OMP THREADPRIVATE(firstcall)
27 
28  IF (firstcall) THEN
29  WRITE (lunout, *) 'hgardfou garantit la temperature dans [100,370] K'
30  firstcall = .false.
31  ! DO i = 1, klon
32  ! WRITE(lunout,*)'i=',i,'rlon=',rlon(i),'rlat=',rlat(i)
33  ! ENDDO
34 
35  END IF
36 
37  ok = .true.
38  DO k = 1, klev
39  DO i = 1, klon
40  zt(i) = t(i, k)
41  END DO
42 #ifdef CRAY
43  CALL whenfgt(klon, zt, 1, 370.0, jadrs, jbad)
44 #else
45  jbad = 0
46  DO i = 1, klon
47  IF (zt(i)>370.) THEN
48  jbad = jbad + 1
49  jadrs(jbad) = i
50  END IF
51  END DO
52 #endif
53  IF (jbad>0) THEN
54  ok = .false.
55  DO i = 1, jbad
56  WRITE (lunout, *) 'i,k,temperature,lon,lat,pourc ter,lic,oce,sic =', &
57  jadrs(i), k, zt(jadrs(i)), rlon(jadrs(i)), rlat(jadrs(i)), &
58  (pctsrf(jadrs(i),nsrf), nsrf=1, nbsrf)
59  END DO
60  END IF
61 #ifdef CRAY
62  CALL whenflt(klon, zt, 1, 100.0, jadrs, jbad)
63 #else
64  jbad = 0
65  DO i = 1, klon
66  ! IF (zt(i).LT.100.0) THEN
67  IF (zt(i)<50.0) THEN
68  jbad = jbad + 1
69  jadrs(jbad) = i
70  END IF
71  END DO
72 #endif
73  IF (jbad>0) THEN
74  ok = .false.
75  DO i = 1, jbad
76  WRITE (lunout, *) 'i,k,temperature,lon,lat,pourc ter,lic,oce,sic =', &
77  jadrs(i), k, zt(jadrs(i)), rlon(jadrs(i)), rlat(jadrs(i)), &
78  (pctsrf(jadrs(i),nsrf), nsrf=1, nbsrf)
79  END DO
80  END IF
81  END DO
82 
83  DO nsrf = 1, nbsrf
84  DO i = 1, klon
85  zt(i) = tsol(i, nsrf)
86  END DO
87 #ifdef CRAY
88  CALL whenfgt(klon, zt, 1, 370.0, jadrs, jbad)
89 #else
90  jbad = 0
91  DO i = 1, klon
92  IF (zt(i)>370.0) THEN
93  jbad = jbad + 1
94  jadrs(jbad) = i
95  END IF
96  END DO
97 #endif
98  IF (jbad>0) THEN
99  ok = .false.
100  DO i = 1, jbad
101  WRITE (lunout, *) &
102  'i,nsrf,temperature,lon,lat,pourc ter,lic,oce,sic =', jadrs(i), &
103  nsrf, zt(jadrs(i)), rlon(jadrs(i)), rlat(jadrs(i)), &
104  pctsrf(jadrs(i), nsrf)
105  END DO
106  END IF
107 #ifdef CRAY
108  CALL whenflt(klon, zt, 1, 100.0, jadrs, jbad)
109 #else
110  jbad = 0
111  DO i = 1, klon
112  ! IF (zt(i).LT.100.0) THEN
113  IF (zt(i)<50.0) THEN
114  jbad = jbad + 1
115  jadrs(jbad) = i
116  END IF
117  END DO
118 #endif
119  IF (jbad>0) THEN
120  ok = .false.
121  DO i = 1, jbad
122  WRITE (lunout, *) &
123  'i,nsrf,temperature,lon,lat,pourc ter,lic,oce,sic =', jadrs(i), &
124  nsrf, zt(jadrs(i)), rlon(jadrs(i)), rlat(jadrs(i)), &
125  pctsrf(jadrs(i), nsrf)
126  END DO
127  END IF
128  END DO
129 
130 ! IF (.NOT. ok) CALL abort_physic(modname, text, 1)
131  IF (.NOT. ok) abortphy=1
132 
133 END SUBROUTINE hgardfou
integer, save klon
Definition: dimphy.F90:3
real, dimension(:,:), allocatable, save pctsrf
integer, save klev
Definition: dimphy.F90:7
!$Id itapm1 ENDIF!IM on interpole les champs sur les niveaux STD de pression!IM a chaque pas de temps de la physique c!positionnement de l argument logique a false c!pour ne pas recalculer deux fois la meme chose!c!a cet effet un appel a plevel_new a ete deplace c!a la fin de la serie d appels c!la boucle DO nlevSTD a ete internalisee c!dans d ou la creation de cette routine c c!CALL false
Definition: calcul_STDlev.h:26
real, dimension(:), allocatable, save rlon
!$Id itapm1 ENDIF!IM on interpole les champs sur les niveaux STD de pression!IM a chaque pas de temps de la physique c!positionnement de l argument logique a false c!pour ne pas recalculer deux fois la meme chose!c!a cet effet un appel a plevel_new a ete deplace c!a la fin de la serie d appels c!la boucle DO nlevSTD a ete internalisee c!dans d ou la creation de cette routine c c!CALL ulevSTD CALL &zphi philevSTD CALL &zx_rh rhlevSTD!DO klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon klev DO klon du jour ou toutes les read_climoz CALL true
subroutine hgardfou(t, tsol, text, abortphy)
Definition: hgardfou.F90:4
integer, parameter nbsrf
real, dimension(:), allocatable, save rlat
Definition: dimphy.F90:1
!$Header!gestion des impressions de sorties et de débogage la sortie standard prt_level COMMON comprint lunout
Definition: iniprint.h:7