Ignore:
Timestamp:
Nov 5, 2018, 3:24:59 PM (6 years ago)
Author:
Laurent Fairhead
Message:

Undoing merge with trunk (r3356) to properly register Yann's latest modifications

Location:
LMDZ6/branches/DYNAMICO-conv
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/DYNAMICO-conv

  • LMDZ6/branches/DYNAMICO-conv/libf/phylmd/acama_gwd_rando_m.F90

    r3356 r3411  
    2020    use dimphy, only: klon, klev
    2121    use assert_m, only: assert
    22     USE ioipsl_getin_p_mod, ONLY : getin_p
    23     USE vertical_layers_mod, ONLY : presnivs
    24 
    2522    include "YOMCST.h"
    2623    include "clesphys.h"
     
    114111    REAL BV(KLON, KLEV + 1) ! Brunt Vaisala freq. (BVF) at 1/2 levels
    115112    REAL BVSEC ! Security to avoid negative BVF
    116 
    117     REAL, DIMENSION(klev+1) ::HREF
    118     LOGICAL, SAVE :: gwd_reproductibilite_mpiomp=.true.
    119     LOGICAL, SAVE :: firstcall = .TRUE.
    120   !$OMP THREADPRIVATE(firstcall,gwd_reproductibilite_mpiomp)
    121 
    122     CHARACTER (LEN=20) :: modname='flott_gwd_rando'
    123     CHARACTER (LEN=80) :: abort_message
    124 
    125 
    126 
    127   IF (firstcall) THEN
    128     ! Cle introduite pour resoudre un probleme de non reproductibilite
    129     ! Le but est de pouvoir tester de revenir a la version precedenete
    130     ! A eliminer rapidement
    131     CALL getin_p('gwd_reproductibilite_mpiomp',gwd_reproductibilite_mpiomp)
    132     IF (NW+4*(NA-1)+NA>=KLEV) THEN
    133        abort_message = 'NW+3*NA>=KLEV Probleme pour generation des ondes'
    134        CALL abort_physic (modname,abort_message,1)
    135     ENDIF
    136     firstcall=.false.
    137 !    CALL iophys_ini
    138   ENDIF
    139113
    140114    !-----------------------------------------------------------------
     
    231205    ! Launching altitude
    232206
    233     IF (gwd_reproductibilite_mpiomp) THEN
    234        ! Reprend la formule qui calcule PH en fonction de PP=play
    235        DO LL = 2, KLEV
    236           HREF(LL) = EXP((LOG(presnivs(LL)) + LOG(presnivs(LL - 1))) / 2.)
    237        end DO
    238        HREF(KLEV + 1) = 0.
    239        HREF(1) = 2. * presnivs(1) - HREF(2)
    240     ELSE
    241        HREF(1:KLEV)=PH(KLON/2,1:KLEV)
    242     ENDIF
    243 
    244207    LAUNCH=0
    245208    LTROP =0
    246209    DO LL = 1, KLEV
    247        IF (HREF(LL) / HREF(1) > XLAUNCH) LAUNCH = LL
     210       IF (PH(KLON / 2, LL) / PH(KLON / 2, 1) > XLAUNCH) LAUNCH = LL
    248211    ENDDO
    249212    DO LL = 1, KLEV
    250        IF (HREF(LL) / HREF(1) > XTROP) LTROP = LL
     213       IF (PH(KLON / 2, LL) / PH(KLON / 2, 1) > XTROP) LTROP = LL
    251214    ENDDO
    252     !LAUNCH=22 ; LTROP=33
    253 !   print*,'LAUNCH=',LAUNCH,'LTROP=',LTROP
    254 
    255215
    256216!   PRINT *,'LAUNCH IN ACAMARA:',LAUNCH
     
    333293
    334294    JW = 0
    335     DO JW = 1, NW
     295    DO JP = 1, NP
     296       DO JK = 1, NK
     297          DO JO = 1, NO
     298             JW = JW + 1
    336299             ! Angle
    337300             DO II = 1, KLON
     
    377340                ! RUW0(JW, II) = RUWFRT
    378341             ENDDO
     342          end DO
     343       end DO
    379344    end DO
    380345
Note: See TracChangeset for help on using the changeset viewer.