source: palm/trunk/SOURCE/init_coupling.f90 @ 225

Last change on this file since 225 was 222, checked in by letzel, 15 years ago
  • Bugfixes for nonparallel execution
  • Property svn:keywords set to Id
File size: 3.3 KB
Line 
1  SUBROUTINE init_coupling
2
3!------------------------------------------------------------------------------!
4! Actual revisions:
5! -----------------
6! Bugfix for nonparallel execution
7!
8! Former revisions:
9! ------------------
10! $Id: init_coupling.f90 222 2009-01-12 16:04:16Z raasch $
11!
12! Description:
13! ------------
14! Initializing coupling via MPI-1 or MPI-2 if the coupled version of PALM is
15! called.
16!------------------------------------------------------------------------------!
17
18    USE pegrid
19    USE control_parameters
20
21    IMPLICIT NONE
22
23!
24!-- Local variables
25    INTEGER               ::  i, inter_color
26    INTEGER, DIMENSION(:) ::  bc_data(0:2) = 0
27
28!
29!-- Get information about the coupling mode from the environment variable
30!-- which has been set by the mpiexec command.
31!-- This method is currently not used because the mpiexec command is not
32!-- available on some machines
33!    CALL local_getenv( 'coupling_mode', 13, coupling_mode, i )
34!    IF ( i == 0 )  coupling_mode = 'uncoupled'
35!    IF ( coupling_mode == 'ocean_to_atmosphere' )  coupling_char = '_O'
36
37!
38!-- Get information about the coupling mode from standard input (PE0 only) and
39!-- distribute it to the other PEs. If __mpi2 was defined, suggest a
40!-- coupling via MPI-2. Otherwise initate a coupling using MPI-1 only.
41!-- In this case, distribute PEs to 2 new communicators.
42!-- ATTENTION: numprocs will be reset according to the new communicators
43#if defined ( __parallel )
44    IF ( myid == 0 )  THEN
45       READ (*,*,ERR=10,END=10)  coupling_mode, bc_data(1), bc_data(2)
4610     CONTINUE
47
48#if defined( __mpi2 )
49       IF ( TRIM( coupling_mode ) == 'atmosphere_to_ocean' )  THEN
50          i = 1
51       ELSEIF ( TRIM( coupling_mode ) == 'ocean_to_atmosphere' )  THEN
52          i = 2
53       ELSE
54          i = 0
55       ENDIF
56#else
57       IF ( TRIM( coupling_mode ) == 'coupled_run' )  THEN
58          i = 1
59       ELSE
60          i = 0
61       ENDIF
62#endif
63    bc_data(0) = i
64    ENDIF
65
66    CALL MPI_BCAST( bc_data(0), 3, MPI_INTEGER, 0, MPI_COMM_WORLD, ierr )
67    i = bc_data(0)
68
69#if defined ( __mpi2 )
70    IF ( i == 0 )  THEN
71       coupling_mode = 'uncoupled'
72    ELSEIF ( i == 1 )  THEN
73       coupling_mode = 'atmosphere_to_ocean'
74    ELSEIF ( i == 2 )  THEN
75       coupling_mode = 'ocean_to_atmosphere'
76    ENDIF
77    target_id = myid
78#else
79    IF ( i == 0 ) THEN
80       coupling_mode = 'uncoupled'
81    ELSE
82       comm_inter = MPI_COMM_WORLD
83
84       IF ( myid < bc_data(1) ) THEN
85          inter_color = 0
86          numprocs = bc_data(1)
87       ELSE
88          inter_color = 1
89          numprocs = bc_data(2)
90       ENDIF
91!
92!--    Calculate the target PE for coupling and set up the new communicators.
93!--    Currently only 1:1 topologies are supported.
94       target_id = myid - ISIGN( numprocs, inter_color - 1 )
95       IF ( inter_color == 0 ) THEN
96          coupling_mode = 'atmosphere_to_ocean'
97       ELSE
98          coupling_mode = 'ocean_to_atmosphere'
99       ENDIF
100       CALL MPI_COMM_SPLIT( MPI_COMM_WORLD, inter_color, 0, comm_palm, ierr )
101       comm2d = comm_palm
102
103!
104!--    Write a flag file for the ocean model and the other atmosphere
105!--    processes.
106       OPEN( 90, FILE='COUPLING_PORT_OPENED', FORM='FORMATTED' )
107       WRITE ( 90, '(''TRUE'')' )
108       CLOSE ( 90 )
109    ENDIF
110#endif
111#endif
112
113    IF ( coupling_mode == 'ocean_to_atmosphere' )  coupling_char = '_O'
114
115 END SUBROUTINE init_coupling
Note: See TracBrowser for help on using the repository browser.