Rocstar  1.0
Rocstar multiphysics simulation application
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
PREP_ModBcDistribution.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: Suite of bc distribution routines.
26 !
27 ! Description: None.
28 !
29 ! Notes: None.
30 !
31 ! ******************************************************************************
32 !
33 ! $Id: PREP_ModBcDistribution.F90,v 1.9 2008/12/06 08:44:50 mtcampbe Exp $
34 !
35 ! Copyright: (c) 2004 by the University of Illinois
36 !
37 ! ******************************************************************************
38 
40 
41  USE modglobal, ONLY: t_global
42  USE modparameters
43  USE moddatatypes
44  USE moderror
45  USE moddatastruct, ONLY: t_region
46  USE modbndpatch, ONLY : t_patch
47  USE modgrid, ONLY: t_grid
48  USE modmpi
50 
51  IMPLICIT NONE
52 
53  PRIVATE
54  PUBLIC :: bcdistributionfiles
55 
56 ! private : BcNoslipDistrib, &
57 ! BcInflowDistrib, &
58 ! BcInjectDistrib, &
59 ! BcOutflowDistrib, &
60 ! BcFarfDistrib, &
61 ! BcSlipWallDistrib, &
62 ! ReadPatchSection, &
63 ! WriteBcToFile
64 
65 ! ******************************************************************************
66 ! Declarations and definitions
67 ! ******************************************************************************
68 
69  CHARACTER(CHRLEN) :: RCSIdentString = &
70  '$RCSfile: PREP_ModBcDistribution.F90,v $ $Revision: 1.9 $'
71 
72 ! ******************************************************************************
73 ! Routines
74 ! ******************************************************************************
75 
76  CONTAINS
77 
78 !******************************************************************************
79 !
80 ! Purpose: make bc distribution files
81 !
82 ! Description: none.
83 !
84 ! Input: boundary condition file.
85 !
86 ! Output: regions = BC files containing data distribution.
87 !
88 ! Notes:
89 !
90 !******************************************************************************
91 
92 SUBROUTINE bcdistributionfiles( regions )
93 
94  IMPLICIT NONE
95 
96 ! ... parameters
97  TYPE(t_region), POINTER :: regions(:)
98 
99 ! ... local variables
100  CHARACTER(2*CHRLEN+9) :: fname
101  CHARACTER(256) :: line
102 
103  INTEGER :: distrib, errorflag
104 
105  TYPE(t_global), POINTER :: global
106 
107 !******************************************************************************
108 
109  global => regions(1)%global
110 
111  CALL registerfunction( global,'BcDistributionFiles',&
112  'PREP_ModBcDistribution.F90' )
113 
114 ! open file
115 
116  WRITE(fname,'(A)') trim(global%inDir)//trim(global%casename)//'.bc'
117  OPEN(if_input,file=fname,form='formatted',status='old',iostat=errorflag)
118  global%error = errorflag
119  IF (global%error /= 0) &
120  CALL errorstop( global,err_file_open,__line__,'File: '//trim(fname) )
121 
122 ! allocate and initialize bc-plane edges
123 
124  ALLOCATE( global%infloPlanEdges(xcoord:zcoord,xcoord:zcoord,2), &
125  stat=errorflag )
126  global%error = errorflag
127  IF (global%error /= 0) CALL errorstop( global,err_allocate,__line__ )
128 
129  ALLOCATE( global%xyzMinmax(xcoord:zcoord,2),stat=errorflag )
130  global%error = errorflag
131  IF (global%error /= 0) CALL errorstop( global,err_allocate,__line__ )
132 
133  global%infloPlanEdges = 0._rfreal
134  global%xyzMinmax(:,1) = real_large
135  global%xyzMinmax(:,2) = real_small
136 
137 ! read file looking for keywords
138 
139  CALL bccaseloop( 1 )
140  IF (abs( sum( global%infloPlanEdges ) ) > 1.e-10_rfreal) THEN
141  rewind(if_input)
142  CALL bccaseloop( 2)
143  ENDIF
144 
145 ! close file ------------------------------------------------------------------
146 
147  CLOSE(if_input,iostat=errorflag)
148  global%error = errorflag
149  IF (global%error /= 0) &
150  CALL errorstop( global,err_file_close,__line__,'File: '//trim(fname) )
151 
152 ! finalization & error handling -----------------------------------------------
153 
154  CALL deregisterfunction( global )
155 
156 ! -----------------------------------------------------------------------------
157  CONTAINS
158 
159  SUBROUTINE bccaseloop( n )
160 
161  INTEGER :: n
162 
163  DO
164  READ(if_input,'(A256)',err=10,end=86) line
165  SELECT CASE(trim(line))
166 
167  CASE ('# BC_SLIPWALL')
168  distrib=0
169  CALL bcslipwalldistrib( regions,n,bc_slipwall,distrib )
170  IF (distrib/=0) CALL errorstop( global,err_unknown_option,__line__, &
171  ' generator for slip wall distribution not ready yet' )
172 
173  CASE ('# BC_NOSLIPWALL')
174  distrib=0
175  CALL bcnoslipdistrib( regions,n,bc_noslipwall,distrib )
176  IF (distrib/=0) CALL errorstop( global,err_unknown_option,__line__, &
177  ' generator for noslip wall distribution not ready yet' )
178 
179 ! TEMPORARY - Keep this for backward compatibility
180  CASE ('# BC_INFLOW')
181  distrib=0
182  CALL bcinflowtotangdistrib( regions,n,bc_inflow,distrib )
183  IF (distrib/=0) CALL errorstop( global,err_unknown_option,__line__, &
184  ' generator for TotAng-inflow distribution not ready yet' )
185 ! END TEMPORARY
186 
187  CASE ('# BC_INFLOW_TOTANG')
188  distrib=0
189  CALL bcinflowtotangdistrib( regions,n,bc_inflow_totang,distrib )
190  IF (distrib/=0) CALL errorstop( global,err_unknown_option,__line__, &
191  ' generator for TotAng-inflow distribution not ready yet' )
192 
193  CASE ('# BC_INFLOW_VELTEMP')
194  distrib=0
195  CALL bcinflowveldistrib( regions,n,bc_inflow_veltemp,distrib )
196 
197  CASE ('# BC_INFLOW_VELPRESS')
198  distrib=0
199  CALL bcinflowveldistrib( regions,n,bc_inflow_velpress,distrib )
200 
201  CASE ('# BC_OUTFLOW')
202  distrib=0
203  CALL bcoutflowdistrib( regions,n,bc_outflow,distrib )
204  IF (distrib/=0) CALL errorstop( global,err_unknown_option,__line__, &
205  ' generator for outflow distribution not ready yet' )
206 
207  CASE ('# BC_FARFIELD')
208  distrib=0
209  CALL bcfarfdistrib( regions,n,bc_farfield,distrib )
210  IF (distrib/=0) CALL errorstop( global,err_unknown_option,__line__, &
211  ' generator for farfield distribution not ready yet' )
212 
213  CASE ('# BC_INJECTION')
214  distrib=0
215  CALL bcinjectdistrib( regions,n,bc_injection,distrib )
216  IF (distrib/=0) CALL errorstop( global,err_unknown_option,__line__, &
217  ' generator for injection distribution not ready yet' )
218 
219  END SELECT
220  ENDDO
221 
222 86 CONTINUE
223 
224  goto 999
225 
226 10 CONTINUE
227  CALL errorstop( global,err_file_read,__line__,'File: '//trim(fname) )
228 
229 999 CONTINUE
230 
231  END SUBROUTINE bccaseloop
232 
233 END SUBROUTINE bcdistributionfiles
234 
235 !******************************************************************************
236 !
237 ! Purpose: read in user input related to slip-wall boundary condition
238 ! and create bc distribution file if applicable
239 !
240 ! Description: none.
241 !
242 ! Input: boundary condition file.
243 !
244 ! Output: regions = BC data.
245 !
246 ! Notes: none.
247 !
248 !******************************************************************************
249 
250 SUBROUTINE bcslipwalldistrib( regions,ithRead,bcTitle,distrib )
251 
252  IMPLICIT NONE
253 
254 ! ... parameters
255  TYPE(t_region), POINTER :: regions(:)
256  INTEGER :: ithread, bctitle, distrib
257 
258 ! ... loop variables
259  INTEGER :: ireg, ipatch
260 
261 ! ... local variables
262  CHARACTER(10) :: keys(2)
263  CHARACTER(256) :: fname
264 
265  INTEGER :: brbeg, brend, prbeg, prend, proftype, errorflag
266 
267  LOGICAL :: defined(2)
268 
269  REAL(RFREAL) :: vals(2)
270 
271  TYPE(t_patch), POINTER :: patch
272  TYPE(t_global), POINTER :: global
273 
274 !******************************************************************************
275 
276  global => regions(1)%global
277 
278  CALL registerfunction( global,'BcSlipWallDistrib',&
279  'PREP_ModBcDistribution.F90' )
280 
281 ! specify keywords and search for them ----------------------------------------
282 
283  keys(1) = 'EXTRAPOL'
284  keys(2) = 'MAXCHANGE'
285 
286  distrib = 0
287  proftype = 0
288  CALL readpatchsection( global,if_input,2,keys,vals,brbeg,brend, &
289  prbeg,prend,distrib,proftype,fname,defined )
290 
291 ! check if all values defined -------------------------------------------------
292 
293  IF (.NOT. defined(1) .OR. &
294  .NOT. defined(2)) CALL errorstop( global,err_bcval_missing,__line__ )
295 
296 ! copy values/distribution to variables ---------------------------------------
297 
298  DO ireg=brbeg,brend
299  DO ipatch=prbeg,min(prend,regions(ireg)%nPatches)
300 
301  patch => regions(ireg)%levels(1)%patches(ipatch)
302 
303  IF ((patch%bcType>=bc_slipwall .AND. &
304  patch%bcType<=bc_slipwall+bc_range) .AND. & ! my boundary type
305  regions(ireg)%procid==global%myProcid .AND. & ! region active and
306  regions(ireg)%active==active) THEN ! on my processor
307 
308  IF (patch%mixt%bcSet) &
309  CALL errorstop( global,err_patch_overspec,__line__,'Slip-wall boundary.' )
310 
311  patch%mixt%nData = 0
312  patch%mixt%nSwitches = 1
313  patch%mixt%distrib = bcdat_constant
314  IF (ithread==2) patch%mixt%bcSet = .true.
315 
316 ! ----- get value of switch
317 
318  ALLOCATE( patch%mixt%switches(patch%mixt%nSwitches), &
319  stat=errorflag )
320  global%error = errorflag
321  IF (global%error /= 0) CALL errorstop( global,err_allocate,__line__ )
322 
323  patch%mixt%switches(bcswi_slipw_extrap) = extrapol_const
324  IF (vals(1) > 0.1) &
325  patch%mixt%switches(bcswi_slipw_extrap) = extrapol_linear
326 
327  patch%mixt%maxChange = vals(2)
328 
329  ENDIF ! bcType, active region on my processor
330 
331  ENDDO ! iPatch
332  ENDDO ! iReg
333 
334 ! finalize --------------------------------------------------------------------
335 
336  CALL deregisterfunction( global )
337 
338 END SUBROUTINE bcslipwalldistrib
339 
340 !******************************************************************************
341 !
342 ! Purpose: read in user input related to noslip wall boundary condition.
343 ! and create bc distribution file if applicable
344 !
345 ! Description: none.
346 !
347 ! Input: boundary condition file.
348 !
349 ! Output: regions = BC data.
350 !
351 ! Notes: none.
352 !
353 !******************************************************************************
354 
355 SUBROUTINE bcnoslipdistrib( regions,ithRead,bcTitle,distrib )
356 
357  IMPLICIT NONE
358 
359 #include "Indexing.h"
360 
361 ! ... parameters
362  TYPE(t_region), POINTER :: regions(:)
363  INTEGER :: ithread, bctitle, distrib
364 
365 ! ... loop variables
366  INTEGER :: ireg, ipatch
367 
368 ! ... local variables
369  CHARACTER(10) :: keys(2)
370  CHARACTER(256) :: fname
371 
372  INTEGER :: brbeg, brend, prbeg, prend, proftype, switch
373  INTEGER :: n1, n2, ioff, ijbeg, ijend, errorflag
374 
375  LOGICAL :: defined(2)
376 
377  REAL(RFREAL) :: vals(2)
378 
379  TYPE(t_patch), POINTER :: patch
380  TYPE(t_global), POINTER :: global
381 
382 !******************************************************************************
383 
384  global => regions(1)%global
385 
386  CALL registerfunction( global,'BcNoslipDistrib',&
387  'PREP_ModBcDistribution.F90' )
388 
389 ! specify keywords and search for them ----------------------------------------
390 
391  keys(1) = 'ADIABAT'
392  keys(2) = 'TWALL'
393 
394  distrib = 0
395  proftype = 0
396  CALL readpatchsection( global,if_input,2,keys,vals,brbeg,brend, &
397  prbeg,prend,distrib,proftype,fname,defined )
398 
399 ! get switches & check if all necessary values defined ------------------------
400 
401  DO ireg=brbeg,brend
402  DO ipatch=prbeg,min(prend,regions(ireg)%nPatches)
403 
404  patch => regions(ireg)%levels(1)%patches(ipatch)
405 
406  IF ((patch%bcType>=bc_noslipwall .AND. &
407  patch%bcType<=bc_noslipwall+bc_range) .AND. & ! my boundary type,
408  regions(ireg)%procid==global%myProcid .AND. & ! region active and
409  regions(ireg)%active==active) THEN ! on my processor
410 
411  IF (patch%mixt%bcSet) &
412  CALL errorstop( global,err_patch_overspec,__line__,'Noslip boundary.' )
413 
414  patch%mixt%nData = 0
415  patch%mixt%nSwitches = 1
416  IF (patch%bcCoupled == bc_external) THEN ! data from outside
417  patch%mixt%distrib = bcdat_distrib ! => always distribution
418  ELSE
419  patch%mixt%distrib = distrib
420  ENDIF
421 
422  ALLOCATE( patch%mixt%switches(patch%mixt%nSwitches), &
423  stat=errorflag )
424  global%error = errorflag
425  IF (global%error /= 0) CALL errorstop( global,err_allocate,__line__ )
426 
427 ! ----- check if switch defined
428  IF (defined(1)) THEN
429  patch%mixt%switches(bcswi_noslip_adiabat) = bcopt_adiabat
430  IF (vals(1) < 0.1) &
431  patch%mixt%switches(bcswi_noslip_adiabat) = bcopt_non_adiabat
432  ELSE
433  CALL errorstop( global,err_no_bcswitch,__line__,'(adiabatic wall yes/no).' )
434  ENDIF
435 
436 ! ----- check if Twall specified (value or file with distribution)
437  IF (patch%mixt%switches(bcswi_noslip_adiabat) == &
438  bcopt_non_adiabat) THEN
439  IF (patch%mixt%distrib==bcdat_constant .AND. &
440  (.NOT. defined(2))) CALL errorstop( global,err_bcval_missing,__line__ )
441  ENDIF
442 
443 ! ----- set flag to BC specified
444  IF (ithread==2) patch%mixt%bcSet = .true.
445 
446  ENDIF ! my BC & processor, active
447  ENDDO
448  ENDDO
449 
450 ! copy values/distribution to variables ---------------------------------------
451 
452  DO ireg=brbeg,brend
453  DO ipatch=prbeg,min(prend,regions(ireg)%nPatches)
454 
455  patch => regions(ireg)%levels(1)%patches(ipatch)
456 
457  IF ((patch%bcType>=bc_noslipwall .AND. &
458  patch%bcType<=bc_noslipwall+bc_range) .AND. & ! my boundary type,
459  regions(ireg)%procid==global%myProcid .AND. & ! region active and
460  regions(ireg)%active==active) THEN ! on my processor
461  switch = patch%mixt%switches(bcswi_noslip_adiabat)
462  ELSE
463  switch = bcopt_adiabat
464  ENDIF
465 
466  IF ((patch%bcType>=bc_noslipwall .AND. &
467  patch%bcType<=bc_noslipwall+bc_range) .AND. & ! my boundary type,
468  switch==bcopt_non_adiabat .AND. & ! Twall required,
469  regions(ireg)%procid==global%myProcid .AND. & ! region active and
470  regions(ireg)%active==active) THEN ! on my processor
471 
472 ! ----- allocate memory for the values
473 
474  patch%mixt%nData = 1
475 
476  IF (patch%mixt%distrib == bcdat_distrib) THEN
477  n1 = abs(patch%l1end-patch%l1beg)
478  n2 = abs(patch%l2end-patch%l2beg)
479  ioff = n1 + 1
480  ijbeg = indij( 0, 0,ioff)
481  ijend = indij(n1,n2,ioff)
482  ELSE
483  ijbeg = 0
484  ijend = 1
485  ENDIF
486  ALLOCATE( patch%mixt%vals(patch%mixt%nData,ijbeg:ijend), &
487  stat=errorflag )
488  global%error = errorflag
489  IF (global%error /= 0) CALL errorstop( global,err_allocate,__line__ )
490 
491 ! ----- distribution from file
492 
493  IF (patch%mixt%distrib==bcdat_distrib .AND. &
494  patch%bcCoupled /=bc_external ) THEN
495 ! CALL WriteBcToFile( global,fname,patch )
496 
497 ! ----- distribution from external source / constant value
498 
499  ELSE
500  patch%mixt%vals(bcdat_noslip_twall,:) = vals(2)
501  ENDIF ! distribution?
502 
503  ENDIF ! bcType, Twall req., active region on my processor
504 
505  ENDDO ! iPatch
506  ENDDO ! iReg
507 
508 ! finalize --------------------------------------------------------------------
509 
510  CALL deregisterfunction( global )
511 
512 END SUBROUTINE bcnoslipdistrib
513 
514 !******************************************************************************
515 !
516 ! Purpose: read in user input related to inflow boundary condition.
517 ! and create bc distribution file if applicable
518 !
519 ! Description: present inflow bc is based on total pressure, total temperature
520 ! and flow angle.
521 !
522 ! Input: boundary condition file.
523 !
524 ! Output: regions = BC data.
525 !
526 ! Notes: none.
527 !
528 !******************************************************************************
529 
530 SUBROUTINE bcinflowtotangdistrib( regions,ithRead,bcTitle,distrib )
531 
532  IMPLICIT NONE
533 
534 #include "Indexing.h"
535 
536 ! ... parameters
537  TYPE(t_region), POINTER :: regions(:)
538  INTEGER :: ithread, bctitle, distrib
539 
540 ! ... loop variables
541  INTEGER :: ireg, ipatch
542 
543 ! ... local variables
544  CHARACTER(10) :: keys(7)
545  CHARACTER(256) :: fname
546 
547  INTEGER :: brbeg, brend, prbeg, prend, proftype, switch
548  INTEGER :: n1, n2, ioff, ijbeg, ijend, errorflag
549 
550  LOGICAL :: defined(7)
551 
552  REAL(RFREAL) :: vals(7)
553 
554  TYPE(t_patch), POINTER :: patch
555  TYPE(t_global), POINTER :: global
556 
557 !******************************************************************************
558 
559  global => regions(1)%global
560 
561  CALL registerfunction( global,'BcInflowTotAngDistrib',&
562  'PREP_ModBcDistribution.F90' )
563 
564 ! specify keywords and search for them ----------------------------------------
565 
566  keys(1) = 'TYPE'
567  keys(2) = 'FIXED'
568  keys(3) = 'PTOT'
569  keys(4) = 'TTOT'
570  keys(5) = 'BETAH'
571  keys(6) = 'BETAV'
572  keys(7) = 'MACH'
573 
574  distrib = 0
575  proftype = 0
576  CALL readpatchsection( global,if_input,7,keys,vals,brbeg,brend, &
577  prbeg,prend,distrib,proftype,fname,defined )
578 
579 ! get switches & check if all necessary values defined ------------------------
580 
581  DO ireg=brbeg,brend
582  DO ipatch=prbeg,min(prend,regions(ireg)%nPatches)
583 
584  patch => regions(ireg)%levels(1)%patches(ipatch)
585 
586  IF ((patch%bcType>=bc_inflow .AND. &
587  patch%bcType<=bc_inflow+bc_range) .AND. & ! my boundary type,
588  regions(ireg)%procid==global%myProcid .AND. & ! region active and
589  regions(ireg)%active==active) THEN ! on my processor
590 
591  patch%bcType = bc_inflow_totang
592 
593  IF (patch%mixt%bcSet) &
594  CALL errorstop( global,err_patch_overspec,__line__,'Inflow boundary.' )
595 
596  patch%mixt%nSwitches = 2
597  IF (patch%bcCoupled == bc_external) THEN ! data from outside
598  patch%mixt%distrib = bcdat_distrib ! => always distribution
599  ELSE
600  patch%mixt%distrib = distrib
601  ENDIF
602 
603  ALLOCATE( patch%mixt%switches(patch%mixt%nSwitches), &
604  stat=errorflag )
605  global%error = errorflag
606  IF (global%error /= 0) CALL errorstop( global,err_allocate,__line__ )
607 
608 ! ----- check if switch defined
609  IF (defined(1)) THEN
610  patch%mixt%switches(bcswi_inflow_type) = bcopt_subsonic
611  IF (vals(1) < 0.1) &
612  patch%mixt%switches(bcswi_inflow_type) = bcopt_supersonic
613  IF (vals(1) > 1.9) &
614  patch%mixt%switches(bcswi_inflow_type) = bcopt_mixed
615  ELSE
616  CALL errorstop( global,err_no_bcswitch,__line__,'(inflow type).' )
617  ENDIF
618 
619  IF (defined(2)) THEN
620  IF (vals(2) < 0.1) &
621  patch%mixt%switches(bcswi_inflow_fixed) = bcopt_fixed_no
622  IF (vals(2) > 0.9) &
623  patch%mixt%switches(bcswi_inflow_fixed) = bcopt_fixed_yes
624  ELSE
625  patch%mixt%switches(bcswi_inflow_fixed) = bcopt_fixed_no
626  ENDIF
627 
628 ! ----- check if appropriate values specified
629  IF (patch%mixt%switches(bcswi_inflow_type) == bcopt_subsonic) THEN
630  IF (patch%mixt%distrib==bcdat_constant .AND. &
631  (.NOT. defined(3) .OR. &
632  .NOT. defined(4) .OR. &
633  .NOT. defined(5) .OR. &
634  .NOT. defined(6))) CALL errorstop( global,err_bcval_missing,__line__ )
635  ENDIF
636  IF (patch%mixt%switches(bcswi_inflow_type) == bcopt_supersonic .OR. &
637  patch%mixt%switches(bcswi_inflow_type) == bcopt_mixed) THEN
638  IF (patch%mixt%distrib==bcdat_constant .AND. &
639  (.NOT. defined(3) .OR. &
640  .NOT. defined(4) .OR. &
641  .NOT. defined(5) .OR. &
642  .NOT. defined(6) .OR. &
643  .NOT. defined(7))) CALL errorstop( global,err_bcval_missing,__line__ )
644  ENDIF
645 
646 ! ----- set flag to BC specified
647  IF (ithread==2) patch%mixt%bcSet = .true.
648 
649  ENDIF ! my BC & processor, active
650  ENDDO
651  ENDDO
652 
653 ! copy values/distribution to variables ---------------------------------------
654 
655  DO ireg=brbeg,brend
656  DO ipatch=prbeg,min(prend,regions(ireg)%nPatches)
657 
658  patch => regions(ireg)%levels(1)%patches(ipatch)
659 
660  IF ((patch%bcType>=bc_inflow .AND. &
661  patch%bcType<=bc_inflow+bc_range) .AND. & ! my boundary type,
662  regions(ireg)%procid==global%myProcid .AND. & ! region active and
663  regions(ireg)%active==active) THEN ! on my processor
664 
665  switch = patch%mixt%switches(bcswi_inflow_type)
666  IF (switch == bcopt_subsonic) THEN
667  patch%mixt%nData = 4
668  ELSE
669  patch%mixt%nData = 5
670  ENDIF
671 
672 ! ----- allocate memory for the values
673 
674  IF (patch%mixt%distrib == bcdat_distrib) THEN
675  n1 = abs(patch%l1end-patch%l1beg)
676  n2 = abs(patch%l2end-patch%l2beg)
677  ioff = n1 + 1
678  ijbeg = indij( 0, 0,ioff)
679  ijend = indij(n1,n2,ioff)
680  ELSE
681  ijbeg = 0
682  ijend = 1
683  ENDIF
684  ALLOCATE( patch%mixt%vals(patch%mixt%nData,ijbeg:ijend), &
685  stat=errorflag )
686  global%error = errorflag
687  IF (global%error /= 0) CALL errorstop( global,err_allocate,__line__ )
688 
689 ! ----- distribution from file
690 
691  IF (patch%mixt%distrib==bcdat_distrib .AND. &
692  patch%bcCoupled /=bc_external ) THEN
693 ! CALL WriteBcToFile( global,fname,patch )
694 
695  IF (switch == bcopt_subsonic) THEN
696  patch%mixt%vals(bcdat_inflow_betah,:) = &
697  patch%mixt%vals(bcdat_inflow_betah,:)*global%rad
698  patch%mixt%vals(bcdat_inflow_betav,:) = &
699  patch%mixt%vals(bcdat_inflow_betav,:)*global%rad
700  ENDIF
701 
702 ! ----- distribution from external source / constant value
703 
704  ELSE
705  patch%mixt%vals(bcdat_inflow_ptot ,:) = vals(3)
706  patch%mixt%vals(bcdat_inflow_ttot ,:) = vals(4)
707  patch%mixt%vals(bcdat_inflow_betah,:) = vals(5)*global%rad
708  patch%mixt%vals(bcdat_inflow_betav,:) = vals(6)*global%rad
709  IF (switch /= bcopt_subsonic) THEN
710  patch%mixt%vals(bcdat_inflow_mach,:) = vals(7)
711  ENDIF
712  ENDIF ! distribution?
713 
714  ENDIF ! bcType, active region on my processor
715 
716  ENDDO ! iPatch
717  ENDDO ! iReg
718 
719 ! finalize --------------------------------------------------------------------
720 
721  CALL deregisterfunction( global )
722 
723 END SUBROUTINE bcinflowtotangdistrib
724 
725 !******************************************************************************
726 !
727 ! Purpose: read in user input related to inflow boundary condition.
728 ! and create bc distribution file if applicable
729 !
730 ! Description: present inflow bc is based on prescribed velocities and
731 ! either temperature or pressure.
732 !
733 ! Input: boundary condition file.
734 !
735 ! Output: regions = BC data.
736 !
737 ! Notes: none.
738 !
739 !******************************************************************************
740 
741 SUBROUTINE bcinflowveldistrib( regions,ithRead,bcTitle,distrib )
742 
744  IMPLICIT NONE
745 
746 #include "Indexing.h"
747 
748 ! ... parameters
749  TYPE(t_region), POINTER :: regions(:)
750  INTEGER :: ithread, bctitle, distrib
751 
752 ! ... loop variables
753  INTEGER :: ireg, ipatch, i, j, k, l
754 
755 ! ... local variables
756  INTEGER, PARAMETER :: nvals_max = 8
757 
758  CHARACTER(10) :: keys(nvals_max)
759  CHARACTER(256) :: fname
760 
761  INTEGER :: nvals, brbeg, brend, prbeg, prend, proftype, switch
762  INTEGER :: n1, n2, ioff, ijbeg, ijend, errorflag
763  INTEGER :: ibeg, iend, jbeg, jend, kbeg, kend, ilev, inoff, ijnoff
764  INTEGER :: idnbeg, idnend, jdnbeg, jdnend, kdnbeg, kdnend, ijkn
765 
766  LOGICAL :: defined(nvals_max)
767 
768  REAL(RFREAL) :: vals(nvals_max)
769  REAL(RFREAL), POINTER :: xyz(:,:)
770 
771  TYPE(t_patch), POINTER :: patch
772  TYPE(t_global), POINTER :: global
773 
774 !******************************************************************************
775 
776  global => regions(1)%global
777 
778  CALL registerfunction( global,'BcInflowVelDistrib',&
779  'PREP_ModBcDistribution.F90' )
780 
781 ! specify keywords and search for them ----------------------------------------
782 
783  keys(1) = 'TYPE'
784  keys(2) = 'VELX'
785  keys(3) = 'VELY'
786  keys(4) = 'VELZ'
787  IF (bctitle==bc_inflow_veltemp) THEN
788  keys(5) = 'TEMP'
789  keys(6) = 'PRESS'
790  ELSEIF (bctitle==bc_inflow_velpress) THEN
791  keys(5) = 'PRESS'
792  keys(6) = 'TEMP'
793  ELSE
794  CALL errorstop( global,err_unknown_bc,__line__ )
795  ENDIF
796  keys(7) = 'AXIALPOWER'
797  keys(8) = 'NORMALFACT'
798 
799  nvals = nvals_max
800 
801  distrib = 0
802  proftype = 0
803  CALL readpatchsection( global,if_input,nvals,keys,vals,brbeg,brend, &
804  prbeg,prend,distrib,proftype,fname,defined )
805 
806 ! get switches & check if all necessary values defined ------------------------
807 
808  DO ireg=brbeg,brend
809  DO ipatch=prbeg,min(prend,regions(ireg)%nPatches)
810 
811  patch => regions(ireg)%levels(1)%patches(ipatch)
812 
813  IF ((patch%bcType>=bc_inflow .AND. &
814  patch%bcType<=bc_inflow+bc_range) .AND. & ! my boundary type,
815  regions(ireg)%procid==global%myProcid .AND. & ! region active and
816  regions(ireg)%active==active) THEN ! on my processor
817 
818  patch%bcType = bctitle
819 
820  IF (patch%mixt%bcSet) &
821  CALL errorstop( global,err_patch_overspec,__line__,'Inflow boundary.' )
822 
823  patch%mixt%nSwitches = 2
824  IF (patch%bcCoupled == bc_external) THEN ! data from outside
825  patch%mixt%distrib = bcdat_distrib ! => always distribution
826  ELSE
827  patch%mixt%distrib = distrib
828  ENDIF
829 
830  ALLOCATE( patch%mixt%switches(patch%mixt%nSwitches), &
831  stat=errorflag )
832  global%error = errorflag
833  IF (global%error /= 0) CALL errorstop( global,err_allocate,__line__ )
834 
835 ! ----- check if switch defined
836  IF (defined(1)) THEN
837  patch%mixt%switches(bcswi_inflow_type) = bcopt_subsonic
838  IF (vals(1) < 0.1) &
839  patch%mixt%switches(bcswi_inflow_type) = bcopt_supersonic
840  IF (vals(1) > 1.9) &
841  patch%mixt%switches(bcswi_inflow_type) = bcopt_mixed
842  ELSE
843  CALL errorstop( global,err_no_bcswitch,__line__,'(inflow type).' )
844  ENDIF
845 
846 ! ----- check if appropriate values specified
847  IF (patch%mixt%switches(bcswi_inflow_type) == bcopt_subsonic) THEN
848  IF (patch%mixt%distrib==bcdat_constant .AND. &
849  (.NOT. defined(2) .OR. &
850  .NOT. defined(3) .OR. &
851  .NOT. defined(4) .OR. &
852  .NOT. defined(5))) CALL errorstop( global,err_bcval_missing,__line__ )
853  ENDIF
854  IF (patch%mixt%switches(bcswi_inflow_type) == bcopt_supersonic .OR. &
855  patch%mixt%switches(bcswi_inflow_type) == bcopt_mixed) THEN
856  IF (patch%mixt%distrib==bcdat_constant .AND. &
857  (.NOT. defined(2) .OR. &
858  .NOT. defined(3) .OR. &
859  .NOT. defined(4) .OR. &
860  .NOT. defined(5) .OR. &
861  .NOT. defined(6))) CALL errorstop( global,err_bcval_missing,__line__ )
862  ENDIF
863 
864 ! ----- set flag to BC specified
865  IF (ithread==2) patch%mixt%bcSet = .true.
866 
867  ENDIF ! my BC & processor, active
868  ENDDO
869  ENDDO
870 
871 ! obtain geometrical parameters -----------------------------------------------
872 
873 ! allocate memory for the geometrical edges
874 
875  DO ireg=brbeg,brend
876 
877  ilev = regions(ireg)%currLevel
878  xyz => regions(ireg)%levels(ilev)%grid%xyz
879 
880  CALL rflo_getnodeoffset( regions(ireg),ilev,inoff,ijnoff )
881 
882  DO ipatch=prbeg,min(prend,regions(ireg)%nPatches)
883 
884  patch => regions(ireg)%levels(1)%patches(ipatch)
885 
886  IF ((patch%bcType>=bc_inflow .AND. &
887  patch%bcType<=bc_inflow+bc_range) .AND. & ! my boundary type,
888  regions(ireg)%procid==global%myProcid .AND. & ! region active and
889  regions(ireg)%active==active) THEN ! on my processor
890 
891  IF (patch%mixt%distrib == bcdat_distrib .AND. &
892  patch%bcCoupled /= bc_external ) THEN
893 
894  IF (.NOT. defined(6) .OR. proftype==0) &
895  CALL errorstop( global,err_bcval_missing,__line__, &
896  ' PROFILE or TEMP or PRESS should be defined' )
897  IF (.NOT. defined(7)) vals(7) = 2._rfreal
898  IF (.NOT. defined(8)) vals(8) = 1._rfreal
899 
900 ! ------- search for global geometrical edges on the bc plane
901 
902  CALL rflo_getpatchindicesnodes( regions(ireg),patch,ilev, &
903  ibeg,iend,jbeg,jend,kbeg,kend )
904  DO k=kbeg,kend
905  DO j=jbeg,jend
906  DO i=ibeg,iend
907  ijkn = indijk(i,j,k,inoff,ijnoff)
908  IF (xyz(xcoord,ijkn) < global%xyzMinmax(xcoord,1)) THEN
909  global%xyzMinmax(xcoord,1) = xyz(xcoord,ijkn)
910  DO l = xcoord,zcoord
911  global%infloPlanEdges(l,xcoord,1) = xyz(l,ijkn)
912  ENDDO
913  ENDIF
914  IF (xyz(xcoord,ijkn) > global%xyzMinmax(xcoord,2)) THEN
915  global%xyzMinmax(xcoord,2) = xyz(xcoord,ijkn)
916  DO l = xcoord,zcoord
917  global%infloPlanEdges(l,xcoord,2) = xyz(l,ijkn)
918  ENDDO
919  ENDIF
920  IF (xyz(ycoord,ijkn) < global%xyzMinmax(ycoord,1)) THEN
921  global%xyzMinmax(ycoord,1) = xyz(ycoord,ijkn)
922  DO l = xcoord,zcoord
923  global%infloPlanEdges(l,ycoord,1) = xyz(l,ijkn)
924  ENDDO
925  ENDIF
926  IF (xyz(ycoord,ijkn) > global%xyzMinmax(ycoord,2)) THEN
927  global%xyzMinmax(ycoord,2) = xyz(ycoord,ijkn)
928  DO l = xcoord,zcoord
929  global%infloPlanEdges(l,ycoord,2) = xyz(l,ijkn)
930  ENDDO
931  ENDIF
932  IF (xyz(zcoord,ijkn) < global%xyzMinmax(zcoord,1)) THEN
933  global%xyzMinmax(zcoord,1) = xyz(zcoord,ijkn)
934  DO l = xcoord,zcoord
935  global%infloPlanEdges(l,zcoord,1) = xyz(l,ijkn)
936  ENDDO
937  ENDIF
938  IF (xyz(zcoord,ijkn) > global%xyzMinmax(zcoord,2)) THEN
939  global%xyzMinmax(zcoord,2) = xyz(zcoord,ijkn)
940  DO l = xcoord,zcoord
941  global%infloPlanEdges(l,zcoord,2) = xyz(l,ijkn)
942  ENDDO
943  ENDIF
944 
945  ENDDO ! i
946  ENDDO ! j
947  ENDDO ! k
948 
949  ENDIF ! distrib and not-coupled
950 
951  ENDIF ! bcType, active region on my processor
952 
953  ENDDO ! iPatch
954  ENDDO ! iReg
955 
956 ! copy values/distribution to variables ---------------------------------------
957 
958  DO ireg=brbeg,brend
959  DO ipatch=prbeg,min(prend,regions(ireg)%nPatches)
960 
961  patch => regions(ireg)%levels(1)%patches(ipatch)
962 
963  IF ((patch%bcType>=bc_inflow .AND. &
964  patch%bcType<=bc_inflow+bc_range) .AND. & ! my boundary type,
965  regions(ireg)%procid==global%myProcid .AND. & ! region active and
966  regions(ireg)%active==active) THEN ! on my processor
967 
968  switch = patch%mixt%switches(bcswi_inflow_type)
969  IF (switch == bcopt_subsonic) THEN
970  patch%mixt%nData = 4
971  ELSE
972  patch%mixt%nData = 5
973  ENDIF
974 
975 ! ----- allocate memory for the values
976 
977  IF (patch%mixt%distrib == bcdat_distrib) THEN
978  n1 = abs(patch%l1end-patch%l1beg)
979  n2 = abs(patch%l2end-patch%l2beg)
980  ioff = n1 + 1
981  ijbeg = indij( 0, 0,ioff)
982  ijend = indij(n1,n2,ioff)
983  ELSE
984  ijbeg = 0
985  ijend = 1
986  ENDIF
987  ALLOCATE( patch%mixt%vals(patch%mixt%nData,ijbeg:ijend), &
988  stat=errorflag )
989  global%error = errorflag
990  IF (global%error /= 0) CALL errorstop( global,err_allocate,__line__ )
991 
992 ! ----- distribution from file
993 
994  IF (patch%mixt%distrib==bcdat_distrib .AND. &
995  patch%bcCoupled /=bc_external ) THEN
996 
997  IF (patch%mixt%bcSet) &
998  WRITE(stdout,*)'inlet region and patch #:',ireg,ipatch
999 
1000  IF (proftype==inflo_taylor_cyl) THEN
1001  CALL profinflowvttaylorcyl( global,patch,nvals,switch,keys, &
1002  defined,vals )
1003  ELSEIF (proftype==inflo_taylor_plan) THEN
1004 ! CALL ProfInflowVTTaylorPlan( global,patch,nvals,switch,keys, &
1005 ! defined,vals )
1006  CALL errorstop( global,err_unknown_option,__line__, &
1007  'INFLO_TAYLOR_PLAN' )
1008  ELSEIF (proftype==inflo_bllam_cyl) THEN
1009 ! CALL ProfInflowVTBlLamCyl( global,patch,nvals,switch,keys, &
1010 ! defined,vals )
1011  CALL errorstop( global,err_unknown_option,__line__, &
1012  'INFLO_BLLAM_CYL' )
1013  ELSEIF (proftype==inflo_bllam_plan) THEN
1014 ! CALL ProfInflowVTBlLamPlan( global,patch,nvals,switch,keys, &
1015 ! defined,vals )
1016  CALL errorstop( global,err_unknown_option,__line__, &
1017  'INFLO_BLLAM_PLAM' )
1018  ELSEIF (proftype==inflo_blturb_cyl) THEN
1019 ! CALL ProfInflowVTBlTurbCyl( global,patch,nvals,switch,keys, &
1020 ! defined,vals )
1021  CALL errorstop( global,err_unknown_option,__line__, &
1022  'INFLO_BLTURB_CYL' )
1023  ELSEIF (proftype==inflo_blturb_plan) THEN
1024 ! CALL ProfInflowVTBlTurbPlan( global,patch,nvals,switch,keys, &
1025 ! defined,vals )
1026  CALL errorstop( global,err_unknown_option,__line__, &
1027  'INFLO_BLTURB_PLAN' )
1028  ENDIF
1029 
1030  CALL writebctofile( global,fname,patch )
1031 
1032 ! ----- distribution from external source / constant value
1033 
1034  ELSE
1035  patch%mixt%vals(bcdat_inflow_u,:) = vals(2)
1036  patch%mixt%vals(bcdat_inflow_v,:) = vals(3)
1037  patch%mixt%vals(bcdat_inflow_w,:) = vals(4)
1038  IF (bctitle==bc_inflow_veltemp) THEN
1039  patch%mixt%vals(bcdat_inflow_t,:) = vals(5)
1040  ELSEIF (bctitle==bc_inflow_velpress) THEN
1041  patch%mixt%vals(bcdat_inflow_p,:) = vals(5)
1042  ENDIF
1043  IF (switch /= bcopt_subsonic) THEN
1044  IF (bctitle==bc_inflow_veltemp) THEN
1045  patch%mixt%vals(bcdat_inflow_p,:) = vals(6)
1046  ELSEIF (bctitle==bc_inflow_velpress) THEN
1047  patch%mixt%vals(bcdat_inflow_t,:) = vals(6)
1048  ENDIF
1049  ENDIF
1050  ENDIF ! distribution?
1051 
1052  ENDIF ! bcType, active region on my processor
1053 
1054  ENDDO ! iPatch
1055  ENDDO ! iReg
1056 
1057 ! finalize --------------------------------------------------------------------
1058 
1059  CALL deregisterfunction( global )
1060 
1061 END SUBROUTINE bcinflowveldistrib
1062 
1063 !******************************************************************************
1064 !
1065 ! Purpose: read in user input related to outflow boundary condition.
1066 ! and create bc distribution file if applicable
1067 !
1068 ! Description: none.
1069 !
1070 ! Input: boundary condition file.
1071 !
1072 ! Output: regions = BC data.
1073 !
1074 ! Notes: none.
1075 !
1076 !******************************************************************************
1077 
1078 SUBROUTINE bcoutflowdistrib( regions,ithRead,bcTitle,distrib )
1079 
1080  IMPLICIT NONE
1081 
1082 #include "Indexing.h"
1083 
1084 ! ... parameters
1085  TYPE(t_region), POINTER :: regions(:)
1086  INTEGER :: ithread, bctitle, distrib
1087 
1088 ! ... loop variables
1089  INTEGER :: ireg, ipatch
1090 
1091 ! ... local variables
1092  CHARACTER(10) :: keys(2)
1093  CHARACTER(256) :: fname
1094 
1095  INTEGER :: brbeg, brend, prbeg, prend, proftype, switch
1096  INTEGER :: n1, n2, ioff, ijbeg, ijend, errorflag
1097 
1098  LOGICAL :: defined(2)
1099 
1100  REAL(RFREAL) :: vals(2)
1101 
1102  TYPE(t_patch), POINTER :: patch
1103  TYPE(t_global), POINTER :: global
1104 
1105 !******************************************************************************
1106 
1107  global => regions(1)%global
1108 
1109  CALL registerfunction( global,'BcOutflowDistrib',&
1110  'PREP_ModBcDistribution.F90' )
1111 
1112 ! specify keywords and search for them ----------------------------------------
1113 
1114  keys(1) = 'TYPE'
1115  keys(2) = 'PRESS'
1116 
1117  distrib = 0
1118  proftype = 0
1119  CALL readpatchsection( global,if_input,2,keys,vals,brbeg,brend, &
1120  prbeg,prend,distrib,proftype,fname,defined )
1121 
1122 ! get switches & check if all necessary values defined ------------------------
1123 
1124  DO ireg=brbeg,brend
1125  DO ipatch=prbeg,min(prend,regions(ireg)%nPatches)
1126 
1127  patch => regions(ireg)%levels(1)%patches(ipatch)
1128 
1129  IF ((patch%bcType>=bc_outflow .AND. &
1130  patch%bcType<=bc_outflow+bc_range) .AND. & ! my boundary type,
1131  regions(ireg)%procid==global%myProcid .AND. & ! region active and
1132  regions(ireg)%active==active) THEN ! on my processor
1133 
1134  IF (patch%mixt%bcSet) &
1135  CALL errorstop( global,err_patch_overspec,__line__,'Outflow boundary.' )
1136 
1137  patch%mixt%nData = 0
1138  patch%mixt%nSwitches = 1
1139  IF (patch%bcCoupled == bc_external) THEN ! data from outside
1140  patch%mixt%distrib = bcdat_distrib ! => always distribution
1141  ELSE
1142  patch%mixt%distrib = distrib
1143  ENDIF
1144 
1145  ALLOCATE( patch%mixt%switches(patch%mixt%nSwitches), &
1146  stat=errorflag )
1147  global%error = errorflag
1148  IF (global%error /= 0) CALL errorstop( global,err_allocate,__line__ )
1149 
1150 ! ----- check if switch defined
1151  IF (defined(1)) THEN
1152  patch%mixt%switches(bcswi_outflow_type) = bcopt_subsonic
1153  IF (vals(1) < 0.1) &
1154  patch%mixt%switches(bcswi_outflow_type) = bcopt_supersonic
1155  IF (vals(1) > 1.9) &
1156  patch%mixt%switches(bcswi_outflow_type) = bcopt_mixed
1157  ELSE
1158  CALL errorstop( global,err_no_bcswitch,__line__,'(outflow type).' )
1159  ENDIF
1160 
1161 ! ----- check if appropriate values specified
1162  IF (patch%mixt%switches(bcswi_outflow_type) /= bcopt_supersonic) THEN
1163  IF (patch%mixt%distrib==bcdat_constant .AND. &
1164  .NOT. defined(2)) CALL errorstop( global,err_bcval_missing,__line__ )
1165  ENDIF
1166 
1167 ! ----- set flag to BC specified
1168  IF (ithread==2) patch%mixt%bcSet = .true.
1169 
1170  ENDIF ! my BC & processor, active
1171  ENDDO
1172  ENDDO
1173 
1174 ! copy values/distribution to variables ---------------------------------------
1175 
1176  DO ireg=brbeg,brend
1177  DO ipatch=prbeg,min(prend,regions(ireg)%nPatches)
1178 
1179  patch => regions(ireg)%levels(1)%patches(ipatch)
1180 
1181  IF ((patch%bcType>=bc_outflow .AND. &
1182  patch%bcType<=bc_outflow+bc_range) .AND. & ! my boundary type,
1183  regions(ireg)%procid==global%myProcid .AND. & ! region active and
1184  regions(ireg)%active==active) THEN ! on my processor
1185  switch = patch%mixt%switches(bcswi_outflow_type)
1186  ELSE
1187  switch = bcopt_supersonic
1188  ENDIF
1189 
1190  IF ((patch%bcType>=bc_outflow .AND. &
1191  patch%bcType<=bc_outflow+bc_range) .AND. & ! my boundary type,
1192  switch/=bcopt_supersonic .AND. & ! p required
1193  regions(ireg)%procid==global%myProcid .AND. & ! region active and
1194  regions(ireg)%active==active) THEN ! on my processor
1195 
1196 ! ----- allocate memory for the values
1197 
1198  patch%mixt%nData = 1
1199 
1200  IF (patch%mixt%distrib == bcdat_distrib) THEN
1201  n1 = abs(patch%l1end-patch%l1beg)
1202  n2 = abs(patch%l2end-patch%l2beg)
1203  ioff = n1 + 1
1204  ijbeg = indij( 0, 0,ioff)
1205  ijend = indij(n1,n2,ioff)
1206  ELSE
1207  ijbeg = 0
1208  ijend = 1
1209  ENDIF
1210  ALLOCATE( patch%mixt%vals(patch%mixt%nData,ijbeg:ijend), &
1211  stat=errorflag )
1212  global%error = errorflag
1213  IF (global%error /= 0) CALL errorstop( global,err_allocate,__line__ )
1214 
1215 ! ----- distribution from file
1216 
1217  IF (patch%mixt%distrib==bcdat_distrib .AND. &
1218  patch%bcCoupled /=bc_external ) THEN
1219 ! CALL WriteBcToFile( global,fname,patch )
1220 
1221 ! ----- distribution from external source / constant value
1222 
1223  ELSE
1224  patch%mixt%vals(bcdat_outflow_press,:) = vals(2)
1225  ENDIF ! distribution?
1226 
1227  ENDIF ! bcType, p req., active region on my processor
1228 
1229  ENDDO ! iPatch
1230  ENDDO ! iReg
1231 
1232 ! finalize --------------------------------------------------------------------
1233 
1234  CALL deregisterfunction( global )
1235 
1236 END SUBROUTINE bcoutflowdistrib
1237 
1238 !******************************************************************************
1239 !
1240 ! Purpose: read in user input related to far field boundary condition.
1241 ! and create bc distribution file if applicable
1242 !
1243 ! Description: none.
1244 !
1245 ! Input: boundary condition file.
1246 !
1247 ! Output: regions = BC data
1248 !
1249 ! Notes: none.
1250 !
1251 !******************************************************************************
1252 
1253 SUBROUTINE bcfarfdistrib( regions,ithRead,bcTitle,distrib )
1254 
1255  IMPLICIT NONE
1256 
1257 #include "Indexing.h"
1258 
1259 ! ... parameters
1260  TYPE(t_region), POINTER :: regions(:)
1261  INTEGER :: ithread, bctitle, distrib
1262 
1263 ! ... loop variables
1264  INTEGER :: ireg, ipatch
1265 
1266 ! ... local variables
1267  CHARACTER(10) :: keys(5)
1268  CHARACTER(256) :: fname
1269 
1270  INTEGER :: brbeg, brend, prbeg, prend, proftype
1271  INTEGER :: n1, n2, ioff, ijbeg, ijend, errorflag
1272 
1273  LOGICAL :: defined(5)
1274 
1275  REAL(RFREAL) :: vals(5)
1276 
1277  TYPE(t_patch), POINTER :: patch
1278  TYPE(t_global), POINTER :: global
1279 
1280 !******************************************************************************
1281 
1282  global => regions(1)%global
1283 
1284  CALL registerfunction( global,'BcFarfDistrib',&
1285  'PREP_ModBcDistribution.F90' )
1286 
1287 ! specify keywords and search for them ----------------------------------------
1288 
1289  keys(1) = 'MACH'
1290  keys(2) = 'ATTACK'
1291  keys(3) = 'SLIP'
1292  keys(4) = 'PRESS'
1293  keys(5) = 'TEMP'
1294 
1295  distrib = 0
1296  proftype = 0
1297  CALL readpatchsection( global,if_input,5,keys,vals,brbeg,brend, &
1298  prbeg,prend,distrib,proftype,fname,defined )
1299 
1300 ! check if all values defined -------------------------------------------------
1301 
1302  IF (distrib==bcdat_constant .AND. &
1303  (.NOT. defined(1) .OR. &
1304  .NOT. defined(2) .OR. &
1305  .NOT. defined(3) .OR. &
1306  .NOT. defined(4) .OR. &
1307  .NOT. defined(5))) CALL errorstop( global,err_bcval_missing,__line__ )
1308 
1309 ! copy values/distribution to variables ---------------------------------------
1310 
1311  DO ireg=brbeg,brend
1312  DO ipatch=prbeg,min(prend,regions(ireg)%nPatches)
1313 
1314  patch => regions(ireg)%levels(1)%patches(ipatch)
1315 
1316  IF ((patch%bcType>=bc_farfield .AND. &
1317  patch%bcType<=bc_farfield+bc_range) .AND. & ! my boundary type
1318  regions(ireg)%procid==global%myProcid .AND. & ! region active and
1319  regions(ireg)%active==active) THEN ! on my processor
1320 
1321  IF (patch%mixt%bcSet) &
1322  CALL errorstop( global,err_patch_overspec,__line__,'Farfield boundary.' )
1323 
1324  patch%mixt%nData = 5
1325  patch%mixt%nSwitches = 0
1326  IF (ithread==2) patch%mixt%bcSet = .true.
1327 
1328  IF (patch%bcCoupled == bc_external) THEN ! data from outside
1329  patch%mixt%distrib = bcdat_distrib ! => always distribution
1330  ELSE
1331  patch%mixt%distrib = distrib
1332  ENDIF
1333 
1334 ! ----- allocate memory for the values
1335 
1336  IF (patch%mixt%distrib == bcdat_distrib) THEN
1337  n1 = abs(patch%l1end-patch%l1beg)
1338  n2 = abs(patch%l2end-patch%l2beg)
1339  ioff = n1 + 1
1340  ijbeg = indij( 0, 0,ioff)
1341  ijend = indij(n1,n2,ioff)
1342  ELSE
1343  ijbeg = 0
1344  ijend = 1
1345  ENDIF
1346  ALLOCATE( patch%mixt%vals(patch%mixt%nData,ijbeg:ijend), &
1347  stat=errorflag )
1348  global%error = errorflag
1349  IF (global%error /= 0) CALL errorstop( global,err_allocate,__line__ )
1350 
1351 ! ----- distribution from file
1352 
1353  IF (patch%mixt%distrib==bcdat_distrib .AND. &
1354  patch%bcCoupled /=bc_external ) THEN
1355 ! CALL WriteBcToFile( global,fname,patch )
1356 
1357  patch%mixt%vals(bcdat_farf_attack,:) = &
1358  patch%mixt%vals(bcdat_farf_attack,:)*global%rad
1359  patch%mixt%vals(bcdat_farf_slip ,:) = &
1360  patch%mixt%vals(bcdat_farf_slip ,:)*global%rad
1361 
1362 ! ----- distribution from external source / constant value
1363 
1364  ELSE
1365  patch%mixt%vals(bcdat_farf_mach ,:) = vals(1)
1366  patch%mixt%vals(bcdat_farf_attack,:) = vals(2)*global%rad
1367  patch%mixt%vals(bcdat_farf_slip ,:) = vals(3)*global%rad
1368  patch%mixt%vals(bcdat_farf_press ,:) = vals(4)
1369  patch%mixt%vals(bcdat_farf_temp ,:) = vals(5)
1370  ENDIF ! distribution?
1371 
1372  ENDIF ! bcType, active region on my processor
1373 
1374  ENDDO ! iPatch
1375  ENDDO ! iReg
1376 
1377 ! finalize --------------------------------------------------------------------
1378 
1379  CALL deregisterfunction( global )
1380 
1381 END SUBROUTINE bcfarfdistrib
1382 
1383 !******************************************************************************
1384 !
1385 ! Purpose: read in user input related to injection boundary condition.
1386 ! and create bc distribution file if applicable
1387 !
1388 ! Description: none.
1389 !
1390 ! Input: boundary condition file.
1391 !
1392 ! Output: regions = BC data.
1393 !
1394 ! Notes: none.
1395 !
1396 !******************************************************************************
1397 
1398 SUBROUTINE bcinjectdistrib( regions,ithRead,bcTitle,distrib )
1399 
1400  IMPLICIT NONE
1401 
1402 #include "Indexing.h"
1403 
1404 ! ... parameters
1405  TYPE(t_region), POINTER :: regions(:)
1406  INTEGER :: ithread, bctitle, distrib
1407 
1408 ! ... loop variables
1409  INTEGER :: ireg, ipatch
1410 
1411 ! ... local variables
1412  CHARACTER(10) :: keys(4)
1413  CHARACTER(256) :: fname
1414 
1415  INTEGER :: brbeg, brend, prbeg, prend, proftype
1416  INTEGER :: n1, n2, ioff, ijbeg, ijend, errorflag
1417 
1418  LOGICAL :: defined(4)
1419 
1420  REAL(RFREAL) :: vals(4)
1421 
1422  TYPE(t_patch), POINTER :: patch
1423  TYPE(t_global), POINTER :: global
1424 
1425 !******************************************************************************
1426 
1427  global => regions(1)%global
1428 
1429  CALL registerfunction( global,'BcInjectDistrib',&
1430  'PREP_ModBcDistribution.F90' )
1431 
1432 ! specify keywords and search for them ----------------------------------------
1433 
1434  keys(1) = 'MFRATE'
1435  keys(2) = 'TEMP'
1436  keys(3) = 'EXTRAPOL'
1437  keys(4) = 'MAXCHANGE'
1438 
1439  distrib = 0
1440  proftype = 0
1441  CALL readpatchsection( global,if_input,4,keys,vals,brbeg,brend, &
1442  prbeg,prend,distrib,proftype,fname,defined )
1443 
1444 ! check if all values defined -------------------------------------------------
1445 
1446  IF (distrib==bcdat_constant .AND. &
1447  (.NOT. defined(1) .OR. &
1448  .NOT. defined(2))) CALL errorstop( global,err_bcval_missing,__line__ )
1449 
1450  IF (.NOT. defined(3) .OR. &
1451  .NOT. defined(4)) CALL errorstop( global,err_bcval_missing,__line__ )
1452 
1453 ! copy values/distribution to variables ---------------------------------------
1454 
1455  DO ireg=brbeg,brend
1456  DO ipatch=prbeg,min(prend,regions(ireg)%nPatches)
1457 
1458  patch => regions(ireg)%levels(1)%patches(ipatch)
1459 
1460  IF ((patch%bcType>=bc_injection .AND. &
1461  patch%bcType<=bc_injection+bc_range) .AND. & ! my boundary type
1462  regions(ireg)%procid==global%myProcid .AND. & ! region active and
1463  regions(ireg)%active==active) THEN ! on my processor
1464 
1465  IF (patch%mixt%bcSet) &
1466  CALL errorstop( global,err_patch_overspec,__line__,'Injection boundary.' )
1467 
1468  patch%mixt%nData = 5
1469  patch%mixt%nSwitches = 1
1470  IF (ithread==2) patch%mixt%bcSet = .true.
1471 
1472  IF (patch%bcCoupled == bc_external) THEN ! data from outside
1473  patch%mixt%distrib = bcdat_distrib ! => always distribution
1474  ELSE
1475  patch%mixt%distrib = distrib
1476  ENDIF
1477 
1478 ! ----- get value of switch
1479 
1480  ALLOCATE( patch%mixt%switches(patch%mixt%nSwitches), &
1481  stat=errorflag )
1482  global%error = errorflag
1483  IF (global%error /= 0) CALL errorstop( global,err_allocate,__line__ )
1484 
1485  patch%mixt%switches(bcswi_inject_extrap) = extrapol_const
1486  IF (vals(3) > 0.1) &
1487  patch%mixt%switches(bcswi_inject_extrap) = extrapol_linear
1488 
1489  patch%mixt%maxChange = vals(4)
1490 
1491 ! ----- allocate memory for the values
1492 
1493  IF (patch%mixt%distrib == bcdat_distrib) THEN
1494  n1 = abs(patch%l1end-patch%l1beg)
1495  n2 = abs(patch%l2end-patch%l2beg)
1496  ioff = n1 + 1
1497  ijbeg = indij( 0, 0,ioff)
1498  ijend = indij(n1,n2,ioff)
1499  ELSE
1500  ijbeg = 0
1501  ijend = 1
1502  ENDIF
1503  ALLOCATE( patch%mixt%vals(patch%mixt%nData,ijbeg:ijend), &
1504  stat=errorflag )
1505  global%error = errorflag
1506  IF (global%error /= 0) CALL errorstop( global,err_allocate,__line__ )
1507 
1508 ! ----- distribution from file
1509 
1510  IF (patch%mixt%distrib==bcdat_distrib .AND. &
1511  patch%bcCoupled /=bc_external ) THEN
1512  patch%mixt%nData = 2
1513 ! CALL WriteBcToFile( global,fname,patch )
1514  patch%mixt%nData = 5
1515 
1516 ! ----- distribution from external source / constant value
1517 
1518  ELSE
1519  patch%mixt%vals(bcdat_inject_mfrate,:) = vals(1)
1520  patch%mixt%vals(bcdat_inject_temp ,:) = vals(2)
1521  ENDIF ! distribution?
1522 
1523  ENDIF ! bcType, active region on my processor
1524 
1525  ENDDO ! iPatch
1526  ENDDO ! iReg
1527 
1528 ! finalize --------------------------------------------------------------------
1529 
1530  CALL deregisterfunction( global )
1531 
1532 END SUBROUTINE bcinjectdistrib
1533 
1534 !******************************************************************************
1535 !
1536 ! Purpose: read in a section of a file (until # is encountered), read
1537 ! keywords and store the associated numerical values.
1538 !
1539 ! Description:
1540 ! - ReadPatchSection = section applies to a range of patches (prbeg:prend)
1541 ! within a range of regions (brbeg:brend)
1542 !
1543 ! Input: fileID = file number
1544 ! nvals = number of values to search for and to store
1545 ! keys = keywords to search for
1546 !
1547 ! Output: vals = values associated with keywords (reals only)
1548 ! defined = flag if for certain keyword a value was read in
1549 ! brbeg = begin of region range (values set for these regions)
1550 ! brend = end of region range
1551 ! prbeg = begin of patch range (values set for these patches)
1552 ! prend = end of patch range
1553 ! distrib = single value for a patch (=0) or distribution (>0)
1554 ! profType= profile type of vals data
1555 ! fname = file with distribution for a patch
1556 !
1557 !******************************************************************************
1558 
1559 SUBROUTINE readpatchsection( global,fileID,nvals,keys,vals,brbeg,brend, &
1560  prbeg,prend,distrib,proftype,fname,defined )
1561 
1562  IMPLICIT NONE
1563 
1564 ! ... parameters
1565  INTEGER :: brbeg, brend
1566  INTEGER :: fileid, nvals, prbeg, prend, distrib, proftype
1567  CHARACTER(*) :: keys(nvals), fname
1568 
1569  LOGICAL :: defined(nvals)
1570  REAL(RFREAL) :: vals(nvals)
1571  TYPE(t_global), POINTER :: global
1572 
1573 ! ... loop variables
1574  INTEGER :: ival
1575 
1576 ! ... local variables
1577  CHARACTER(256) :: line
1578 
1579  INTEGER :: errorflag, nc
1580 
1581 !******************************************************************************
1582 
1583  CALL registerfunction( global,'ReadPatchSection',&
1584  'PREP_ModBcDistribution.F90' )
1585 
1586 ! read lines from file until # or EOF found
1587 
1588  brbeg = 1 ! region range: input applies to all regions (default)
1589  brend = global%nRegions
1590 
1591  prbeg = 1 ! patch range: input applies to all patches (default)
1592  prend = 999999 ! can have different # of patches in each region
1593 
1594  distrib = 0 ! no distribution as a default
1595  fname = '' ! no file name
1596 
1597  IF ( nvals /= 0 ) THEN
1598  defined(:) = .false. ! keeps track of values being provided by the user
1599  END IF ! nvals
1600 
1601  DO
1602  READ(fileid,'(A256)',iostat=errorflag) line
1603  global%error = errorflag
1604  IF (global%error /= 0) CALL errorstop( global,err_file_read,__line__ )
1605  IF (line(1:1) == '#') EXIT
1606 
1607  IF (line(1:5) == 'BLOCK') THEN
1608  READ(line(6:256),*) brbeg,brend
1609  brend = min(brend,global%nRegions)
1610  IF (brbeg <= 0 ) brbeg = 1
1611  IF (brend <= 0 ) brend = global%nRegions
1612  IF (brend < brbeg) brend = brbeg
1613  ELSE IF (line(1:5) == 'PATCH') THEN
1614  READ(line(6:256),*) prbeg,prend
1615  IF (prbeg <= 0 ) prbeg = 1
1616  IF (prend <= 0 ) prend = 999999
1617  IF (prend < prbeg) prend = prbeg
1618  ELSE IF (line(1:7) == 'DISTRIB') THEN
1619  READ(line(8:256),*) distrib
1620  distrib = max(distrib,0)
1621  distrib = min(distrib,1)
1622  ELSE IF (line(1:7) == 'PROFILE') THEN
1623  READ(line(8:256),*) proftype
1624  ELSE IF (line(1:4) == 'FILE') THEN
1625  READ(line(5:256),*) fname
1626  ELSE
1627  DO ival=1,nvals
1628  nc = len_trim(keys(ival))
1629  IF (line(1:nc) == trim(keys(ival))) THEN ! found matching keyword
1630  READ(line(nc+1:256),*) vals(ival)
1631  defined(ival) = .true.
1632  ENDIF
1633  ENDDO
1634  ENDIF
1635  ENDDO
1636 
1637 ! finalize
1638 
1639  CALL deregisterfunction( global )
1640 
1641 END SUBROUTINE readpatchsection
1642 
1643 !******************************************************************************
1644 !
1645 ! Purpose: write boundary condition data to a file.
1646 !
1647 ! Description: none.
1648 !
1649 ! Input: global = global variables (needed for error function)
1650 ! fname = file name
1651 ! patch = BC patch for which the data is to be read in.
1652 !
1653 ! Output: patch%mixt%vals = BC data for the mixture.
1654 !
1655 ! Notes: currently only the mixture BC data are written out.
1656 !
1657 !******************************************************************************
1658 
1659 SUBROUTINE writebctofile( global,fname,patch )
1660 
1661  IMPLICIT NONE
1662 
1663 #include "Indexing.h"
1664 
1665 ! ... parameters
1666  CHARACTER(*) :: fname
1667 
1668  TYPE(t_global), POINTER :: global
1669  TYPE(t_patch), POINTER :: patch
1670 
1671 ! ... loop variables
1672  INTEGER :: ireg, ipatch, n, i, j, ij
1673 
1674 ! ... local variables
1675  INTEGER :: n1, n2, ioff, errorflag
1676 
1677 !******************************************************************************
1678 
1679  CALL registerfunction( global,'WriteBcToFile',&
1680  'PREP_ModBcDistribution.F90' )
1681 
1682 ! dimensions
1683 
1684  n1 = abs(patch%l1end-patch%l1beg)
1685  n2 = abs(patch%l2end-patch%l2beg)
1686  ioff = n1 + 1
1687 
1688 ! write to file
1689 
1690  OPEN(if_distr,file=fname,form='formatted',status='unknown',iostat=errorflag)
1691  global%error = errorflag
1692  IF (global%error /= 0) &
1693  CALL errorstop( global,err_file_open,__line__,'File: '//trim(fname) )
1694 
1695  WRITE(if_distr,*,err=10) n1+1,n2+1
1696 
1697  DO n=1,patch%mixt%nData
1698  DO j=0,n2
1699  DO i=0,n1
1700  ij = indij(i,j,ioff)
1701  WRITE(if_distr,*,err=10) patch%mixt%vals(n,ij)
1702  ENDDO
1703  ENDDO
1704  ENDDO
1705 
1706  CLOSE(if_distr,iostat=errorflag)
1707  global%error = errorflag
1708  IF (global%error /= 0) &
1709  CALL errorstop( global,err_file_close,__line__,'File: '//trim(fname) )
1710 
1711 goto 999
1712 
1713 ! error handling
1714 
1715 10 CONTINUE
1716  CALL errorstop( global,err_file_write,__line__,'File: '//trim(fname) )
1717 
1718 999 CONTINUE
1719 
1720  CALL deregisterfunction( global )
1721 
1722 END SUBROUTINE writebctofile
1723 
1724 !******************************************************************************
1725 !
1726 ! Purpose: write boundary condition data to a file.
1727 !
1728 ! Description: none.
1729 !
1730 ! Input: global = global variables (needed for error function)
1731 ! patch = BC patch for which the data is to be read in.
1732 ! nvals = number of values to search for and to store
1733 ! keys = keywords to search for
1734 ! defined = flag if for certain keyword a value was read in
1735 !
1736 ! Output: patch%mixt%vals = BC data for the mixture.
1737 !
1738 ! Notes: currently only the mixture BC data are written out.
1739 !
1740 !******************************************************************************
1741 
1742 SUBROUTINE profinflowvttaylorcyl( global,patch,nvals,switch,keys,defined,vals )
1743 
1744  IMPLICIT NONE
1745 
1746 #include "Indexing.h"
1747 
1748 ! ... parameters
1749  TYPE(t_global), POINTER :: global
1750  TYPE(t_patch), POINTER :: patch
1751  INTEGER :: nvals, switch
1752  CHARACTER(*) :: keys(nvals)
1753  LOGICAL :: defined(nvals)
1754 
1755  REAL(RFREAL) :: vals(nvals)
1756 
1757 ! ... loop variables
1758  INTEGER :: ireg, ipatch, n, i, j, ij
1759 
1760 ! ... local variables
1761  INTEGER :: n1, n2, ioff, nf1, nf2, lbound, errorflag
1762  INTEGER :: ivelx, ively, ivelz, itemp, ipres, ipow, ifact
1763  INTEGER :: in, jn, ip, jp, ng1, ng2
1764  REAL(RFREAL) :: vaxi, vinj, xc, yc, zc, xs, ys, zs, radius, rd
1765  REAL(RFREAL) :: sign, costerm, sinterm, cosa, sina
1766  REAL(RFREAL) :: ymin(xcoord:zcoord), ymax(xcoord:zcoord)
1767  REAL(RFREAL) :: zmin(xcoord:zcoord), zmax(xcoord:zcoord)
1768 
1769 !******************************************************************************
1770 
1771  CALL registerfunction( global,'ProfInflowVTTaylorCyl',&
1772  'PREP_ModBcDistribution.F90' )
1773 
1774 ! remember keys
1775 
1776  DO i=1,nvals
1777  IF (keys(i)=='VELX') ivelx =i
1778  IF (keys(i)=='VELY') ively =i
1779  IF (keys(i)=='VELZ') ivelz =i
1780  IF (keys(i)=='TEMP') itemp =i
1781  IF (keys(i)=='PRESS') ipres =i
1782  IF (keys(i)=='AXIALPOWER') ipow =i
1783  IF (keys(i)=='NORMALFACT') ifact =i
1784  ENDDO
1785 
1786  lbound = patch%lbound
1787 
1788  IF (lbound==1 .OR. lbound==2) THEN
1789  vaxi = vals(ivelx)
1790  vinj = vals(ively)
1791  ELSEIF (lbound==3 .OR. lbound==4) THEN
1792  vaxi = vals(ively)
1793  vinj = vals(ivelz)
1794  ELSEIF (lbound==5 .OR. lbound==6) THEN
1795  vaxi = vals(ivelz)
1796  vinj = vals(ivelx)
1797  ENDIF
1798 
1799 ! dimensions
1800 
1801  n1 = abs(patch%l1end-patch%l1beg)
1802  n2 = abs(patch%l2end-patch%l2beg)
1803  ioff = n1 + 1
1804 
1805 ! define cirkel center and radius
1806 
1807  IF (lbound/=3 .AND. lbound/=4) THEN
1808  ymin(xcoord:zcoord) = global%infloPlanEdges(xcoord:zcoord,ycoord,1)
1809  ymax(xcoord:zcoord) = global%infloPlanEdges(xcoord:zcoord,ycoord,2)
1810  xc = 0.5_rfreal*(ymin(xcoord) + ymax(xcoord))
1811  yc = 0.5_rfreal*(ymin(ycoord) + ymax(ycoord))
1812  zc = 0.5_rfreal*(ymin(zcoord) + ymax(zcoord))
1813  radius = 0.5_rfreal*sqrt( (ymax(xcoord)-ymin(xcoord))**2 + &
1814  (ymax(ycoord)-ymin(ycoord))**2 + &
1815  (ymax(zcoord)-ymin(zcoord))**2 )
1816  ELSEIF (lbound==3 .OR. lbound==4) THEN
1817  zmin(xcoord:zcoord) = global%infloPlanEdges(xcoord:zcoord,zcoord,1)
1818  zmax(xcoord:zcoord) = global%infloPlanEdges(xcoord:zcoord,zcoord,2)
1819  xc = 0.5_rfreal*(zmin(xcoord) + zmax(xcoord))
1820  yc = 0.5_rfreal*(zmin(ycoord) + zmax(ycoord))
1821  zc = 0.5_rfreal*(zmin(zcoord) + zmax(zcoord))
1822  radius = 0.5_rfreal*sqrt( (zmax(xcoord)-zmin(xcoord))**2 + &
1823  (zmax(ycoord)-zmin(ycoord))**2 + &
1824  (zmax(zcoord)-zmin(zcoord))**2 )
1825  ENDIF
1826 
1827  IF (patch%mixt%bcSet) &
1828  WRITE(stdout,100)'(x,y,z)_cirkel-center, radius:', xc,yc,zc,radius
1829 
1830 ! compute inflow profiles
1831 
1832  DO j=0,n2
1833  DO i=0,n1
1834  ij = indij(i,j,ioff)
1835 
1836  IF (lbound==1 .OR. lbound==2) THEN
1837  IF (lbound == 2) THEN
1838  ng1 = i - 0 + 1
1839  ELSE
1840  ng1 = n1 - i + 1
1841  ENDIF
1842  ng2 = j - 0 + 1
1843  ELSE IF (lbound==3 .OR. lbound==4) THEN
1844  ng1 = i - 0 + 1
1845  IF (lbound == 4) THEN
1846  ng2 = j - 0 + 1
1847  ELSE
1848  ng2 = n2 - j + 1
1849  ENDIF
1850  ELSE IF (lbound==5 .OR. lbound==6) THEN
1851  IF (lbound == 6) THEN
1852  ng1 = i - 0 + 1
1853  ELSE
1854  ng1 = n1 - i + 1
1855  ENDIF
1856  ng2 = j - 0 + 1
1857  ENDIF
1858 
1859  in = ng1
1860  jn = ng2
1861  ip = ng1+1
1862  jp = ng2+1
1863  xs = 0.25_rfreal*(patch%surfCoord(xcoord,in,jn) + &
1864  patch%surfCoord(xcoord,ip,jn) + &
1865  patch%surfCoord(xcoord,in,jp) + &
1866  patch%surfCoord(xcoord,ip,jp))
1867  ys = 0.25_rfreal*(patch%surfCoord(ycoord,in,jn) + &
1868  patch%surfCoord(ycoord,ip,jn) + &
1869  patch%surfCoord(ycoord,in,jp) + &
1870  patch%surfCoord(ycoord,ip,jp))
1871  zs = 0.25_rfreal*(patch%surfCoord(zcoord,in,jn) + &
1872  patch%surfCoord(zcoord,ip,jn) + &
1873  patch%surfCoord(zcoord,in,jp) + &
1874  patch%surfCoord(zcoord,ip,jp))
1875  rd = sqrt((xs-xc)**2+(ys-yc)**2+(zs-zc)**2)/radius
1876 
1877  costerm = cos( 0.5_rfreal*global%pi*rd**vals(ipow) )
1878  sinterm = sin( 0.5_rfreal/vals(ifact)*global%pi*rd*rd )/rd/ &
1879  sin( 0.5_rfreal/vals(ifact)*global%pi )
1880 
1881  sign = 1._rfreal
1882  IF (lbound==1 .OR. lbound==2) THEN
1883  cosa = (ys-yc)/rd/radius
1884  sina = (zs-zc)/rd/radius
1885  IF (lbound==2) sign=-1._rfreal
1886  patch%mixt%vals(bcdat_inflow_u,ij) = vaxi*costerm*sign
1887  patch%mixt%vals(bcdat_inflow_v,ij) = -vinj*sinterm*cosa
1888  patch%mixt%vals(bcdat_inflow_w,ij) = -vinj*sinterm*sina
1889  ELSEIF (lbound==3 .OR. lbound==4) THEN
1890  cosa = (zs-zc)/rd/radius
1891  sina = (xs-xc)/rd/radius
1892  IF (lbound==4) sign=-1._rfreal
1893  patch%mixt%vals(bcdat_inflow_v,ij) = vaxi*costerm*sign
1894  patch%mixt%vals(bcdat_inflow_w,ij) = -vinj*sinterm*cosa
1895  patch%mixt%vals(bcdat_inflow_u,ij) = -vinj*sinterm*sina
1896  ELSEIF (lbound==5 .OR. lbound==6) THEN
1897  cosa = (xs-xc)/rd/radius
1898  sina = (ys-yc)/rd/radius
1899  IF (lbound==6) sign=-1._rfreal
1900  patch%mixt%vals(bcdat_inflow_w,ij) = vaxi*costerm*sign
1901  patch%mixt%vals(bcdat_inflow_u,ij) = -vinj*sinterm*cosa
1902  patch%mixt%vals(bcdat_inflow_v,ij) = -vinj*sinterm*sina
1903  ENDIF
1904  patch%mixt%vals(bcdat_inflow_t,ij) = vals(itemp)
1905  IF (switch/=bcopt_subsonic) &
1906  patch%mixt%vals(bcdat_inflow_p,ij) = vals(ipres)
1907  ENDDO
1908  ENDDO
1909 
1910 100 FORMAT( a,4e17.10 )
1911 
1912  CALL deregisterfunction( global )
1913 
1914 END SUBROUTINE profinflowvttaylorcyl
1915 
1916 ! ******************************************************************************
1917 ! End
1918 ! ******************************************************************************
1919 
1920 END MODULE prep_modbcdistribution
1921 
1922 ! ******************************************************************************
1923 !
1924 ! RCS Revision history:
1925 !
1926 ! $Log: PREP_ModBcDistribution.F90,v $
1927 ! Revision 1.9 2008/12/06 08:44:50 mtcampbe
1928 ! Updated license.
1929 !
1930 ! Revision 1.8 2008/11/19 22:18:00 mtcampbe
1931 ! Added Illinois Open Source License/Copyright
1932 !
1933 ! Revision 1.7 2006/08/19 15:41:08 mparmar
1934 ! Renamed patch variables
1935 !
1936 ! Revision 1.6 2005/05/06 00:32:52 wasistho
1937 ! fixed orientation of patch%surfCoord TaylorVTCyl routine
1938 !
1939 ! Revision 1.5 2005/05/04 19:04:35 wasistho
1940 ! fixed bug, integer headers n1,n2 in WriteBcToFile
1941 !
1942 ! Revision 1.4 2005/05/03 08:18:22 wasistho
1943 ! make more efficient
1944 !
1945 ! Revision 1.3 2005/05/03 03:20:09 wasistho
1946 ! enabled modified cyl.Taylor inflow profile
1947 !
1948 ! Revision 1.2 2005/05/02 18:08:48 wasistho
1949 ! added cylindrical Taylor inflow profile capability
1950 !
1951 ! Revision 1.1 2005/04/29 03:32:33 wasistho
1952 ! added distribution bc file generator
1953 !
1954 !
1955 ! ******************************************************************************
1956 
1957 
1958 
1959 
1960 
1961 
1962 
1963 
1964 
1965 
1966 
1967 
1968 
1969 
1970 
1971 
1972 
**********************************************************************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
subroutine bccaseloop(n)
Tfloat sum() const
Return the sum of all the pixel values in an image.
Definition: CImg.h:13022
static SURF_BEGIN_NAMESPACE double sign(double x)
double ymin() const
j indices k indices k
Definition: Indexing.h:6
subroutine bcinflowveldistrib(regions, ithRead, bcTitle, distrib)
CImg< T > & line(const unsigned int y0)
Get a line.
Definition: CImg.h:18421
Vector_n max(const Array_n_const &v1, const Array_n_const &v2)
Definition: Vector_n.h:354
subroutine writebctofile(global, fname, patch)
subroutine registerfunction(global, funName, fileName)
Definition: ModError.F90:449
subroutine bcnoslipdistrib(regions, ithRead, bcTitle, distrib)
int status() const
Obtain the status of the attribute.
Definition: Attribute.h:240
subroutine bcoutflowdistrib(regions, ithRead, bcTitle, distrib)
double zmin() const
double sqrt(double d)
Definition: double.h:73
**********************************************************************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 brbeg
**********************************************************************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 jdnbeg
**********************************************************************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 idnend
subroutine readpatchsection(global, fileID, nvals, keys, vals, brbeg, brend, prbeg, prend, distrib, profType, fname, defined)
subroutine rflo_getnodeoffset(region, iLev, iNodeOffset, ijNodeOffset)
**********************************************************************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 jdnend
**********************************************************************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 idnbeg
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
NT & sin
subroutine bcinflowtotangdistrib(regions, ithRead, bcTitle, distrib)
subroutine rflo_getpatchindicesnodes(region, patch, iLev, ibeg, iend, jbeg, jend, kbeg, kend)
blockLoc i
Definition: read.cpp:79
**********************************************************************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 USE ModDataTypes USE prend
**********************************************************************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 form
double zmax() const
const NT & n
double ymax() const
**********************************************************************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 USE ModDataTypes USE prbeg
Vector_n min(const Array_n_const &v1, const Array_n_const &v2)
Definition: Vector_n.h:346
j indices j
Definition: Indexing.h:6
subroutine bcslipwalldistrib(regions, ithRead, bcTitle, distrib)
**********************************************************************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
**********************************************************************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 USE ModDataTypes USE nvals
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
subroutine profinflowvttaylorcyl(global, patch, nvals, switch, keys, defined, vals)
**********************************************************************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
subroutine, public bcdistributionfiles(regions)
NT & cos
subroutine bcinjectdistrib(regions, ithRead, bcTitle, distrib)
**********************************************************************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 kdnbeg
RT a() const
Definition: Line_2.h:140
subroutine bcfarfdistrib(regions, ithRead, bcTitle, distrib)