Ignore:
Timestamp:
Feb 14, 2018 4:01:55 PM (6 years ago)
Author:
thiele
Message:

Introduce particle transfer in nested models

File:
1 edited

Legend:

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

    r2718 r2801  
    2626! -----------------
    2727! $Id$
     28! Introduce particle transfer in nested models.
     29!
     30! 2718 2018-01-02 08:49:38Z maronga
    2831! Corrected "Former revisions" section
    2932!
     
    8891    SAVE
    8992
    90     INTEGER, PARAMETER, PUBLIC :: da_desclen       =  8  !<
    91     INTEGER, PARAMETER, PUBLIC :: da_namelen       = 16  !<
    92     INTEGER, PARAMETER, PUBLIC :: pmc_da_name_err  = 10  !<
    93     INTEGER, PARAMETER, PUBLIC :: pmc_max_array    = 32  !< max # of arrays which can be coupled
    94     INTEGER, PARAMETER, PUBLIC :: pmc_max_models   = 64  !<
    95     INTEGER, PARAMETER, PUBLIC :: pmc_status_ok    =  0  !<
    96     INTEGER, PARAMETER, PUBLIC :: pmc_status_error = -1  !<
     93    INTEGER(iwp), PARAMETER, PUBLIC :: da_desclen       =  8  !<
     94    INTEGER(iwp), PARAMETER, PUBLIC :: da_namelen       = 16  !<
     95    INTEGER(iwp), PARAMETER, PUBLIC :: pmc_da_name_err  = 10  !<
     96    INTEGER(iwp), PARAMETER, PUBLIC :: pmc_max_array    = 32  !< max # of arrays which can be coupled
     97    INTEGER(iwp), PARAMETER, PUBLIC :: pmc_max_models   = 64  !<
     98    INTEGER(iwp), PARAMETER, PUBLIC :: pmc_status_ok    =  0  !<
     99    INTEGER(iwp), PARAMETER, PUBLIC :: pmc_status_error = -1  !<
    97100
    98101
    99102    TYPE, PUBLIC :: xy_ind  !< pair of indices in horizontal plane
    100        INTEGER ::  i
    101        INTEGER ::  j
     103       INTEGER(iwp) ::  i
     104       INTEGER(iwp) ::  j
    102105    END TYPE
    103106
    104107    TYPE, PUBLIC ::  arraydef
    105        INTEGER                   :: coupleindex  !<
    106        INTEGER                   :: nrdims       !< number of dimensions
    107        INTEGER, DIMENSION(4)     :: a_dim        !< size of dimensions
     108       INTEGER(iwp)                   :: coupleindex  !<
     109       INTEGER(iwp)                   :: nrdims       !< number of dimensions
     110       INTEGER(iwp)                   :: dimkey       !< key for NR dimensions and array type
     111       INTEGER(iwp), DIMENSION(4)     :: a_dim        !< size of dimensions
    108112       TYPE(C_PTR)               :: data         !< pointer of data in parent space
    109113       TYPE(C_PTR), DIMENSION(2) :: po_data      !< base pointers,
     
    112116       INTEGER(idp)              :: SendIndex    !< index in send buffer
    113117       INTEGER(idp)              :: RecvIndex    !< index in receive buffer
    114        INTEGER                   :: SendSize     !< size in send buffer
    115        INTEGER                   :: RecvSize     !< size in receive buffer
     118       INTEGER(iwp)              :: SendSize     !< size in send buffer
     119       INTEGER(iwp)              :: RecvSize     !< size in receive buffer
    116120       TYPE(C_PTR)               :: SendBuf      !< data pointer in send buffer
    117121       TYPE(C_PTR)               :: RecvBuf      !< data pointer in receive buffer
     
    123127
    124128    TYPE, PUBLIC ::  pedef
    125        INTEGER :: nr_arrays = 0  !< number of arrays which will be transfered
    126        INTEGER :: nrele          !< number of elements, same for all arrays
     129       INTEGER(iwp) :: nr_arrays = 0  !< number of arrays which will be transfered
     130       INTEGER(iwp) :: nrele          !< number of elements, same for all arrays
    127131       TYPE(xy_ind), POINTER, DIMENSION(:)   ::  locInd      !< xy index local array for remote PE
    128132       TYPE(arraydef), POINTER, DIMENSION(:) ::  array_list  !< list of data arrays to be transfered
     
    131135    TYPE, PUBLIC ::  childdef
    132136       INTEGER(idp) ::  totalbuffersize    !<
    133        INTEGER      ::  model_comm         !< communicator of this model
    134        INTEGER      ::  inter_comm         !< inter communicator model and child
    135        INTEGER      ::  intra_comm         !< intra communicator model and child
    136        INTEGER      ::  model_rank         !< rank of this model
    137        INTEGER      ::  model_npes         !< number of PEs this model
    138        INTEGER      ::  inter_npes         !< number of PEs child model
    139        INTEGER      ::  intra_rank         !< rank within intra_comm
    140        INTEGER      ::  win_parent_child   !< MPI RMA for preparing data on parent AND child side
     137       INTEGER(iwp) ::  model_comm         !< communicator of this model
     138       INTEGER(iwp) ::  inter_comm         !< inter communicator model and child
     139       INTEGER(iwp) ::  intra_comm         !< intra communicator model and child
     140       INTEGER(iwp) ::  model_rank         !< rank of this model
     141       INTEGER(iwp) ::  model_npes         !< number of PEs this model
     142       INTEGER(iwp) ::  inter_npes         !< number of PEs child model
     143       INTEGER(iwp) ::  intra_rank         !< rank within intra_comm
     144       INTEGER(iwp) ::  win_parent_child   !< MPI RMA for preparing data on parent AND child side
    141145       TYPE(pedef), DIMENSION(:), POINTER ::  pes  !< list of all child PEs
    142146    END TYPE childdef
    143147
    144148    TYPE, PUBLIC ::  da_namedef  !< data array name definition
    145        INTEGER                   ::  couple_index  !< unique number of array
     149       INTEGER(iwp)              ::  couple_index  !< unique number of array
    146150       CHARACTER(LEN=da_desclen) ::  parentdesc    !< parent array description
    147151       CHARACTER(LEN=da_namelen) ::  nameonparent  !< name of array within parent
     
    168172    IMPLICIT NONE
    169173
    170     CHARACTER(LEN=*)               ::  aname         !<
    171     INTEGER, INTENT(IN)            ::  couple_index  !<
    172     TYPE(childdef), INTENT(INOUT)  ::  mychild       !<
    173 
    174     INTEGER ::  i  !<
     174    CHARACTER(LEN=*)              ::  aname         !<
     175    INTEGER(iwp), INTENT(IN)      ::  couple_index  !<
     176    TYPE(childdef), INTENT(INOUT) ::  mychild       !<
     177
     178    INTEGER(iwp) ::  i  !<
    175179
    176180    TYPE(arraydef), POINTER ::  ar   !<
     
    195199    IMPLICIT NONE
    196200
    197     INTEGER, INTENT(IN)                    ::  sort_ind
    198     INTEGER, DIMENSION(:,:), INTENT(INOUT) ::  array
    199 
    200     INTEGER ::  i  !<
    201     INTEGER ::  j  !<
    202     INTEGER ::  n  !<
    203 
    204     INTEGER, DIMENSION(SIZE(array,1)) ::  tmp  !<
     201    INTEGER(iwp), INTENT(IN)                    ::  sort_ind
     202    INTEGER(iwp), DIMENSION(:,:), INTENT(INOUT) ::  array
     203
     204    INTEGER(iwp) ::  i  !<
     205    INTEGER(iwp) ::  j  !<
     206    INTEGER(iwp) ::  n  !<
     207
     208    INTEGER(iwp), DIMENSION(SIZE(array,1)) ::  tmp  !<
    205209
    206210    n = SIZE(array,2)
Note: See TracChangeset for help on using the changeset viewer.