source: codes/icosagcm/devel/src/initial/etat0_dcmip4.f90 @ 979

Last change on this file since 979 was 972, checked in by jisesh, 5 years ago

devel: Added option up0 and CASE 'wind_temperature'

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