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/modules.f90

    r98 r102  
    55! Actual revisions:
    66! -----------------
    7 !
     7! +comm_inter, coupling_char, coupling_mode, dt_coupling, ngp_xy, port_name,
     8! time_coupling, type_xy, uswst*, vswst*
    89!
    910! Former revisions:
     
    107108    REAL, DIMENSION(:,:), ALLOCATABLE, TARGET ::                               &
    108109          qsws_1, qsws_2, qswst_1, qswst_2, rif_1, rif_2, saswsb_1, saswst_1,  &
    109           shf_1, shf_2, tswst_1, tswst_2, usws_1, usws_2, vsws_1, vsws_2
     110          shf_1, shf_2, tswst_1, tswst_2, usws_1, usws_2, uswst_1, uswst_2,    &
     111          vsws_1, vsws_2, vswst_1, vswst_2
    110112
    111113    REAL, DIMENSION(:,:), POINTER ::                                           &
    112114          qsws, qsws_m, qswst, qswst_m, rif, rif_m, saswsb, saswst, shf,       &
    113           shf_m, tswst, tswst_m, usws, usws_m, vsws, vsws_m
     115          shf_m, tswst, tswst_m, usws, uswst, usws_m, uswst_m, vsws, vswst,    &
     116          vsws_m, vswst_m
    114117
    115118    REAL, DIMENSION(:,:,:), ALLOCATABLE ::                                     &
     
    229232
    230233    CHARACTER (LEN=1)   ::  cycle_mg = 'w', timestep_reason = ' '
     234    CHARACTER (LEN=2)   ::  coupling_char = ''
    231235    CHARACTER (LEN=5)   ::  write_binary = 'false'
    232236    CHARACTER (LEN=6)   ::  grid_matching = 'match'
     
    246250                            bc_sa_t = 'neumann', &
    247251                            bc_uv_b = 'dirichlet', bc_uv_t = 'dirichlet', &
     252                            coupling_mode = 'uncoupled', &
    248253                            dissipation_1d = 'as_in_3d_model', &
    249254                            fft_method = 'system-specific', &
     
    348353             disturbance_level_t = -9999999.9, &
    349354             dt = -1.0, dt_averaging_input = 0.0, &
    350              dt_averaging_input_pr = 9999999.9, dt_data_output = 9999999.9, &
     355             dt_averaging_input_pr = 9999999.9, dt_coupling = 9999999.9, &
     356             dt_data_output = 9999999.9, &
    351357             dt_data_output_av = 9999999.9, dt_disturb = 9999999.9, &
    352358             dt_dopr = 9999999.9, dt_dopr_listing = 9999999.9, &
     
    382388             surface_scalarflux = 0.0, surface_waterflux = 0.0, &
    383389             s_surface = 0.0, s_surface_initial_change = 0.0, &
    384              termination_time_needed = -1.0, time_disturb = 0.0, &
     390             termination_time_needed = -1.0, time_coupling = 0.0, &
     391             time_disturb = 0.0, &
    385392             time_dopr = 0.0, time_dopr_av = 0.0, time_dopr_listing = 0.0, &
    386393             time_dopts = 0.0, time_dosp = 0.0, time_dosp_av = 0.0, &
     
    389396             time_do_sla = 0.0, time_dvrp = 0.0, time_prel = 0.0, &
    390397             time_restart = 9999999.9, time_run_control = 0.0, &
    391              top_heatflux = 9999999.9, top_salinityflux = 9999999.9, &
     398             top_heatflux = 9999999.9, top_momentumflux_u = 0.0, &
     399             top_momentumflux_v = 0.0, top_salinityflux = 9999999.9, &
    392400             ug_surface = 0.0, u_gtrans = 0.0, &
    393401             ups_limit_e = 0.0, ups_limit_pt = 0.0, ups_limit_u = 0.0, &
     
    916924
    917925#if defined( __parallel )
    918     INTEGER ::  comm1dx, comm1dy, comm2d, comm_palm, ierr, myidx, myidy,       &
    919                 ndim = 2, ngp_y, pleft, pnorth, pright, psouth,                &
     926#if defined( __mpi2 )
     927    CHARACTER (LEN=MPI_MAX_PORT_NAME) ::  port_name
     928#endif
     929
     930    INTEGER ::  comm1dx, comm1dy, comm2d, comm_inter, comm_palm, ierr, myidx,  &
     931                myidy, ndim = 2, ngp_xy, ngp_y, pleft, pnorth, pright, psouth, &
    920932                sendrecvcount_xy, sendrecvcount_yz, sendrecvcount_zx,          &
    921933                sendrecvcount_zyd, sendrecvcount_yxd,                          &
    922                 type_x, type_x_int, ibuf(12), pcoord(2), pdims(2),             &
    923                 status(MPI_STATUS_SIZE)
     934                type_x, type_x_int, type_xy
     935
     936    INTEGER ::  ibuf(12), pcoord(2), pdims(2), status(MPI_STATUS_SIZE)
    924937
    925938    INTEGER, DIMENSION(:), ALLOCATABLE ::  ngp_yz, type_xz
Note: See TracChangeset for help on using the changeset viewer.