source: codes/icosagcm/devel/src/initial/etat0_collocated.f90 @ 849

Last change on this file since 849 was 848, checked in by dubos, 5 years ago

devel : reorganized etat0_collocated.f90

File size: 9.4 KB
Line 
1MODULE etat0_collocated_mod
2  USE icosa
3  USE omp_para, ONLY : is_omp_level_master
4  USE caldyn_vars_mod, ONLY : hydrostatic
5  IMPLICIT NONE         
6  PRIVATE
7
8  LOGICAL :: autoinit_mass, autoinit_NH
9  CHARACTER(len=255),SAVE :: etat0_type
10!$OMP THREADPRIVATE(autoinit_mass, autoinit_NH, etat0_type)
11
12    PUBLIC :: etat0_type, etat0_collocated
13
14! Important notes for OpenMP
15! When etat0 is called, vertical OpenMP parallelism is deactivated.
16! Therefore only the omp_level_master thread must work, i.e. :
17!   !$OMP BARRIER
18!    DO ind=1,ndomain
19!      IF (.NOT. assigned_domain(ind) .OR. .NOT. is_omp_level_master) CYCLE
20!      ...
21!    END DO
22!   !$OMP BARRIER
23! There MUST be NO OMP BARRIER inside the DO-LOOP or any routine it calls.
24
25CONTAINS
26 
27  SUBROUTINE etat0_collocated(f_phis,f_ps,f_mass,f_theta_rhodz,f_u, f_geopot,f_W, f_q)
28    USE theta2theta_rhodz_mod
29    TYPE(t_field),POINTER :: f_ps(:)
30    TYPE(t_field),POINTER :: f_mass(:)
31    TYPE(t_field),POINTER :: f_phis(:)
32    TYPE(t_field),POINTER :: f_theta_rhodz(:)
33    TYPE(t_field),POINTER :: f_u(:)
34    TYPE(t_field),POINTER :: f_geopot(:)
35    TYPE(t_field),POINTER :: f_W(:)
36    TYPE(t_field),POINTER :: f_q(:)
37 
38    TYPE(t_field),POINTER,SAVE :: f_temp(:)
39    REAL(rstd),POINTER :: ps(:)
40    REAL(rstd),POINTER :: mass(:,:)
41    REAL(rstd),POINTER :: phis(:)
42    REAL(rstd),POINTER :: theta_rhodz(:,:,:)
43    REAL(rstd),POINTER :: temp(:,:)
44    REAL(rstd),POINTER :: u(:,:)
45    REAL(rstd),POINTER :: geopot(:,:)
46    REAL(rstd),POINTER :: W(:,:)
47    REAL(rstd),POINTER :: q(:,:,:)
48    INTEGER :: ind
49
50    CALL allocate_field(f_temp,field_t,type_real,llm,name='temp')
51
52    DO ind=1,ndomain
53      IF (.NOT. assigned_domain(ind) .OR. .NOT. is_omp_level_master) CYCLE
54      CALL swap_dimensions(ind)
55      CALL swap_geometry(ind)
56      ps=f_ps(ind)
57      mass=f_mass(ind)
58      phis=f_phis(ind)
59      theta_rhodz=f_theta_rhodz(ind)
60      temp=f_temp(ind)
61      u=f_u(ind)
62      geopot=f_geopot(ind)
63      w=f_w(ind)
64      q=f_q(ind)
65
66      IF( TRIM(etat0_type)=='williamson91.6' ) THEN
67         CALL compute_etat0_collocated_hex(ps,mass, phis, theta_rhodz(:,:,1), u, geopot, W, q)
68      ELSE
69         CALL compute_etat0_collocated_hex(ps,mass, phis, temp, u, geopot, W, q)
70      ENDIF
71
72      IF( TRIM(etat0_type)/='williamson91.6' ) CALL compute_temperature2entropy(ps,temp,q,theta_rhodz, 1)
73   
74    ENDDO
75   
76    CALL deallocate_field(f_temp)
77   
78  END SUBROUTINE etat0_collocated
79
80  SUBROUTINE compute_temperature2entropy(ps,temp,q,theta_rhodz,offset)
81    USE icosa
82    USE pression_mod
83    USE exner_mod
84    USE omp_para
85    REAL(rstd),INTENT(IN)  :: ps(iim*jjm)
86    REAL(rstd),INTENT(IN)  :: temp(iim*jjm,llm)
87    REAL(rstd),INTENT(IN)  :: q(iim*jjm,llm,nqtot)
88    REAL(rstd),INTENT(OUT) :: theta_rhodz(iim*jjm,llm)
89    INTEGER,INTENT(IN) :: offset
90
91    REAL(rstd) :: p(iim*jjm,llm+1)
92    REAL(rstd) :: cppd,Rd, mass, p_ij, q_ij,r_ij, chi,nu, entropy, theta
93    INTEGER :: i,j,ij,l
94
95    cppd=cpp
96    Rd=kappa*cppd
97
98    CALL compute_pression(ps,p,offset)
99    ! flush p
100    DO    l    = ll_begin, ll_end
101       DO j=jj_begin-offset,jj_end+offset
102          DO i=ii_begin-offset,ii_end+offset
103             ij=(j-1)*iim+i
104             mass = (p(ij,l)-p(ij,l+1))/g ! dry+moist mass
105             p_ij = .5*(p(ij,l)+p(ij,l+1))  ! pressure at full level
106             SELECT CASE(caldyn_thermo)
107             CASE(thermo_theta)
108                theta = temp(ij,l)*(p_ij/preff)**(-kappa) 
109                theta_rhodz(ij,l) = mass * theta
110             CASE(thermo_entropy)
111                nu = log(p_ij/preff)
112                chi = log(temp(ij,l)/Treff)
113                entropy = cppd*chi-Rd*nu
114                theta_rhodz(ij,l) = mass * entropy
115!             CASE(thermo_moist)
116!                q_ij=q(ij,l,1)
117!                r_ij=1.-q_ij
118!                mass=mass*(1-q_ij) ! dry mass
119!                nu = log(p_ij/preff)
120!                chi = log(temp(ij,l)/Treff)
121!                entropy = r_ij*(cppd*chi-Rd*nu) + q_ij*(cppv*chi-Rv*nu)
122!                theta_rhodz(ij,l) = mass * entropy               
123                CASE DEFAULT
124                   STOP
125             END SELECT
126          ENDDO
127       ENDDO
128    ENDDO
129  END SUBROUTINE compute_temperature2entropy
130
131  SUBROUTINE compute_etat0_collocated_hex(ps,mass,phis,temp_i,u, geopot,W, q)
132    USE wind_mod
133    USE disvert_mod
134    REAL(rstd),INTENT(INOUT) :: ps(iim*jjm)
135    REAL(rstd),INTENT(INOUT) :: mass(iim*jjm,llm)
136    REAL(rstd),INTENT(OUT) :: phis(iim*jjm)
137    REAL(rstd),INTENT(OUT) :: temp_i(iim*jjm,llm)
138    REAL(rstd),INTENT(OUT) :: u(3*iim*jjm,llm)
139    REAL(rstd),INTENT(OUT) :: W(iim*jjm,llm+1)
140    REAL(rstd),INTENT(OUT) :: geopot(iim*jjm,llm+1)
141    REAL(rstd),INTENT(OUT) :: q(iim*jjm,llm,nqtot)
142
143    REAL(rstd) :: ulon_i(iim*jjm,llm)
144    REAL(rstd) :: ulat_i(iim*jjm,llm)
145
146    REAL(rstd) :: ps_e(3*iim*jjm)
147    REAL(rstd) :: mass_e(3*iim*jjm,llm)
148    REAL(rstd) :: phis_e(3*iim*jjm)
149    REAL(rstd) :: temp_e(3*iim*jjm,llm)
150    REAL(rstd) :: geopot_e(3*iim*jjm,llm+1)
151    REAL(rstd) :: ulon_e(3*iim*jjm,llm)
152    REAL(rstd) :: ulat_e(3*iim*jjm,llm)
153    REAL(rstd) :: q_e(3*iim*jjm,llm,nqtot)
154
155    INTEGER :: l,i,j,ij
156    REAL :: p_ik, v_ik, mass_ik
157
158    ! For NH geopotential and vertical momentum must be initialized.
159    ! Unless autoinit_NH is set to .FALSE. , they will be initialized
160    ! to hydrostatic geopotential and zero
161    autoinit_mass = .TRUE.
162    autoinit_NH = .NOT. hydrostatic
163    w(:,:) = 0
164
165    CALL compute_etat0_collocated(iim*jjm  , lon_i, lat_i, phis,   ps,   mass,   temp_i, ulon_i, ulat_i, geopot,   q)
166    CALL compute_etat0_collocated(3*iim*jjm, lon_e, lat_e, phis_e, ps_e, mass_e, temp_e, ulon_e, ulat_e, geopot_e, q_e)
167
168    IF(autoinit_mass) CALL compute_rhodz(.TRUE., ps, mass) ! initialize mass distribution using ps
169    IF(autoinit_NH) THEN
170       geopot(:,1) = phis(:) ! surface geopotential
171       DO l = 1, llm
172          DO ij=1,iim*jjm
173             ! hybrid pressure coordinate
174             p_ik = ptop + mass_ak(l) + mass_bk(l)*ps(ij)
175             mass_ik = (mass_dak(l) + mass_dbk(l)*ps(ij))/g
176             ! v=R.T/p, R=kappa*cpp
177             v_ik = kappa*cpp*temp_i(ij,l)/p_ik
178             geopot(ij,l+1) = geopot(ij,l) + mass_ik*v_ik*g
179          END DO
180       END DO
181    END IF
182
183    CALL compute_wind_perp_from_lonlat_compound(ulon_e, ulat_e, u)
184
185  END SUBROUTINE compute_etat0_collocated_hex
186
187  SUBROUTINE compute_etat0_collocated(ngrid, lon, lat, phis, ps, mass, temp, ulon, ulat, geopot, q)
188    USE etat0_isothermal_mod, ONLY : compute_isothermal => compute_etat0
189    USE etat0_jablonowsky06_mod, ONLY : compute_jablonowsky06 => compute_etat0
190    USE etat0_dcmip1_mod, ONLY : compute_dcmip1 => compute_etat0
191    USE etat0_dcmip2_mod, ONLY : compute_dcmip2 => compute_etat0
192    USE etat0_dcmip3_mod, ONLY : compute_dcmip3 => compute_etat0
193    USE etat0_dcmip4_mod, ONLY : compute_dcmip4 => compute_etat0
194    USE etat0_dcmip5_mod, ONLY : compute_dcmip5 => compute_etat0
195    USE etat0_bubble_mod, ONLY : compute_bubble => compute_etat0 
196    USE etat0_williamson_mod, ONLY : compute_w91_6 => compute_etat0
197    USE etat0_temperature_mod, ONLY: compute_temperature => compute_etat0
198    USE etat0_dcmip2016_baroclinic_wave_mod, ONLY : compute_dcmip2016_baroclinic_wave => compute_etat0
199    USE etat0_dcmip2016_cyclone_mod, ONLY : compute_dcmip2016_cyclone => compute_etat0
200    USE etat0_dcmip2016_supercell_mod, ONLY : compute_dcmip2016_supercell => compute_etat0
201    INTEGER :: ngrid
202    REAL(rstd),INTENT(IN)    :: lon(ngrid), lat(ngrid)
203    REAL(rstd),INTENT(INOUT) :: ps(ngrid)
204    REAL(rstd),INTENT(INOUT) :: mass(ngrid,llm)
205    REAL(rstd),INTENT(OUT)   :: phis(ngrid)
206    REAL(rstd),INTENT(OUT)   :: temp(ngrid,llm)
207    REAL(rstd),INTENT(OUT)   :: ulon(ngrid,llm)
208    REAL(rstd),INTENT(OUT)   :: ulat(ngrid,llm)
209    REAL(rstd),INTENT(OUT)   :: geopot(ngrid,llm+1)
210    REAL(rstd),INTENT(OUT)   :: q(ngrid,llm,nqtot)
211
212    SELECT CASE (TRIM(etat0_type))
213    CASE ('isothermal')
214       CALL compute_isothermal(ngrid, phis, ps, temp, ulon, ulat, q)
215    CASE ('temperature_profile')
216       CALL compute_temperature(ngrid, phis, ps, temp, ulon, ulat, q)
217    CASE('jablonowsky06')
218       CALL compute_jablonowsky06(ngrid, lon, lat, phis, ps, temp, ulon, ulat)
219    CASE('dcmip1')
220       CALL compute_dcmip1(ngrid, lon, lat, phis, ps, temp, ulon, ulat, q)
221    CASE ('dcmip2_mountain','dcmip2_schaer_noshear','dcmip2_schaer_shear')
222       CALL compute_dcmip2(ngrid, lon, lat, phis, ps, temp, ulon, ulat)
223    CASE('dcmip3')
224       CALL compute_dcmip3(ngrid, lon, lat, phis, ps, temp, ulon, ulat, geopot, q)
225       autoinit_NH = .FALSE. ! compute_dcmip3 initializes geopot
226    CASE('dcmip4')
227       CALL compute_dcmip4(ngrid, lon, lat, phis, ps, temp, ulon, ulat, q)
228    CASE('dcmip5')
229       CALL compute_dcmip5(ngrid, lon, lat, phis, ps, temp, ulon, ulat, q)
230    CASE('bubble')
231       CALL compute_bubble(ngrid, lon, lat, phis, ps, temp, ulon, ulat, geopot, q)
232!       autoinit_NH = .FALSE. ! compute_bubble initializes geopot
233    CASE('williamson91.6')
234       CALL compute_w91_6(ngrid, lon, lat, phis, mass(:,1), temp(:,1), ulon(:,1), ulat(:,1))
235       autoinit_mass = .FALSE. ! do not overwrite mass
236    CASE('dcmip2016_baroclinic_wave')
237       CALL compute_dcmip2016_baroclinic_wave(ngrid, lon, lat, phis, ps, temp, ulon, ulat, q)
238    CASE('dcmip2016_cyclone')
239       CALL compute_dcmip2016_cyclone(ngrid, lon, lat, phis, ps, temp, ulon, ulat, q)
240    CASE('dcmip2016_supercell')
241       CALL compute_dcmip2016_supercell(ngrid, lon, lat, phis, ps, temp, ulon, ulat, q)
242    END SELECT
243
244  END SUBROUTINE compute_etat0_collocated
245
246END MODULE etat0_collocated_mod
Note: See TracBrowser for help on using the repository browser.