Ignore:
Timestamp:
Oct 28, 2024, 1:11:48 PM (6 hours ago)
Author:
abarral
Message:

Turn iniprint.h clesphys.h into modules
Remove unused description.h

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/phylmd/phytrac_mod.f90

    r5274 r5282  
    5858    USE infotrac_phy, ONLY: nbtr, type_trac
    5959    USE tracco2i_mod, ONLY: tracco2i_init
    60    
     60
    6161    IMPLICIT NONE
    6262
     
    7575    !===============================================================================
    7676    !    -- Do specific treatment according to chemestry model or local LMDZ tracers
    77     !     
     77    !
    7878    !===============================================================================
    7979    !   -- CO2 interactif --
    8080    IF (ANY(type_trac == ['co2i','inco'])) CALL tracco2i_init()
    8181
    82        !   -- type_trac == 'co2i' ! PC 
     82       !   -- type_trac == 'co2i' ! PC
    8383       !   -- CO2 interactif --
    84        !   -- source is updated with FF and BB emissions 
    85        !   -- and net fluxes from ocean and orchidee 
     84       !   -- source is updated with FF and BB emissions
     85       !   -- and net fluxes from ocean and orchidee
    8686       !   -- sign convention : positive into the atmosphere
    8787
     
    105105       da,        phi,      mp,       upwd,           &
    106106       phi2,      d1a,      dam,      sij, wght_cvfd, &   ! RomP +RL
    107        wdtrainA,  wdtrainM, sigd,     clw, elij,      &   ! RomP 
     107       wdtrainA,  wdtrainM, sigd,     clw, elij,      &   ! RomP
    108108       evap,      ep,       epmlmMm,  eplaMm,         &   ! RomP
    109109       dnwd,      aerosol_couple,     flxmass_w,      &
     
    111111       rfname,                                        &
    112112       d_tr_dyn,                                      &   ! RomP
    113        tr_seri, init_source)         
     113       tr_seri, init_source)
    114114    !
    115115    !======================================================================
     
    163163          , RESTT, RALPW, RBETW, RGAMW, RALPS, RBETS, RGAMS            &
    164164          , RALPD, RBETD, RGAMD
     165    USE clesphys_mod_h
    165166IMPLICIT NONE
    166167
    167168
    168     INCLUDE "clesphys.h"
    169169    !==========================================================================
    170170    !                   -- ARGUMENT DESCRIPTION --
Note: See TracChangeset for help on using the changeset viewer.