Ignore:
Timestamp:
Jul 23, 2024, 5:57:06 PM (2 months ago)
Author:
abarral
Message:

Replace 1DUTILS.h by module lmdz_1dutils.f90
Replace 1DConv.h by module lmdz_old_1dconv.f90 (it's only used by old_* files)
Convert *.F in DUST to *.f90

File:
1 moved

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/Amaury_dev/libf/phylmd/Dust/deposition.f90

    r5103 r5104  
    1 c Subroutine that estimates the Deposition velocities and the depostion
    2 C for the different tracers
    3       SUBROUTINE deposition(vdep_oce,vdep_sic,vdep_ter,vdep_lic,pctsrf,
    4      .                      zrho,zdz,pdtphys,RHcl,masse,t_seri,pplay,
    5      .                      paprs,lminmax,qmin,qmax,
    6      .                        his_ds,source_tr,tr_seri)
     1! Subroutine that estimates the Deposition velocities and the depostion
     2! for the different tracers
     3SUBROUTINE deposition(vdep_oce, vdep_sic, vdep_ter, vdep_lic, pctsrf, &
     4        zrho, zdz, pdtphys, RHcl, masse, t_seri, pplay, &
     5        paprs, lminmax, qmin, qmax, &
     6        his_ds, source_tr, tr_seri)
    77
    8       USE dimphy
    9       USE infotrac
    10       USE indice_sol_mod
     8  USE dimphy
     9  USE infotrac
     10  USE indice_sol_mod
    1111
    12       IMPLICIT NONE
     12  IMPLICIT NONE
    1313
    14       INCLUDE "dimensions.h"
    15       INCLUDE "chem.h"
    16       INCLUDE "YOMCST.h"
    17       INCLUDE "paramet.h"
     14  INCLUDE "dimensions.h"
     15  INCLUDE "chem.h"
     16  INCLUDE "YOMCST.h"
     17  INCLUDE "paramet.h"
    1818
    19 c----------------------------- INPUT -----------------------------------
    20       LOGICAL lminmax
    21       REAL qmin, qmax
    22       REAL vdep_oce(nbtr), vdep_sic(nbtr)
    23       REAL vdep_ter(nbtr), vdep_lic(nbtr)     
    24       REAL pctsrf(klon,nbsrf)
    25       REAL zrho(klon,klev)        !Density of air at mid points of Z (kg/m3)
    26       REAL zdz(klon,klev)       
    27       REAL pdtphys  ! pas d'integration pour la physique (seconde)
    28       REAL RHcl(klon,klev)  ! humidite relativen ciel clair
    29       REAL t_seri(klon,klev)  ! temperature
    30       REAL pplay(klon,klev)  ! pression pour le mileu de chaque couche (en Pa)
    31       REAL paprs(klon, klev+1)    !pressure at interface of layers Z (Pa)
    32       REAL masse(nbtr)
    33                                          
    34 c----------------------------- OUTPUT ----------------------------------
    35       REAL his_ds(klon,nbtr)                                         
    36       REAL source_tr(klon,nbtr)
    37       REAL tr_seri(klon, klev,nbtr) !conc of tracers
    38 c--------------------- INTERNAL VARIABLES ------------------------------     
    39       INTEGER i, it
    40       REAL vdep        !sed. velocity
     19  !----------------------------- INPUT -----------------------------------
     20  LOGICAL :: lminmax
     21  REAL :: qmin, qmax
     22  REAL :: vdep_oce(nbtr), vdep_sic(nbtr)
     23  REAL :: vdep_ter(nbtr), vdep_lic(nbtr)
     24  REAL :: pctsrf(klon, nbsrf)
     25  REAL :: zrho(klon, klev)        !Density of air at mid points of Z (kg/m3)
     26  REAL :: zdz(klon, klev)
     27  REAL :: pdtphys  ! pas d'integration pour la physique (seconde)
     28  REAL :: RHcl(klon, klev)  ! humidite relativen ciel clair
     29  REAL :: t_seri(klon, klev)  ! temperature
     30  REAL :: pplay(klon, klev)  ! pression pour le mileu de chaque couche (en Pa)
     31  REAL :: paprs(klon, klev + 1)    !pressure at interface of layers Z (Pa)
     32  REAL :: masse(nbtr)
    4133
    42       DO it=1, nbtr
    43       DO i=1, klon
    44           vdep=vdep_oce(it)*pctsrf(i,is_oce)+
    45      .         vdep_sic(it)*pctsrf(i,is_sic)+
    46      .         vdep_ter(it)*pctsrf(i,is_ter)+
    47      .         vdep_lic(it)*pctsrf(i,is_lic)
    48 c--Unit: molec/m2/s for it=1 to nbtr-3, mg/m2/s for it=nbtr-2 to nbtr
    49           source_tr(i,it)=source_tr(i,it)
    50      .                    -vdep*tr_seri(i,1,it)*zrho(i,1)/1.e2
    51           his_ds(i,it)=vdep*tr_seri(i,1,it)*zrho(i,1)/1.e2
    52      .                 /RNAVO*masse(it)*1.e3               ! mg/m2/s
    53       ENDDO
    54       ENDDO
    55 c
    56       END
     34  !----------------------------- OUTPUT ----------------------------------
     35  REAL :: his_ds(klon, nbtr)
     36  REAL :: source_tr(klon, nbtr)
     37  REAL :: tr_seri(klon, klev, nbtr) !conc of tracers
     38  !--------------------- INTERNAL VARIABLES ------------------------------
     39  INTEGER :: i, it
     40  REAL :: vdep        !sed. velocity
     41
     42  DO it = 1, nbtr
     43    DO i = 1, klon
     44      vdep = vdep_oce(it) * pctsrf(i, is_oce) + &
     45              vdep_sic(it) * pctsrf(i, is_sic) + &
     46              vdep_ter(it) * pctsrf(i, is_ter) + &
     47              vdep_lic(it) * pctsrf(i, is_lic)
     48      !--Unit: molec/m2/s for it=1 to nbtr-3, mg/m2/s for it=nbtr-2 to nbtr
     49      source_tr(i, it) = source_tr(i, it) &
     50              - vdep * tr_seri(i, 1, it) * zrho(i, 1) / 1.e2
     51      his_ds(i, it) = vdep * tr_seri(i, 1, it) * zrho(i, 1) / 1.e2 &
     52              / RNAVO * masse(it) * 1.e3               ! mg/m2/s
     53    ENDDO
     54  ENDDO
     55  !
     56END SUBROUTINE deposition
Note: See TracChangeset for help on using the changeset viewer.