Rocstar  1.0
Rocstar multiphysics simulation application
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
PEUL_ReceiveDummyVals.F90
Go to the documentation of this file.
1 ! *********************************************************************
2 ! * Rocstar Simulation Suite *
3 ! * Copyright@2015, Illinois Rocstar LLC. All rights reserved. *
4 ! * *
5 ! * Illinois Rocstar LLC *
6 ! * Champaign, IL *
7 ! * www.illinoisrocstar.com *
8 ! * sales@illinoisrocstar.com *
9 ! * *
10 ! * License: See LICENSE file in top level of distribution package or *
11 ! * http://opensource.org/licenses/NCSA *
12 ! *********************************************************************
13 ! *********************************************************************
14 ! * THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, *
15 ! * EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES *
16 ! * OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND *
17 ! * NONINFRINGEMENT. IN NO EVENT SHALL THE CONTRIBUTORS OR *
18 ! * COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER *
19 ! * LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, *
20 ! * Arising FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE *
21 ! * USE OR OTHER DEALINGS WITH THE SOFTWARE. *
22 ! *********************************************************************
23 !******************************************************************************
24 !
25 ! Purpose: receive values to the dummy cells of the patch from neighboring
26 ! region / periodic boundary, which is located on a different
27 ! processor specific to PEUL Module.
28 !
29 ! Description: none.
30 !
31 ! Input: region = current region
32 ! regionSrc = source region
33 ! patch = current patch of region
34 ! patchSrc = source patch of regionSrc.
35 !
36 ! Output: region%levels%peul = flow variables in dummy cells.
37 !
38 ! Notes: none.
39 !
40 !******************************************************************************
41 !
42 ! $Id: PEUL_ReceiveDummyVals.F90,v 1.3 2008/12/06 08:44:39 mtcampbe Exp $
43 !
44 ! Copyright: (c) 2003 by the University of Illinois
45 !
46 !******************************************************************************
47 
48 SUBROUTINE peul_receivedummyvals( region,regionSrc,patch,patchSrc )
49 
50  USE moddatatypes
51  USE modparteul, ONLY : t_buffer_peul
52  USE modbndpatch, ONLY : t_patch
53  USE moddatastruct, ONLY : t_region
54  USE modglobal, ONLY : t_global
56  USE moderror
57  USE modmpi
58  USE modparameters
60  IMPLICIT NONE
61 
62 #include "Indexing.h"
63 
64 ! ... parameters
65  TYPE(t_region), INTENT(INOUT) :: region
66  TYPE(t_region), INTENT(IN) :: regionsrc
67  TYPE(t_patch), INTENT(INOUT) :: patch
68  TYPE(t_patch), INTENT(IN) :: patchsrc
69 
70 ! ... loop variables
71  INTEGER :: icv, idum, i, j, k, ijkbuff
72 
73 ! ... local variables
74  CHARACTER(CHRLEN) :: rcsidentstring
75 
76 #ifdef MPI
77  INTEGER :: status(mpi_status_size)
78 #endif
79  INTEGER :: lb, ibeg, iend, jbeg, jend, kbeg, kend, icoff, ijcoff, ijkd, &
80  n1, n2, ncv, ndim, ndimrecvbuff, source, tagpeul, ilev
81 
82  REAL(RFREAL), POINTER, DIMENSION(:) :: precvbuffeul
83  REAL(RFREAL), POINTER, DIMENSION(:,:) :: pcv
84 
85  TYPE(t_global), POINTER :: global
86 
87 !******************************************************************************
88 
89  rcsidentstring = '$RCSfile: PEUL_ReceiveDummyVals.F90,v $ $Revision: 1.3 $'
90 
91  global => region%global
92 
93  CALL registerfunction( global,'PEUL_ReceiveDummyVals',&
94  'PEUL_ReceiveDummyVals.F90' )
95 
96 ! check if the source region is active ----------------------------------------
97 
98  IF (regionsrc%active == off) THEN
99  CALL errorstop( global,err_srcregion_off,__line__ )
100  ENDIF
101 
102 ! get dimensions and pointers -------------------------------------------------
103 
104  ilev = region%currLevel
105 
106  CALL rflo_getpatchindices( region,patch,ilev,ibeg,iend, &
107  jbeg,jend,kbeg,kend )
108  CALL rflo_getcelloffset( region,ilev,icoff,ijcoff )
109 
110  pcv => region%levels(ilev)%peul%cv
111  precvbuffeul => patch%bufferPeul%recvBuff
112 
113  n1 = abs(patch%l1end-patch%l1beg) + 1 ! here, dimensions of current
114  n2 = abs(patch%l2end-patch%l2beg) + 1 ! and source patch are identical
115  ndim = n1*n2*region%nDumCells ! ... but not the # of dummy cells
116 
117  ncv = region%levels(ilev)%peul%nCv
118 
119  IF (ncv /= region%peulInput%nPtypes) &
120  CALL errorstop( region%global,err_peul_npmismatch,__line__ )
121 
122  ndimrecvbuff = ncv*ndim
123 
124 ! receive data ----------------------------------------------------------------
125 
126 #ifdef MPI
127  source = regionsrc%procid
128  tagpeul = region%localNumber + mpi_patchoff*patchsrc%srcPatch &
129  * peul_tag_shift
130  CALL mpi_recv( precvbuffeul,ndimrecvbuff,mpi_rfreal, &
131  source,tagpeul,global%mpiComm,status,global%mpierr )
132  IF (global%mpierr /= err_none) &
133  CALL errorstop( global,err_mpi_trouble,__line__ )
134 #endif
135 
136 ! copy from buffer to dummy nodes ---------------------------------------------
137 
138  lb = patch%lbound
139  ijkbuff = 0
140 
141  DO icv = 1, ncv
142  DO idum=1,region%nDumCells
143 
144 ! - face i=const. -------------------------------------------------------------
145 
146  IF (lb==1 .OR. lb==2) THEN
147 
148  SELECT CASE(lb)
149  CASE(1)
150  i = ibeg - idum
151  CASE(2)
152  i = iend + idum
153  END SELECT ! lb
154 
155  DO k=kbeg,kend
156  DO j=jbeg,jend
157  ijkd = indijk(i,j,k,icoff,ijcoff)
158  ijkbuff = ijkbuff + 1
159  pcv(icv,ijkd) = precvbuffeul(ijkbuff)
160  ENDDO ! j
161  ENDDO ! k
162 
163 ! - face j=const. -------------------------------------------------------------
164 
165  ELSE IF (lb==3 .OR. lb==4) THEN
166 
167  SELECT CASE(lb)
168  CASE(3)
169  j = jbeg - idum
170  CASE(4)
171  j = jend + idum
172  END SELECT ! lb
173 
174  DO i=ibeg,iend
175  DO k=kbeg,kend
176  ijkd = indijk(i,j,k,icoff,ijcoff)
177  ijkbuff = ijkbuff + 1
178  pcv(icv,ijkd) = precvbuffeul(ijkbuff)
179  ENDDO ! k
180  ENDDO ! i
181 
182 ! - face k=const.
183 
184  ELSE IF (lb==5 .OR. lb==6) THEN
185 
186  SELECT CASE(lb)
187  CASE(5)
188  k = kbeg - idum
189  CASE(6)
190  k = kend + idum
191  END SELECT ! lb
192 
193  DO j=jbeg,jend
194  DO i=ibeg,iend
195  ijkd = indijk(i,j,k,icoff,ijcoff)
196  ijkbuff = ijkbuff + 1
197  pcv(icv,ijkd) = precvbuffeul(ijkbuff)
198  ENDDO ! j
199  ENDDO ! i
200  ENDIF ! lb
201 
202  ENDDO ! idum
203  ENDDO ! iCv
204 
205 ! finalize --------------------------------------------------------------------
206 
207  CALL deregisterfunction( global )
208 
209 END SUBROUTINE peul_receivedummyvals
210 
211 !******************************************************************************
212 !
213 ! RCS Revision history:
214 !
215 ! $Log: PEUL_ReceiveDummyVals.F90,v $
216 ! Revision 1.3 2008/12/06 08:44:39 mtcampbe
217 ! Updated license.
218 !
219 ! Revision 1.2 2008/11/19 22:17:52 mtcampbe
220 ! Added Illinois Open Source License/Copyright
221 !
222 ! Revision 1.1 2004/12/01 21:09:52 haselbac
223 ! Initial revision after changing case
224 !
225 ! Revision 1.5 2004/04/15 16:04:03 jferry
226 ! minor formatting (removed trailing spaces)
227 !
228 ! Revision 1.4 2004/03/02 21:44:07 jferry
229 ! Added corner and edge cell data structures and routines
230 !
231 ! Revision 1.3 2003/05/15 02:57:05 jblazek
232 ! Inlined index function.
233 !
234 ! Revision 1.2 2003/04/09 20:57:24 fnajjar
235 ! Fixed sign error for ibeg, iend
236 !
237 ! Revision 1.1 2003/04/09 14:34:25 fnajjar
238 ! Initial Import of MPI-based rocsmoke
239 !
240 !******************************************************************************
241 
242 
243 
244 
245 
246 
247 
**********************************************************************Rocstar Simulation Suite Illinois Rocstar LLC All rights reserved ****Illinois Rocstar LLC IL **www illinoisrocstar com **sales illinoisrocstar com WITHOUT WARRANTY OF ANY **EXPRESS OR INCLUDING BUT NOT LIMITED TO THE WARRANTIES **OF FITNESS FOR A PARTICULAR PURPOSE AND **NONINFRINGEMENT IN NO EVENT SHALL THE CONTRIBUTORS OR **COPYRIGHT HOLDERS BE LIABLE FOR ANY DAMAGES OR OTHER WHETHER IN AN ACTION OF TORT OR **Arising OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE **USE OR OTHER DEALINGS WITH THE SOFTWARE **********************************************************************INTERFACE SUBROUTINE ibeg
j indices k indices k
Definition: Indexing.h:6
subroutine registerfunction(global, funName, fileName)
Definition: ModError.F90:449
int status() const
Obtain the status of the attribute.
Definition: Attribute.h:240
subroutine rflo_getpatchindices(region, patch, iLev, ibeg, iend, jbeg, jend, kbeg, kend)
Definition: patch.h:74
**********************************************************************Rocstar Simulation Suite Illinois Rocstar LLC All rights reserved ****Illinois Rocstar LLC IL **www illinoisrocstar com **sales illinoisrocstar com WITHOUT WARRANTY OF ANY **EXPRESS OR INCLUDING BUT NOT LIMITED TO THE WARRANTIES **OF FITNESS FOR A PARTICULAR PURPOSE AND **NONINFRINGEMENT IN NO EVENT SHALL THE CONTRIBUTORS OR **COPYRIGHT HOLDERS BE LIABLE FOR ANY DAMAGES OR OTHER WHETHER IN AN ACTION OF TORT OR **Arising OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE **USE OR OTHER DEALINGS WITH THE SOFTWARE **********************************************************************INTERFACE SUBROUTINE knode iend
blockLoc i
Definition: read.cpp:79
subroutine peul_receivedummyvals(region, regionSrc, patch, patchSrc)
subroutine rflo_getcelloffset(region, iLev, iCellOffset, ijCellOffset)
j indices j
Definition: Indexing.h:6
**********************************************************************Rocstar Simulation Suite Illinois Rocstar LLC All rights reserved ****Illinois Rocstar LLC IL **www illinoisrocstar com **sales illinoisrocstar com WITHOUT WARRANTY OF ANY **EXPRESS OR INCLUDING BUT NOT LIMITED TO THE WARRANTIES **OF FITNESS FOR A PARTICULAR PURPOSE AND **NONINFRINGEMENT IN NO EVENT SHALL THE CONTRIBUTORS OR **COPYRIGHT HOLDERS BE LIABLE FOR ANY DAMAGES OR OTHER WHETHER IN AN ACTION OF TORT OR **Arising OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE **USE OR OTHER DEALINGS WITH THE SOFTWARE **********************************************************************INTERFACE SUBROUTINE knode jend
CGAL::Point_2< R > source() const
Definition: Ray_2.h:128
subroutine errorstop(global, errorCode, errorLine, addMessage)
Definition: ModError.F90:483
**********************************************************************Rocstar Simulation Suite Illinois Rocstar LLC All rights reserved ****Illinois Rocstar LLC IL **www illinoisrocstar com **sales illinoisrocstar com WITHOUT WARRANTY OF ANY **EXPRESS OR INCLUDING BUT NOT LIMITED TO THE WARRANTIES **OF FITNESS FOR A PARTICULAR PURPOSE AND **NONINFRINGEMENT IN NO EVENT SHALL THE CONTRIBUTORS OR **COPYRIGHT HOLDERS BE LIABLE FOR ANY DAMAGES OR OTHER WHETHER IN AN ACTION OF TORT OR **Arising OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE **USE OR OTHER DEALINGS WITH THE SOFTWARE **********************************************************************INTERFACE SUBROUTINE knode jbeg
**********************************************************************Rocstar Simulation Suite Illinois Rocstar LLC All rights reserved ****Illinois Rocstar LLC IL **www illinoisrocstar com **sales illinoisrocstar com WITHOUT WARRANTY OF ANY **EXPRESS OR INCLUDING BUT NOT LIMITED TO THE WARRANTIES **OF FITNESS FOR A PARTICULAR PURPOSE AND **NONINFRINGEMENT IN NO EVENT SHALL THE CONTRIBUTORS OR **COPYRIGHT HOLDERS BE LIABLE FOR ANY DAMAGES OR OTHER WHETHER IN AN ACTION OF TORT OR **Arising OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE **USE OR OTHER DEALINGS WITH THE SOFTWARE **********************************************************************INTERFACE SUBROUTINE knode kbeg
subroutine deregisterfunction(global)
Definition: ModError.F90:469