Ignore:
Timestamp:
Jul 28, 2025, 7:23:15 PM (7 days ago)
Author:
aborella
Message:

Merge with trunk r5789

Location:
LMDZ6/branches/contrails
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/contrails

  • LMDZ6/branches/contrails/libf/phylmd/phys_output_var_mod.f90

    r5618 r5791  
    105105  INTEGER, DIMENSION(nfiles), SAVE :: nnhorim
    106106  INTEGER, DIMENSION(nfiles), SAVE :: nhorim, nvertm
     107  INTEGER, DIMENSION(nfiles), SAVE :: ncanaux  !FC
     108  !$OMP THREADPRIVATE(ncanaux)
    107109  INTEGER, DIMENSION(nfiles), SAVE :: nvertap, nvertbp, nvertAlt
    108110  REAL, DIMENSION(nfiles), SAVE                :: zoutm
     
    179181  !$OMP THREADPRIVATE(cloud_cover_sw, cloud_cover_sw_s2)
    180182
     183  ! Direct-beam shortwave into a horizontal plane
     184  REAL, SAVE, ALLOCATABLE :: ZFLUX_DIR(:,:), ZFLUX_DIR_CLEAR(:,:), &
     185         &     ZFLUX_DIR_s2(:,:), ZFLUX_DIR_CLEAR_s2(:,:)
     186  !$OMP THREADPRIVATE(ZFLUX_DIR, ZFLUX_DIR_CLEAR, ZFLUX_DIR_s2, ZFLUX_DIR_CLEAR_s2)
     187  REAL, SAVE, ALLOCATABLE :: ZFLUX_DIR_SUN(:), ZFLUX_DIR_SUN_s2(:)
     188  !$OMP THREADPRIVATE(ZFLUX_DIR_SUN, ZFLUX_DIR_SUN_s2)
     189
    181190CONTAINS
    182191
     
    252261    ALLOCATE(icc3dstra(klon, klev))
    253262
    254     ! cloud_cover_sw, cloud_cover_sw_s2 from Ecrad
     263! cloud_cover_sw, cloud_cover_sw_s2 from Ecrad
    255264    ALLOCATE(cloud_cover_sw(klon))
    256265    ALLOCATE(cloud_cover_sw_s2(klon))
     266    ALLOCATE(ZFLUX_DIR(klon,klev+1))
     267    ALLOCATE(ZFLUX_DIR_CLEAR(klon,klev+1))
     268    ALLOCATE(ZFLUX_DIR_s2(klon,klev+1))
     269    ALLOCATE(ZFLUX_DIR_CLEAR_s2(klon,klev+1))
     270    ALLOCATE(ZFLUX_DIR_SUN(klon))
     271    ALLOCATE(ZFLUX_DIR_SUN_s2(klon))
    257272
    258273  END SUBROUTINE phys_output_var_init
     
    308323    !AI cloud_cover_sw, cloud_cover_sw_s2 from Ecrad
    309324    DEALLOCATE(cloud_cover_sw, cloud_cover_sw_s2)
     325    DEALLOCATE(ZFLUX_DIR, ZFLUX_DIR_CLEAR, ZFLUX_DIR_s2, ZFLUX_DIR_CLEAR_s2)
     326    DEALLOCATE(ZFLUX_DIR_SUN, ZFLUX_DIR_SUN_s2)
    310327
    311328  END SUBROUTINE phys_output_var_end
Note: See TracChangeset for help on using the changeset viewer.