source: trunk/LMDZ.VENUS/libf/phyvenus/phytrac_emiss.F @ 1723

Last change on this file since 1723 was 1621, checked in by emillour, 8 years ago

Further work on full dynamics/physics separation.

LMDZ.COMMON:

  • added phy_common/vertical_layers_mod.F90 to store information on vertical grid. This is where routines in the physics should get the information.
  • The contents of vertical_layers_mod intialized via dynphy_lonlat/inigeomphy_mod.F90.

LMDZ.MARS:

  • physics now completely decoupled from dynamics; the physics package may now be compiled as a library (-libphy option of makelmdz_fcm).
  • created an "ini_tracer_mod" routine in module "tracer_mod" for a cleaner initialization of the later.
  • removed some purely dynamics-related outputs (etot0, zoom parameters, etc.) from diagfi.nc and stats.nc outputs as these informations are not available in the physics.

LMDZ.GENERIC:

  • physics now completely decoupled from dynamics; the physics package may now be compiled as a library (-libphy option of makelmdz_fcm).
  • added nqtot to tracer_h.F90.
  • removed some purely dynamics-related outputs (etot0, zoom parameters, etc.) from diagfi.nc and stats.nc outputs as these informations are not available in the physics.

LMDZ.VENUS:

  • physics now completely decoupled from dynamics; the physics package may now be compiled as a library (-libphy option of makelmdz_fcm).
  • added infotrac_phy.F90 to store information on tracers in the physics. Initialized via iniphysiq.
  • added cpdet_phy_mod.F90 to store t2tpot etc. functions to be used in the physics. Initialized via iniphysiq. IMPORTANT: there are some hard-coded constants! These should match what is in cpdet_mod.F90 in the dynamics.
  • got rid of references to moyzon_mod module within the physics. The required variables (tmoy, plevmoy) are passed to the physics as arguments to physiq.

LMDZ.TITAN:

  • added infotrac_phy.F90 to store information on tracers in the physics. Initialized via iniphysiq.
  • added cpdet_phy_mod.F90 to store t2tpot etc. functions to be used in the physics.
  • Extra work required to completely decouple physics and dynamics: moyzon_mod should be cleaned up and information passed from dynamics to physics as as arguments. Likewise moyzon_ch and moyzon_mu should not be queried from logic_mod (which is in the dynamics).

EM

