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

Last change on this file since 272 was 252, checked in by dubos, 10 years ago

Fix recently introduced bug : slope limiter

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