Ignore:
Timestamp:
Jun 29, 2018, 12:31:11 PM (6 years ago)
Author:
Laurent Fairhead
Message:

First attempt at merging with trunk

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

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/DYNAMICO-conv

  • LMDZ6/branches/DYNAMICO-conv/libf/phylmd/rrtm/aeropt_5wv_rrtm.F90

    r2951 r3356  
    381381     ALLOCATE (aerosol_name(nb_aer))
    382382     aerosol_name(1) = id_CIDUSTM_phy
    383   ELSEIF (flag_aerosol .EQ. 6) THEN
     383  ELSEIF (flag_aerosol .EQ. 6 .OR. flag_aerosol .EQ. 7 ) THEN
    384384     nb_aer = 13
    385385     ALLOCATE (aerosol_name(nb_aer))
  • LMDZ6/branches/DYNAMICO-conv/libf/phylmd/rrtm/aeropt_6bands_rrtm.F90

    r2842 r3356  
    507507     ALLOCATE (aerosol_name(nb_aer))
    508508     aerosol_name(1) = id_CIDUSTM_phy
    509   ELSEIF (flag_aerosol .EQ. 6) THEN
     509  ELSEIF (flag_aerosol .EQ. 6 .OR. flag_aerosol .EQ. 7 ) THEN
    510510     nb_aer = 13
    511511     ALLOCATE (aerosol_name(nb_aer))
  • LMDZ6/branches/DYNAMICO-conv/libf/phylmd/rrtm/aeropt_lw_rrtm.F90

    • Property svn:executable deleted
    r2748 r3356  
    4646  IF (ok_alw) THEN                                   !--aerosol LW effects
    4747   !
    48    IF (flag_aerosol.EQ.5.OR.flag_aerosol.EQ.6) THEN  !-Dust
     48   IF (flag_aerosol.EQ.5.OR.flag_aerosol.EQ.6.OR.flag_aerosol.EQ.7) THEN  !-Dust
    4949    !
    5050    zdh(:,:)=pdel(:,:)/(RG*zrho(:,:))      ! m
  • LMDZ6/branches/DYNAMICO-conv/libf/phylmd/rrtm/readaerosol_optic_rrtm.F90

    r2953 r3356  
    173173     !
    174174     ! Read and interpolate sulfate
    175      IF ( flag_aerosol .EQ. 1 .OR. flag_aerosol .EQ. 6 ) THEN
     175     IF ( flag_aerosol .EQ. 1 .OR. flag_aerosol .EQ. 6 .OR. flag_aerosol .EQ. 7 ) THEN
    176176
    177177        CALL readaerosol_interp(id_ASSO4M_phy, itap, pdtphys, rjourvrai, debut, pplay, paprs, t_seri, sulfacc, sulfacc_pi,loadso4)
     
    182182
    183183     ! Read and interpolate bcsol and bcins
    184      IF ( flag_aerosol .EQ. 2 .OR. flag_aerosol .EQ. 6 ) THEN
     184     IF ( flag_aerosol .EQ. 2 .OR. flag_aerosol .EQ. 6 .OR. flag_aerosol .EQ. 7 ) THEN
    185185
    186186        ! Get bc aerosol distribution
     
    195195
    196196     ! Read and interpolate pomsol and pomins
    197      IF ( flag_aerosol .EQ. 3 .OR. flag_aerosol .EQ. 6 ) THEN
     197     IF ( flag_aerosol .EQ. 3 .OR. flag_aerosol .EQ. 6 .OR. flag_aerosol .EQ. 7 ) THEN
    198198
    199199        CALL readaerosol_interp(id_ASPOMM_phy, itap, pdtphys, rjourvrai, debut, pplay, paprs, t_seri, pomsol, pomsol_pi, load_tmp3)
     
    207207
    208208     ! Read and interpolate csssm, ssssm, assssm
    209      IF (flag_aerosol .EQ. 4 .OR. flag_aerosol .EQ. 6 ) THEN
     209     IF (flag_aerosol .EQ. 4 .OR. flag_aerosol .EQ. 6 .OR. flag_aerosol .EQ. 7 ) THEN
    210210
    211211        CALL readaerosol_interp(id_SSSSM_phy ,itap, pdtphys,rjourvrai, &
     
    224224
    225225     ! Read and interpolate cidustm
    226      IF (flag_aerosol .EQ. 5 .OR. flag_aerosol .EQ. 6 ) THEN
     226     IF (flag_aerosol .EQ. 5 .OR. flag_aerosol .EQ. 6 .OR. flag_aerosol .EQ. 7 ) THEN
    227227
    228228        CALL readaerosol_interp(id_CIDUSTM_phy, itap, pdtphys, rjourvrai, debut, pplay, paprs, t_seri, cidust, cidust_pi, loaddust)
     
    234234     !
    235235     ! Read and interpolate asno3m, csno3m, cino3m
    236      IF (flag_aerosol .EQ. 6) THEN
     236     IF (flag_aerosol .EQ. 6 .OR. flag_aerosol .EQ. 7 ) THEN
    237237
    238238        CALL readaerosol_interp(id_ASNO3M_phy, itap, pdtphys, rjourvrai, &
  • LMDZ6/branches/DYNAMICO-conv/libf/phylmd/rrtm/recmwf_aero.F90

    r2529 r3356  
    2424!--end
    2525 & PFLUX,PFLUC,&
    26  & PFSDN ,PFSUP , PFSCDN , PFSCUP,&
     26 & PFSDN ,PFSUP , PFSCDN , PFSCUP, PFSCCDN, PFSCCUP, PFLCCDN, PFLCCUP,&
    2727!--OB diagnostics
    2828 & PTOPSWADAERO,PSOLSWADAERO,&
     
    8282! ok_ade---input-L- apply the Aerosol Direct Effect or not?
    8383! ok_aie---input-L- apply the Aerosol Indirect Effect or not?
    84 ! flag_aerosol-input-I- aerosol flag from 0 to 6
     84! flag_aerosol-input-I- aerosol flag from 0 to 7
    8585! flag_aerosol_strat-input-I- use stratospheric aerosols flag (T/F)
    8686! PPIZA_NAT  : (KPROMA,KLEV,NSW); Single scattering albedo of natural aerosol
     
    110110! PFSCDN(KPROMA,KLEV+1)         ; SW clear sky flux down
    111111! PFSCUP(KPROMA,KLEV+1)         ; SW clear sky flux up
     112! PFSCCDN(KPROMA,KLEV+1)        ; SW clear sky clean (no aerosol) flux down
     113! PFSCCUP(KPROMA,KLEV+1)        ; SW clear sky clean (no aerosol) flux up
     114! PFLCCDN(KPROMA,KLEV+1)        ; LW clear sky clean (no aerosol) flux down
     115! PFLCCUP(KPROMA,KLEV+1)        ; LW clear sky clean (no aerosol) flux up
    112116
    113117
     
    152156USE YOERDI   , ONLY : RRAE   ,REPCLC    ,REPH2O
    153157USE YOMARPHY , ONLY : LRDUST
    154 USE phys_output_mod, ONLY : swaero_diag
     158USE phys_output_mod, ONLY : swaerofree_diag, swaero_diag
    155159
    156160!-----------------------------------------------------------------------
     
    241245REAL(KIND=JPRB)   ,INTENT(OUT)   :: PFSCDN(KPROMA,KLEV+1)  ! SW clear sky flux down
    242246REAL(KIND=JPRB)   ,INTENT(OUT)   :: PFSCUP(KPROMA,KLEV+1)  ! SW clear sky flux up
     247REAL(KIND=JPRB)   ,INTENT(OUT)   :: PFSCCDN(KPROMA,KLEV+1) ! SW clear sky clean (no aerosol) flux down
     248REAL(KIND=JPRB)   ,INTENT(OUT)   :: PFSCCUP(KPROMA,KLEV+1) ! SW clear sky clean (no aerosol) flux up
     249REAL(KIND=JPRB)   ,INTENT(OUT)   :: PFLCCDN(KPROMA,KLEV+1) ! LW clear sky clean (no aerosol) flux down
     250REAL(KIND=JPRB)   ,INTENT(OUT)   :: PFLCCUP(KPROMA,KLEV+1) ! LW clear sky clean (no aerosol) flux up
    243251
    244252!     ==== COMPUTED IN RADITE ===
     
    607615
    608616! case with no aerosols at all is also computed IF ACTIVEFEEDBACK_ACTIVE is false
    609 !IF (swaero_diag .OR. .not. AEROSOLFEEDBACK_ACTIVE .OR. flag_aerosol .EQ. 0 ) THEN   
    610 IF (.not. AEROSOLFEEDBACK_ACTIVE .OR. flag_aerosol .EQ. 0 ) THEN   
     617IF (.not. AEROSOLFEEDBACK_ACTIVE .OR. flag_aerosol .EQ. 0 .OR. swaerofree_diag) THEN   
    611618
    612619! ZERO aerosol effect
     
    775782ENDIF
    776783
     784IF (swaerofree_diag) THEN
     785! copy shortwave clear-sky clean (no aerosol) case
     786  PFSCCUP(:,:) =   ZFSUP0_AERO(:,:,5)
     787  PFSCCDN(:,:) =   ZFSDN0_AERO(:,:,5)
     788! copy longwave clear-sky clean (no aerosol) case
     789  PFLCCUP(:,:) =   LWUP0_AERO(:,:,5)
     790  PFLCCDN(:,:) =   LWDN0_AERO(:,:,5)
     791ENDIF
     792
    777793!OB- HERE CHECK WITH MP IF BOTTOM AND TOP INDICES ARE OK !!!!!!!!!!!!!!!!!!
    778794! net anthropogenic forcing direct and 1st indirect effect diagnostics
  • LMDZ6/branches/DYNAMICO-conv/libf/phylmd/rrtm/suecrad.F90

    r2627 r3356  
    681681!    CALL GSTATS(667,0)     MPL 2.12.08
    682682    IF( NPROC > 1 )THEN
    683       stop'Pas pret pour proc > 1'
     683      stop 'Pas pret pour proc > 1'
    684684!     CALL MPL_BROADCAST (RADGRID%NDGLG,MTAGRAD,JPIOMASTER,CDSTRING='SUECRAD:')
    685685    ENDIF
     
    689689    ENDIF
    690690    IF( NPROC > 1 )THEN
    691       stop'Pas pret pour proc > 1'
     691      stop 'Pas pret pour proc > 1'
    692692!     CALL MPL_BROADCAST (RADGRID%NRGRI(1:RADGRID%NDGLG),MTAGRAD,JPIOMASTER,CDSTRING='SUECRAD:')
    693693    ENDIF
     
    864864        WRITE(NULOUT,'("RADGRID,BEGIN")')
    865865        IF( MYPROC /= 1 )THEN
    866           stop'Pas pret pour proc > 1'
     866          stop 'Pas pret pour proc > 1'
    867867!         CALL MPL_SEND(RADGRID%NGPTOT,KDEST=NPRCIDS(1),KTAG=1,CDSTRING='SUECRAD.R')
    868868!         CALL MPL_SEND(ZLATX(1:RADGRID%NGPTOT),KDEST=NPRCIDS(1),KTAG=2,CDSTRING='SUECRAD.R')
     
    876876              ENDDO
    877877            ELSE
    878               stop'Pas pret pour proc > 1'
     878              stop 'Pas pret pour proc > 1'
    879879!             CALL MPL_RECV(IGPTOT,KSOURCE=NPRCIDS(JROC),KTAG=1,CDSTRING='SUECRAD.M')
    880880!             CALL MPL_RECV(ZLATX(1:IGPTOT),KSOURCE=NPRCIDS(JROC),KTAG=2,CDSTRING='SUECRAD.M')
     
    904904        WRITE(NULOUT,'("MODELGRID,BEGIN")')
    905905        IF( MYPROC /= 1 )THEN
    906           stop'Pas pret pour proc > 1'
     906          stop 'Pas pret pour proc > 1'
    907907!         CALL MPL_SEND(NGPTOT,KDEST=NPRCIDS(1),KTAG=1,CDSTRING='SUECRAD')
    908908!         CALL MPL_SEND(ZLATX(1:NGPTOT),KDEST=NPRCIDS(1),KTAG=2,CDSTRING='SUECRAD')
     
    917917              ENDDO
    918918            ELSE
    919               stop'Pas pret pour proc > 1'
     919              stop 'Pas pret pour proc > 1'
    920920!             CALL MPL_RECV(IGPTOT,KSOURCE=NPRCIDS(JROC),KTAG=1,CDSTRING='SUECRAD')
    921921!             CALL MPL_RECV(ZLATX(1:IGPTOT),KSOURCE=NPRCIDS(JROC),KTAG=2,CDSTRING='SUECRAD')
     
    11661166        IWIDE(10)=NAROB1
    11671167        IF( MYPROC /= 1 )THEN
    1168           stop'Pas pret pour proc > 1'
     1168          stop 'Pas pret pour proc > 1'
    11691169!         CALL MPL_SEND(IWIDE(1:10),KDEST=NPRCIDS(1),KTAG=1,CDSTRING='SUECRAD.W')
    11701170        ENDIF
     
    11721172          DO JROC=1,NPROC
    11731173            IF( JROC /= MYPROC )THEN
    1174               stop'Pas pret pour proc > 1'
     1174              stop 'Pas pret pour proc > 1'
    11751175!             CALL MPL_RECV(IWIDE(1:10),KSOURCE=NPRCIDS(JROC),KTAG=1,CDSTRING='SUECRAD.W')
    11761176            ENDIF
  • LMDZ6/branches/DYNAMICO-conv/libf/phylmd/rrtm/susw15.F90

    r2010 r3356  
    5858
    5959IMPLICIT NONE
    60 REAL(KIND=JPRB)   :: ZPDH2O=0.8_JPRB
    61 REAL(KIND=JPRB)   :: ZPDUMG=0.75_JPRB
    62 REAL(KIND=JPRB)   :: ZPRH2O=30000._JPRB
    63 REAL(KIND=JPRB)   :: ZPRUMG=30000._JPRB
     60REAL(KIND=JPRB),SAVE   :: ZPDH2O=0.8_JPRB
     61REAL(KIND=JPRB),SAVE   :: ZPDUMG=0.75_JPRB
     62REAL(KIND=JPRB),SAVE   :: ZPRH2O=30000._JPRB
     63REAL(KIND=JPRB),SAVE   :: ZPRUMG=30000._JPRB
    6464
    6565!$OMP THREADPRIVATE(zpdh2o,zpdumg,zprh2o,zprumg)
Note: See TracChangeset for help on using the changeset viewer.