File size: 6.4 KB
Line 
1!
2! $Header: /home/cvsroot/LMDZ4/libf/phylmd/phytrac.F,v 1.16 2006/03/24 15:06:23 lmdzadmin Exp $
3!
4c
5c
6      SUBROUTINE phytrac_emiss (timesimu,
7     I                    debutphy,
8     I                    lafin,
9     I                    nqmax,
10     I                    nlon,
11     I                    nlev,
12     I                    pdtphys,
13     I                    paprs,
14     I                    xlat,xlon,
15     O                    tr_seri)
16
17c======================================================================
18c Auteur(s) FH
19c Objet: Moniteur general des tendances traceurs
20c
21cAA Remarques en vrac:
22cAA--------------------
23cAA 1/ le call phytrac se fait avec nqmax
24c
25c SL: Janvier 2014
26c Version developed for surface emission
27c Maybe could be used just to compute the 'source' variable from physiq
28c
29c======================================================================
30      USE infotrac_phy, ONLY: nqtot
31      use dimphy
32      USE geometry_mod, only: cell_area
33      USE chemparam_mod,only:M_tr
34      USE mod_grid_phy_lmdz, ONLY: nbp_lon, nbp_lat
35      IMPLICIT none
36#include "YOMCST.h"
37#include "clesphys.h"
38c======================================================================
39
40c Arguments:
41
42c   EN ENTREE:
43c   ==========
44
45      real timesimu   ! duree depuis debut simu (s)
46      logical debutphy       ! le flag de l'initialisation de la physique
47      logical lafin          ! le flag de la fin de la physique
48      integer nqmax ! nombre de traceurs auxquels on applique la physique
49      integer nlon  ! nombre de points horizontaux
50      integer nlev  ! nombre de couches verticales
51      real pdtphys  ! pas d'integration pour la physique (seconde)
52      real paprs(nlon,nlev+1)  ! pression pour chaque inter-couche (en Pa)
53      REAL xlat(nlon)       ! latitudes pour chaque point
54      REAL xlon(nlon)       ! longitudes pour chaque point
55
56c   EN ENTREE/SORTIE:
57c   =================
58
59      real tr_seri(nlon,nlev,nqmax) ! traceur 
60
61cAA ----------------------------
62cAA  VARIABLES LOCALES TRACEURS
63cAA ----------------------------
64
65c pour emission volcan
66      real :: deltatr(klon,klev,nqtot)
67
68      integer,parameter :: nblat=5,nblon=4,nbz=3
69      integer,parameter :: Nemiss=1     ! duree emission (Ed)
70      integer,save :: Nheight(nbz)      ! layer emission
71      real,save :: so2_quantity         ! quantity so2 (kg)
72      real,save :: lat_volcan(nblat),lon_volcan(nblon)
73      real,save :: area_emiss(nblat,nblon)
74      integer,save :: ig_volcan(nblat,nblon)
75
76      INTEGER i, k, it
77      integer ilat,ilon,iz
78      real    deltalat,deltalon
79c======================================================================
80
81c EMISSION TRACEURS
82
83c---------
84c debutphy
85c---------     
86      if (debutphy) then
87
88        print*,"DEBUT PHYTRAC"
89        print*,"PHYTRAC: EMISSION"
90
91        ALLOCATE(M_tr(nqtot))
92        M_tr(:)=64.                 ! SO2
93       
94C=========================================================================
95c Caracteristiques des traceurs emis:
96C=========================================================================
97
98c nombre total de traceur
99         if (nbz*nblat*nblon .gt. nqtot) then
100            print*, nbz*nblat*nblon, nqtot
101            write(*,*) "Attention, pas assez de traceurs"
102            write(*,*) "le dernier sera bien le dernier"
103         endif
104
105c quantite en kg
106         so2_quantity = 20.*10.**9.
107
108c height (in layer index)
109         Nheight(1) =  6  ! ~ 1 km
110         Nheight(2) = 16  ! ~ 25 km
111         Nheight(3) = 24  ! ~ 50 km
112
113c localisation volcan
114         lat_volcan(1) =  70.
115         lat_volcan(2) =  35.
116         lat_volcan(3) =   0.
117         lat_volcan(4) = -35.
118         lat_volcan(5) = -70.
119         lon_volcan(1) = -125.
120         lon_volcan(2) =  -35.
121         lon_volcan(3) =   55.
122         lon_volcan(4) =  145.
123         
124         ig_volcan(ilat,ilon)= 0
125         if ((nbp_lon*nbp_lat)==1) then ! running a 1D simulation
126           deltalat=180.
127           deltalon=360.
128         else
129           deltalat = 180./(nbp_lat-1)
130           deltalon = 360./nbp_lon
131         endif
132
133         do i=1,nlon
134          do ilat=1,nblat
135           do ilon=1,nblon
136            if ((xlat(i).ge.lat_volcan(ilat))
137     &     .and.((xlat(i)-deltalat).lt.lat_volcan(ilat))
138     &     .and.(xlon(i).le.lon_volcan(ilon))
139     &     .and.((xlon(i)+deltalon).gt.lon_volcan(ilon)) ) then
140             ig_volcan(ilat,ilon)= i
141             area_emiss(ilat,ilon) = cell_area(i)
142             print*,"Lat,lon=",ilat,ilon," OK"
143            end if
144           end do
145          end do
146         end do
147
148c Reinit des traceurs si necessaire
149         if (reinit_trac) then
150           tr_seri(:,:,:)=0.
151         endif
152         
153C=========================================================================
154C=========================================================================
155      ENDIF  ! fin debutphy
156c-------------
157c fin debutphy
158c-------------
159
160c======================================================================
161c Emission d'un traceur pendant un certain temps
162c necessite raz_date=1 dans run.def
163c et reinit_trac=y
164c======================================================================
165       deltatr(:,:,:) = 0.
166
167c source appliquee pendant Nemiss Ed
168       if (timesimu .lt. 86400*Nemiss) then
169
170c emet les traceurs qui sont presents sur la grille
171        do ilat  = 1,nblat
172        do ilon  = 1,nblon
173         if (ig_volcan(ilat,ilon).ne.0) then
174         
175          do iz = 1,nbz
176           it=min( (iz-1)*nblat*nblon+(ilat-1)*nblon+ilon , nqtot )         
177           i=ig_volcan(ilat,ilon)
178           
179c injection dans une seule cellule:
180c source en kg/kg/s
181c            deltatr(i,Nheight(iz),it) = so2_quantity/(86400.*Nemiss) ! kg/s
182c     $ *RG/( area_emiss(ilat,ilon)
183c     $      *(paprs(i,Nheight(iz))-paprs(i,Nheight(iz)+1)) )    ! /kg (masse cellule)
184     
185c            tr_seri(i,Nheight(iz),it) = tr_seri(i,Nheight(iz),it)
186c     $      + deltatr(i,Nheight(iz),it)*pdtphys
187
188c injection dans toute la colonne (a faire):
189            do k=1,Nheight(iz)
190             deltatr(i,k,it) = so2_quantity/(86400.*Nemiss) ! kg/s
191     $  *RG/( area_emiss(ilat,ilon)
192     $       *(paprs(i,1)-paprs(i,Nheight(iz)+1)) )    ! /kg (masse colonne)
193     
194             tr_seri(i,k,it) = tr_seri(i,k,it)+deltatr(i,k,it)*pdtphys
195            end do
196           
197          end do
198         
199         endif  ! ig_volcan!=0
200        end do
201        end do
202
203       end if  ! duree emission
204       
205c======================================================================
206c======================================================================
207
208      RETURN
209      END
Note: See TracBrowser for help on using the repository browser.