Ignore:
Timestamp:
Mar 21, 2016 4:50:28 PM (8 years ago)
Author:
raasch
Message:

Introduction of different data transfer modes; restart mechanism adjusted for nested runs; parameter consistency checks for nested runs; further formatting cleanup

File:
1 edited

Legend:

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

    r1792 r1797  
    2020! Current revisions:
    2121! ------------------
    22 !
     22! introduction of different datatransfer modes
    2323!
    2424! Former revisions:
     
    498498      REAL(wp), POINTER, DIMENSION(:,:,:) ::  data_3d
    499499
    500       t1 = PMC_Time()
    501       CALL MPI_Barrier(Clients(ClientId)%intra_comm, ierr)              ! Wait for buffer empty
    502       t2 = PMC_Time()
    503       if(present(WaitTime)) WaitTime = t2-t1
     500!--   Synchronization of the model is done in pmci_client_synchronize and pmci_server_synchronize
     501!--   Therefor the RMA window cann be filled without sychronization at this point and the barrier
     502!--   is not necessary
     503!--   Please note that WaitTime has to be set in PMC_S_FillBuffer AND PMC_C_GetBuffer
     504
     505      if(present(WaitTime)) then
     506        t1 = PMC_Time()
     507        CALL MPI_Barrier(Clients(ClientId)%intra_comm, ierr)
     508        t2 = PMC_Time()
     509        WaitTime = t2-t1
     510      end if
    504511
    505512      do ip=1,Clients(ClientId)%inter_npes
Note: See TracChangeset for help on using the changeset viewer.