source: trunk/LMDZ.PLUTO/libf/phypluto/callsedim.F @ 3586

Last change on this file since 3586 was 3356, checked in by afalco, 8 months ago

Pluto PCM:
sedimentation uses pphi. More precise than generic sedimentation?
molrad and visc adapted to Pluto.
AF

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