Rocstar  1.0
Rocstar multiphysics simulation application
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
SURF_WriteSurfaceGrid.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: output surface grid for all patches interacting with GenX.
26 !
27 ! Description: none.
28 !
29 ! Input: iReg = global number of current region
30 ! region = dimensions of patches, types of BC`s, grid.
31 !
32 ! Output: to file.
33 !
34 ! Notes: none.
35 !
36 !******************************************************************************
37 !
38 ! $Id: SURF_WriteSurfaceGrid.F90,v 1.4 2008/12/06 08:44:52 mtcampbe Exp $
39 !
40 ! Copyright: (c) 2002 by the University of Illinois
41 !
42 !******************************************************************************
43 
44 SUBROUTINE writesurfacegrid( iReg,region )
45 
46  USE moddatatypes
47  USE modglobal, ONLY : t_global
48  USE modbndpatch, ONLY : t_patch
49  USE moddatastruct, ONLY : t_region
51  USE moderror
52  USE modparameters
53  IMPLICIT NONE
54 
55 #include "Indexing.h"
56 
57 ! ... parameters
58  INTEGER :: ireg
59 
60  TYPE(t_region) :: region
61 
62 ! ... loop variables
63  INTEGER :: ipatch, i, j, k, ijkn, n1, n2, ng1, ng2
64 
65 ! ... local variables
66  INTEGER :: ilev, bctype, lbound, inoff, ijnoff, dims(2)
67  INTEGER :: ibeg, iend, jbeg, jend, kbeg, kend, icount, pid, errorflag
68 
69  REAL(RFREAL), POINTER :: xyz(:,:), surfcoord(:,:,:)
70 
71  TYPE(t_global), POINTER :: global
72  TYPE(t_patch) , POINTER :: patch
73 
74 !******************************************************************************
75 
76  global => region%global
77 
78  CALL registerfunction( global,'WriteSurfaceGrid',&
79  'SURF_WriteSurfaceGrid.F90' )
80 
81 ! store pointer to coordinates ------------------------------------------------
82 
83  ilev = region%currLevel
84  icount = 0
85 
86  CALL rflo_getnodeoffset( region,ilev,inoff,ijnoff )
87 
88  xyz => region%levels(ilev)%grid%xyz
89 
90 ! loop over all cells of the patch (if an interface) --------------------------
91 
92  DO ipatch=1,region%nPatches
93 
94  patch => region%levels(ilev)%patches(ipatch)
95  bctype = patch%bcType
96  lbound = patch%lbound
97 
98  IF (patch%bcCoupled == bc_external) THEN ! interacting
99  icount = icount + 1
100  pid = ireg*regoff + icount
101 
102 ! --- get dimensions, allocate memory
103 
104  dims(1) = abs(patch%l1end-patch%l1beg) + 2 ! nodal values
105  dims(2) = abs(patch%l2end-patch%l2beg) + 2
106  ALLOCATE( surfcoord(3,dims(1),dims(2)),stat=errorflag )
107  global%error = errorflag
108  IF (global%error /= 0) CALL errorstop( global,err_allocate,__line__ )
109 
110  CALL rflo_getpatchindicesnodes( region,patch,ilev, &
111  ibeg,iend,jbeg,jend,kbeg,kend )
112 
113 ! --- copy coordinates to temporary array
114 
115  DO k=kbeg,kend
116  DO j=jbeg,jend
117  DO i=ibeg,iend
118  ijkn = indijk(i,j,k,inoff,ijnoff)
119  IF (lbound==1 .OR. lbound==2) THEN
120  IF (lbound == 1) THEN
121  ng1 = j - jbeg + 1
122  ELSE
123  ng1 = jend - j + 1
124  ENDIF
125  ng2 = k - kbeg + 1
126  ELSE IF (lbound==3 .OR. lbound==4) THEN
127  ng1 = k - kbeg + 1
128  IF (lbound == 3) THEN
129  ng2 = i - ibeg + 1
130  ELSE
131  ng2 = iend - i + 1
132  ENDIF
133  ELSE IF (lbound==5 .OR. lbound==6) THEN
134  IF (lbound == 5) THEN
135  ng1 = i - ibeg + 1
136  ELSE
137  ng1 = iend - i + 1
138  ENDIF
139  ng2 = j - jbeg + 1
140  ENDIF
141  surfcoord(1,ng1,ng2) = xyz(xcoord,ijkn)
142  surfcoord(2,ng1,ng2) = xyz(ycoord,ijkn)
143  surfcoord(3,ng1,ng2) = xyz(zcoord,ijkn)
144  ENDDO
145  ENDDO
146  ENDDO
147 
148 ! --- write to file
149 
150  WRITE(if_plot,*) pid
151  WRITE(if_plot,*) dims(1),dims(2)
152  DO ng2=1,dims(2)
153  DO ng1=1,dims(1)
154 !RAF WRITE(IF_PLOT,*) surfCoord(1,ng1,ng2), &
155  WRITE(if_plot,'(3E24.14)') surfcoord(1,ng1,ng2), &
156  surfcoord(2,ng1,ng2), &
157  surfcoord(3,ng1,ng2)
158  ENDDO
159  ENDDO
160 
161 ! --- release temporary storage
162 
163  DEALLOCATE( surfcoord,stat=errorflag )
164  global%error = errorflag
165  IF (global%error /= 0) CALL errorstop( global,err_allocate,__line__ )
166  nullify( surfcoord )
167 
168  ENDIF ! external BC
169  ENDDO ! iPatch
170 
171 ! finalize --------------------------------------------------------------------
172 
173  CALL deregisterfunction( global )
174 
175 END SUBROUTINE writesurfacegrid
176 
177 !******************************************************************************
178 !
179 ! RCS Revision history:
180 !
181 ! $Log: SURF_WriteSurfaceGrid.F90,v $
182 ! Revision 1.4 2008/12/06 08:44:52 mtcampbe
183 ! Updated license.
184 !
185 ! Revision 1.3 2008/11/19 22:18:02 mtcampbe
186 ! Added Illinois Open Source License/Copyright
187 !
188 ! Revision 1.2 2004/12/03 03:35:56 wasistho
189 ! rflo_modinterfacessurf to surf_modinterfaces
190 !
191 ! Revision 1.1 2004/12/03 02:47:00 wasistho
192 ! added prefix
193 !
194 ! Revision 1.1 2004/12/03 00:49:09 wasistho
195 ! lower to upper case
196 !
197 ! Revision 1.6 2004/06/30 04:08:08 wasistho
198 ! moved Genx related parameter REGOFF to ModParameters
199 !
200 ! Revision 1.5 2004/04/14 20:28:38 rfiedler
201 ! Use formatted output to avoid exponentials with D, which C hates.
202 !
203 ! Revision 1.4 2003/05/15 02:57:07 jblazek
204 ! Inlined index function.
205 !
206 ! Revision 1.3 2003/03/20 22:35:02 haselbac
207 ! Renamed ModInterfaces
208 !
209 ! Revision 1.2 2003/03/20 19:48:09 haselbac
210 ! Corrected mistake in phased check-in
211 !
212 ! Revision 1.1 2002/10/19 00:40:31 jblazek
213 ! Added utility (rflosurf) to write out surface grids for GenX.
214 !
215 !******************************************************************************
216 
217 
218 
219 
220 
221 
222 
**********************************************************************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
subroutine rflo_getnodeoffset(region, iLev, iNodeOffset, ijNodeOffset)
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
subroutine rflo_getpatchindicesnodes(region, patch, iLev, ibeg, iend, jbeg, jend, kbeg, kend)
blockLoc i
Definition: read.cpp:79
subroutine writesurfacegrid(iReg, region)
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
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