source: codes/icosagcm/trunk/src/initial/etat0_heldsz.f90 @ 1025

Last change on this file since 1025 was 970, checked in by ymipsl, 5 years ago

Bug fix in openMP for held&suarez physic.

YM

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