Ignore:
Timestamp:
May 9, 2019 9:48:32 AM (5 years ago)
Author:
suehring
Message:

In a nested child domain, distinguish between soil moisture and temperature initialization in case the parent domain is initialized via the dynamic input file; in the offline nesting, add a safety factor for the calculation of bulk Richardson number in order to avoid division by zero which can potentially happen if 3D buildings are located directly at the lateral model boundaries

File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/land_surface_model_mod.f90

    r3943 r3964  
    2525! -----------------
    2626! $Id$
     27! In a nested child domain, distinguish between soil moisture and temperature
     28! initialization from parent via dynamic input file. Further, initialize soil
     29! moisture/temperature from dynamic input file only when initialization via
     30! 'inifor' is desired.
     31!
     32! 3943 2019-05-02 09:50:41Z maronga
    2733! Removed extra blank character
    2834!
     
    26362642       IMPLICIT NONE
    26372643
    2638        LOGICAL      ::  init_soil_from_parent   !< flag controlling initialization of soil in child domains
     2644       LOGICAL      ::  init_msoil_from_parent   !< flag controlling initialization of soil moisture in nested child domains
     2645       LOGICAL      ::  init_tsoil_from_parent   !< flag controlling initialization of soil temperature in nested child domains
    26392646
    26402647       INTEGER(iwp) ::  i                       !< running index
     
    43564363       IF (  TRIM( initializing_actions ) /= 'read_restart_data' )  THEN
    43574364!
    4358 !--       Read soil properties from dynamic input file
    4359           CALL netcdf_data_input_init_lsm
     4365!--       Read soil properties from dynamic input file.
     4366          IF ( INDEX( initializing_actions, 'inifor' ) /= 0 )                  &
     4367             CALL netcdf_data_input_init_lsm
    43604368!
    43614369!--       In case no dynamic input is available for a child domain but root
     
    43634371!--       properties can lead to significant discrepancies in the atmospheric
    43644372!--       surface forcing. For this reason, the child domain
    4365 !--       is initialized with mean soil profiles from the root domain.         
    4366           init_soil_from_parent = .FALSE.
     4373!--       is initialized with mean soil profiles from the root domain, even if
     4374!--       no initialization with inifor is set.
     4375          init_tsoil_from_parent = .FALSE.
     4376          init_msoil_from_parent = .FALSE.
    43674377          IF ( nested_run )  THEN
    43684378#if defined( __parallel )
    4369              CALL MPI_ALLREDUCE( init_3d%from_file_tsoil  .OR.                 &
    4370                                  init_3d%from_file_msoil,                      &
    4371                                  init_soil_from_parent,                        &
     4379             CALL MPI_ALLREDUCE( init_3d%from_file_tsoil,                      &
     4380                                 init_tsoil_from_parent,                       &
     4381                                 1, MPI_LOGICAL, MPI_LOR, MPI_COMM_WORLD, ierr )
     4382             CALL MPI_ALLREDUCE( init_3d%from_file_msoil,                      &
     4383                                 init_msoil_from_parent,                       &
    43724384                                 1, MPI_LOGICAL, MPI_LOR, MPI_COMM_WORLD, ierr )
    43734385#endif
     
    44074419!--       transfer soil mean profiles from the root-parent domain onto all
    44084420!--       child domains.
    4409           IF ( init_soil_from_parent )  THEN
     4421          IF ( init_msoil_from_parent )  THEN
    44104422!
    44114423!--          Child domains will be only initialized with horizontally
     
    44344446                DEALLOCATE( pr_soil_init )
    44354447             ENDIF
     4448          ENDIF
     4449          IF ( init_tsoil_from_parent )  THEN
    44364450             IF ( init_3d%from_file_tsoil  .AND.  init_3d%lod_tsoil == 2 )  THEN
    44374451                ALLOCATE( pr_soil_init(0:init_3d%nzs-1) )
     
    44554469
    44564470             ENDIF
    4457 
    4458 #if defined( __parallel )
     4471          ENDIF
     4472          IF ( init_msoil_from_parent  .OR.  init_tsoil_from_parent )  THEN
    44594473!
    44604474!--          Distribute soil grid information on file from root to all childs.
    44614475!--          Only process with rank 0 sends the information.
     4476#if defined( __parallel )
    44624477             CALL MPI_BCAST( init_3d%nzs,    1,                                &
    44634478                             MPI_INTEGER, 0, MPI_COMM_WORLD, ierr )
     4479#endif
    44644480
    44654481             IF ( .NOT.  ALLOCATED( init_3d%z_soil ) )                         &
    44664482                ALLOCATE( init_3d%z_soil(1:init_3d%nzs) )
    4467 
     4483#if defined( __parallel )
    44684484             CALL MPI_BCAST( init_3d%z_soil, SIZE(init_3d%z_soil),             &
    44694485                             MPI_REAL, 0, MPI_COMM_WORLD, ierr )
    44704486#endif
    4471 !
    4472 !--          ALLOCATE arrays on child domains and set control attributes.
    4473 !--          Note, 1d soil profiles are allocated even though soil information
    4474 !--          is already read from dynamic file in one child domain.
    4475 !--          This case, however, data is not used for further initialization
    4476 !--          since the LoD=2.
     4487          ENDIF
     4488!
     4489!--       ALLOCATE arrays on child domains and set control attributes.
     4490!--       Note, 1d soil profiles are allocated even though soil information
     4491!--       is already read from dynamic file in one child domain.
     4492!--       This case, however, data is not used for further initialization
     4493!--       since the LoD=2.
     4494          IF ( init_msoil_from_parent )  THEN
    44774495             IF ( .NOT. ALLOCATED( init_3d%msoil_1d ) )  THEN
    44784496                ALLOCATE( init_3d%msoil_1d(0:init_3d%nzs-1) )
     
    44804498                init_3d%from_file_msoil = .TRUE.
    44814499             ENDIF
     4500          ENDIF
     4501          IF ( init_tsoil_from_parent )  THEN
    44824502             IF ( .NOT. ALLOCATED( init_3d%tsoil_1d ) )  THEN
    44834503                ALLOCATE( init_3d%tsoil_1d(0:init_3d%nzs-1) )
     
    44854505                init_3d%from_file_tsoil = .TRUE.
    44864506             ENDIF
    4487 
    4488 
     4507          ENDIF
     4508!
     4509!--       Distribute soil profiles from root to all childs
     4510          IF ( init_msoil_from_parent )  THEN
    44894511#if defined( __parallel )
    4490 !
    4491 !--          Distribute soil profiles from root to all childs
    44924512             CALL MPI_BCAST( init_3d%msoil_1d, SIZE(init_3d%msoil_1d),         &
    44934513                             MPI_REAL, 0, MPI_COMM_WORLD, ierr )
     4514#endif
     4515                   
     4516          ENDIF
     4517          IF ( init_tsoil_from_parent )  THEN
     4518#if defined( __parallel )
    44944519             CALL MPI_BCAST( init_3d%tsoil_1d, SIZE(init_3d%tsoil_1d),         &
    44954520                             MPI_REAL, 0, MPI_COMM_WORLD, ierr )
    44964521#endif
    4497 
    44984522          ENDIF
    44994523!
Note: See TracChangeset for help on using the changeset viewer.