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

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

Introduced DCMIP-supplied routines for optional use in test cases 1,2,3.

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