Ignore:
Timestamp:
Apr 13, 2020 8:11:20 PM (4 years ago)
Author:
raasch
Message:

restart data handling with MPI-IO added, first part

File:
1 edited

Legend:

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

    r4493 r4495  
    2828! -----------------
    2929! $Id$
     30! restart data handling with MPI-IO added
     31!
     32! 4493 2020-04-10 09:49:43Z pavelkrc
    3033! J.Resler, 2020/03/19
    3134! - remove reading of deprecated input parameters c_surface and lambda_surf
     
    252255               pt_surface, large_scale_forcing, lsf_surf,                      &
    253256               spinup_pt_mean, spinup_time, time_do3d, dt_do3d,                &
    254                average_count_3d, varnamelength, urban_surface, dz
     257               average_count_3d, varnamelength, urban_surface, dz, restart_data_format_output
    255258
    256259    USE bulk_cloud_model_mod,                                                  &
     
    282285               iwest_u, iup_l, inorth_l, isouth_l, ieast_l, iwest_l, id,       &
    283286               nz_urban_b, nz_urban_t, unscheduled_radiation_calls
     287
     288    USE restart_data_mpi_io_mod,                                                                   &
     289        ONLY:  rd_mpi_io_surface_filetypes, wrd_mpi_io, wrd_mpi_io_surface
    284290
    285291    USE statistics,                                                            &
     
    89098915!> Subroutine writes t_surf and t_wall data into restart files
    89108916!------------------------------------------------------------------------------!
    8911      SUBROUTINE usm_wrd_local
     8917    SUBROUTINE usm_wrd_local
    89128918 
    89138919     
    8914         IMPLICIT NONE
     8920       IMPLICIT NONE
    89158921       
    8916         CHARACTER(LEN=1) ::  dum     !< dummy string to create output-variable name 
    8917         INTEGER(iwp)     ::  l       !< index surface type orientation
     8922       CHARACTER(LEN=1) ::  dum     !< dummy string to create output-variable name
     8923
     8924       INTEGER(iwp)     ::  l       !< index surface type orientation
     8925
     8926       INTEGER(iwp),DIMENSION(nys:nyn,nxl:nxr) ::  global_start_index  !< index for surface data (MPI-IO)
     8927
     8928       LOGICAL ::  surface_data_to_write  !< switch for MPI-I/O if PE has surface data to write
    89188929 
    8919         CALL wrd_write_string( 'ns_h_on_file_usm' )
    8920         WRITE ( 14 )  surf_usm_h%ns
     8930
     8931       IF ( TRIM( restart_data_format_output ) == 'fortran_binary' )  THEN
     8932
     8933          CALL wrd_write_string( 'ns_h_on_file_usm' )
     8934          WRITE ( 14 )  surf_usm_h%ns
     8935
     8936          CALL wrd_write_string( 'ns_v_on_file_usm' )
     8937          WRITE ( 14 )  surf_usm_v(0:3)%ns
     8938
     8939          CALL wrd_write_string( 'usm_start_index_h' )
     8940          WRITE ( 14 )  surf_usm_h%start_index
     8941
     8942          CALL wrd_write_string( 'usm_end_index_h' )
     8943          WRITE ( 14 )  surf_usm_h%end_index
     8944
     8945          CALL wrd_write_string( 't_surf_wall_h' )
     8946          WRITE ( 14 )  t_surf_wall_h
     8947
     8948          CALL wrd_write_string( 't_surf_window_h' )
     8949          WRITE ( 14 )  t_surf_window_h
     8950
     8951          CALL wrd_write_string( 't_surf_green_h' )
     8952          WRITE ( 14 )  t_surf_green_h
     8953
     8954          CALL wrd_write_string( 'm_liq_usm_h' )
     8955          WRITE ( 14 )  m_liq_usm_h%var_usm_1d
     8956!
     8957!--       Write restart data which is especially needed for the urban-surface
     8958!--       model. In order to do not fill up the restart routines in surface_mod.
     8959!--       Output of waste heat from indoor model. Restart data is required in
     8960!--       this special case, because the indoor model where waste heat is
     8961!--       computed is call each hour (current default), so that waste heat would
     8962!--       have zero value until next call of indoor model.
     8963          IF ( indoor_model )  THEN
     8964             CALL wrd_write_string( 'waste_heat_h' )
     8965             WRITE ( 14 )  surf_usm_h%waste_heat
     8966          ENDIF
     8967           
     8968          DO  l = 0, 3
    89218969 
    8922         CALL wrd_write_string( 'ns_v_on_file_usm' )
    8923         WRITE ( 14 )  surf_usm_v(0:3)%ns
     8970             CALL wrd_write_string( 'usm_start_index_v' )
     8971             WRITE ( 14 )  surf_usm_v(l)%start_index
     8972
     8973             CALL wrd_write_string( 'usm_end_index_v' )
     8974             WRITE ( 14 )  surf_usm_v(l)%end_index
     8975
     8976             WRITE( dum, '(I1)')  l
     8977
     8978             CALL wrd_write_string( 't_surf_wall_v(' // dum // ')' )
     8979             WRITE ( 14 )  t_surf_wall_v(l)%t
     8980
     8981             CALL wrd_write_string( 't_surf_window_v(' // dum // ')' )
     8982             WRITE ( 14 ) t_surf_window_v(l)%t
     8983
     8984             CALL wrd_write_string( 't_surf_green_v(' // dum // ')' )
     8985             WRITE ( 14 ) t_surf_green_v(l)%t
     8986
     8987             IF ( indoor_model )  THEN
     8988                CALL wrd_write_string( 'waste_heat_v(' // dum // ')' )
     8989                WRITE ( 14 )  surf_usm_v(l)%waste_heat
     8990             ENDIF
     8991
     8992          ENDDO
    89248993 
    8925         CALL wrd_write_string( 'usm_start_index_h' )
    8926         WRITE ( 14 )  surf_usm_h%start_index
    8927  
    8928         CALL wrd_write_string( 'usm_end_index_h' )
    8929         WRITE ( 14 )  surf_usm_h%end_index
    8930  
    8931         CALL wrd_write_string( 't_surf_wall_h' )
    8932         WRITE ( 14 )  t_surf_wall_h
    8933  
    8934         CALL wrd_write_string( 't_surf_window_h' )
    8935         WRITE ( 14 )  t_surf_window_h
    8936  
    8937         CALL wrd_write_string( 't_surf_green_h' )
    8938         WRITE ( 14 )  t_surf_green_h
    8939 
    8940         CALL wrd_write_string( 'm_liq_usm_h' )
    8941         WRITE ( 14 )  m_liq_usm_h%var_usm_1d
    8942 !
    8943 !--     Write restart data which is especially needed for the urban-surface
    8944 !--     model. In order to do not fill up the restart routines in
    8945 !--     surface_mod.
    8946 !--     Output of waste heat from indoor model. Restart data is required in
    8947 !--     this special case, because the indoor model where waste heat is
    8948 !--     computed is call each hour (current default), so that waste heat would
    8949 !--     have zero value until next call of indoor model.
    8950         IF ( indoor_model )  THEN
    8951            CALL wrd_write_string( 'waste_heat_h' )
    8952            WRITE ( 14 )  surf_usm_h%waste_heat
    8953         ENDIF   
    8954            
    8955         DO  l = 0, 3
    8956  
    8957            CALL wrd_write_string( 'usm_start_index_v' )
    8958            WRITE ( 14 )  surf_usm_v(l)%start_index
    8959  
    8960            CALL wrd_write_string( 'usm_end_index_v' )
    8961            WRITE ( 14 )  surf_usm_v(l)%end_index
    8962  
    8963            WRITE( dum, '(I1)')  l         
    8964  
    8965            CALL wrd_write_string( 't_surf_wall_v(' // dum // ')' )
    8966            WRITE ( 14 )  t_surf_wall_v(l)%t
    8967  
    8968            CALL wrd_write_string( 't_surf_window_v(' // dum // ')' )
    8969            WRITE ( 14 ) t_surf_window_v(l)%t     
    8970  
    8971            CALL wrd_write_string( 't_surf_green_v(' // dum // ')' )
    8972            WRITE ( 14 ) t_surf_green_v(l)%t 
    8973            
    8974            IF ( indoor_model )  THEN
    8975               CALL wrd_write_string( 'waste_heat_v(' // dum // ')' )
    8976               WRITE ( 14 )  surf_usm_v(l)%waste_heat
    8977            ENDIF
    8978            
    8979         ENDDO
    8980  
    8981         CALL wrd_write_string( 'usm_start_index_h' )
    8982         WRITE ( 14 )  surf_usm_h%start_index
    8983  
    8984         CALL wrd_write_string( 'usm_end_index_h' )
    8985         WRITE ( 14 )  surf_usm_h%end_index
    8986  
    8987         CALL wrd_write_string( 't_wall_h' )
    8988         WRITE ( 14 )  t_wall_h
    8989  
    8990         CALL wrd_write_string( 't_window_h' )
    8991         WRITE ( 14 )  t_window_h
    8992  
    8993         CALL wrd_write_string( 't_green_h' )
    8994         WRITE ( 14 )  t_green_h
    8995  
    8996         DO  l = 0, 3
    8997  
    8998            CALL wrd_write_string( 'usm_start_index_v' )
    8999            WRITE ( 14 )  surf_usm_v(l)%start_index
    9000  
    9001            CALL wrd_write_string( 'usm_end_index_v' )
    9002            WRITE ( 14 )  surf_usm_v(l)%end_index
    9003  
    9004            WRITE( dum, '(I1)')  l     
    9005  
    9006            CALL wrd_write_string( 't_wall_v(' // dum // ')' )
    9007            WRITE ( 14 )  t_wall_v(l)%t
    9008  
    9009            CALL wrd_write_string( 't_window_v(' // dum // ')' )
    9010            WRITE ( 14 )  t_window_v(l)%t
    9011  
    9012            CALL wrd_write_string( 't_green_v(' // dum // ')' )
    9013            WRITE ( 14 )  t_green_v(l)%t
    9014        
    9015         ENDDO
    9016        
    9017      END SUBROUTINE usm_wrd_local
     8994          CALL wrd_write_string( 'usm_start_index_h' )
     8995          WRITE ( 14 )  surf_usm_h%start_index
     8996
     8997          CALL wrd_write_string( 'usm_end_index_h' )
     8998          WRITE ( 14 )  surf_usm_h%end_index
     8999
     9000          CALL wrd_write_string( 't_wall_h' )
     9001          WRITE ( 14 )  t_wall_h
     9002
     9003          CALL wrd_write_string( 't_window_h' )
     9004          WRITE ( 14 )  t_window_h
     9005
     9006          CALL wrd_write_string( 't_green_h' )
     9007          WRITE ( 14 )  t_green_h
     9008
     9009          DO  l = 0, 3
     9010
     9011             CALL wrd_write_string( 'usm_start_index_v' )
     9012             WRITE ( 14 )  surf_usm_v(l)%start_index
     9013
     9014             CALL wrd_write_string( 'usm_end_index_v' )
     9015             WRITE ( 14 )  surf_usm_v(l)%end_index
     9016
     9017             WRITE( dum, '(I1)')  l
     9018
     9019             CALL wrd_write_string( 't_wall_v(' // dum // ')' )
     9020             WRITE ( 14 )  t_wall_v(l)%t
     9021
     9022             CALL wrd_write_string( 't_window_v(' // dum // ')' )
     9023             WRITE ( 14 )  t_window_v(l)%t
     9024
     9025             CALL wrd_write_string( 't_green_v(' // dum // ')' )
     9026             WRITE ( 14 )  t_green_v(l)%t
     9027
     9028          ENDDO
     9029
     9030       ELSEIF ( TRIM( restart_data_format_output ) == 'mpi' )  THEN
     9031!
     9032!--       There is no information about the PE-grid necessary because the restart files consists
     9033!--       the whole domain. Therefore, ns_h_on_file_usm and ns_v_on_file_usm are not used with
     9034!--       MPI-IO.
     9035          CALL rd_mpi_io_surface_filetypes( surf_usm_h%start_index, surf_usm_h%end_index,          &
     9036                                            surface_data_to_write, global_start_index )
     9037
     9038          CALL wrd_mpi_io( 'usm_start_index_h',  surf_usm_h%start_index )
     9039          CALL wrd_mpi_io( 'usm_end_index_h', surf_usm_h%end_index )
     9040          CALL wrd_mpi_io( 'usm_global_start_h', global_start_index )
     9041
     9042          CALL wrd_mpi_io_surface( 't_surf_wall_h',  t_surf_wall_h )
     9043          CALL wrd_mpi_io_surface( 't_surf_window_h', t_surf_window_h )
     9044          CALL wrd_mpi_io_surface( 't_surf_green_h', t_surf_green_h )
     9045
     9046          CALL wrd_mpi_io_surface( 'm_liq_usm_h', m_liq_usm_h%var_usm_1d )
     9047          IF ( indoor_model )  THEN
     9048             CALL wrd_mpi_io_surface( 'waste_heat_h', surf_usm_h%waste_heat ) ! NEED TO BE CHECKED!!!!!
     9049          ENDIF
     9050
     9051          DO  l = 0, 3
     9052
     9053             WRITE( dum, '(I1)')  l
     9054
     9055             CALL rd_mpi_io_surface_filetypes( surf_usm_v(l)%start_index, surf_usm_v(l)%end_index, &
     9056                                               surface_data_to_write, global_start_index )
     9057
     9058             CALL wrd_mpi_io( 'usm_start_index_v_' // dum, surf_usm_v(l)%start_index )
     9059             CALL wrd_mpi_io( 'usm_end_index_v_' // dum, surf_usm_v(l)%end_index )
     9060             CALL wrd_mpi_io( 'usm_global_start_v_' // dum, global_start_index )
     9061
     9062             IF ( .NOT. surface_data_to_write )  CYCLE
     9063
     9064             CALL wrd_mpi_io_surface( 't_surf_wall_v(' // dum // ')', t_surf_wall_v(l)%t )
     9065             CALL wrd_mpi_io_surface( 't_surf_window_v(' // dum // ')', t_surf_window_v(l)%t )
     9066             CALL wrd_mpi_io_surface( 't_surf_green_v(' // dum // ')', t_surf_green_v(l)%t )
     9067
     9068          ENDDO
     9069
     9070          CALL rd_mpi_io_surface_filetypes( surf_usm_h%start_index, surf_usm_h%end_index,          &
     9071                                            surface_data_to_write, global_start_index )
     9072
     9073          CALL wrd_mpi_io( 'usm_start_index_h_2',  surf_usm_h%start_index )
     9074          CALL wrd_mpi_io( 'usm_end_index_h_2', surf_usm_h%end_index )
     9075          CALL wrd_mpi_io( 'usm_global_start_h_2', global_start_index )
     9076
     9077          CALL wrd_mpi_io_surface( 't_wall_h', t_wall_h )
     9078          CALL wrd_mpi_io_surface( 't_window_h', t_window_h )
     9079          CALL wrd_mpi_io_surface( 't_green_h', t_green_h )
     9080
     9081          DO  l = 0, 3
     9082
     9083             WRITE( dum, '(I1)')  l
     9084
     9085             CALL rd_mpi_io_surface_filetypes( surf_usm_v(l)%start_index, surf_usm_v(l)%end_index, &
     9086                                               surface_data_to_write, global_start_index )
     9087
     9088             CALL wrd_mpi_io( 'usm_start_index_v_2_' //dum, surf_usm_v(l)%start_index )
     9089             CALL wrd_mpi_io( 'usm_end_index_v_2_' // dum, surf_usm_v(l)%end_index )
     9090             CALL wrd_mpi_io( 'usm_global_start_v_2_' // dum, global_start_index )
     9091
     9092             IF ( .NOT. surface_data_to_write )  CYCLE
     9093
     9094             CALL wrd_mpi_io_surface( 't_wall_v(' // dum // ')', t_wall_v(l)%t )
     9095             CALL wrd_mpi_io_surface( 't_window_v(' // dum // ')', t_window_v(l)%t )
     9096             CALL wrd_mpi_io_surface( 't_green_v(' // dum // ')', t_green_v(l)%t )
     9097
     9098          ENDDO
     9099
     9100       ENDIF
     9101
     9102    END SUBROUTINE usm_wrd_local
    90189103     
    90199104     
Note: See TracChangeset for help on using the changeset viewer.