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

Last change on this file since 488 was 353, checked in by dubos, 9 years ago

OpenMP fixes for DCMIP

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