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_client.f90

    r1763 r1764  
    2020! Current revisions:
    2121! ------------------
    22 !
     22! cpp-statement added (nesting can only be used in parallel mode),
     23! all kinds given in PALM style
    2324!
    2425! Former revisions:
     
    3536!------------------------------------------------------------------------------!
    3637
     38#if defined( __parallel )
    3739
    3840    use, intrinsic :: iso_c_binding
    3941
    40     USE  mpi
    41     USE  kinds,         ONLY: wp, iwp
     42#if defined( __lc )
     43    USE MPI
     44#else
     45    INCLUDE "mpif.h"
     46#endif
     47    USE  kinds
    4248    USE  PMC_general,   ONLY: ClientDef, DA_NameDef, DA_Namelen, PMC_STATUS_OK, PMC_DA_NAME_ERR, PeDef, ArrayDef, &
    4349                                         DA_Desclen, DA_Namelen, PMC_G_SetName, PMC_G_GetName
     
    5157!   data local to this MODULE
    5258    Type(ClientDef)                       :: me
    53     INTEGER, PARAMETER                    :: dp = wp
     59!-- TO_DO: what is the meaning of this? Could variables declared in this module
     60!--        also have single precision?
     61!    INTEGER, PARAMETER                    :: dp = wp
    5462
    5563    INTEGER, save                         :: myIndex = 0                !Counter and unique number for Data Arrays
     
    310318    SUBROUTINE PMC_C_Set_DataArray_2d (array)
    311319       IMPLICIT none
     320!--    TO_DO: is double precision absolutely required here?
    312321       REAL(kind=dp),INTENT(IN),DIMENSION(:,:)    :: array
    313322       !-- local variables
     
    344353    SUBROUTINE PMC_C_Set_DataArray_3d (array)
    345354       IMPLICIT none
     355!--    TO_DO: is double precision absolutely required here?
    346356       REAL(kind=dp),INTENT(IN),DIMENSION(:,:,:)  :: array
    347357       !-- local variables
     
    377387
    378388   SUBROUTINE PMC_C_setInd_and_AllocMem
     389
    379390      IMPLICIT none
    380391
    381392      INTEGER                                 :: i, ierr
    382393      INTEGER                                 :: arlen, myIndex, tag
    383       INTEGER(kind=8)                         :: bufsize                   ! Size of MPI data Window
     394      INTEGER(idp)                            :: bufsize                   ! Size of MPI data Window
    384395      TYPE(PeDef),POINTER                     :: aPE
    385396      TYPE(ArrayDef),POINTER                  :: ar
     
    574585    END SUBROUTINE PMC_C_PutBuffer
    575586
    576 
    577 ! Private SUBROUTINEs
    578 
     587#endif
    579588END MODULE pmc_client
Note: See TracChangeset for help on using the changeset viewer.