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

Last change on this file since 5407 was 5400, checked in by evignon, 5 days ago

ajout de omp threadprivate manquants

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