source: codes/icosagcm/trunk/src/etat0_dcmip3.f90 @ 78

Last change on this file since 78 was 55, checked in by dubos, 12 years ago

Some DCMIP test case cleanup for consistency

File size: 6.0 KB
Line 
1MODULE etat0_dcmip3_mod
2
3! test cases DCMIP 2012, category 3 : Non-hydrostatic gravity waves
4
5! Questions
6! Replace ps0 by preff ??
7
8  USE genmod
9  USE dcmip_initial_conditions_test_1_2_3
10
11  PRIVATE
12
13  PUBLIC  etat0
14
15CONTAINS
16
17
18  SUBROUTINE etat0(f_ps,f_phis,f_theta_rhodz,f_u, f_q)
19  USE icosa
20  IMPLICIT NONE
21    TYPE(t_field),POINTER :: f_ps(:)
22    TYPE(t_field),POINTER :: f_phis(:)
23    TYPE(t_field),POINTER :: f_theta_rhodz(:)
24    TYPE(t_field),POINTER :: f_u(:)
25    TYPE(t_field),POINTER :: f_q(:)
26   
27    REAL(rstd),POINTER :: ps(:)
28    REAL(rstd),POINTER :: phis(:)
29    REAL(rstd),POINTER :: u(:,:)
30    REAL(rstd),POINTER :: theta_rhodz(:,:)
31    REAL(rstd),POINTER :: q(:,:,:)
32
33    INTEGER :: ind
34
35    DO ind=1,ndomain
36      CALL swap_dimensions(ind)
37      CALL swap_geometry(ind)
38
39      ps=f_ps(ind)
40      phis=f_phis(ind)
41      u=f_u(ind)
42      theta_rhodz=f_theta_rhodz(ind)
43      q=f_q(ind)
44      CALL compute_etat0_DCMIP3(ps,phis,u,theta_rhodz,q)
45    ENDDO
46           
47  END SUBROUTINE etat0
48 
49
50  SUBROUTINE compute_etat0_DCMIP3(ps, phis, u, theta_rhodz,q)
51  USE icosa
52  USE pression_mod
53  USE theta2theta_rhodz_mod
54  USE wind_mod
55  IMPLICIT NONE
56  REAL(rstd),PARAMETER :: u0=20.         ! Maximum amplitude of the zonal wind (m.s-1)
57  REAL(rstd),PARAMETER :: N=0.01         ! Brunt-Vaisala frequency (s-1)
58  REAL(rstd),PARAMETER :: Teq=300.       ! Surface temperature at the equator (K)
59  REAL(rstd),PARAMETER :: Peq=1e5        ! Reference surface pressure at the equator (hPa)
60  REAL(rstd),PARAMETER :: d=5000.        ! Witdth parameter for theta
61  REAL(rstd),PARAMETER :: lonc=2*pi/3    ! Longitudinal centerpoint of theta
62  REAL(rstd),PARAMETER :: latc=0         ! Longitudinal centerpoint of theta
63  REAL(rstd),PARAMETER :: dtheta=1.      ! Maximum amplitude of theta (K)
64  REAL(rstd),PARAMETER :: Lz=20000.      ! Vertical wave lenght of the theta perturbation
65
66  REAL(rstd), INTENT(OUT) :: ps(iim*jjm)
67  REAL(rstd), INTENT(OUT) :: phis(iim*jjm)
68  REAL(rstd), INTENT(OUT) :: u(3*iim*jjm,llm)
69  REAL(rstd), INTENT(OUT) :: theta_rhodz(iim*jjm,llm)
70  REAL(rstd), INTENT(OUT) :: q(iim*jjm,llm,nqtot)
71 
72  REAL(rstd) :: Ts(iim*jjm)
73  REAL(rstd) :: s(iim*jjm)
74  REAL(rstd) :: T(iim*jjm,llm)
75  REAL(rstd) :: p(iim*jjm,llm+1)
76  REAL(rstd) :: theta(iim*jjm,llm)
77  REAL(rstd) :: ulon(3*iim*jjm,llm)
78  REAL(rstd) :: ulat(3*iim*jjm,llm)
79 
80 
81  INTEGER :: i,j,l,ij
82  REAL(rstd) :: Rd        ! gas constant of dry air, P=rho.Rd.T
83  REAL(rstd) :: alpha, rm
84  REAL(rstd) :: lon,lat, C0, C1, GG
85  REAL(rstd) :: p0psk, pspsk,r,zz, thetab, thetap
86  REAL(rstd) :: dummy, pp
87  LOGICAL    :: use_dcmip_routine
88 
89  Rd=cpp*kappa
90 
91  GG=(g/N)**2/cpp
92  C0=0.25*u0*(u0+2.*Omega*radius)
93 
94  q(:,:,:)=0
95 
96!  use_dcmip_routine=.TRUE.
97  use_dcmip_routine=.FALSE.
98  dummy=0.
99
100  pp=peq
101  DO j=jj_begin,jj_end
102     DO i=ii_begin,ii_end
103        ij=(j-1)*iim+i
104        CALL xyz2lonlat(xyz_i(ij,:),lon,lat)
105
106        IF(use_dcmip_routine) THEN
107           CALL test3_gravity_wave(lon,lat,pp,dummy,0, dummy,dummy,dummy,dummy,phis(ij),ps(ij),dummy,dummy)
108        ELSE
109           C1=C0*(cos(2*lat)-1)
110           
111           !--- GROUND GEOPOTENTIAL
112           phis(ij)=0.
113           
114           !--- GROUND TEMPERATURE
115           Ts(ij) = GG+(Teq-GG)*EXP(-C1*(N/g)**2)
116           
117           !--- GROUND PRESSURE
118           Ps(ij) = peq*EXP(C1/GG/Rd)*(Ts(ij)/Teq)**(1/kappa)
119           
120           
121           r=radius*acos(sin(latc)*sin(lat)+cos(latc)*cos(lat)*cos(lon-lonc))
122           s(ij)= d**2/(d**2+r**2)
123        END IF
124     END DO
125  END DO
126 
127  CALL compute_pression(ps,p,0)
128 
129  DO l=1,llm
130     DO j=jj_begin,jj_end
131        DO i=ii_begin,ii_end
132           ij=(j-1)*iim+i
133           pp=0.5*(p(ij,l+1)+p(ij,l))  ! full-layer pressure
134           IF(use_dcmip_routine) THEN
135              CALL xyz2lonlat(xyz_i(ij,:),lon,lat)
136              CALL test3_gravity_wave(lon,lat,pp,dummy,0,dummy,dummy,dummy,T(ij,l),dummy,dummy,dummy,dummy)
137           ELSE
138              pspsk=(pp/ps(ij))**kappa
139              p0psk=(Peq/ps(ij))**kappa
140              thetab = Ts(ij)*p0psk / ( Ts(ij) / GG * ( pspsk-1) +1)  ! background pot. temp.
141              zz     = -g/N**2*log( Ts(ij)/GG * (pspsk -1)+1)         ! altitude
142              thetap = dtheta *sin(2*Pi*zz/Lz) * s(ij)                ! perturbation pot. temp.
143              theta(ij,l) = thetab + thetap
144              T(ij,l) = theta(ij,l)* ((pp/peq)**kappa)
145              ! T(ij,l) = Ts(ij)*pspsk / ( Ts(ij) / GG * ( pspsk-1) +1)  ! background temp.
146           END IF
147        ENDDO
148     ENDDO
149  ENDDO
150 
151  IF(use_dcmip_routine) THEN
152     CALL compute_temperature2theta_rhodz(ps,T,theta_rhodz,0)
153  ELSE
154     CALL compute_temperature2theta_rhodz(ps,T,theta_rhodz,0)
155  END IF
156 
157  pp=peq
158  DO l=1,llm
159     DO j=jj_begin-1,jj_end+1
160        DO i=ii_begin-1,ii_end+1
161           ij=(j-1)*iim+i
162           IF(use_dcmip_routine) THEN
163              CALL xyz2lonlat(xyz_e(ij+u_right,:),lon,lat)
164              CALL test3_gravity_wave(lon,lat,pp,0.,0, &
165                   ulon(ij+u_right,l),ulat(ij+u_right,l),&
166                   dummy,dummy,dummy,dummy,dummy,dummy)
167              CALL xyz2lonlat(xyz_e(ij+u_lup,:),lon,lat)
168              CALL test3_gravity_wave(lon,lat,pp,0.,0,&
169                   ulon(ij+u_lup,l),ulat(ij+u_lup,l),&
170                   dummy,dummy,dummy,dummy,dummy,dummy)
171              CALL xyz2lonlat(xyz_e(ij+u_ldown,:),lon,lat)
172              CALL test3_gravity_wave(lon,lat,pp,0.,0,&
173                   ulon(ij+u_ldown,l),ulat(ij+u_ldown,l),&
174                   dummy,dummy,dummy,dummy,dummy,dummy)
175           ELSE
176              CALL xyz2lonlat(xyz_e(ij+u_right,:),lon,lat)
177              ulon(ij+u_right,l)=u0*cos(lat)
178              ulat(ij+u_right,l)=0
179             
180              CALL xyz2lonlat(xyz_e(ij+u_lup,:),lon,lat)
181              ulon(ij+u_lup,l)=u0*cos(lat)
182              ulat(ij+u_lup,l)=0
183             
184              CALL xyz2lonlat(xyz_e(ij+u_ldown,:),lon,lat)
185              ulon(ij+u_ldown,l)=u0*cos(lat)
186              ulat(ij+u_ldown,l)=0
187           END IF
188        ENDDO
189     ENDDO
190  ENDDO
191 
192  CALL compute_wind_perp_from_lonlat_compound(ulon,ulat,u)   
193 
194END SUBROUTINE compute_etat0_DCMIP3
195
196
197END MODULE etat0_DCMIP3_mod
Note: See TracBrowser for help on using the repository browser.