LMDZ
printflag.F90
Go to the documentation of this file.
1 
2 ! $Id$
3 
4 SUBROUTINE printflag(tabcntr0, radpas, ok_journe, ok_instan, ok_region)
5 
6 
7 
8  ! Auteur : P. Le Van
9 
10  IMPLICIT NONE
11 
12  REAL tabcntr0(100)
13  LOGICAL cycle_diurn0, soil_model0, new_oliq0, ok_orodr0
14  LOGICAL ok_orolf0, ok_limitvr0
15  LOGICAL ok_journe, ok_instan, ok_region
16  INTEGER radpas, radpas0
17 
18  include "clesphys.h"
19 
20 
21  print 100
22  print *, ' ******************************************************* &
23  & &
24  & ************'
25  print *, ' ******** Choix des principales cles de la physique &
26  & &
27  & *********'
28  print *, ' ******************************************************* &
29  & &
30  & ************'
31  print 100
32  print 10, cycle_diurne, soil_model
33  print 100
34 
35  IF (iflag_con==1) THEN
36  print *, ' ***** Shema convection LMD &
37  & &
38  & ******'
39  ELSE IF (iflag_con==2) THEN
40  print *, ' ***** Shema convection Tiedtke &
41  & &
42  & ******'
43  ELSE IF (iflag_con>=3) THEN
44  print *, ' ***** Shema convection Emanuel &
45  & &
46  & ******'
47  END IF
48  print 100
49 
50  print 11, new_oliq, ok_orodr, ok_orolf
51  print 100
52 
53  print 7, ok_limitvrai
54  print 100
55 
56  print 12, nbapp_rad
57  print 100
58 
59  print 8, radpas
60  print 100
61 
62  print 4, ok_journe, ok_instan, ok_region
63  print 100
64  print 100
65 
66 
67  cycle_diurn0 = .false.
68  soil_model0 = .false.
69  new_oliq0 = .false.
70  ok_orodr0 = .false.
71  ok_orolf0 = .false.
72  ok_limitvr0 = .false.
73 
74  IF (tabcntr0(7)==1.) cycle_diurn0 = .true.
75  IF (tabcntr0(8)==1.) soil_model0 = .true.
76  IF (tabcntr0(9)==1.) new_oliq0 = .true.
77  IF (tabcntr0(10)==1.) ok_orodr0 = .true.
78  IF (tabcntr0(11)==1.) ok_orolf0 = .true.
79  IF (tabcntr0(12)==1.) ok_limitvr0 = .true.
80 
81  print *, ' $$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$$ &
82  & &
83  & $$$$$$$$$$$$$'
84  print 100
85 
86  IF (int(tabcntr0(5))/=iflag_con) THEN
87  print 20, int(tabcntr0(5)), iflag_con
88  print 100
89  END IF
90 
91  IF (int(tabcntr0(6))/=nbapp_rad) THEN
92  print 21, int(tabcntr0(6)), nbapp_rad
93  ! radpas0 = NINT( 86400./tabcntr0(1)/INT( tabcntr0(6) ) )
94  print 100
95  ! PRINT 22, radpas0, radpas
96  print 100
97  END IF
98 
99  IF (cycle_diurn0 .AND. .NOT. cycle_diurne .OR. .NOT. cycle_diurn0 .AND. &
100  cycle_diurne) THEN
101  print 13, cycle_diurn0, cycle_diurne
102  print 100
103  END IF
104 
105  IF (soil_model0 .AND. .NOT. soil_model .OR. .NOT. soil_model0 .AND. &
106  soil_model) THEN
107  print 14, soil_model0, soil_model
108  print 100
109  END IF
110 
111  IF (new_oliq0 .AND. .NOT. new_oliq .OR. .NOT. new_oliq0 .AND. new_oliq) &
112  THEN
113  print 16, new_oliq0, new_oliq
114  print 100
115  END IF
116 
117  IF (ok_orodr0 .AND. .NOT. ok_orodr .OR. .NOT. ok_orodr0 .AND. ok_orodr) &
118  THEN
119  print 15, ok_orodr0, ok_orodr
120  print 100
121  END IF
122 
123  IF (ok_orolf0 .AND. .NOT. ok_orolf .OR. .NOT. ok_orolf0 .AND. ok_orolf) &
124  THEN
125  print 17, ok_orolf0, ok_orolf
126  print 100
127  END IF
128 
129  IF (ok_limitvr0 .AND. .NOT. ok_limitvrai .OR. .NOT. ok_limitvr0 .AND. &
130  ok_limitvrai) THEN
131  print 18, ok_limitvr0, ok_limitvrai
132  print 100
133  END IF
134 
135  print 100
136  print *, ' ******************************************************* &
137  & &
138  & ************'
139  print 100
140 
141 4 FORMAT (2x, 5('*'), ' ok_journe= ', l3, 3x, ',ok_instan = ', l3, 3x, &
142  ',ok_region = ', l3, 3x, 5('*'))
143 
144 7 FORMAT (2x, 5('*'), 15x, ' ok_limitvrai = ', l3, 16x, 5('*'))
145 
146 8 FORMAT (2x, '***** radpas = ', i4, 6x, &
147  ' *****')
148 
149 10 FORMAT (2x, 5('*'), ' Cycle_diurne = ', l3, 4x, ', Soil_model = ', l3, &
150  12x, 6('*'))
151 
152 
153 11 FORMAT (2x, 5('*'), ' new_oliq = ', l3, 3x, ', Ok_orodr = ', l3, 3x, &
154  ', Ok_orolf = ', l3, 3x, 5('*'))
155 
156 
157 12 FORMAT (2x, '***** Nb d appels /jour des routines de rayonn. = ', i4, 6x, &
158  ' *****')
159 
160 13 FORMAT (2x, '$$$$$$$$ Attention !! cycle_diurne different sur', /1x, &
161  10x, ' startphy = ', l3, 2x, ' et run.def = ', l3)
162 
163 14 FORMAT (2x, '$$$$$$$$ Attention !! soil_model different sur', /1x, &
164  10x, ' startphy = ', l3, 2x, ' et run.def = ', l3)
165 
166 15 FORMAT (2x, '$$$$$$$$ Attention !! ok_orodr different sur', /1x, &
167  10x, ' startphy = ', l3, 2x, ' et run.def = ', l3)
168 
169 16 FORMAT (2x, '$$$$$$$$ Attention !! new_oliq different sur', /1x, &
170  10x, ' startphy = ', l3, 2x, ' et run.def = ', l3)
171 
172 17 FORMAT (2x, '$$$$$$$$ Attention !! ok_orolf different sur', /1x, &
173  10x, ' startphy = ', l3, 2x, ' et run.def = ', l3)
174 
175 18 FORMAT (2x, '$$$$$$$$ Attention !! ok_limitvrai different sur', /1x, &
176  10x, ' startphy = ', l3, 2x, ' et run.def = ', l3)
177 
178 20 FORMAT (/2x, '$$$$$$$$ Attention !! iflag_con different sur', /1x, &
179  10x, ' startphy = ', i3, 2x, ' et run.def = ', i3)
180 
181 21 FORMAT (2x, '$$$$$$$$ Attention !! nbapp_rad different sur', /1x, &
182  10x, ' startphy = ', i3, 2x, ' et run.def = ', i3)
183 
184 22 FORMAT (2x, '$$$$$$$$ Attention !! radpas different sur', /1x, &
185  10x, ' startphy = ', i3, 2x, ' et run.def = ', i3)
186 
187 100 FORMAT (/)
188 
189  RETURN
190 END SUBROUTINE printflag
!$Header!c include clesph0 h c COMMON clesph0 ok_orolf
Definition: clesph0.h:6
!$Header!c include clesph0 h c COMMON clesph0 soil_model
Definition: clesph0.h:6
!$Header!c include clesph0 h c COMMON clesph0 ok_orodr
Definition: clesph0.h:6
!$Id ok_orolf LOGICAL ok_limitvrai LOGICAL ok_all_xml INTEGER iflag_con
Definition: clesphys.h:12
!$Header!c include clesph0 h c COMMON clesph0 cycle_diurne
Definition: clesph0.h:6
!$Header!c include clesph0 h c COMMON clesph0 ok_limitvrai
Definition: clesph0.h:6
!$Header!c include clesph0 h c COMMON clesph0 new_oliq
Definition: clesph0.h:6
!$Header!c include clesph0 h c COMMON clesph0 nbapp_rad
Definition: clesph0.h:6
!$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
subroutine printflag(tabcntr0, radpas, ok_journe, ok_instan, ok_region)
Definition: printflag.F90:5
!$Header!c c INCLUDE fxyprim h c c c Fonctions in line c c REAL fyprim REAL rj c c il faut la calculer avant d appeler ces fonctions c c c Fonctions a changer selon x(x) et y(y) choisis.c-----------------------------------------------------------------c c.....ici
!$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