Changeset 4429


Ignore:
Timestamp:
Feb 27, 2020 3:24:30 PM (4 years ago)
Author:
raasch
Message:

serial (non-MPI) test case added, several bugfixes for the serial mode

Location:
palm/trunk
Files:
11 added
14 edited

Legend:

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

    r4360 r4429  
    2525! -----------------
    2626! $Id$
     27! bugfix: cpp-directives added for serial mode
     28!
     29! 4360 2020-01-07 11:25:50Z suehring
    2730! Corrected "Former revisions" section
    2831!
     
    104107       INTEGER(iwp) ::  j         !<
    105108       INTEGER(iwp) ::  k         !<
     109       INTEGER(iwp) ::  sr        !<
     110#if defined( __parallel )
    106111       INTEGER(iwp) ::  ngp       !<
    107        INTEGER(iwp) ::  sr        !<
    108112       INTEGER(iwp) ::  type_xz_2 !<
     113#endif
    109114
    110115       REAL(wp) ::  cim    !<
  • palm/trunk/SOURCE/cpulog_mod.f90

    r4378 r4429  
    2525! -----------------
    2626! $Id$
     27! bugfix: cpp-directives added for serial mode
     28!
     29! 4378 2020-01-16 13:22:48Z Giersch
    2730! Format of rms output changed to allow values >= 100
    2831!
     
    263266       INTEGER(iwp)    ::  i               !<
    264267       INTEGER(iwp)    ::  ii(1)           !<
     268#if defined( __parallel )
    265269       INTEGER(iwp)    ::  iii             !<
    266        INTEGER(iwp)    ::  sender          !<
     270       INTEGER(iwp)    ::  sender          !<
     271#endif
    267272       REAL(dp)       ::  average_cputime  !<
    268273       REAL(dp), SAVE ::  norm = 1.0_dp    !<
  • palm/trunk/SOURCE/data_output_netcdf4_module.f90

    r4408 r4429  
    2525! -----------------
    2626! $Id$
     27! bugfix: cpp-directive moved to avoid compile error due to unused dummy argument
     28!
     29! 4408 2020-02-14 10:04:39Z gronemeier
    2730! Enable character-array output
    2831!
     
    427430       nc_stat = NF90_DEF_VAR( file_id, variable_name, nc_variable_type, dimension_ids, variable_id )
    428431
    429 #if defined( __netcdf4_parallel )
    430432!
    431433!--    Define how variable can be accessed by PEs in parallel netcdf file
    432434       IF ( nc_stat == NF90_NOERR  .AND.  TRIM( mode ) == mode_parallel )  THEN
     435#if defined( __netcdf4_parallel )
    433436          IF ( is_global )  THEN
    434437             nc_stat = NF90_VAR_PAR_ACCESS( file_id, variable_id, NF90_INDEPENDENT )
     
    436439             nc_stat = NF90_VAR_PAR_ACCESS( file_id, variable_id, NF90_COLLECTIVE )
    437440          ENDIF
     441#else
     442          CONTINUE
     443#endif
    438444       ENDIF
    439 #endif
    440445
    441446       IF ( nc_stat /= NF90_NOERR )  THEN
  • palm/trunk/SOURCE/exchange_horiz.f90

    r4360 r4429  
    2525! -----------------
    2626! $Id$
     27! bugfix: cpp-directives added for serial mode
     28!
     29! 4360 2020-01-07 11:25:50Z suehring
    2730! Corrected "Former revisions" section
    2831!
     
    4649
    4750    USE control_parameters,                                                    &
    48         ONLY:  bc_lr_cyc, bc_ns_cyc, grid_level, mg_switch_to_pe0, synchronous_exchange
     51        ONLY:  bc_lr_cyc, bc_ns_cyc
     52
     53#if defined( __parallel )
     54    USE control_parameters,                                                    &
     55        ONLY:  grid_level, mg_switch_to_pe0, synchronous_exchange
     56#endif
    4957               
    5058    USE cpulog,                                                                &
     
    272280!> @todo Missing subroutine description.
    273281!------------------------------------------------------------------------------!
    274  SUBROUTINE exchange_horiz_int( ar, nys_l, nyn_l, nxl_l, nxr_l, nzt_l, nbgp_local)
     282 SUBROUTINE exchange_horiz_int( ar, nys_l, nyn_l, nxl_l, nxr_l, nzt_l, nbgp_local )
     283
    275284
    276285    USE control_parameters,                                                    &
    277         ONLY:  bc_lr_cyc, bc_ns_cyc, grid_level
     286        ONLY:  bc_lr_cyc, bc_ns_cyc
     287
     288#if defined( __parallel )
     289    USE control_parameters,                                                    &
     290        ONLY:  grid_level
     291#endif
    278292                       
    279293    USE indices,                                                               &
  • palm/trunk/SOURCE/global_min_max.f90

    r4360 r4429  
    2525! -----------------
    2626! $Id$
     27! bugfix: cpp-directives added for serial mode
     28!
     29! 4360 2020-01-07 11:25:50Z suehring
    2730! OpenACC support added
    2831!
     
    5962    INTEGER(iwp) ::  i1             !<
    6063    INTEGER(iwp) ::  i2             !<
     64#if defined( __parallel )
    6165    INTEGER(iwp) ::  id_fmax        !<
    6266    INTEGER(iwp) ::  id_fmin        !<
     67#endif
    6368    INTEGER(iwp) ::  j              !<
    6469    INTEGER(iwp) ::  j1             !<
  • palm/trunk/SOURCE/inflow_turbulence.f90

    r4360 r4429  
    2525! -----------------
    2626! $Id$
     27! bugfix: cpp-directives added for serial mode
     28!
     29! 4360 2020-01-07 11:25:50Z suehring
    2730! use y_shift instead of old parameter recycling_yshift
    2831!
     
    5760        ONLY:  e, inflow_damping_factor, mean_inflow_profiles, pt, q, s, u, v, w
    5861       
     62#if defined( __parallel )
    5963    USE control_parameters,                                                    &
    60         ONLY:  humidity, passive_scalar, recycling_plane, y_shift,    &
     64        ONLY:  humidity, passive_scalar, recycling_plane, y_shift,             &
    6165               recycling_method_for_thermodynamic_quantities
     66#else
     67    USE control_parameters,                                                    &
     68        ONLY:  humidity, passive_scalar, recycling_plane,                      &
     69               recycling_method_for_thermodynamic_quantities
     70#endif
    6271       
    6372    USE cpulog,                                                                &
     
    7887    INTEGER(iwp) ::  k        !< loop index
    7988    INTEGER(iwp) ::  l        !< loop index
    80     INTEGER(iwp) ::  next     !< ID of receiving PE for y-shift
    8189    INTEGER(iwp) ::  ngp_ifd  !< number of grid points stored in avpr
    8290    INTEGER(iwp) ::  ngp_pr   !< number of grid points stored in inflow_dist
     91#if defined( __parallel )
     92    INTEGER(iwp) ::  next     !< ID of receiving PE for y-shift
    8393    INTEGER(iwp) ::  prev     !< ID of sending PE for y-shift
     94#endif
    8495
    8596    REAL(wp), DIMENSION(nzb:nzt+1,7,nbgp)           ::                         &
     
    89100    REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,7,nbgp) ::                         &
    90101       inflow_dist        !< turbulence signal of vars, added at inflow boundary
     102#if defined( __parallel )
    91103    REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,7,nbgp) ::                         &
    92104       local_inflow_dist  !< auxiliary variable for inflow_dist, used for y-shift
     105#endif
    93106   
    94107    CALL cpu_log( log_point(40), 'inflow_turbulence', 'start' )
  • palm/trunk/SOURCE/land_surface_model_mod.f90

    r4381 r4429  
    2525! -----------------
    2626! $Id$
     27! bugfix: missing cpp-directives for serial mode added, misplaced cpp-directives moved
     28!
     29! 4381 2020-01-20 13:51:46Z suehring
    2730! - Bugfix in nested soil initialization in case no dynamic input file is
    2831!   present
     
    23322335           ONLY:  nx, ny, topo_min_level
    23332336
     2337#if defined( __parallel )
    23342338       USE pmc_handle_communicator,                                            &
    23352339        ONLY:  pmc_is_rootmodel
     2340#endif
    23362341           
    23372342       USE pmc_interface,                                                      &
     
    44474452                DEALLOCATE( t_soil_root )
    44484453             ENDIF
    4449           ENDIF
    44504454#endif
     4455          ENDIF
    44514456!
    44524457!--       Proceed with Level 2 initialization.
  • palm/trunk/SOURCE/poisfft_mod.f90

    r4366 r4429  
    2525! -----------------
    2626! $Id$
     27! Statements added to avoid compile errors due to unused dummy arguments in serial mode
     28!
     29! 4366 2020-01-09 08:12:43Z raasch
    2730! modification concerning NEC vectorizatio
    2831!
     
    780783                          comm1dx, ierr )
    781784       CALL cpu_log( log_point_s(32), 'mpi_alltoall', 'stop' )
     785#else
     786!
     787!--    Next line required to avoid compile error about unused dummy argument in serial mode
     788       i = SIZE( f_out )
    782789#endif
    783790
     
    830837                          comm1dx, ierr )
    831838       CALL cpu_log( log_point_s(32), 'mpi_alltoall', 'stop' )
     839#else
     840!
     841!--    Next line required to avoid compile error about unused dummy argument in serial mode
     842       i = SIZE( f_in )
    832843#endif
    833844
     
    11721183                          comm1dy, ierr )
    11731184       CALL cpu_log( log_point_s(32), 'mpi_alltoall', 'stop' )
     1185#else
     1186!
     1187!--    Next line required to avoid compile error about unused dummy argument in serial mode
     1188       i = SIZE( f_out )
    11741189#endif
    11751190
     
    12061221       REAL(wp), DIMENSION(1:nz,nys:nyn,0:nx)             ::  f_out      !<
    12071222       REAL(wp), DIMENSION(nys:nyn,1:nz,0:nx)             ::  work       !<
     1223
    12081224
    12091225!
     
    12161232                          comm1dy, ierr )
    12171233       CALL cpu_log( log_point_s(32), 'mpi_alltoall', 'stop' )
     1234#else
     1235!
     1236!--    Next line required to avoid compile error about unused dummy argument in serial mode
     1237       i = SIZE( f_in )
    12181238#endif
    12191239
  • palm/trunk/SOURCE/poismg_mod.f90

    r4360 r4429  
    2525! -----------------
    2626! $Id$
     27! statement added to avoid compile error due to unused dummy argument
     28! bugfix: cpp-directives added for serial mode
     29!
     30! 4360 2020-01-07 11:25:50Z suehring
    2731! Corrected "Former revisions" section
    2832!
     
    12101214!> Gather subdomain data from all PEs.
    12111215!------------------------------------------------------------------------------!
     1216#if defined( __parallel )
    12121217    SUBROUTINE mg_gather( f2, f2_sub )
    12131218
     
    12441249
    12451250
    1246 #if defined( __parallel )
    12471251       CALL cpu_log( log_point_s(34), 'mg_gather', 'start' )
    12481252
     
    12791283
    12801284       CALL cpu_log( log_point_s(34), 'mg_gather', 'stop' )
    1281 #endif
    12821285   
    12831286    END SUBROUTINE mg_gather
    1284 
     1287#endif
    12851288
    12861289
     
    12911294!>       non-blocking communication
    12921295!------------------------------------------------------------------------------!
     1296#if defined( __parallel )
    12931297    SUBROUTINE mg_scatter( p2, p2_sub )
    12941298
     
    13031307
    13041308       IMPLICIT NONE
    1305 
    1306        INTEGER(iwp) ::  nwords  !<
    13071309
    13081310       REAL(wp), DIMENSION(nzb:nzt_mg(grid_level-1)+1,                         &
     
    13141316                           mg_loc_ind(1,myid)-1:mg_loc_ind(2,myid)+1) ::  p2_sub  !<
    13151317
    1316 !
    1317 !--    Find out the number of array elements of the subdomain array
    1318        nwords = SIZE( p2_sub )
    1319 
    1320 #if defined( __parallel )
     1318
    13211319       CALL cpu_log( log_point_s(35), 'mg_scatter', 'start' )
    13221320
     
    13251323
    13261324       CALL cpu_log( log_point_s(35), 'mg_scatter', 'stop' )
    1327 #endif
    13281325   
    13291326    END SUBROUTINE mg_scatter
    1330 
     1327#endif
    13311328
    13321329!------------------------------------------------------------------------------!
     
    13831380
    13841381       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  f2_sub  !<
     1382
     1383#if defined( __parallel )
    13851384       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  p2_sub  !<
     1385#endif
    13861386
    13871387!
     
    14721472!
    14731473!--          Gather all arrays from the subdomains on PE0
     1474#if defined( __parallel )
    14741475             CALL mg_gather( f2, f2_sub )
     1476#endif
    14751477
    14761478!
     
    17601762
    17611763       USE control_parameters,                                                 &
    1762            ONLY:  grid_level, mg_switch_to_pe0_level, synchronous_exchange
     1764           ONLY:  grid_level
     1765
     1766#if defined( __parallel )
     1767       USE control_parameters,                                                 &
     1768           ONLY:  mg_switch_to_pe0_level, synchronous_exchange
     1769#endif
    17631770
    17641771       USE indices,                                                            &
    1765            ONLY:  nxl, nxl_mg, nxr, nxr_mg, nys, nys_mg, nyn,      &
    1766                   nyn_mg, nzb, nzt, nzt_mg
     1772           ONLY:  nxl_mg, nxr_mg, nys_mg, nyn_mg, nzb, nzt_mg
     1773
     1774#if defined( __parallel )
     1775       USE indices,                                                            &
     1776           ONLY:  nxl, nxr, nys, nyn, nzt
     1777#endif
    17671778
    17681779       IMPLICIT NONE
     
    17731784                                    p_mg   !< treated array
    17741785
    1775        INTEGER(iwp), intent(IN) ::  color  !< flag for grid point type (red or black)
     1786       INTEGER(iwp), INTENT(IN) ::  color  !< flag for grid point type (red or black)
     1787
     1788#if defined ( __parallel )
    17761789!
    17771790!--    Local variables
     
    17941807       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  temp  !< temporary array on next coarser grid level
    17951808
    1796 #if defined ( __parallel )
    17971809       synchronous_exchange_save   = synchronous_exchange
    17981810       synchronous_exchange        = .FALSE.
     
    22612273
    22622274                IF ( i == nxl_mg(l) )  THEN
    2263                    !DIR$ IVDEP
     2275                   !DIR$ IVDEP       INTEGER(iwp) ::  ngp       !<
     2276
    22642277                   DO  k = nzb+1, ind_even_odd
    22652278                      p_mg(k,j,nxr_mg(l)+1)  = temp(k,j1,ixr+1)
     
    22992312
    23002313!
     2314!--    Next line is to avoid compile error due to unused dummy argument
     2315       IF ( color == 1234567 )  RETURN
     2316!
    23012317!--    Standard horizontal ghost boundary exchange for small coarse grid
    23022318!--    levels, where the transfer time is latency bound
  • palm/trunk/SOURCE/poismg_noopt_mod.f90

    r4414 r4429  
    2525! -----------------
    2626! $Id$
     27! bugfix: cpp-directives added for serial mode
     28!
     29! 4414 2020-02-19 20:16:04Z suehring
    2730! Remove double-declared use only construct.
    2831!
     
    11721175!> Gather subdomain data from all PEs.
    11731176!------------------------------------------------------------------------------!
     1177#if defined( __parallel )
    11741178    SUBROUTINE mg_gather_noopt( f2, f2_sub )
    11751179
     
    12071211
    12081212
    1209 #if defined( __parallel )
    12101213       CALL cpu_log( log_point_s(34), 'mg_gather_noopt', 'start' )
    12111214
     
    12421245
    12431246       CALL cpu_log( log_point_s(34), 'mg_gather_noopt', 'stop' )
    1244 #endif
    12451247       
    12461248    END SUBROUTINE mg_gather_noopt
    1247 
     1249#endif
    12481250
    12491251
     
    12541256!>       non-blocking communication
    12551257!------------------------------------------------------------------------------!
     1258#if defined( __parallel )
    12561259    SUBROUTINE mg_scatter_noopt( p2, p2_sub )
    12571260
     
    12671270
    12681271       IMPLICIT NONE
    1269 
    1270        INTEGER(iwp) ::  nwords  !<
    12711272
    12721273       REAL(wp), DIMENSION(nzb:nzt_mg(grid_level-1)+1,                         &
     
    12781279                           mg_loc_ind(1,myid)-1:mg_loc_ind(2,myid)+1) ::  p2_sub  !<
    12791280
    1280 !
    1281 !--    Find out the number of array elements of the subdomain array
    1282        nwords = SIZE( p2_sub )
    1283 
    1284 #if defined( __parallel )
     1281
    12851282       CALL cpu_log( log_point_s(35), 'mg_scatter_noopt', 'start' )
    12861283
     
    12891286
    12901287       CALL cpu_log( log_point_s(35), 'mg_scatter_noopt', 'stop' )
    1291 #endif
    12921288       
    12931289    END SUBROUTINE mg_scatter_noopt
     1290#endif
    12941291
    12951292
     
    13521349
    13531350       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  f2_sub  !<
     1351
     1352#if defined( __parallel )
    13541353       REAL(wp), DIMENSION(:,:,:), ALLOCATABLE ::  p2_sub  !<
     1354#endif
    13551355
    13561356!
     
    14371437!
    14381438!--          Gather all arrays from the subdomains on PE0
     1439#if defined( __parallel )
    14391440             CALL mg_gather_noopt( f2, f2_sub )
     1441#endif
    14401442
    14411443!
  • palm/trunk/SOURCE/radiation_model_mod.f90

    r4400 r4429  
    2828! -----------------
    2929! $Id$
     30! bugfixes: cpp-directives for serial mode moved, small changes to get serial mode compiled
     31!
     32! 4400 2020-02-10 20:32:41Z suehring
    3033! Initialize radiation arrays with zero
    3134!
     
    795798    REAL(wp), DIMENSION(:,:), ALLOCATABLE          ::  csf              !< array of plant canopy sink fators + direct irradiation factors (transparency)
    796799    REAL(wp), DIMENSION(:,:,:), POINTER            ::  sub_lad          !< subset of lad_s within urban surface, transformed to plain Z coordinate
     800#if defined( __parallel )
    797801    REAL(wp), DIMENSION(:), POINTER                ::  sub_lad_g        !< sub_lad globalized (used to avoid MPI RMA calls in raytracing)
     802#endif
    798803    REAL(wp)                                       ::  prototype_lad    !< prototype leaf area density for computing effective optical depth
    799804    INTEGER(iwp), DIMENSION(:), ALLOCATABLE        ::  nzterr, plantt   !< temporary global arrays for raytracing
     
    831836    INTEGER(iwp)                                   ::  win_lad          !< MPI RMA window for leaf area density
    832837    INTEGER(iwp)                                   ::  win_gridsurf     !< MPI RMA window for reverse grid surface index
     838    REAL(wp), DIMENSION(:), ALLOCATABLE            ::  lad_s_ray        !< array of received lad_s for appropriate gridboxes crossed by ray
    833839#endif
    834     REAL(wp), DIMENSION(:), ALLOCATABLE            ::  lad_s_ray        !< array of received lad_s for appropriate gridboxes crossed by ray
    835840    INTEGER(iwp), DIMENSION(:), ALLOCATABLE        ::  target_surfl
    836841    INTEGER(iwp), DIMENSION(:,:), ALLOCATABLE      ::  rt2_track
     
    14951500!
    14961501!--    Parallel rad_angular_discretization without raytrace_mpi_rma is not implemented
     1502!--    Serial mode does not allow mpi_rma
    14971503#if defined( __parallel )     
    14981504       IF ( rad_angular_discretization  .AND.  .NOT. raytrace_mpi_rma )  THEN
     
    15001506                           'together with raytrace_mpi_rma or when ' //  &
    15011507                           'no parallelization is applied.'
    1502           CALL message( 'check_parameters', 'PA0486', 1, 2, 0, 6, 0 )
     1508          CALL message( 'readiation_check_parameters', 'PA0486', 1, 2, 0, 6, 0 )
     1509       ENDIF
     1510#else
     1511       IF ( raytrace_mpi_rma )  THEN
     1512          message_string = 'raytrace_mpi_rma = .T. not allowed in serial mode'
     1513          CALL message( 'readiation_check_parameters', 'PA0710', 1, 2, 0, 6, 0 )
    15031514       ENDIF
    15041515#endif
     
    73707381
    73717382        INTEGER(iwp)                                  :: udim
    7372         INTEGER(iwp), DIMENSION(:), ALLOCATABLE,TARGET:: nzterrl_l
    7373         INTEGER(iwp), DIMENSION(:,:), POINTER         :: nzterrl
    73747383        REAL(wp),     DIMENSION(:), ALLOCATABLE,TARGET:: csflt_l, pcsflt_l
    73757384        REAL(wp),     DIMENSION(:,:), POINTER         :: csflt, pcsflt
     
    73857394        INTEGER(idp)                                  :: ray_skip_maxdist, ray_skip_minval !< skipped raytracing counts
    73867395        INTEGER(iwp)                                  :: max_track_len !< maximum 2d track length
     7396#if defined( __parallel )
     7397        INTEGER(iwp), DIMENSION(:), ALLOCATABLE,TARGET:: nzterrl_l
     7398        INTEGER(iwp), DIMENSION(:,:), POINTER         :: nzterrl
    73877399        INTEGER(iwp)                                  :: minfo
    73887400        REAL(wp), DIMENSION(:), POINTER, SAVE         :: lad_s_rma       !< fortran 1D pointer
    73897401        TYPE(c_ptr)                                   :: lad_s_rma_p     !< allocated c pointer
    7390 #if defined( __parallel )
    73917402        INTEGER(kind=MPI_ADDRESS_KIND)                :: size_lad_rma
    73927403#endif
     
    86248635      INTEGER(iwp)                           ::  ip           !< number of processor where gridbox reside
    86258636      INTEGER(iwp)                           ::  ig           !< 1D index of gridbox in global 2D array
    8626       INTEGER(iwp)                           ::  wcount       !< RMA window item count
    86278637      INTEGER(iwp)                           ::  maxboxes     !< max no of CSF created
    86288638      INTEGER(iwp)                           ::  nly          !< maximum  plant canopy height
     
    86348644      INTEGER(iwp)                           ::  iz
    86358645      INTEGER(iwp)                           ::  zsgn
    8636       INTEGER(iwp)                           ::  lowest_lad   !< lowest column cell for which we need LAD
    86378646      INTEGER(iwp)                           ::  lastdir      !< wall direction before hitting this column
    86388647      INTEGER(iwp), DIMENSION(2)             ::  lastcolumn
    86398648
    86408649#if defined( __parallel )
     8650      INTEGER(iwp)                           ::  lowest_lad   !< lowest column cell for which we need LAD
     8651      INTEGER(iwp)                           ::  wcount       !< RMA window item count
    86418652      INTEGER(MPI_ADDRESS_KIND)              ::  wdisp        !< RMA window displacement
    86428653#endif
     
    90559066         INTEGER(iwp), INTENT(out)           ::  iproc
    90569067#if defined( __parallel )
    9057 #else
    9058          INTEGER(iwp)                        ::  target_displ  !< index of the grid in the local gridsurf array
    9059 #endif
    90609068         INTEGER(iwp)                        ::  px, py        !< number of processors in x and y direction
    90619069                                                               !< before the processor in the question
     9070#endif
     9071
    90629072#if defined( __parallel )
    90639073         INTEGER(KIND=MPI_ADDRESS_KIND)      ::  target_displ  !< index of the grid in the local gridsurf array
     
    90829092!--      set index target_surfl(i)
    90839093         isurfl = gridsurf(d,z,y,x)
     9094         iproc  = 0  ! required to avoid compile error about unused variable in serial mode
    90849095#endif
    90859096
  • palm/trunk/SOURCE/spectra_mod.f90

    r4360 r4429  
    2525! -----------------
    2626! $Id$
     27! bugfix: preprocessor directives rearranged for serial mode
     28!
     29! 4360 2020-01-07 11:25:50Z suehring
    2730! Corrected "Former revisions" section
    2831!
     
    8184    END INTERFACE preprocess_spectra
    8285
     86#if defined( __parallel )
    8387    INTERFACE calc_spectra_x
    8488       MODULE PROCEDURE calc_spectra_x
     
    8892       MODULE PROCEDURE calc_spectra_y
    8993    END INTERFACE calc_spectra_y
     94#endif
    9095
    9196    INTERFACE spectra_check_parameters
     
    345350
    346351       USE arrays_3d,                                                          &
    347            ONLY:  d, tend
     352           ONLY:  d
     353#if defined( __parallel )
     354       USE arrays_3d,                                                          &
     355           ONLY:  tend
     356#endif
    348357
    349358       USE control_parameters,                                                 &
     
    362371
    363372       USE pegrid,                                                             &
    364            ONLY:  myid, pdims
     373           ONLY:  myid
     374#if defined( __parallel )
     375       USE pegrid,                                                             &
     376           ONLY:  pdims
     377#endif
    365378
    366379       IMPLICIT NONE
     
    489502       USE MPI
    490503#endif
    491 #endif
    492504
    493505       USE pegrid,                                                             &
    494506           ONLY:  collective_wait, comm2d, ierr
     507#endif
    495508
    496509       USE statistics,                                                         &
     
    583596!> @todo Missing subroutine description.
    584597!------------------------------------------------------------------------------!
     598#if defined( __parallel )
    585599    SUBROUTINE calc_spectra_x( ddd, m )
    586600
     
    596610       USE kinds
    597611
    598 #if defined( __parallel )
    599612#if !defined( __mpifh )
    600613       USE MPI
    601614#endif
    602 #endif
    603615
    604616       USE pegrid,                                                             &
     
    611623       IMPLICIT NONE
    612624
    613 #if defined( __parallel )
    614625#if defined( __mpifh )
    615626       INCLUDE "mpif.h"
    616 #endif
    617627#endif
    618628
     
    718728
    719729    END SUBROUTINE calc_spectra_x
     730#endif
    720731
    721732
     
    725736!> @todo Missing subroutine description.
    726737!------------------------------------------------------------------------------!
     738#if defined( __parallel )
    727739    SUBROUTINE calc_spectra_y( ddd, m )
    728740
     
    738750       USE kinds
    739751
    740 #if defined( __parallel )
    741752#if !defined( __mpifh )
    742753       USE MPI
    743754#endif
    744 #endif
    745755
    746756       USE pegrid,                                                             &
     
    753763       IMPLICIT NONE
    754764
    755 #if defined( __parallel )
    756765#if defined( __mpifh )
    757766       INCLUDE "mpif.h"
    758 #endif
    759767#endif
    760768
     
    862870
    863871    END SUBROUTINE calc_spectra_y
     872#endif
    864873
    865874 END MODULE spectra_mod
  • palm/trunk/SOURCE/surface_coupler.f90

    r4360 r4429  
    2525! -----------------
    2626! $Id$
     27! bugfix: preprocessor directives rearranged for serial mode
     28!
     29! 4360 2020-01-07 11:25:50Z suehring
    2730! Corrected "Former revisions" section
    2831!
     
    3841!------------------------------------------------------------------------------!
    3942 SUBROUTINE surface_coupler
     43#if defined( __parallel )
    4044 
    4145
     
    7882    REAL(wp), DIMENSION(nysg:nyng,nxlg:nxrg) ::  surface_flux !< dummy array for surface fluxes on 2D grid
    7983
    80 
    81 #if defined( __parallel )
    8284
    8385    CALL cpu_log( log_point(39), 'surface_coupler', 'start' )
     
    454456    CALL cpu_log( log_point(39), 'surface_coupler', 'stop' )
    455457
    456 #endif
    457458
    458459     CONTAINS
     
    613614        END SUBROUTINE transfer_2D_to_1D_unequal
    614615
     616#endif
    615617  END SUBROUTINE surface_coupler
    616618
     
    622624!> @todo Missing subroutine description.
    623625!------------------------------------------------------------------------------!
     626#if defined( __parallel )
     627
    624628  SUBROUTINE interpolate_to_atmos( tag )
    625 
    626 #if defined( __parallel )
    627629
    628630    USE arrays_3d,                                                             &
     
    701703    CALL MPI_BARRIER( comm2d, ierr )
    702704
     705  END SUBROUTINE interpolate_to_atmos
     706
    703707#endif
    704 
    705   END SUBROUTINE interpolate_to_atmos
    706708
    707709
     
    711713!> @todo Missing subroutine description.
    712714!------------------------------------------------------------------------------!
     715#if defined( __parallel )
     716
    713717  SUBROUTINE interpolate_to_ocean( tag )
    714 
    715 #if defined( __parallel )
    716718
    717719    USE arrays_3d,                                                             &
     
    786788    CALL MPI_BARRIER( comm2d, ierr ) 
    787789
     790  END SUBROUTINE interpolate_to_ocean
     791
    788792#endif
    789 
    790   END SUBROUTINE interpolate_to_ocean
  • palm/trunk/SOURCE/transpose.f90

    r4415 r4429  
    2525! -----------------
    2626! $Id$
     27! bugfix: cpp-directives added for serial mode
     28!
     29! 4415 2020-02-20 10:30:33Z raasch
    2730! bugfix for misplaced preprocessor directive
    2831!
     
    111114
    112115
     116#if defined( __parallel )
    113117    USE cpulog,                                                                &
    114118        ONLY:  cpu_log, cpu_log_nowait, log_point_s
     119#endif
    115120
    116121    USE indices,                                                               &
     
    129134    INTEGER(iwp) ::  j  !<
    130135    INTEGER(iwp) ::  k  !<
     136
     137#if defined( __parallel )
    131138    INTEGER(iwp) ::  l  !<
    132139    INTEGER(iwp) ::  ys !<
     140#endif
    133141
    134142    REAL(wp) ::  f_inv(nys_x:nyn_x,nzb_x:nzt_x,0:nx) !<
    135143    REAL(wp) ::  f_out(0:ny,nxl_y:nxr_y,nzb_y:nzt_y) !<
    136144
     145#if defined( __parallel )
    137146    REAL(wp), DIMENSION(nyn_x-nys_x+1,nzb_y:nzt_y,nxl_y:nxr_y,0:pdims(2)-1) ::  work !<
    138147#if __acc_fft_device
    139148    !$ACC DECLARE CREATE(work)
     149#endif
    140150#endif
    141151
     
    271281 SUBROUTINE transpose_xz( f_in, f_inv )
    272282
    273 
     283#if defined( __parallel )
    274284    USE cpulog,                                                                &
    275285        ONLY:  cpu_log, cpu_log_nowait, log_point_s
     
    277287    USE fft_xy,                                                                &
    278288        ONLY:  f_vec_x, temperton_fft_vec
     289#endif
    279290
    280291    USE indices,                                                               &
    281         ONLY:  nnx, nx, nxl, nxr, nyn, nys, nz
     292        ONLY:  nx, nxl, nxr, nyn, nys, nz
     293#if defined( __parallel )
     294    USE indices,                                                               &
     295        ONLY:  nnx
     296#endif
    282297
    283298    USE kinds
     
    293308    INTEGER(iwp) ::  j  !<
    294309    INTEGER(iwp) ::  k  !<
     310#if defined( __parallel )
    295311    INTEGER(iwp) ::  l  !<
    296312    INTEGER(iwp) ::  mm !<
    297313    INTEGER(iwp) ::  xs !<
     314#endif
    298315
    299316    REAL(wp) ::  f_in(0:nx,nys_x:nyn_x,nzb_x:nzt_x) !<
    300317    REAL(wp) ::  f_inv(nys:nyn,nxl:nxr,1:nz) !<
    301318
     319#if defined( __parallel )
    302320    REAL(wp), DIMENSION(nys_x:nyn_x,nnx,nzb_x:nzt_x,0:pdims(1)-1) ::  work !<
    303321#if __acc_fft_device
    304322    !$ACC DECLARE CREATE(work)
     323#endif
    305324#endif
    306325
     
    460479
    461480
     481#if defined( __parallel )
    462482    USE cpulog,                                                                &
    463483        ONLY:  cpu_log, cpu_log_nowait, log_point_s
     484#endif
    464485
    465486    USE indices,                                                               &
     
    478499    INTEGER(iwp) ::  j  !<
    479500    INTEGER(iwp) ::  k  !<
     501#if defined( __parallel )
    480502    INTEGER(iwp) ::  l  !<
    481503    INTEGER(iwp) ::  ys !<
     504#endif
    482505
    483506    REAL(wp) ::  f_in(0:ny,nxl_y:nxr_y,nzb_y:nzt_y)  !<
    484507    REAL(wp) ::  f_inv(nys_x:nyn_x,nzb_x:nzt_x,0:nx) !<
    485508
     509#if defined( __parallel )
    486510    REAL(wp), DIMENSION(nyn_x-nys_x+1,nzb_y:nzt_y,nxl_y:nxr_y,0:pdims(2)-1) ::  work !<
    487511#if __acc_fft_device
    488512    !$ACC DECLARE CREATE(work)
     513#endif
    489514#endif
    490515
     
    575600!> (k,j,i) (cf. transpose_yx).
    576601!------------------------------------------------------------------------------!
     602#if defined( __parallel )
    577603 SUBROUTINE transpose_yxd( f_in, f_out )
    578604
     
    604630    REAL(wp) ::  f_out(0:nx,nys_x:nyn_x,nzb_x:nzt_x) !<
    605631    REAL(wp) ::  work(nnx*nny*nnz)                   !<
    606 #if defined( __parallel )
    607632
    608633!
     
    641666    ENDDO
    642667
    643 #endif
    644 
    645668 END SUBROUTINE transpose_yxd
     669#endif
    646670
    647671
     
    703727
    704728
     729#if defined( __parallel )
    705730    USE cpulog,                                                                &
    706731        ONLY:  cpu_log, cpu_log_nowait, log_point_s
     732#endif
    707733
    708734    USE indices,                                                               &
     
    721747    INTEGER(iwp) ::  j  !<
    722748    INTEGER(iwp) ::  k  !<
     749#if defined( __parallel )
    723750    INTEGER(iwp) ::  l  !<
    724751    INTEGER(iwp) ::  zs !<
     752#endif
    725753
    726754    REAL(wp) ::  f_inv(nxl_y:nxr_y,nzb_y:nzt_y,0:ny) !<
    727755    REAL(wp) ::  f_out(nxl_z:nxr_z,nys_z:nyn_z,1:nz) !<
    728756
     757#if defined( __parallel )
    729758    REAL(wp), DIMENSION(nxl_z:nxr_z,nzt_y-nzb_y+1,nys_z:nyn_z,0:pdims(1)-1) ::  work !<
    730759#if __acc_fft_device
    731760    !$ACC DECLARE CREATE(work)
     761#endif
    732762#endif
    733763
     
    864894
    865895
     896#if defined( __parallel )
    866897    USE cpulog,                                                                &
    867898        ONLY:  cpu_log, cpu_log_nowait, log_point_s
     
    869900    USE fft_xy,                                                                &
    870901        ONLY:  f_vec_x, temperton_fft_vec
     902#endif
    871903
    872904    USE indices,                                                               &
    873         ONLY:  nnx, nx, nxl, nxr, nyn, nys, nz
     905        ONLY:  nx, nxl, nxr, nyn, nys, nz
     906#if defined( __parallel )
     907    USE indices,                                                               &
     908        ONLY:  nnx
     909#endif
    874910
    875911    USE kinds
     
    885921    INTEGER(iwp) ::  j  !<
    886922    INTEGER(iwp) ::  k  !<
     923#if defined( __parallel )
    887924    INTEGER(iwp) ::  l  !<
    888925    INTEGER(iwp) ::  mm !<
    889926    INTEGER(iwp) ::  xs !<
     927#endif
    890928
    891929    REAL(wp) ::  f_inv(nys:nyn,nxl:nxr,1:nz)         !<
    892930    REAL(wp) ::  f_out(0:nx,nys_x:nyn_x,nzb_x:nzt_x) !<
    893931
     932#if defined( __parallel )
    894933    REAL(wp), DIMENSION(nys_x:nyn_x,nnx,nzb_x:nzt_x,0:pdims(1)-1) ::  work !<
    895934#if __acc_fft_device
    896935    !$ACC DECLARE CREATE(work)
     936#endif
    897937#endif
    898938
     
    10541094
    10551095
     1096#if defined( __parallel )
    10561097    USE cpulog,                                                                &
    10571098        ONLY:  cpu_log, cpu_log_nowait, log_point_s
     1099#endif
    10581100
    10591101    USE indices,                                                               &
     
    10721114    INTEGER(iwp) ::  j  !<
    10731115    INTEGER(iwp) ::  k  !<
     1116#if defined( __parallel )
    10741117    INTEGER(iwp) ::  l  !<
    10751118    INTEGER(iwp) ::  zs !<
     1119#endif
    10761120
    10771121    REAL(wp) ::  f_in(nxl_z:nxr_z,nys_z:nyn_z,1:nz)  !<
    10781122    REAL(wp) ::  f_inv(nxl_y:nxr_y,nzb_y:nzt_y,0:ny) !<
    10791123
     1124#if defined( __parallel )
    10801125    REAL(wp), DIMENSION(nxl_z:nxr_z,nzt_y-nzb_y+1,nys_z:nyn_z,0:pdims(1)-1) ::  work !<
    10811126#if __acc_fft_device
    10821127    !$ACC DECLARE CREATE(work)
     1128#endif
    10831129#endif
    10841130
     
    11701216!> (k,j,i) (cf. transpose_zy).
    11711217!------------------------------------------------------------------------------!
     1218#if defined( __parallel )
    11721219 SUBROUTINE transpose_zyd( f_in, f_out )
    11731220
     
    11991246    REAL(wp) ::  f_out(0:ny,nxl_yd:nxr_yd,nzb_yd:nzt_yd) !<
    12001247    REAL(wp) ::  work(nnx*nny*nnz)                       !<
    1201 
    1202 #if defined( __parallel )
    12031248
    12041249!
     
    12531298    ENDDO
    12541299
    1255 #endif
    1256 
    12571300 END SUBROUTINE transpose_zyd
     1301#endif
Note: See TracChangeset for help on using the changeset viewer.