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_general.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
    37 
     38#if defined( __parallel )
    3839   use, intrinsic :: iso_c_binding
    39    USE            :: MPI
     40
     41   USE kinds
     42
     43#if defined( __lc )
     44    USE MPI
     45#else
     46    INCLUDE "mpif.h"
     47#endif
    4048
    4149   IMPLICIT none
     
    6573      INTEGER                       :: dim_order                   ! Order of Dimensions: 2 = 2D array, 33 = 3D array
    6674      TYPE (c_ptr)                  :: data                        ! Pointer of data in server space
    67       INTEGER(kind=8)               :: BufIndex                    ! index in Send Buffer
     75      INTEGER(idp)                  :: BufIndex                    ! index in Send Buffer
    6876      INTEGER                       :: BufSize                     ! size in Send Buffer
    6977      TYPE (c_ptr)                  :: SendBuf                     ! Pointer of Data in Send buffer
     
    7684
    7785   TYPE, PUBLIC :: PeDef
    78       INTEGER(KIND=8)                     :: NrEle                 ! Number of Elemets
     86      INTEGER(idp)                        :: NrEle                 ! Number of Elemets
    7987      TYPE (xy_ind), POINTER,DIMENSION(:) :: locInd                ! xy index local array for remote PE
    8088      TYPE( ArrayDef), POINTER            :: Arrays                ! Pointer to Data Array List (Type ArrayDef)
     
    8391
    8492   TYPE, PUBLIC :: ClientDef
    85       INTEGER(KIND=8)               :: TotalBufferSize
     93      INTEGER(idp)                  :: TotalBufferSize
    8694      INTEGER                       :: model_comm                  ! Communicator of this model
    8795      INTEGER                       :: inter_comm                  ! Inter communicator model and client
     
    258266    END FUNCTION DA_List_next
    259267
     268#endif
    260269end MODULE pmc_general
Note: See TracChangeset for help on using the changeset viewer.