Ignore:
Timestamp:
Jul 22, 2024, 9:29:09 PM (4 months ago)
Author:
abarral
Message:

Replace most uses of CPP_DUST by the corresponding logical defined in lmdz_cppkeys_wrapper.F90
Convert several files from .F to .f90 to allow Dust to compile w/o rrtm/ecrad
Create lmdz_yoerad.f90
(lint) Remove "!" on otherwise empty line

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/Amaury_dev/libf/phylmd/macv2sp.F90

    r5082 r5099  
    11SUBROUTINE MACv2SP(pphis,pplay,paprs,xlon,xlat,tau_allaer,piz_allaer,cg_allaer)
    2   !
     2
    33  !--routine to read the MACv2SP plume and compute optical properties
    44  !--requires flag_aerosol = 7
     
    77  !--pre-ind aerosols (index=1) are not changed, present-day aerosols (index=2) are incremented
    88  !--uses model year so year_cur needs to be correct in the model simulation
    9   !
     9
    1010  !--aod_prof = AOD per layer
    1111  !--ssa_prof = SSA
    1212  !--asy_prof = asymetry parameter
    1313  !--dNovrN   = enhancement factor for CDNC
    14   !
     14
    1515  USE mo_simple_plumes, ONLY: sp_aop_profile
    1616  USE phys_cal_mod, ONLY : year_cur, day_cur, year_len
     
    1919  USE phys_local_var_mod, ONLY: t_seri, od443aer, od550aer, od865aer, ec550aer, dryod550aer, od550lt1aer, dNovrN
    2020  !!USE YOMCST, ONLY : RD, RG
    21   !
     21
    2222  IMPLICIT NONE
    23   !
     23
    2424  include "YOMCST.h"
    25   !
     25
    2626  REAL,DIMENSION(klon),INTENT(IN)        :: pphis   ! Geopotentiel de surface
    2727  REAL,DIMENSION(klon,klev),INTENT(IN)   :: pplay   ! pression pour le mileu de chaque couche (en Pa)
     
    2929  REAL,DIMENSION(klon),INTENT(IN)        :: xlat    ! latitudes pour chaque point
    3030  REAL,DIMENSION(klon),INTENT(IN)        :: xlon    ! longitudes pour chaque point
    31   !
     31
    3232  REAL, DIMENSION(klon,klev,2,nbands_sw_rrtm), INTENT(OUT) :: tau_allaer !  epaisseur optique aerosol
    3333  REAL, DIMENSION(klon,klev,2,nbands_sw_rrtm), INTENT(OUT) :: piz_allaer !  single scattering albedo aerosol
    3434  REAL, DIMENSION(klon,klev,2,nbands_sw_rrtm), INTENT(OUT) :: cg_allaer  !  asymmetry parameter aerosol
    35   !
     35
    3636  REAL,DIMENSION(klon,klev) :: aod_prof, ssa_prof, asy_prof
    3737  REAL,DIMENSION(klon,klev) :: z, dz
    3838  REAL,DIMENSION(klon)      :: oro, zrho, zt
    39   !
     39
    4040  INTEGER, PARAMETER :: nmon = 12
    41   !
     41
    4242  REAL, PARAMETER    :: l443 = 443.0, l550 = 550.0, l865 = 865.0 !--wavelengths in nm
    43   !
     43
    4444  INTEGER, PARAMETER :: Nwvmax=25
    4545  REAL, DIMENSION(0:Nwvmax), PARAMETER :: lambda=(/ 240.0, &  !--this one is for band 1
     
    4949                 1100.0, 1190.0, 1280.0, 1530.0, 1640.0,   &
    5050                 2130.0, 2380.0, 2910.0, 3420.0, 4000.0   /)
    51   !
     51
    5252  REAL, DIMENSION(1:Nwvmax-1), PARAMETER :: weight =(/    &   !--and the weights to be given to the bands
    5353                 0.01,  4.05,  9.51, 15.99, 26.07, 33.10, &   !--corresponding to a typical solar spectrum
     
    5555                42.22, 40.12, 32.70, 14.44, 19.48, 14.23, &
    5656                13.43, 16.42,  8.33,  0.95,  0.65,  2.76  /)
    57   !
     57
    5858  REAL :: zlambda, zweight
    5959  REAL :: year_fr
    60   !
     60
    6161  INTEGER band, i, k, Nwv
    62   !
     62
    6363  ! define the height and dheight arrays
    64   !
     64
    6565  oro(:)  = pphis(:)/RG                             ! surface height in m
    66   !
     66
    6767  DO k = 1, klev
    6868    zrho(:) = pplay(:,k)/t_seri(:,k)/RD                         ! air density in kg/m3
     
    7676    ENDIF
    7777  ENDDO
    78   !
     78
    7979  !--fractional year
    80   !
     80
    8181  year_fr = FLOAT(year_cur) + (FLOAT(day_cur)-0.5) / FLOAT(year_len)
    8282  IF (year_fr<1850.0.OR.year_fr>=2017.0) THEN
    8383     CALL abort_physic ('macv2sp','year not supported by plume model',1)
    8484  ENDIF
    85   !
     85
    8686  !--call to sp routine -- 443 nm
    87   !
     87
    8888  CALL sp_aop_profile                                    ( &
    8989       klev     ,klon ,l443 ,oro    ,xlon     ,xlat      , &
    9090       year_fr  ,z    ,dz   ,dNovrN ,aod_prof ,ssa_prof  , &
    9191       asy_prof )
    92   !
     92
    9393  !--AOD calculations for diagnostics
    9494  od443aer(:)= od443aer(:)+SUM(aod_prof(:,:),dim=2)
    95   !
     95
    9696  !--call to sp routine -- 550 nm
    97   !
     97
    9898  CALL sp_aop_profile                                    ( &
    9999       klev     ,klon ,l550 ,oro    ,xlon     ,xlat      , &
    100100       year_fr  ,z    ,dz   ,dNovrN ,aod_prof ,ssa_prof  , &
    101101       asy_prof )
    102   !
     102
    103103  !--AOD calculations for diagnostics
    104104  od550aer(:)=od550aer(:)+SUM(aod_prof(:,:),dim=2)
    105   !
     105
    106106  !--dry AOD calculation for diagnostics
    107107  dryod550aer(:)=dryod550aer(:)+od550aer(:)
    108   !
     108
    109109  !--fine-mode AOD calculation for diagnostics
    110110  od550lt1aer(:)=od550lt1aer(:)+od550aer(:)
    111   !
     111
    112112  !--extinction coefficient for diagnostic
    113113  ec550aer(:,:)=ec550aer(:,:)+aod_prof(:,:)/dz(:,:)
    114   !
     114
    115115  !--call to sp routine -- 865 nm
    116   !
     116
    117117  CALL sp_aop_profile                                    ( &
    118118       klev     ,klon ,l865 ,oro    ,xlon     ,xlat      , &
    119119       year_fr  ,z    ,dz   ,dNovrN ,aod_prof ,ssa_prof  , &
    120120       asy_prof )
    121   !
     121
    122122  !--AOD calculations for diagnostics
    123123  od865aer(:)=od865aer(:)+SUM(aod_prof(:,:),dim=2)
    124   !
     124
    125125  !--re-weighting of piz and cg arrays before adding the anthropogenic aerosols
    126126  !--index 2 = all natural + anthropogenic aerosols
    127127  piz_allaer(:,:,2,:)=piz_allaer(:,:,2,:)*tau_allaer(:,:,2,:)
    128128  cg_allaer(:,:,2,:) =cg_allaer(:,:,2,:)*piz_allaer(:,:,2,:)
    129   !
     129
    130130  !--now computing the same at many wavelengths to fill the model bands
    131   !
     131
    132132  DO Nwv=0,Nwvmax-1
    133133
     
    157157      band=6
    158158    ENDIF
    159     !
     159
    160160    CALL sp_aop_profile                                       ( &
    161161         klev     ,klon ,zlambda ,oro    ,xlon     ,xlat      , &
    162162         year_fr  ,z    ,dz      ,dNovrN ,aod_prof ,ssa_prof  , &
    163163         asy_prof )
    164     !
     164
    165165    !--adding up the quantities tau, piz*tau and cg*piz*tau
    166166    tau_allaer(:,:,2,band)=tau_allaer(:,:,2,band)+zweight*MAX(aod_prof(:,:),1.e-15)
    167167    piz_allaer(:,:,2,band)=piz_allaer(:,:,2,band)+zweight*MAX(aod_prof(:,:),1.e-15)*ssa_prof(:,:)
    168168    cg_allaer(:,:,2,band) =cg_allaer(:,:,2,band) +zweight*MAX(aod_prof(:,:),1.e-15)*ssa_prof(:,:)*asy_prof(:,:)
    169     !
     169
    170170  ENDDO
    171   !
     171
    172172  !--renpomalizing cg and piz now that MACv2SP increments have been added
    173173  cg_allaer(:,:,2,:) =cg_allaer(:,:,2,:) /piz_allaer(:,:,2,:)
    174174  piz_allaer(:,:,2,:)=piz_allaer(:,:,2,:)/tau_allaer(:,:,2,:)
    175   !
     175
    176176END SUBROUTINE MACv2SP
Note: See TracChangeset for help on using the changeset viewer.