Rocstar  1.0
Rocstar multiphysics simulation application
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
TURB_coRansWallDistOVFlu.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: compute distance of each cell centers to the nearest no-slip wall
26 !
27 ! Description: distance to nearest wall (walldist) using this direct method
28 ! is computed by collecting coordinates of no-slip wall patches
29 ! in all regions and stored in a buffer. The wall distance is
30 ! the minimum of the distance between the coordinates in the
31 ! buffer and each cell centroid. In this way, global wall distance
32 ! is obtained, assuming open view (OV) from cell centers to
33 ! the nearest wall.
34 !
35 ! Input: region = data of current region.
36 !
37 ! Output: region%levels%turb%lens = turbulence length scale.
38 !
39 ! Notes: this method is computationally intensive, not suitable for moving
40 ! grid. More efficient method is provided by other routines.
41 !
42 !******************************************************************************
43 !
44 ! $Id: TURB_coRansWallDistOVFlu.F90,v 1.7 2009/08/26 12:28:53 mtcampbe Exp $
45 !
46 ! Copyright: (c) 2003 by the University of Illinois
47 !
48 !******************************************************************************
49 
50 SUBROUTINE turb_coranswalldistov( regions )
51 
52  USE moddatatypes
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 ! ... parameters
63  TYPE(t_region), POINTER :: regions(:)
64 
65 ! ... loop variables
66  INTEGER :: ireg, ic, n, ipatch
67 
68 ! ... local variables
69  TYPE(t_global), POINTER :: global
70 
71 #ifdef MPI
72  INTEGER :: status(mpi_status_size)
73 #endif
74  INTEGER :: iregglob, ncount, icount, accwalldim
75  INTEGER, POINTER :: walldim(:)
76  REAL(RFREAL) :: onethird, distance, xdist, ydist, zdist, loclens, cdes
77  REAL(RFREAL), POINTER :: xyz(:,:), cofg(:,:), lens(:)
78 
79 !******************************************************************************
80 
81  global => regions(1)%global
82  CALL registerfunction( global,'TURB_CoRansWallDistOV',&
83  'TURB_coRansWallDistOVFlu.F90' )
84 
85  IF (global%turbWallDim == 0) goto 888
86 
87 ! allocation and initialisation -----------------------------------------------
88 
89  ALLOCATE( walldim(global%nRegions) ) ! wall dimension/region, all processors
90 
91  IF (.NOT. (global%turbWorkUnused .eqv. .true.)) &
92  CALL errorstop( global,err_turb_workspace,__line__ )
93  global%turbWorkDim = ndir*global%turbWallDim
94  ALLOCATE( global%turbWork1D(global%turbWorkDim) )
95 
96  global%turbWorkUnused = .false.
97  onethird = 1._rfreal/3._rfreal
98  walldim(:) = 0
99  ncount = 0
100  icount = 0
101  accwalldim = 0
102  global%turbWorkDim = 0
103 
104 ! search for ns patch and store wall xyz in global%turbWork1D
105 
106  DO ireg=1,global%nRegionsLocal
107  iregglob = regions(ireg)%iRegionGlobal
108 
109  DO ipatch=1,regions(ireg)%grid%nPatches
110  CALL turb_ranswalldistovpatch( regions(ireg), &
111  regions(ireg)%patches(ipatch) )
112  ENDDO ! iPatch
113  walldim(iregglob) = global%turbWorkDim - accwalldim
114  accwalldim = accwalldim + walldim(iregglob)
115 
116 #ifdef MPI
117 ! - distribut wall dimension acquired from each region/processor to all procs.
118 
119 !c CALL MPI_BCAST( wallDim(iRegGlob),1,MPI_INTEGER,regions(iReg)%procId, &
120 !c global%mpiComm,global%mpierr )
121  IF (global%mpierr /=0 ) CALL errorstop( global,err_mpi_trouble,__line__ )
122 
123 ! - screen output check
124 ! write(*,*)global%myProcid,iReg,global%turbWorkDim,wallDim(iReg), &
125 ! NDIR*global%turbWallDim
126 
127 ! - collect wall coordinates (xyz) from all processors to Master processor
128 
129  IF (global%myProcid == masterproc) THEN
130 
131  IF (walldim(iregglob) > 0) THEN
132 !c IF (regions(iReg)%procid /= global%myProcid) THEN
133 
134 !c CALL MPI_RECV( global%turbWork1D(1+ncount),wallDim(iRegGlob), &
135 !c MPI_RFREAL,regions(iReg)%procId,iRegGlob, &
136 !c global%mpiComm,status,global%mpierr )
137  IF (global%mpierr /=0 ) CALL errorstop( global,err_mpi_trouble,__line__ )
138 
139 !c ENDIF
140 
141  ncount = ncount + walldim(iregglob)
142 
143 ! ----- screen output check
144 ! write(*,*) 'ncount',ireg,ncount
145 
146  ENDIF
147  ELSE
148  IF (walldim(iregglob) > 0) THEN
149 
150 ! ----- screen output check
151 ! write(*,*)'send=',ireg
152 
153  CALL mpi_send( global%turbWork1D(1+icount),walldim(iregglob),mpi_rfreal, &
154  masterproc,iregglob,global%mpiComm,status,global%mpierr )
155  IF (global%mpierr /=0 ) CALL errorstop( global,err_mpi_trouble,__line__ )
156 
157  icount = icount + walldim(iregglob)
158 
159  ENDIF ! wallDim
160  ENDIF ! myProcId
161 #endif
162  ENDDO ! iReg
163 
164 ! check consistency of total wall dimension
165 
166  IF (global%myProcid == masterproc) THEN
167 #ifdef MPI
168  global%turbWorkDim = ncount
169 #endif
170  IF (global%turbWorkDim /= ndir*global%turbWallDim) &
171  CALL errorstop( global,err_turb_ransinput,__line__, &
172  'work array dim. is not consistent with wall array dim.')
173  ENDIF
174 
175 ! distribute wall coordinates from Master processor to all
176 
177 #ifdef MPI
178  CALL mpi_bcast( global%turbWork1D,ndir*global%turbWallDim,mpi_rfreal, &
179  masterproc,global%mpiComm,global%mpierr )
180  IF (global%mpierr /=0 ) CALL errorstop( global,err_mpi_trouble,__line__ )
181 #endif
182 
183 888 CONTINUE
184 
185 ! compute turbulence length scale for RaNS and modified if DES is selected
186 
187  DO ireg=1,global%nRegionsLocal
188 
189  cdes = regions(ireg)%turbInput%cDes
190 
191  xyz => regions(ireg)%grid%xyz
192  cofg => regions(ireg)%grid%cofg
193  lens => regions(ireg)%turb%lens
194  lens = global%refLength
195 
196 ! - RaNS wall distance providing no-slip wall exist
197 
198  DO ic = 1,regions(ireg)%grid%nCellsTot
199  lens(ic) = 1.e+32_rfreal
200  DO n = 1,ndir*global%turbWallDim,ndir
201  xdist = cofg(xcoord,ic)-global%turbWork1D(n)
202  ydist = cofg(ycoord,ic)-global%turbWork1D(n+1)
203  zdist = cofg(zcoord,ic)-global%turbWork1D(n+2)
204  distance = sqrt( xdist**2 + ydist**2 + zdist**2 )
205  lens(ic) = min( lens(ic),distance )
206  ENDDO ! n
207 
208 ! --- screen output check
209 ! IF(i==30 .and.k==2) write(*,*)ireg,j,lens(iC)
210  ENDDO ! iC
211 
212 ! - DES length scale and flows without no-slip walls
213 
214  IF ((regions(ireg)%mixtInput%turbModel == turb_model_dessa) .OR. &
215  (regions(ireg)%mixtInput%turbModel == turb_model_hdessa) .OR. &
216  (global%turbWallDim == 0)) THEN
217  DO ic = 1,regions(ireg)%grid%nCellsTot
218  loclens = regions(ireg)%grid%vol(ic)**onethird ! waiting for
219  ! Andreas` c2e
220  lens(ic) = min( lens(ic),cdes*loclens )
221  ENDDO ! iC
222  ENDIF ! DES or no-nswall
223 
224  ENDDO ! iReg
225 
226 ! finalize --------------------------------------------------------------------
227 
228  DEALLOCATE( global%turbWork1D, walldim )
229  global%turbWorkUnused = .true.
230 
231  CALL deregisterfunction( global )
232 
233 END SUBROUTINE turb_coranswalldistov
234 
235 !******************************************************************************
236 !
237 ! RCS Revision history:
238 !
239 ! $Log: TURB_coRansWallDistOVFlu.F90,v $
240 ! Revision 1.7 2009/08/26 12:28:53 mtcampbe
241 ! Ported to Hera. Fixed logical expression syntax errors. Replaced all
242 ! IF (logical_variable) with IF (logical_variable .eqv. .true.) as
243 ! consistent with the specification. Also changed: IF( ASSOCIATED(expr) )
244 ! to IF ( ASSOCIATED(expr) .eqv. .true. ). Intel compilers produce code
245 ! which silently fails for some mal-formed expressions, so these changes
246 ! are a net which should ensure that they are evaluated as intended.
247 !
248 ! Revision 1.6 2008/12/06 08:44:43 mtcampbe
249 ! Updated license.
250 !
251 ! Revision 1.5 2008/11/19 22:17:55 mtcampbe
252 ! Added Illinois Open Source License/Copyright
253 !
254 ! Revision 1.4 2005/03/09 06:36:15 wasistho
255 ! incorporated HDESSA
256 !
257 ! Revision 1.3 2005/01/12 01:13:12 wasistho
258 ! removed single quote signs since SUN has trouble with it
259 !
260 ! Revision 1.2 2004/05/28 01:55:38 wasistho
261 ! commented MPI lines temporarily to compile RFLU with MPI
262 !
263 ! Revision 1.1 2004/03/25 04:42:57 wasistho
264 ! prepared for RFLU
265 !
266 !
267 !
268 !******************************************************************************
269 
270 
271 
272 
273 
274 
275 
subroutine registerfunction(global, funName, fileName)
Definition: ModError.F90:449
int status() const
Obtain the status of the attribute.
Definition: Attribute.h:240
**********************************************************************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 ic
double sqrt(double d)
Definition: double.h:73
subroutine turb_coranswalldistov(regions)
const NT & n
Vector_n min(const Array_n_const &v1, const Array_n_const &v2)
Definition: Vector_n.h:346
subroutine errorstop(global, errorCode, errorLine, addMessage)
Definition: ModError.F90:483
CImg< T > & distance(const T isovalue, const float sizex=1, const float sizey=1, const float sizez=1, const bool compute_sqrt=true)
Compute the Euclidean distance map to a shape of specified isovalue.
Definition: CImg.h:20441
subroutine turb_ranswalldistovpatch(region, patch)
subroutine deregisterfunction(global)
Definition: ModError.F90:469