Changeset 5253


Ignore:
Timestamp:
Oct 22, 2024, 2:29:31 PM (3 hours ago)
Author:
abarral
Message:

Wrap uses of cpp key DUST

Location:
LMDZ6/trunk
Files:
1 added
7 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/trunk/libf/phylmd/Dust/read_surface.F90

    r5249 r5253  
    1010       USE mod_phys_lmdz_para
    1111       USE iophy
    12 !       USE netcdf
     12       USE netcdf, ONLY: nf90_get_var
    1313       IMPLICIT NONE
    1414
  • LMDZ6/trunk/libf/phylmd/Dust/read_vent.F90

    r5249 r5253  
    33  USE mod_grid_phy_lmdz
    44  USE mod_phys_lmdz_para
     5  USE netcdf, ONLY: nf90_get_var
    56   ! USE write_field_phy
    67  IMPLICIT NONE
  • LMDZ6/trunk/libf/phylmd/phys_output_ctrlout_mod.F90

    r5252 r5253  
    22472247       "inst(X)", "inst(X)", "inst(X)", "inst(X)", "inst(X)", "inst(X)", "inst(X)"  /))
    22482248
    2249 #ifdef CPP_Dust
    2250       INCLUDE 'spla_output_dat.h'
    2251 #endif
     2249   INCLUDE 'spla_output_dat.h'
    22522250
    22532251   type(ctrl_out), save:: o_delta_sst &
  • LMDZ6/trunk/libf/phylmd/physiq_mod.F90

    r5252 r5253  
    100100!
    101101!
    102 #ifdef CPP_Dust
    103     USE phytracr_spl_mod, ONLY: phytracr_spl, phytracr_spl_out_init
    104     USE phys_output_write_spl_mod
    105 #else
    106102    USE phytrac_mod, ONLY : phytrac_init, phytrac
    107103    USE phys_output_write_mod
    108 #endif
    109104
    110105
     
    118113    USE time_phylmdz_mod,    ONLY: annee_ref, day_ini, day_ref, start_time
    119114    USE vertical_layers_mod, ONLY: aps, bps, ap, bp
    120     USE lmdz_cppkeys_wrapper, ONLY: CPPKEY_INCA, CPPKEY_REPROBUS, CPPKEY_STRATAER
     115    USE lmdz_cppkeys_wrapper, ONLY: CPPKEY_INCA, CPPKEY_REPROBUS, CPPKEY_STRATAER, CPPKEY_DUST
    121116
    122117#ifdef CPP_RRTM
     
    15091504       ok_water_mass_fixer=.FALSE.  ! OB: by default we do not apply the mass fixer
    15101505       CALL getin_p('ok_water_mass_fixer',ok_water_mass_fixer)
    1511 #ifdef CPP_Dust
    1512        IF (iflag_phytrac.EQ.0) THEN 
     1506IF (CPPKEY_DUST) THEN
     1507       IF (iflag_phytrac.EQ.0) THEN
    15131508         WRITE(lunout,*) 'In order to run with SPLA, iflag_phytrac will be forced to 1'
    15141509         iflag_phytrac = 1
    15151510       ENDIF
    1516 #endif
     1511END IF
    15171512       nvm_lmdz = 13
    15181513       CALL getin_p('NVM',nvm_lmdz)
     
    18881883END IF
    18891884
    1890 #ifdef CPP_Dust
     1885IF (CPPKEY_DUST) THEN
    18911886       ! Quand on utilise SPLA, on force iflag_phytrac=1
    18921887       CALL phytracr_spl_out_init()
     
    18971892                                ptconvth, d_t, qx, d_qx, d_tr_dyn, zmasse,      &
    18981893                                flag_aerosol, flag_aerosol_strat, ok_cdnc)
    1899 #else
     1894ELSE
    19001895       ! phys_output_write écrit des variables traceurs seulement si iflag_phytrac == 1
    19011896       ! donc seulement dans ce cas on doit appeler phytrac_init()
     
    19091904                              ptconvth, d_u, d_t, qx, d_qx, zmasse,           &
    19101905                              flag_aerosol, flag_aerosol_strat, ok_cdnc, t, u1, v1)
    1911 #endif
     1906END IF
    19121907
    19131908
     
    42614256                   !--new aerosol properties SW and LW
    42624257                   !
    4263 #ifdef CPP_Dust
     4258IF (CPPKEY_DUST) THEN
    42644259                   !--SPL aerosol model
    42654260                   CALL splaerosol_optic_rrtm( ok_alw, pplay, paprs, t_seri, rhcl, &
     
    42674262                        tau_aero_sw_rrtm, piz_aero_sw_rrtm, cg_aero_sw_rrtm,  &
    42684263                        tausum_aero, tau3d_aero)
    4269 #else
     4264ELSE
    42704265                   !--climatologies or INCA aerosols
    42714266                   CALL readaerosol_optic_rrtm( debut, aerosol_couple, ok_alw, ok_volcan, &
     
    42754270                        tau_aero_sw_rrtm, piz_aero_sw_rrtm, cg_aero_sw_rrtm,  &
    42764271                        tausum_aero, drytausum_aero, tau3d_aero)
    4277 #endif
     4272END IF
    42784273
    42794274                   IF (flag_aerosol .EQ. 7) THEN
     
    53155310    ENDIF
    53165311
    5317 #ifdef CPP_Dust
     5312IF (CPPKEY_DUST) THEN
    53185313    !  Avec SPLA, iflag_phytrac est forcé =1
    53195314    CALL       phytracr_spl ( debut,lafin , jD_cur,jH_cur,iflag_con,       &  ! I
     
    53325327                      d_tr_dyn,tr_seri)
    53335328
    5334 #else
     5329ELSE
    53355330    IF (iflag_phytrac == 1 ) THEN
    53365331      CALL phytrac ( &
     
    53735368    ENDIF    ! (iflag_phytrac=1)
    53745369
    5375 #endif
     5370END IF
    53765371    !ENDIF    ! (iflag_phytrac=1)
    53775372
     
    57325727    !On effectue les sorties:
    57335728
    5734 #ifdef CPP_Dust
     5729IF (CPPKEY_DUST) THEN
    57355730  CALL phys_output_write_spl(itap, pdtphys, paprs, pphis,  &
    57365731       pplay, lmax_th, aerosol_couple,                 &
     
    57395734       ptconvth, d_t, qx, d_qx, d_tr_dyn, zmasse,      &
    57405735       flag_aerosol, flag_aerosol_strat, ok_cdnc)
    5741 #else
     5736ELSE
    57425737    CALL phys_output_write(itap, pdtphys, paprs, pphis,  &
    57435738         pplay, lmax_th, aerosol_couple,                 &
     
    57465741         ptconvth, d_u, d_t, qx, d_qx, zmasse,           &
    57475742         flag_aerosol, flag_aerosol_strat, ok_cdnc,t, u1, v1)
    5748 #endif
     5743END IF
    57495744
    57505745#ifndef CPP_XIOS
  • LMDZ6/trunk/libf/phylmdiso/physiq_mod.F90

    r5252 r5253  
    100100!
    101101!
    102 #ifdef CPP_Dust
    103102    USE phytracr_spl_mod, ONLY: phytracr_spl, phytracr_spl_out_init
    104103    USE phys_output_write_spl_mod
    105 #else
    106104    USE phytrac_mod, ONLY : phytrac_init, phytrac
    107105    USE phys_output_write_mod
    108 #endif
    109106
    110107
     
    433430       reffclwc, cldnvi, lcc3d, lcc3dcon, lcc3dstra, icc3dcon, icc3dstra
    434431       USE output_physiqex_mod, ONLY: output_physiqex
    435        USE lmdz_cppkeys_wrapper, ONLY: CPPKEY_INCA, CPPKEY_REPROBUS, CPPKEY_STRATAER
     432       USE lmdz_cppkeys_wrapper, ONLY: CPPKEY_INCA, CPPKEY_REPROBUS, CPPKEY_STRATAER, CPPKEY_DUST
    436433
    437434
     
    16431640       iflag_phytrac = 1 ! by default we do want to call phytrac
    16441641       CALL getin_p('iflag_phytrac',iflag_phytrac)
    1645 #ifdef CPP_Dust
    1646        IF (iflag_phytrac.EQ.0) THEN 
     1642IF (CPPKEY_DUST) THEN
     1643       IF (iflag_phytrac.EQ.0) THEN
    16471644         WRITE(lunout,*) 'In order to run with SPLA, iflag_phytrac will be forced to 1'
    16481645         iflag_phytrac = 1
    16491646       ENDIF
    1650 #endif
     1647END IF
    16511648       nvm_lmdz = 13
    16521649       CALL getin_p('NVM',nvm_lmdz)
     
    20472044!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
    20482045
    2049 #ifdef CPP_Dust
     2046IF (CPPKEY_DUST) THEN
    20502047       ! Quand on utilise SPLA, on force iflag_phytrac=1
    20512048       CALL phytracr_spl_out_init()
     
    20562053                                ptconvth, d_t, qx, d_qx, d_tr_dyn, zmasse,      &
    20572054                                flag_aerosol, flag_aerosol_strat, ok_cdnc)
    2058 #else
     2055ELSE
    20592056       ! phys_output_write écrit des variables traceurs seulement si iflag_phytrac == 1
    20602057       ! donc seulement dans ce cas on doit appeler phytrac_init()
     
    20682065                              ptconvth, d_u, d_t, qx, d_qx, zmasse,           &
    20692066                              flag_aerosol, flag_aerosol_strat, ok_cdnc, t, u1, v1)
    2070 #endif
     2067END IF
    20712068
    20722069
     
    57185715                   !--new aerosol properties SW and LW
    57195716                   !
    5720 #ifdef CPP_Dust
     5717IF (CPPKEY_DUST) THEN
    57215718                   !--SPL aerosol model
    57225719                   CALL splaerosol_optic_rrtm( ok_alw, pplay, paprs, t_seri, rhcl, &
     
    57245721                        tau_aero_sw_rrtm, piz_aero_sw_rrtm, cg_aero_sw_rrtm,  &
    57255722                        tausum_aero, tau3d_aero)
    5726 #else
     5723ELSE
    57275724                   !--climatologies or INCA aerosols
    57285725                   CALL readaerosol_optic_rrtm( debut, aerosol_couple, ok_alw, ok_volcan, &
     
    57325729                        tau_aero_sw_rrtm, piz_aero_sw_rrtm, cg_aero_sw_rrtm,  &
    57335730                        tausum_aero, drytausum_aero, tau3d_aero)
    5734 #endif
     5731END IF
    57355732
    57365733                   IF (flag_aerosol .EQ. 7) THEN
     
    69026899    ENDIF
    69036900
    6904 #ifdef CPP_Dust
     6901IF (CPPKEY_DUST) THEN
    69056902    !  Avec SPLA, iflag_phytrac est forcé =1
    69066903    CALL       phytracr_spl ( debut,lafin , jD_cur,jH_cur,iflag_con,       &  ! I
     
    69196916                      d_tr_dyn,tr_seri)
    69206917
    6921 #else
     6918ELSE
    69226919    IF (iflag_phytrac == 1 ) THEN
    69236920      CALL phytrac ( &
     
    69626959    ENDIF    ! (iflag_phytrac=1)
    69636960
    6964 #endif
     6961END IF
    69656962    !ENDIF    ! (iflag_phytrac=1)
    69666963
     
    73617358    !On effectue les sorties:
    73627359
    7363 #ifdef CPP_Dust
     7360IF (CPPKEY_DUST) THEN
    73647361  CALL phys_output_write_spl(itap, pdtphys, paprs, pphis,  &
    73657362       pplay, lmax_th, aerosol_couple,                 &
     
    73687365       ptconvth, d_t, qx, d_qx, d_tr_dyn, zmasse,      &
    73697366       flag_aerosol, flag_aerosol_strat, ok_cdnc)
    7370 #else
     7367ELSE
    73717368    CALL phys_output_write(itap, pdtphys, paprs, pphis,  &
    73727369         pplay, lmax_th, aerosol_couple,                 &
     
    73757372         ptconvth, d_u, d_t, qx, d_qx, zmasse,           &
    73767373         flag_aerosol, flag_aerosol_strat, ok_cdnc,t, u1, v1)
    7377 #endif
     7374END IF
    73787375
    73797376#ifndef CPP_XIOS
  • LMDZ6/trunk/makelmdz

    r5252 r5253  
    500500fi
    501501
    502 if [[ "$dust" == "true" ]]
    503 then
     502src_dirs="$src_dirs phy${physique}/Dust"
     503if [[ "$dust" == "true" ]]; then
    504504   CPP_KEY="$CPP_KEY CPP_Dust"
    505    src_dirs="$src_dirs phy${physique}/Dust"
    506505fi
    507506
  • LMDZ6/trunk/makelmdz_fcm

    r5252 r5253  
    488488fi
    489489
    490 if [[ "$dust" == "true" ]]
    491 then
     490DUST_PATH="$LIBFGCM/phy${physique}/Dust"
     491if [[ "$dust" == "true" ]]; then
    492492   CPP_KEY="$CPP_KEY CPP_Dust"
    493    DUST_PATH="$LIBFGCM/phy${physique}/Dust"
    494493fi
    495494
Note: See TracChangeset for help on using the changeset viewer.