source: codes/icosagcm/trunk/src/initial/etat0_dcmip3.f90

Last change on this file was 899, checked in by adurocher, 5 years ago

trunk : Fixed GCC warnings

Fixed iso c bindings
fixed warnings with -Wall -Wno-aliasing -Wno-unused -Wno-unused-dummy-argument -Wno-maybe-uninitialized -Wno-tabs warnings
Removed all unused variables (-Wunused-variable)
vector%dot_product is now dot_product_3d to avoid compilation warning "dot_product shadows intrinsic" with GCC

File size: 2.0 KB
Line 
1MODULE etat0_dcmip3_mod
2  ! test cases DCMIP 2012, category 3 : Non-hydrostatic gravity waves
3  IMPLICIT NONE
4  PRIVATE
5  PUBLIC :: compute_etat0
6 
7CONTAINS
8 
9  SUBROUTINE compute_etat0(ngrid,lon,lat, phis,ps,temp,ulon,ulat,geopot,q)
10    USE dcmip_initial_conditions_test_1_2_3
11    USE disvert_mod
12    USE omp_para
13    INTEGER, INTENT(IN) :: ngrid
14    REAL(rstd), INTENT(IN) :: lon(ngrid)
15    REAL(rstd), INTENT(IN) :: lat(ngrid)
16    REAL(rstd), INTENT(OUT) :: phis(ngrid)
17    REAL(rstd), INTENT(OUT) :: ps(ngrid)
18    REAL(rstd), INTENT(OUT) :: ulon(ngrid,llm)
19    REAL(rstd), INTENT(OUT) :: ulat(ngrid,llm)
20    REAL(rstd), INTENT(OUT) :: temp(ngrid,llm)
21    REAL(rstd), INTENT(OUT) :: geopot(ngrid,llm+1)
22    REAL(rstd), INTENT(OUT) :: q(ngrid,llm,nqtot)
23    REAL(rstd),PARAMETER :: Peq=1e5        ! Reference surface pressure at the equator (hPa)
24    REAL(rstd) :: dummy_z, dummy_u, dummy_v, dummy_w, dummy_t, dummy_phis, dummy_ps, dummy_rho, dummy_q
25    REAL(rstd) :: pp, zz
26    INTEGER :: l,ij
27    dummy_z=0;dummy_u=0;dummy_v=0;dummy_w=0;dummy_t=0;dummy_phis=0;dummy_ps=0;dummy_rho=0;dummy_q=0;
28    pp=peq
29    DO ij=1,ngrid
30       CALL test3_gravity_wave(scale_factor, lon(ij),lat(ij),pp,dummy_z,0, &
31            dummy_u,dummy_v,dummy_w,dummy_t,phis(ij),ps(ij),dummy_rho,dummy_q)
32    END DO
33    DO l=ll_begin,ll_endp1
34       DO ij=1,ngrid
35          pp = ap(l) + bp(l)*ps(ij) ! half-layer pressure
36          CALL test3_gravity_wave(scale_factor, lon(ij),lat(ij),pp,zz,0, &
37               dummy_u,dummy_v,dummy_w,dummy_t,dummy_phis,dummy_ps,dummy_rho,dummy_q)
38          geopot(ij,l) = g*zz ! initialize geopotential for NH
39       END DO
40    END DO
41    DO l=ll_begin,ll_end
42       DO ij=1,ngrid
43          pp = .5*(ap(l)+ap(l+1)) + .5*(bp(l)+bp(l+1))*ps(ij) ! full-layer pressure
44          CALL test3_gravity_wave(scale_factor, lon(ij),lat(ij),pp,dummy_z,0, &
45               ulon(ij,l),ulat(ij,l),dummy_w,Temp(ij,l),dummy_phis,dummy_ps,dummy_rho,dummy_q)
46       END DO
47       q(:,l,:)=0.
48    END DO
49   
50  END SUBROUTINE compute_etat0
51
52END MODULE etat0_DCMIP3_mod
Note: See TracBrowser for help on using the repository browser.