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

Last change on this file since 709 was 709, checked in by raasch, 13 years ago

formatting adjustments

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