source: LMDZ6/trunk/libf/phylmd/lmdz_ratqs_ini.f90 @ 5321

Last change on this file since 5321 was 5278, checked in by abarral, 3 weeks ago

Fix: duplicate save attribute

File size: 2.4 KB
RevLine 
[4613]1MODULE lmdz_ratqs_ini
2
3IMPLICIT NONE
4
5integer :: lunout
6
7INTEGER, SAVE, PROTECTED :: nbsrf,is_lic,is_ter
8REAL, SAVE, PROTECTED :: RG,RV,RD,RCPD,RLSTT,RLVTT,RTT
9REAL, SAVE, PROTECTED :: a_ratqs_cv
10REAL, SAVE, PROTECTED :: tau_var
11REAL, SAVE, PROTECTED :: fac_tau
12REAL, SAVE, PROTECTED :: tau_cumul
13REAL, SAVE, PROTECTED :: a_ratqs_wake
14INTEGER, SAVE, PROTECTED :: dqimpl
15
16real, allocatable, SAVE :: povariance(:,:)
17!$OMP THREADPRIVATE(povariance)
18real, allocatable, SAVE :: var_conv(:,:)
19!$OMP THREADPRIVATE(var_conv)
20
21!$OMP THREADPRIVATE(a_ratqs_cv,tau_var,fac_tau,tau_cumul,a_ratqs_wake)
22
23
24CONTAINS
25SUBROUTINE ratqs_ini(klon,klev,iflag_thermals,lunout_in,nbsrf_in,is_lic_in,is_ter_in,RG_in,RV_in,RD_in,RCPD_in,RLSTT_in,RLVTT_in,RTT_in)
26
27   USE ioipsl_getin_p_mod, ONLY : getin_p
28
29integer, intent(in) :: klon,klev,iflag_thermals,lunout_in
30integer, intent(in) :: nbsrf_in,is_lic_in,is_ter_in
31real, intent(in) :: RG_in,RV_in,RD_in,RCPD_in,RLSTT_in,RLVTT_in,RTT_in
32
33integer :: i,k
34
35nbsrf   =nbsrf_in
36is_lic  =is_lic_in
37is_ter  =is_ter_in
38RG      =RG_in   
39RV      =RV_in
40RD      =RD_in
41RCPD    =RCPD_in
42RLSTT   =RLSTT_in
43RLVTT   =RLVTT_in
44RTT     =RTT_in
45
46print*,'ratqs_ini'
47if (iflag_thermals==15.or.iflag_thermals==16) then
48   dqimpl=-1
49else
50   dqimpl=1
51endif
52lunout=lunout_in
53
54allocate(povariance(klon,klev))
55allocate(var_conv(klon,klev))
56
57
[4812]58tau_var = 700. ! temps de relaxation de la variabilit?? pour les thermiques
[4613]59fac_tau = 2.
60tau_cumul = 1000
[4812]61a_ratqs_wake = 3.    ! param??tre pilotant l'importance du terme d??pendant des poches froides
[4613]62a_ratqs_cv = 1.
63CALL getin_p('tau_var', tau_var)
64CALL getin_p('fac_tau', fac_tau)
65CALL getin_p('tau_cumul', tau_cumul)
66CALL getin_p('a_ratqs_wake', a_ratqs_wake)
[4739]67CALL getin_p('a_ratqs_cv', a_ratqs_cv)
[4613]68
[4739]69!--------------------------------------------------------
[4812]70! Initialisation des variances pour la param??trisation
[4739]71! pronostique des variances de Louis.
72! Ne marche pour le moment qu'en 1D en forcant une
[4812]73! initialisation des variances ?? une valeur constante.
[4739]74! A terme la variance doit devenir une variable d'etat
75! passee en argument
76!--------------------------------------------------------
77
78if (klon.eq.1) then
79    do k=1,klev
80      do i=1,klon
[4812]81          povariance(i,k) = 0.00000000001
82          var_conv(i,k) = 0.00000000001
[4739]83      enddo
84    enddo
85else
[4740]86    print*, 'conserver la variance dans les restarts'
[4739]87endif
88!--------------------------------------------------------
89
[4613]90 RETURN
91
92END SUBROUTINE ratqs_ini
93END MODULE lmdz_ratqs_ini
Note: See TracBrowser for help on using the repository browser.