Ignore:
Timestamp:
Mar 27, 2018 3:52:42 PM (6 years ago)
Author:
suehring
Message:

Nesting in RANS-LES and RANS-RANS mode enabled; synthetic turbulence generator at all lateral boundaries in nesting or non-cyclic forcing mode; revised Inifor initialization in nesting mode

File:
1 edited

Legend:

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

    r2932 r2938  
    2525! -----------------
    2626! $Id$
     27! Initialization of soil moisture and temperature via Inifor-provided data also
     28! in nested child domains, even if no dynamic input file is available for
     29! child domain. 1D soil profiles are received from parent model. 
     30!
     31! 2936 2018-03-27 14:49:27Z suehring
    2732! renamed lsm_par to land_surface_parameters. Bugfix in message calls
    2833!
     
    23652370       USE control_parameters,                                                 &
    23662371           ONLY:  message_string
     2372
     2373       USE indices,                                                            &
     2374           ONLY:  nx, ny
     2375
     2376       USE pmc_interface,                                                      &
     2377           ONLY:  nested_run
    23672378   
    23682379       IMPLICIT NONE
     2380
     2381       LOGICAL      ::  init_soil_dynamically_in_child !< flag controlling initialization of soil in child domains
    23692382
    23702383       INTEGER(iwp) ::  i                       !< running index
     
    23842397
    23852398       REAL(wp), DIMENSION(:), ALLOCATABLE ::  bound, bound_root_fr  !< temporary arrays for storing index bounds
     2399       REAL(wp), DIMENSION(:), ALLOCATABLE ::  pr_soil_init !< temporary array used for averaging soil profiles
    23862400
    23872401!
     
    38943908       IF (  TRIM( initializing_actions ) /= 'read_restart_data' )  THEN
    38953909!
     3910!--       In case of nested runs, check if soil is initialized via dynamic
     3911!--       input file in root domain and distribute this information
     3912!--       to all embedded child domains. This case, soil moisture and
     3913!--       temperature will be initialized via root domain. 
     3914          init_soil_dynamically_in_child = .FALSE.
     3915          IF ( nested_run )  THEN
     3916#if defined( __parallel )
     3917             CALL MPI_ALLREDUCE( init_3d%from_file_tsoil  .OR.                 &
     3918                                 init_3d%from_file_msoil,                      &
     3919                                 init_soil_dynamically_in_child,               &
     3920                                 1, MPI_LOGICAL, MPI_LOR, MPI_COMM_WORLD, ierr )
     3921#endif
     3922          ENDIF
     3923
     3924!
    38963925!--       First, initialize soil temperature and moisture.
    38973926!--       According to the initialization for surface and soil parameters,
     
    39233952          ENDDO
    39243953!
    3925 !--       Level 2, if soil moisture and/or temperature  are
    3926 !--       provided from file, interpolate / extrapolate the provided data
    3927 !--       onto the respective soil layers. Please note, both, zs as well as
    3928 !--       init_3d%z_soil indicate a depth with positive values, so that no
    3929 !--       distinction between atmosphere is required concerning interpolation.
    3930 !--       Start with soil moisture
     3954!--       Initialization of soil moisture and temperature from file.
     3955!--       In case of nested runs, only root parent reads dynamic input file.
     3956!--       This case, transfer respective soil information provide
     3957!--       by dynamic input file from root parent domain onto all other domains.
     3958          IF ( init_soil_dynamically_in_child )  THEN
     3959!
     3960!--          Child domains will be only initialized with horizontally
     3961!--          averaged soil profiles in parent domain (for sake of simplicity).
     3962!--          If required, average soil data on root parent domain before
     3963!--          distribute onto child domains.
     3964             IF ( init_3d%from_file_msoil  .AND.  init_3d%lod_msoil == 2 )     &
     3965             THEN
     3966                ALLOCATE( pr_soil_init(0:init_3d%nzs-1) )
     3967
     3968                DO  k = 0, init_3d%nzs-1
     3969                   pr_soil_init(k) = SUM( init_3d%msoil(k,nys:nyn,nxl:nxr)  )
     3970                ENDDO
     3971!
     3972!--             Allocate 1D array for soil-moisture profile (will not be
     3973!--             allocated in lod==2 case).
     3974                ALLOCATE( init_3d%msoil_init(0:init_3d%nzs-1) )
     3975                init_3d%msoil_init = 0.0_wp
     3976#if defined( __parallel )
     3977                CALL MPI_ALLREDUCE( pr_soil_init(0), init_3d%msoil_init(0),    &
     3978                                    SIZE(pr_soil_init),                        &
     3979                                    MPI_REAL, MPI_SUM, comm2d, ierr )
     3980#endif
     3981                init_3d%msoil_init = init_3d%msoil_init /                      &
     3982                                        REAL( ( nx + 1 ) * ( ny + 1), KIND=wp )
     3983                DEALLOCATE( pr_soil_init )
     3984             ENDIF
     3985             IF ( init_3d%from_file_tsoil  .AND.  init_3d%lod_tsoil == 2 )  THEN
     3986                ALLOCATE( pr_soil_init(0:init_3d%nzs-1) )
     3987
     3988                DO  k = 0, init_3d%nzs-1
     3989                   pr_soil_init(k) = SUM( init_3d%tsoil(k,nys:nyn,nxl:nxr)  )
     3990                ENDDO
     3991!
     3992!--             Allocate 1D array for soil-temperature profile (will not be
     3993!--             allocated in lod==2 case).
     3994                ALLOCATE( init_3d%tsoil_init(0:init_3d%nzs-1) )
     3995                init_3d%tsoil_init = 0.0_wp
     3996#if defined( __parallel )
     3997                CALL MPI_ALLREDUCE( pr_soil_init(0), init_3d%tsoil_init(0),    &
     3998                                    SIZE(pr_soil_init),                        &
     3999                                    MPI_REAL, MPI_SUM, comm2d, ierr )
     4000#endif
     4001                init_3d%tsoil_init = init_3d%tsoil_init /                      &
     4002                                        REAL( ( nx + 1 ) * ( ny + 1), KIND=wp )
     4003                DEALLOCATE( pr_soil_init )
     4004
     4005             ENDIF
     4006
     4007#if defined( __parallel )
     4008!
     4009!--          Distribute soil grid information on file from root to all childs.
     4010!--          Only process with rank 0 sends the information.
     4011             CALL MPI_BCAST( init_3d%nzs,    1,                                &
     4012                             MPI_INTEGER, 0, MPI_COMM_WORLD, ierr )
     4013
     4014             IF ( .NOT.  ALLOCATED( init_3d%z_soil ) )                         &
     4015                ALLOCATE( init_3d%z_soil(1:init_3d%nzs) )
     4016
     4017             CALL MPI_BCAST( init_3d%z_soil, SIZE(init_3d%z_soil),             &
     4018                             MPI_REAL, 0, MPI_COMM_WORLD, ierr )
     4019#endif
     4020!
     4021!--          ALLOCATE arrays on child domains and set control attributes.
     4022             IF ( .NOT. init_3d%from_file_msoil )  THEN
     4023                ALLOCATE( init_3d%msoil_init(0:init_3d%nzs-1) )
     4024                init_3d%lod_msoil = 1
     4025                init_3d%from_file_msoil = .TRUE.
     4026             ENDIF
     4027             IF ( .NOT. init_3d%from_file_tsoil )  THEN
     4028                ALLOCATE( init_3d%tsoil_init(0:init_3d%nzs-1) )
     4029                init_3d%lod_tsoil = 1
     4030                init_3d%from_file_tsoil = .TRUE.
     4031             ENDIF
     4032
     4033
     4034#if defined( __parallel )
     4035!
     4036!--          Distribute soil profiles from root to all childs
     4037             CALL MPI_BCAST( init_3d%msoil_init, SIZE(init_3d%msoil_init),     &
     4038                             MPI_REAL, 0, MPI_COMM_WORLD, ierr )
     4039             CALL MPI_BCAST( init_3d%tsoil_init, SIZE(init_3d%tsoil_init),     &
     4040                             MPI_REAL, 0, MPI_COMM_WORLD, ierr )
     4041#endif
     4042
     4043          ENDIF
     4044!
     4045!--       Proceed with Level 2 initialization. Information from dynamic input
     4046!--       is now available on all processes.
    39314047          IF ( init_3d%from_file_msoil )  THEN
    39324048
     
    39834099                ENDDO
    39844100             ENDIF
    3985 
    39864101          ENDIF
    39874102!
Note: See TracChangeset for help on using the changeset viewer.