Ignore:
Timestamp:
Feb 28, 2016 12:45:19 PM (8 years ago)
Author:
raasch
Message:

update of the nested domain system + some bugfixes

File:
1 edited

Legend:

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

    r1763 r1764  
    2020! Current revisions:
    2121! ------------------
    22 !
     22! cpp-statement added (nesting can only be used in parallel mode),
     23! kind-parameters adjusted to PALM-kinds
    2324!
    2425! Former revisions:
     
    3536!------------------------------------------------------------------------------!
    3637
     38#if defined( __parallel )
    3739   use, intrinsic :: iso_c_binding
    3840
    39    USE  mpi
    40    USE  kinds,         ONLY: wp
     41#if defined( __lc )
     42    USE MPI
     43#else
     44    INCLUDE "mpif.h"
     45#endif
     46   USE  kinds
    4147   USE  PMC_handle_communicator, ONLY: m_to_server_comm, m_to_client_comm, m_model_comm, m_model_rank
    4248   IMPLICIT none
     
    4450   SAVE
    4551
    46    INTEGER, PARAMETER :: dp = wp
     52!-- TO_DO: what is the meaning of this? Could variables declared in this module
     53!--        also have single precision?
     54!   INTEGER, PARAMETER :: dp = wp
    4755
    4856
     
    149157   SUBROUTINE  PMC_Send_to_Server_real_r1 (buf, n, Server_rank, tag, ierr)
    150158      IMPLICIT     none
     159!--   TO_DO: has buf always to be of dp-kind, or can wp used here
     160!--          this effects all respective declarations in this file
    151161      REAL(kind=dp), DIMENSION(:), INTENT(IN)   :: buf
    152162      INTEGER, INTENT(IN)                       :: n
     
    485495      IMPLICIT     none
    486496      REAL(kind=wp),DIMENSION(:),POINTER,INTENT(INOUT) :: array
    487       INTEGER(kind=8),INTENT(IN)                       :: idim1
     497      INTEGER(idp),INTENT(IN)                          :: idim1
    488498      Type(c_ptr),INTENT(OUT),optional                 :: base_ptr
    489499
     
    516526    END FUNCTION PMC_TIME
    517527
     528#endif
    518529 END MODULE pmc_mpi_wrapper
Note: See TracChangeset for help on using the changeset viewer.