LMDZ
suphy2.F90
Go to the documentation of this file.
1 !OPTIONS XOPT(NOEVAL)
2 SUBROUTINE suphy2(KULOUT)
3 
4 !**** *SUPHY2* - Initialize common YOMPHY2 physics controlling
5 ! constants
6 
7 ! Purpose.
8 ! --------
9 ! Initialize YOMPHY2, the common that contains the parameters
10 ! for the control part of the physics of the model.
11 
12 !** Interface.
13 ! ----------
14 ! *CALL* *SUPHY2(KULOUT)
15 
16 ! Explicit arguments :
17 ! --------------------
18 ! KULOUT : Logical unit for the output
19 
20 ! Implicit arguments :
21 ! --------------------
22 ! COMMON YOMPHY2
23 
24 ! Method.
25 ! -------
26 ! See documentation
27 
28 ! Externals.
29 ! ----------
30 
31 ! Reference.
32 ! ----------
33 ! Documentation ARPEGE
34 
35 ! Author.
36 ! -------
37 ! J.-F. Geleyn .
38 ! Original : 90-9-1
39 
40 ! Modifications.
41 ! --------------
42 ! R. EL Khatib : 93-04-02 Set-up defaults controled by LECMWF
43 ! J.-F. Geleyn : 93-08-19 New cloudiness diagnostics.
44 ! J.-F. Geleyn : 95-04-10 Anti-fibril. Girard-Delage.
45 ! P. Marquet : 97-02-18 Value of VETAF=VAH/VP00+VBH.
46 ! J.M. Piriou : 97-04-17 XMULAF default value.
47 ! E. Bazile : 98-03-10 Introduce XMUCVPP.
48 ! W. Owcarz : 2000-03-27 Set a default value for TSPHY
49 ! R. EL Khatib : 2000-06-13 RIPBLC
50 ! R. EL Khatib : 2000-08-21 Turbulent gusts setup
51 ! J.M. Piriou : 2002-01-10 set default values to operational ones.
52 ! Modified by R. EL Khatib : 02-03-29 Control XMULAF<0 ; add LMULAF
53 ! Modified by D. Banciu : 02-12-09 Introduction of XDAMP
54 ! M.Hamrud 01-Oct-2003 CY28 Cleaning
55 ! ------------------------------------------------------------------
56 
57 USE parkind1 ,ONLY : jpim ,jprb
58 USE yomhook ,ONLY : lhook, dr_hook
59 
60 ! Ce qui concerne NULNAM commente par MPL le 15.04.09
61 !USE YOMLUN , ONLY : NULNAM
62 USE yomct0b , ONLY : lecmwf
63 ! commente par MPL 25.11.08
64 !USE YOMGEM , ONLY : VALH ,VBH
65 USE yomdim , ONLY : nflevg
66 USE yomphy2 , ONLY : ntshm ,ntsml ,xmucvpp ,lmulaf ,&
67  & xmulaf ,xdamp ,hclp ,htcls ,&
68  & ripblc ,&
69  & lraftur ,gz0raf ,facraf ,&
70  & hvcls ,htshm ,htsml ,&
71  & tsphy
72 
73 IMPLICIT NONE
74 
75 INTEGER(KIND=JPIM),INTENT(IN) :: KULOUT
76 INTEGER(KIND=JPIM) :: JLEV
77 
78 REAL(KIND=JPRB) :: ZVETAF
79 REAL(KIND=JPRB) :: ZHOOK_HANDLE
80 
81 #include "abor1.intfb.h"
82 #include "posnam.intfb.h"
83 
84 #include "namphy2.h"
85 ! ------------------------------------------------------------------
86 
87 !* 1. Set default values.
88 ! -------------------
89 
90 ! 1.1 Set implicit default values
91 
92 IF (lhook) CALL dr_hook('SUPHY2',0,zhook_handle)
93 xmulaf=-1.75_jprb
94 xmucvpp=0._jprb
95 xdamp=0._jprb
96 hclp=1500._jprb
97 htcls=2._jprb
98 hvcls=10._jprb
99 htshm=0.450_jprb
100 htsml=0.785_jprb
101 tsphy=1._jprb
102 ripblc=0.5_jprb
103 lraftur=.false.
104 gz0raf=10.0_jprb
105 facraf=15.0_jprb
106 lmulaf=.false.
107 
108 ! 1.2 Modify default values according to LECMWF
109 
110 IF (lecmwf) THEN
111 ELSE
112  lraftur=.true.
113 ENDIF
114 
115 ! Remark : values for TSPHY, NTSHM/ML are calculated and not set up.
116 
117 ! ------------------------------------------------------------------
118 
119 !* 2. Modify default values.
120 ! ----------------------
121 
122 ! Ce qui concerne NAMPHY2 commente par MPL le 15.04.09
123 !CALL POSNAM(NULNAM,'NAMPHY2')
124 !READ(NULNAM,NAMPHY2)
125 ! ------------------------------------------------------------------
126 
127 !* 3. Compute cloud transition indexes.
128 ! ---------------------------------
129 
130 ntshm=0
131 ntsml=0
132 ! commente par MPL 25.11.08
133 !DO JLEV=1,NFLEVG
134 ! ZVETAF=(VALH(JLEV)+VBH(JLEV)+VALH(JLEV-1)+VBH(JLEV-1))*0.5_JPRB
135 ! IF (ZVETAF <= HTSHM) THEN
136 ! NTSHM=JLEV
137 ! ENDIF
138 ! IF (ZVETAF <= HTSML) THEN
139 ! NTSML=JLEV
140 ! ENDIF
141 !ENDDO
142 
143 ! ------------------------------------------------------------------
144 
145 !* 4. Print final values.
146 ! -------------------
147 
148 WRITE(unit=kulout,fmt='('' COMMON YOMPHY2 '')')
149 WRITE(unit=kulout,fmt='('' XMUCVPP = '',E10.4,'' XMULAF = '',E10.4 &
150  & ,'' XDAMP = '',E10.4 &
151  & ,'' LMULAF = '',L2,/,'' HTCLS = '',E10.4 &
152  & ,'' HVCLS = '',E10.4,'' HCLP = '',E10.4,/&
153  & ,'' RIPBLC = '',F8.4 &
154  & ,'' LRAFTUR = '',L2,'' GZ0RAF = '',E10.4,'' FACRAF = '',E10.4 &
155  & ,'' HTSHM = '',F8.4,'' NTSHM = '',I3,'' HTSML = '',F8.4 &
156  & ,'' NTSML = '',I3 &
157  & )')&
159  & htcls,hvcls,hclp,&
160  & ripblc,&
161  & lraftur,gz0raf,facraf,&
163 
164 !* 5. Control
165 ! -------
166 
167 IF (xmulaf > 0.0_jprb) THEN
168  WRITE(kulout,*) 'XMULAF SHOULD BE NEGATIVE'
169  CALL abor1('SUPHY2 : ABOR1 CALLED')
170 ENDIF
171 
172 IF ((xdamp /= 0.0_jprb).AND.(xmucvpp /= 0.0_jprb)) THEN
173  WRITE(unit=kulout,fmt='(A)') 'INCONSISTENCY BETWEEN XDAMP AND XMUCVPP !'
174  CALL abor1('XDAMP/=0. IMPLIES XMUCVPP=0.!...')
175 ENDIF
176 
177 ! ------------------------------------------------------------------
178 
179 IF (lhook) CALL dr_hook('SUPHY2',1,zhook_handle)
180 END SUBROUTINE suphy2
logical lraftur
Definition: yomphy2.F90:64
real(kind=jprb) gz0raf
Definition: yomphy2.F90:62
real(kind=jprb) htsml
Definition: yomphy2.F90:60
subroutine abor1(CDTEXT)
Definition: abor1.F90:2
subroutine suphy2(KULOUT)
Definition: suphy2.F90:3
integer(kind=jpim) nflevg
Definition: yomdim.F90:112
real(kind=jprb) htshm
Definition: yomphy2.F90:59
!$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
logical lmulaf
Definition: yomphy2.F90:65
logical lecmwf
Definition: yomct0b.F90:15
real(kind=jprb) tsphy
Definition: yomphy2.F90:52
real(kind=jprb) ripblc
Definition: yomphy2.F90:61
integer, parameter jprb
Definition: parkind1.F90:31
real(kind=jprb) hclp
Definition: yomphy2.F90:56
Definition: yomdim.F90:1
real(kind=jprb) hvcls
Definition: yomphy2.F90:58
real(kind=jprb) xmucvpp
Definition: yomphy2.F90:53
real(kind=jprb) xmulaf
Definition: yomphy2.F90:54
!$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
logical lhook
Definition: yomhook.F90:12
real(kind=jprb) htcls
Definition: yomphy2.F90:57
subroutine dr_hook(CDNAME, KSWITCH, PKEY)
Definition: yomhook.F90:17
integer(kind=jpim) ntshm
Definition: yomphy2.F90:50
integer, parameter jpim
Definition: parkind1.F90:13
real(kind=jprb) xdamp
Definition: yomphy2.F90:55
!$Header!integer nvarmx s s unit
Definition: gradsdef.h:20
real(kind=jprb) facraf
Definition: yomphy2.F90:63
integer(kind=jpim) ntsml
Definition: yomphy2.F90:51