Ignore:
Timestamp:
Jan 6, 2021 11:25:45 AM (4 years ago)
Author:
Giersch
Message:

Reformatted to follow PALM coding standard

File:
1 edited

Legend:

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

    r4828 r4830  
    1  MODULE pmc_general
    2 
     1!> @file pmc_general_mod.f90
    32!--------------------------------------------------------------------------------------------------!
    43! This file is part of the PALM model system.
     
    1817!--------------------------------------------------------------------------------------------------!
    1918!
    20 !
    2119! Current revisions:
    2220! -----------------
     
    2624! -----------------
    2725! $Id$
     26! Reformatted to follow PALM coding standard
     27!
     28! 4828 2021-01-05 11:21:41Z Giersch
    2829! Interface pmc_sort removed. Subroutine description added.
    2930!
     
    4849! Initial revision by K. Ketelsen
    4950!
     51! Authors:
     52! --------
     53!> @author Klaus Ketelsen (no affiliation)
     54!
    5055! Description:
    5156! ------------
    52 !
    53 ! Structure definition and utilities of Palm Model Coupler
     57!> Structure definition and utilities of Palm Model Coupler
    5458!--------------------------------------------------------------------------------------------------!
     59 MODULE pmc_general
    5560
    5661#if defined( __parallel )
     
    6166    USE MPI
    6267
     68
    6369    IMPLICIT NONE
    6470
    65 
    66     PRIVATE
    67     SAVE
    68 
    69     INTEGER(iwp), PARAMETER, PUBLIC :: da_desclen       =  8  !<
    70     INTEGER(iwp), PARAMETER, PUBLIC :: da_namelen       = 16  !<
    71     INTEGER(iwp), PARAMETER, PUBLIC :: pmc_da_name_err  = 10  !<
    72     INTEGER(iwp), PARAMETER, PUBLIC :: pmc_max_models   = 64  !<
    73     INTEGER(iwp), PARAMETER, PUBLIC :: pmc_status_ok    =  0  !<
    74     INTEGER(iwp), PARAMETER, PUBLIC :: pmc_status_error = -1  !<
    75 
    76     INTEGER(iwp), PUBLIC ::  pmc_max_array  !< max # of arrays which can be coupled
    77                                             !< - will be determined dynamically in pmc_interface
    78 
    79 
    80     TYPE, PUBLIC :: xy_ind  !< pair of indices in horizontal plane
    81        INTEGER(iwp) ::  i
    82        INTEGER(iwp) ::  j
     71    INTEGER(iwp) ::  pmc_max_array  !< max # of arrays which can be coupled
     72                                    !< - will be determined dynamically in pmc_interface
     73
     74    INTEGER(iwp), PARAMETER ::  da_desclen       =  8  !<
     75    INTEGER(iwp), PARAMETER ::  da_namelen       = 16  !<
     76    INTEGER(iwp), PARAMETER ::  pmc_da_name_err  = 10  !<
     77    INTEGER(iwp), PARAMETER ::  pmc_max_models   = 64  !<
     78    INTEGER(iwp), PARAMETER ::  pmc_status_ok    =  0  !<
     79    INTEGER(iwp), PARAMETER ::  pmc_status_error = -1  !<
     80
     81    TYPE ::  xy_ind  !< pair of indices in horizontal plane
     82       INTEGER(iwp) ::  i  !<
     83       INTEGER(iwp) ::  j  !<
    8384    END TYPE
    8485
    85     TYPE, PUBLIC ::  arraydef
     86    TYPE ::  arraydef
    8687       CHARACTER(LEN=da_namelen) ::  Name  !< name of array
    8788
     
    9192       INTEGER(iwp) ::  RecvSize     !< size in receive buffer
    9293       INTEGER(iwp) ::  SendSize     !< size in send buffer
    93 
    94        INTEGER(idp) ::  RecvIndex  !< index in receive buffer
    95        INTEGER(idp) ::  SendIndex  !< index in send buffer
     94       INTEGER(idp) ::  RecvIndex    !< index in receive buffer
     95       INTEGER(idp) ::  SendIndex    !< index in send buffer
    9696
    9797       INTEGER(iwp), DIMENSION(4) ::  a_dim  !< size of dimensions
     
    107107    END TYPE arraydef
    108108
    109 
    110     TYPE(arraydef), PUBLIC, POINTER  :: next  !<
    111 
    112 
    113     TYPE, PUBLIC ::  pedef
    114        INTEGER(iwp) :: nr_arrays = 0  !< number of arrays which will be transfered
    115        INTEGER(iwp) :: nrele          !< number of elements, same for all arrays
     109    TYPE ::  pedef
     110       INTEGER(iwp) ::  nr_arrays = 0  !< number of arrays which will be transfered
     111       INTEGER(iwp) ::  nrele          !< number of elements, same for all arrays
    116112
    117113       TYPE(arraydef), POINTER, DIMENSION(:) ::  array_list  !< list of data arrays to be transfered
    118        TYPE(xy_ind), POINTER, DIMENSION(:)   ::  locInd      !< xy index local array for remote PE
     114
     115       TYPE(xy_ind), POINTER, DIMENSION(:) ::  locInd  !< xy index local array for remote PE
    119116    END TYPE pedef
    120117
    121 
    122     TYPE, PUBLIC ::  childdef
    123        INTEGER(iwp) ::  inter_comm         !< inter communicator model and child
    124        INTEGER(iwp) ::  inter_npes         !< number of PEs child model
    125        INTEGER(iwp) ::  intra_comm         !< intra communicator model and child
    126        INTEGER(iwp) ::  intra_rank         !< rank within intra_comm
    127        INTEGER(iwp) ::  model_comm         !< communicator of this model
    128        INTEGER(iwp) ::  model_npes         !< number of PEs this model
    129        INTEGER(iwp) ::  model_rank         !< rank of this model
    130        INTEGER(idp) ::  totalbuffersize    !<
    131        INTEGER(iwp) ::  win_parent_child   !< MPI RMA for preparing data on parent AND child side
     118    TYPE ::  childdef
     119       INTEGER(iwp) ::  inter_comm        !< inter communicator model and child
     120       INTEGER(iwp) ::  inter_npes        !< number of PEs child model
     121       INTEGER(iwp) ::  intra_comm        !< intra communicator model and child
     122       INTEGER(iwp) ::  intra_rank        !< rank within intra_comm
     123       INTEGER(iwp) ::  model_comm        !< communicator of this model
     124       INTEGER(iwp) ::  model_npes        !< number of PEs this model
     125       INTEGER(iwp) ::  model_rank        !< rank of this model
     126       INTEGER(idp) ::  totalbuffersize   !<
     127       INTEGER(iwp) ::  win_parent_child  !< MPI RMA for preparing data on parent AND child side
     128
    132129       TYPE(pedef), DIMENSION(:), POINTER ::  pes  !< list of all child PEs
    133130    END TYPE childdef
    134131
    135 
    136     TYPE, PUBLIC ::  da_namedef  !< data array name definition
     132    TYPE ::  da_namedef  !< data array name definition
    137133       CHARACTER(LEN=da_desclen) ::  childdesc     !< child array description
    138134       CHARACTER(LEN=da_namelen) ::  nameonchild   !< name of array within child
    139135       CHARACTER(LEN=da_namelen) ::  nameonparent  !< name of array within parent
    140136       CHARACTER(LEN=da_desclen) ::  parentdesc    !< parent array description
    141        INTEGER(iwp)              ::  couple_index  !< unique number of array
     137
     138       INTEGER(iwp) ::  couple_index  !< unique number of array
    142139    END TYPE da_namedef
     140
     141    TYPE(arraydef), POINTER ::  next  !<
     142
     143    SAVE
     144
     145    PRIVATE
     146
     147!
     148!-- Public functions
     149    PUBLIC pmc_g_setname
     150
     151!
     152!-- Public variables, constants and types
     153    PUBLIC arraydef,                                                                               &
     154           childdef,                                                                               &
     155           da_desclen,                                                                             &
     156           da_namedef,                                                                             &
     157           da_namelen,                                                                             &
     158           next,                                                                                   &
     159           pedef,                                                                                  &
     160           pmc_da_name_err,                                                                        &
     161           pmc_max_array,                                                                          &
     162           pmc_max_models,                                                                         &
     163           pmc_status_error,                                                                       &
     164           pmc_status_ok,                                                                          &
     165           xy_ind
    143166
    144167    INTERFACE pmc_g_setname
     
    146169    END INTERFACE pmc_g_setname
    147170
    148     PUBLIC pmc_g_setname
    149171
    150172 CONTAINS
     173
    151174
    152175!---------------------------------------------------------------------------------------------------!
     
    157180 SUBROUTINE pmc_g_setname( mychild, couple_index, aname )
    158181
    159     IMPLICIT NONE
    160 
    161     CHARACTER(LEN=*)              ::  aname         !<
    162 
    163     INTEGER(iwp), INTENT(IN)      ::  couple_index  !<
     182    CHARACTER(LEN=*), INTENT(IN) ::  aname  !<
    164183
    165184    INTEGER(iwp) ::  i  !<
    166185
    167     TYPE(childdef), INTENT(INOUT) ::  mychild       !<
    168 
    169     TYPE(pedef), POINTER    ::  ape  !<
     186    INTEGER(iwp), INTENT(IN) ::  couple_index  !<
     187
     188    TYPE(childdef), INTENT(INOUT) ::  mychild  !<
     189
     190    TYPE(pedef), POINTER ::  ape  !<
     191
    170192
    171193!
     
    180202
    181203 END SUBROUTINE pmc_g_setname
    182 
    183204#endif
     205
     206
    184207 END MODULE pmc_general
Note: See TracChangeset for help on using the changeset viewer.