Ignore:
Timestamp:
Apr 25, 2025, 2:21:02 PM (2 months ago)
Author:
amaison
Message:

Representation of heterogeneous continental subsurfaces with parameter or flux aggregation in the simplified surface model (bucket) for 1D case studies.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • TabularUnified LMDZ6/trunk/libf/phylmd/dyn1d/scm.f90

    r5490 r5627  
    88       clwcon, detr_therm, &
    99       qsol, fevap, z0m, z0h, agesno, &
     10       frac_tersrf, z0m_tersrf, ratio_z0m_z0h_tersrf, &
     11       albedo_tersrf, beta_tersrf, inertie_tersrf, &
     12       alpha_soil_tersrf, period_tersrf, hcond_tersrf, &
     13       tsurfi_tersrf, tsoili_tersrf, tsoil_depth, &
    1014       du_gwd_rando, du_gwd_front, entr_therm, f0, fm_therm, &
    1115       falb_dir, falb_dif, &
     
    178182      real :: fder(1),snsrf(1,nbsrf),qsurfsrf(1,nbsrf)
    179183      real :: tsoil(1,nsoilmx,nbsrf)
     184      ! AM
     185      REAL, ALLOCATABLE, DIMENSION(:,:) :: tsoil_ter_srf2 ! resized initial soil temperature on vertical levels (K)
     186      REAL, ALLOCATABLE, DIMENSION(:,:) :: tsoil_depths2  ! resized soil depth at which inititial temperature is given (m)
    180187
    181188!---------------------------------------------------------------------
     
    222229!                           <> 0, tendencies of forcing are not added
    223230      INTEGER :: flag_inhib_forcing = 0
    224 
     231      CHARACTER(len=80) :: abort_message
     232      CHARACTER(len=20) :: modname = 'scm'
    225233
    226234      print*,'VOUS ENTREZ DANS LE 1D FORMAT STANDARD'
     
    385393!     call init_phys_lmdz(1,1,llm,1,(/1/)) ! job now done via iniphysiq
    386394!     but we still need to initialize dimphy module (klon,klev,etc.)  here.
    387       call init_dimphy1D(1,llm)
     395      call init_dimphy1D(1,llm,nb_ter_srf,nb_tsoil_depths)
    388396      call suphel
    389397      call init_infotrac
     
    560568        agesno  = xagesno
    561569        tsoil(:,:,:)=tsurf
     570
     571        iflag_hetero_surf = 0
     572        CALL getin('iflag_hetero_surf',iflag_hetero_surf)
     573
     574        IF (iflag_hetero_surf .GT. 0) THEN
     575          PRINT*, 'scm iflag_hetero_surf', iflag_hetero_surf
     576          IF ((nbtersrf .LT. 2) .OR. (nbtersrf .GT. max_nbtersrf)) THEN
     577            abort_message='The number of continental sub-surfaces (nb_ter_srf) must be between 2 and 5'
     578            CALL abort_physic(modname,abort_message,1)
     579          ENDIF
     580          ! resized initial soil temperature on vertical levels and soil depth at which inititial temperature is given
     581          ALLOCATE(tsoil_ter_srf2(nbtsoildepths,nbtersrf))
     582          ALLOCATE(tsoil_depths2(nbtsoildepths,nbtersrf))
     583          tsoil_ter_srf2(:,:) = 0.
     584          tsoil_depths2(:,:) = 0.
     585          DO i=1, nbtersrf
     586            DO l=1, nbtsoildepths
     587              k = nbtsoildepths*(i-1)+l
     588              tsoil_ter_srf2(l,i) = tsoil_ter_srf(k)
     589              tsoil_depths2(l,i) = tsoil_depths(k)
     590            ENDDO
     591          ENDDO
     592          !
     593          DO i=1, nbtersrf
     594            frac_tersrf(:,i) = frac_ter_srf(i)                   ! fraction of land surface heterogeneity (-)
     595            z0m_tersrf(:,i) = rugos_ter_srf(i)                   ! roughness length for momentum of land sub-surfaces (m)
     596            ratio_z0m_z0h_tersrf(:,i) = ratio_z0m_z0h_ter_srf(i) ! ratio of heat to momentum roughness length of land sub-surfaces (-)
     597            albedo_tersrf(:,i) = albedo_ter_srf(i)               ! albedo of land sub-surfaces (-)
     598            beta_tersrf(:,i) = beta_ter_srf(i)                   ! evapotranspiration coef of land sub-surfaces (-)
     599            inertie_tersrf(:,i) = inertie_ter_srf(i)             ! soil thermal inertia of land sub-surfaces (J/m2/K/s1/2)
     600            hcond_tersrf(:,i) = hcond_ter_srf(i)                 ! soil heat conductivity (W/(m.K))
     601            tsurfi_tersrf(:,i) = tsurf_ter_srf(i)                ! initial surface temperature (K)
     602            DO l=1, nbtsoildepths
     603              tsoili_tersrf(:,l,i) = tsoil_ter_srf2(l,i)         ! initial soil temperature on vertical levels (K)
     604              tsoil_depth(:,l,i) = tsoil_depths2(l,i)
     605            ENDDO
     606          ENDDO
     607          alpha_soil_tersrf = alpha_soil_ter_srf               ! ratio between the thicknesses of 2 successive layers (-)
     608          period_tersrf = period_ter_srf                       ! temperature oscillation amplitude period
     609          !
     610          DEALLOCATE(tsoil_ter_srf2)
     611          DEALLOCATE(tsoil_depths2)
     612        ENDIF
     613
    562614!-----------------------------------------------------------------------
    563615        call pbl_surface_init(fder, snsrf, qsurfsrf, tsoil)
Note: See TracChangeset for help on using the changeset viewer.