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

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

Merging OpenMP parallisme mode : by subdomain and on vertical level.
This feature is actually experimental but may be retro-compatible with the last method based only on subdomain

YM

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