source: codes/icosagcm/trunk/src/initial/etat0_dcmip1.f90 @ 1048

Last change on this file since 1048 was 899, checked in by adurocher, 5 years ago

trunk : Fixed GCC warnings

Fixed iso c bindings
fixed warnings with -Wall -Wno-aliasing -Wno-unused -Wno-unused-dummy-argument -Wno-maybe-uninitialized -Wno-tabs warnings
Removed all unused variables (-Wunused-variable)
vector%dot_product is now dot_product_3d to avoid compilation warning "dot_product shadows intrinsic" with GCC

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