Ignore:
Timestamp:
Mar 3, 2016 8:01:28 AM (8 years ago)
Author:
raasch
Message:

pmc array management changed from linked list to sequential loop; further small changes and cosmetics for the pmc

File:
1 edited

Legend:

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

    r1767 r1779  
    2020! Current revisions:
    2121! ------------------
    22 !
     22! only the total number of PEs is given for the domains, npe_x and npe_y
     23! replaced by npe_total,
     24! array management changed from linked list to sequential loop
    2325!
    2426! Former revisions:
     
    5961
    6062    USE control_parameters,                                                    &
    61         ONLY:  dt_3d, dz, humidity, message_string, nest_bound_l,              &
    62                nest_bound_r, nest_bound_s, nest_bound_n, passive_scalar,       &
    63                simulated_time, topography, volume_flow
     63        ONLY:  coupling_char, dt_3d, dz, humidity, message_string,             &
     64               nest_bound_l, nest_bound_r, nest_bound_s, nest_bound_n,         &
     65               nest_domain, passive_scalar, simulated_time, topography,        &
     66               volume_flow
    6467
    6568    USE cpulog,                                                                &
     
    8891
    8992    USE pmc_client,                                                            &
    90         ONLY:  pmc_clientinit, pmc_c_getnextarray, pmc_c_get_2d_index_list,    &
    91                pmc_c_getbuffer, pmc_c_putbuffer, pmc_c_setind_and_allocmem,    &
     93        ONLY:  pmc_clientinit, pmc_c_clear_next_array_list,                    &
     94               pmc_c_getnextarray, pmc_c_get_2d_index_list, pmc_c_getbuffer,   &
     95               pmc_c_putbuffer, pmc_c_setind_and_allocmem,                     &
    9296               pmc_c_set_dataarray, pmc_set_dataarray_name
    9397
     
    104108
    105109    USE pmc_server,                                                            &
    106         ONLY:  pmc_serverinit, pmc_s_fillbuffer, pmc_s_getdata_from_buffer,    &
    107                pmc_s_getnextarray, pmc_s_setind_and_allocmem,                  &
    108                pmc_s_set_active_data_array, pmc_s_set_dataarray,               &
    109                pmc_s_set_2d_index_list
     110        ONLY:  pmc_serverinit, pmc_s_clear_next_array_list, pmc_s_fillbuffer,  &
     111               pmc_s_getdata_from_buffer, pmc_s_getnextarray,                  &
     112               pmc_s_setind_and_allocmem, pmc_s_set_active_data_array,         &
     113               pmc_s_set_dataarray, pmc_s_set_2d_index_list
    110114
    111115#endif
     
    116120!--        limit. Try to reduce as much as possible
    117121
    118 !-- TO_DO: shouldn't we use public as default here? Only a minority of the
    119 !-- variables is private.
     122!-- TO_DO: are all of these variables following now really PUBLIC?
     123!--        Klaus and I guess they are not
    120124    PRIVATE    !:  Note that the default publicity is here set to private.
    121125
     
    129133    INTEGER(iwp), PUBLIC, SAVE      ::  cpl_id  = 1            !:
    130134    CHARACTER(LEN=32), PUBLIC, SAVE ::  cpl_name               !:
    131     INTEGER(iwp), PUBLIC, SAVE      ::  cpl_npex               !:
    132     INTEGER(iwp), PUBLIC, SAVE      ::  cpl_npey               !:
     135    INTEGER(iwp), PUBLIC, SAVE      ::  cpl_npe_total          !:
    133136    INTEGER(iwp), PUBLIC, SAVE      ::  cpl_parent_id          !:
    134137
     
    266269!-- Module private variables.
    267270    INTEGER(iwp), DIMENSION(3)          ::  define_coarse_grid_int    !:
    268     REAL(wp), DIMENSION(9)              ::  define_coarse_grid_real   !:
     271    REAL(wp), DIMENSION(7)              ::  define_coarse_grid_real   !:
    269272
    270273    TYPE coarsegrid_def
     
    364367!
    365368!--    This is not a nested run
    366 !
    367 !--    TO_DO: this wouldn't be required any more?
    368369       world_comm = MPI_COMM_WORLD
    369370       cpl_id     = 1
    370371       cpl_name   = ""
    371        cpl_npex   = 2
    372        cpl_npey   = 2
    373        lower_left_coord_x = 0.0_wp
    374        lower_left_coord_y = 0.0_wp
     372
    375373       RETURN
    376     ELSE
    377 !
    378 !--    Set the general steering switch which tells PALM that its a nested run
    379        nested_run = .TRUE.
     374
    380375    ENDIF
    381376
     377!
     378!-- Set the general steering switch which tells PALM that its a nested run
     379    nested_run = .TRUE.
     380
     381!
     382!-- Get some variables required by the pmc-interface (and in some cases in the
     383!-- PALM code out of the pmci) out of the pmc-core
    382384    CALL pmc_get_local_model_info( my_cpl_id = cpl_id,                         &
    383385                                   my_cpl_parent_id = cpl_parent_id,           &
    384386                                   cpl_name = cpl_name,                        &
    385                                    npe_x = cpl_npex, npe_y = cpl_npey,         &
     387                                   npe_total = cpl_npe_total,                  &
    386388                                   lower_left_x = lower_left_coord_x,          &
    387389                                   lower_left_y = lower_left_coord_y )
     390!
     391!-- Set the steering switch which tells the models that they are nested (of
     392!-- course the root domain (cpl_id = 1 ) is not nested)
     393    IF ( cpl_id >= 2 )  THEN
     394       nest_domain = .TRUE.
     395       WRITE( coupling_char, '(A1,I2.2)') '_', cpl_id
     396    ENDIF
     397
    388398!
    389399!-- Message that communicators for nesting are initialized.
     
    493503          define_coarse_grid_real(1) = lower_left_coord_x
    494504          define_coarse_grid_real(2) = lower_left_coord_y
    495 !--       TO_DO: remove this?
    496           define_coarse_grid_real(3) = 0             !  KK currently not used.
    497           define_coarse_grid_real(4) = 0
    498           define_coarse_grid_real(5) = dx
    499           define_coarse_grid_real(6) = dy
    500           define_coarse_grid_real(7) = lower_left_coord_x + ( nx + 1 ) * dx
    501           define_coarse_grid_real(8) = lower_left_coord_y + ( ny + 1 ) * dy
    502           define_coarse_grid_real(9) = dz
     505          define_coarse_grid_real(3) = dx
     506          define_coarse_grid_real(4) = dy
     507          define_coarse_grid_real(5) = lower_left_coord_x + ( nx + 1 ) * dx
     508          define_coarse_grid_real(6) = lower_left_coord_y + ( ny + 1 ) * dy
     509          define_coarse_grid_real(7) = dz
    503510
    504511          define_coarse_grid_int(1)  = nx
     
    512519          yez = ( nbgp + 1 ) * dy
    513520          IF ( cl_coord_x(0) < define_coarse_grid_real(1) + xez )          nomatch = 1
    514           IF ( cl_coord_x(nx_cl + 1) > define_coarse_grid_real(7) - xez )  nomatch = 1
     521          IF ( cl_coord_x(nx_cl + 1) > define_coarse_grid_real(5) - xez )  nomatch = 1
    515522          IF ( cl_coord_y(0) < define_coarse_grid_real(2) + yez )          nomatch = 1
    516           IF ( cl_coord_y(ny_cl + 1) > define_coarse_grid_real(8) - yez )  nomatch = 1
     523          IF ( cl_coord_y(ny_cl + 1) > define_coarse_grid_real(6) - yez )  nomatch = 1
    517524
    518525          DEALLOCATE( cl_coord_x )
     
    521528!
    522529!--       Send coarse grid information to client
    523           CALL pmc_send_to_client( client_id, Define_coarse_grid_real, 9, 0,   &
     530          CALL pmc_send_to_client( client_id, Define_coarse_grid_real,         &
     531                                   SIZE(define_coarse_grid_real), 0,           &
    524532                                   21, ierr )
    525533          CALL pmc_send_to_client( client_id, Define_coarse_grid_int,  3, 0,   &
     
    553561!
    554562!--    Include couple arrays into server content
     563       CALL pmc_s_clear_next_array_list
    555564       DO  WHILE ( pmc_s_getnextarray( client_id, myname ) )
    556565          CALL pmci_set_array_pointer( myname, client_id = client_id,          &
     
    676685    IF ( .NOT. pmc_is_rootmodel() )  THEN
    677686       CALL pmc_clientinit
    678        
     687!
     688!--    Here and only here the arrays are defined, which actualy will be
     689!--    exchanged between client and server.
     690!--    Please check, if the arrays are in the list of possible exchange arrays
     691!--    in subroutines:
     692!--    pmci_set_array_pointer (for server arrays)
     693!--    pmci_create_client_arrays (for client arrays)
    679694       CALL pmc_set_dataarray_name( 'coarse', 'u'  ,'fine', 'u',  ierr )
    680695       CALL pmc_set_dataarray_name( 'coarse', 'v'  ,'fine', 'v',  ierr )
     
    709724!
    710725!--       Receive Coarse grid information.
    711           CALL pmc_recv_from_server( define_coarse_grid_real, 9, 0, 21, ierr )
     726          CALL pmc_recv_from_server( define_coarse_grid_real,                  &
     727                                     SIZE(define_coarse_grid_real), 0, 21, ierr )
    712728          CALL pmc_recv_from_server( define_coarse_grid_int,  3, 0, 22, ierr )
    713729
     
    719735          WRITE(0,*) 'startx_tot    = ',define_coarse_grid_real(1)
    720736          WRITE(0,*) 'starty_tot    = ',define_coarse_grid_real(2)
    721           WRITE(0,*) 'endx_tot      = ',define_coarse_grid_real(7)
    722           WRITE(0,*) 'endy_tot      = ',define_coarse_grid_real(8)
    723           WRITE(0,*) 'dx            = ',define_coarse_grid_real(5)
    724           WRITE(0,*) 'dy            = ',define_coarse_grid_real(6)
    725           WRITE(0,*) 'dz            = ',define_coarse_grid_real(9)
     737          WRITE(0,*) 'endx_tot      = ',define_coarse_grid_real(5)
     738          WRITE(0,*) 'endy_tot      = ',define_coarse_grid_real(6)
     739          WRITE(0,*) 'dx            = ',define_coarse_grid_real(3)
     740          WRITE(0,*) 'dy            = ',define_coarse_grid_real(4)
     741          WRITE(0,*) 'dz            = ',define_coarse_grid_real(7)
    726742          WRITE(0,*) 'nx_coarse     = ',define_coarse_grid_int(1)
    727743          WRITE(0,*) 'ny_coarse     = ',define_coarse_grid_int(2)
     
    729745       ENDIF
    730746
    731        CALL MPI_BCAST( define_coarse_grid_real, 9, MPI_REAL, 0, comm2d, ierr )
     747       CALL MPI_BCAST( define_coarse_grid_real, SIZE(define_coarse_grid_real), &
     748                       MPI_REAL, 0, comm2d, ierr )
    732749       CALL MPI_BCAST( define_coarse_grid_int, 3, MPI_INTEGER, 0, comm2d, ierr )
    733750
    734        cg%dx = define_coarse_grid_real(5)
    735        cg%dy = define_coarse_grid_real(6)
    736        cg%dz = define_coarse_grid_real(9)
     751       cg%dx = define_coarse_grid_real(3)
     752       cg%dy = define_coarse_grid_real(4)
     753       cg%dz = define_coarse_grid_real(7)
    737754       cg%nx = define_coarse_grid_int(1)
    738755       cg%ny = define_coarse_grid_int(2)
     
    778795!
    779796!--    Include couple arrays into client content.
     797       CALL  pmc_c_clear_next_array_list
    780798       DO  WHILE ( pmc_c_getnextarray( myname ) )
    781799!--       TO_DO: Klaus, why the c-arrays are still up to cg%nz??
     
    880898           ENDIF
    881899        ENDDO
    882 
    883         WRITE( 0, * )  'Coarse area ', myid, icl, icr, jcs, jcn
    884900
    885901        coarse_bound(1) = icl
     
    33973413!
    33983414!-- List of array names, which can be coupled
     3415!-- In case of 3D please change also the second array for the pointer version
    33993416    IF ( TRIM(name) == "u" )     p_3d => u
    34003417    IF ( TRIM(name) == "v" )     p_3d => v
     
    34033420    IF ( TRIM(name) == "pt" )    p_3d => pt
    34043421    IF ( TRIM(name) == "q" )     p_3d => q
    3405     !IF ( TRIM(name) == "z0" )    p_2d => z0
     3422!
     3423!-- This is just an example for a 2D array, not active for coupling
     3424!-- Please note, that z0 has to be declared as TARGET array in modules.f90
     3425!    IF ( TRIM(name) == "z0" )    p_2d => z0
    34063426
    34073427#if defined( __nopointer )
     
    34313451    IF ( TRIM(name) == "e" )     p_3d_sec => e_2
    34323452    IF ( TRIM(name) == "pt" )    p_3d_sec => pt_2
    3433     !IF ( TRIM(name) == "z0" )    p_2d_sec => z0_2
     3453    IF ( TRIM(name) == "q" )     p_3d_sec => q_2
    34343454
    34353455    IF ( ASSOCIATED( p_3d ) )  THEN
     
    34373457                                 array_2 = p_3d_sec )
    34383458    ELSEIF ( ASSOCIATED( p_2d ) )  THEN
    3439        CALL pmc_s_set_dataarray( client_id, p_2d, array_2 = p_2d_sec )
     3459       CALL pmc_s_set_dataarray( client_id, p_2d )
    34403460    ELSE
    34413461!
Note: See TracChangeset for help on using the changeset viewer.