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

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