Ignore:
Timestamp:
Aug 27, 2018 4:58:37 PM (6 years ago)
Author:
suehring
Message:

Additional namelist parameter to switch on/off the nesting of chemical species; Enable the input of soil data from dynamic input files independent on atmosphere in order to initialize soil properties in nested child domains from dynamic input; Revise error message number for static/dynamic input; Revise and add checks for static/dynamic input; Bugfix, add netcdf4_parallel directive for collective read operation

File:
1 edited

Legend:

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

    r3196 r3209  
    2020! Current revisions:
    2121! -----------------
    22 !
     22! Enable optional initialization of soil properties directly from dynamic
     23! input file.
    2324!
    2425! Former revisions:
     
    465466    USE netcdf_data_input_mod,                                                 &
    466467        ONLY :  building_type_f, init_3d, input_pids_static,                   &
    467                 netcdf_data_input_interpolate,                                 &
     468                netcdf_data_input_interpolate, netcdf_data_input_init_lsm,     &
    468469                pavement_pars_f, pavement_subsurface_pars_f, pavement_type_f,  &
    469470                root_area_density_lsm_f, soil_pars_f, soil_type_f,             &
     
    24542455       IMPLICIT NONE
    24552456
    2456        LOGICAL      ::  init_soil_dynamically_in_child !< flag controlling initialization of soil in child domains
     2457       LOGICAL      ::  init_soil_from_parent  !< flag controlling initialization of soil in child domains
    24572458
    24582459       INTEGER(iwp) ::  i                       !< running index
     
    40204021       IF (  TRIM( initializing_actions ) /= 'read_restart_data' )  THEN
    40214022!
    4022 !--       In case of nested runs, check if soil is initialized via dynamic
    4023 !--       input file in root domain and distribute this information
    4024 !--       to all embedded child domains. This case, soil moisture and
    4025 !--       temperature will be initialized via root domain. 
    4026           init_soil_dynamically_in_child = .FALSE.
     4023!--       Read soil properties from dynamic input file
     4024          CALL netcdf_data_input_init_lsm
     4025!
     4026!--       In case no dynamic input is available for a child domain but root
     4027!--       domain is initialized with dynamic input file, the different soil
     4028!--       properties can lead to significant discrepancies in the atmospheric
     4029!--       surface forcing. For this reason, the child domain
     4030!--       is initialized with mean soil profiles from the root domain.         
     4031          init_soil_from_parent = .FALSE.
    40274032          IF ( nested_run )  THEN
    40284033#if defined( __parallel )
    40294034             CALL MPI_ALLREDUCE( init_3d%from_file_tsoil  .OR.                 &
    40304035                                 init_3d%from_file_msoil,                      &
    4031                                  init_soil_dynamically_in_child,               &
     4036                                 init_soil_from_parent,                        &
    40324037                                 1, MPI_LOGICAL, MPI_LOR, MPI_COMM_WORLD, ierr )
    40334038#endif
    40344039          ENDIF
    4035 
    40364040!
    40374041!--       First, initialize soil temperature and moisture.
     
    40654069!
    40664070!--       Initialization of soil moisture and temperature from file.
    4067 !--       In case of nested runs, only root parent reads dynamic input file.
    4068 !--       This case, transfer respective soil information provide
    4069 !--       by dynamic input file from root parent domain onto all other domains.
    4070           IF ( init_soil_dynamically_in_child )  THEN
     4071!--       In case of no dynamic input file is available for the child domain,
     4072!--       transfer soil mean profiles from the root-parent domain onto all
     4073!--       child domains.
     4074          IF ( init_soil_from_parent )  THEN
    40714075!
    40724076!--          Child domains will be only initialized with horizontally
     
    40794083
    40804084                DO  k = 0, init_3d%nzs-1
    4081                    pr_soil_init(k) = SUM( init_3d%msoil(k,nys:nyn,nxl:nxr)  )
     4085                   pr_soil_init(k) = SUM( init_3d%msoil_3d(k,nys:nyn,nxl:nxr)  )
    40824086                ENDDO
    40834087!
    40844088!--             Allocate 1D array for soil-moisture profile (will not be
    40854089!--             allocated in lod==2 case).
    4086                 ALLOCATE( init_3d%msoil_init(0:init_3d%nzs-1) )
    4087                 init_3d%msoil_init = 0.0_wp
     4090                ALLOCATE( init_3d%msoil_1d(0:init_3d%nzs-1) )
     4091                init_3d%msoil_1d = 0.0_wp
    40884092#if defined( __parallel )
    4089                 CALL MPI_ALLREDUCE( pr_soil_init(0), init_3d%msoil_init(0),    &
     4093                CALL MPI_ALLREDUCE( pr_soil_init(0), init_3d%msoil_1d(0),      &
    40904094                                    SIZE(pr_soil_init),                        &
    40914095                                    MPI_REAL, MPI_SUM, comm2d, ierr )
    40924096#endif
    4093                 init_3d%msoil_init = init_3d%msoil_init /                      &
     4097                init_3d%msoil_1d = init_3d%msoil_1d /                          &
    40944098                                        REAL( ( nx + 1 ) * ( ny + 1), KIND=wp )
    40954099                DEALLOCATE( pr_soil_init )
     
    40994103
    41004104                DO  k = 0, init_3d%nzs-1
    4101                    pr_soil_init(k) = SUM( init_3d%tsoil(k,nys:nyn,nxl:nxr)  )
     4105                   pr_soil_init(k) = SUM( init_3d%tsoil_3d(k,nys:nyn,nxl:nxr)  )
    41024106                ENDDO
    41034107!
    41044108!--             Allocate 1D array for soil-temperature profile (will not be
    41054109!--             allocated in lod==2 case).
    4106                 ALLOCATE( init_3d%tsoil_init(0:init_3d%nzs-1) )
    4107                 init_3d%tsoil_init = 0.0_wp
     4110                ALLOCATE( init_3d%tsoil_1d(0:init_3d%nzs-1) )
     4111                init_3d%tsoil_1d = 0.0_wp
    41084112#if defined( __parallel )
    4109                 CALL MPI_ALLREDUCE( pr_soil_init(0), init_3d%tsoil_init(0),    &
     4113                CALL MPI_ALLREDUCE( pr_soil_init(0), init_3d%tsoil_1d(0),      &
    41104114                                    SIZE(pr_soil_init),                        &
    41114115                                    MPI_REAL, MPI_SUM, comm2d, ierr )
    41124116#endif
    4113                 init_3d%tsoil_init = init_3d%tsoil_init /                      &
     4117                init_3d%tsoil_1d = init_3d%tsoil_1d /                          &
    41144118                                        REAL( ( nx + 1 ) * ( ny + 1), KIND=wp )
    41154119                DEALLOCATE( pr_soil_init )
     
    41324136!
    41334137!--          ALLOCATE arrays on child domains and set control attributes.
    4134              IF ( .NOT. init_3d%from_file_msoil )  THEN
    4135                 ALLOCATE( init_3d%msoil_init(0:init_3d%nzs-1) )
    4136                 init_3d%lod_msoil = 1
     4138!--          Note, 1d soil profiles are allocated even though soil information
     4139!--          is already read from dynamic file in one child domain.
     4140!--          This case, however, data is not used for further initialization
     4141!--          since the LoD=2.
     4142             IF ( .NOT. ALLOCATED( init_3d%msoil_1d ) )  THEN
     4143                ALLOCATE( init_3d%msoil_1d(0:init_3d%nzs-1) )
     4144                IF( .NOT. init_3d%from_file_msoil )  init_3d%lod_msoil = 1
    41374145                init_3d%from_file_msoil = .TRUE.
    41384146             ENDIF
    4139              IF ( .NOT. init_3d%from_file_tsoil )  THEN
    4140                 ALLOCATE( init_3d%tsoil_init(0:init_3d%nzs-1) )
    4141                 init_3d%lod_tsoil = 1
     4147             IF ( .NOT. ALLOCATED( init_3d%tsoil_1d ) )  THEN
     4148                ALLOCATE( init_3d%tsoil_1d(0:init_3d%nzs-1) )
     4149                IF( .NOT. init_3d%from_file_tsoil )  init_3d%lod_tsoil = 1
    41424150                init_3d%from_file_tsoil = .TRUE.
    41434151             ENDIF
     
    41474155!
    41484156!--          Distribute soil profiles from root to all childs
    4149              CALL MPI_BCAST( init_3d%msoil_init, SIZE(init_3d%msoil_init),     &
     4157             CALL MPI_BCAST( init_3d%msoil_1d, SIZE(init_3d%msoil_1d),         &
    41504158                             MPI_REAL, 0, MPI_COMM_WORLD, ierr )
    4151              CALL MPI_BCAST( init_3d%tsoil_init, SIZE(init_3d%tsoil_init),     &
     4159             CALL MPI_BCAST( init_3d%tsoil_1d, SIZE(init_3d%tsoil_1d),         &
    41524160                             MPI_REAL, 0, MPI_COMM_WORLD, ierr )
    41534161#endif
     
    41554163          ENDIF
    41564164!
    4157 !--       Proceed with Level 2 initialization. Information from dynamic input
    4158 !--       is now available on all processes.
     4165!--       Proceed with Level 2 initialization.
    41594166          IF ( init_3d%from_file_msoil )  THEN
    41604167
     
    41644171                   CALL netcdf_data_input_interpolate(                         &
    41654172                                       m_soil_h%var_2d(nzb_soil:nzt_soil,m),   &
    4166                                        init_3d%msoil_init(:),                  &
     4173                                       init_3d%msoil_1d(:),                    &
    41674174                                       zs(nzb_soil:nzt_soil), init_3d%z_soil,  &
    41684175                                       nzb_soil, nzt_soil,                     &
     
    41744181                      CALL netcdf_data_input_interpolate(                      &
    41754182                                       m_soil_v(l)%var_2d(nzb_soil:nzt_soil,m),&
    4176                                        init_3d%msoil_init(:),                  &
     4183                                       init_3d%msoil_1d(:),                    &
    41774184                                       zs(nzb_soil:nzt_soil), init_3d%z_soil,  &
    41784185                                       nzb_soil, nzt_soil,                     &
     
    41864193                   j = surf_lsm_h%j(m)
    41874194
    4188                    IF ( init_3d%msoil(0,j,i) /= init_3d%fill_msoil )           &
     4195                   IF ( init_3d%msoil_3d(0,j,i) /= init_3d%fill_msoil )        &
    41894196                      CALL netcdf_data_input_interpolate(                      &
    41904197                                       m_soil_h%var_2d(nzb_soil:nzt_soil,m),   &
    4191                                        init_3d%msoil(:,j,i),                   &
     4198                                       init_3d%msoil_3d(:,j,i),                &
    41924199                                       zs(nzb_soil:nzt_soil), init_3d%z_soil,  &
    41934200                                       nzb_soil, nzt_soil,                     &
     
    42014208                                             surf_lsm_v(l)%building_covered(m) )
    42024209
    4203                       IF ( init_3d%msoil(0,j,i) /= init_3d%fill_msoil )        &
     4210                      IF ( init_3d%msoil_3d(0,j,i) /= init_3d%fill_msoil )     &
    42044211                         CALL netcdf_data_input_interpolate(                   &
    42054212                                       m_soil_v(l)%var_2d(nzb_soil:nzt_soil,m),&
    4206                                        init_3d%msoil(:,j,i),                   &
     4213                                       init_3d%msoil_3d(:,j,i),                &
    42074214                                       zs(nzb_soil:nzt_soil), init_3d%z_soil,  &
    42084215                                       nzb_soil, nzt_soil,                     &
     
    42214228                   CALL netcdf_data_input_interpolate(                         &
    42224229                                       t_soil_h%var_2d(nzb_soil:nzt_soil,m),   &
    4223                                        init_3d%tsoil_init(:),                  &
     4230                                       init_3d%tsoil_1d(:),                    &
    42244231                                       zs(nzb_soil:nzt_soil), init_3d%z_soil,  &
    42254232                                       nzb_soil, nzt_soil,                     &
     
    42324239                      CALL netcdf_data_input_interpolate(                      &
    42334240                                       t_soil_v(l)%var_2d(nzb_soil:nzt_soil,m),&
    4234                                        init_3d%tsoil_init(:),                  &
     4241                                       init_3d%tsoil_1d(:),                    &
    42354242                                       zs(nzb_soil:nzt_soil), init_3d%z_soil,  &
    42364243                                       nzb_soil, nzt_soil,                     &
     
    42464253                   j = surf_lsm_h%j(m)
    42474254
    4248                    IF ( init_3d%msoil(0,j,i) /= init_3d%fill_msoil )           &
     4255                   IF ( init_3d%tsoil_3d(0,j,i) /= init_3d%fill_tsoil )        &
    42494256                      CALL netcdf_data_input_interpolate(                      &
    42504257                                       t_soil_h%var_2d(nzb_soil:nzt_soil,m),   &
    4251                                        init_3d%tsoil(:,j,i),                   &
     4258                                       init_3d%tsoil_3d(:,j,i),                &
    42524259                                       zs(nzb_soil:nzt_soil), init_3d%z_soil,  &
    42534260                                       nzb_soil, nzt_soil,                     &
     
    42624269                                                surf_lsm_v(l)%building_covered(m) )
    42634270
    4264                       IF ( init_3d%msoil(0,j,i) /= init_3d%fill_msoil )        &
     4271                      IF ( init_3d%tsoil_3d(0,j,i) /= init_3d%fill_tsoil )     &
    42654272                         CALL netcdf_data_input_interpolate(                   &
    42664273                                       t_soil_v(l)%var_2d(nzb_soil:nzt_soil,m),&
    4267                                        init_3d%tsoil(:,j,i),                   &
     4274                                       init_3d%tsoil_3d(:,j,i),                &
    42684275                                       zs(nzb_soil:nzt_soil), init_3d%z_soil,  &
    42694276                                       nzb_soil, nzt_soil,                     &
     
    43114318             surf_lsm_h%shf(m)  = - surf_lsm_h%us(m) * surf_lsm_h%ts(m)        &
    43124319                                  * rho_surface
    4313          ENDDO
    4314 !
    4315 !--      Vertical surfaces
    4316          DO  l = 0, 3
     4320          ENDDO
     4321!
     4322!--       Vertical surfaces
     4323          DO  l = 0, 3
    43174324             DO  m = 1, surf_lsm_v(l)%ns
    43184325                i   = surf_lsm_v(l)%i(m)           
Note: See TracChangeset for help on using the changeset viewer.