Changeset 3630


Ignore:
Timestamp:
Feb 10, 2020, 11:04:40 AM (4 years ago)
Author:
Laurent Fairhead
Message:

Parameter new_aod is not needed anymore as it is assumed to be true
all the time. This means that we cannot replay AR4 simulations with new
LMDZ sources (we probably couldn't anyway)
LF, OB

Location:
LMDZ6/trunk/libf
Files:
9 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/dynphy_lonlat/phylmd/etat0phys_netcdf.F90

    r3584 r3630  
    121121  LOGICAL :: flag_aer_feedback
    122122  LOGICAL :: flag_bc_internal_mixture
    123   LOGICAL :: new_aod
    124123  REAL    :: bl95_b0, bl95_b1
    125124  INTEGER :: read_climoz                        !--- Read ozone climatology
     
    143142                   chemistry_couple, flag_aerosol, flag_aerosol_strat,  &
    144143                   flag_aer_feedback,                                   &
    145                    new_aod, flag_bc_internal_mixture, bl95_b0, bl95_b1, &
     144                   flag_bc_internal_mixture, bl95_b0, bl95_b1, &
    146145                   read_climoz, alp_offset)
    147146  CALL phys_state_var_init(read_climoz)
  • LMDZ6/trunk/libf/phylmd/Dust/phys_output_write_spl_mod.F90

    r3332 r3630  
    8585  SUBROUTINE phys_output_write_spl(itap, pdtphys, paprs, pphis, &
    8686       pplay, lmax_th, aerosol_couple,         &
    87        ok_ade, ok_aie, ivap, new_aod, ok_sync, &
     87       ok_ade, ok_aie, ivap, ok_sync, &
    8888       ptconv, read_climoz, clevSTD, ptconvth, &
    8989       d_t, qx, d_qx, d_tr_dyn, zmasse, flag_aerosol, flag_aerosol_strat, ok_cdnc)
     
    405405    INTEGER, DIMENSION(klon) :: lmax_th
    406406    LOGICAL :: aerosol_couple, ok_sync
    407     LOGICAL :: ok_ade, ok_aie, new_aod
    408407    LOGICAL, DIMENSION(klon, klev) :: ptconv, ptconvth
    409408    REAL :: pdtphys
     
    994993!--OLIVIER
    995994!This is warranted by treating INCA aerosols as offline aerosols
    996 !       IF (new_aod .and. (.not. aerosol_couple)) THEN
    997        IF (new_aod) THEN
    998           IF (flag_aerosol.GT.0) THEN
    999              CALL histwrite_phy(o_od550aer, od550aer)
    1000              CALL histwrite_phy(o_od865aer, od865aer)
    1001              CALL histwrite_phy(o_absvisaer, absvisaer)
    1002              CALL histwrite_phy(o_od550lt1aer, od550lt1aer)
    1003              CALL histwrite_phy(o_sconcso4, sconcso4)
    1004              CALL histwrite_phy(o_sconcno3, sconcno3)
    1005              CALL histwrite_phy(o_sconcoa, sconcoa)
    1006              CALL histwrite_phy(o_sconcbc, sconcbc)
    1007              CALL histwrite_phy(o_sconcss, sconcss)
    1008              CALL histwrite_phy(o_sconcdust, sconcdust)
    1009              CALL histwrite_phy(o_concso4, concso4)
    1010              CALL histwrite_phy(o_concno3, concno3)
    1011              CALL histwrite_phy(o_concoa, concoa)
    1012              CALL histwrite_phy(o_concbc, concbc)
    1013              CALL histwrite_phy(o_concss, concss)
    1014              CALL histwrite_phy(o_concdust, concdust)
    1015              CALL histwrite_phy(o_loadso4, loadso4)
    1016              CALL histwrite_phy(o_loadoa, loadoa)
    1017              CALL histwrite_phy(o_loadbc, loadbc)
    1018              CALL histwrite_phy(o_loadss, loadss)
    1019              CALL histwrite_phy(o_loaddust, loaddust)
    1020              !--STRAT AER
    1021           ENDIF
    1022           IF (flag_aerosol.GT.0.OR.flag_aerosol_strat>=1) THEN
    1023 !             DO naero = 1, naero_spc
     995       IF (flag_aerosol.GT.0) THEN
     996          CALL histwrite_phy(o_od550aer, od550aer)
     997          CALL histwrite_phy(o_od865aer, od865aer)
     998          CALL histwrite_phy(o_absvisaer, absvisaer)
     999          CALL histwrite_phy(o_od550lt1aer, od550lt1aer)
     1000          CALL histwrite_phy(o_sconcso4, sconcso4)
     1001          CALL histwrite_phy(o_sconcno3, sconcno3)
     1002          CALL histwrite_phy(o_sconcoa, sconcoa)
     1003          CALL histwrite_phy(o_sconcbc, sconcbc)
     1004          CALL histwrite_phy(o_sconcss, sconcss)
     1005          CALL histwrite_phy(o_sconcdust, sconcdust)
     1006          CALL histwrite_phy(o_concso4, concso4)
     1007          CALL histwrite_phy(o_concno3, concno3)
     1008          CALL histwrite_phy(o_concoa, concoa)
     1009          CALL histwrite_phy(o_concbc, concbc)
     1010          CALL histwrite_phy(o_concss, concss)
     1011          CALL histwrite_phy(o_concdust, concdust)
     1012          CALL histwrite_phy(o_loadso4, loadso4)
     1013          CALL histwrite_phy(o_loadoa, loadoa)
     1014          CALL histwrite_phy(o_loadbc, loadbc)
     1015          CALL histwrite_phy(o_loadss, loadss)
     1016          CALL histwrite_phy(o_loaddust, loaddust)
     1017          !--STRAT AER
     1018       ENDIF
     1019       IF (flag_aerosol.GT.0.OR.flag_aerosol_strat>=1) THEN
     1020!          DO naero = 1, naero_spc
    10241021!--correction mini bug OB
    1025              DO naero = 1, naero_tot
    1026                 CALL histwrite_phy(o_tausumaero(naero), &
    1027                      tausum_aero(:,2,naero) )
    1028              ENDDO
    1029           ENDIF
    1030           IF (flag_aerosol_strat>=1) THEN
    1031              CALL histwrite_phy(o_tausumaero_lw, &
    1032                   tausum_aero(:,6,id_STRAT_phy) )
    1033           ENDIF
     1022          DO naero = 1, naero_tot
     1023             CALL histwrite_phy(o_tausumaero(naero), &
     1024                  tausum_aero(:,2,naero) )
     1025          ENDDO
     1026       ENDIF
     1027       IF (flag_aerosol_strat>=1) THEN
     1028          CALL histwrite_phy(o_tausumaero_lw, &
     1029               tausum_aero(:,6,id_STRAT_phy) )
    10341030       ENDIF
    10351031       IF (ok_ade) THEN
     
    10431039          CALL histwrite_phy(o_sollwad0, sollwad0_aero)
    10441040          !====MS forcing diagnostics
    1045           IF (new_aod) THEN
    1046              CALL histwrite_phy(o_swtoaas_nat, topsw_aero(:,1))
    1047              CALL histwrite_phy(o_swsrfas_nat, solsw_aero(:,1))
    1048              CALL histwrite_phy(o_swtoacs_nat, topsw0_aero(:,1))
    1049              CALL histwrite_phy(o_swsrfcs_nat, solsw0_aero(:,1))
    1050              !ant
    1051              CALL histwrite_phy(o_swtoaas_ant, topsw_aero(:,2))
    1052              CALL histwrite_phy(o_swsrfas_ant, solsw_aero(:,2))
    1053              CALL histwrite_phy(o_swtoacs_ant, topsw0_aero(:,2))
    1054              CALL histwrite_phy(o_swsrfcs_ant, solsw0_aero(:,2))
    1055              !cf
    1056              IF (.not. aerosol_couple) THEN
    1057                 CALL histwrite_phy(o_swtoacf_nat, topswcf_aero(:,1))
    1058                 CALL histwrite_phy(o_swsrfcf_nat, solswcf_aero(:,1))
    1059                 CALL histwrite_phy(o_swtoacf_ant, topswcf_aero(:,2))
    1060                 CALL histwrite_phy(o_swsrfcf_ant, solswcf_aero(:,2))
    1061                 CALL histwrite_phy(o_swtoacf_zero,topswcf_aero(:,3))
    1062                 CALL histwrite_phy(o_swsrfcf_zero,solswcf_aero(:,3))
    1063              ENDIF
    1064           ENDIF ! new_aod
     1041          CALL histwrite_phy(o_swtoaas_nat, topsw_aero(:,1))
     1042          CALL histwrite_phy(o_swsrfas_nat, solsw_aero(:,1))
     1043          CALL histwrite_phy(o_swtoacs_nat, topsw0_aero(:,1))
     1044          CALL histwrite_phy(o_swsrfcs_nat, solsw0_aero(:,1))
     1045          !ant
     1046          CALL histwrite_phy(o_swtoaas_ant, topsw_aero(:,2))
     1047          CALL histwrite_phy(o_swsrfas_ant, solsw_aero(:,2))
     1048          CALL histwrite_phy(o_swtoacs_ant, topsw0_aero(:,2))
     1049          CALL histwrite_phy(o_swsrfcs_ant, solsw0_aero(:,2))
     1050          !cf
     1051          IF (.not. aerosol_couple) THEN
     1052             CALL histwrite_phy(o_swtoacf_nat, topswcf_aero(:,1))
     1053             CALL histwrite_phy(o_swsrfcf_nat, solswcf_aero(:,1))
     1054             CALL histwrite_phy(o_swtoacf_ant, topswcf_aero(:,2))
     1055             CALL histwrite_phy(o_swsrfcf_ant, solswcf_aero(:,2))
     1056             CALL histwrite_phy(o_swtoacf_zero,topswcf_aero(:,3))
     1057             CALL histwrite_phy(o_swsrfcf_zero,solswcf_aero(:,3))
     1058          ENDIF
    10651059          !====MS forcing diagnostics
    10661060       ENDIF
  • LMDZ6/trunk/libf/phylmd/conf_phys_m.F90

    r3479 r3630  
    1818       iflag_ratqs,ratqsbas,ratqshaut,tau_ratqs, &
    1919       ok_ade, ok_aie, ok_alw, ok_cdnc, ok_volcan, aerosol_couple, chemistry_couple, &
    20        flag_aerosol, flag_aerosol_strat, flag_aer_feedback, new_aod, &
     20       flag_aerosol, flag_aerosol_strat, flag_aer_feedback, &
    2121       flag_bc_internal_mixture, bl95_b0, bl95_b1,&
    2222       read_climoz, &
     
    7878    LOGICAL              :: flag_aer_feedback
    7979    LOGICAL              :: flag_bc_internal_mixture
    80     LOGICAL              :: new_aod
    8180    REAL                 :: bl95_b0, bl95_b1
    8281    REAL                 :: fact_cldcon, facttemps,ratqsbas,ratqshaut,tau_ratqs
     
    10099    LOGICAL, SAVE       :: flag_aer_feedback_omp
    101100    LOGICAL, SAVE       :: flag_bc_internal_mixture_omp
    102     LOGICAL, SAVE       :: new_aod_omp
    103101    REAL,SAVE           :: bl95_b0_omp, bl95_b1_omp
    104102    REAL,SAVE           :: freq_ISCCP_omp, ecrit_ISCCP_omp
     
    453451    CALL getin('flag_bc_internal_mixture',flag_bc_internal_mixture_omp)
    454452
    455     ! Temporary variable for testing purpose!
    456     !Config Key  = new_aod
    457     !Config Desc = which calcul of aeropt
    458     !Config Def  = FALSE
    459     !Config Help = Used in physiq.F
    460     !
    461     new_aod_omp = .TRUE.
    462     CALL getin('new_aod',new_aod_omp)
    463 
    464453    !
    465454    !Config Key  = aer_type
     
    23282317    flag_aer_feedback=flag_aer_feedback_omp
    23292318    flag_bc_internal_mixture=flag_bc_internal_mixture_omp
    2330     new_aod=new_aod_omp
    23312319    aer_type = aer_type_omp
    23322320    bl95_b0 = bl95_b0_omp
     
    25032491       IF ( flag_aerosol .EQ. 0 ) THEN
    25042492          CALL abort_physic('conf_phys','flag_aerosol=0 not compatible avec ok_ade ou ok_aie=.TRUE.',1)
    2505        ENDIF
    2506        IF ( .NOT. new_aod .AND.  flag_aerosol .NE. 1) THEN
    2507           CALL abort_physic('conf_phys','new_aod=.FALSE. not compatible avec flag_aerosol=1',1)
    25082493       ENDIF
    25092494    ENDIF
     
    26762661    WRITE(lunout,*) ' flag_aerosol_strat= ', flag_aerosol_strat
    26772662    WRITE(lunout,*) ' flag_aer_feedback= ', flag_aer_feedback
    2678     WRITE(lunout,*) ' new_aod = ', new_aod
    26792663    WRITE(lunout,*) ' aer_type = ',aer_type
    26802664    WRITE(lunout,*) ' bl95_b0 = ',bl95_b0
  • LMDZ6/trunk/libf/phylmd/phys_output_mod.F90

    r3474 r3630  
    2929       ok_hf,ok_instan,ok_LES,ok_ade,ok_aie, read_climoz, &
    3030       phys_out_filestations, &
    31        new_aod, aerosol_couple, flag_aerosol_strat, &
     31       aerosol_couple, flag_aerosol_strat, &
    3232       pdtphys, paprs, pphis, pplay, lmax_th, ptconv, ptconvth, ivap, &
    3333       d_u, d_t, qx, d_qx, zmasse, ok_sync)   
     
    8585    LOGICAL                               :: ok_LES,ok_ade,ok_aie
    8686    INTEGER                               :: flag_aerosol_strat
    87     LOGICAL                               :: new_aod, aerosol_couple
     87    LOGICAL                               :: aerosol_couple
    8888    INTEGER, INTENT(IN)::  read_climoz ! read ozone climatology
    8989    !     Allowed values are 0, 1 and 2
  • LMDZ6/trunk/libf/phylmd/phys_output_write_mod.F90

    r3623 r3630  
    1717  SUBROUTINE phys_output_write(itap, pdtphys, paprs, pphis, &
    1818       pplay, lmax_th, aerosol_couple,         &
    19        ok_ade, ok_aie, ok_volcan, ivap, iliq, isol, new_aod, ok_sync, &
     19       ok_ade, ok_aie, ok_volcan, ivap, iliq, isol, ok_sync, &
    2020       ptconv, read_climoz, clevSTD, ptconvth, &
    2121       d_u, d_t, qx, d_qx, zmasse, flag_aerosol, flag_aerosol_strat, ok_cdnc)
     
    400400    INTEGER, DIMENSION(klon) :: lmax_th
    401401    LOGICAL :: aerosol_couple, ok_sync
    402     LOGICAL :: ok_ade, ok_aie, ok_volcan, new_aod
     402    LOGICAL :: ok_ade, ok_aie, ok_volcan
    403403    LOGICAL, DIMENSION(klon, klev) :: ptconv, ptconvth
    404404    REAL :: pdtphys
     
    13931393!--OLIVIER
    13941394!This is warranted by treating INCA aerosols as offline aerosols
    1395 !       IF (new_aod .and. (.not. aerosol_couple)) THEN
    1396        IF (new_aod) THEN
    1397           IF (flag_aerosol.GT.0) THEN
    1398              CALL histwrite_phy(o_od443aer, od443aer)
    1399              CALL histwrite_phy(o_od550aer, od550aer)
    1400              CALL histwrite_phy(o_od865aer, od865aer)
    1401              CALL histwrite_phy(o_abs550aer, abs550aer)
    1402              CALL histwrite_phy(o_od550lt1aer, od550lt1aer)
    1403              CALL histwrite_phy(o_sconcso4, sconcso4)
    1404              CALL histwrite_phy(o_sconcno3, sconcno3)
    1405              CALL histwrite_phy(o_sconcoa, sconcoa)
    1406              CALL histwrite_phy(o_sconcbc, sconcbc)
    1407              CALL histwrite_phy(o_sconcss, sconcss)
    1408              CALL histwrite_phy(o_sconcdust, sconcdust)
    1409              CALL histwrite_phy(o_concso4, concso4)
    1410              CALL histwrite_phy(o_concno3, concno3)
    1411              CALL histwrite_phy(o_concoa, concoa)
    1412              CALL histwrite_phy(o_concbc, concbc)
    1413              CALL histwrite_phy(o_concss, concss)
    1414              CALL histwrite_phy(o_concdust, concdust)
    1415              CALL histwrite_phy(o_loadso4, loadso4)
    1416              CALL histwrite_phy(o_loadoa, loadoa)
    1417              CALL histwrite_phy(o_loadbc, loadbc)
    1418              CALL histwrite_phy(o_loadss, loadss)
    1419              CALL histwrite_phy(o_loaddust, loaddust)
    1420              CALL histwrite_phy(o_loadno3, loadno3)
    1421              CALL histwrite_phy(o_dryod550aer, dryod550aer)
    1422              DO naero = 1, naero_tot-1
    1423                 CALL histwrite_phy(o_drytausumaero(naero),drytausum_aero(:,naero))
    1424              END DO
    1425           ENDIF
    1426           !--STRAT AER
    1427           IF (flag_aerosol.GT.0.OR.flag_aerosol_strat.GT.0) THEN
    1428              DO naero = 1, naero_tot
    1429                 CALL histwrite_phy(o_tausumaero(naero),tausum_aero(:,2,naero))
    1430              END DO
    1431           ENDIF
    1432           IF (flag_aerosol_strat.GT.0) THEN
    1433              CALL histwrite_phy(o_tausumaero_lw,tausum_aero(:,6,id_STRAT_phy))
    1434           ENDIF
     1395       IF (flag_aerosol.GT.0) THEN
     1396          CALL histwrite_phy(o_od443aer, od443aer)
     1397          CALL histwrite_phy(o_od550aer, od550aer)
     1398          CALL histwrite_phy(o_od865aer, od865aer)
     1399          CALL histwrite_phy(o_abs550aer, abs550aer)
     1400          CALL histwrite_phy(o_od550lt1aer, od550lt1aer)
     1401          CALL histwrite_phy(o_sconcso4, sconcso4)
     1402          CALL histwrite_phy(o_sconcno3, sconcno3)
     1403          CALL histwrite_phy(o_sconcoa, sconcoa)
     1404          CALL histwrite_phy(o_sconcbc, sconcbc)
     1405          CALL histwrite_phy(o_sconcss, sconcss)
     1406          CALL histwrite_phy(o_sconcdust, sconcdust)
     1407          CALL histwrite_phy(o_concso4, concso4)
     1408          CALL histwrite_phy(o_concno3, concno3)
     1409          CALL histwrite_phy(o_concoa, concoa)
     1410          CALL histwrite_phy(o_concbc, concbc)
     1411          CALL histwrite_phy(o_concss, concss)
     1412          CALL histwrite_phy(o_concdust, concdust)
     1413          CALL histwrite_phy(o_loadso4, loadso4)
     1414          CALL histwrite_phy(o_loadoa, loadoa)
     1415          CALL histwrite_phy(o_loadbc, loadbc)
     1416          CALL histwrite_phy(o_loadss, loadss)
     1417          CALL histwrite_phy(o_loaddust, loaddust)
     1418          CALL histwrite_phy(o_loadno3, loadno3)
     1419          CALL histwrite_phy(o_dryod550aer, dryod550aer)
     1420          DO naero = 1, naero_tot-1
     1421             CALL histwrite_phy(o_drytausumaero(naero),drytausum_aero(:,naero))
     1422          END DO
     1423       ENDIF
     1424       !--STRAT AER
     1425       IF (flag_aerosol.GT.0.OR.flag_aerosol_strat.GT.0) THEN
     1426          DO naero = 1, naero_tot
     1427             CALL histwrite_phy(o_tausumaero(naero),tausum_aero(:,2,naero))
     1428          END DO
     1429       ENDIF
     1430       IF (flag_aerosol_strat.GT.0) THEN
     1431          CALL histwrite_phy(o_tausumaero_lw,tausum_aero(:,6,id_STRAT_phy))
    14351432       ENDIF
    14361433
     
    15221519          CALL histwrite_phy(o_sollwad0, sollwad0_aero)
    15231520          !====MS forcing diagnostics
    1524           IF (new_aod) THEN
    15251521          !ym warning : topsw_aero, solsw_aero, topsw0_aero, solsw0_aero are not defined by model
    15261522          !ym => init to 0 in radlwsw_m.F90 ztopsw_aero, zsolsw_aero, ztopsw0_aero, zsolsw0_aero
    15271523
    1528              IF (vars_defined) zx_tmp_fi2d(:)=topsw_aero(:,1)*swradcorr(:)
    1529              CALL histwrite_phy(o_swtoaas_nat,zx_tmp_fi2d)
    1530              IF (vars_defined) zx_tmp_fi2d(:)=solsw_aero(:,1)*swradcorr(:)
    1531              CALL histwrite_phy(o_swsrfas_nat,zx_tmp_fi2d)
    1532              IF (vars_defined) zx_tmp_fi2d(:)=topsw0_aero(:,1)*swradcorr(:)
    1533              CALL histwrite_phy(o_swtoacs_nat,zx_tmp_fi2d)
    1534              IF (vars_defined) zx_tmp_fi2d(:)=solsw0_aero(:,1)*swradcorr(:)
    1535              CALL histwrite_phy(o_swsrfcs_nat,zx_tmp_fi2d)
    1536              !ant
    1537              IF (vars_defined) zx_tmp_fi2d(:)=topsw_aero(:,2)*swradcorr(:)
    1538              CALL histwrite_phy(o_swtoaas_ant,zx_tmp_fi2d)
    1539              IF (vars_defined) zx_tmp_fi2d(:)=solsw_aero(:,2)*swradcorr(:)
    1540              CALL histwrite_phy(o_swsrfas_ant,zx_tmp_fi2d)
    1541              IF (vars_defined) zx_tmp_fi2d(:)=topsw0_aero(:,2)*swradcorr(:)
    1542              CALL histwrite_phy(o_swtoacs_ant,zx_tmp_fi2d)
    1543              IF (vars_defined) zx_tmp_fi2d(:)=solsw0_aero(:,2)*swradcorr(:)
    1544              CALL histwrite_phy(o_swsrfcs_ant,zx_tmp_fi2d)
    1545              !cf
    1546              IF (.not. aerosol_couple) THEN
    1547                 IF (vars_defined) zx_tmp_fi2d(:)=topswcf_aero(:,1)*swradcorr(:)
    1548                 CALL histwrite_phy(o_swtoacf_nat,zx_tmp_fi2d)
    1549                 IF (vars_defined) zx_tmp_fi2d(:)=solswcf_aero(:,1)*swradcorr(:)
    1550                 CALL histwrite_phy(o_swsrfcf_nat,zx_tmp_fi2d)
    1551                 IF (vars_defined) zx_tmp_fi2d(:)=topswcf_aero(:,2)*swradcorr(:)
    1552                 CALL histwrite_phy(o_swtoacf_ant,zx_tmp_fi2d)
    1553                 IF (vars_defined) zx_tmp_fi2d(:)=solswcf_aero(:,2)*swradcorr(:)
    1554                 CALL histwrite_phy(o_swsrfcf_ant,zx_tmp_fi2d)
    1555                 IF (vars_defined) zx_tmp_fi2d(:)=topswcf_aero(:,3)*swradcorr(:)
    1556                 CALL histwrite_phy(o_swtoacf_zero,zx_tmp_fi2d)
    1557                 IF (vars_defined) zx_tmp_fi2d(:)=solswcf_aero(:,3)*swradcorr(:)
    1558                 CALL histwrite_phy(o_swsrfcf_zero,zx_tmp_fi2d)
    1559              ENDIF
    1560           ENDIF ! new_aod
     1524          IF (vars_defined) zx_tmp_fi2d(:)=topsw_aero(:,1)*swradcorr(:)
     1525          CALL histwrite_phy(o_swtoaas_nat,zx_tmp_fi2d)
     1526          IF (vars_defined) zx_tmp_fi2d(:)=solsw_aero(:,1)*swradcorr(:)
     1527          CALL histwrite_phy(o_swsrfas_nat,zx_tmp_fi2d)
     1528          IF (vars_defined) zx_tmp_fi2d(:)=topsw0_aero(:,1)*swradcorr(:)
     1529          CALL histwrite_phy(o_swtoacs_nat,zx_tmp_fi2d)
     1530          IF (vars_defined) zx_tmp_fi2d(:)=solsw0_aero(:,1)*swradcorr(:)
     1531          CALL histwrite_phy(o_swsrfcs_nat,zx_tmp_fi2d)
     1532          !ant
     1533          IF (vars_defined) zx_tmp_fi2d(:)=topsw_aero(:,2)*swradcorr(:)
     1534          CALL histwrite_phy(o_swtoaas_ant,zx_tmp_fi2d)
     1535          IF (vars_defined) zx_tmp_fi2d(:)=solsw_aero(:,2)*swradcorr(:)
     1536          CALL histwrite_phy(o_swsrfas_ant,zx_tmp_fi2d)
     1537          IF (vars_defined) zx_tmp_fi2d(:)=topsw0_aero(:,2)*swradcorr(:)
     1538          CALL histwrite_phy(o_swtoacs_ant,zx_tmp_fi2d)
     1539          IF (vars_defined) zx_tmp_fi2d(:)=solsw0_aero(:,2)*swradcorr(:)
     1540          CALL histwrite_phy(o_swsrfcs_ant,zx_tmp_fi2d)
     1541          !cf
     1542          IF (.not. aerosol_couple) THEN
     1543             IF (vars_defined) zx_tmp_fi2d(:)=topswcf_aero(:,1)*swradcorr(:)
     1544             CALL histwrite_phy(o_swtoacf_nat,zx_tmp_fi2d)
     1545             IF (vars_defined) zx_tmp_fi2d(:)=solswcf_aero(:,1)*swradcorr(:)
     1546             CALL histwrite_phy(o_swsrfcf_nat,zx_tmp_fi2d)
     1547             IF (vars_defined) zx_tmp_fi2d(:)=topswcf_aero(:,2)*swradcorr(:)
     1548             CALL histwrite_phy(o_swtoacf_ant,zx_tmp_fi2d)
     1549             IF (vars_defined) zx_tmp_fi2d(:)=solswcf_aero(:,2)*swradcorr(:)
     1550             CALL histwrite_phy(o_swsrfcf_ant,zx_tmp_fi2d)
     1551             IF (vars_defined) zx_tmp_fi2d(:)=topswcf_aero(:,3)*swradcorr(:)
     1552             CALL histwrite_phy(o_swtoacf_zero,zx_tmp_fi2d)
     1553             IF (vars_defined) zx_tmp_fi2d(:)=solswcf_aero(:,3)*swradcorr(:)
     1554             CALL histwrite_phy(o_swsrfcf_zero,zx_tmp_fi2d)
     1555          ENDIF
    15611556          !====MS forcing diagnostics
    15621557       ENDIF
  • LMDZ6/trunk/libf/phylmd/physiq_mod.F90

    r3613 r3630  
    10651065    LOGICAL, SAVE :: flag_bc_internal_mixture
    10661066    !$OMP THREADPRIVATE(flag_bc_internal_mixture)
    1067     LOGICAL, SAVE :: new_aod
    1068     !$OMP THREADPRIVATE(new_aod)
    10691067    !
    10701068    !--STRAT AEROSOL
     
    12491247            ok_ade, ok_aie, ok_alw, ok_cdnc, ok_volcan, aerosol_couple, &
    12501248            chemistry_couple, &
    1251             flag_aerosol, flag_aerosol_strat, flag_aer_feedback, new_aod, &
     1249            flag_aerosol, flag_aerosol_strat, flag_aer_feedback, &
    12521250            flag_bc_internal_mixture, bl95_b0, bl95_b1, &
    12531251                                ! nv flags pour la convection et les
     
    15751573            ok_hf,ok_instan,ok_LES,ok_ade,ok_aie, &
    15761574            read_climoz, phys_out_filestations, &
    1577             new_aod, aerosol_couple, &
     1575            aerosol_couple, &
    15781576            flag_aerosol_strat, pdtphys, paprs, pphis,  &
    15791577            pplay, lmax_th, ptconv, ptconvth, ivap,  &
     
    16881686       CALL phys_output_write(itap, pdtphys, paprs, pphis,                    &
    16891687                              pplay, lmax_th, aerosol_couple,                 &
    1690                               ok_ade, ok_aie, ok_volcan, ivap, iliq, isol, new_aod, ok_sync,&
     1688                              ok_ade, ok_aie, ok_volcan, ivap, iliq, isol, ok_sync,&
    16911689                              ptconv, read_climoz, clevSTD,                   &
    16921690                              ptconvth, d_u, d_t, qx, d_qx, zmasse,           &
     
    37713769                !
    37723770                CALL readaerosol_optic( &
    3773                      debut, new_aod, flag_aerosol, itap, jD_cur-jD_ref, &
     3771                     debut, flag_aerosol, itap, jD_cur-jD_ref, &
    37743772                     pdtphys, pplay, paprs, t_seri, rhcl, presnivs,  &
    37753773                     mass_solu_aero, mass_solu_aero_pi,  &
     
    37963794                   !--climatologies or INCA aerosols
    37973795                   CALL readaerosol_optic_rrtm( debut, aerosol_couple, ok_alw, ok_volcan, &
    3798                         new_aod, flag_aerosol, flag_bc_internal_mixture, itap, jD_cur-jD_ref, &
     3796                        flag_aerosol, flag_bc_internal_mixture, itap, jD_cur-jD_ref, &
    37993797                        pdtphys, pplay, paprs, t_seri, rhcl, presnivs,  &
    38003798                        tr_seri, mass_solu_aero, mass_solu_aero_pi,  &
     
    38133811                   !
    38143812                   CALL readaerosol_optic( &
    3815                         debut, new_aod, flag_aerosol, itap, jD_cur-jD_ref, &
     3813                        debut, flag_aerosol, itap, jD_cur-jD_ref, &
    38163814                        pdtphys, pplay, paprs, t_seri, rhcl, presnivs,  &
    38173815                        mass_solu_aero, mass_solu_aero_pi,  &
     
    41024100               ! Rajoute par OB pour RRTM
    41034101               tau_aero_lw_rrtm, &
    4104                cldtaupirad,new_aod, &
     4102               cldtaupirad, &
    41054103!              zqsat, flwcrad, fiwcrad, &
    41064104               zqsat, flwc, fiwc, &
     
    41894187                                ! Rajoute par OB pour RRTM
    41904188                     tau_aero_lw_rrtm, &
    4191                      cldtaupi,new_aod, &
     4189                     cldtaupi, &
    41924190!                    zqsat, flwcrad, fiwcrad, &
    41934191                     zqsat, flwc, fiwc, &
     
    50725070  CALL phys_output_write_spl(itap, pdtphys, paprs, pphis,  &
    50735071       pplay, lmax_th, aerosol_couple,                 &
    5074        ok_ade, ok_aie, ivap, new_aod, ok_sync,         &
     5072       ok_ade, ok_aie, ivap, ok_sync,         &
    50755073       ptconv, read_climoz, clevSTD,                   &
    50765074       ptconvth, d_t, qx, d_qx, d_tr_dyn, zmasse,      &
     
    50795077    CALL phys_output_write(itap, pdtphys, paprs, pphis,  &
    50805078         pplay, lmax_th, aerosol_couple,                 &
    5081          ok_ade, ok_aie, ok_volcan, ivap, iliq, isol, new_aod,      &
     5079         ok_ade, ok_aie, ok_volcan, ivap, iliq, isol,    &
    50825080         ok_sync, ptconv, read_climoz, clevSTD,          &
    50835081         ptconvth, d_u, d_t, qx, d_qx, zmasse,           &
  • LMDZ6/trunk/libf/phylmd/radlwsw_m.F90

    r3480 r3630  
    2121   tau_aero_sw_rrtm, piz_aero_sw_rrtm, cg_aero_sw_rrtm,& ! rajoute par OB pour RRTM
    2222   tau_aero_lw_rrtm, &                                   ! rajoute par C. Kleinschmitt pour RRTM
    23    cldtaupi, new_aod, &
     23   cldtaupi, &
    2424   qsat, flwc, fiwc, &
    2525   ref_liq, ref_ice, ref_liq_pi, ref_ice_pi, &
     
    222222
    223223  REAL,    INTENT(in)  :: cldtaupi(KLON,KLEV)                            ! cloud optical thickness for pre-industrial aerosol concentrations
    224   LOGICAL, INTENT(in)  :: new_aod                                        ! flag pour retrouver les resultats exacts de l'AR4 dans le cas ou l'on ne travaille qu'avec les sulfates
    225224  REAL,    INTENT(in)  :: qsat(klon,klev) ! Variable pour iflag_rrtm=1
    226225  REAL,    INTENT(in)  :: flwc(klon,klev) ! Variable pour iflag_rrtm=1
     
    652651!     print *,'Avant SW_LMDAR4: PSCT zrmu0 zfract',PSCT, zrmu0, zfract
    653652       ! daylight ozone, if we have it, for short wave
    654        IF (.NOT. new_aod) THEN
    655           ! use old version
    656           CALL SW_LMDAR4(PSCT, zrmu0, zfract,&
    657                PPMB, PDP, &
    658                PPSOL, PALBD, PALBP,&
    659                PTAVE, PWV, PQS, POZON(:, :, size(wo, 3)), PAER,&
    660                PCLDSW, PTAU, POMEGA, PCG,&
    661                zheat, zheat0,&
    662                zalbpla,ztopsw,zsolsw,ztopsw0,zsolsw0,&
    663                ZFSUP,ZFSDN,ZFSUP0,ZFSDN0,&
    664                tauaero(:,:,5,:), pizaero(:,:,5,:), cgaero(:,:,5,:),&
    665                PTAUA, POMEGAA,&
    666                ztopswadaero,zsolswadaero,&
    667                ztopswaiaero,zsolswaiaero,&
    668                ok_ade, ok_aie)
    669          
    670        ELSE ! new_aod=T         
    671           CALL SW_AEROAR4(PSCT, zrmu0, zfract,&
     653      CALL SW_AEROAR4(PSCT, zrmu0, zfract,&
    672654               PPMB, PDP,&
    673655               PPSOL, PALBD, PALBP,&
     
    686668               ztopswcf_aero,zsolswcf_aero, &
    687669               ok_ade, ok_aie, flag_aerosol,flag_aerosol_strat)
    688        ENDIF
    689670
    690671       ZSWFT0_i(:,:) = ZFSDN0(:,:)-ZFSUP0(:,:)
  • LMDZ6/trunk/libf/phylmd/readaerosol_optic.F90

    r2953 r3630  
    11! $Id$
    22!
    3 SUBROUTINE readaerosol_optic(debut, new_aod, flag_aerosol, itap, rjourvrai, &
     3SUBROUTINE readaerosol_optic(debut, flag_aerosol, itap, rjourvrai, &
    44     pdtphys, pplay, paprs, t_seri, rhcl, presnivs, &
    55     mass_solu_aero, mass_solu_aero_pi, &
     
    2222!****************************************************************************************
    2323  LOGICAL, INTENT(IN)                      :: debut
    24   LOGICAL, INTENT(IN)                      :: new_aod
    2524  INTEGER, INTENT(IN)                      :: flag_aerosol
    2625  INTEGER, INTENT(IN)                      :: itap
     
    189188  END DO
    190189
    191   IF (new_aod) THEN
    192 
    193190! RAF delete??     fractnat_allaer(:,:) = 0.
    194191! RAF fractnat_allaer -> m_allaer_pi
     
    206203          flag_aerosol, pplay, t_seri,   &
    207204          tausum_aero, tau3d_aero, presnivs)
    208   ELSE
    209 
    210      CALL aeropt(pplay, paprs, t_seri, sulfate, rhcl, &
    211           tau_aero(:,:,id_ASSO4M_phy,:), piz_aero(:,:,id_ASSO4M_phy,:), cg_aero(:,:,id_ASSO4M_phy,:), aerindex)
    212      
    213   END IF
    214205
    215206! Diagnostics calculation for CMIP5 protocol
  • LMDZ6/trunk/libf/phylmd/rrtm/readaerosol_optic_rrtm.F90

    r3480 r3630  
    22!
    33SUBROUTINE readaerosol_optic_rrtm(debut, aerosol_couple, ok_alw, ok_volcan, &
    4      new_aod, flag_aerosol, flag_bc_internal_mixture, itap, rjourvrai, &
     4     flag_aerosol, flag_bc_internal_mixture, itap, rjourvrai, &
    55     pdtphys, pplay, paprs, t_seri, rhcl, presnivs, &
    66     tr_seri, mass_solu_aero, mass_solu_aero_pi, &
     
    3333  LOGICAL, INTENT(IN)                      :: ok_alw
    3434  LOGICAL, INTENT(IN)                      :: ok_volcan
    35   LOGICAL, INTENT(IN)                      :: new_aod
    3635  INTEGER, INTENT(IN)                      :: flag_aerosol
    3736  LOGICAL, INTENT(IN)                      :: flag_bc_internal_mixture
Note: See TracChangeset for help on using the changeset viewer.