Changeset 4356 for palm


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

Location:
palm/trunk/SOURCE
Files:
7 edited

Legend:

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

    r4242 r4356  
    2727! -----------------
    2828! $Id$
     29! Minor formatting adjustment
     30!
     31! 4242 2019-09-27 12:59:10Z suehring
    2932! Adjust index_hh access to new definition accompanied with new
    3033! palm_date_time_mod. Note, this is just a preleminary fix. (E Chan)
     
    934937        ONLY: days_per_week, get_date_time, hours_per_day, months_per_year, seconds_per_day
    935938   
    936  IMPLICIT NONE
     939    IMPLICIT NONE
    937940 
    938941
  • palm/trunk/SOURCE/init_grid.f90

    r4346 r4356  
    2525! -----------------
    2626! $Id$
     27! Revise error messages for generic tunnel setup.
     28!
     29! 4346 2019-12-18 11:55:56Z motisi
    2730! Introduction of wall_flags_total_0, which currently sets bits based on static
    2831! topography information used in wall_flags_static_0
     
    20732076          ENDIF
    20742077!
    2075 !--       Tunnel axis along y
     2078!--       Check for too small tunnel width in x- and y-direction
     2079          IF ( tunnel_width_x /= 9999999.9_wp  .AND.                           &   
     2080               tunnel_width_x - 2.0_wp * td <= 2.0_wp * dx )  THEN
     2081             message_string = 'tunnel_width_x too small'
     2082             CALL message( 'init_grid', 'PA0175', 1, 2, 0, 6, 0 )
     2083          ENDIF
     2084          IF ( tunnel_width_y /= 9999999.9_wp  .AND.                           &
     2085               tunnel_width_y - 2.0_wp * td <= 2.0_wp * dy )  THEN
     2086             message_string = 'tunnel_width_y too small'
     2087             CALL message( 'init_grid', 'PA0455', 1, 2, 0, 6, 0 )
     2088          ENDIF
     2089!
     2090!--       Check for too large tunnel width.
     2091!--       Tunnel axis along y.
    20762092          IF ( tunnel_width_x /= 9999999.9_wp )  THEN
    20772093             IF ( tunnel_width_x > ( nx + 1 ) * dx )  THEN
    2078                 message_string = 'Tunnel width too large'
     2094                message_string = 'tunnel_width_x too large'
    20792095                CALL message( 'init_grid', 'PA0282', 1, 2, 0, 6, 0 )
    20802096             ENDIF
     
    20922108             tye_in  = tye_out
    20932109          ENDIF
    2094           IF ( tunnel_width_x /= 9999999.9_wp  .AND.                           &   
    2095                tunnel_width_x - 2.0_wp * td <= 2.0_wp * dx )                   &
    2096           THEN
    2097              message_string = 'Tunnel width too small'
    2098              CALL message( 'init_grid', 'PA0175', 1, 2, 0, 6, 0 )
    2099           ENDIF
    2100           IF ( tunnel_width_y /= 9999999.9_wp  .AND.                           &
    2101                tunnel_width_y - 2.0_wp * td <= 2.0_wp * dy )                   &
    2102           THEN
    2103              message_string = 'Tunnel width too small'
    2104              CALL message( 'init_grid', 'PA0455', 1, 2, 0, 6, 0 )
    2105           ENDIF
    2106 !
    2107 !--       Tunnel axis along x
     2110!
     2111!--       Tunnel axis along x.
    21082112          IF ( tunnel_width_y /= 9999999.9_wp )  THEN
    21092113             IF ( tunnel_width_y > ( ny + 1 ) * dy )  THEN
    2110                 message_string = 'Tunnel width too large'
     2114                message_string = 'tunnel_width_y too large'
    21112115                CALL message( 'init_grid', 'PA0456', 1, 2, 0, 6, 0 )
    21122116             ENDIF
  • palm/trunk/SOURCE/land_surface_model_mod.f90

    r4339 r4356  
    2525! -----------------
    2626! $Id$
     27! Correct single message calls, local checks must be given by the respective
     28! mpi rank.
     29!
     30! 4339 2019-12-13 18:18:30Z suehring
    2731! Bugfix, character length too short, caused crash on NEC.
    2832!
     
    48564860          message_string = 'For non-pavement surfaces the combination ' //     &
    48574861                           ' lai = 0.0 and c_veg = 1.0 is not allowed.'
    4858           CALL message( 'lsm_rrd_local', 'PA0671', 2, 2, 0, 6, 0 )
     4862          CALL message( 'lsm_rrd_local', 'PA0671', 2, 2, myid, 6, 0 )
    48594863       ENDIF
    48604864
     
    48654869             message_string = 'For non-pavement surfaces the combination ' //  &
    48664870                              ' lai = 0.0 and c_veg = 1.0 is not allowed.'
    4867              CALL message( 'lsm_rrd_local', 'PA0671', 2, 2, 0, 6, 0 )
     4871             CALL message( 'lsm_rrd_local', 'PA0671', 2, 2, myid, 6, 0 )
    48684872          ENDIF
    48694873       ENDDO
  • palm/trunk/SOURCE/netcdf_data_input_mod.f90

    r4346 r4356  
    2525! -----------------
    2626! $Id$
     27! Correct single message calls, local checks must be given by the respective
     28! mpi rank.
     29!
     30! 4346 2019-12-18 11:55:56Z motisi
    2731! Introduction of wall_flags_total_0, which currently sets bits based on static
    2832! topography information used in wall_flags_static_0
     
    34953499                message_string = 'If vegetation_type = 0 at any location, ' // &
    34963500                                 'vegetation_pars is required'
    3497                 CALL message( 'netcdf_data_input_mod', 'PA0555', 2, 2, -1, 6, 0 )
     3501                CALL message( 'netcdf_data_input_mod', 'PA0555', 2, 2, myid, 6, 0 )
    34983502             ENDIF
    34993503             IF ( .NOT. root_area_density_lsm_f%from_file )  THEN
     
    35283532          message_string = 'If buildings are provided, also building_type ' // &
    35293533                           'is required'
    3530           CALL message( 'netcdf_data_input_mod', 'PA0581', 2, 2, myid, 6, 0 )
     3534          CALL message( 'netcdf_data_input_mod', 'PA0581', 2, 2, 0, 6, 0 )
    35313535       ENDIF
    35323536!
     
    35353539          message_string = 'If buildings are provided, also building_id ' //   &
    35363540                           'is required'
    3537           CALL message( 'netcdf_data_input_mod', 'PA0582', 2, 2, myid, 6, 0 )
     3541          CALL message( 'netcdf_data_input_mod', 'PA0582', 2, 2, 0, 6, 0 )
    35383542       ENDIF
    35393543!
     
    35553559          message_string = 'If building_type is provided, also building_id '// &
    35563560                           'is required'
    3557           CALL message( 'netcdf_data_input_mod', 'PA0519', 2, 2, myid, 6, 0 )
     3561          CALL message( 'netcdf_data_input_mod', 'PA0519', 2, 2, 0, 6, 0 )
    35583562       ENDIF       
    35593563!
     
    48384842                   'non-building coordinates (xs, ys, zenith, azimuth): ',   &
    48394843                   xs(isurf), ys(isurf), zenith(isurf), azimuth(isurf)
    4840                 CALL message( 'get_variable_surf', 'PA0684', 2, 2, 0, 6, 0 )
     4844                CALL message( 'get_variable_surf', 'PA0684', 2, 2, myid, 6, 0 )
    48414845             ENDIF
    48424846!
  • palm/trunk/SOURCE/plant_canopy_model_mod.f90

    r4346 r4356  
    2727! -----------------
    2828! $Id$
     29! Correct single message call, local check must be given by the respective
     30! mpi rank.
     31!
     32! 4346 2019-12-18 11:55:56Z motisi
    2933! Introduction of wall_flags_total_0, which currently sets bits based on static
    3034! topography information used in wall_flags_static_0
     
    11261130!--          Check whether topography and local vegetation on top exceed
    11271131!--          height of the model domain.
    1128              k = topo_top_ind(j,i,0)
    1129              IF ( k + pch_index_ji(j,i) >= nzt + 1 )  THEN
     1132             IF ( topo_top_ind(j,i,0) + pch_index_ji(j,i) >= nzt + 1 )  THEN
    11301133                message_string =  'Local vegetation height on top of ' //      &
    11311134                                  'topography exceeds height of model domain.'
    1132                 CALL message( 'pcm_init', 'PA0674', 2, 2, 0, 6, 0 )
     1135                CALL message( 'pcm_init', 'PA0674', 2, 2, myid, 6, 0 )
    11331136             ENDIF
    11341137
  • 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
  • palm/trunk/SOURCE/time_integration.f90

    r4346 r4356  
    2525! -----------------
    2626! $Id$
     27! Bugfix, hour_call_emis uninitialized at first call of time_integration
     28!
     29! 4346 2019-12-18 11:55:56Z motisi
    2730! Introduction of wall_flags_total_0, which currently sets bits based on static
    2831! topography information used in wall_flags_static_0
     
    390393    CHARACTER (LEN=9) ::  time_to_string   !<
    391394
    392     INTEGER(iwp) ::  hour            !< hour of current time
    393     INTEGER(iwp) ::  hour_call_emis !< last hour where emission was called
    394     INTEGER(iwp) ::  ib              !< index for aerosol size bins
    395     INTEGER(iwp) ::  ic              !< index for aerosol mass bins
    396     INTEGER(iwp) ::  icc             !< additional index for aerosol mass bins
    397     INTEGER(iwp) ::  ig              !< index for salsa gases
    398     INTEGER(iwp) ::  lsp             !<
    399     INTEGER(iwp) ::  lsp_usr         !<
    400     INTEGER(iwp) ::  mid             !< masked output running index
    401     INTEGER(iwp) ::  n               !< loop counter for chemistry species
     395    INTEGER(iwp) ::  hour                !< hour of current time
     396    INTEGER(iwp) ::  hour_call_emis = -1 !< last hour where emission was called
     397    INTEGER(iwp) ::  ib                  !< index for aerosol size bins
     398    INTEGER(iwp) ::  ic                  !< index for aerosol mass bins
     399    INTEGER(iwp) ::  icc                 !< additional index for aerosol mass bins
     400    INTEGER(iwp) ::  ig                  !< index for salsa gases
     401    INTEGER(iwp) ::  lsp                 !<
     402    INTEGER(iwp) ::  lsp_usr             !<
     403    INTEGER(iwp) ::  mid                 !< masked output running index
     404    INTEGER(iwp) ::  n                   !< loop counter for chemistry species
    402405
    403406    REAL(wp) ::  dt_3d_old  !< temporary storage of timestep to be used for
Note: See TracChangeset for help on using the changeset viewer.