source: palm/trunk/SOURCE/pmc_general.f90 @ 1779

Last change on this file since 1779 was 1779, checked in by raasch, 8 years ago

pmc array management changed from linked list to sequential loop; further small changes and cosmetics for the pmc

  • Property svn:keywords set to Id
File size: 7.0 KB
Line 
1MODULE pmc_general
2
3!--------------------------------------------------------------------------------!
4! This file is part of PALM.
5!
6! PALM is free software: you can redistribute it and/or modify it under the terms
7! of the GNU General Public License as published by the Free Software Foundation,
8! either version 3 of the License, or (at your option) any later version.
9!
10! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
11! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
12! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
13!
14! You should have received a copy of the GNU General Public License along with
15! PALM. If not, see <http://www.gnu.org/licenses/>.
16!
17! Copyright 1997-2015 Leibniz Universitaet Hannover
18!--------------------------------------------------------------------------------!
19!
20! Current revisions:
21! ------------------
22! PMC_MPI_REAL removed, dim_order removed from type arraydef,
23! array management changed from linked list to sequential loop
24!
25! Former revisions:
26! -----------------
27! $Id: pmc_general.f90 1779 2016-03-03 08:01:28Z raasch $
28!
29! 1766 2016-02-29 08:37:15Z raasch
30! +po_data in type arraydef
31!
32! 1764 2016-02-28 12:45:19Z raasch
33! cpp-statement added (nesting can only be used in parallel mode),
34! all kinds given in PALM style
35!
36! 1762 2016-02-25 12:31:13Z hellstea
37! Initial revision by K. Ketelsen
38!
39! Description:
40! ------------
41!
42! Structure definition and utilities of Palm Model Coupler
43!------------------------------------------------------------------------------!
44
45#if defined( __parallel )
46   use, intrinsic :: iso_c_binding
47
48   USE kinds
49
50#if defined( __lc )
51    USE MPI
52#else
53    INCLUDE "mpif.h"
54#endif
55
56   IMPLICIT none
57   PRIVATE
58   SAVE
59
60! return status
61   INTEGER,parameter,PUBLIC              :: PMC_STATUS_OK    = 0
62   INTEGER,parameter,PUBLIC              :: PMC_STATUS_ERROR = -1
63   INTEGER,parameter,PUBLIC              :: PMC_DA_NAME_ERR  = 10
64
65   INTEGER,parameter,PUBLIC              :: PMC_MAX_ARRAY    = 32  !Max Number of Array which can be coupled
66   INTEGER,parameter,PUBLIC              :: PMC_MAX_MODELL   = 64
67   INTEGER,parameter,PUBLIC              :: DA_Desclen       = 8
68   INTEGER,parameter,PUBLIC              :: DA_Namelen       = 16
69
70   TYPE, PUBLIC :: xy_ind                                          ! Pair of indices in horizontal plane
71      INTEGER                       ::  i
72      INTEGER                       ::  j
73   END TYPE
74
75   TYPE, PUBLIC :: ArrayDef
76      INTEGER                       :: coupleIndex
77      INTEGER                       :: NrDims                      ! Number of Dimensions
78      INTEGER,DIMENSION(4)          :: A_dim                       ! Size of dimensions
79      TYPE(c_ptr)                   :: data                        ! Pointer of data in server space
80      TYPE(c_ptr), DIMENSION(2)     :: po_data                     ! Base Pointers, PMC_S_Set_Active_data_array sets active pointer
81      INTEGER(idp)                  :: BufIndex                    ! index in Send Buffer
82      INTEGER                       :: BufSize                     ! size in Send Buffer
83      TYPE (c_ptr)                  :: SendBuf                     ! Pointer of Data in Send buffer
84      CHARACTER(len=8)              :: Name                        ! Name of Array
85
86      Type(ArrayDef),POINTER        :: next
87   END TYPE ArrayDef
88
89   TYPE (ArrayDef), PUBLIC, POINTER :: next;
90
91   TYPE, PUBLIC :: PeDef
92      INTEGER                                :: Nr_arrays=0        ! Number of arrays which will be transfered in this run
93      INTEGER                                :: NrEle              ! Number of Elemets, same for all arrays
94      TYPE (xy_ind), POINTER,DIMENSION(:)    :: locInd             ! xy index local array for remote PE
95      TYPE( ArrayDef), POINTER, DIMENSION(:) :: array_list         ! List of Data Arrays to be transfered
96   END TYPE PeDef
97
98   TYPE, PUBLIC :: ClientDef
99      INTEGER(idp)                  :: TotalBufferSize
100      INTEGER                       :: model_comm                  ! Communicator of this model
101      INTEGER                       :: inter_comm                  ! Inter communicator model and client
102      INTEGER                       :: intra_comm                  ! Intra communicator model and client
103      INTEGER                       :: model_rank                  ! Rank of this model
104      INTEGER                       :: model_npes                  ! Number of PEs this model
105      INTEGER                       :: inter_npes                  ! Number of PEs client model
106      INTEGER                       :: intra_rank                  ! rank within intra_comm
107      INTEGER                       :: BufWin                      ! MPI RMA windows
108      TYPE (PeDef), DIMENSION(:), POINTER      :: PEs              ! List of all Client PEs
109   END TYPE ClientDef
110
111   TYPE, PUBLIC    :: DA_NameDef                                   ! Data Array Name Definition
112      INTEGER                       :: couple_index                ! Unique Number of Array
113      CHARACTER(len=DA_Desclen)     :: ServerDesc                  ! Server array description
114      CHARACTER(len=DA_Namelen)     :: NameOnServer                ! Name of array within Server
115      CHARACTER(len=DA_Desclen)     :: ClientDesc                  ! Client array description
116      CHARACTER(len=DA_Namelen)     :: NameOnClient                ! Name of array within Client
117    END TYPE DA_NameDef
118
119    INTERFACE PMC_G_SetName
120       MODULE procedure PMC_G_SetName
121    end INTERFACE PMC_G_SetName
122
123    INTERFACE PMC_sort
124       MODULE procedure sort_2d_i
125    end INTERFACE PMC_sort
126
127    PUBLIC PMC_G_SetName, PMC_sort
128
129
130 CONTAINS
131    SUBROUTINE PMC_G_SetName (myClient, couple_index, aName)
132       IMPLICIT none
133
134       TYPE(ClientDef),INTENT(INOUT)           :: myClient
135       INTEGER,INTENT(IN)                      :: couple_index
136       CHARACTER(LEN=*)                        :: aName
137
138       INTEGER                                 :: i
139       TYPE(ArrayDef),POINTER                  :: ar
140       TYPE(PeDef),POINTER                     :: aPE
141
142!
143!--    Assign array to next free index in array_list.
144!--    Set name of array in ArrayDef structure
145       do i=1,myClient%inter_npes
146          aPE => myClient%PEs(i)
147          aPE%Nr_arrays = aPE%Nr_arrays+1
148          aPE%array_list(aPE%Nr_arrays)%name        = aName
149          aPE%array_list(aPE%Nr_arrays)%coupleIndex = couple_index
150       end do
151
152       return
153    end SUBROUTINE PMC_G_SetName
154
155
156    SUBROUTINE sort_2d_i (array,sort_ind)
157       IMPLICIT none
158       INTEGER,DIMENSION(:,:),INTENT(INOUT)         :: array
159       INTEGER,INTENT(IN)                           :: sort_ind
160
161       !-- local Variables
162       INTEGER      :: i,j,n
163       INTEGER,DIMENSION(size(array,1))             :: tmp
164
165       n = size(array,2)
166       do j=1,n-1
167          do i=j+1,n
168             if(array(sort_ind,i) < array(sort_ind,j) )  then
169                tmp = array(:,i)
170                array(:,i) = array(:,j)
171                array(:,j) = tmp
172             end if
173          end do
174       end do
175
176       return
177    END  SUBROUTINE sort_2d_i
178
179#endif
180end MODULE pmc_general
Note: See TracBrowser for help on using the repository browser.