source: codes/icosagcm/trunk/src/advect_tracer.f90 @ 174

Last change on this file since 174 was 174, checked in by ymipsl, 11 years ago

Transform 2 loops on i and j in one loop ij for efficiency, vectorization and future GPU programing

YM

File size: 9.4 KB
Line 
1MODULE advect_tracer_mod
2  USE icosa
3  IMPLICIT NONE
4  PRIVATE
5
6  TYPE(t_field),POINTER :: f_normal(:)
7  TYPE(t_field),POINTER :: f_tangent(:)
8  TYPE(t_field),POINTER :: f_gradq3d(:)
9  TYPE(t_field),POINTER :: f_cc(:)  ! starting point of backward-trajectory (Miura approach)
10  TYPE(t_field),POINTER :: f_one_over_sqrt_leng(:)
11
12  TYPE(t_message) :: req_u, req_cc, req_wfluxt, req_q, req_rhodz, req_gradq3d
13
14  REAL(rstd), PARAMETER :: pente_max=2.0 ! for vlz
15
16! temporary shared variable for vlz
17  TYPE(t_field),POINTER :: f_dzqw(:)   ! vertical finite difference of q
18  TYPE(t_field),POINTER :: f_adzqw(:)  ! abs(dzqw)
19  TYPE(t_field),POINTER :: f_dzq(:)    ! limited slope of q
20  TYPE(t_field),POINTER :: f_wq(:)     ! time-integrated flux of q
21
22  PUBLIC init_advect_tracer, advect_tracer
23
24CONTAINS
25
26  SUBROUTINE init_advect_tracer
27    USE advect_mod
28    REAL(rstd),POINTER :: tangent(:,:)
29    REAL(rstd),POINTER :: normal(:,:)
30    REAL(rstd),POINTER :: one_over_sqrt_leng(:)
31    INTEGER :: ind
32
33    CALL allocate_field(f_normal,field_u,type_real,3, name='normal')
34    CALL allocate_field(f_tangent,field_u,type_real,3, name='tangent')
35    CALL allocate_field(f_gradq3d,field_t,type_real,llm,3, name='gradq3d')
36    CALL allocate_field(f_cc,field_u,type_real,llm,3, name='cc')
37    CALL allocate_field(f_one_over_sqrt_leng,field_t,type_real, name='one_over_sqrt_leng')
38    CALL allocate_field(f_dzqw, field_t, type_real, llm, name='dzqw')
39    CALL allocate_field(f_adzqw, field_t, type_real, llm, name='adzqw')
40    CALL allocate_field(f_dzq, field_t, type_real, llm, name='dzq')
41    CALL allocate_field(f_wq, field_t, type_real, llm+1, name='wq')
42   
43    DO ind=1,ndomain
44       CALL swap_dimensions(ind)
45       CALL swap_geometry(ind)
46       normal=f_normal(ind)
47       tangent=f_tangent(ind)
48       one_over_sqrt_leng=f_one_over_sqrt_leng(ind)
49       CALL init_advect(normal,tangent,one_over_sqrt_leng)
50    END DO
51
52  END SUBROUTINE init_advect_tracer
53
54  SUBROUTINE advect_tracer(f_hfluxt, f_wfluxt,f_u, f_q,f_rhodz)
55    USE advect_mod
56    USE mpipara
57    USE trace
58    USE write_field
59    IMPLICIT NONE
60   
61    TYPE(t_field),POINTER :: f_hfluxt(:)   ! time-integrated horizontal mass flux
62    TYPE(t_field),POINTER :: f_wfluxt(:)   ! time-integrated vertical mass flux
63    TYPE(t_field),POINTER :: f_u(:)        ! velocity (for back-trajectories)
64    TYPE(t_field),POINTER :: f_q(:)        ! tracer
65    TYPE(t_field),POINTER :: f_rhodz(:)    ! mass field at beginning of macro time step
66
67    REAL(rstd),POINTER :: q(:,:,:), normal(:,:), tangent(:,:), one_over_sqrt_leng(:), gradq3d(:,:,:), cc(:,:,:)
68    REAL(rstd),POINTER :: hfluxt(:,:), wfluxt(:,:)
69    REAL(rstd),POINTER :: rhodz(:,:), u(:,:) 
70! temporary shared variable for vlz
71    REAL(rstd),POINTER ::  dzqw(:,:)         ! vertical finite difference of q
72    REAL(rstd),POINTER ::  adzqw(:,:)        ! abs(dzqw)
73    REAL(rstd),POINTER ::  dzq(:,:)          ! limited slope of q
74    REAL(rstd),POINTER ::  wq(:,:)           ! time-integrated flux of q
75   
76     INTEGER :: ind,k
77    LOGICAL,SAVE :: first=.TRUE.
78!$OMP THREADPRIVATE(first)
79
80    IF (first) THEN
81      first=.FALSE.
82      CALL init_message(f_u,req_e1_vect,req_u)
83      CALL init_message(f_cc,req_e1_scal,req_cc)
84      CALL init_message(f_wfluxt,req_i1,req_wfluxt)
85      CALL init_message(f_q,req_i1,req_q)
86      CALL init_message(f_rhodz,req_i1,req_rhodz)
87      CALL init_message(f_gradq3d,req_i1,req_gradq3d)
88    ENDIF
89   
90!$OMP BARRIER
91
92    CALL trace_start("advect_tracer") 
93
94    CALL send_message(f_u,req_u)
95    CALL send_message(f_wfluxt,req_wfluxt)
96    CALL send_message(f_q,req_q)
97    CALL send_message(f_rhodz,req_rhodz)
98    CALL wait_message(req_u)
99    CALL wait_message(req_wfluxt)
100    CALL wait_message(req_q)
101    CALL wait_message(req_rhodz)
102   
103    ! 1/2 vertical transport + back-trajectories
104    DO ind=1,ndomain
105       CALL swap_dimensions(ind)
106       CALL swap_geometry(ind)
107       normal  = f_normal(ind)
108       tangent = f_tangent(ind)
109       cc      = f_cc(ind)
110       u       = f_u(ind)
111       q       = f_q(ind)
112       rhodz   = f_rhodz(ind)
113       wfluxt  = f_wfluxt(ind) 
114       dzqw    = f_dzqw(ind)
115       adzqw   = f_adzqw(ind)
116       dzq     = f_dzq(ind)
117       wq      = f_wq(ind) 
118
119       DO k = 1, nqtot
120          CALL vlz(k==nqtot,0.5, wfluxt,rhodz,q(:,:,k),1,dzqw, adzqw, dzq, wq)
121       END DO
122
123       CALL compute_backward_traj(tangent,normal,u,0.5*dt*itau_adv, cc) 
124
125    END DO
126
127    CALL send_message(f_cc,req_cc)
128
129
130    ! horizontal transport - split in two to place transfer of gradq3d
131!$OMP BARRIER
132    DO k = 1, nqtot
133       DO ind=1,ndomain
134          CALL swap_dimensions(ind)
135          CALL swap_geometry(ind)
136          q       = f_q(ind)
137          gradq3d = f_gradq3d(ind)
138          one_over_sqrt_leng=f_one_over_sqrt_leng(ind)
139          CALL compute_gradq3d(q(:,:,k),one_over_sqrt_leng,gradq3d)
140       END DO
141
142       CALL send_message(f_gradq3d,req_gradq3d)
143       CALL wait_message(req_cc)
144       CALL wait_message(req_gradq3d)
145
146
147       DO ind=1,ndomain
148          CALL swap_dimensions(ind)
149          CALL swap_geometry(ind)
150          cc      = f_cc(ind)
151          q       = f_q(ind)
152          rhodz   = f_rhodz(ind)
153          hfluxt  = f_hfluxt(ind) 
154          gradq3d = f_gradq3d(ind)
155          CALL compute_advect_horiz(k==nqtot,hfluxt,cc,gradq3d, rhodz,q(:,:,k))
156       END DO
157    END DO 
158   
159    ! 1/2 vertical transport
160!$OMP BARRIER
161
162    DO ind=1,ndomain
163       CALL swap_dimensions(ind)
164       CALL swap_geometry(ind)
165       q       = f_q(ind)
166       rhodz   = f_rhodz(ind)
167       wfluxt  = f_wfluxt(ind) 
168       dzqw    = f_dzqw(ind)
169       adzqw   = f_adzqw(ind)
170       dzq     = f_dzq(ind)
171       wq      = f_wq(ind) 
172
173       DO k = 1,nqtot
174          CALL vlz(k==nqtot, 0.5,wfluxt,rhodz, q(:,:,k),0, dzqw, adzqw, dzq, wq)
175       END DO
176
177    END DO
178
179    CALL trace_end("advect_tracer")
180
181!$OMP BARRIER
182
183  END SUBROUTINE advect_tracer
184
185  SUBROUTINE vlz(update_mass, fac,wfluxt,mass, q, halo, dzqw, adzqw, dzq, wq)
186    !
187    !     Auteurs:   P.Le Van, F.Hourdin, F.Forget, T. Dubos
188    !
189    !    ********************************************************************
190    !     Update tracers using vertical mass flux only
191    !     Van Leer scheme with minmod limiter
192    !     wfluxt >0 for upward transport
193    !    ********************************************************************
194    USE trace
195    USE omp_para
196    IMPLICIT NONE
197    LOGICAL, INTENT(IN)       :: update_mass
198    REAL(rstd), INTENT(IN)    :: fac, wfluxt(iim*jjm,llm+1) ! vertical mass flux
199    REAL(rstd), INTENT(INOUT) :: mass(iim*jjm,llm)
200    REAL(rstd), INTENT(INOUT) :: q(iim*jjm,llm)
201    INTEGER, INTENT(IN) :: halo
202
203! temporary shared variable
204    REAL(rstd),INTENT(INOUT) :: dzqw(iim*jjm,llm),        & ! vertical finite difference of q
205                                adzqw(iim*jjm,llm),       & ! abs(dzqw)
206                                dzq(iim*jjm,llm),         & ! limited slope of q
207                                wq(iim*jjm,llm+1)           ! time-integrated flux of q
208
209
210    REAL(rstd) :: dzqmax, newmass, sigw, qq, w
211    INTEGER :: i,ij,l,j,ijb,ije
212
213    CALL trace_start("vlz")
214     
215     ijb=((jj_begin-halo)-1)*iim+ii_begin-halo
216     ije = ((jj_end+halo)-1)*iim+ii_end+halo
217
218    ! finite difference of q
219
220     DO l=ll_beginp1,ll_end
221!$SIMD
222       DO ij=ijb,ije
223         dzqw(ij,l)=q(ij,l)-q(ij,l-1)
224         adzqw(ij,l)=abs(dzqw(ij,l))
225       ENDDO
226    ENDDO
227
228!--> flush dzqw, adzqw
229!$OMP BARRIER
230
231    ! minmod-limited slope of q
232    ! dzq = slope*dz, i.e. the reconstructed q varies by dzq inside level l
233
234     DO l=ll_beginp1,ll_endm1
235!$SIMD
236       DO ij=ijb,ije 
237         IF(dzqw(ij,l)*dzqw(ij,l+1).gt.0.) THEN
238             dzq(ij,l) = 0.5*( dzqw(ij,l)+dzqw(ij,l+1) )
239             dzqmax    = pente_max * min( adzqw(ij,l),adzqw(ij,l+1) )
240             dzq(ij,l) = sign( min(abs(dzq(ij,l)),dzqmax) , dzq(ij,l) )  ! NB : sign(a,b)=a*sign(b)
241          ELSE
242             dzq(ij,l)=0.
243          ENDIF
244       ENDDO
245    ENDDO
246
247
248    ! 0 slope in top and bottom layers
249    IF (omp_first) THEN
250      DO ij=ijb,ije
251           dzq(ij,1)=0.
252      ENDDO
253    ENDIF
254     
255    IF (omp_last) THEN
256      DO ij=ijb,ije
257          dzq(ij,llm)=0.
258      ENDDO
259    ENDIF
260
261!---> flush dzq
262!$OMP BARRIER 
263
264    ! sigw = fraction of mass that leaves level l/l+1
265    ! then amount of q leaving level l/l+1 = wq = w * qq
266     DO l=ll_beginp1,ll_end
267!$SIMD
268       DO ij=ijb,ije
269             w = fac*wfluxt(ij,l)
270             IF(w>0.) THEN  ! upward transport, upwind side is at level l
271                sigw       = w/mass(ij,l-1)
272                qq         = q(ij,l-1)+0.5*(1.-sigw)*dzq(ij,l-1) ! qq = q if sigw=1 , qq = q+dzq/2 if sigw=0
273             ELSE           ! downward transport, upwind side is at level l+1
274                sigw       = w/mass(ij,l)
275                qq         = q(ij,l)-0.5*(1.+sigw)*dzq(ij,l) ! qq = q if sigw=-1 , qq = q-dzq/2 if sigw=0               
276             ENDIF
277             wq(ij,l) = w*qq
278       ENDDO
279    END DO
280    ! wq = 0 at top and bottom
281    IF (omp_first) THEN
282       DO ij=ijb,ije
283            wq(ij,1)=0.
284      END DO
285    ENDIF
286   
287    IF (omp_last) THEN
288      DO ij=ijb,ije
289            wq(ij,llm+1)=0.
290      END DO
291    ENDIF
292
293! --> flush wq
294!$OMP BARRIER
295
296
297    ! update q, mass is updated only after all q's have been updated
298    DO l=ll_begin,ll_end
299!$SIMD
300       DO ij=ijb,ije
301             newmass = mass(ij,l) + fac*(wfluxt(ij,l)-wfluxt(ij,l+1))
302             q(ij,l) = ( q(ij,l)*mass(ij,l) + wq(ij,l)-wq(ij,l+1) ) / newmass
303             IF(update_mass) mass(ij,l)=newmass
304       ENDDO
305    END DO
306
307    CALL trace_end("vlz")
308
309  END SUBROUTINE vlz
310
311END MODULE advect_tracer_mod
Note: See TracBrowser for help on using the repository browser.