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

Last change on this file since 548 was 548, checked in by dubos, 7 years ago

trunk : reorganize source tree

File size: 1.8 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, pp, zz
25    INTEGER :: l,ij
26    pp=peq
27    DO ij=1,ngrid
28       CALL test3_gravity_wave(scale_factor, lon(ij),lat(ij),pp,dummy,0, &
29            dummy,dummy,dummy,dummy,phis(ij),ps(ij),dummy,dummy)
30    END DO
31    DO l=ll_begin,ll_endp1
32       DO ij=1,ngrid
33          pp = ap(l) + bp(l)*ps(ij) ! half-layer pressure
34          CALL test3_gravity_wave(scale_factor, lon(ij),lat(ij),pp,zz,0, &
35               dummy,dummy,dummy,dummy,dummy,dummy,dummy,dummy)
36          geopot(ij,l) = g*zz ! initialize geopotential for NH
37       END DO
38    END DO
39    DO l=ll_begin,ll_end
40       DO ij=1,ngrid
41          pp = .5*(ap(l)+ap(l+1)) + .5*(bp(l)+bp(l+1))*ps(ij) ! full-layer pressure
42          CALL test3_gravity_wave(scale_factor, lon(ij),lat(ij),pp,dummy,0, &
43               ulon(ij,l),ulat(ij,l),dummy,Temp(ij,l),dummy,dummy,dummy,dummy)
44       END DO
45       q(:,l,:)=0.
46    END DO
47   
48  END SUBROUTINE compute_etat0
49
50END MODULE etat0_DCMIP3_mod
Note: See TracBrowser for help on using the repository browser.