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

Last change on this file since 592 was 484, checked in by raasch, 14 years ago

typo in file headers removed

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