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

    r1763 r1764  
    2020! Current revisions:
    2121! ------------------
    22 !
     22! cpp-statement added (nesting can only be used in parallel mode)
    2323!
    2424! Former revisions:
     
    3535!------------------------------------------------------------------------------!
    3636
     37#if defined( __parallel )
    3738   use, intrinsic :: iso_c_binding
    3839
    39    USE  mpi
    40    USE  kinds,                     ONLY: wp, iwp
     40#if defined( __lc )
     41    USE MPI
     42#else
     43    INCLUDE "mpif.h"
     44#endif
     45   USE  kinds
    4146   USE  PMC_general,               ONLY: ClientDef, PMC_MAX_MODELL,PMC_sort, DA_NameDef, DA_Desclen, DA_Namelen,       &
    4247                                         PMC_G_SetName, PMC_G_GetName, PeDef, ArrayDef
     
    6065   PUBLIC PMC_Server_for_Client
    6166
    62    INTEGER, PARAMETER :: dp = wp
     67!-- TO_DO: what is the meaning of this? Could variables declared in this module
     68!--        also have single precision?
     69!   INTEGER, PARAMETER :: dp = wp
    6370
    6471   ! INTERFACE section
     
    225232        IMPLICIT none
    226233        INTEGER,INTENT(IN)                         :: ClientId
     234!--   TO_DO: has array always to be of dp-kind, or can wp used here
     235!--          this effects all respective declarations in this file
    227236        REAL(kind=dp),INTENT(IN),DIMENSION(:,:)    :: array
    228237        !-- local variables
     
    282291      INTEGER                                 :: arlen, myIndex, tag
    283292      INTEGER                                 :: rCount                    ! count MPI requests
    284       INTEGER(kind=8)                         :: bufsize                   ! Size of MPI data Window
     293      INTEGER(idp)                            :: bufsize                   ! Size of MPI data Window
    285294      TYPE(PeDef),POINTER                     :: aPE
    286295      TYPE(ArrayDef),POINTER                  :: ar
     
    347356         do while (PMC_S_GetNextArray ( ClientId, myName,i))
    348357            ar  => aPE%Arrays
     358!--         TO_DO:  Adressrechnung ueberlegen?
    349359            ar%SendBuf = c_loc(base_array(ar%BufIndex))                         !kk Adressrechnung ueberlegen
    350360            if(ar%BufIndex+ar%BufSize > bufsize) then
     361!--            TO_DO: can this error really happen, and what can be the reason?
    351362               write(0,'(a,i4,4i7,1x,a)') 'Buffer too small ',i,ar%BufIndex,ar%BufSize,ar%BufIndex+ar%BufSize,bufsize,trim(myName)
    352363               CALL MPI_Abort (MPI_COMM_WORLD, istat, ierr)
     
    402413               end do
    403414            else
     415!--            TO_DO: can this error really happen, and what can be the reason?
    404416               write(0,*) "Illegal Order of Dimension ",ar%dim_order
    405417               CALL MPI_Abort (MPI_COMM_WORLD, istat, ierr);
     
    458470               end do
    459471            else
     472!--            TO_DO: can this error really happen, and what can be the reason?
    460473               write(0,*) "Illegal Order of Dimension ",ar%dim_order
    461474               CALL MPI_Abort (MPI_COMM_WORLD, istat, ierr);
     
    624637    END SUBROUTINE Set_PE_index_list
    625638
     639#endif
    626640END MODULE pmc_server
Note: See TracChangeset for help on using the changeset viewer.