source: trunk/LMDZ.GENERIC/libf/phystd/callsedim.F @ 2987

Last change on this file since 2987 was 2972, checked in by emillour, 18 months ago

Generic PCM:
Make number of scatterers fully dynamic (i.e. set in callphys.def
and no longer by compilation option "-s #").
One should now specify
naerkind = #
in callphys.def (default is 0).
EM

File size: 5.7 KB
RevLine 
[135]1      SUBROUTINE callsedim(ngrid,nlay, ptimestep,
[858]2     &                pplev,zlev, pt, pdt,
3     &                pq, pdqfi, pdqsed,pdqs_sed,nq)
[787]4
[858]5      use radinc_h, only : naerkind
6      use radii_mod, only: h2o_reffrad
7      use aerosol_mod, only : iaero_h2o
8      USE tracer_h, only : igcm_co2_ice,igcm_h2o_ice,radius,rho_q
[1384]9      use comcstfi_mod, only: g
[1397]10      use callkeys_mod, only : water
[787]11
[135]12      IMPLICIT NONE
13
14!==================================================================
15!     
16!     Purpose
17!     -------
18!     Calculates sedimentation of aerosols depending on their
19!     density and radius.
20!     
21!     Authors
22!     -------
23!     F. Forget (1999)
24!     Tracer generalisation by E. Millour (2009)
25!     
26!==================================================================
27
28c-----------------------------------------------------------------------
29c   declarations:
30c   -------------
31
32c   arguments:
33c   ----------
34
[858]35      integer,intent(in):: ngrid ! number of horizontal grid points
36      integer,intent(in):: nlay  ! number of atmospheric layers
37      real,intent(in):: ptimestep  ! physics time step (s)
38      real,intent(in):: pplev(ngrid,nlay+1) ! pressure at inter-layers (Pa)
39      real,intent(in):: pt(ngrid,nlay)      ! temperature at mid-layer (K)
40      real,intent(in):: pdt(ngrid,nlay) ! tendency on temperature
41      real,intent(in):: zlev(ngrid,nlay+1)  ! altitude at layer boundaries
42      integer,intent(in) :: nq ! number of tracers
43      real,intent(in) :: pq(ngrid,nlay,nq)  ! tracers (kg/kg)
44      real,intent(in) :: pdqfi(ngrid,nlay,nq)  ! tendency on tracers before
45                                               ! sedimentation (kg/kg.s-1)
[135]46     
[858]47      real,intent(out) :: pdqsed(ngrid,nlay,nq) ! tendency due to sedimentation (kg/kg.s-1)
48      real,intent(out) :: pdqs_sed(ngrid,nq)    ! flux at surface (kg.m-2.s-1)
[2671]49
[135]50c   local:
51c   ------
52
53      INTEGER l,ig, iq
54
[858]55      ! for particles with varying radii:
[2972]56      real,allocatable,save :: reffrad(:,:,:) ! particle radius (m)
57      real,allocatable,save :: nueffrad(:,:,:) ! aerosol effective radius variance
58!$OMP THREADPRIVATE(reffrad,nueffrad)
[858]59
60      real zqi(ngrid,nlay,nq) ! to locally store tracers
61      real zt(ngrid,nlay) ! to locally store temperature (K)
62      real masse (ngrid,nlay) ! Layer mass (kg.m-2)
63      real epaisseur (ngrid,nlay) ! Layer thickness (m)
64      real wq(ngrid,nlay+1) ! displaced tracer mass (kg.m-2)
[1308]65c      real dens(ngrid,nlay) ! Mean density of the ice part. accounting for dust core
[135]66
67
[858]68      LOGICAL,SAVE :: firstcall=.true.
[1315]69!$OMP THREADPRIVATE(firstcall)
[135]70
71c    ** un petit test de coherence
72c       --------------------------
73
74      IF (firstcall) THEN
75        firstcall=.false.
[1006]76        ! add some tests on presence of required tracers/aerosols:
[2536]77        if (water.and.(igcm_h2o_ice.eq.0)) then
[1006]78            write(*,*) "callsedim error: water=.true.",
79     &                 " but igcm_h2o_ice=0"
80          stop
81        endif
[2972]82        ! allocate "naerkind" size local arrays (which are also
83        ! "saved" so that this is done only once in for all even if
84        ! we don't need to store the value from a time step to the next)
85        allocate(reffrad(ngrid,nlay,naerkind))
86        allocate(nueffrad(ngrid,nlay,naerkind))
[135]87      ENDIF ! of IF (firstcall)
[486]88     
[135]89!=======================================================================
90!     Preliminary calculation of the layer characteristics
91!     (mass (kg.m-2), thickness (m), etc.
92
93      do  l=1,nlay
94        do ig=1, ngrid
95          masse(ig,l)=(pplev(ig,l) - pplev(ig,l+1)) /g
96          epaisseur(ig,l)= zlev(ig,l+1) - zlev(ig,l)
[858]97          zt(ig,l)=pt(ig,l)+pdt(ig,l)*ptimestep
[135]98        end do
99      end do
100
[486]101!======================================================================
102! Calculate the transport due to sedimentation for each tracer
103! [This has been rearranged by L. Kerber to allow the sedimentation
104!  of general tracers.]
105 
106      do iq=1,nq
[1764]107       if((radius(iq).gt.1.e-9).and.(iq.ne.igcm_co2_ice)) then ! JVO 08/2017 : be careful radius was tested uninitialized (fixed) ...
108       
[1477]109!         (no sedim for gases, and co2_ice sedim is done in condense_co2)     
[135]110
[486]111! store locally updated tracers
[135]112
[486]113          do l=1,nlay
[787]114            do ig=1, ngrid
[486]115              zqi(ig,l,iq)=pq(ig,l,iq)+pdqfi(ig,l,iq)*ptimestep
[135]116            enddo
117          enddo ! of do l=1,nlay
[486]118       
119!======================================================================
120! Sedimentation
121!======================================================================
122! Water         
[2536]123       if (water.and.(iaero_h2o.ne.0).and.(iq.eq.igcm_h2o_ice)) then
[858]124            ! compute radii for h2o_ice
[1308]125             call h2o_reffrad(ngrid,nlay,zqi(1,1,igcm_h2o_ice),zt,
[858]126     &                reffrad(1,1,iaero_h2o),nueffrad(1,1,iaero_h2o))
127            ! call sedimentation for h2o_ice
[486]128             call newsedim(ngrid,nlay,ngrid*nlay,ptimestep,
[858]129     &            pplev,masse,epaisseur,zt,reffrad(1,1,iaero_h2o),
[2671]130     &            rho_q(iq),zqi(1,1,igcm_h2o_ice),wq,iq)
[135]131
[486]132! General Case
[2536]133       else
[486]134             call newsedim(ngrid,nlay,1,ptimestep,
[858]135     &            pplev,masse,epaisseur,zt,radius(iq),rho_q(iq),
[2671]136     &            zqi(1,1,iq),wq,iq)
[2536]137       endif
[253]138
[135]139!=======================================================================
140!     Calculate the tendencies
[486]141!======================================================================
[135]142
[787]143          do ig=1,ngrid
[135]144!     Ehouarn: with new way of tracking tracers by name, this is simply
[486]145            pdqs_sed(ig,iq) = wq(ig,1)/ptimestep
[135]146          end do
147
148          DO l = 1, nlay
149            DO ig=1,ngrid
[486]150              pdqsed(ig,l,iq)=(zqi(ig,l,iq)-
151     &        (pq(ig,l,iq) + pdqfi(ig,l,iq)*ptimestep))/ptimestep
[135]152            ENDDO
153          ENDDO
[486]154       endif ! of no gases no co2_ice
155      enddo ! of do iq=1,nq
[253]156      return
157      end
Note: See TracBrowser for help on using the repository browser.