Ignore:
Timestamp:
Dec 20, 2019 5:09:33 PM (4 years ago)
Author:
suehring
Message:

Bugfix in message calls for local checks; error messages in init_grid slightly revised; bugfix in time_integration (uninitialized emission time index); read_restart_data (change from J.Resler): use dynamic array allocation rather than automatic arrays to avoid problems with stack memory

File:
1 edited

Legend:

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

    r4331 r4356  
    2525! -----------------
    2626! $Id$
     27! Change automatic arrays to allocatable ones in rrd_local, in order to avoid
     28! memory problems due to too small stack size for large jobs with intel
     29! compiler. (J.Resler)
     30!
     31! 4331 2019-12-10 18:25:02Z suehring
    2732! Enable restart data for 2-m potential temperature output
    2833!
     
    10501055    INTEGER(iwp), DIMENSION(numprocs_previous_run) ::  overlap_count   !<
    10511056
    1052     INTEGER(iwp), DIMENSION(numprocs_previous_run,1000) ::  nxlfa      !<
    1053     INTEGER(iwp), DIMENSION(numprocs_previous_run,1000) ::  nxrfa      !<
    1054     INTEGER(iwp), DIMENSION(numprocs_previous_run,1000) ::  nynfa      !<
    1055     INTEGER(iwp), DIMENSION(numprocs_previous_run,1000) ::  nysfa      !<
    1056     INTEGER(iwp), DIMENSION(numprocs_previous_run,1000) ::  offset_xa  !<
    1057     INTEGER(iwp), DIMENSION(numprocs_previous_run,1000) ::  offset_ya  !<
     1057    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  nxlfa      !<
     1058    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  nxrfa      !<
     1059    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  nynfa      !<
     1060    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  nysfa      !<
     1061    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  offset_xa  !<
     1062    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE ::  offset_ya  !<
    10581063
    10591064    INTEGER(isp), DIMENSION(:,:),   ALLOCATABLE ::  tmp_2d_id_random   !< temporary array for storing random generator data
     
    10701075!-- Read data from previous model run.
    10711076    CALL cpu_log( log_point_s(14), 'rrd_local', 'start' )
     1077!
     1078!-- Allocate temporary buffer arrays. In previous versions, there were
     1079!-- declared as automated arrays, causing memory problems when these
     1080!-- were allocate on stack.
     1081    ALLOCATE( nxlfa(numprocs_previous_run,1000) )
     1082    ALLOCATE( nxrfa(numprocs_previous_run,1000) )
     1083    ALLOCATE( nynfa(numprocs_previous_run,1000) )
     1084    ALLOCATE( nysfa(numprocs_previous_run,1000) )
     1085    ALLOCATE( offset_xa(numprocs_previous_run,1000) )
     1086    ALLOCATE( offset_ya(numprocs_previous_run,1000) )
    10721087
    10731088!
     
    17931808
    17941809       ENDDO ! dataloop
    1795 
    17961810!
    17971811!--    Close the restart file
     
    18011815
    18021816    ENDDO  ! loop over restart files
    1803 
     1817!
     1818!-- Deallocate temporary buffer arrays
     1819    DEALLOCATE( nxlfa )
     1820    DEALLOCATE( nxrfa )
     1821    DEALLOCATE( nynfa )
     1822    DEALLOCATE( nysfa )
     1823    DEALLOCATE( offset_xa )
     1824    DEALLOCATE( offset_ya )
    18041825!
    18051826!-- Restore the original filename for the restart file to be written
Note: See TracChangeset for help on using the changeset viewer.