Ignore:
Timestamp:
Jan 30, 2015, 2:57:13 PM (10 years ago)
Author:
Laurent Fairhead
Message:

Merged trunk changes -r2158:2186 into testing branch.

Location:
LMDZ5/branches/testing
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/branches/testing

  • LMDZ5/branches/testing/libf/phylmd/rrtm/readaerosol_optic_rrtm.F90

    r2160 r2187  
    8484  REAL, DIMENSION(klon,klev,naero_tot) :: m_allaer
    8585  REAL, DIMENSION(klon,klev,naero_tot) :: m_allaer_pi !RAF 
    86   !  REAL, DIMENSION(klon,naero_tot)      :: fractnat_allaer !RAF delete??
    87   character(len=8), dimension(nbtr) :: tracname
     86
    8887  integer :: id_ASBCM, id_ASPOMM, id_ASSO4M, id_ASMSAM, id_CSSO4M, id_CSMSAM, id_SSSSM
    8988  integer :: id_CSSSM, id_ASSSM, id_CIDUSTM, id_AIBCM, id_AIPOMM, id_ASNO3M, id_CSNO3M, id_CINO3M
     
    104103     !--convert to ug m-3 unit for consistency with offline fields
    105104     !
    106 #ifdef INCA
    107      call tracinca_name(tracname)
    108 #endif
    109 
    110105     do i=1,nbtr
    111         select case(trim(tracname(i)))
     106        select case(trim(solsym(i)))
    112107           case ("ASBCM")
    113108              id_ASBCM = i
  • LMDZ5/branches/testing/libf/phylmd/rrtm/readaerosolstrato_rrtm.F90

    r2160 r2187  
    4545    real, allocatable:: tauaerstrat_mois(:, :, :)
    4646    real, allocatable:: tauaerstrat_mois_glo(:, :)
    47     real, allocatable:: tauaerstrat_mois_glo_bands(:,:,:)
    4847
    4948    real, allocatable:: sum_tau_aer_strat(:)
     
    8180    IF (.not.ALLOCATED(sum_tau_aer_strat)) ALLOCATE(sum_tau_aer_strat(klon))
    8281
     82    IF (debut.OR.mth_cur.NE.mth_pre) THEN
     83
    8384    IF (is_mpi_root) THEN
    84 
    85     IF (debut.OR.mth_cur.NE.mth_pre) THEN
    8685
    8786    IF (nbands_sw_rrtm.NE.6) THEN
     
    130129    ALLOCATE(tauaerstrat_mois(n_lon, n_lat, n_lev))
    131130    ALLOCATE(tauaerstrat_mois_glo(klon_glo, n_lev))
    132     ALLOCATE(tauaerstrat_mois_glo_bands(klon_glo, n_lev,nbands_sw_rrtm))
    133131
    134132!--reading stratospheric AOD at 550 nm
     
    170168    DO k=1, klev
    171169    tausum_aero(:,wave,id_STRAT_phy)=tausum_aero(:,wave,id_STRAT_phy)+ &
    172     tau_aer_strat(:,k)*alpha_sw_strat_wave(wave)/alpha_sw_strat_wave(2)
     170       tau_aer_strat(:,k)*alpha_sw_strat_wave(wave)/alpha_sw_strat_wave(2)
    173171    ENDDO
    174172    ENDDO
Note: See TracChangeset for help on using the changeset viewer.