Changeset 4826


Ignore:
Timestamp:
Feb 16, 2024, 12:42:21 PM (3 months ago)
Author:
jyg
Message:

New flag in alpale_th.F90: multiply_proba_notrig; default=.FALSE.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/phylmd/alpale_th.F90

    r4089 r4826  
    5353  INTEGER                                                    :: i
    5454  LOGICAL, SAVE                                              :: first = .TRUE.
     55  LOGICAL, SAVE                                              :: multiply_proba_notrig = .FALSE.
    5556  REAL, SAVE                                                 :: random_notrig_max=1.
    5657  REAL, SAVE                                                 :: cv_feed_area
     
    5960  REAL, DIMENSION(klon)                                      :: tau_trig
    6061!
     62    !$OMP THREADPRIVATE(multiply_proba_notrig)
    6163    !$OMP THREADPRIVATE(random_notrig_max)
    6264    !$OMP THREADPRIVATE(cv_feed_area)
     
    6567 REAL umexp  ! expression of (1.-exp(-x))/x valid for all x, especially when x->0
    6668 REAL x
     69!
    6770     CHARACTER (LEN=20) :: modname='alpale_th'
    6871     CHARACTER (LEN=80) :: abort_message
     
    8386!+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
    8487!
     88
     89    IF (first) THEN
     90      CALL getin_p('multiply_proba_notrig',multiply_proba_notrig)
     91      IF (iflag_clos_bl .LT. 3) THEN
     92         random_notrig_max=1.
     93         CALL getin_p('random_notrig_max',random_notrig_max)
     94      ELSEIF (iflag_clos_bl .EQ. 3) THEN  ! (iflag_clos_bl .LT. 3)
     95         cv_feed_area = 1.e10   ! m2
     96         CALL getin_p('cv_feed_area', cv_feed_area)
     97      ENDIF  !! (iflag_clos_bl .LT. 3)
     98      first=.FALSE.
     99    ENDIF
     100
    85101!!
    86102!!  The following 3 lines should be commented if one wants to activate the
     
    88104!! scheme.
    89105!!
    90              do i=1,klon
     106    IF (.NOT.multiply_proba_notrig) THEN
     107             DO i=1,klon
    91108                proba_notrig(i)=1.
    92              enddo
     109             ENDDO
     110    ENDIF  !! (.NOT.multiply_proba_notrig)
    93111!!
    94112!!
     
    99117!      Original code (Nicolas Rochetin)
    100118!     --------------------------------
    101 
    102     IF (first) THEN
    103        random_notrig_max=1.
    104        CALL getin_p('random_notrig_max',random_notrig_max)
    105        first=.FALSE.
    106     ENDIF
    107119          !cc nrlmd le 10/04/2012
    108120          !-----------Stochastic triggering-----------
     
    220232!      New code with Effective Lifting Power
    221233!     -------------------------------------
    222     IF (first) THEN
    223        cv_feed_area = 1.e10   ! m2
    224        CALL getin_p('cv_feed_area', cv_feed_area)
    225        first=.FALSE.
    226     ENDIF
    227234
    228235          !-----------Stochastic triggering-----------
Note: See TracChangeset for help on using the changeset viewer.