Changeset 3714 for trunk/LMDZ.VENUS


Ignore:
Timestamp:
Apr 4, 2025, 4:13:19 PM (3 months ago)
Author:
slebonnois
Message:

SL: small adjustment in radlwsw.F

Location:
trunk/LMDZ.VENUS/libf/phyvenus
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • TabularUnified trunk/LMDZ.VENUS/libf/phyvenus/phytrac_emiss.F

    r2464 r3714  
    3535      use dimphy
    3636      USE geometry_mod, only: cell_area
    37       USE chemparam_mod,only:M_tr
     37      USE chemparam_mod,only:M_tr,type_tr
    3838      USE mod_grid_phy_lmdz, ONLY: nbp_lon, nbp_lat
    3939      IMPLICIT none
     
    7070      real :: deltatr(klon,klev,nqtot)
    7171
    72 
    73 
    74 
    75       integer,parameter :: nblat=3,nblon=3,nbaire=3,nbflux=2,maxcell=16
     72c several identical tracers emitted at different places, with different
     73c fluxes, at the same time :
     74c same_tracer=.true. and various number of areas and fluxes
     75c      logical,parameter :: same_tracer=.true.
     76c      integer,parameter :: nblat=3,nblon=3,nbaire=3,nbflux=2,maxcell=16
     77c Otherwise, emission of one of the tracers only, in one area only
     78      logical,parameter :: same_tracer=.false.
     79      integer,parameter :: nblat=1,nblon=1,nbaire=1,nbflux=1
     80      integer,save :: iq_co2,iq_n2
     81
     82      integer,parameter :: maxcell=10000
    7683      integer,parameter :: Nheight=3 ! layer emission (150m)
    7784      integer,save :: Ncell(nbaire)
     
    8188      integer,save :: ig_zone(nblat,nblon,nbaire,nbflux,maxcell)
    8289      integer,save :: numcell(nblat,nblon,nbaire,nbflux)
    83        
    8490
    8591      INTEGER i, k, it
     
    102108
    103109        ALLOCATE(M_tr(nqtot))
    104         M_tr(:)=44.                ! CO2
     110        ALLOCATE(type_tr(nqtot))
     111        do i=1,nqtot
     112           if (tname(i)(1:3).eq.'co2') then   ! CO2
     113               M_tr(i)=44.
     114               iq_co2 =i
     115               type_tr(i)=1
     116           endif
     117           if (tname(i)(1:2).eq.'n2')  then   ! N2
     118               M_tr(i)=28.
     119               iq_n2 =i
     120               type_tr(i)=1
     121           endif
     122        enddo
    105123
    106124C=========================================================================
    107125c Caracteristiques des traceurs emis:
    108126C=========================================================================
     127
    109128
    110129c nombre total de traceur
     
    115134         endif
    116135                 
    117 
    118 
    119 
    120136c flux de CO2 (kg/s/m2)
    121          flux_surface_co2(1) = 5.*10.**-9.
    122          flux_surface_co2(2) = 5.*10.**-15.
     137c 4.5e-7 correspond a 1% (en masse) d une couche de 2E6 Pa en 500 jV
     138c donc avec 5E-7, on vide le N2 en 1000 jV
     139c         flux_surface_co2(1) = 5.E-5
     140         flux_surface_co2(1) = 0.
    123141
    124142c nombre de cellule pour le cote du carre d'aire
    125          Ncell(1)= 2
    126          Ncell(2)= 3
    127          Ncell(3)= 4
    128      
    129 
     143         Ncell(1)= 9999
    130144
    131145c localisation zone emission
    132          lat_zone(1) = 08.
    133          lat_zone(2) = -50.
    134          lat_zone(3) = 35.
    135          lon_zone(1) = -172.
    136          lon_zone(2) = -20.
    137          lon_zone(3) = 70.
    138 
     146         lat_zone(1) = 0.
     147         lon_zone(1) = 0.
    139148 
    140149         if ((nbp_lon*nbp_lat)==1) then ! running a 1D simulation
     
    153162            do iaire=1,nbaire
    154163
    155              if ((xlat(i).ge.lat_zone(ilat))
     164            if ( 
     165     &       (Ncell(iaire).ne.9999)
     166c emission on some areas only
     167     &      .and.((xlat(i).ge.lat_zone(ilat))
    156168     &      .and.((xlat(i)-Ncell(iaire)*deltalat)
    157169     &      .lt.lat_zone(ilat))
    158170     &      .and.(xlon(i).le.lon_zone(ilon))
    159171     &      .and.((xlon(i)+Ncell(iaire)*deltalon)
    160      &      .gt.lon_zone(ilon))) then
     172     &      .gt.lon_zone(ilon))) ) then
    161173
    162174              do iflux=1,nbflux
     
    178190          tr_seri(:,:,:)=0.
    179191
    180 
    181192           do i=1,klon
    182193            do k=1,klev
    183               tr_seri(i,k,:)=1.-28/43.44*max(min(0.035,
    184      &           0.035*(1.-log(paprs(i,k)/6.e6)/log(9.e6/6.e6))),0.)
     194c Profile for VeGa2
     195c              tr_seri(i,k,iq_n2) = M_tr(i_n2)/43.44*max(min(0.035,
     196c     &           0.035*(1.-log(paprs(i,k)/6.e6)/log(9.e6/6.e6))),0.)
     197c              tr_seri(i,k,iq_co2)= 1. - tr_seri(i,k,iq_n2)
     198
     199c Uniform initialization, yN2=3.5%, regular mean mol mass = 43.44 g/mol
     200              tr_seri(i,k,iq_n2) = 0.035*M_tr(iq_n2)/43.44
     201              tr_seri(i,k,iq_co2)= 1. - tr_seri(i,k,iq_n2)
    185202            end do
    186203           end do
     
    202219       flux(:,:)=0.
    203220
     221        if (same_tracer) then
    204222c emet les traceurs qui sont presents sur la grille
    205       do ilat  = 1,nblat
    206        do ilon  = 1,nblon
     223        do ilat  = 1,nblat
     224        do ilon  = 1,nblon
    207225        do iaire = 1,nbaire
    208          do iflux = 1,nbflux
     226        do iflux = 1,nbflux
    209227     
    210228              it=min( (ilat-1)*nblon*nbflux*nbaire+(iaire-1)*nbflux
    211229     &         +(ilon-1)*nbaire*nbflux+iflux , nqtot )   
    212230 
    213 
    214 c injection dans une seule cellule:
    215 c source en kg/kg/s
    216 c            deltatr(i,Nheight(iz),it) = so2_quantity/(86400.*Nemiss) ! kg/s
    217 c     $ *RG/( area_emiss(ilat,ilon)
    218 c     $      *(paprs(i,Nheight(iz))-paprs(i,Nheight(iz)+1)) )    ! /kg (masse cellule)
    219      
    220 c            tr_seri(i,Nheight(iz),it) = tr_seri(i,Nheight(iz),it)
    221 c     $      + deltatr(i,Nheight(iz),it)*pdtphys
    222 
    223 c injection dans toute la colonne (a faire):
     231         if (Ncell(iaire).ne.9999) then
     232c column injection
    224233          do ipos=1,maxcell
    225234 
     
    231240            do k=1,Nheight
    232241             deltatr(i,k,it) = flux_surface_co2(iflux) ! kg/s/m2
    233      $         *RG/(paprs(i,1)-paprs(i,Nheight+1))    ! /kg (masse colonne)
    234      
    235                tr_seri(i,k,it) = tr_seri(i,k,it)+deltatr(i,k,it)*pdtphys
     242     $         *RG/(paprs(i,1)-paprs(i,Nheight+1))    ! / (kg/m2) (masse colonne)
     243     
     244             tr_seri(i,k,it) = tr_seri(i,k,it)+deltatr(i,k,it)*pdtphys
    236245            end do
    237246
    238247           end if
    239248          end do
    240  
    241         end do
    242         end do
    243         end do
    244         end do
    245 
     249         endif
     250        end do
     251        end do
     252        end do
     253        end do
     254
     255        else  ! same_tracer=.false.
     256
     257c column injection !! with constant mass !!
     258          do i=1,nlon
     259 
     260             flux(i,iq_co2)=flux_surface_co2(1) 
     261             
     262            do k=1,Nheight
     263          deltatr(i,k,iq_co2) = min((1.-tr_seri(i,k,iq_co2))/pdtphys,
     264     $                                flux(i,iq_co2)) ! kg/s/m2
     265     $         *RG/(paprs(i,1)-paprs(i,Nheight+1))    ! / (kg/m2) (masse colonne)
     266             deltatr(i,k,iq_n2)  = -deltatr(i,k,iq_co2)
     267             tr_seri(i,k,iq_co2) = tr_seri(i,k,iq_co2)
     268     $                            +deltatr(i,k,iq_co2)*pdtphys
     269             tr_seri(i,k,iq_n2)  = tr_seri(i,k,iq_n2)
     270     $                            +deltatr(i,k,iq_n2)*pdtphys
     271            end do
     272
     273          end do
     274
     275        endif ! same_tracer
     276 
    246277       
    247278c======================================================================
    248279c======================================================================
    249280
    250    
    251      
    252 
    253      
    254281#ifdef CPP_XIOS     
    255        do it=1,nqtot
    256        CALL  send_xios_field("flux_"//tname(it),
    257      &                     flux(:,it))
    258       end do
     282!      do it=1,nqtot
     283!      CALL  send_xios_field("flux_"//tname(it),
     284!    &                     flux(:,it))
     285!     end do
    259286#endif
    260 
    261 
    262287
    263288      RETURN
  • TabularUnified trunk/LMDZ.VENUS/libf/phyvenus/radlwsw.F

    r2560 r3714  
    6262      INTEGER k, kk, i, j, band
    6363      integer,save :: i_sw
    64       integer,parameter :: subloop=100
     64      integer,save :: subloop
    6565
    6666      REAL   PPB(klev+1)
     
    101101
    102102      if (firstcall) then
     103
     104c s2: solar only 240 times per Vd if diurnal cycle
     105        if (cycle_diurne) then
     106            subloop = nbapp_rad/240
     107        else
     108            subloop = nbapp_rad  ! no diurnal cycle, once per Vd is enough
     109        endif
    103110
    104111c ---------- ksive --------------
Note: See TracChangeset for help on using the changeset viewer.