Ignore:
Timestamp:
Jun 13, 2016 7:12:51 AM (8 years ago)
Author:
hellstea
Message:

last commit documented

File:
1 edited

Legend:

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

    r1901 r1933  
    11 MODULE pmc_general
    22
    3 !--------------------------------------------------------------------------------!
     3!-------------------------------------------------------------------------------!
    44! This file is part of PALM.
    55!
     
    1616!
    1717! Copyright 1997-2016 Leibniz Universitaet Hannover
    18 !--------------------------------------------------------------------------------!
     18!-------------------------------------------------------------------------------!
    1919!
    2020! Current revisions:
    2121! ------------------
    22 !
    23 !
     22! 
     23! 
    2424! Former revisions:
    2525! -----------------
    2626! $Id$
    2727!
     28! 1901 2016-05-04 15:39:38Z raasch
     29! Code clean up. The words server/client changed to parent/child.
     30!
    2831! 1900 2016-05-04 15:27:53Z raasch
    2932! re-formatted to match PALM style, file renamed again
     
    3336!
    3437! 1786 2016-03-08 05:49:27Z raasch
    35 ! change in client-server data transfer: server now gets data from client
    36 ! instead that client put's it to the server
     38! change in child-parent data transfer: parent now gets data from child
     39! instead of that child puts it to the parent
    3740!
    3841! 1779 2016-03-03 08:01:28Z raasch
     
    9093       INTEGER                   :: nrdims       !< number of dimensions
    9194       INTEGER, DIMENSION(4)     :: a_dim        !< size of dimensions
    92        TYPE(C_PTR)               :: data         !< pointer of data in server space
     95       TYPE(C_PTR)               :: data         !< pointer of data in parent space
    9396       TYPE(C_PTR), DIMENSION(2) :: po_data      !< base pointers,
    9497                                                 !< pmc_s_set_active_data_array
     
    113116    END TYPE pedef
    114117
    115     TYPE, PUBLIC ::  clientdef
     118    TYPE, PUBLIC ::  childdef
    116119       INTEGER(idp) ::  totalbuffersize    !<
    117120       INTEGER      ::  model_comm         !< communicator of this model
    118        INTEGER      ::  inter_comm         !< inter communicator model and client
    119        INTEGER      ::  intra_comm         !< intra communicator model and client
     121       INTEGER      ::  inter_comm         !< inter communicator model and child
     122       INTEGER      ::  intra_comm         !< intra communicator model and child
    120123       INTEGER      ::  model_rank         !< rank of this model
    121124       INTEGER      ::  model_npes         !< number of PEs this model
    122        INTEGER      ::  inter_npes         !< number of PEs client model
     125       INTEGER      ::  inter_npes         !< number of PEs child model
    123126       INTEGER      ::  intra_rank         !< rank within intra_comm
    124        INTEGER      ::  win_server_client  !< MPI RMA for preparing data on server AND client side
    125        TYPE(pedef), DIMENSION(:), POINTER ::  pes  !< list of all client PEs
    126     END TYPE clientdef
     127       INTEGER      ::  win_parent_child   !< MPI RMA for preparing data on parent AND child side
     128       TYPE(pedef), DIMENSION(:), POINTER ::  pes  !< list of all child PEs
     129    END TYPE childdef
    127130
    128131    TYPE, PUBLIC ::  da_namedef  !< data array name definition
    129132       INTEGER                   ::  couple_index  !< unique number of array
    130        CHARACTER(LEN=da_desclen) ::  serverdesc    !< server array description
    131        CHARACTER(LEN=da_namelen) ::  nameonserver  !< name of array within server
    132        CHARACTER(LEN=da_desclen) ::  clientdesc    !< client array description
    133        CHARACTER(LEN=da_namelen) ::  nameonclient  !< name of array within client
     133       CHARACTER(LEN=da_desclen) ::  parentdesc    !< parent array description
     134       CHARACTER(LEN=da_namelen) ::  nameonparent  !< name of array within parent
     135       CHARACTER(LEN=da_desclen) ::  childdesc     !< child array description
     136       CHARACTER(LEN=da_namelen) ::  nameonchild   !< name of array within child
    134137    END TYPE da_namedef
    135138
     
    146149 CONTAINS
    147150
    148  SUBROUTINE pmc_g_setname( myclient, couple_index, aname )
     151 SUBROUTINE pmc_g_setname( mychild, couple_index, aname )
    149152
    150153    IMPLICIT NONE
     
    152155    CHARACTER(LEN=*)               ::  aname         !<
    153156    INTEGER, INTENT(IN)            ::  couple_index  !<
    154     TYPE(clientdef), INTENT(INOUT) ::  myclient      !<
     157    TYPE(childdef), INTENT(INOUT)  ::  mychild       !<
    155158
    156159    INTEGER ::  i  !<
     
    162165!-- Assign array to next free index in array list.
    163166!-- Set name of array in arraydef structure
    164     DO  i = 1, myclient%inter_npes
    165 
    166        ape => myclient%pes(i)
     167    DO  i = 1, mychild%inter_npes
     168
     169       ape => mychild%pes(i)
    167170       ape%nr_arrays = ape%nr_arrays + 1
    168171       ape%array_list(ape%nr_arrays)%name        = aname
Note: See TracChangeset for help on using the changeset viewer.