Ignore:
Timestamp:
Jul 22, 2024, 9:29:09 PM (2 months ago)
Author:
abarral
Message:

Replace most uses of CPP_DUST by the corresponding logical defined in lmdz_cppkeys_wrapper.F90
Convert several files from .F to .f90 to allow Dust to compile w/o rrtm/ecrad
Create lmdz_yoerad.f90
(lint) Remove "!" on otherwise empty line

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/Amaury_dev/libf/phylmdiso/add_phys_tend_mod.F90

    r5087 r5099  
    1 !
     1
    22! $Id$
    3 !
    4 !
     3
     4
    55MODULE add_phys_tend_mod
    66
     
    120120  RETURN
    121121END SUBROUTINE add_pbl_tend
    122 !
     122
    123123! $Id$
    124 !
     124
    125125SUBROUTINE add_phys_tend (zdu,zdv,zdt,zdq,zdql,zdqi,zdqbs,paprs,text, &
    126126                          abortphy,flag_inhib_tend, itap, diag_mode &
     
    175175INTEGER,                        INTENT(IN)    :: diag_mode       ! 0 -> normal effective mode
    176176                                                                 ! 1 -> only conservation stats are computed
    177 !
     177
    178178REAL, DIMENSION(klon,klev),     INTENT(INOUT) :: zdq
    179179#ifdef ISO
     
    204204REAL, DIMENSION(ntraciso,klon,klev)   :: sav_xtl_seri, sav_xts_seri, sav_xt_seri
    205205#endif
    206 !
     206
    207207INTEGER i, k,j, n
    208208INTEGER jadrs(klon*klev), jbad
     
    216216logical, save :: first=.true.
    217217!$OMP THREADPRIVATE(first)
    218 !
     218
    219219!======================================================================
    220220! Variables for energy conservation tests
    221221!======================================================================
    222 !
    223222
    224223! zh_col-------  total enthalpy of vertical air column
     
    234233! zqbs_col------  total mass of blowing snow (kg/m2)
    235234! zek_col------  total kinetic energy (kg/m2)
    236 !
     235
    237236REAL zairm(klon, klev) ! layer air mass (kg/m2)
    238237REAL zqw_col(klon,2)
     
    273272        first=.false.
    274273     endif
    275 !
     274
    276275!  print *,'add_phys_tend: paprs ',paprs
    277276! When in diagnostic mode, save initial values of out variables
     
    422421      ENDDO
    423422ENDIF
    424 !
     423
    425424!=====================================================================================
    426425! Impression, warning et correction en cas de probleme moins important
     
    531530#endif
    532531#endif
    533 !
    534532
    535533!IM ajout memes tests pour reverifier les jbad, jqbad beg
     
    572570      ENDDO
    573571ENDIF
    574 !
     572
    575573IF (jqbad > 0) THEN
    576574      DO j = 1, jqbad
     
    646644
    647645  end if ! end if (fl_ebil .GT. 0)
    648 !
     646
    649647! When in diagnostic mode, restore "out" variables to initial values.
    650648  IF (diag_mode == 1) THEN
     
    706704REAL, DIMENSION(nlon,nlev)      :: temp_n, qv_n, ql_n, qs_n, qbs_n
    707705
    708 
    709 !
    710706INTEGER k, n
    711707
     
    713709logical, save :: first=.true.
    714710!$OMP THREADPRIVATE(first)
    715 !
     711
    716712!======================================================================
    717713! Variables for energy conservation tests
    718714!======================================================================
    719 !
    720715
    721716! zh_col-------  total enthalpy of vertical air column
     
    730725! zqbs_col------  total mass of blowing snow (kg/m2)
    731726! zek_col------  total kinetic energy (kg/m2)
    732 !
     727
    733728REAL zairm(nlon, nlev) ! layer air mass (kg/m2)
    734729REAL zqw_col(nlon,2)
     
    754749        first=.false.
    755750     endif
    756 !
     751
    757752!  print *,'add_phys_tend: paprs ',paprs
    758753!======================================================================
     
    832827
    833828  end if ! end if (fl_ebil .GT. 0)
    834 !
    835829
    836830  RETURN
     
    978972  if ( abs(bilq_error) > bilq_seuil) bilq_ok=1
    979973  if ( abs(bilh_error) > bilh_seuil) bilh_ok=1
    980 !
     974
    981975! Print diagnostics
    982976! =================
Note: See TracChangeset for help on using the changeset viewer.