source: LMDZ6/trunk/libf/phylmd/rrtm/suphy2.F90 @ 3981

Last change on this file since 3981 was 1990, checked in by Laurent Fairhead, 10 years ago

Corrections à la version r1989 pour permettre la compilation avec RRTM
Inclusion de la licence CeCILL_V2 pour RRTM


Changes to revision r1989 to enable RRTM code compilation
RRTM part put under CeCILL_V2 licence

  • Property copyright set to
    Name of program: LMDZ
    Creation date: 1984
    Version: LMDZ5
    License: CeCILL version 2
    Holder: Laboratoire de m\'et\'eorologie dynamique, CNRS, UMR 8539
    See the license file in the root directory
File size: 4.8 KB
Line 
1!OPTIONS XOPT(NOEVAL)
2SUBROUTINE 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
57USE PARKIND1  ,ONLY : JPIM     ,JPRB
58USE YOMHOOK   ,ONLY : LHOOK,   DR_HOOK
59
60! Ce qui concerne NULNAM commente par MPL le 15.04.09
61!USE YOMLUN   , ONLY : NULNAM
62USE YOMCT0B  , ONLY : LECMWF
63! commente par MPL 25.11.08
64!USE YOMGEM   , ONLY : VALH     ,VBH
65USE YOMDIM   , ONLY : NFLEVG
66USE YOMPHY2  , ONLY : NTSHM    ,NTSML    ,XMUCVPP  ,LMULAF   ,&
67 & XMULAF   ,XDAMP    ,HCLP     ,HTCLS    ,&
68 & RIPBLC   ,&
69 & LRAFTUR  ,GZ0RAF   ,FACRAF   ,&
70 & HVCLS    ,HTSHM    ,HTSML    ,&
71 & TSPHY 
72
73IMPLICIT NONE
74
75INTEGER(KIND=JPIM),INTENT(IN)    :: KULOUT
76INTEGER(KIND=JPIM) :: JLEV
77
78REAL(KIND=JPRB) :: ZVETAF
79REAL(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
92IF (LHOOK) CALL DR_HOOK('SUPHY2',0,ZHOOK_HANDLE)
93XMULAF=-1.75_JPRB
94XMUCVPP=0._JPRB
95XDAMP=0._JPRB
96HCLP=1500._JPRB
97HTCLS=2._JPRB
98HVCLS=10._JPRB
99HTSHM=0.450_JPRB
100HTSML=0.785_JPRB
101TSPHY=1._JPRB
102RIPBLC=0.5_JPRB
103LRAFTUR=.FALSE.
104GZ0RAF=10.0_JPRB
105FACRAF=15.0_JPRB
106LMULAF=.FALSE.
107
108!        1.2 Modify default values according to LECMWF
109
110IF (LECMWF) THEN
111ELSE
112  LRAFTUR=.TRUE.
113ENDIF
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
130NTSHM=0
131NTSML=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
148WRITE(UNIT=KULOUT,FMT='('' COMMON YOMPHY2 '')')
149WRITE(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 & )')&
158 & XMUCVPP,XMULAF,XDAMP,LMULAF,&
159 & HTCLS,HVCLS,HCLP,&
160 & RIPBLC,&
161 & LRAFTUR,GZ0RAF,FACRAF,&
162 & HTSHM,NTSHM,HTSML,NTSML 
163
164!*       5.    Control
165!              -------
166
167IF (XMULAF > 0.0_JPRB) THEN
168  WRITE(KULOUT,*) 'XMULAF SHOULD BE NEGATIVE'
169  CALL ABOR1('SUPHY2 : ABOR1 CALLED')
170ENDIF
171
172IF ((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.!...')
175ENDIF
176
177!     ------------------------------------------------------------------
178
179IF (LHOOK) CALL DR_HOOK('SUPHY2',1,ZHOOK_HANDLE)
180END SUBROUTINE SUPHY2
Note: See TracBrowser for help on using the repository browser.