source: codes/icosagcm/trunk/src/etat0_dcmip2016_baroclinic_wave.f90 @ 386

Last change on this file since 386 was 386, checked in by ymipsl, 8 years ago

Some fixes in dcmip2016 physics

YM

File size: 3.4 KB
Line 
1MODULE etat0_dcmip2016_baroclinic_wave_mod
2  USE icosa
3  IMPLICIT NONE
4  PRIVATE
5 
6  REAL(rstd),PARAMETER :: eta0=0.252
7  REAL(rstd),PARAMETER :: etat=0.2
8  REAL(rstd),PARAMETER :: ps0=1e5
9  REAL(rstd),PARAMETER :: u0=35
10  REAL(rstd),PARAMETER :: T0=288
11  REAL(rstd),PARAMETER :: DeltaT=4.8e5
12  REAL(rstd),PARAMETER :: Rd=287
13  REAL(rstd),PARAMETER :: Gamma=0.005
14  REAL(rstd),PARAMETER :: up0=1
15  REAL(rstd),PARAMETER :: lonc=Pi/9, latc=2*Pi/9, latw=2*Pi/9
16  REAL(rstd),PARAMETER :: pw=34000
17  REAL(rstd),PARAMETER :: q0=0.021
18 
19  INTEGER,SAVE :: testcase
20  !$OMP THREADPRIVATE(testcase) 
21 
22  PUBLIC getin_etat0, compute_etat0
23
24CONTAINS
25
26  SUBROUTINE getin_etat0
27    USE mpipara, ONLY : is_mpi_root
28    USE tracer_mod
29    IF(nqtot<5) THEN
30       IF (is_mpi_root)  THEN
31          PRINT *, "nqtot must be at least 5 for test case dcmip2016_baroclinic_wave"
32       END IF
33       STOP
34    END IF
35!    CALL set_advection_scheme(3,advect_none)
36   
37  END SUBROUTINE getin_etat0
38
39  SUBROUTINE compute_etat0(ngrid,lon,lat, phis,ps,temp,ulon,ulat,q)
40    USE icosa
41    USE disvert_mod
42    USE omp_para
43    USE terminator
44    USE tracer_mod
45    INTEGER, INTENT(IN) :: ngrid
46    REAL(rstd),INTENT(IN) :: lon(ngrid)
47    REAL(rstd),INTENT(IN) :: lat(ngrid)
48    REAL(rstd),INTENT(OUT) :: phis(ngrid)
49    REAL(rstd),INTENT(OUT) :: ps(ngrid)
50    REAL(rstd),INTENT(OUT) :: temp(ngrid,llm)
51    REAL(rstd),INTENT(OUT) :: ulon(ngrid,llm)
52    REAL(rstd),INTENT(OUT) :: ulat(ngrid,llm)
53    REAL(rstd),INTENT(OUT) :: q(ngrid,llm,nqtot)
54   
55    INTEGER :: l,ij
56    REAL(rstd) :: etal, etavl, etas, etavs, sinlat, coslat, &
57         Y, Tave, T, phis_ave, vort, r2, utot, &
58         dthetaodeta_ave, dthetaodeta, dthetaodlat, duodeta, K, r
59   
60    etas=ap(1)/preff+bp(1)
61    etavs=(etas-eta0)*Pi/2
62    phis_ave=T0*g/Gamma*(1-etas**(Rd*Gamma/g))
63   
64    DO ij=1,ngrid
65       sinlat=SIN(lat(ij))
66       coslat=COS(lat(ij))
67       phis(ij)=phis_ave+u0*cos(etavs)**1.5*( (-2*sinlat**6 * (coslat**2+1./3) + 10./63 )*u0*cos(etavs)**1.5  &
68            +(8./5*coslat**3 * (sinlat**2 + 2./3) - Pi/4)*radius*Omega )
69       ps(ij)=ps0
70    ENDDO
71   
72    DO l=ll_begin,ll_end
73       etal = 0.5 *( ap(l)/preff+bp(l) + ap(l+1)/preff+bp(l+1) )
74       etavl=(etal-eta0)*Pi/2
75       
76       Tave=T0*etal**(Rd*Gamma/g)
77       dthetaodeta_ave = T0 *( Rd*Gamma/g - kappa)* etal**(Rd*Gamma/g-kappa-1)
78       IF (etat>etal) THEN
79          Tave=Tave+DeltaT*(etat-etal)**5
80          dthetaodeta_ave = dthetaodeta_ave - DeltaT * ( 5*(etat-etal)**4 * etal**(-kappa)  &
81               + kappa * (etat-etal)**5 * etal**(-kappa-1))
82       END IF
83       
84       DO ij=1,ngrid
85          sinlat=SIN(lat(ij))
86          coslat=COS(lat(ij))
87         
88          K=sin(latc)*sinlat+cos(latc)*coslat*cos(lon(ij)-lonc)
89          r=radius*acos(K)
90          utot=u0*cos(etavl)**1.5*sin(2*lat(ij))**2 + up0*exp(-(r/(0.1*radius))**2)
91          ulon(ij,l) = utot
92          ulat(ij,l) = 0.
93          Y = ((-2*sinlat**6*(coslat**2+1./3)+10./63)*2*u0*cos(etavl)**1.5     &
94               + (8./5*coslat**3*(sinlat**2+2./3)-Pi/4)*radius*Omega)
95          T = Tave + 0.75*(etal*Pi*u0/Rd)*sin(etavl)*cos(etavl)**0.5 * Y
96          temp(ij,l)=T
97         
98          q(ij,l,1)=q0*exp(-(lat(ij)/latw)**4)*exp(-((etal-1)*preff/pw)**2)
99          q(ij,l,2)=0.
100          q(ij,l,3)=0.
101          CALL initial_value_Terminator(lat(ij),lon(ij),q(ij,l,4),q(ij,l,5))
102       END DO
103    END DO
104   
105  END SUBROUTINE compute_etat0
106 
107END MODULE etat0_dcmip2016_baroclinic_wave_mod
Note: See TracBrowser for help on using the repository browser.