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

Last change on this file since 208 was 206, checked in by raasch, 15 years ago

ocean-atmosphere coupling realized with MPI-1, adjustments in mrun, mbuild, subjob for lcxt4

  • Property svn:keywords set to Id
File size: 3.2 KB
Line 
1  SUBROUTINE init_coupling
2
3!------------------------------------------------------------------------------!
4! Actual revisions:
5! -----------------
6!
7!
8! Former revisions:
9! ------------------
10! $Id: init_coupling.f90 206 2008-10-13 14:59:11Z 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 ( myid == 0 )  THEN
44       READ (*,*,ERR=10,END=10)  coupling_mode, bc_data(1), bc_data(2)
4510     CONTINUE
46
47#if defined( __mpi2 )
48       IF ( TRIM( coupling_mode ) == 'atmosphere_to_ocean' )  THEN
49          i = 1
50       ELSEIF ( TRIM( coupling_mode ) == 'ocean_to_atmosphere' )  THEN
51          i = 2
52       ELSE
53          i = 0
54       ENDIF
55#else
56       IF ( TRIM( coupling_mode ) == 'coupled_run' )  THEN
57          i = 1
58       ELSE
59          i = 0
60       ENDIF
61#endif
62    bc_data(0) = i
63    ENDIF
64
65    CALL MPI_BCAST( bc_data(0), 3, MPI_INTEGER, 0, MPI_COMM_WORLD, ierr )
66    i = bc_data(0)
67
68#if defined ( __mpi2 )
69    IF ( i == 0 )  THEN
70       coupling_mode = 'uncoupled'
71    ELSEIF ( i == 1 )  THEN
72       coupling_mode = 'atmosphere_to_ocean'
73    ELSEIF ( i == 2 )  THEN
74       coupling_mode = 'ocean_to_atmosphere'
75    ENDIF
76    target_id = myid
77#else
78    IF ( i == 0 ) THEN
79       coupling_mode = 'uncoupled'
80    ELSE
81       comm_inter = MPI_COMM_WORLD
82
83       IF ( myid < bc_data(1) ) THEN
84          inter_color = 0
85          numprocs = bc_data(1)
86       ELSE
87          inter_color = 1
88          numprocs = bc_data(2)
89       ENDIF
90!
91!--    Calculate the target PE for coupling and set up the new communicators.
92!--    Currently only 1:1 topologies are supported.
93       target_id = myid - ISIGN( numprocs, inter_color - 1 )
94       IF ( inter_color == 0 ) THEN
95          coupling_mode = 'atmosphere_to_ocean'
96       ELSE
97          coupling_mode = 'ocean_to_atmosphere'
98       ENDIF
99       CALL MPI_COMM_SPLIT( MPI_COMM_WORLD, inter_color, 0, comm_palm, ierr )
100       comm2d = comm_palm
101
102!
103!--    Write a flag file for the ocean model and the other atmosphere
104!--    processes.
105       OPEN( 90, FILE='COUPLING_PORT_OPENED', FORM='FORMATTED' )
106       WRITE ( 90, '(''TRUE'')' )
107       CLOSE ( 90 )
108    ENDIF
109#endif
110
111    IF ( coupling_mode == 'ocean_to_atmosphere' )  coupling_char = '_O'
112
113 END SUBROUTINE init_coupling
Note: See TracBrowser for help on using the repository browser.