1 | MODULE etat0_heldsz_mod |
---|
2 | USE icosa |
---|
3 | IMPLICIT NONE |
---|
4 | PRIVATE |
---|
5 | |
---|
6 | TYPE(t_field),POINTER :: f_theta_eq(:) |
---|
7 | TYPE(t_field),POINTER :: f_theta(:) |
---|
8 | |
---|
9 | REAL(rstd),ALLOCATABLE,SAVE :: knewt_t(:),kfrict(:) |
---|
10 | !$OMP THREADPRIVATE(knewt_t,kfrict) |
---|
11 | LOGICAL, SAVE :: done=.FALSE. |
---|
12 | !$OMP THREADPRIVATE(done) |
---|
13 | |
---|
14 | REAL(rstd),SAVE :: teta0,ttp,delt_y,delt_z,eps |
---|
15 | !$OMP THREADPRIVATE(teta0,ttp,delt_y,delt_z,eps) |
---|
16 | |
---|
17 | REAL(rstd),SAVE :: knewt_g, k_f,k_c_a,k_c_s |
---|
18 | !$OMP THREADPRIVATE(knewt_g, k_f,k_c_a,k_c_s) |
---|
19 | |
---|
20 | PUBLIC :: etat0, held_suarez |
---|
21 | |
---|
22 | CONTAINS |
---|
23 | |
---|
24 | SUBROUTINE test_etat0_heldsz |
---|
25 | USE icosa |
---|
26 | USE kinetic_mod |
---|
27 | IMPLICIT NONE |
---|
28 | TYPE(t_field),POINTER :: f_ps(:) |
---|
29 | TYPE(t_field),POINTER :: f_phis(:) |
---|
30 | TYPE(t_field),POINTER :: f_theta_rhodz(:) |
---|
31 | TYPE(t_field),POINTER :: f_u(:) |
---|
32 | TYPE(t_field),POINTER :: f_q(:) |
---|
33 | TYPE(t_field),POINTER :: f_Ki(:) |
---|
34 | |
---|
35 | REAL(rstd),POINTER :: Ki(:,:) |
---|
36 | INTEGER :: ind |
---|
37 | |
---|
38 | CALL allocate_field(f_ps,field_t,type_real) |
---|
39 | CALL allocate_field(f_phis,field_t,type_real) |
---|
40 | CALL allocate_field(f_theta_rhodz,field_t,type_real,llm) |
---|
41 | CALL allocate_field(f_u,field_u,type_real,llm) |
---|
42 | CALL allocate_field(f_Ki,field_t,type_real,llm) |
---|
43 | |
---|
44 | CALL etat0(f_ps,f_phis,f_theta_rhodz,f_u, f_q) |
---|
45 | CALL kinetic(f_u,f_Ki) |
---|
46 | |
---|
47 | CALL writefield('ps',f_ps) |
---|
48 | CALL writefield('theta',f_theta_rhodz) |
---|
49 | END SUBROUTINE test_etat0_heldsz |
---|
50 | |
---|
51 | SUBROUTINE etat0(f_ps,f_phis,f_theta_rhodz,f_u, f_q) |
---|
52 | USE icosa |
---|
53 | USE theta2theta_rhodz_mod |
---|
54 | IMPLICIT NONE |
---|
55 | TYPE(t_field),POINTER :: f_ps(:) |
---|
56 | TYPE(t_field),POINTER :: f_phis(:) |
---|
57 | TYPE(t_field),POINTER :: f_theta_rhodz(:) |
---|
58 | TYPE(t_field),POINTER :: f_u(:) |
---|
59 | TYPE(t_field),POINTER :: f_q(:) |
---|
60 | |
---|
61 | REAL(rstd),POINTER :: ps(:) |
---|
62 | REAL(rstd),POINTER :: phis(:) |
---|
63 | REAL(rstd),POINTER :: theta_rhodz(:,:) |
---|
64 | REAL(rstd),POINTER :: u(:,:) |
---|
65 | REAL(rstd),POINTER :: q(:,:,:) |
---|
66 | REAL(rstd),POINTER :: theta_eq(:,:) |
---|
67 | REAL(rstd),POINTER :: theta(:,:) |
---|
68 | |
---|
69 | INTEGER :: ind |
---|
70 | |
---|
71 | CALL Init_Teq |
---|
72 | DO ind=1,ndomain |
---|
73 | IF (.NOT. assigned_domain(ind)) CYCLE |
---|
74 | CALL swap_dimensions(ind) |
---|
75 | CALL swap_geometry(ind) |
---|
76 | |
---|
77 | theta_eq=f_theta_eq(ind) |
---|
78 | CALL compute_Teq(lat_i,theta_eq) ! FIXME : already done by Init_Teq |
---|
79 | |
---|
80 | ps=f_ps(ind) |
---|
81 | phis=f_phis(ind) |
---|
82 | u=f_u(ind) |
---|
83 | ps(:)=1e5 |
---|
84 | phis(:)=0. |
---|
85 | u(:,:)=0 |
---|
86 | |
---|
87 | theta_rhodz=f_theta_rhodz(ind) |
---|
88 | theta=f_theta(ind) |
---|
89 | CALL compute_etat0_heldsz(theta_eq,theta) |
---|
90 | CALL compute_theta2theta_rhodz(ps,theta,theta_rhodz,1) |
---|
91 | q=f_q(ind) |
---|
92 | q(:,:,1)=1e-2 |
---|
93 | q(:,:,2)=0 |
---|
94 | q(:,:,3:)=1e-2 |
---|
95 | ENDDO |
---|
96 | END SUBROUTINE etat0 |
---|
97 | |
---|
98 | SUBROUTINE init_Teq |
---|
99 | USE icosa |
---|
100 | USE disvert_mod, ONLY : ap,bp |
---|
101 | IMPLICIT NONE |
---|
102 | REAL(rstd),POINTER :: clat(:) |
---|
103 | REAL(rstd),POINTER :: theta_eq(:,:) |
---|
104 | REAL(rstd) :: zsig |
---|
105 | INTEGER :: ind, l |
---|
106 | |
---|
107 | IF(.NOT.done) THEN |
---|
108 | done = .TRUE. |
---|
109 | |
---|
110 | CALL allocate_field(f_theta,field_t,type_real,llm) |
---|
111 | CALL allocate_field(f_theta_eq,field_t,type_real,llm) |
---|
112 | ALLOCATE(knewt_t(llm)); ALLOCATE( kfrict(llm)) |
---|
113 | |
---|
114 | k_f=1. !friction |
---|
115 | CALL getin('k_j',k_f) |
---|
116 | k_f=1./(daysec*k_f) |
---|
117 | k_c_s=4. !cooling surface |
---|
118 | CALL getin('k_c_s',k_c_s) |
---|
119 | k_c_s=1./(daysec*k_c_s) |
---|
120 | k_c_a=40. !cooling free atm |
---|
121 | CALL getin('k_c_a',k_c_a) |
---|
122 | k_c_a=1./(daysec*k_c_a) |
---|
123 | ! Constants for Teta equilibrium profile |
---|
124 | teta0=315. ! mean Teta (S.H. 315K) |
---|
125 | CALL getin('teta0',teta0) |
---|
126 | ttp=200. ! Tropopause temperature (S.H. 200K) |
---|
127 | CALL getin('ttp',ttp) |
---|
128 | eps=0. ! Deviation to N-S symmetry(~0-20K) |
---|
129 | CALL getin('eps',eps) |
---|
130 | delt_y=60. ! Merid Temp. Gradient (S.H. 60K) |
---|
131 | CALL getin('delt_y',delt_y) |
---|
132 | delt_z=10. ! Vertical Gradient (S.H. 10K) |
---|
133 | CALL getin('delt_z',delt_z) |
---|
134 | |
---|
135 | !----------------------------------------------------------- |
---|
136 | knewt_g=k_c_a |
---|
137 | DO l=1,llm |
---|
138 | zsig=ap(l)/preff+bp(l) |
---|
139 | knewt_t(l)=(k_c_s-k_c_a)*MAX(0.,(zsig-0.7)/0.3) |
---|
140 | kfrict(l)=k_f*MAX(0.,(zsig-0.7)/0.3) |
---|
141 | ENDDO |
---|
142 | |
---|
143 | DO ind=1,ndomain |
---|
144 | IF (.NOT. assigned_domain(ind)) CYCLE |
---|
145 | CALL swap_dimensions(ind) |
---|
146 | CALL swap_geometry(ind) |
---|
147 | theta_eq=f_theta_eq(ind) |
---|
148 | CALL compute_Teq(lat_i,theta_eq) |
---|
149 | ENDDO |
---|
150 | |
---|
151 | ELSE |
---|
152 | PRINT *, 'Init_Teq called twice' |
---|
153 | CALL ABORT |
---|
154 | END IF |
---|
155 | |
---|
156 | END SUBROUTINE init_Teq |
---|
157 | |
---|
158 | SUBROUTINE compute_Teq(lat,theta_eq) |
---|
159 | USE icosa |
---|
160 | USE disvert_mod |
---|
161 | IMPLICIT NONE |
---|
162 | REAL(rstd),INTENT(IN) :: lat(iim*jjm) |
---|
163 | REAL(rstd),INTENT(OUT) :: theta_eq(iim*jjm,llm) |
---|
164 | |
---|
165 | REAL(rstd) :: r, zsig, ddsin, tetastrat, tetajl |
---|
166 | INTEGER :: i,j,l,ij |
---|
167 | |
---|
168 | DO l=1,llm |
---|
169 | zsig=ap(l)/preff+bp(l) |
---|
170 | tetastrat=ttp*zsig**(-kappa) |
---|
171 | DO j=jj_begin-1,jj_end+1 |
---|
172 | DO i=ii_begin-1,ii_end+1 |
---|
173 | ij=(j-1)*iim+i |
---|
174 | ddsin=SIN(lat(ij)) |
---|
175 | tetajl=teta0-delt_y*ddsin*ddsin+eps*ddsin & |
---|
176 | -delt_z*(1.-ddsin*ddsin)*log(zsig) |
---|
177 | theta_eq(ij,l)=MAX(tetajl,tetastrat) |
---|
178 | ENDDO |
---|
179 | ENDDO |
---|
180 | ENDDO |
---|
181 | END SUBROUTINE compute_Teq |
---|
182 | |
---|
183 | SUBROUTINE compute_etat0_heldsz(theta_eq, theta) |
---|
184 | USE icosa |
---|
185 | USE disvert_mod |
---|
186 | USE pression_mod |
---|
187 | USE exner_mod |
---|
188 | USE geopotential_mod |
---|
189 | USE theta2theta_rhodz_mod |
---|
190 | IMPLICIT NONE |
---|
191 | REAL(rstd),INTENT(IN) :: theta_eq(iim*jjm,llm) |
---|
192 | REAL(rstd),INTENT(OUT) :: theta(iim*jjm,llm) |
---|
193 | |
---|
194 | REAL(rstd) :: r ! random number |
---|
195 | INTEGER :: i,j,l,ij |
---|
196 | |
---|
197 | DO l=1,llm |
---|
198 | DO j=jj_begin-1,jj_end+1 |
---|
199 | DO i=ii_begin-1,ii_end+1 |
---|
200 | ij=(j-1)*iim+i |
---|
201 | CALL RANDOM_NUMBER(r); r = 0.0 |
---|
202 | theta(ij,l)=theta_eq(ij,l)*(1.+0.0005*r) |
---|
203 | ENDDO |
---|
204 | ENDDO |
---|
205 | ENDDO |
---|
206 | |
---|
207 | END SUBROUTINE compute_etat0_heldsz |
---|
208 | |
---|
209 | |
---|
210 | SUBROUTINE held_suarez(f_ps,f_theta_rhodz,f_u) |
---|
211 | USE icosa |
---|
212 | IMPLICIT NONE |
---|
213 | TYPE(t_field),POINTER :: f_theta_rhodz(:) |
---|
214 | TYPE(t_field),POINTER :: f_u(:) |
---|
215 | TYPE(t_field),POINTER :: f_ps(:) |
---|
216 | REAL(rstd),POINTER :: theta_rhodz(:,:) |
---|
217 | REAL(rstd),POINTER :: u(:,:) |
---|
218 | REAL(rstd),POINTER :: ps(:) |
---|
219 | REAL(rstd),POINTER :: theta_eq(:,:) |
---|
220 | REAL(rstd),POINTER :: theta(:,:) |
---|
221 | REAL(rstd),POINTER :: clat(:) |
---|
222 | INTEGER::ind |
---|
223 | |
---|
224 | DO ind=1,ndomain |
---|
225 | IF (.NOT. assigned_domain(ind)) CYCLE |
---|
226 | CALL swap_dimensions(ind) |
---|
227 | CALL swap_geometry(ind) |
---|
228 | theta_rhodz=f_theta_rhodz(ind) |
---|
229 | u=f_u(ind) |
---|
230 | ps=f_ps(ind) |
---|
231 | theta_eq=f_theta_eq(ind) |
---|
232 | theta=f_theta(ind) |
---|
233 | CALL compute_heldsz(ps,theta_eq,lat_i, theta_rhodz,u, theta) |
---|
234 | ENDDO |
---|
235 | END SUBROUTINE held_suarez |
---|
236 | |
---|
237 | SUBROUTINE compute_heldsz(ps,theta_eq,lat, theta_rhodz,u, theta) |
---|
238 | USE icosa |
---|
239 | USE theta2theta_rhodz_mod |
---|
240 | IMPLICIT NONE |
---|
241 | REAL(rstd),INTENT(IN) :: ps(iim*jjm) |
---|
242 | REAL(rstd),INTENT(IN) :: theta_eq(iim*jjm,llm) |
---|
243 | REAL(rstd),INTENT(IN) :: lat(iim*jjm) |
---|
244 | REAL(rstd),INTENT(INOUT) :: theta_rhodz(iim*jjm,llm) |
---|
245 | REAL(rstd),INTENT(INOUT) :: u(3*iim*jjm,llm) |
---|
246 | REAL(rstd),INTENT(OUT) :: theta(iim*jjm,llm) |
---|
247 | |
---|
248 | INTEGER :: i,j,l,ij |
---|
249 | |
---|
250 | CALL compute_theta_rhodz2theta(ps,theta_rhodz,theta,1) |
---|
251 | DO l=1,llm |
---|
252 | DO j=jj_begin-1,jj_end+1 |
---|
253 | DO i=ii_begin-1,ii_end+1 |
---|
254 | ij=(j-1)*iim+i |
---|
255 | theta(ij,l)=theta(ij,l) - dt*(theta(ij,l)-theta_eq(ij,l))* & |
---|
256 | (knewt_g+knewt_t(l)*COS(lat(ij))**4 ) |
---|
257 | ENDDO |
---|
258 | ENDDO |
---|
259 | ENDDO |
---|
260 | CALL compute_theta2theta_rhodz(ps,theta,theta_rhodz,1) |
---|
261 | |
---|
262 | Do l=1,llm |
---|
263 | u(:,l)=u(:,l)*(1.-dt*kfrict(l)) |
---|
264 | END DO |
---|
265 | |
---|
266 | END SUBROUTINE compute_heldsz |
---|
267 | |
---|
268 | END MODULE etat0_heldsz_mod |
---|