1 | module disvert_icosa_lmdz_mod |
---|
2 | |
---|
3 | implicit none |
---|
4 | |
---|
5 | contains |
---|
6 | |
---|
7 | SUBROUTINE disvert_icosa_lmdz(ap,bp,presnivs,presinter) |
---|
8 | ! Routine to compute ap(),bp() and presnivs() in the same way as done |
---|
9 | ! in LMDZ for planets (see LMDZ.COMMON/libf/dyn3d_common/disvert_noterre.F) |
---|
10 | |
---|
11 | USE prec, ONLY : rstd |
---|
12 | USE getin_mod, ONLY : getin |
---|
13 | USE grid_param, ONLY: llm |
---|
14 | USE earth_const, ONLY: pa,preff,scale_height |
---|
15 | USE abort_mod, ONLY: dynamico_abort |
---|
16 | USE mpipara, ONLY: is_mpi_root |
---|
17 | USE omp_para, ONLY: omp_in_parallel |
---|
18 | USE transfert_omp_mod, ONLY: bcast_omp |
---|
19 | USE free_unit_mod, ONLY : free_unit |
---|
20 | IMPLICIT NONE |
---|
21 | |
---|
22 | REAL(rstd),INTENT(OUT) :: ap(:) |
---|
23 | REAL(rstd),INTENT(OUT) :: bp(:) |
---|
24 | REAL(rstd),INTENT(OUT) :: presnivs(:) |
---|
25 | REAL(rstd),INTENT(OUT) :: presinter(:) |
---|
26 | |
---|
27 | INTEGER :: unit |
---|
28 | CHARACTER(len=255) :: filename |
---|
29 | INTEGER :: l,ok |
---|
30 | LOGICAL :: hybrid |
---|
31 | REAL(rstd) :: scaleheight ! atmospheric scale height (km) from file z2sig.def |
---|
32 | REAL(rstd) :: zsig(llm) |
---|
33 | REAL(rstd) :: sig(llm+1) |
---|
34 | REAL(rstd) :: newsig |
---|
35 | |
---|
36 | filename="z2sig.def" !file to read |
---|
37 | |
---|
38 | ! User may choose between hybrid (default) or sigma coordinates |
---|
39 | hybrid=.true. ! default: use hybrid coordinates |
---|
40 | CALL getin('hybrid',hybrid) |
---|
41 | ! User must also provide "pa" if in hybrid case |
---|
42 | if (hybrid) then |
---|
43 | pa=-999 ! absurd initial value to trigger error if not set |
---|
44 | CALL getin('pa',pa) |
---|
45 | IF (pa<0) THEN |
---|
46 | WRITE(*,*) "disvert_icosa_lmdz error: pa=",pa |
---|
47 | WRITE(*,*) " set a correct value for the pa parameter" |
---|
48 | CALL dynamico_abort("disvert_icosa_lmdz : wrong value for pa") |
---|
49 | ENDIF |
---|
50 | endif |
---|
51 | |
---|
52 | !$OMP MASTER |
---|
53 | unit=free_unit() |
---|
54 | OPEN(unit,file=filename,status="old",action="read",iostat=ok) |
---|
55 | IF (ok/=0) THEN |
---|
56 | WRITE(*,*) "disvert_icosa_lmdz error: input file ",trim(filename)," not found!" |
---|
57 | CALL dynamico_abort("disvert_icosa_lmdz : could not open z2sig.def file" ) |
---|
58 | ENDIF |
---|
59 | ! read "scaleheight" on the first line |
---|
60 | READ(unit,fmt=*,iostat=ok) scaleheight |
---|
61 | IF (ok/=0) THEN |
---|
62 | WRITE(*,*) "disvert_icosa_lmdz error: failed reading scaleheight" |
---|
63 | CALL dynamico_abort("disvert_icosa_lmdz : could not read input file") |
---|
64 | ENDIF |
---|
65 | ! While at it check that this "scaleheight" matches the "scale_height" |
---|
66 | ! from the def files |
---|
67 | IF ((1.-(scaleheight*1000.)/scale_height)>1.e-6) THEN |
---|
68 | WRITE(*,*) "disvert_icosa_lmdz error: significant mismatch between" |
---|
69 | WRITE(*,*) " scale_height (m) from def file:",scale_height |
---|
70 | WRITE(*,*) " and scaleheight (km) from z2sig.def:",scaleheight |
---|
71 | CALL dynamico_abort("disvert_icosa_lmdz : atmospheric scale height issue") |
---|
72 | ENDIF |
---|
73 | ! read zsig() line by line, starting from the surface up to model top |
---|
74 | DO l=1,llm |
---|
75 | READ(unit,fmt=*,iostat=ok) zsig(l) |
---|
76 | IF (ok/=0) THEN |
---|
77 | WRITE(*,*) "disvert_icosa_lmdz error: failed reading zsig(l) for l=",l |
---|
78 | CALL dynamico_abort("disvert_icosa_lmdz : could not read input file" ) |
---|
79 | ENDIF |
---|
80 | ENDDO |
---|
81 | CLOSE(unit) |
---|
82 | |
---|
83 | ! build sig() |
---|
84 | sig(1)=1. |
---|
85 | DO l=2,llm |
---|
86 | sig(l)=0.5*(exp(-zsig(l)/scaleheight)+exp(-zsig(l-1)/scaleheight)) |
---|
87 | ENDDO |
---|
88 | sig(llm+1)=0 ! here we asume 0 pressure at top of atmosphere |
---|
89 | |
---|
90 | ! build ap() and bp() using sig(), pa and preff |
---|
91 | IF (hybrid) THEN ! use hybrid coordinates |
---|
92 | DO l=1,llm |
---|
93 | CALL sig_hybrid(sig(l),pa,preff,newsig) |
---|
94 | bp(l)=exp(1.-1./(newsig**2)) |
---|
95 | ap(l)=pa*(newsig-bp(l)) |
---|
96 | ENDDO |
---|
97 | ELSE ! use sigma coordinates |
---|
98 | ap(1:llm)=0 |
---|
99 | bp(1:llm)=sig(1:llm) |
---|
100 | ENDIF |
---|
101 | ap(llm+1)=0 |
---|
102 | bp(llm+1)=0 |
---|
103 | !$OMP END MASTER |
---|
104 | |
---|
105 | IF (omp_in_parallel()) THEN |
---|
106 | CALL bcast_omp(ap) |
---|
107 | CALL bcast_omp(bp) |
---|
108 | ENDIF |
---|
109 | |
---|
110 | ! build presnivs(), approximative mid-layer pressures |
---|
111 | DO l=1,llm |
---|
112 | presnivs(l)=0.5*(ap(l)+bp(l)*preff+ap(l+1)+bp(l+1)*preff) |
---|
113 | ENDDO |
---|
114 | ! build presinter(), approximative inter-layer pressures |
---|
115 | DO l=1,llm+1 |
---|
116 | presinter(l)=ap(l)+bp(l)*preff |
---|
117 | ENDDO |
---|
118 | |
---|
119 | ! tell the world about it |
---|
120 | IF (is_mpi_root) THEN |
---|
121 | !$OMP MASTER |
---|
122 | WRITE(*,*) "Vertical discretization set by disvert_icosa_lmdz with hybrid=",hybrid |
---|
123 | WRITE(*,*) "ap()=",ap |
---|
124 | WRITE(*,*) "bp()=",bp |
---|
125 | WRITE(*,*) "Approximative mid-layer pressure, assuming a surface pressure preff=",preff," Pa" |
---|
126 | WRITE(*,*) "and approximative mid-layer height, assuming an atmospheric scale height of ",scale_height/1000," (km)" |
---|
127 | DO l=1,llm |
---|
128 | WRITE(*,*) 'PRESNIVS(',l,')=',presnivs(l),' Z ~ ',log(preff/presnivs(l))*scale_height/1000, & |
---|
129 | ' DZ ~ ',scale_height/1000*log((ap(l)+bp(l)*preff)/ max(ap(l+1)+bp(l+1)*preff,1.e-10)) |
---|
130 | ENDDO |
---|
131 | !$OMP END MASTER |
---|
132 | ENDIF |
---|
133 | |
---|
134 | CONTAINS |
---|
135 | |
---|
136 | SUBROUTINE sig_hybrid(sig,pa,preff,newsig) |
---|
137 | ! F. Forget 2002 |
---|
138 | ! Iterative procedure to find "newsig" the sigma value for a layer |
---|
139 | ! based on the target values provided in z2sig.def (sig) |
---|
140 | ! but such that: |
---|
141 | ! (1 -pa/preff)*exp(1-1./newsig**2)+(pa/preff)*newsig = sig |
---|
142 | ! iterative solving of the equation uses the fact that: |
---|
143 | ! where exp(1-1./x**2) become << x |
---|
144 | ! x exp(1-1./x**2)/x |
---|
145 | ! 1 1 |
---|
146 | ! 0.68 0.5 |
---|
147 | ! 0.5 1.E-1 |
---|
148 | ! 0.391 1.E-2 |
---|
149 | ! 0.333 1.E-3 |
---|
150 | ! 0.295 1.E-4 |
---|
151 | ! 0.269 1.E-5 |
---|
152 | ! 0.248 1.E-6 |
---|
153 | ! => thus on can assume newsig = sig*preff/pa if sig*preff/pa < 0.25 |
---|
154 | |
---|
155 | IMPLICIT NONE |
---|
156 | REAL(rstd),INTENT(in) :: sig |
---|
157 | REAL(rstd),INTENT(in) :: pa |
---|
158 | REAL(rstd),INTENT(in) :: preff |
---|
159 | REAL(rstd),INTENT(out) :: newsig |
---|
160 | REAL(rstd) :: F,x1,x2 |
---|
161 | INTEGER :: j |
---|
162 | |
---|
163 | newsig=sig |
---|
164 | x1=0 |
---|
165 | x2=1 |
---|
166 | IF (sig.ge.1) THEN ! handle sigma=1 case |
---|
167 | newsig=sig |
---|
168 | ELSE IF (sig*preff/pa.ge.0.25) THEN |
---|
169 | DO J=1,9999 ! Overkill max number of iterations |
---|
170 | F=((1 -pa/preff)*exp(1-1./newsig**2)+(pa/preff)*newsig)/sig |
---|
171 | IF (F.gt.1) THEN |
---|
172 | x2=newsig |
---|
173 | newsig=(x1+newsig)*0.5 |
---|
174 | ELSE |
---|
175 | x1=newsig |
---|
176 | newsig=(x2+newsig)*0.5 |
---|
177 | ENDIF |
---|
178 | ! Convergence test: stop if sig is approximated to within 0.01m |
---|
179 | IF (abs(10.*log(F)).LT.1.E-5) EXIT |
---|
180 | ENDDO |
---|
181 | ELSE ! IF (sig*preff/pa.le.0.25) THEN |
---|
182 | newsig=sig*preff/pa |
---|
183 | ENDIF |
---|
184 | END SUBROUTINE sig_hybrid |
---|
185 | |
---|
186 | END SUBROUTINE disvert_icosa_lmdz |
---|
187 | |
---|
188 | |
---|
189 | end module disvert_icosa_lmdz_mod |
---|