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

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

pmc-change in server-client get-put, spectra-directives removed, spectra-package modularized

  • Property svn:keywords set to Id
File size: 7.5 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! change in client-server data transfer: server now gets data from client
23! instead that client put's it to the server
24!
25! Former revisions:
26! -----------------
27! $Id: pmc_general.f90 1786 2016-03-08 05:49:27Z raasch $
28!
29! 1779 2016-03-03 08:01:28Z raasch
30! PMC_MPI_REAL removed, dim_order removed from type arraydef,
31! array management changed from linked list to sequential loop
32!
33! 1766 2016-02-29 08:37:15Z raasch
34! +po_data in type arraydef
35!
36! 1764 2016-02-28 12:45:19Z raasch
37! cpp-statement added (nesting can only be used in parallel mode),
38! all kinds given in PALM style
39!
40! 1762 2016-02-25 12:31:13Z hellstea
41! Initial revision by K. Ketelsen
42!
43! Description:
44! ------------
45!
46! Structure definition and utilities of Palm Model Coupler
47!------------------------------------------------------------------------------!
48
49#if defined( __parallel )
50   use, intrinsic :: iso_c_binding
51
52   USE kinds
53
54#if defined( __lc )
55    USE MPI
56#else
57    INCLUDE "mpif.h"
58#endif
59
60   IMPLICIT none
61   PRIVATE
62   SAVE
63
64! return status
65   INTEGER,parameter,PUBLIC              :: PMC_STATUS_OK    = 0
66   INTEGER,parameter,PUBLIC              :: PMC_STATUS_ERROR = -1
67   INTEGER,parameter,PUBLIC              :: PMC_DA_NAME_ERR  = 10
68
69   INTEGER,parameter,PUBLIC              :: PMC_MAX_ARRAY    = 32  !Max Number of Array which can be coupled
70   INTEGER,parameter,PUBLIC              :: PMC_MAX_MODELL   = 64
71   INTEGER,parameter,PUBLIC              :: DA_Desclen       = 8
72   INTEGER,parameter,PUBLIC              :: DA_Namelen       = 16
73
74   TYPE, PUBLIC :: xy_ind                                          ! Pair of indices in horizontal plane
75      INTEGER                       ::  i
76      INTEGER                       ::  j
77   END TYPE
78
79   TYPE, PUBLIC :: ArrayDef
80      INTEGER                       :: coupleIndex
81      INTEGER                       :: NrDims                      ! Number of Dimensions
82      INTEGER,DIMENSION(4)          :: A_dim                       ! Size of dimensions
83      TYPE(c_ptr)                   :: data                        ! Pointer of data in server space
84      TYPE(c_ptr), DIMENSION(2)     :: po_data                     ! Base Pointers, PMC_S_Set_Active_data_array sets active pointer
85      INTEGER(idp)                  :: SendIndex                   ! index in Send Buffer
86      INTEGER(idp)                  :: RecvIndex                   ! index in Receive Buffer
87      INTEGER                       :: SendSize                    ! size in Send Buffer
88      INTEGER                       :: RecvSize                    ! size in Receiver Buffer
89      TYPE (c_ptr)                  :: SendBuf                     ! Pointer of Data in Send buffer
90      TYPE (c_ptr)                  :: RecvBuf                     ! Pointer of Data in ReceiveS buffer
91      CHARACTER(len=8)              :: Name                        ! Name of Array
92
93      Type(ArrayDef),POINTER        :: next
94   END TYPE ArrayDef
95
96   TYPE (ArrayDef), PUBLIC, POINTER :: next;
97
98   TYPE, PUBLIC :: PeDef
99      INTEGER                                :: Nr_arrays=0        ! Number of arrays which will be transfered in this run
100      INTEGER                                :: NrEle              ! Number of Elemets, same for all arrays
101      TYPE (xy_ind), POINTER,DIMENSION(:)    :: locInd             ! xy index local array for remote PE
102      TYPE( ArrayDef), POINTER, DIMENSION(:) :: array_list         ! List of Data Arrays to be transfered
103   END TYPE PeDef
104
105   TYPE, PUBLIC :: ClientDef
106      INTEGER(idp)                  :: TotalBufferSize
107      INTEGER                       :: model_comm                  ! Communicator of this model
108      INTEGER                       :: inter_comm                  ! Inter communicator model and client
109      INTEGER                       :: intra_comm                  ! Intra communicator model and client
110      INTEGER                       :: model_rank                  ! Rank of this model
111      INTEGER                       :: model_npes                  ! Number of PEs this model
112      INTEGER                       :: inter_npes                  ! Number of PEs client model
113      INTEGER                       :: intra_rank                  ! rank within intra_comm
114      INTEGER                       :: win_server_client           ! MPI RMA for preparing data on server AND client side
115      TYPE (PeDef), DIMENSION(:), POINTER      :: PEs              ! List of all Client PEs
116   END TYPE ClientDef
117
118   TYPE, PUBLIC    :: DA_NameDef                                   ! Data Array Name Definition
119      INTEGER                       :: couple_index                ! Unique Number of Array
120      CHARACTER(len=DA_Desclen)     :: ServerDesc                  ! Server array description
121      CHARACTER(len=DA_Namelen)     :: NameOnServer                ! Name of array within Server
122      CHARACTER(len=DA_Desclen)     :: ClientDesc                  ! Client array description
123      CHARACTER(len=DA_Namelen)     :: NameOnClient                ! Name of array within Client
124    END TYPE DA_NameDef
125
126    INTERFACE PMC_G_SetName
127       MODULE procedure PMC_G_SetName
128    end INTERFACE PMC_G_SetName
129
130    INTERFACE PMC_sort
131       MODULE procedure sort_2d_i
132    end INTERFACE PMC_sort
133
134    PUBLIC PMC_G_SetName, PMC_sort
135
136
137 CONTAINS
138    SUBROUTINE PMC_G_SetName (myClient, couple_index, aName)
139       IMPLICIT none
140
141       TYPE(ClientDef),INTENT(INOUT)           :: myClient
142       INTEGER,INTENT(IN)                      :: couple_index
143       CHARACTER(LEN=*)                        :: aName
144
145       INTEGER                                 :: i
146       TYPE(ArrayDef),POINTER                  :: ar
147       TYPE(PeDef),POINTER                     :: aPE
148
149!
150!--    Assign array to next free index in array_list.
151!--    Set name of array in ArrayDef structure
152       do i=1,myClient%inter_npes
153          aPE => myClient%PEs(i)
154          aPE%Nr_arrays = aPE%Nr_arrays+1
155          aPE%array_list(aPE%Nr_arrays)%name        = aName
156          aPE%array_list(aPE%Nr_arrays)%coupleIndex = couple_index
157       end do
158
159       return
160    end SUBROUTINE PMC_G_SetName
161
162
163    SUBROUTINE sort_2d_i (array,sort_ind)
164       IMPLICIT none
165       INTEGER,DIMENSION(:,:),INTENT(INOUT)         :: array
166       INTEGER,INTENT(IN)                           :: sort_ind
167
168       !-- local Variables
169       INTEGER      :: i,j,n
170       INTEGER,DIMENSION(size(array,1))             :: tmp
171
172       n = size(array,2)
173       do j=1,n-1
174          do i=j+1,n
175             if(array(sort_ind,i) < array(sort_ind,j) )  then
176                tmp = array(:,i)
177                array(:,i) = array(:,j)
178                array(:,j) = tmp
179             end if
180          end do
181       end do
182
183       return
184    END  SUBROUTINE sort_2d_i
185
186#endif
187end MODULE pmc_general
Note: See TracBrowser for help on using the repository browser.