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

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

Bugfix for precursor atmosphere/ocean runs, re-adjustments for lcxt4

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