Ignore:
Timestamp:
Jul 27, 2007 9:09:17 AM (17 years ago)
Author:
raasch
Message:

preliminary version for coupled runs

File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/palm.f90

    r97 r102  
    44! Actual revisions:
    55! -----------------
    6 !
     6! Get coupling mode from environment variable
    77!
    88! Former revisions:
     
    4343    USE arrays_3d
    4444    USE constants
     45    USE control_parameters
    4546    USE cpulog
    4647    USE dvrp_variables
     
    5354    USE spectrum
    5455    USE statistics
    55     USE control_parameters
    5656
    5757    IMPLICIT NONE
     
    6363    INTEGER           ::  i, run_description_header_i(80)
    6464
    65     version = 'PALM 3.3'
     65    version = 'PALM 3.3a'
    6666
    6767#if defined( __parallel )
     
    7575#endif
    7676
     77#if defined( __mpi2 )
     78!
     79!-- Get information about the coupling mode from the environment variable
     80!-- which has been set by the mpiexec command
     81    CALL local_getenv( 'coupling_mode', 13, coupling_mode, i )
     82    IF ( i == 0 )  coupling_mode = 'uncoupled'
     83    IF ( coupling_mode == 'ocean_to_atmosphere' )  coupling_char = '_O'
     84#endif
     85
    7786!
    7887!-- Initialize measuring of the CPU-time remaining to the run
     
    104113!
    105114!-- Open a file for debug output
    106     OPEN( 9, FILE='DEBUG'//myid_char, FORM='FORMATTED' )
     115    OPEN( 9, FILE='DEBUG'//TRIM( coupling_char )//myid_char, FORM='FORMATTED' )
     116
     117#if defined( __mpi2 )
     118!
     119!-- TEST OUTPUT (TO BE REMOVED)
     120    WRITE(9,*) '*** coupling_mode = "', TRIM( coupling_mode ), '"'
     121    CALL LOCAL_FLUSH( 9 )
     122    print*, '*** PE', myid, '  ', TRIM( coupling_mode )
     123#endif
    107124
    108125!
     
    167184    CALL cpu_log( log_point(4), 'last actions', 'stop' )
    168185
     186#if defined( __mpi2 )
     187!
     188!-- Test exchange via intercommunicator
     189    IF ( coupling_mode == 'atmosphere_to_ocean' )  THEN
     190       i = 12345 + myid
     191       CALL MPI_SEND( i, 1, MPI_INTEGER, myid, 11, comm_inter, ierr )
     192    ELSEIF ( coupling_mode == 'ocean_to_atmosphere' )  THEN
     193       CALL MPI_RECV( i, 1, MPI_INTEGER, myid, 11, comm_inter, status, ierr )
     194       PRINT*, '### myid: ', myid, '   received from atmosphere:  i = ', i
     195    ENDIF
     196#endif
     197
    169198!
    170199!-- Take final CPU-time for CPU-time analysis
Note: See TracChangeset for help on using the changeset viewer.