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

Last change on this file since 150 was 149, checked in by sdubey, 11 years ago
Added few new routines to read NC files and compute diagnostics to r145.
Few routines of dry physics including radiation module, surface process and convective adjustment in new routine phyparam.f90. dynetat to read start files for dynamics. check_conserve routine to compute conservation of quatities like mass, energy etc.etat0_heldsz.f90 for held-suarez test case initial conditions. new Key time_style=lmd or dcmip to use day_step, ndays like in LMDZ
File size: 8.9 KB
RevLine 
[17]1MODULE advect_tracer_mod
[19]2  USE icosa
[138]3  IMPLICIT NONE
[17]4  PRIVATE
[22]5
6  TYPE(t_field),POINTER :: f_normal(:)
7  TYPE(t_field),POINTER :: f_tangent(:)
8  TYPE(t_field),POINTER :: f_gradq3d(:)
[137]9  TYPE(t_field),POINTER :: f_cc(:)  ! starting point of backward-trajectory (Miura approach)
[148]10  TYPE(t_field),POINTER :: f_one_over_sqrt_leng(:)
11 
[136]12  REAL(rstd), PARAMETER :: pente_max=2.0 ! for vlz
13
14  PUBLIC init_advect_tracer, advect_tracer
15
[17]16CONTAINS
[22]17
[98]18  SUBROUTINE init_advect_tracer
[22]19    USE advect_mod
20    REAL(rstd),POINTER :: tangent(:,:)
21    REAL(rstd),POINTER :: normal(:,:)
[148]22    REAL(rstd),POINTER :: one_over_sqrt_leng(:)
[23]23    INTEGER :: ind
[22]24
[138]25    CALL allocate_field(f_normal,field_u,type_real,3, name='normal')
26    CALL allocate_field(f_tangent,field_u,type_real,3, name='tangent')
27    CALL allocate_field(f_gradq3d,field_t,type_real,llm,3, name='gradq3d')
28    CALL allocate_field(f_cc,field_u,type_real,llm,3, name='cc')
[148]29    CALL allocate_field(f_one_over_sqrt_leng,field_t,type_real, name='one_over_sqrt_leng')
[22]30
31    DO ind=1,ndomain
32       CALL swap_dimensions(ind)
33       CALL swap_geometry(ind)
34       normal=f_normal(ind)
35       tangent=f_tangent(ind)
[148]36       one_over_sqrt_leng=f_one_over_sqrt_leng(ind)
37       CALL init_advect(normal,tangent,one_over_sqrt_leng)
[22]38    END DO
39
[17]40  END SUBROUTINE init_advect_tracer
[22]41
[136]42  SUBROUTINE advect_tracer(f_hfluxt, f_wfluxt,f_u, f_q,f_rhodz)
[22]43    USE advect_mod
[136]44    USE mpipara
[145]45    USE trace
[146]46    USE write_field
[22]47    IMPLICIT NONE
[145]48   
[136]49    TYPE(t_field),POINTER :: f_hfluxt(:)   ! time-integrated horizontal mass flux
50    TYPE(t_field),POINTER :: f_wfluxt(:)   ! time-integrated vertical mass flux
51    TYPE(t_field),POINTER :: f_u(:)        ! velocity (for back-trajectories)
52    TYPE(t_field),POINTER :: f_q(:)        ! tracer
53    TYPE(t_field),POINTER :: f_rhodz(:)    ! mass field at beginning of macro time step
[17]54
[148]55    REAL(rstd),POINTER :: q(:,:,:), normal(:,:), tangent(:,:), one_over_sqrt_leng(:), gradq3d(:,:,:), cc(:,:,:)
[136]56    REAL(rstd),POINTER :: hfluxt(:,:), wfluxt(:,:)
57    REAL(rstd),POINTER :: rhodz(:,:), u(:,:) 
[138]58    INTEGER :: ind,k
[17]59
[145]60    CALL trace_start("advect_tracer") 
61
[146]62    CALL transfert_request(f_u,req_e1_vect)
[138]63!    CALL transfert_request(f_hfluxt,req_e1)  ! BUG : This (unnecessary) transfer makes the computation go wrong
64    CALL transfert_request(f_wfluxt,req_i1)
[136]65    CALL transfert_request(f_q,req_i1)
[138]66    CALL transfert_request(f_rhodz,req_i1)
[136]67       
[149]68!    IF (is_mpi_root) PRINT *, 'Advection scheme'
[17]69
[138]70!    DO ind=1,ndomain
71!       CALL swap_dimensions(ind)
72!       CALL swap_geometry(ind)
73!       normal  = f_normal(ind)
74!       tangent = f_tangent(ind)
75!       cc      = f_cc(ind)
76!       u       = f_u(ind)
77!       q       = f_q(ind)
78!       rhodz   = f_rhodz(ind)
79!       hfluxt  = f_hfluxt(ind)
80!       wfluxt  = f_wfluxt(ind)
81!       gradq3d = f_gradq3d(ind)
82!
83!       ! 1/2 vertical transport
84!       DO k = 1, nqtot
85!          CALL vlz(k==nqtot,0.5, wfluxt,rhodz,q(:,:,k))
86!       END DO
87!
88!       ! horizontal transport
89!       CALL compute_backward_traj(tangent,normal,u,0.5*dt*itau_adv, cc)
90!       DO k = 1,nqtot
91!          CALL compute_gradq3d(q(:,:,k),gradq3d)
92!          CALL compute_advect_horiz(k==nqtot,hfluxt,cc,gradq3d, rhodz,q(:,:,k))
93!       END DO
94!
95!       ! 1/2 vertical transport
96!       DO k = 1,nqtot
97!          CALL vlz(k==nqtot, 0.5,wfluxt,rhodz, q(:,:,k))
98!       END DO
99!    END DO
100
101    ! 1/2 vertical transport + back-trajectories
[22]102    DO ind=1,ndomain
[17]103       CALL swap_dimensions(ind)
104       CALL swap_geometry(ind)
[138]105       normal  = f_normal(ind)
106       tangent = f_tangent(ind)
107       cc      = f_cc(ind)
108       u       = f_u(ind)
[136]109       q       = f_q(ind)
110       rhodz   = f_rhodz(ind)
111       wfluxt  = f_wfluxt(ind) 
[148]112
[138]113       DO k = 1, nqtot
[148]114          CALL vlz(k==nqtot,0.5, wfluxt,rhodz,q(:,:,k),1)
[138]115       END DO
[148]116
[138]117       CALL compute_backward_traj(tangent,normal,u,0.5*dt*itau_adv, cc) 
[22]118    END DO
[17]119
[148]120!    CALL transfert_request(f_q,req_i1)      ! necessary ?
121!    CALL transfert_request(f_rhodz,req_i1)  ! necessary ?
[17]122
[138]123    ! horizontal transport - split in two to place transfer of gradq3d
[17]124
[136]125    DO k = 1, nqtot
[138]126       DO ind=1,ndomain
127          CALL swap_dimensions(ind)
128          CALL swap_geometry(ind)
129          q       = f_q(ind)
130          gradq3d = f_gradq3d(ind)
[148]131          one_over_sqrt_leng=f_one_over_sqrt_leng(ind)
132          CALL compute_gradq3d(q(:,:,k),one_over_sqrt_leng,gradq3d)
[138]133       END DO
[17]134
[138]135       CALL transfert_request(f_gradq3d,req_i1)
[17]136
[148]137
138
[138]139       DO ind=1,ndomain
140          CALL swap_dimensions(ind)
141          CALL swap_geometry(ind)
142          cc      = f_cc(ind)
143          q       = f_q(ind)
144          rhodz   = f_rhodz(ind)
145          hfluxt  = f_hfluxt(ind) 
146          gradq3d = f_gradq3d(ind)
147          CALL compute_advect_horiz(k==nqtot,hfluxt,cc,gradq3d, rhodz,q(:,:,k))
148       END DO
149    END DO 
[146]150   
[148]151!    CALL transfert_request(f_q,req_i1)      ! necessary ?
152!    CALL transfert_request(f_rhodz,req_i1)  ! necessary ?
[146]153   
[136]154    ! 1/2 vertical transport
[138]155    DO ind=1,ndomain
156       CALL swap_dimensions(ind)
157       CALL swap_geometry(ind)
158       q       = f_q(ind)
159       rhodz   = f_rhodz(ind)
160       wfluxt  = f_wfluxt(ind) 
161       DO k = 1,nqtot
[148]162          CALL vlz(k==nqtot, 0.5,wfluxt,rhodz, q(:,:,k),0)
[138]163       END DO
[136]164    END DO
[138]165
[146]166    CALL trace_end("advect_tracer")
167
[138]168  END SUBROUTINE advect_tracer
169
[148]170  SUBROUTINE vlz(update_mass, fac,wfluxt,mass, q, halo)
[136]171    !
172    !     Auteurs:   P.Le Van, F.Hourdin, F.Forget, T. Dubos
173    !
174    !    ********************************************************************
175    !     Update tracers using vertical mass flux only
176    !     Van Leer scheme with minmod limiter
177    !     wfluxt >0 for upward transport
178    !    ********************************************************************
[148]179    USE trace
[22]180    IMPLICIT NONE
[136]181    LOGICAL, INTENT(IN)       :: update_mass
182    REAL(rstd), INTENT(IN)    :: fac, wfluxt(iim*jjm,llm+1) ! vertical mass flux
183    REAL(rstd), INTENT(INOUT) :: mass(iim*jjm,llm)
184    REAL(rstd), INTENT(INOUT) :: q(iim*jjm,llm)
[148]185    INTEGER, INTENT(IN) :: halo
[22]186
[136]187    REAL(rstd) :: dq(iim*jjm,llm), & ! increase of q
188         dzqw(iim*jjm,llm),        & ! vertical finite difference of q
189         adzqw(iim*jjm,llm),       & ! abs(dzqw)
190         dzq(iim*jjm,llm),         & ! limited slope of q
191         wq(iim*jjm,llm+1)           ! time-integrated flux of q
192    REAL(rstd) :: dzqmax, newmass, sigw, qq, w
193    INTEGER :: i,ij,l,j
[22]194
[148]195    CALL trace_start("vlz")
196
[136]197    ! finite difference of q
[22]198    DO l=2,llm
[148]199       DO j=jj_begin-halo,jj_end+halo
200          DO i=ii_begin-halo,ii_end+halo
[22]201             ij=(j-1)*iim+i
[136]202             dzqw(ij,l)=q(ij,l)-q(ij,l-1)
[22]203             adzqw(ij,l)=abs(dzqw(ij,l))
204          ENDDO
205       ENDDO
206    ENDDO
207
[136]208    ! minmod-limited slope of q
209    ! dzq = slope*dz, i.e. the reconstructed q varies by dzq inside level l
[22]210    DO l=2,llm-1
[148]211       DO j=jj_begin-halo,jj_end+halo
212          DO i=ii_begin-halo,ii_end+halo
[22]213             ij=(j-1)*iim+i
214             IF(dzqw(ij,l)*dzqw(ij,l+1).gt.0.) THEN
[136]215                dzq(ij,l) = 0.5*( dzqw(ij,l)+dzqw(ij,l+1) )
216                dzqmax    = pente_max * min( adzqw(ij,l),adzqw(ij,l+1) )
217                dzq(ij,l) = sign( min(abs(dzq(ij,l)),dzqmax) , dzq(ij,l) )  ! NB : sign(a,b)=a*sign(b)
[22]218             ELSE
[17]219                dzq(ij,l)=0.
[22]220             ENDIF
221          ENDDO
222       ENDDO
223    ENDDO
[17]224
[136]225    ! 0 slope in top and bottom layers
[148]226    DO j=jj_begin-halo,jj_end+halo
227       DO i=ii_begin-halo,ii_end+halo
[136]228          ij=(j-1)*iim+i
229          dzq(ij,1)=0.
230          dzq(ij,llm)=0.
[22]231       ENDDO
232    ENDDO
[17]233
[136]234    ! sigw = fraction of mass that leaves level l/l+1
235    ! then amount of q leaving level l/l+1 = wq = w * qq
[22]236    DO l = 1,llm-1
[148]237       DO j=jj_begin-halo,jj_end+halo
238          DO i=ii_begin-halo,ii_end+halo
[17]239             ij=(j-1)*iim+i
[138]240             w = fac*wfluxt(ij,l+1)
241             IF(w>0.) THEN  ! upward transport, upwind side is at level l
242                sigw       = w/mass(ij,l)
243                qq         = q(ij,l)+0.5*(1.-sigw)*dzq(ij,l) ! qq = q if sigw=1 , qq = q+dzq/2 if sigw=0
244             ELSE           ! downward transport, upwind side is at level l+1
[136]245                sigw       = w/mass(ij,l+1)
[138]246                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               
[22]247             ENDIF
[138]248             wq(ij,l+1) = w*qq
[22]249          ENDDO
250       ENDDO
251    END DO
[136]252    ! wq = 0 at top and bottom
[148]253    DO j=jj_begin-halo,jj_end+halo
254       DO i=ii_begin-halo,ii_end+halo
[22]255          ij=(j-1)*iim+i
256          wq(ij,llm+1)=0.
257          wq(ij,1)=0.
258       ENDDO
259    END DO
[17]260
[136]261    ! update q, mass is updated only after all q's have been updated
[22]262    DO l=1,llm
[148]263       DO j=jj_begin-halo,jj_end+halo
264          DO i=ii_begin-halo,ii_end+halo
[17]265             ij=(j-1)*iim+i
[136]266             newmass = mass(ij,l) + fac*(wfluxt(ij,l)-wfluxt(ij,l+1))
267             q(ij,l) = ( q(ij,l)*mass(ij,l) + wq(ij,l)-wq(ij,l+1) ) / newmass
268             IF(update_mass) mass(ij,l)=newmass
[22]269          ENDDO
270       ENDDO
271    END DO
[136]272
[148]273    CALL trace_end("vlz")
274
[22]275  END SUBROUTINE vlz
[17]276
277END MODULE advect_tracer_mod
Note: See TracBrowser for help on using the repository browser.