Changeset 4843
- Timestamp:
- Mar 4, 2024, 6:58:03 PM (9 months ago)
- Location:
- LMDZ6/trunk/libf/phylmd
- Files:
-
- 12 edited
Legend:
- Unmodified
- Added
- Removed
-
LMDZ6/trunk/libf/phylmd/alpale.h
r4090 r4843 5 5 6 6 ! dans alealp_th, thermcell_alp, physiq_mod, conf_phys 7 integer :: iflag_trig_bl,iflag_clos_bl 7 integer :: iflag_trig_bl,iflag_clos_bl,iflag_strig 8 8 integer :: tau_trig_shallow,tau_trig_deep 9 real :: s_trig 9 real :: s_trig, h_trig 10 10 ! thermcell_alp et convection ... 11 11 integer :: iflag_coupl,iflag_clos,iflag_wake … … 13 13 real :: alp_bl_k 14 14 15 common/calpale1/iflag_trig_bl,iflag_clos_bl,tau_trig_shallow,tau_trig_deep 16 common/calpale2/s_trig,iflag_coupl,iflag_clos,iflag_wake,alp_bl_k 15 common/calpale1/iflag_trig_bl,iflag_clos_bl,tau_trig_shallow,tau_trig_deep,iflag_strig 16 common/calpale2/s_trig,iflag_coupl,iflag_clos,iflag_wake,alp_bl_k,h_trig 17 17 18 18 !$OMP THREADPRIVATE(/calpale1/,/calpale2/) -
LMDZ6/trunk/libf/phylmd/alpale_th.F90
r4827 r4843 3 3 ! 4 4 SUBROUTINE alpale_th ( dtime, lmax_th, t_seri, cell_area, & 5 cin, s2, n2, &5 cin, s2, n2, strig, & 6 6 ale_bl_trig, ale_bl_stat, ale_bl, & 7 7 alp_bl, alp_bl_stat, & … … 36 36 REAL, DIMENSION(klon), INTENT(IN) :: ale_bl_stat 37 37 REAL, DIMENSION(klon), INTENT(IN) :: cin 38 REAL, DIMENSION(klon), INTENT(IN) :: s2, n2 38 REAL, DIMENSION(klon), INTENT(IN) :: s2, n2, strig 39 39 40 40 REAL, DIMENSION(klon), INTENT(INOUT) :: ale_bl_trig, ale_bl … … 161 161 if ( (ale_bl_stat(i) .gt. abs(cin(i))+1.e-10) ) then 162 162 proba_notrig(i)=proba_notrig(i)* & 163 (1.-exp(-s _trig/s2(i)))**(n2(i)*dtime/tau_trig(i))163 (1.-exp(-strig(i)/s2(i)))**(n2(i)*dtime/tau_trig(i)) 164 164 ! print *, 'proba_notrig(i) ',proba_notrig(i) 165 165 if (random_notrig(i) .ge. proba_notrig(i)) then … … 168 168 ale_bl_trig(i)=0. 169 169 endif 170 birth_rate(i) = n2(i)*exp(-s _trig/s2(i))/(tau_trig(i)*cell_area(i))170 birth_rate(i) = n2(i)*exp(-strig(i)/s2(i))/(tau_trig(i)*cell_area(i)) 171 171 !!! birth_rate(i) = max(birth_rate(i),1.e-18) 172 172 else … … 183 183 if ( (Ale_bl(i) .gt. abs(cin(i))+1.e-10) ) then 184 184 proba_notrig(i)=proba_notrig(i)* & 185 (1.-exp(-s _trig/s2(i)))**(n2(i)*dtime/tau_trig(i))185 (1.-exp(-strig(i)/s2(i)))**(n2(i)*dtime/tau_trig(i)) 186 186 ! print *, 'proba_notrig(i) ',proba_notrig(i) 187 187 if (random_notrig(i) .ge. proba_notrig(i)) then … … 190 190 ale_bl_trig(i)=0. 191 191 endif 192 birth_rate(i) = n2(i)*exp(-s _trig/s2(i))/(tau_trig(i)*cell_area(i))192 birth_rate(i) = n2(i)*exp(-strig(i)/s2(i))/(tau_trig(i)*cell_area(i)) 193 193 !!! birth_rate(i) = max(birth_rate(i),1.e-18) 194 194 else … … 283 283 do i=1,klon 284 284 if ( (ale_bl_ref(i) .gt. abs(cin(i))+1.e-10) ) then 285 birth_number = n2(i)*exp(-s _trig/s2(i))285 birth_number = n2(i)*exp(-strig(i)/s2(i)) 286 286 birth_rate(i) = birth_number/(tau_trig(i)*cell_area(i)) 287 287 !!! birth_rate(i) = max(birth_rate(i),1.e-18) -
LMDZ6/trunk/libf/phylmd/calltherm.F90
r4837 r4843 12 12 & ,pbl_tke,pctsrf,omega,airephy & 13 13 & ,zlcl_th,fraca0,w0,w_conv,therm_tke_max0,env_tke_max0 & 14 & ,n2,s2, ale_bl_stat &14 & ,n2,s2,strig,zcong,ale_bl_stat & 15 15 & ,therm_tke_max,env_tke_max & 16 16 & ,alp_bl_det,alp_bl_fluct_m,alp_bl_fluct_tke & … … 87 87 real zthl(klon,klev) 88 88 real wmax_sec(klon) 89 real zcong(klon) 89 90 real zmax_sec(klon) 90 91 real f_sec(klon) … … 116 117 real zlcl_th(klon),fraca0(klon),w0(klon),w_conv(klon) 117 118 real therm_tke_max0(klon),env_tke_max0(klon) 118 real n2(klon),s2(klon) 119 real n2(klon),s2(klon),strig(klon) 119 120 real ale_bl_stat(klon) 120 121 real therm_tke_max(klon,klev),env_tke_max(klon,klev) … … 302 303 & ,zmax0,f0,zw2,fraca,ztv,zpspsk & 303 304 & ,ztla,zthl,ztva & 304 & ,pcon,rhobarz,wth3,wmax_sec,lalim,fm,alim_star,zmax &305 & ,pcon,rhobarz,wth3,wmax_sec,lalim,fm,alim_star,zmax,zcong & 305 306 #ifdef ISO 306 307 & ,xt_seri,d_xt_the & … … 314 315 & ,zw2,fraca & ! in 315 316 & ,pcon,rhobarz,wth3,wmax_sec,lalim,fm,alim_star,zmax & ! in 316 & , ale,alp,lalim_conv,wght_th & ! out317 & ,zcong,ale,alp,lalim_conv,wght_th & ! out 317 318 & ,zlcl_th,fraca0,w0,w_conv,therm_tke_max0,env_tke_max0 &! out 318 & ,n2,s2, ale_bl_stat & ! out319 & ,n2,s2,strig,ale_bl_stat & ! out 319 320 & ,therm_tke_max,env_tke_max & ! out 320 321 & ,alp_bl_det,alp_bl_fluct_m,alp_bl_fluct_tke & ! out -
LMDZ6/trunk/libf/phylmd/conf_phys_m.F90
r4754 r4843 144 144 REAL,SAVE :: tau_thermals_omp,alp_bl_k_omp 145 145 ! nrlmd le 10/04/2012 146 INTEGER,SAVE :: iflag_trig_bl_omp,iflag_clos_bl_omp 146 INTEGER,SAVE :: iflag_trig_bl_omp,iflag_clos_bl_omp,iflag_strig_omp 147 147 INTEGER,SAVE :: tau_trig_shallow_omp,tau_trig_deep_omp 148 REAL,SAVE :: s_trig_omp 148 REAL,SAVE :: s_trig_omp,h_trig_omp 149 149 ! fin nrlmd le 10/04/2012 150 150 REAL :: alp_offset … … 1559 1559 CALL getin('iflag_trig_bl',iflag_trig_bl_omp) 1560 1560 1561 !Config Key = iflag_strig 1562 !Config Desc = 1563 !Config Def = 0 1564 !Config Help = 1565 ! 1566 iflag_strig_omp = 0 1567 CALL getin('iflag_strig',iflag_strig_omp) 1568 1561 1569 !Config Key = s_trig_bl 1562 1570 !Config Desc = … … 1566 1574 s_trig_omp = 2e7 1567 1575 CALL getin('s_trig',s_trig_omp) 1576 1577 !Config Key = h_trig 1578 !Config Desc = 1579 !Config Def = 0 1580 !Config Help = 1581 ! 1582 h_trig_omp = 6000. 1583 CALL getin('h_trig',h_trig_omp) 1568 1584 1569 1585 !Config Key = tau_trig_shallow … … 2439 2455 ! nrlmd le 10/04/2012 2440 2456 iflag_trig_bl = iflag_trig_bl_omp 2457 iflag_strig = iflag_strig_omp 2441 2458 s_trig = s_trig_omp 2459 h_trig = h_trig_omp 2442 2460 tau_trig_shallow = tau_trig_shallow_omp 2443 2461 tau_trig_deep = tau_trig_deep_omp … … 2835 2853 ! nrlmd le 10/04/2012 2836 2854 WRITE(lunout,*) ' iflag_trig_bl = ', iflag_trig_bl 2855 WRITE(lunout,*) ' iflag_strig = ', iflag_strig 2837 2856 WRITE(lunout,*) ' s_trig = ', s_trig 2857 WRITE(lunout,*) ' h_trig = ', h_trig 2838 2858 WRITE(lunout,*) ' tau_trig_shallow = ', tau_trig_shallow 2839 2859 WRITE(lunout,*) ' tau_trig_deep = ', tau_trig_deep -
LMDZ6/trunk/libf/phylmd/lmdz_thermcell_alp.F90
r4593 r4843 11 11 & ,pcon,rhobarz,wth3,wmax_sec,lalim,fm,alim_star,zmax & ! in 12 12 ! 13 & , ale_bl,alp_bl,lalim_conv,wght_th & ! out13 & ,zcong,ale_bl,alp_bl,lalim_conv,wght_th & ! out 14 14 & ,zlcl,fraca0,w0,w_conv,therm_tke_max0,env_tke_max0 & ! out 15 & ,n2,s2, ale_bl_stat & ! out15 & ,n2,s2,strig,ale_bl_stat & ! out 16 16 & ,therm_tke_max,env_tke_max & ! out 17 17 & ,alp_bl_det,alp_bl_fluct_m,alp_bl_fluct_tke & ! out … … 50 50 real, intent(in) :: pplay(ngrid,nlay),pplev(ngrid,nlay+1) 51 51 integer, intent(in), dimension(ngrid) ::lmax,lalim 52 real, intent(in), dimension(ngrid) :: zmax 52 real, intent(in), dimension(ngrid) :: zmax, zcong 53 53 real, intent(in), dimension(ngrid,nlay+1) :: zw2 54 54 real, intent(in), dimension(ngrid,nlay+1) :: fraca … … 69 69 integer, intent(out), dimension(ngrid) :: lalim_conv 70 70 real, intent(out), dimension(ngrid) :: zlcl,fraca0,w0,w_conv 71 real, intent(out), dimension(ngrid) :: therm_tke_max0,env_tke_max0,n2,s2,ale_bl_stat 71 real, intent(out), dimension(ngrid) :: therm_tke_max0,env_tke_max0,n2,s2,ale_bl_stat,strig 72 72 real, intent(out), dimension(ngrid,nlay) :: therm_tke_max,env_tke_max 73 73 real, intent(out), dimension(ngrid) :: alp_bl_det,alp_bl_fluct_m,alp_bl_fluct_tke … … 94 94 real, parameter :: zmax_moy_coef=0.33 95 95 real, dimension(ngrid) :: depth ! Epaisseur moyenne du cumulus 96 real, dimension(ngrid) :: zcong_moy 96 97 real, dimension(ngrid) :: w_max ! Vitesse max statistique 97 98 real, dimension(ngrid) :: s_max(ngrid) … … 119 120 s2(ig) = 0. 120 121 ale_bl_stat(ig) = 0. 122 strig(ig) = 0. 121 123 alp_bl_det(ig) = 0. 122 124 alp_bl_fluct_m(ig) = 0. … … 249 251 s_max(:)=0. 250 252 253 254 251 255 !-----Epaisseur du nuage (depth) et détermination de la queue du spectre de panaches (n2,s2) et du panache le plus gros (s_max) 252 256 do ig=1,ngrid … … 270 274 ! print *,'avant Calcul de Wmax ' !!jyg 271 275 276 !CR: calcul de strig 277 if (iflag_strig.eq.0) then 278 strig(:)=s_trig 279 else if (iflag_strig.eq.1) then 280 do ig=1,ngrid 281 ! zcong_moy(ig)=zlcl(ig)+zmax_moy_coef*(zcong(ig)-zlcl(ig)) 282 ! strig(ig)=(hcoef*(zcong_moy(ig)-zlcl(ig))+hmin(ig))**2 283 strig(ig)=(zcong(ig)-zlcl(ig))**2 284 enddo 285 else if (iflag_strig.eq.2) then 286 do ig=1,ngrid 287 if (h_trig.gt.zlcl(ig)) then 288 strig(ig)=(h_trig-zlcl(ig))**2 289 else 290 strig(ig)=s_trig 291 endif 292 enddo 293 endif 294 272 295 susqr2pi=su_cst*sqrt(2.*Rpi) 273 296 reuler=exp(1.) -
LMDZ6/trunk/libf/phylmd/lmdz_thermcell_env.F90
r4590 r4843 3 3 4 4 SUBROUTINE thermcell_env(ngrid,nlay,po,pt,pu,pv,pplay, & 5 & pplev,zo,zh,zl,ztv,zthl,zu,zv,zpspsk,pqsat,l ev_out)5 & pplev,zo,zh,zl,ztv,zthl,zu,zv,zpspsk,pqsat,lcong,lintercong,lev_out) 6 6 7 7 !-------------------------------------------------------------- … … 22 22 real,intent(out), dimension(ngrid,nlay) :: zo,zl,zh,ztv,zthl 23 23 real,intent(out), dimension(ngrid,nlay) :: zpspsk,zu,zv,pqsat 24 24 real, intent(out), dimension(ngrid) :: lintercong 25 integer, intent(out), dimension(ngrid) :: lcong 25 26 ! Local 26 27 … … 78 79 enddo 79 80 enddo 81 !CR: Calcul du niveau de congelation 82 do ig=1,ngrid 83 lcong(ig)=1 84 enddo 85 do ig=1,ngrid 86 do ll=1,nlay-1 87 if ((zh(ig,ll).gt.273.15).and.(zh(ig,ll+1).le.273.15)) then 88 lcong(ig)=ll+1 89 lintercong(ig)=(ll*(zh(ig,ll+1)-zh(ig,ll)) & 90 & -zh(ig,ll)+273.15)/(zh(ig,ll+1)-zh(ig,ll)) 91 endif 92 enddo 93 enddo 80 94 81 95 RETURN -
LMDZ6/trunk/libf/phylmd/lmdz_thermcell_height.F90
r4590 r4843 2 2 CONTAINS 3 3 4 SUBROUTINE thermcell_height(ngrid,nlay,lalim,lmin,linter,l mix, &5 & zw2,zlev,lmax,zmax,zmax0,zmix,wmax )4 SUBROUTINE thermcell_height(ngrid,nlay,lalim,lmin,linter,lcong,lintercong,lmix, & 5 & zw2,zlev,lmax,zmax,zmax0,zmix,wmax,zcong) 6 6 IMPLICIT NONE 7 7 … … 14 14 ! Entree 15 15 integer, intent(in) :: ngrid,nlay 16 real, intent(in), dimension(ngrid) :: linter 16 real, intent(in), dimension(ngrid) :: linter,lintercong 17 17 real, intent(in), dimension(ngrid,nlay+1) :: zlev 18 18 ! Sortie 19 real, intent(out), dimension(ngrid) :: wmax,zmax,zmax0,zmix 20 integer, intent(out), dimension(ngrid) :: lmax 19 real, intent(out), dimension(ngrid) :: wmax,zmax,zmax0,zmix,zcong 20 integer, intent(out), dimension(ngrid) :: lmax,lcong 21 21 ! Les deux 22 22 integer, intent(inout), dimension(ngrid) :: lmix,lalim,lmin … … 24 24 25 25 ! local 26 real, dimension(ngrid) :: num,denom,zlevinter 26 real, dimension(ngrid) :: num,denom,zlevinter,zlevintercong 27 27 integer ig,l 28 28 … … 113 113 enddo 114 114 115 !CR:calcul du zcong 116 do ig=1,ngrid 117 ! calcul de zlevintercong 118 zlevintercong(ig)=(zlev(ig,lcong(ig)+1)-zlev(ig,lcong(ig)))* & 119 & lintercong(ig)+zlev(ig,lcong(ig))-lcong(ig)*(zlev(ig,lcong(ig)+1) & 120 & -zlev(ig,lcong(ig))) 121 zcong(ig)=zlevintercong(ig)-zlev(ig,1) 122 ! print*,"calcul zcong",lcong(ig),lintercong(ig),zlevintercong(ig),zcong(ig) 123 enddo 115 124 116 125 endif -
LMDZ6/trunk/libf/phylmd/lmdz_thermcell_main.F90
r4692 r4843 15 15 & ,zmax0, f0,zw2,fraca,ztv & 16 16 & ,zpspsk,ztla,zthl,ztva & 17 & ,pcon,rhobarz,wth3,wmax_sec,lalim,fm,alim_star,zmax &17 & ,pcon,rhobarz,wth3,wmax_sec,lalim,fm,alim_star,zmax,zcong & 18 18 #ifdef ISO 19 19 & ,xtpo,xtpdoadj & … … 134 134 real, intent(out), dimension(ngrid,nlay+1) :: fm 135 135 real, intent(out), dimension(ngrid,nlay) :: alim_star 136 real, intent(out), dimension(ngrid) :: zmax 136 real, intent(out), dimension(ngrid) :: zmax,zcong 137 137 138 138 ! local: … … 150 150 integer ig,k,l,ierr,ll 151 151 logical sorties 152 real, dimension(ngrid) :: linter,zmix, zmax_sec 153 integer,dimension(ngrid) :: lmin,lmix,lmix_bis,nivcon 152 real, dimension(ngrid) :: linter,zmix, zmax_sec,lintercong 153 integer,dimension(ngrid) :: lmin,lmix,lmix_bis,nivcon, lcong 154 154 real, dimension(ngrid,nlay) :: ztva_est 155 155 real, dimension(ngrid,nlay) :: deltaz,zlay,zdthladj,zu,zv,z_o,zl,zva,zua,z_oa … … 227 227 228 228 CALL thermcell_env(ngrid,nlay,p_o,ptemp_env,puwind,pvwind,pplay, & 229 & pplev,z_o,ztemp_env,zl,ztv,zthl,zu,zv,zpspsk,zqsat,l ev_out)229 & pplev,z_o,ztemp_env,zl,ztv,zthl,zu,zv,zpspsk,zqsat,lcong,lintercong,lev_out) 230 230 231 231 else … … 456 456 !------------------------------------------------------------------------------- 457 457 ! 458 CALL thermcell_height(ngrid,nlay,lalim,lmin,linter,l mix,zw2, &459 & zlev,lmax,zmax,zmax0,zmix,wmax )458 CALL thermcell_height(ngrid,nlay,lalim,lmin,linter,lcong,lintercong,lmix,zw2, & 459 & zlev,lmax,zmax,zmax0,zmix,wmax,zcong) 460 460 ! Attention, w2 est transforme en sa racine carree dans cette routine 461 461 ! Le probleme vient du fait que linter et lmix sont souvent egaux a 1. … … 729 729 endif 730 730 enddo 731 if (ierr==1) then732 abort_message = 'thermcellV0_main: les thermiques vont trop haut '733 CALL abort_physic (modname,abort_message,1)734 endif731 ! if (ierr==1) then 732 ! abort_message = 'thermcellV0_main: les thermiques vont trop haut ' 733 ! CALL abort_physic (modname,abort_message,1) 734 ! endif 735 735 736 736 if (prt_level.ge.1) print*,'14b OK convect8' -
LMDZ6/trunk/libf/phylmd/phys_local_var_mod.F90
r4835 r4843 402 402 REAL,ALLOCATABLE,SAVE,DIMENSION(:) :: alp_bl_fluct_m,alp_bl_fluct_tke 403 403 !$OMP THREADPRIVATE(alp_bl_fluct_m,alp_bl_fluct_tke) 404 REAL,ALLOCATABLE,SAVE,DIMENSION(:) :: alp_bl_stat, n2, s2 405 !$OMP THREADPRIVATE(alp_bl_stat, n2, s2 )404 REAL,ALLOCATABLE,SAVE,DIMENSION(:) :: alp_bl_stat, n2, s2, strig, zcong, zlcl_th 405 !$OMP THREADPRIVATE(alp_bl_stat, n2, s2, strig, zcong, zlcl_th) 406 406 REAL,ALLOCATABLE,SAVE,DIMENSION(:) :: proba_notrig, random_notrig 407 407 !$OMP THREADPRIVATE(proba_notrig, random_notrig) … … 877 877 ALLOCATE(alp_bl_fluct_m(klon), alp_bl_fluct_tke(klon)) 878 878 alp_bl_fluct_m(:)=0 ; alp_bl_fluct_tke(:)= 0. 879 ALLOCATE(alp_bl_stat(klon), n2(klon), s2(klon) )879 ALLOCATE(alp_bl_stat(klon), n2(klon), s2(klon), strig(klon), zcong(klon), zlcl_th(klon)) 880 880 alp_bl_stat(:)=0 881 881 ALLOCATE(proba_notrig(klon), random_notrig(klon)) … … 1205 1205 DEALLOCATE(alp_bl_conv,alp_bl_det) 1206 1206 DEALLOCATE(alp_bl_fluct_m,alp_bl_fluct_tke) 1207 DEALLOCATE(alp_bl_stat, n2, s2 )1207 DEALLOCATE(alp_bl_stat, n2, s2, strig, zcong, zlcl_th) 1208 1208 DEALLOCATE(proba_notrig, random_notrig) 1209 1209 !FC -
LMDZ6/trunk/libf/phylmd/phys_output_ctrlout_mod.F90
r4835 r4843 936 936 TYPE(ctrl_out), SAVE :: o_s2 = ctrl_out((/ 1, 6, 6, 6, 10, 10, 11, 11, 11, 11/), & 937 937 's2', 'Surface moyenne des panaches de type 2', 'm2', (/ ('', i=1, 10) /)) 938 938 TYPE(ctrl_out), SAVE :: o_strig = ctrl_out((/ 1, 6, 6, 6, 10, 10, 11, 11, 11, 11/), & 939 'strig', 'Surface moyenne pour atteindre niveau de congelation', 'm2', (/ ('', i=1, 10) /)) 940 TYPE(ctrl_out), SAVE :: o_zcong = ctrl_out((/ 1, 6, 6, 6, 10, 10, 11, 11, 11, 11/), & 941 'zcong', 'niveau de congelation', 'm', (/ ('', i=1, 10) /)) 942 TYPE(ctrl_out), SAVE :: o_zlcl_th = ctrl_out((/ 1, 6, 6, 6, 10, 10, 11, 11, 11, 11/), & 943 'zlcl_th', 'niveau de condensation', 'm', (/ ('', i=1, 10) /)) 939 944 !-------Déclenchement stochastique 940 945 TYPE(ctrl_out), SAVE :: o_proba_notrig = ctrl_out((/ 1, 6, 6, 6, 10, 10, 11, 11, 11, 11/), & -
LMDZ6/trunk/libf/phylmd/phys_output_write_mod.F90
r4835 r4843 98 98 o_qtaa, o_Clwaa, & 99 99 o_ftd, o_fqd, o_wdtrainA, o_wdtrainS, o_wdtrainM, & 100 o_n2, o_s2, o_ proba_notrig, &100 o_n2, o_s2, o_strig, o_zcong, o_zlcl_th, o_proba_notrig, & 101 101 o_random_notrig, o_ale_bl_stat, & 102 102 o_ale_bl_trig, o_alp_bl_det, & … … 335 335 wake_h, & 336 336 wake_omg, d_t_wake, d_q_wake, Vprecip, qtaa, Clw, & 337 wdtrainA, wdtrainS, wdtrainM, n2, s2, proba_notrig, &337 wdtrainA, wdtrainS, wdtrainM, n2, s2, strig, zcong, zlcl_th, proba_notrig, & 338 338 random_notrig, & 339 339 qclr, qcld, qss, qvc, rnebclr, rnebss, gamma_ss, & … … 1548 1548 CALL histwrite_phy(o_kh ,kh ) 1549 1549 CALL histwrite_phy(o_kh_x ,kh_x ) 1550 CALL histwrite_phy(o_strig, strig) 1551 CALL histwrite_phy(o_zcong, zcong) 1552 CALL histwrite_phy(o_zlcl_th, zlcl_th) 1550 1553 CALL histwrite_phy(o_kh_w ,kh_w ) 1551 1554 ENDIF ! (iflag_pbl_split>=1) -
LMDZ6/trunk/libf/phylmd/physiq_mod.F90
r4835 r4843 307 307 alp_bl_conv,alp_bl_det, & 308 308 alp_bl_fluct_m,alp_bl_fluct_tke, & 309 alp_bl_stat, n2, s2, &309 alp_bl_stat, n2, s2, strig, zcong, zlcl_th, & 310 310 proba_notrig, random_notrig, & 311 311 !! cv_gen, & !moved to phys_state_var_mod … … 750 750 !--------Stochastic Boundary Layer Triggering: ALE_BL-------- 751 751 !---Propri\'et\'es du thermiques au LCL 752 real zlcl_th(klon) ! Altitude du LCL calcul\'e752 ! real zlcl_th(klon) ! Altitude du LCL calcul\'e 753 753 ! continument (pcon dans 754 754 ! thermcell_main.F90) … … 3725 3725 ,pbl_tke_input,pctsrf,omega,cell_area & 3726 3726 ,zlcl_th,fraca0,w0,w_conv,therm_tke_max0,env_tke_max0 & 3727 ,n2,s2, ale_bl_stat &3727 ,n2,s2,strig,zcong,ale_bl_stat & 3728 3728 ,therm_tke_max,env_tke_max & 3729 3729 ,alp_bl_det,alp_bl_fluct_m,alp_bl_fluct_tke & … … 3769 3769 ! 3770 3770 CALL alpale_th( phys_tstep, lmax_th, t_seri, cell_area, & 3771 cin, s2, n2, &3771 cin, s2, n2, strig, & 3772 3772 ale_bl_trig, ale_bl_stat, ale_bl, & 3773 3773 alp_bl, alp_bl_stat, &
Note: See TracChangeset
for help on using the changeset viewer.