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

Last change on this file since 697 was 692, checked in by maronga, 13 years ago

last commit documented

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