Changeset 5833 for LMDZ6/trunk/libf/phylmd/alpale_th.f90
- Timestamp:
- Sep 24, 2025, 3:12:42 PM (2 months ago)
- File:
-
- 1 edited
-
LMDZ6/trunk/libf/phylmd/alpale_th.f90 (modified) (5 diffs)
Legend:
- Unmodified
- Added
- Removed
-
LMDZ6/trunk/libf/phylmd/alpale_th.f90
r5390 r5833 2 2 ! $Id$ 3 3 ! 4 !$gpum horizontal klon 5 MODULE alpale_th_mod 6 PRIVATE 7 8 LOGICAL, SAVE :: first = .TRUE. 9 !$OMP THREADPRIVATE(first) 10 LOGICAL, SAVE :: multiply_proba_notrig = .FALSE. 11 !$OMP THREADPRIVATE(multiply_proba_notrig) 12 REAL, SAVE :: random_notrig_max=1. 13 !$OMP THREADPRIVATE(random_notrig_max) 14 REAL, SAVE :: cv_feed_area 15 !$OMP THREADPRIVATE(cv_feed_area) 16 17 PUBLIC alpale_th, alpale_th_first 18 19 CONTAINS 20 21 SUBROUTINE alpale_th_first() 22 23 USE alpale_mod, ONLY: iflag_clos_bl 24 USE ioipsl_getin_p_mod, ONLY : getin_p 25 26 IMPLICIT NONE 27 28 IF (first) THEN 29 CALL getin_p('multiply_proba_notrig',multiply_proba_notrig) 30 IF (iflag_clos_bl .LT. 3) THEN 31 random_notrig_max=1. 32 CALL getin_p('random_notrig_max',random_notrig_max) 33 ELSEIF (iflag_clos_bl .EQ. 3) THEN ! (iflag_clos_bl .LT. 3) 34 cv_feed_area = 1.e10 ! m2 35 CALL getin_p('cv_feed_area', cv_feed_area) 36 ENDIF !! (iflag_clos_bl .LT. 3) 37 first = .FALSE. 38 ENDIF 39 40 END SUBROUTINE alpale_th_first 41 4 42 SUBROUTINE alpale_th ( dtime, lmax_th, t_seri, cell_area, & 5 43 cin, s2, n2, strig, & … … 18 56 19 57 USE dimphy 20 USE ioipsl_getin_p_mod, ONLY : getin_p21 58 USE print_control_mod, ONLY: mydebug=>debug , lunout, prt_level 22 USE alpale_mod 59 USE alpale_mod, ONLY: iflag_clos_bl, iflag_coupl, iflag_trig_bl, s_trig, tau_trig_deep, tau_trig_shallow 23 60 IMPLICIT NONE 24 61 … … 50 87 !---------------- 51 88 INTEGER :: i 52 LOGICAL, SAVE :: first = .TRUE.53 LOGICAL, SAVE :: multiply_proba_notrig = .FALSE.54 REAL, SAVE :: random_notrig_max=1.55 REAL, SAVE :: cv_feed_area56 89 REAL :: birth_number 57 90 REAL, DIMENSION(klon) :: ale_bl_ref 58 91 REAL, DIMENSION(klon) :: tau_trig 59 ! 60 !$OMP THREADPRIVATE(multiply_proba_notrig) 61 !$OMP THREADPRIVATE(random_notrig_max) 62 !$OMP THREADPRIVATE(cv_feed_area) 63 !$OMP THREADPRIVATE(first) 64 ! 92 65 93 REAL umexp ! expression of (1.-exp(-x))/x valid for all x, especially when x->0 66 94 REAL x 67 95 ! 68 CHARACTER (LEN=20) :: modname='alpale_th'96 CHARACTER (LEN=20), PARAMETER :: modname='alpale_th' 69 97 CHARACTER (LEN=80) :: abort_message 70 98 … … 84 112 !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++ 85 113 ! 86 87 IF (first) THEN88 CALL getin_p('multiply_proba_notrig',multiply_proba_notrig)89 IF (iflag_clos_bl .LT. 3) THEN90 random_notrig_max=1.91 CALL getin_p('random_notrig_max',random_notrig_max)92 ELSEIF (iflag_clos_bl .EQ. 3) THEN ! (iflag_clos_bl .LT. 3)93 cv_feed_area = 1.e10 ! m294 CALL getin_p('cv_feed_area', cv_feed_area)95 ENDIF !! (iflag_clos_bl .LT. 3)96 first=.FALSE.97 ENDIF98 114 99 115 !! … … 344 360 END SUBROUTINE alpale_th 345 361 362 END MODULE alpale_th_mod
Note: See TracChangeset
for help on using the changeset viewer.
