Ignore:
Timestamp:
Aug 25, 2020 7:52:08 AM (4 years ago)
Author:
raasch
Message:

files re-formatted to follow the PALM coding standard

File:
1 edited

Legend:

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

    r4564 r4648  
    11!> @file init_coupling.f90
    2 !------------------------------------------------------------------------------!
     2!--------------------------------------------------------------------------------------------------!
    33! This file is part of the PALM model system.
    44!
    5 ! PALM is free software: you can redistribute it and/or modify it under the
    6 ! terms of the GNU General Public License as published by the Free Software
    7 ! Foundation, either version 3 of the License, or (at your option) any later
    8 ! version.
     5! PALM is free software: you can redistribute it and/or modify it under the terms of the GNU General
     6! Public License as published by the Free Software Foundation, either version 3 of the License, or
     7! (at your option) any later version.
    98!
    10 ! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
    11 ! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
    12 ! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
     9! PALM is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the
     10! implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General
     11! Public License for more details.
    1312!
    14 ! You should have received a copy of the GNU General Public License along with
    15 ! PALM. If not, see <http://www.gnu.org/licenses/>.
     13! You should have received a copy of the GNU General Public License along with PALM. If not, see
     14! <http://www.gnu.org/licenses/>.
    1615!
    1716! Copyright 1997-2020 Leibniz Universitaet Hannover
    18 !------------------------------------------------------------------------------!
     17!--------------------------------------------------------------------------------------------------!
    1918!
    2019! Current revisions:
    2120! -----------------
    22 ! 
    23 ! 
     21!
     22!
    2423! Former revisions:
    2524! ------------------
    2625! $Id$
     26! file re-formatted to follow the PALM coding standard
     27!
     28! 4564 2020-06-12 14:03:36Z raasch
    2729! Vertical nesting method of Huq et al. (2019) removed
    28 ! 
     30!
    2931! 4444 2020-03-05 15:59:50Z raasch
    3032! bugfix: cpp-directives for serial mode added
    31 ! 
     33!
    3234! 4360 2020-01-07 11:25:50Z suehring
    3335! Corrected "Former revisions" section
    34 ! 
     36!
    3537! 3655 2019-01-07 16:51:22Z knoop
    3638! references to mrun replaced by palmrun, and updated
     
    4143! Description:
    4244! ------------
    43 !> Initializing coupling via MPI-1 or MPI-2 if the coupled version of PALM is
    44 !> called.
    45 !------------------------------------------------------------------------------!
     45!> Initializing coupling via MPI-1 or MPI-2 if the coupled version of PALM is called.
     46!--------------------------------------------------------------------------------------------------!
    4647  SUBROUTINE init_coupling
    47  
    4848
    49     USE control_parameters,                                                    &
     49
     50    USE control_parameters,                                                                        &
    5051        ONLY:  coupling_char, coupling_mode
    51        
     52
    5253    USE kinds
    53    
     54
    5455    USE pegrid
    5556
     
    6263    INTEGER(iwp) ::  inter_color  !<
    6364#endif
    64    
     65
    6566    INTEGER(iwp), DIMENSION(:) ::  bc_data(0:3) = 0  !<
    6667
    6768!
    68 !-- Get information about the coupling mode from the environment variable
    69 !-- which has been set by the mpiexec command.
    70 !-- This method is currently not used because the mpiexec command is not
    71 !-- available on some machines
     69!-- Get information about the coupling mode from the environment variable which has been set by the
     70!-- mpiexec command.
     71!-- This method is currently not used because the mpiexec command is not available on some machines.
    7272!    CALL GET_ENVIRONMENT_VARIABLE( 'coupling_mode', coupling_mode, i )
    7373!    IF ( i == 0 )  coupling_mode = 'uncoupled'
     
    7575
    7676!
    77 !-- Get information about the coupling mode from standard input (PE0 only) and
    78 !-- distribute it to the other PEs. Distribute PEs to 2 new communicators.
     77!-- Get information about the coupling mode from standard input (PE0 only) and distribute it to the
     78!-- other PEs. Distribute PEs to 2 new communicators.
    7979!-- ATTENTION: numprocs will be reset according to the new communicators
    8080#if defined ( __parallel )
     
    9191
    9292!
    93 !--    Check if '_O' has to be used as file extension in an uncoupled ocean
    94 !--    run. This is required, if this run shall be continued as a coupled run.
     93!--    Check if '_O' has to be used as file extension in an uncoupled ocean run. This is required,
     94!--    if this run shall be continued as a coupled run.
    9595       IF ( TRIM( coupling_mode ) == 'precursor_ocean' )  bc_data(3) = 1
    9696
     
    127127
    128128!
    129 !--    Write a flag file for the ocean model and the other atmosphere
    130 !--    processes.
     129!--    Write a flag file for the ocean model and the other atmosphere processes.
    131130       OPEN( 90, FILE='COUPLING_PORT_OPENED', FORM='FORMATTED' )
    132131       WRITE ( 90, '(''TRUE'')' )
     
    136135
    137136!
    138 !-- In case of a precursor ocean run (followed by a coupled run), or a
    139 !-- coupled atmosphere-ocean run, set the file extension for the ocean files
    140     IF ( TRIM( coupling_mode ) == 'ocean_to_atmosphere' .OR. bc_data(3) == 1 ) &
    141     THEN
     137!-- In case of a precursor ocean run (followed by a coupled run), or a coupled atmosphere-ocean run,
     138!-- set the file extension for the ocean files.
     139    IF ( TRIM( coupling_mode ) == 'ocean_to_atmosphere' .OR. bc_data(3) == 1 )  THEN
    142140       coupling_char = '_O'
    143141    ENDIF
Note: See TracChangeset for help on using the changeset viewer.