source: codes/icosagcm/trunk/src/etat0_dcmip1.f90 @ 155

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

Improved etat0_dcmip1.f90

File size: 8.1 KB
Line 
1MODULE etat0_dcmip1_mod
2  USE icosa
3  PRIVATE
4
5  REAL(rstd), SAVE  :: h0=1.
6  REAL(rstd), SAVE  :: lon0=3*pi/2
7  REAL(rstd), SAVE  :: lat0=0.0
8  REAL(rstd), SAVE  :: alpha=0.0
9  REAL(rstd), SAVE  :: R0 
10  REAL(rstd), SAVE  :: lat1=0.
11  REAL(rstd), SAVE  :: lat2=0.
12  REAL(rstd), SAVE  :: lon1=pi/6
13  REAL(rstd), SAVE  :: lon2=-pi/6
14  REAL(rstd), SAVE  :: latc1=0.
15  REAL(rstd), SAVE  :: latc2=0.
16  REAL(rstd), SAVE  :: lonc1=5*pi/6
17  REAL(rstd), SAVE  :: lonc2=7*pi/6
18  REAL(rstd), SAVE  :: zt=1000.0
19  REAL(rstd), SAVE  :: rt
20  REAL(rstd), SAVE  :: zc=5000.0
21
22  PUBLIC etat0
23 
24CONTAINS
25 
26  SUBROUTINE etat0(f_ps,f_phis,f_theta_rhodz,f_u,f_q)
27  USE icosa
28  IMPLICIT NONE
29    TYPE(t_field),POINTER :: f_ps(:)
30    TYPE(t_field),POINTER :: f_phis(:)
31    TYPE(t_field),POINTER :: f_theta_rhodz(:)
32    TYPE(t_field),POINTER :: f_u(:)
33    TYPE(t_field),POINTER :: f_q(:)
34 
35    REAL(rstd),POINTER :: ps(:)
36    REAL(rstd),POINTER :: phis(:)
37    REAL(rstd),POINTER :: theta_rhodz(:,:)
38    REAL(rstd),POINTER :: u(:,:)
39    REAL(rstd),POINTER :: q(:,:,:)
40    CHARACTER(len=255) :: dcmip1_adv_shape
41    INTEGER :: ind
42   
43    R0=radius*0.5
44    rt=radius*0.5
45    dcmip1_adv_shape='cos_bell'
46    CALL getin('dcmip1_shape',dcmip1_adv_shape)
47   
48    DO ind=1,ndomain
49      CALL swap_dimensions(ind)
50      CALL swap_geometry(ind)
51      ps=f_ps(ind)
52      phis=f_phis(ind)
53      theta_rhodz=f_theta_rhodz(ind)
54      u=f_u(ind)
55      q=f_q(ind)
56
57
58      SELECT CASE(TRIM(dcmip1_adv_shape))
59      CASE('const')
60         CALL compute_etat0_ncar(1,ps, phis, theta_rhodz, u, q(:,:,1))
61      CASE('cos_bell')
62         CALL compute_etat0_ncar(2,ps, phis, theta_rhodz, u, q(:,:,1))
63      CASE('slotted_cyl')
64         CALL compute_etat0_ncar(3,ps, phis, theta_rhodz, u, q(:,:,1))
65      CASE('dbl_cos_bell_q1')
66         CALL compute_etat0_ncar(4,ps, phis, theta_rhodz, u, q(:,:,1))
67      CASE('dbl_cos_bell_q2')
68         CALL compute_etat0_ncar(5,ps, phis, theta_rhodz, u, q(:,:,1))
69      CASE('complement')
70         CALL compute_etat0_ncar(6,ps, phis, theta_rhodz, u, q(:,:,1))
71      CASE('hadley')  ! hadley like meridional circulation
72         CALL compute_etat0_ncar(7,ps, phis, theta_rhodz, u, q(:,:,1))
73      CASE('dcmip11')
74         IF(nqtot==5) THEN
75            CALL compute_etat0_ncar(4,ps, phis, theta_rhodz, u, q(:,:,1))
76            CALL compute_etat0_ncar(5,ps, phis, theta_rhodz, u, q(:,:,2))
77            CALL compute_etat0_ncar(3,ps, phis, theta_rhodz, u, q(:,:,3))
78            CALL compute_etat0_ncar(6,ps, phis, theta_rhodz, u, q(:,:,4))
79            CALL compute_etat0_ncar(1,ps, phis, theta_rhodz, u, q(:,:,5))
80         ELSE
81            PRINT *,'Error : etat0_dcmip=dcmip11 and nqtot = ',nqtot,' .'
82            PRINT *,'nqtot must be equal to 5 when etat0_dcmip=dcmip11'
83            STOP
84         END IF
85      CASE DEFAULT
86         PRINT *, 'Bad selector for variable dcmip1_adv_shape : <', TRIM(dcmip1_adv_shape),   &
87              '> options are <const>, <slotted_cyl>, <cos_bell>, <dbl_cos_bell_q1>', &
88              '<dbl_cos_bell_q2>, <complement>, <hadley>'
89         STOP
90      END SELECT
91
92    ENDDO
93
94  END SUBROUTINE etat0
95 
96  SUBROUTINE compute_etat0_ncar(icase, ps, phis, theta_rhodz, u, q)
97  USE icosa
98  USE disvert_mod
99  USE pression_mod
100  USE exner_mod
101  USE geopotential_mod
102  USE theta2theta_rhodz_mod
103  IMPLICIT NONE 
104  INTEGER, INTENT(in) :: icase
105  REAL(rstd),INTENT(OUT) :: ps(iim*jjm)
106  REAL(rstd),INTENT(OUT) :: phis(iim*jjm)
107  REAL(rstd),INTENT(OUT) :: theta_rhodz(iim*jjm,llm)
108  REAL(rstd),INTENT(OUT) :: u(3*iim*jjm,llm)
109  REAL(rstd),INTENT(OUT) :: q(iim*jjm,llm) 
110
111  REAL(rstd) :: qxt1(iim*jjm,llm)
112  REAL(rstd) :: lon, lat
113  REAL(rstd) ::dd1,dd2,dd1t1,dd1t2,dd2t1
114  REAL(rstd) :: pr, zr(llm+1), zrl(llm)
115  REAL(rstd) :: rr1,rr2,bb,cc,aa,hmx
116  REAL(rstd) :: X2(3),X1(3)
117  INTEGER :: i,j,n,l
118
119  u = 0.0 ; phis = 0 ; theta_rhodz = 0 ; ps = ncar_p0
120 
121  DO l=1, llm+1
122     pr = ap(l) + bp(l)*ncar_p0
123     zr(l) = -kappa*cpp*ncar_T0/g*log(pr/ncar_p0) 
124  ENDDO
125 
126  DO l=1, llm 
127     zrl(l) = 0.5*(zr(l) + zr(l+1)) 
128  END DO
129 
130  SELECT CASE(icase)
131  CASE(1)
132     q=1
133  CASE(2)
134     !--------------------------------------------- SINGLE COSINE BELL
135     CALL cosine_bell_1(q)     
136  CASE(3)
137     CALL slotted_cylinders(q) 
138  CASE(4)
139     PRINT *, 'Double cosine bell'
140     CALL cosine_bell_2(q)     
141  CASE(5)
142     CALL cosine_bell_2(q) 
143     DO l=1,llm
144        q(:,l)= 0.9 - 0.8*q(:,l)*q(:,l)
145     END DO     
146  CASE(6)
147     ! tracer such that, in combination with the other tracer fields
148     ! with weight (3/10), the sum is equal to one
149     CALL cosine_bell_2(qxt1)
150     DO l = 1,llm
151        q(:,l) = 0.9 - 0.8*qxt1(:,l)*qxt1(:,l) 
152     END DO
153     q = q + qxt1 
154     CALL slotted_cylinders(qxt1)
155     q = q + qxt1 
156     q = 1. - q*0.3
157  CASE(7)  ! hadley like meridional circulation
158     CALL hadleyq(q) 
159  END SELECT
160     
161CONTAINS
162
163!======================================================================
164
165    SUBROUTINE cosine_bell_1(hx)
166    IMPLICIT NONE
167    REAL(rstd) :: hx(iim*jjm,llm)
168   
169      DO l=1,llm 
170        DO j=jj_begin-1,jj_end+1
171          DO i=ii_begin-1,ii_end+1
172            n=(j-1)*iim+i
173            CALL xyz2lonlat(xyz_i(n,:),lon,lat)
174            CALL dist_lonlat(lon0,lat0,lon,lat,rr1)  ! GC distance from center
175            rr1 = radius*rr1
176            IF ( rr1 .LT. R0 ) then
177              hx(n,l)= 0.5*h0*(1+cos(pi*rr1/R0)) 
178            ELSE
179              hx(n,l)=0.0
180            END IF
181          END DO
182        END DO
183      END DO
184   
185    END SUBROUTINE cosine_bell_1
186
187!==============================================================================
188
189    SUBROUTINE   cosine_bell_2(hx) 
190    IMPLICIT NONE       
191    REAL(rstd) :: hx(iim*jjm,llm)
192   
193      DO l=1,llm
194        DO j=jj_begin-1,jj_end+1
195          DO i=ii_begin-1,ii_end+1
196            n=(j-1)*iim+i
197            CALL xyz2lonlat(xyz_i(n,:),lon,lat)
198            CALL dist_lonlat(lonc1,latc1,lon,lat,rr1)  ! GC distance from center
199            rr1 = radius*rr1
200            CALL dist_lonlat(lonc2,latc2,lon,lat,rr2)  ! GC distance from center
201            rr2 = radius*rr2
202            dd1t1 = rr1/rt
203            dd1t1 = dd1t1*dd1t1
204            dd1t2 = (zrl(l) - zc)/zt
205            dd1t2 = dd1t2*dd1t2 
206            dd1 = dd1t1 + dd1t2 
207            dd1 = Min(1.0,dd1) 
208            dd2t1 = rr2/rt
209            dd2t1 = dd2t1*dd2t1
210            dd2 = dd2t1 + dd1t2 
211            dd2 = Min(1.0,dd2) 
212            hx(n,l)= 0.5*(1. + cos(pi*dd1))+0.5*(1.+cos(pi*dd2))
213          END DO
214        END DO
215      END DO
216
217    END SUBROUTINE cosine_bell_2
218
219!=============================================================================
220
221    SUBROUTINE slotted_cylinders(hx) 
222    IMPLICIT NONE
223    REAL(rstd) :: hx(iim*jjm,llm)
224   
225      DO l=1,llm
226        DO j=jj_begin-1,jj_end+1
227          DO i=ii_begin-1,ii_end+1
228            n=(j-1)*iim+i
229            CALL xyz2lonlat(xyz_i(n,:),lon,lat)
230            CALL dist_lonlat(lonc1,latc1,lon,lat,rr1)  ! GC distance from center
231            rr1 = radius*rr1
232            CALL dist_lonlat(lonc2,latc2,lon,lat,rr2)  ! GC distance from center
233            rr2 = radius*rr2
234            dd1t1 = rr1/rt
235            dd1t1 = dd1t1*dd1t1
236            dd1t2 = (zrl(l) - zc)/zt
237            dd1t2 = dd1t2*dd1t2 
238            dd1 = dd1t1 + dd1t2 
239            dd2t1 = rr2/rt
240            dd2t1 = dd2t1*dd2t1
241            dd2 = dd2t1 + dd1t2
242           
243            IF ( dd1 .LT. 0.5 ) Then
244              hx(n,l) = 1.0
245            ELSEIF ( dd2 .LT. 0.5 ) Then
246              hx(n,l) = 1.0
247            ELSE
248              hx(n,l) = 0.1 
249            END IF 
250   
251            IF ( zrl(l) .GT. zc ) Then
252              IF ( ABS(latc1 - lat) .LT. 0.125 ) Then
253                hx(n,l)= 0.1
254              ENDIF
255            ENDIF 
256 
257          ENDDO
258       END DO
259      END DO
260
261    END SUBROUTINE slotted_cylinders 
262
263!==============================================================================
264
265    SUBROUTINE hadleyq(hx) 
266    IMPLICIT NONE
267    REAL(rstd)::hx(iim*jjm,llm) 
268    REAL(rstd),PARAMETER:: zz1=3500.,zz2=6500.,zz0=0.5*(zz1+zz2)
269   
270      DO l=1,llm
271        IF ( ( zz1 .LT. zrl(l) ) .and. ( zrl(l) .LT. zz2 ) )  THEN
272          hx(:,l) = 0.5*(1. + cos(0.002*pi*(zrl(l)-zz0)/3.)) 
273        ELSE
274          hx(:,l) = 0.0 
275        END IF
276      END DO
277    END SUBROUTINE hadleyq 
278
279  END SUBROUTINE compute_etat0_ncar
280 
281
282END MODULE etat0_dcmip1_mod
Note: See TracBrowser for help on using the repository browser.