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

Last change on this file since 186 was 186, checked in by ymipsl, 10 years ago

Add new openMP parallelism based on distribution of domains on threads. There is no more limitation of number of threads by MPI process.

YM

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