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

Last change on this file since 1328 was 1315, checked in by milmd, 11 years ago

LMDZ.GENERIC. OpenMP directives added in generic physic. When running in pure OpenMP or hybrid OpenMP/MPI, may have some bugs with condense_cloud and wstats routines.

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