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

Last change on this file since 674 was 668, checked in by suehring, 13 years ago

last commit documented

  • Property svn:keywords set to Id
File size: 3.7 KB
Line 
1  SUBROUTINE init_coupling
2
3!------------------------------------------------------------------------------!
4! Current revisions:
5! -----------------
6!
7!
8! Former revisions:
9! ------------------
10! $Id: init_coupling.f90 668 2010-12-23 13:22:58Z suehring $
11!
12! 667 2010-12-23 12:06:00Z suehring/gryschka
13! determination of target_id's moved to init_pegrid
14!
15! 291 2009-04-16 12:07:26Z raasch
16! Coupling with independent precursor runs.
17!
18! 222 2009-01-12 16:04:16Z letzel
19! Initial revision
20!
21! Description:
22! ------------
23! Initializing coupling via MPI-1 or MPI-2 if the coupled version of PALM is
24! called.
25!------------------------------------------------------------------------------!
26
27    USE pegrid
28    USE control_parameters
29    USE indices
30
31    IMPLICIT NONE
32
33!
34!-- Local variables
35    INTEGER               ::  i, inter_color
36    INTEGER, DIMENSION(:) ::  bc_data(0:3) = 0
37
38!
39!-- Get information about the coupling mode from the environment variable
40!-- which has been set by the mpiexec command.
41!-- This method is currently not used because the mpiexec command is not
42!-- available on some machines
43!    CALL local_getenv( 'coupling_mode', 13, coupling_mode, i )
44!    IF ( i == 0 )  coupling_mode = 'uncoupled'
45!    IF ( coupling_mode == 'ocean_to_atmosphere' )  coupling_char = '_O'
46
47!
48!-- Get information about the coupling mode from standard input (PE0 only) and
49!-- distribute it to the other PEs. If __mpi2 was defined, suggest a
50!-- coupling via MPI-2. Otherwise initate a coupling using MPI-1 only.
51!-- In this case, distribute PEs to 2 new communicators.
52!-- ATTENTION: numprocs will be reset according to the new communicators
53#if defined ( __parallel )
54
55!myid_absolut = myid
56    IF ( myid == 0 )  THEN
57       READ (*,*,ERR=10,END=10)  coupling_mode, bc_data(1), bc_data(2)
5810     CONTINUE
59#if defined( __mpi2 )
60       IF ( TRIM( coupling_mode ) == 'atmosphere_to_ocean' )  THEN
61          i = 1
62       ELSEIF ( TRIM( coupling_mode ) == 'ocean_to_atmosphere' )  THEN
63          i = 2
64       ELSE
65          i = 0
66       ENDIF
67#else
68       IF ( TRIM( coupling_mode ) == 'coupled_run' )  THEN
69          i = 1
70       ELSE
71          i = 0
72       ENDIF
73#endif
74       bc_data(0) = i
75
76!
77!--    Check if '_O' has to be used as file extension in an uncoupled ocean
78!--    run. This is required, if this run shall be continued as a coupled run.
79       IF ( TRIM( coupling_mode ) == 'precursor_ocean' )  bc_data(3) = 1
80
81    ENDIF
82
83    CALL MPI_BCAST( bc_data(0), 4, MPI_INTEGER, 0, MPI_COMM_WORLD, ierr )
84    i = bc_data(0)
85
86#if defined ( __mpi2 )
87    IF ( i == 0 )  THEN
88       coupling_mode = 'uncoupled'
89    ELSEIF ( i == 1 )  THEN
90       coupling_mode = 'atmosphere_to_ocean'
91    ELSEIF ( i == 2 )  THEN
92       coupling_mode = 'ocean_to_atmosphere'
93    ENDIF
94    target_id = myid
95#else
96    IF ( i == 0 ) THEN
97       coupling_mode = 'uncoupled'
98    ELSE
99       comm_inter = MPI_COMM_WORLD
100
101       IF ( myid < bc_data(1) ) THEN
102          inter_color     = 0
103          numprocs        = bc_data(1)
104          coupling_mode   = 'atmosphere_to_ocean'
105       ELSE
106          inter_color     = 1
107          numprocs        = bc_data(2)
108          coupling_mode   = 'ocean_to_atmosphere'
109       ENDIF
110
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.