Ignore:
Timestamp:
Feb 11, 2019 1:06:27 PM (5 years ago)
Author:
suehring
Message:

Consider restart data in time-averaged surface output; revise error message; split initialization of surface-output module

File:
1 edited

Legend:

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

    r3728 r3731  
    2020! Current revisions:
    2121! ------------------
    22 !
     22! - Split initialization into initialization of arrays and further initialization
     23!   in order to enable reading of restart data.
     24! - Consider restarts in surface data averaging.
     25! - Correct error message numbers
    2326!
    2427! Former revisions:
     
    197200   END INTERFACE  surface_data_output_init
    198201   
     202   INTERFACE  surface_data_output_init_arrays
     203      MODULE PROCEDURE surface_data_output_init_arrays
     204   END INTERFACE  surface_data_output_init_arrays
     205   
    199206   INTERFACE  surface_data_output_last_action
    200207      MODULE PROCEDURE surface_data_output_last_action
     
    204211      MODULE PROCEDURE surface_data_output_parin
    205212   END INTERFACE  surface_data_output_parin
     213   
     214   INTERFACE  surface_data_output_rrd_global
     215      MODULE PROCEDURE surface_data_output_rrd_global
     216   END INTERFACE  surface_data_output_rrd_global
     217   
     218   INTERFACE  surface_data_output_rrd_local
     219      MODULE PROCEDURE surface_data_output_rrd_local
     220   END INTERFACE  surface_data_output_rrd_local
     221   
     222   INTERFACE  surface_data_output_wrd_global
     223      MODULE PROCEDURE surface_data_output_wrd_global
     224   END INTERFACE  surface_data_output_wrd_global
     225   
     226   INTERFACE  surface_data_output_wrd_local
     227      MODULE PROCEDURE surface_data_output_wrd_local
     228   END INTERFACE  surface_data_output_wrd_local
    206229
    207230!
     
    209232   PUBLIC surface_data_output, surface_data_output_averaging,                  &
    210233          surface_data_output_check_parameters, surface_data_output_init,      &
    211           surface_data_output_last_action, surface_data_output_parin
     234          surface_data_output_init_arrays, surface_data_output_last_action,    &
     235          surface_data_output_parin, surface_data_output_rrd_global,           &
     236          surface_data_output_rrd_local, surface_data_output_wrd_local,        &
     237          surface_data_output_wrd_global
    212238!
    213239!--Public variables
     
    217243 CONTAINS
    218244
     245!------------------------------------------------------------------------------!
     246! Description:
     247! ------------
     248!> This routine counts the number of surfaces on each core and allocates
     249!> arrays.
     250!------------------------------------------------------------------------------!
     251   SUBROUTINE surface_data_output_init_arrays
     252   
     253      IMPLICIT NONE
     254
     255!
     256!--   Determine the number of surface elements on subdomain
     257      surfaces%ns = surf_def_h(0)%ns + surf_lsm_h%ns + surf_usm_h%ns           & !horizontal upward-facing
     258                  + surf_def_h(1)%ns                                           & !horizontal downard-facing   
     259                  + surf_def_v(0)%ns + surf_lsm_v(0)%ns + surf_usm_v(0)%ns     & !northward-facing
     260                  + surf_def_v(1)%ns + surf_lsm_v(1)%ns + surf_usm_v(1)%ns     & !southward-facing   
     261                  + surf_def_v(2)%ns + surf_lsm_v(2)%ns + surf_usm_v(2)%ns     & !westward-facing   
     262                  + surf_def_v(3)%ns + surf_lsm_v(3)%ns + surf_usm_v(3)%ns       !eastward-facing   
     263!
     264!--    Determine the total number of surfaces in the model domain
     265#if defined( __parallel )
     266       CALL MPI_ALLREDUCE( surfaces%ns, surfaces%ns_total, 1,                  &
     267                           MPI_INTEGER, MPI_SUM, comm2d, ierr )
     268#else
     269       surfaces%ns_total = surfaces%ns
     270#endif
     271!
     272!--   Allocate output variable and set to _FillValue attribute
     273      ALLOCATE ( surfaces%var_out(1:surfaces%ns) )
     274      surfaces%var_out = surfaces%fillvalue
     275!
     276!--   If there is an output of time average output variables, allocate the
     277!--   required array.
     278      IF ( dosurf_no(1) > 0 )  THEN
     279         ALLOCATE ( surfaces%var_av(1:surfaces%ns,1:dosurf_no(1)) )
     280         surfaces%var_av = 0.0_wp
     281      ENDIF
     282     
     283   END SUBROUTINE surface_data_output_init_arrays
     284 
     285 
    219286!------------------------------------------------------------------------------!
    220287! Description:
     
    252319      REAL(wp), DIMENSION(:), ALLOCATABLE ::  netcdf_data_1d  !< dummy array to output 1D data into netcdf file
    253320
    254 
    255 !
    256 !--   Determine the number of surface elements on subdomain
    257       surfaces%ns = surf_def_h(0)%ns + surf_lsm_h%ns + surf_usm_h%ns           & !horizontal upward-facing
    258                   + surf_def_h(1)%ns                                           & !horizontal downard-facing   
    259                   + surf_def_v(0)%ns + surf_lsm_v(0)%ns + surf_usm_v(0)%ns     & !northward-facing
    260                   + surf_def_v(1)%ns + surf_lsm_v(1)%ns + surf_usm_v(1)%ns     & !southward-facing   
    261                   + surf_def_v(2)%ns + surf_lsm_v(2)%ns + surf_usm_v(2)%ns     & !westward-facing   
    262                   + surf_def_v(3)%ns + surf_lsm_v(3)%ns + surf_usm_v(3)%ns       !eastward-facing   
    263 !
    264 !--    Determine the total number of surfaces in the model domain
    265 #if defined( __parallel )
    266        CALL MPI_ALLREDUCE( surfaces%ns, surfaces%ns_total, 1,                  &
    267                            MPI_INTEGER, MPI_SUM, comm2d, ierr )
    268 #else
    269        surfaces%ns_total = surfaces%ns
    270 #endif
    271 !
    272 !--   Allocate output variable and set to _FillValue attribute
    273       ALLOCATE ( surfaces%var_out(1:surfaces%ns) )
    274       surfaces%var_out = surfaces%fillvalue
    275 !
    276 !--   If there is an output of time average output variables, allocate the
    277 !--   required array.
    278       IF ( dosurf_no(1) > 0 )  THEN
    279          ALLOCATE ( surfaces%var_av(1:surfaces%ns,1:dosurf_no(1)) )
    280          surfaces%var_av = 0.0_wp
    281       ENDIF
    282321!
    283322!--   If output to VTK format is enabled, initialize point and polygon data.
     
    13331372                                        time_since_reference_point, 's because the maximum ', &
    13341373                                        'number of output time levels is exceeded.'
    1335             CALL message( 'surface_data_output', 'PA0???', 0, 1, 0, 6, 0 )
     1374            CALL message( 'surface_data_output', 'PA0539', 0, 1, 0, 6, 0 )
    13361375           
    13371376            RETURN
     
    40514090
    40524091       USE control_parameters,                                                 &
    4053            ONLY:  averaging_interval, dt_data_output, message_string
     4092           ONLY:  averaging_interval, dt_data_output, initializing_actions,    &
     4093                  message_string
     4094                 
     4095       USE pegrid,                                                             &
     4096           ONLY:  numprocs_previous_run
    40544097
    40554098       IMPLICIT NONE
     
    40774120                dt_dosurf_av
    40784121          CALL message( 'surface_data_output_check_parameters',                &
    4079                         'PA0087', 1, 2, 0, 6, 0 )
     4122                        'PA0536', 1, 2, 0, 6, 0 )
    40804123       ENDIF
    40814124       
     
    40894132       ENDIF
    40904133#endif
     4134!
     4135!--   In case of restart runs, check it the number of cores has been changed.
     4136!--   With surface output this is not allowed.
     4137      IF ( TRIM( initializing_actions ) == 'read_restart_data'  .AND.          &
     4138           numprocs_previous_run /= numprocs ) THEN
     4139         message_string = 'The number of cores has been changed between ' //   &
     4140                          'restart runs. This is not allowed when surface ' // &
     4141                          'data output is used.'
     4142          CALL message( 'surface_data_output_check_parameters',                &
     4143                        'PA0585', 1, 2, 0, 6, 0 )
     4144      ENDIF
    40914145!
    40924146!--   Count number of output variables and separate output strings for
     
    41214175                             ' is not yet implemented in the surface output'
    41224176               CALL message( 'surface_data_output_check_parameters',           &
    4123                              'PA0087', 1, 2, 0, 6, 0 )
     4177                             'PA0537', 1, 2, 0, 6, 0 )
    41244178
    41254179            CASE ( 'us', 'uvw1' )
     
    41734227                             ' is not part of the surface output'
    41744228               CALL message( 'surface_data_output_check_parameters',           &
    4175                              'PA0087', 1, 2, 0, 6, 0 )
     4229                             'PA0538', 1, 2, 0, 6, 0 )
    41764230         END SELECT
    41774231
     
    42234277
    42244278    END SUBROUTINE surface_data_output_last_action   
     4279   
     4280!------------------------------------------------------------------------------!
     4281! Description:
     4282! ------------
     4283!> This routine reads globally used restart data.
     4284!------------------------------------------------------------------------------!
     4285    SUBROUTINE surface_data_output_rrd_global( found )
     4286
     4287
     4288       USE control_parameters,                                                 &
     4289           ONLY: length, restart_string
     4290       
     4291       IMPLICIT NONE
     4292       
     4293       LOGICAL, INTENT(OUT)  ::  found !< flag indicating if variable was found
     4294       
     4295       found = .TRUE.
     4296       
     4297       SELECT CASE ( restart_string(1:length) )
     4298       
     4299          CASE ( 'average_count_surf' )
     4300             READ ( 13 )  average_count_surf
     4301       
     4302          CASE DEFAULT
     4303       
     4304             found = .FALSE.
     4305       
     4306       END SELECT
     4307
     4308
     4309    END SUBROUTINE surface_data_output_rrd_global
     4310   
     4311!------------------------------------------------------------------------------!
     4312! Description:
     4313! ------------
     4314!> This routine reads the respective restart data.
     4315!------------------------------------------------------------------------------!
     4316    SUBROUTINE surface_data_output_rrd_local( i, k, nxlf, nxlc, nxl_on_file,   &
     4317                              nxrf, nxrc, nxr_on_file, nynf, nync, nyn_on_file,&
     4318                              nysf, nysc, nys_on_file, found )
     4319
     4320
     4321       USE control_parameters,                                                 &
     4322           ONLY: length, restart_string
     4323           
     4324       IMPLICIT NONE
     4325
     4326       INTEGER(iwp)       ::  l                 !< index variable for surface type
     4327       INTEGER(iwp)       ::  i                 !< running index over input files
     4328       INTEGER(iwp)       ::  k                 !< running index over previous input files covering current local domain
     4329       INTEGER(iwp)       ::  ns_h_on_file_usm  !< number of horizontal surface elements (urban type) on file
     4330       INTEGER(iwp)       ::  nxlc              !< index of left boundary on current subdomain
     4331       INTEGER(iwp)       ::  nxlf              !< index of left boundary on former subdomain
     4332       INTEGER(iwp)       ::  nxl_on_file       !< index of left boundary on former local domain
     4333       INTEGER(iwp)       ::  nxrc              !< index of right boundary on current subdomain
     4334       INTEGER(iwp)       ::  nxrf              !< index of right boundary on former subdomain
     4335       INTEGER(iwp)       ::  nxr_on_file       !< index of right boundary on former local domain
     4336       INTEGER(iwp)       ::  nync              !< index of north boundary on current subdomain
     4337       INTEGER(iwp)       ::  nynf              !< index of north boundary on former subdomain
     4338       INTEGER(iwp)       ::  nyn_on_file       !< index of north boundary on former local domain
     4339       INTEGER(iwp)       ::  nysc              !< index of south boundary on current subdomain
     4340       INTEGER(iwp)       ::  nysf              !< index of south boundary on former subdomain
     4341       INTEGER(iwp)       ::  nys_on_file       !< index of south boundary on former local domain
     4342
     4343       LOGICAL, INTENT(OUT)  ::  found
     4344!
     4345!--    Here the reading of user-defined restart data follows:
     4346!--    Sample for user-defined output
     4347       found = .TRUE.
     4348
     4349       SELECT CASE ( restart_string(1:length) )
     4350
     4351          CASE ( 'surfaces%var_av' )
     4352             IF ( k == 1 )  READ ( 13 )  surfaces%var_av
     4353             
     4354          CASE DEFAULT
     4355
     4356             found = .FALSE.
     4357
     4358          END SELECT
     4359
     4360
     4361    END SUBROUTINE surface_data_output_rrd_local
     4362   
     4363!------------------------------------------------------------------------------!
     4364! Description:
     4365! ------------
     4366!> This routine writes the respective restart data.
     4367!------------------------------------------------------------------------------!
     4368    SUBROUTINE surface_data_output_wrd_global
     4369
     4370       IMPLICIT NONE
     4371
     4372       CALL wrd_write_string( 'average_count_surf' )
     4373       WRITE ( 14 )  average_count_surf
     4374
     4375    END SUBROUTINE surface_data_output_wrd_global
     4376   
     4377!------------------------------------------------------------------------------!
     4378! Description:
     4379! ------------
     4380!> This routine writes restart data which individual on each PE
     4381!------------------------------------------------------------------------------!
     4382    SUBROUTINE surface_data_output_wrd_local
     4383
     4384       IMPLICIT NONE
     4385
     4386         IF ( ALLOCATED( surfaces%var_av ) )  THEN
     4387            CALL wrd_write_string( 'surfaces%var_av' )
     4388            WRITE ( 14 )  surfaces%var_av
     4389         ENDIF
     4390
     4391
     4392    END SUBROUTINE surface_data_output_wrd_local
    42254393
    42264394
Note: See TracChangeset for help on using the changeset viewer.