Ignore:
Timestamp:
Jul 22, 2024, 9:29:09 PM (4 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/phylmd/alpale_th.F90

    r5082 r5099  
    1 !
     1
    22! $Id$
    3 !
     3
    44SUBROUTINE alpale_th ( dtime, lmax_th, t_seri, cell_area,  &
    55                       cin, s2, n2, strig,  &
     
    2020  USE ioipsl_getin_p_mod, ONLY : getin_p
    2121  USE print_control_mod, ONLY: mydebug=>debug , lunout, prt_level
    22 !
     22
    2323  IMPLICIT NONE
    2424
     
    5959  REAL, DIMENSION(klon)                                      :: ale_bl_ref
    6060  REAL, DIMENSION(klon)                                      :: tau_trig
    61 !
     61
    6262    !$OMP THREADPRIVATE(multiply_proba_notrig)
    6363    !$OMP THREADPRIVATE(random_notrig_max)
    6464    !$OMP THREADPRIVATE(cv_feed_area)
    6565    !$OMP THREADPRIVATE(first)
    66 !
     66
    6767 REAL umexp  ! expression of (1.-exp(-x))/x valid for all x, especially when x->0
    6868 REAL x
    69 !
     69
    7070     CHARACTER (LEN=20) :: modname='alpale_th'
    7171     CHARACTER (LEN=80) :: abort_message
     
    7575!!!            (1.-max(sign(1.,x-1.e-3),0.))*(-0.5*x*(1.-x/3.*(1.-0.25*x))) !!! bug introduced by mistake  (jyg)
    7676!!!            (1.-max(sign(1.,x-1.e-3),0.))*(1.-0.5*x*(1.-x/3.*(1.-0.25*x)))  !!! initial correct formula (jyg)
    77 !
     77
    7878!+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
    7979!  JYG, 20160513 : Introduction of the Effective Lifting Power (ELP), which
     
    8383! zero. It is activated by iflag_clos_bl = 3.
    8484!   The ELP values are stored in the ALP_bl variable.
    85 !   
     85
    8686!+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
    87 !
    8887
    8988    IF (first) THEN
     
    122121  IF (iflag_clos_bl < 3) THEN
    123122!---------------------------------------
    124 !
     123
    125124!      Original code (Nicolas Rochetin)
    126125!     --------------------------------
     
    128127          !-----------Stochastic triggering-----------
    129128          if (iflag_trig_bl>=1) then
    130              !
     129
    131130             IF (prt_level >= 10) THEN
    132131                WRITE(lunout,*)'cin, ale_bl_stat, alp_bl, alp_bl_stat ', &
     
    146145                endif
    147146             enddo
    148              !
     147
    149148             IF (prt_level >= 10) THEN
    150149                WRITE(lunout,*)'random_notrig, tau_trig ', &
     
    202201             ENDIF
    203202
    204              !
    205203             IF (prt_level >= 10) THEN
    206204                WRITE(lunout,*)'proba_notrig, ale_bl_trig ', &
     
    233231          endif !(iflag_clos_bl)
    234232
    235 !
    236233!---------------------------------------
    237234  ELSEIF (iflag_clos_bl == 3) THEN  ! (iflag_clos_bl .LT. 3)
    238235!---------------------------------------
    239 !
     236
    240237!      New code with Effective Lifting Power
    241238!     -------------------------------------
     
    243240          !-----------Stochastic triggering-----------
    244241     if (iflag_trig_bl>=1) then
    245         !
     242
    246243        IF (prt_level >= 10) THEN
    247244           WRITE(lunout,*)'cin, ale_bl_stat, alp_bl_stat ', &
     
    272269           endif
    273270        enddo
    274         !
     271
    275272        IF (prt_level >= 10) THEN
    276273           WRITE(lunout,*)'random_notrig, tau_trig ', &
     
    308305         enddo
    309306
    310         !
    311307        IF (prt_level >= 10) THEN
    312308           WRITE(lunout,*)'proba_notrig, ale_bl_trig ', &
     
    326322
    327323          !cc fin nrlmd le 10/04/2012
    328 !
     324
    329325          !IM/FH: 2011/02/23
    330326          ! Couplage Thermiques/Emanuel seulement si T<0
Note: See TracChangeset for help on using the changeset viewer.