1 | module vert_prof_dissip_icosa_lmdz_mod |
---|
2 | |
---|
3 | implicit none |
---|
4 | |
---|
5 | contains |
---|
6 | |
---|
7 | subroutine vert_prof_dissip_icosa_lmdz(llm,presnivs,preff,scale_height,zvert) |
---|
8 | ! Routine to compute zvert(), the multiplicative coefficient |
---|
9 | ! for dissipation along model levels in the same way as done |
---|
10 | ! in LMDZ for planets (see LMDZ.COMMON/libf/dyn3d_common/inidissip.F90) |
---|
11 | USE prec, ONLY : rstd |
---|
12 | USE getin_mod, ONLY : getin |
---|
13 | USE abort_mod, ONLY: dynamico_abort |
---|
14 | USE omp_para, ONLY: is_master |
---|
15 | |
---|
16 | integer,intent(in) :: llm ! number of atmospheric layers |
---|
17 | real(rstd),intent(in) :: presnivs(:) ! approx. pressure of model layers (Pa) |
---|
18 | real(rstd),intent(in) :: preff ! reference surface pressure (Pa) |
---|
19 | real(rstd),intent(in) :: scale_height ! atmos. scale height (m) |
---|
20 | real(rstd),intent(out) :: zvert(:) ! multiplicative coeff. for dissipation |
---|
21 | |
---|
22 | real(rstd) :: fac_mid,fac_up |
---|
23 | real(rstd) :: startalt,dissip_deltaz |
---|
24 | real(rstd) :: dissip_hdelta,dissip_pupstart |
---|
25 | real(rstd) :: zz,middle,pup |
---|
26 | character(len=80) :: vert_prof_dissip_setup |
---|
27 | integer ::l |
---|
28 | |
---|
29 | ! get parameters |
---|
30 | vert_prof_dissip_setup="none" |
---|
31 | call getin("vert_prof_dissip_setup",vert_prof_dissip_setup) |
---|
32 | |
---|
33 | select case (trim(vert_prof_dissip_setup)) |
---|
34 | case("none") ! no vertical variation |
---|
35 | zvert(1:llm)=1. |
---|
36 | |
---|
37 | case("altitude") ! the "Mars"/"generic" model setup |
---|
38 | fac_mid=3. ! multiplicative coefficient in the middle atmosphere |
---|
39 | call getin("dissip_fac_mid",fac_mid) |
---|
40 | fac_up=30. ! multiplicative coefficient in the upper atmosphere |
---|
41 | call getin("dissip_fac_up",fac_up) |
---|
42 | startalt=70. ! pseudo-altitude (km) for the middle to upper transition |
---|
43 | call getin("dissip_startalt",startalt) |
---|
44 | dissip_deltaz=30. ! size (km) of the middle-upper transition region |
---|
45 | call getin("dissip_deltaz",dissip_deltaz) |
---|
46 | |
---|
47 | middle=startalt+dissip_deltaz/2 |
---|
48 | do l=1,llm |
---|
49 | zz= 1. - preff/presnivs(l) |
---|
50 | zvert(l)=fac_mid-(fac_mid-1)/(1+zz*zz) |
---|
51 | zvert(l)=zvert(l)*(1.0+((fac_up/fac_mid-1)* & |
---|
52 | (1-(0.5*(1+tanh(-6./ & |
---|
53 | dissip_deltaz*(scale_height/1000.* & |
---|
54 | (-log(presnivs(l)/preff))-middle)))) & |
---|
55 | ))) |
---|
56 | enddo |
---|
57 | |
---|
58 | case("pressure") ! the "Venus" setup |
---|
59 | fac_mid=2. ! multiplicative coefficient in the middle atmosphere |
---|
60 | call getin("dissip_fac_mid",fac_mid) |
---|
61 | fac_up =10. ! multiplicative coefficient in the upper atmosphere |
---|
62 | call getin("dissip_fac_up",fac_up) |
---|
63 | dissip_deltaz=10. ! size (km) of the middle-upper transition zone |
---|
64 | call getin("dissip_deltaz",dissip_deltaz) |
---|
65 | dissip_hdelta=5. ! scale height (km) in the transition region |
---|
66 | call getin("dissip_hdelta",dissip_hdelta) |
---|
67 | dissip_pupstart=1.e3 ! pressure (Pa) at which the transition starts |
---|
68 | call getin("dissip_pupstart",dissip_pupstart) |
---|
69 | |
---|
70 | Pup = dissip_pupstart*exp(-0.5*dissip_deltaz/dissip_hdelta) |
---|
71 | do l=1,llm |
---|
72 | zz= 1. - preff/presnivs(l) |
---|
73 | zvert(l)=fac_mid-(fac_mid-1)/(1+zz*zz) |
---|
74 | zvert(l)=zvert(l)*(1.0+( (fac_up/fac_mid-1) & |
---|
75 | *(1-(0.5*(1+tanh(-6./dissip_deltaz* & |
---|
76 | (-dissip_hdelta*log(presnivs(l)/Pup)) )))) )) |
---|
77 | enddo |
---|
78 | |
---|
79 | case default ! none of the above |
---|
80 | write(*,*) "vert_prof_dissip_icosa_lmdz: Error: ",& |
---|
81 | trim(vert_prof_dissip_setup),& |
---|
82 | " is not a valid option for vert_prof_dissip_setup" |
---|
83 | call dynamico_abort("vert_prof_dissip_icosa_lmdz :"//& |
---|
84 | " bad value for option vert_prof_dissip_setup") |
---|
85 | end select ! vert_prof_dissip_setup |
---|
86 | |
---|
87 | if (is_master) then |
---|
88 | write(*,*) "vert_prof_dissip_icosa_lmdz:" |
---|
89 | write(*,*) " l presnivs(l) zvert(l)" |
---|
90 | do l=1,llm |
---|
91 | write(*,*)l,presnivs(l),zvert(l) |
---|
92 | enddo |
---|
93 | endif |
---|
94 | |
---|
95 | end subroutine vert_prof_dissip_icosa_lmdz |
---|
96 | |
---|
97 | end module vert_prof_dissip_icosa_lmdz_mod |
---|