Changeset 4598 for palm/trunk


Ignore:
Timestamp:
Jul 10, 2020 10:13:23 AM (4 years ago)
Author:
suehring
Message:

Revise and bugfix surface-element mapping and 3D soil array in mpi-io restart branch

Location:
palm/trunk/SOURCE
Files:
2 edited

Legend:

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

    r4591 r4598  
    2525! -----------------
    2626! $Id$
     27! Bugfix in treatment of 3D soil arrays
     28!
     29! 4591 2020-07-06 15:56:08Z raasch
    2730! File re-formatted to follow the PALM coding standard
    2831!
     
    823826#endif
    824827
    825        IF ( include_total_domain_boundaries)  THEN
     828       IF ( include_total_domain_boundaries )  THEN
    826829          DO  i = lb%nxl, lb%nxr
    827830             data(lb%nys-nbgp:lb%nyn-nbgp,i-nbgp) = array_2d(i,lb%nys:lb%nyn)
     
    980983       CALL posix_read(fh, array_3d, SIZE( array_3d ) )
    981984#endif
    982        IF ( include_total_domain_boundaries)  THEN
    983           DO  i = lb%nxl, lb%nxr
    984              data(:,lb%nys-nbgp:lb%nyn-nbgp,i-nbgp) = array_3d(:,i,lb%nys:lb%nyn)
    985           ENDDO
    986        ELSE
    987           DO  i = nxl, nxr
    988              data(:,nys:nyn,i) = array_3d(:,i,nys:nyn)
    989           ENDDO
    990        ENDIF
    991 
    992        CALL exchange_horiz( data, nbgp )
    993 
    994     ELSE
    995 
    996        message_string = '3d-REAL array "' // TRIM( name ) // '" not found in restart file'
    997        CALL message( 'rrd_mpi_io_real_3d', 'PA0722', 3, 2, 0, 6, 0 )
    998 
    999     ENDIF
    1000 
    1001  END SUBROUTINE rrd_mpi_io_real_3d
    1002 
    1003 
    1004 
    1005 !--------------------------------------------------------------------------------------------------!
    1006 ! Description:
    1007 ! ------------
    1008 !> Read 3d-REAL soil array with MPI-IO
    1009 !> nzb_soil, nzt_soil are located in the module land_surface_model_mod. Since Fortran does not allow
    1010 !> cross referencing of module variables, it is required to pass these variables as arguments.
    1011 !--------------------------------------------------------------------------------------------------!
    1012  SUBROUTINE rrd_mpi_io_real_3d_soil( name, data, nzb_soil, nzt_soil )
    1013 
    1014     IMPLICIT NONE
    1015 
    1016     CHARACTER(LEN=*), INTENT(IN)       ::  name      !<
    1017 
    1018     INTEGER(iwp)                       ::  i         !<
    1019     INTEGER, INTENT(IN)                ::  nzb_soil  !<
    1020     INTEGER, INTENT(IN)                ::  nzt_soil  !<
    1021 
    1022 #if defined( __parallel )
    1023     INTEGER, DIMENSION(rd_status_size) ::  status    !<
    1024 #endif
    1025 
    1026     LOGICAL                            ::  found     !<
    1027 
    1028     REAL(wp), INTENT(INOUT), DIMENSION(nzb_soil:nzt_soil,nysg:nyng,nxlg:nxrg) ::  data  !<
    1029 
    1030 
    1031     found = .FALSE.
    1032 
    1033     DO  i = 1, tgh%nr_arrays
    1034        IF ( TRIM(array_names(i)) == TRIM( name ) )  THEN
    1035           array_position = array_offset(i)
    1036           found = .TRUE.
    1037           EXIT
    1038        ENDIF
    1039     ENDDO
    1040 
    1041     IF ( found )  THEN
    1042 #if defined( __parallel )
    1043        CALL rd_mpi_io_create_filetypes_3dsoil( nzb_soil, nzt_soil )
    1044        CALL sm_io%sm_node_barrier()  ! Has no effect if I/O on limited number of cores is inactive
    1045        IF ( sm_io%iam_io_pe )  THEN
    1046           CALL MPI_FILE_SET_VIEW( fh, array_position, MPI_REAL, ft_3dsoil, 'native',               &
    1047                                   MPI_INFO_NULL, ierr )
    1048           CALL MPI_FILE_READ_ALL( fh, array_3d_soil, SIZE( array_3d_soil ), MPI_REAL, status, ierr )
    1049           CALL MPI_TYPE_FREE( ft_3dsoil, ierr )
    1050        ENDIF
    1051        CALL sm_io%sm_node_barrier()
    1052 #else
    1053        CALL posix_lseek( fh, array_position )
    1054        CALL posix_read( fh, array_3d_soil, SIZE( array_3d_soil ) )
    1055 #endif
    1056985       IF ( include_total_domain_boundaries )  THEN
    1057986          DO  i = lb%nxl, lb%nxr
     
    1064993       ENDIF
    1065994
     995       CALL exchange_horiz( data, nbgp )
     996
     997    ELSE
     998
     999       message_string = '3d-REAL array "' // TRIM( name ) // '" not found in restart file'
     1000       CALL message( 'rrd_mpi_io_real_3d', 'PA0722', 3, 2, 0, 6, 0 )
     1001
     1002    ENDIF
     1003
     1004 END SUBROUTINE rrd_mpi_io_real_3d
     1005
     1006
     1007
     1008!--------------------------------------------------------------------------------------------------!
     1009! Description:
     1010! ------------
     1011!> Read 3d-REAL soil array with MPI-IO
     1012!> nzb_soil, nzt_soil are located in the module land_surface_model_mod. Since Fortran does not allow
     1013!> cross referencing of module variables, it is required to pass these variables as arguments.
     1014!--------------------------------------------------------------------------------------------------!
     1015 SUBROUTINE rrd_mpi_io_real_3d_soil( name, data, nzb_soil, nzt_soil )
     1016
     1017    IMPLICIT NONE
     1018
     1019    CHARACTER(LEN=*), INTENT(IN)       ::  name      !<
     1020
     1021    INTEGER(iwp)                       ::  i         !<
     1022    INTEGER, INTENT(IN)                ::  nzb_soil  !<
     1023    INTEGER, INTENT(IN)                ::  nzt_soil  !<
     1024
     1025#if defined( __parallel )
     1026    INTEGER, DIMENSION(rd_status_size) ::  status    !<
     1027#endif
     1028
     1029    LOGICAL                            ::  found     !<
     1030
     1031    REAL(wp), INTENT(INOUT), DIMENSION(nzb_soil:nzt_soil,nysg:nyng,nxlg:nxrg) ::  data  !<
     1032
     1033
     1034    found = .FALSE.
     1035
     1036    DO  i = 1, tgh%nr_arrays
     1037       IF ( TRIM(array_names(i)) == TRIM( name ) )  THEN
     1038          array_position = array_offset(i)
     1039          found = .TRUE.
     1040          EXIT
     1041       ENDIF
     1042    ENDDO
     1043
     1044    IF ( found )  THEN
     1045#if defined( __parallel )
     1046       CALL rd_mpi_io_create_filetypes_3dsoil( nzb_soil, nzt_soil )
     1047       CALL sm_io%sm_node_barrier()  ! Has no effect if I/O on limited number of cores is inactive
     1048       IF ( sm_io%iam_io_pe )  THEN
     1049          CALL MPI_FILE_SET_VIEW( fh, array_position, MPI_REAL, ft_3dsoil, 'native',               &
     1050                                  MPI_INFO_NULL, ierr )
     1051          CALL MPI_FILE_READ_ALL( fh, array_3d_soil, SIZE( array_3d_soil ), MPI_REAL, status, ierr )
     1052          CALL MPI_TYPE_FREE( ft_3dsoil, ierr )
     1053       ENDIF
     1054       CALL sm_io%sm_node_barrier()
     1055#else
     1056       CALL posix_lseek( fh, array_position )
     1057       CALL posix_read( fh, array_3d_soil, SIZE( array_3d_soil ) )
     1058#endif
     1059       IF ( include_total_domain_boundaries )  THEN
     1060          DO  i = lb%nxl, lb%nxr
     1061             data(:,lb%nys-nbgp:lb%nyn-nbgp,i-nbgp) = array_3d_soil(:,i,lb%nys:lb%nyn)
     1062          ENDDO
     1063       ELSE
     1064          DO  i = nxl, nxr
     1065             data(:,nys:nyn,i) = array_3d_soil(:,i,nys:nyn)
     1066          ENDDO
     1067       ENDIF
     1068
    10661069    ELSE
    10671070
     
    14321435#endif
    14331436
    1434     IF ( include_total_domain_boundaries)  THEN
     1437    IF ( include_total_domain_boundaries )  THEN
    14351438!
    14361439!--    Prepare output of 3d-REAL-array with ghost layers. In the virtual PE grid, the first
  • palm/trunk/SOURCE/surface_mod.f90

    r4595 r4598  
    2525! -----------------
    2626! $Id$
     27! Revise surface-element mapping in mpi-io restart branch
     28!
     29! 4595 2020-07-09 17:18:21Z suehring
    2730! Fix accidently commented subroutine
    2831!
     
    488491       REAL(wp), DIMENSION(:,:), ALLOCATABLE ::  tswc_h_m           !<
    489492
    490 
    491 !-- Arrays for time averages
     493!
     494!--    Arrays for time averages
    492495       REAL(wp), DIMENSION(:), ALLOCATABLE ::  rad_net_av          !< average of rad_net_l
    493496       REAL(wp), DIMENSION(:), ALLOCATABLE ::  surfinsw_av         !< average of sw radiation falling to local surface including
     
    42434246!--          Horizontal downward facing
    42444247             surf_h(1)%ns = ns_h_on_file(1)
    4245              CALL allocate_surface_attributes_h( surf_h(1), nys_on_file, nyn_on_file, nxl_on_file,  &
     4248             CALL allocate_surface_attributes_h( surf_h(1), nys_on_file, nyn_on_file, nxl_on_file, &
    42464249                                                 nxr_on_file )
    42474250!
     
    50795082
    50805083 CONTAINS
     5084
     5085
    50815086!--------------------------------------------------------------------------------------------------!
    50825087! Description:
     
    52605265 END SUBROUTINE restore_surface_elements
    52615266
    5262 
    52635267 END SUBROUTINE surface_rrd_local_ftn
    52645268
     
    52775281    CHARACTER(LEN=1) ::  dum  !< dummy string to create input-variable name
    52785282
    5279     INTEGER(iwp) ::  l  !< loop index for surface types
     5283    INTEGER(iwp) ::  i  !< loop index, x-direction
     5284    INTEGER(iwp) ::  j  !< loop index, y-direction
     5285    INTEGER(iwp) ::  l  !< loop index for surface orientation
     5286    INTEGER(iwp) ::  m  !< loop index for surface types - target array
     5287    INTEGER(iwp) ::  mm !< loop index for surface types - file array
    52805288
    52815289    INTEGER(iwp), DIMENSION(nys:nyn,nxl:nxr) ::  global_start_index  !< index for surface data (MPI-IO)
    52825290
    5283     LOGICAL ::  ldum  !< dummy variable
     5291    LOGICAL ::  ldum            !< dummy variable
     5292    LOGICAL ::  surf_match_def  !< flag indicating that surface element is of default type
     5293    LOGICAL ::  surf_match_lsm  !< flag indicating that surface element is of natural type
     5294    LOGICAL ::  surf_match_usm  !< flag indicating that surface element is of urban type
    52845295
    52855296    TYPE(surf_type), DIMENSION(0:2) ::  surf_h  !< gathered horizontal surfaces, contains all surface types
     
    55695580
    55705581!
    5571 !-- Redistribute surface elements on its respective type.
     5582!-- Redistribute surface elements on its respective type. Start with horizontal default surfaces.
    55725583    DO  l = 0, 2
    5573        CALL restore_surface_elements( surf_def_h(l), surf_h(l) )
     5584       DO  i = nxl, nxr
     5585          DO  j = nys, nyn
     5586             surf_match_def  = surf_def_h(l)%end_index(j,i) >= surf_def_h(l)%start_index(j,i)
     5587             IF ( surf_match_def )  THEN
     5588!
     5589!--             Set the start index for the local surface element
     5590                mm = surf_def_h(l)%start_index(j,i)
     5591!
     5592!--             For index pair (j,i) on file loop from start to end index, and in case the local
     5593!--             surface element mm is smaller than the local end index, assign the respective
     5594!--             surface data to this element.
     5595                DO  m = surf_h(l)%start_index(j,i), surf_h(l)%end_index(j,i)
     5596                   IF ( surf_def_h(l)%end_index(j,i) >= mm )                                       &
     5597                      CALL restore_surface_elements( surf_def_h(l), mm, surf_h(l), m )
     5598                   mm = mm + 1
     5599                ENDDO
     5600             ENDIF
     5601          ENDDO
     5602       ENDDO
    55745603    ENDDO
    5575     CALL restore_surface_elements( surf_lsm_h, surf_h(0) )
    5576     CALL restore_surface_elements( surf_usm_h, surf_h(0) )
    5577 
     5604!
     5605!-- Natural- and urban-like horizontal surfaces.
     5606    DO  i = nxl, nxr
     5607       DO  j = nys, nyn
     5608          surf_match_lsm  = surf_lsm_h%end_index(j,i) >= surf_lsm_h%start_index(j,i)
     5609          surf_match_usm  = surf_usm_h%end_index(j,i) >= surf_usm_h%start_index(j,i)
     5610
     5611          IF ( surf_match_lsm )  THEN
     5612             mm = surf_lsm_h%start_index(j,i)
     5613             DO  m = surf_h(0)%start_index(j,i), surf_h(0)%end_index(j,i)
     5614                IF ( surf_lsm_h%end_index(j,i) >= mm )                                             &
     5615                   CALL restore_surface_elements( surf_lsm_h, mm, surf_h(0), m )
     5616                mm = mm + 1
     5617             ENDDO
     5618          ENDIF
     5619
     5620          IF ( surf_match_usm )  THEN
     5621             mm = surf_usm_h%start_index(j,i)
     5622             DO  m = surf_h(0)%start_index(j,i), surf_h(0)%end_index(j,i)
     5623                IF ( surf_usm_h%end_index(j,i) >= mm )                                             &
     5624                   CALL restore_surface_elements( surf_usm_h, mm, surf_h(0), m )
     5625                mm = mm + 1
     5626             ENDDO
     5627          ENDIF
     5628       ENDDO
     5629    ENDDO
     5630!
     5631!-- Same for vertical surfaces.
    55785632    DO  l = 0, 3
    5579        CALL restore_surface_elements( surf_def_v(l), surf_v(l) )
    5580        CALL restore_surface_elements( surf_lsm_v(l), surf_v(l) )
    5581        CALL restore_surface_elements( surf_usm_v(l), surf_v(l) )
     5633       DO  i = nxl, nxr
     5634          DO  j = nys, nyn
     5635             surf_match_def  = surf_def_v(l)%end_index(j,i) >= surf_def_v(l)%start_index(j,i)
     5636             surf_match_lsm  = surf_lsm_v(l)%end_index(j,i) >= surf_lsm_v(l)%start_index(j,i)
     5637             surf_match_usm  = surf_usm_v(l)%end_index(j,i) >= surf_usm_v(l)%start_index(j,i)
     5638
     5639             IF ( surf_match_def )  THEN
     5640                mm = surf_def_v(l)%start_index(j,i)
     5641                DO  m = surf_v(l)%start_index(j,i), surf_v(l)%end_index(j,i)
     5642                   IF ( surf_def_v(l)%end_index(j,i) >= mm )                                       &
     5643                      CALL restore_surface_elements( surf_def_v(l), mm, surf_v(l), m )
     5644                   mm = mm + 1
     5645                ENDDO
     5646             ENDIF
     5647             IF ( surf_match_lsm )  THEN
     5648                mm = surf_lsm_v(l)%start_index(j,i)
     5649                DO  m = surf_v(l)%start_index(j,i), surf_v(l)%end_index(j,i)
     5650                   IF ( surf_lsm_v(l)%end_index(j,i) >= mm )                                       &
     5651                      CALL restore_surface_elements( surf_lsm_v(l), mm, surf_v(l), m )
     5652                   mm = mm + 1
     5653                ENDDO
     5654             ENDIF
     5655             IF ( surf_match_usm )  THEN
     5656                mm = surf_usm_v(l)%start_index(j,i)
     5657                DO  m = surf_v(l)%start_index(j,i), surf_v(l)%end_index(j,i)
     5658                   IF ( surf_usm_v(l)%end_index(j,i) >= mm )                                       &
     5659                      CALL restore_surface_elements( surf_usm_v(l), mm, surf_v(l), m )
     5660                   mm = mm + 1
     5661                ENDDO
     5662             ENDIF
     5663          ENDDO
     5664       ENDDO
    55825665    ENDDO
    55835666
    55845667 CONTAINS
    55855668
    5586  SUBROUTINE restore_surface_elements( surf_target, surf_file )
    5587 
    5588     IMPLICIT NONE
    5589 
    5590     INTEGER(iwp) ::  lsp  !< running index chemical species
     5669!--------------------------------------------------------------------------------------------------!
     5670! Description:
     5671! ------------
     5672!> Restores surface elements back on its respective type.
     5673!--------------------------------------------------------------------------------------------------!
     5674 SUBROUTINE restore_surface_elements( surf_target, m_target, surf_file, m_file )
     5675
     5676    INTEGER(iwp) ::  m_file    !< respective surface-element index of current surface array
     5677    INTEGER(iwp) ::  m_target  !< respecitve surface-element index of surface array on file
     5678    INTEGER(iwp) ::  lsp       !< running index chemical species
    55915679
    55925680    TYPE(surf_type) ::  surf_target  !< target surface type
    55935681    TYPE(surf_type) ::  surf_file    !< surface type on file
    55945682
    5595 
    5596     IF ( ALLOCATED( surf_target%us )  .AND.  ALLOCATED( surf_file%us ) )  THEN
    5597        surf_target%us = surf_file%us
    5598     ENDIF
     5683    IF ( ALLOCATED( surf_target%us )  .AND.  ALLOCATED( surf_file%us ) )                           &
     5684       surf_target%us(m_target) = surf_file%us(m_file)
    55995685
    56005686    IF ( ALLOCATED( surf_target%ol )  .AND.  ALLOCATED( surf_file%ol ) )                           &
    5601        surf_target%ol = surf_file%ol
     5687       surf_target%ol(m_target) = surf_file%ol(m_file)
     5688
     5689    IF ( ALLOCATED( surf_target%rib )  .AND.  ALLOCATED( surf_file%rib ) )                         &
     5690       surf_target%rib(m_target) = surf_file%rib(m_file)
     5691
     5692    IF ( ALLOCATED( surf_target%ol )  .AND.  ALLOCATED( surf_file%ol ) )                           &
     5693       surf_target%ol(m_target) = surf_file%ol(m_file)
    56025694
    56035695    IF ( ALLOCATED( surf_target%pt_surface )  .AND.  ALLOCATED( surf_file%pt_surface ) )           &
    5604        surf_target%pt_surface = surf_file%pt_surface
     5696       surf_target%pt_surface(m_target) = surf_file%pt_surface(m_file)
    56055697
    56065698    IF ( ALLOCATED( surf_target%q_surface )  .AND.  ALLOCATED( surf_file%q_surface ) )             &
    5607        surf_target%q_surface = surf_file%q_surface
     5699       surf_target%q_surface(m_target) = surf_file%q_surface(m_file)
    56085700
    56095701    IF ( ALLOCATED( surf_target%vpt_surface )  .AND.  ALLOCATED( surf_file%vpt_surface ) )         &
    5610        surf_target%vpt_surface = surf_file%vpt_surface
     5702       surf_target%vpt_surface(m_target) = surf_file%vpt_surface(m_file)
    56115703
    56125704    IF ( ALLOCATED( surf_target%usws )  .AND.  ALLOCATED( surf_file%usws ) )                       &
    5613        surf_target%usws = surf_file%usws
     5705       surf_target%usws(m_target) = surf_file%usws(m_file)
    56145706
    56155707    IF ( ALLOCATED( surf_target%vsws )  .AND.  ALLOCATED( surf_file%vsws ) )                       &
    5616        surf_target%vsws = surf_file%vsws
     5708       surf_target%vsws(m_target) = surf_file%vsws(m_file)
    56175709
    56185710    IF ( ALLOCATED( surf_target%ts )  .AND.  ALLOCATED( surf_file%ts ) )                           &
    5619        surf_target%ts = surf_file%ts
     5711       surf_target%ts(m_target) = surf_file%ts(m_file)
    56205712
    56215713    IF ( ALLOCATED( surf_target%shf )  .AND.  ALLOCATED( surf_file%shf ) )                         &
    5622        surf_target%shf = surf_file%shf
     5714       surf_target%shf(m_target) = surf_file%shf(m_file)
    56235715
    56245716    IF ( ALLOCATED( surf_target%qs )  .AND.  ALLOCATED( surf_file%qs ) )                           &
    5625        surf_target%qs = surf_file%qs
     5717       surf_target%qs(m_target) = surf_file%qs(m_file)
    56265718
    56275719    IF ( ALLOCATED( surf_target%qsws )  .AND.  ALLOCATED( surf_file%qsws ) )                       &
    5628        surf_target%qsws = surf_file%qsws
     5720       surf_target%qsws(m_target) = surf_file%qsws(m_file)
    56295721
    56305722    IF ( ALLOCATED( surf_target%ss )  .AND.  ALLOCATED( surf_file%ss ) )                           &
    5631        surf_target%ss = surf_file%ss
     5723       surf_target%ss(m_target) = surf_file%ss(m_file)
    56325724
    56335725    IF ( ALLOCATED( surf_target%ssws )  .AND.  ALLOCATED( surf_file%ssws ) )                       &
    5634        surf_target%ssws = surf_file%ssws
    5635 
    5636     IF ( ALLOCATED( surf_target%css )  .AND.  ALLOCATED( surf_file%css   ) )  THEN
     5726       surf_target%ssws(m_target) = surf_file%ssws(m_file)
     5727
     5728    IF ( ALLOCATED( surf_target%css )  .AND.  ALLOCATED( surf_file%css ) )  THEN
    56375729       DO  lsp = 1, nvar
    5638           surf_target%css(lsp,:) = surf_file%css(lsp,:)
     5730          surf_target%css(lsp,m_target) = surf_file%css(lsp,m_file)
    56395731       ENDDO
    56405732    ENDIF
    56415733
    5642     IF ( ALLOCATED( surf_target%cssws )  .AND.  ALLOCATED( surf_file%cssws   ) )  THEN
     5734    IF ( ALLOCATED( surf_target%cssws )  .AND.  ALLOCATED( surf_file%cssws ) )  THEN
    56435735       DO  lsp = 1, nvar
    5644           surf_target%cssws(lsp,:) = surf_file%cssws(lsp,:)
     5736          surf_target%cssws(lsp,m_target) = surf_file%cssws(lsp,m_file)
    56455737       ENDDO
    56465738    ENDIF
     5739
    56475740    IF ( ALLOCATED( surf_target%qcs )  .AND.  ALLOCATED( surf_file%qcs ) )                         &
    5648        surf_target%qcs = surf_file%qcs
     5741      surf_target%qcs(m_target) = surf_file%qcs(m_file)
     5742
    56495743    IF ( ALLOCATED( surf_target%qcsws )  .AND.  ALLOCATED( surf_file%qcsws ) )                     &
    5650        surf_target%qcsws = surf_file%qcsws
     5744       surf_target%qcsws(m_target) = surf_file%qcsws(m_file)
     5745
    56515746    IF ( ALLOCATED( surf_target%ncs )  .AND.  ALLOCATED( surf_file%ncs ) )                         &
    5652        surf_target%ncs = surf_file%ncs
     5747       surf_target%ncs(m_target) = surf_file%ncs(m_file)
     5748
    56535749    IF ( ALLOCATED( surf_target%ncsws )  .AND.  ALLOCATED( surf_file%ncsws ) )                     &
    5654        surf_target%ncsws = surf_file%ncsws
     5750       surf_target%ncsws(m_target) = surf_file%ncsws(m_file)
     5751
     5752    IF ( ALLOCATED( surf_target%qis )  .AND.  ALLOCATED( surf_file%qis ) )                         &
     5753      surf_target%qis(m_target) = surf_file%qis(m_file)
     5754
     5755    IF ( ALLOCATED( surf_target%qisws )  .AND.  ALLOCATED( surf_file%qisws ) )                     &
     5756       surf_target%qisws(m_target) = surf_file%qisws(m_file)
     5757
     5758    IF ( ALLOCATED( surf_target%nis )  .AND.  ALLOCATED( surf_file%nis ) )                         &
     5759       surf_target%nis(m_target) = surf_file%nis(m_file)
     5760
     5761    IF ( ALLOCATED( surf_target%nisws )  .AND.  ALLOCATED( surf_file%nisws ) )                     &
     5762       surf_target%nisws(m_target) = surf_file%nisws(m_file)
     5763
    56555764    IF ( ALLOCATED( surf_target%qrs )  .AND.  ALLOCATED( surf_file%qrs ) )                         &
    5656        surf_target%qrs = surf_file%qrs
     5765       surf_target%qrs(m_target) = surf_file%qrs(m_file)
     5766
    56575767    IF ( ALLOCATED( surf_target%qrsws )  .AND.  ALLOCATED( surf_file%qrsws ) )                     &
    5658        surf_target%qrsws = surf_file%qrsws
     5768       surf_target%qrsws(m_target) = surf_file%qrsws(m_file)
     5769
    56595770    IF ( ALLOCATED( surf_target%nrs )  .AND.  ALLOCATED( surf_file%nrs ) )                         &
    5660        surf_target%nrs = surf_file%nrs
     5771       surf_target%nrs(m_target) = surf_file%nrs(m_file)
    56615772
    56625773    IF ( ALLOCATED( surf_target%nrsws )  .AND.  ALLOCATED( surf_file%nrsws ) )                     &
    5663        surf_target%nrsws = surf_file%nrsws
    5664     IF ( ALLOCATED( surf_target%sasws )  .AND. ALLOCATED( surf_file%sasws ) )                      &
    5665        surf_target%sasws = surf_file%sasws
     5774       surf_target%nrsws(m_target) = surf_file%nrsws(m_file)
     5775
     5776    IF ( ALLOCATED( surf_target%sasws )  .AND.  ALLOCATED( surf_file%sasws ) )                     &
     5777       surf_target%sasws(m_target) = surf_file%sasws(m_file)
     5778
    56665779    IF ( ALLOCATED( surf_target%mom_flux_uv )  .AND.  ALLOCATED( surf_file%mom_flux_uv ) )         &
    5667        surf_target%mom_flux_uv = surf_file%mom_flux_uv
     5780       surf_target%mom_flux_uv(m_target) = surf_file%mom_flux_uv(m_file)
     5781
    56685782    IF ( ALLOCATED( surf_target%mom_flux_w )  .AND.  ALLOCATED( surf_file%mom_flux_w ) )           &
    5669        surf_target%mom_flux_w = surf_file%mom_flux_w
    5670     IF ( ALLOCATED( surf_target%mom_flux_tke )  .AND.  ALLOCATED( surf_file%mom_flux_tke ) )       &
    5671        surf_target%mom_flux_tke(0:1,:) = surf_file%mom_flux_tke(0:1,:)
    5672 
     5783       surf_target%mom_flux_w(m_target) = surf_file%mom_flux_w(m_file)
     5784
     5785    IF ( ALLOCATED( surf_target%mom_flux_tke )  .AND.                                              &
     5786         ALLOCATED( surf_file%mom_flux_tke   ) )                                                   &
     5787       surf_target%mom_flux_tke(0:1,m_target) = surf_file%mom_flux_tke(0:1,m_file)
    56735788
    56745789 END SUBROUTINE restore_surface_elements
    56755790
    56765791 END SUBROUTINE surface_rrd_local_mpi
    5677 
    5678 
    5679 
    5680 
    56815792
    56825793!--------------------------------------------------------------------------------------------------!
Note: See TracChangeset for help on using the changeset viewer.