MODULE etat0_collocated_mod USE icosa USE omp_para, ONLY : is_omp_level_master USE caldyn_vars_mod, ONLY : hydrostatic IMPLICIT NONE PRIVATE LOGICAL :: autoinit_mass, autoinit_NH CHARACTER(len=255),SAVE :: etat0_type !$OMP THREADPRIVATE(autoinit_mass, autoinit_NH, etat0_type) PUBLIC :: etat0_type, etat0_collocated ! Important notes for OpenMP ! When etat0 is called, vertical OpenMP parallelism is deactivated. ! Therefore only the omp_level_master thread must work, i.e. : ! !$OMP BARRIER ! DO ind=1,ndomain ! IF (.NOT. assigned_domain(ind) .OR. .NOT. is_omp_level_master) CYCLE ! ... ! END DO ! !$OMP BARRIER ! There MUST be NO OMP BARRIER inside the DO-LOOP or any routine it calls. CONTAINS SUBROUTINE etat0_collocated(f_phis,f_ps,f_mass,f_theta_rhodz,f_u, f_geopot,f_W, f_q) USE theta2theta_rhodz_mod TYPE(t_field),POINTER :: f_ps(:) TYPE(t_field),POINTER :: f_mass(:) TYPE(t_field),POINTER :: f_phis(:) TYPE(t_field),POINTER :: f_theta_rhodz(:) TYPE(t_field),POINTER :: f_u(:) TYPE(t_field),POINTER :: f_geopot(:) TYPE(t_field),POINTER :: f_W(:) TYPE(t_field),POINTER :: f_q(:) TYPE(t_field),POINTER,SAVE :: f_temp(:) REAL(rstd),POINTER :: ps(:) REAL(rstd),POINTER :: mass(:,:) REAL(rstd),POINTER :: phis(:) REAL(rstd),POINTER :: theta_rhodz(:,:,:) REAL(rstd),POINTER :: temp(:,:) REAL(rstd),POINTER :: u(:,:) REAL(rstd),POINTER :: geopot(:,:) REAL(rstd),POINTER :: W(:,:) REAL(rstd),POINTER :: q(:,:,:) INTEGER :: ind CALL allocate_field(f_temp,field_t,type_real,llm,name='temp') DO ind=1,ndomain IF (.NOT. assigned_domain(ind) .OR. .NOT. is_omp_level_master) CYCLE CALL swap_dimensions(ind) CALL swap_geometry(ind) ps=f_ps(ind) mass=f_mass(ind) phis=f_phis(ind) theta_rhodz=f_theta_rhodz(ind) temp=f_temp(ind) u=f_u(ind) geopot=f_geopot(ind) w=f_w(ind) q=f_q(ind) IF( TRIM(etat0_type)=='williamson91.6' ) THEN CALL compute_etat0_collocated_hex(ps,mass, phis, theta_rhodz(:,:,1), u, geopot, W, q) ELSE CALL compute_etat0_collocated_hex(ps,mass, phis, temp, u, geopot, W, q) ENDIF IF( TRIM(etat0_type)/='williamson91.6' ) CALL compute_temperature2entropy(ps,temp,q,theta_rhodz, 1) ENDDO CALL deallocate_field(f_temp) END SUBROUTINE etat0_collocated SUBROUTINE compute_temperature2entropy(ps,temp,q,theta_rhodz,offset) USE icosa USE pression_mod USE exner_mod USE omp_para REAL(rstd),INTENT(IN) :: ps(iim*jjm) REAL(rstd),INTENT(IN) :: temp(iim*jjm,llm) REAL(rstd),INTENT(IN) :: q(iim*jjm,llm,nqtot) REAL(rstd),INTENT(OUT) :: theta_rhodz(iim*jjm,llm) INTEGER,INTENT(IN) :: offset REAL(rstd) :: p(iim*jjm,llm+1) REAL(rstd) :: cppd,Rd, mass, p_ij, q_ij,r_ij, chi,nu, entropy, theta INTEGER :: i,j,ij,l cppd=cpp Rd=kappa*cppd CALL compute_pression(ps,p,offset) ! flush p DO l = ll_begin, ll_end DO j=jj_begin-offset,jj_end+offset DO i=ii_begin-offset,ii_end+offset ij=(j-1)*iim+i mass = (p(ij,l)-p(ij,l+1))/g ! dry+moist mass p_ij = .5*(p(ij,l)+p(ij,l+1)) ! pressure at full level SELECT CASE(caldyn_thermo) CASE(thermo_theta) theta = temp(ij,l)*(p_ij/preff)**(-kappa) theta_rhodz(ij,l) = mass * theta CASE(thermo_entropy) nu = log(p_ij/preff) chi = log(temp(ij,l)/Treff) entropy = cppd*chi-Rd*nu theta_rhodz(ij,l) = mass * entropy ! CASE(thermo_moist) ! q_ij=q(ij,l,1) ! r_ij=1.-q_ij ! mass=mass*(1-q_ij) ! dry mass ! nu = log(p_ij/preff) ! chi = log(temp(ij,l)/Treff) ! entropy = r_ij*(cppd*chi-Rd*nu) + q_ij*(cppv*chi-Rv*nu) ! theta_rhodz(ij,l) = mass * entropy CASE DEFAULT STOP END SELECT ENDDO ENDDO ENDDO END SUBROUTINE compute_temperature2entropy SUBROUTINE compute_etat0_collocated_hex(ps,mass,phis,temp_i,u, geopot,W, q) USE wind_mod USE disvert_mod REAL(rstd),INTENT(INOUT) :: ps(iim*jjm) REAL(rstd),INTENT(INOUT) :: mass(iim*jjm,llm) REAL(rstd),INTENT(OUT) :: phis(iim*jjm) REAL(rstd),INTENT(OUT) :: temp_i(iim*jjm,llm) REAL(rstd),INTENT(OUT) :: u(3*iim*jjm,llm) REAL(rstd),INTENT(OUT) :: W(iim*jjm,llm+1) REAL(rstd),INTENT(OUT) :: geopot(iim*jjm,llm+1) REAL(rstd),INTENT(OUT) :: q(iim*jjm,llm,nqtot) REAL(rstd) :: ulon_i(iim*jjm,llm) REAL(rstd) :: ulat_i(iim*jjm,llm) REAL(rstd) :: ps_e(3*iim*jjm) REAL(rstd) :: mass_e(3*iim*jjm,llm) REAL(rstd) :: phis_e(3*iim*jjm) REAL(rstd) :: temp_e(3*iim*jjm,llm) REAL(rstd) :: geopot_e(3*iim*jjm,llm+1) REAL(rstd) :: ulon_e(3*iim*jjm,llm) REAL(rstd) :: ulat_e(3*iim*jjm,llm) REAL(rstd) :: q_e(3*iim*jjm,llm,nqtot) INTEGER :: l,i,j,ij REAL :: p_ik, v_ik, mass_ik ! For NH geopotential and vertical momentum must be initialized. ! Unless autoinit_NH is set to .FALSE. , they will be initialized ! to hydrostatic geopotential and zero autoinit_mass = .TRUE. autoinit_NH = .NOT. hydrostatic w(:,:) = 0 CALL compute_etat0_collocated(iim*jjm , lon_i, lat_i, phis, ps, mass, temp_i, ulon_i, ulat_i, geopot, q) 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) IF(autoinit_mass) CALL compute_rhodz(.TRUE., ps, mass) ! initialize mass distribution using ps IF(autoinit_NH) THEN geopot(:,1) = phis(:) ! surface geopotential DO l = 1, llm DO ij=1,iim*jjm ! hybrid pressure coordinate p_ik = ptop + mass_ak(l) + mass_bk(l)*ps(ij) mass_ik = (mass_dak(l) + mass_dbk(l)*ps(ij))/g ! v=R.T/p, R=kappa*cpp v_ik = kappa*cpp*temp_i(ij,l)/p_ik geopot(ij,l+1) = geopot(ij,l) + mass_ik*v_ik*g END DO END DO END IF CALL compute_wind_perp_from_lonlat_compound(ulon_e, ulat_e, u) END SUBROUTINE compute_etat0_collocated_hex SUBROUTINE compute_etat0_collocated(ngrid, lon, lat, phis, ps, mass, temp, ulon, ulat, geopot, q) USE etat0_isothermal_mod, ONLY : compute_isothermal => compute_etat0 USE etat0_jablonowsky06_mod, ONLY : compute_jablonowsky06 => compute_etat0 USE etat0_dcmip1_mod, ONLY : compute_dcmip1 => compute_etat0 USE etat0_dcmip2_mod, ONLY : compute_dcmip2 => compute_etat0 USE etat0_dcmip3_mod, ONLY : compute_dcmip3 => compute_etat0 USE etat0_dcmip4_mod, ONLY : compute_dcmip4 => compute_etat0 USE etat0_dcmip5_mod, ONLY : compute_dcmip5 => compute_etat0 USE etat0_bubble_mod, ONLY : compute_bubble => compute_etat0 USE etat0_williamson_mod, ONLY : compute_w91_6 => compute_etat0 USE etat0_temperature_mod, ONLY: compute_temperature => compute_etat0 USE etat0_dcmip2016_baroclinic_wave_mod, ONLY : compute_dcmip2016_baroclinic_wave => compute_etat0 USE etat0_dcmip2016_cyclone_mod, ONLY : compute_dcmip2016_cyclone => compute_etat0 USE etat0_dcmip2016_supercell_mod, ONLY : compute_dcmip2016_supercell => compute_etat0 INTEGER :: ngrid REAL(rstd),INTENT(IN) :: lon(ngrid), lat(ngrid) REAL(rstd),INTENT(INOUT) :: ps(ngrid) REAL(rstd),INTENT(INOUT) :: mass(ngrid,llm) REAL(rstd),INTENT(OUT) :: phis(ngrid) REAL(rstd),INTENT(OUT) :: temp(ngrid,llm) REAL(rstd),INTENT(OUT) :: ulon(ngrid,llm) REAL(rstd),INTENT(OUT) :: ulat(ngrid,llm) REAL(rstd),INTENT(OUT) :: geopot(ngrid,llm+1) REAL(rstd),INTENT(OUT) :: q(ngrid,llm,nqtot) SELECT CASE (TRIM(etat0_type)) CASE ('isothermal') CALL compute_isothermal(ngrid, phis, ps, temp, ulon, ulat, q) CASE ('temperature_profile') CALL compute_temperature(ngrid, phis, ps, temp, ulon, ulat, q) CASE('jablonowsky06') CALL compute_jablonowsky06(ngrid, lon, lat, phis, ps, temp, ulon, ulat) CASE('dcmip1') CALL compute_dcmip1(ngrid, lon, lat, phis, ps, temp, ulon, ulat, q) CASE ('dcmip2_mountain','dcmip2_schaer_noshear','dcmip2_schaer_shear') CALL compute_dcmip2(ngrid, lon, lat, phis, ps, temp, ulon, ulat) CASE('dcmip3') CALL compute_dcmip3(ngrid, lon, lat, phis, ps, temp, ulon, ulat, geopot, q) autoinit_NH = .FALSE. ! compute_dcmip3 initializes geopot CASE('dcmip4') CALL compute_dcmip4(ngrid, lon, lat, phis, ps, temp, ulon, ulat, q) CASE('dcmip5') CALL compute_dcmip5(ngrid, lon, lat, phis, ps, temp, ulon, ulat, q) CASE('bubble') CALL compute_bubble(ngrid, lon, lat, phis, ps, temp, ulon, ulat, geopot, q) ! autoinit_NH = .FALSE. ! compute_bubble initializes geopot CASE('williamson91.6') CALL compute_w91_6(ngrid, lon, lat, phis, mass(:,1), temp(:,1), ulon(:,1), ulat(:,1)) autoinit_mass = .FALSE. ! do not overwrite mass CASE('dcmip2016_baroclinic_wave') CALL compute_dcmip2016_baroclinic_wave(ngrid, lon, lat, phis, ps, temp, ulon, ulat, q) CASE('dcmip2016_cyclone') CALL compute_dcmip2016_cyclone(ngrid, lon, lat, phis, ps, temp, ulon, ulat, q) CASE('dcmip2016_supercell') CALL compute_dcmip2016_supercell(ngrid, lon, lat, phis, ps, temp, ulon, ulat, q) END SELECT END SUBROUTINE compute_etat0_collocated END MODULE etat0_collocated_mod