Rocstar  1.0
Rocstar multiphysics simulation application
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
RFLU_ModReadBcInputFile.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: Collection of routines to read boundary condition input file.
26 !
27 ! Description: None.
28 !
29 ! Notes: None.
30 !
31 ! ******************************************************************************
32 !
33 ! $Id: RFLU_ModReadBcInputFile.F90,v 1.27 2008/12/06 08:44:23 mtcampbe Exp $
34 !
35 ! Copyright: (c) 2004-2006 by the University of Illinois
36 !
37 ! ******************************************************************************
38 
40 
41  USE modparameters
42  USE moddatatypes
43  USE moderror
44  USE modglobal, ONLY: t_global
45  USE modbndpatch, ONLY: t_patch
46  USE moddatastruct, ONLY: t_region
47  USE modgrid, ONLY: t_grid
48  USE modmpi
49 
50  IMPLICIT NONE
51 
52  PRIVATE
54 
55 ! ******************************************************************************
56 ! Declarations and definitions
57 ! ******************************************************************************
58 
59  CHARACTER(CHRLEN) :: RCSIdentString = &
60  '$RCSfile: RFLU_ModReadBcInputFile.F90,v $ $Revision: 1.27 $'
61 
62 ! ******************************************************************************
63 ! Routines
64 ! ******************************************************************************
65 
66  CONTAINS
67 
68 
69 
70 
71 
72 
73 
74 ! ******************************************************************************
75 !
76 ! Purpose: Read in user input related to farfield boundary condition.
77 !
78 ! Description: None.
79 !
80 ! Input: None.
81 !
82 ! Output: None.
83 !
84 ! Notes: None.
85 !
86 ! ******************************************************************************
87 
88  SUBROUTINE rflu_readbcfarfsection(pRegion)
89 
91 
92  IMPLICIT NONE
93 
94 ! ******************************************************************************
95 ! Declarations and definitions
96 ! ******************************************************************************
97 
98 ! ==============================================================================
99 ! Arguments
100 ! ==============================================================================
101 
102  TYPE(t_region), POINTER :: pregion
103 
104 ! ==============================================================================
105 ! Local variables
106 ! ==============================================================================
107 
108  INTEGER, PARAMETER :: nvals_max = 13
109 
110  LOGICAL, DIMENSION(NVALS_MAX) :: defined
111  CHARACTER(10) :: keys(nvals_max)
112  CHARACTER(256) :: ifilename
113  CHARACTER(CHRLEN) :: bcname
114  INTEGER :: checksum,distrib,errorflag,i,idata,ifl,ipatch,ipatchbeg, &
115  ipatchend,nbfacestot,nvals
116  REAL(RFREAL), DIMENSION(NVALS_MAX) :: vals
117  TYPE(t_grid) :: grid
118  TYPE(t_patch), POINTER :: ppatch
119  TYPE(t_global), POINTER :: global
120 
121 ! ******************************************************************************
122 ! Start
123 ! ******************************************************************************
124 
125  global => pregion%global
126 
127  CALL registerfunction(global,'RFLU_ReadBcFarfSection',&
128  'RFLU_ModReadBcInputFile.F90')
129 
130 ! ******************************************************************************
131 ! Specify keywords and search for them
132 ! ******************************************************************************
133 
134  nvals = nvals_max
135 
136  keys(1) = 'CORR'
137  keys(2) = 'MACH'
138  keys(3) = 'ATTACK'
139  keys(4) = 'SLIP'
140  keys(5) = 'PRESS'
141  keys(6) = 'TEMP'
142  keys(7) = 'MVPATCH'
143  keys(8) = 'SMGRID'
144  keys(9) = 'ORDER'
145  keys(10) = 'MOVEDIR'
146  keys(11) = 'COUPLED'
147  keys(12) = 'KIND'
148  keys(13) = 'THRUSTFLAG'
149 
150  CALL readpatchsection(global,if_input,nvals,keys,vals,ipatchbeg,ipatchend, &
151  distrib,ifilename,bcname,defined )
152 
153 ! ******************************************************************************
154 ! Check if specified number of patches exceeds available ones
155 ! ******************************************************************************
156 
157  IF ( ipatchend > global%nPatches ) THEN
158  CALL errorstop(global,err_patch_range,__line__)
159  END IF ! iPatchEnd
160 
161 ! ******************************************************************************
162 ! Get switches and check that all necessary values defined
163 ! ******************************************************************************
164 
165  DO ipatch = 1,pregion%grid%nPatches
166  ppatch => pregion%patches(ipatch)
167 
168 ! ==============================================================================
169 ! Check whether this global patch exists in this region
170 ! ==============================================================================
171 
172  IF ( ppatch%iPatchGlobal >= ipatchbeg .AND. &
173  ppatch%iPatchGlobal <= ipatchend ) THEN
174  ppatch%bcType = bc_farfield
175  ppatch%bcName = bcname
176 
177 ! pPatch%bcCoupled = BC_NOT_COUPLED
178 ! pPatch%movePatchDir = MOVEPATCH_DIR_NONE
179 
180  ppatch%cReconst = constr_none
181  ppatch%plotStatsFlag = .false.
182 
183 ! TEMPORARY - No longer used, keep for backward compatibility
184  ppatch%movePatch = .false.
185  ppatch%smoothGrid = .false.
186 ! END TEMPORARY
187 
188 ! ------------------------------------------------------------------------------
189 ! initialize Boundary Condition kind
190 ! ------------------------------------------------------------------------------
191 
192  IF ( defined(12) .EQV. .true. ) THEN
193  IF ( (nint(vals(12)) >= bc_kind_min) .AND. &
194  (nint(vals(12)) <= bc_kind_max) ) THEN
195  ppatch%bcKind = nint(vals(12))
196  ELSE
197 ! TEMPORARY : issue a warning here ...
198  ppatch%bcKind = bc_kind_simple ! Initialize with Default BC Kind
199  END IF ! checking range of vals(12)
200  ELSE
201  ppatch%bcKind = bc_kind_simple ! Default BC Kind
202  END IF ! defined(12)
203 
204 ! ------------------------------------------------------------------------------
205 ! initialize patch thrustFlag
206 ! ------------------------------------------------------------------------------
207 
208  IF ( defined(13) .EQV. .true. ) THEN
209  IF ( (vals(13) > 0.5_rfreal) .AND. &
210  (vals(13) < 1.5_rfreal) ) THEN
211  ppatch%thrustFlag = .true.
212  ELSE
213  ppatch%thrustFlag = .false.
214  END IF !
215  ELSE
216  ppatch%thrustFlag = .false.
217  END IF ! defined(13)
218 
219 ! ------------------------------------------------------------------------------
220 ! Set switches
221 ! ------------------------------------------------------------------------------
222 
223  ppatch%mixt%nSwitches = 1
224 
225  ALLOCATE(ppatch%mixt%switches(ppatch%mixt%nSwitches), &
226  stat=errorflag)
227  global%error = errorflag
228  IF ( global%error /= err_none ) THEN
229  CALL errorstop(global,err_allocate,__line__)
230  END IF ! global
231 
232 ! ------------------------------------------------------------------------------
233 ! Check if switches defined
234 ! ------------------------------------------------------------------------------
235 
236  IF ( defined(1) .EQV. .true. ) THEN
237  IF ( (nint(vals(1)) == bcopt_corr_yes) .OR. &
238  (nint(vals(1)) == bcopt_corr_no ) ) THEN
239  ppatch%mixt%switches(bcswi_farf_corr) = nint(vals(1))
240  ELSE
241  CALL errorstop(global,err_val_bcswitch,__line__,'(farfield type).')
242  END IF ! NINT
243  ELSE
244  CALL errorstop(global,err_no_bcswitch,__line__,'(farfield type).')
245  END IF ! defined
246 
247 ! ------------------------------------------------------------------------------
248 ! Check whether appropriate values specified
249 ! ------------------------------------------------------------------------------
250 
251  ppatch%mixt%nData = 5
252  ppatch%mixt%distrib = distrib
253 
254  IF ( ppatch%mixt%distrib == bcdat_constant ) THEN
255  checksum = 0
256 
257  DO i = 0,ppatch%mixt%nData-1
258  IF ( defined(2+i) .EQV. .true. ) THEN
259  checksum = checksum + 1
260  END IF ! defined
261  END DO ! i
262 
263  IF ( checksum /= ppatch%mixt%nData ) THEN
264  CALL errorstop(global,err_bcval_missing,__line__)
265  END IF ! checkSum
266  END IF ! pPatch%mixt%distrib
267 
268 ! ------------------------------------------------------------------------------
269 ! Set patch spatial order
270 ! ------------------------------------------------------------------------------
271 
272  IF ( defined(9) .EQV. .true. ) THEN
273  IF ( nint(vals(9)) == 2 ) THEN
274  ppatch%spaceOrder = 2
275  ELSE
276  ppatch%spaceOrder = 1
277  END IF ! NINT(vals(9))
278  ELSE
279  ppatch%spaceOrder = pregion%mixtInput%spaceOrderBFaces
280  END IF ! defined
281 
282 ! ------------------------------------------------------------------------------
283 ! Set patch motion variable
284 ! ------------------------------------------------------------------------------
285 
286  IF ( defined(10) .EQV. .true. ) THEN
287  ppatch%movePatchDir = vals(10)
288  ELSE
289  ppatch%movePatchDir = movepatch_dir_none
290  END IF ! defined
291 
292 ! ------------------------------------------------------------------------------
293 ! Set coupling variable
294 ! ------------------------------------------------------------------------------
295 
296  IF ( defined(11) .EQV. .true. ) THEN
297  ppatch%bcCoupled = vals(11)
298  ELSE
299  ppatch%bcCoupled = bc_not_coupled
300  END IF ! defined
301 
302  END IF ! pPatch%iPatchGlobal
303  END DO ! iPatch
304 
305 ! ******************************************************************************
306 ! Copy values/distribution to variables
307 ! ******************************************************************************
308 
309  DO ipatch = 1,pregion%grid%nPatches
310  ppatch => pregion%patches(ipatch)
311 
312 ! ==============================================================================
313 ! Check whether this global patch exists in this region
314 ! ==============================================================================
315 
316  IF ( ppatch%iPatchGlobal >= ipatchbeg .AND. &
317  ppatch%iPatchGlobal <= ipatchend ) THEN
318 
319 ! ------------------------------------------------------------------------------
320 ! Distribution from file: Allocate and initialize, actual values read in
321 ! at later stage
322 ! ------------------------------------------------------------------------------
323 
324  IF ( ppatch%mixt%distrib == bcdat_distrib ) THEN
325  nbfacestot = ppatch%nBTrisTot + ppatch%nBQuadsTot
326 
327  ALLOCATE(ppatch%mixt%vals(ppatch%mixt%nData,nbfacestot), &
328  stat=errorflag)
329  global%error = errorflag
330  IF ( global%error /= err_none ) THEN
331  CALL errorstop(global,err_allocate,__line__,'pPatch%mixt%vals')
332  END IF ! global
333 
334  DO ifl = 1,nbfacestot
335  DO idata = 1,ppatch%mixt%nData
336  ppatch%mixt%vals(idata,ifl) = REAL(crazy_value_int,kind=rfreal)
337  END DO ! iData
338  END DO ! ifl
339 
340 ! ------------------------------------------------------------------------------
341 ! Constant value
342 ! ------------------------------------------------------------------------------
343 
344  ELSE
345  ALLOCATE(ppatch%mixt%vals(ppatch%mixt%nData,0:1), &
346  stat=errorflag)
347  global%error = errorflag
348  IF ( global%error /= err_none ) THEN
349  CALL errorstop(global,err_allocate,__line__,'pPatch%mixt%vals')
350  END IF ! global
351 
352  ppatch%mixt%vals(bcdat_farf_mach ,0:1) = vals(2)
353  ppatch%mixt%vals(bcdat_farf_attack,0:1) = vals(3)*global%deg2rad
354  ppatch%mixt%vals(bcdat_farf_slip ,0:1) = vals(4)*global%deg2rad
355  ppatch%mixt%vals(bcdat_farf_press ,0:1) = vals(5)
356  ppatch%mixt%vals(bcdat_farf_temp ,0:1) = vals(6)
357  END IF ! pPatch%mixt%distrib
358 
359  END IF ! pPatch%iPatchGlobal
360  END DO ! iPatch
361 
362 ! ******************************************************************************
363 ! End
364 ! ******************************************************************************
365 
366  CALL deregisterfunction(global)
367 
368  END SUBROUTINE rflu_readbcfarfsection
369 
370 
371 
372 
373 
374 
375 
376 ! ******************************************************************************
377 !
378 ! Purpose: Read in user input related to inflow boundary condition based on
379 ! total conditions and flow angles.
380 !
381 ! Description: None.
382 !
383 ! Input:
384 ! pRegion Pointer to region
385 !
386 ! Output: None.
387 !
388 ! Notes: None.
389 !
390 ! ******************************************************************************
391 
392  SUBROUTINE rflu_readbcinflowtotangsection(pRegion)
393 
395 
396  IMPLICIT NONE
397 
398 ! ******************************************************************************
399 ! Declarations and definitions
400 ! ******************************************************************************
401 
402 ! ==============================================================================
403 ! Arguments
404 ! ==============================================================================
405 
406  TYPE(t_region), POINTER :: pregion
407 
408 ! ==============================================================================
409 ! Local variables
410 ! ==============================================================================
411 
412  INTEGER, PARAMETER :: nvals_max = 15
413 
414  LOGICAL :: ifileexists
415  LOGICAL, DIMENSION(NVALS_MAX) :: defined
416  CHARACTER(10) :: keys(nvals_max)
417  CHARACTER(256) :: ifilename
418  CHARACTER(CHRLEN) :: bcname
419  INTEGER :: checksum,distrib,errorflag,i,idata,ifl,ipatch,ireg,nvals, &
420  ipatchbeg,ipatchend,nbfacestot,switch
421  REAL(RFREAL), DIMENSION(NVALS_MAX) :: vals
422  TYPE(t_grid) :: grid
423  TYPE(t_patch), POINTER :: ppatch
424  TYPE(t_global), POINTER :: global
425 
426 ! ******************************************************************************
427 ! Start
428 ! ******************************************************************************
429 
430  global => pregion%global
431 
432  CALL registerfunction(global,'RFLU_ReadBcInflowTotAngSection',&
433  'RFLU_ModReadBcInputFile.F90')
434 
435 ! ******************************************************************************
436 ! Specify keywords and search for them
437 ! ******************************************************************************
438 
439  nvals = nvals_max
440 
441  keys(1) = 'TYPE'
442  keys(2) = 'FIXED'
443  keys(3) = 'PTOT'
444  keys(4) = 'TTOT'
445  keys(5) = 'BETAH'
446  keys(6) = 'BETAV'
447  keys(7) = 'MACH'
448  keys(8) = 'MVPATCH'
449  keys(9) = 'SMGRID'
450  keys(10) = 'MOVEDIR'
451  keys(11) = 'COUPLED'
452  keys(12) = 'KIND'
453  keys(13) = 'REFLECT'
454  keys(14) = 'THRUSTFLAG'
455  keys(15) = 'ORDER'
456 
457  CALL readpatchsection(global,if_input,nvals,keys,vals,ipatchbeg,ipatchend, &
458  distrib,ifilename,bcname,defined)
459 
460 ! ******************************************************************************
461 ! Check if specified number of patches exceeds available ones
462 ! ******************************************************************************
463 
464  IF ( ipatchend > global%nPatches ) THEN
465  CALL errorstop(global,err_patch_range,__line__)
466  END IF ! iPatchEnd
467 
468 ! ******************************************************************************
469 ! Get switches and check that all necessary values defined
470 ! ******************************************************************************
471 
472  DO ipatch = 1,pregion%grid%nPatches
473  ppatch => pregion%patches(ipatch)
474 
475 ! ==============================================================================
476 ! Check whether this global patch exists in this region
477 ! ==============================================================================
478 
479  IF ( ppatch%iPatchGlobal >= ipatchbeg .AND. &
480  ppatch%iPatchGlobal <= ipatchend ) THEN
481  ppatch%bcType = bc_inflow_totang
482  ppatch%bcName = bcname
483 
484 ! pPatch%bcCoupled = BC_NOT_COUPLED
485 ! pPatch%movePatchDir = MOVEPATCH_DIR_NONE
486 
487  ppatch%cReconst = constr_none
488  ppatch%plotStatsFlag = .false.
489 
490 ! TEMPORARY - No longer used, keep for backward compatibility
491  ppatch%movePatch = .false.
492  ppatch%smoothGrid = .false.
493 ! END TEMPORARY
494 
495  ppatch%mixt%distrib = distrib
496 
497 ! ------------------------------------------------------------------------------
498 ! Set switches
499 ! ------------------------------------------------------------------------------
500 
501  ppatch%mixt%nSwitches = 2
502 
503  ALLOCATE(ppatch%mixt%switches(ppatch%mixt%nSwitches), &
504  stat=errorflag)
505  global%error = errorflag
506  IF ( global%error /= err_none ) THEN
507  CALL errorstop(global,err_allocate,__line__)
508  END IF ! global
509 
510 ! ------------------------------------------------------------------------------
511 ! Check if switches defined
512 ! ------------------------------------------------------------------------------
513 
514  IF ( defined(1) .EQV. .true. ) THEN
515  IF ( (nint(vals(1)) >= bcopt_supersonic) .AND. &
516  (nint(vals(1)) <= bcopt_mixed ) ) THEN
517  ppatch%mixt%switches(bcswi_inflow_type) = nint(vals(1))
518  ELSE
519  CALL errorstop(global,err_val_bcswitch,__line__,'(inflow type).')
520  END IF ! NINT
521  ELSE
522  CALL errorstop(global,err_no_bcswitch,__line__,'(inflow type).')
523  END IF ! defined
524 
525  IF ( defined(2) .EQV. .true. ) THEN
526  IF ( (nint(vals(2)) >= bcopt_fixed_no ) .AND. &
527  (nint(vals(2)) <= bcopt_fixed_yes) ) THEN
528  ppatch%mixt%switches(bcswi_inflow_fixed) = nint(vals(2))
529  ELSE
530  CALL errorstop(global,err_val_bcswitch,__line__,'(fixed).')
531  END IF ! NINT
532  ELSE
533  ppatch%mixt%switches(bcswi_inflow_fixed) = bcopt_fixed_no
534  END IF ! defined
535 
536 ! ------------------------------------------------------------------------------
537 ! initialize Boundary Condition kind
538 ! ------------------------------------------------------------------------------
539 
540  IF ( defined(12) .EQV. .true. ) THEN
541  IF ( (nint(vals(12)) >= bc_kind_min) .AND. &
542  (nint(vals(12)) <= bc_kind_max) ) THEN
543  ppatch%bcKind = nint(vals(12))
544  ELSE
545 ! TEMPORARY : issue a warning here ...
546  ppatch%bcKind = bc_kind_simple ! Initialize with Default BC Kind
547  END IF ! checking range of vals(12)
548  ELSE
549  ppatch%bcKind = bc_kind_simple ! Default BC Kind
550  END IF ! defined(12)
551 
552 ! ------------------------------------------------------------------------------
553 ! initialize if inflow BC is reflecting or non reflecting
554 ! ------------------------------------------------------------------------------
555 
556  IF ( defined(13) .EQV. .true. ) THEN
557  IF ( nint(vals(13)) == bc_reflecting ) THEN
558  ppatch%reflect = bc_reflecting
559  ELSE
560  ppatch%reflect = bc_nonreflecting
561  END IF !
562  ELSE
563  ppatch%reflect = bc_reflecting
564  END IF ! defined(13)
565 
566 ! ------------------------------------------------------------------------------
567 ! initialize patch thrustFlag
568 ! ------------------------------------------------------------------------------
569 
570  IF ( defined(14) .EQV. .true. ) THEN
571  IF ( (vals(14) > 0.5_rfreal) .AND. &
572  (vals(14) < 1.5_rfreal) ) THEN
573  ppatch%thrustFlag = .true.
574  ELSE
575  ppatch%thrustFlag = .false.
576  END IF !
577  ELSE
578  ppatch%thrustFlag = .false.
579  END IF ! defined(14)
580 
581 ! ------------------------------------------------------------------------------
582 ! Set patch spatial order
583 ! ------------------------------------------------------------------------------
584 
585  IF ( defined(15) .EQV. .true. ) THEN
586  IF ( nint(vals(15)) == 2 ) THEN
587  ppatch%spaceOrder = 2
588  ELSE
589  ppatch%spaceOrder = 1
590  END IF ! NINT(vals(15))
591  ELSE
592  ppatch%spaceOrder = pregion%mixtInput%spaceOrderBFaces
593  END IF ! defined
594 
595 ! ------------------------------------------------------------------------------
596 ! Check whether appropriate values specified: for subsonic inflow need 4
597 ! quantities, for supersonic and mixed inflow need 5 quantities
598 ! ------------------------------------------------------------------------------
599 
600  IF ( ppatch%mixt%switches(bcswi_inflow_type) /= bcopt_subsonic ) THEN
601  ppatch%mixt%nData = 5
602  ELSE
603  ppatch%mixt%nData = 4
604  END IF ! pPatch
605 
606  IF ( ppatch%mixt%distrib == bcdat_constant ) THEN
607  checksum = 0
608 
609  DO i = 0,ppatch%mixt%nData-1
610  IF ( defined(3+i) .EQV. .true. ) THEN
611  checksum = checksum + 1
612  END IF ! defined
613  END DO ! i
614 
615  IF ( checksum /= ppatch%mixt%nData ) THEN
616  CALL errorstop(global,err_bcval_missing,__line__)
617  END IF ! checkSum
618  END IF ! pPatch
619 
620 ! ------------------------------------------------------------------------------
621 ! Set patch motion variable
622 ! ------------------------------------------------------------------------------
623 
624  IF ( defined(10) .EQV. .true. ) THEN
625  ppatch%movePatchDir = vals(10)
626  ELSE
627  ppatch%movePatchDir = movepatch_dir_none
628  END IF ! defined
629 
630 ! ------------------------------------------------------------------------------
631 ! Set coupling variable
632 ! ------------------------------------------------------------------------------
633 
634  IF ( defined(11) .EQV. .true. ) THEN
635  ppatch%bcCoupled = vals(11)
636  ELSE
637  ppatch%bcCoupled = bc_not_coupled
638 
639  END IF ! defined
640  END IF ! pPatch%iPatchGlobal
641  END DO ! iPatch
642 
643 ! ******************************************************************************
644 ! Copy values/distribution to variables for non-adiabatic walls
645 ! ******************************************************************************
646 
647  DO ipatch = 1,pregion%grid%nPatches
648  ppatch => pregion%patches(ipatch)
649 
650 ! ==============================================================================
651 ! Check whether this global patch exists in this region
652 ! ==============================================================================
653 
654  IF ( ppatch%iPatchGlobal >= ipatchbeg .AND. &
655  ppatch%iPatchGlobal <= ipatchend ) THEN
656  switch = ppatch%mixt%switches(bcswi_inflow_type)
657 
658 ! ------------------------------------------------------------------------------
659 ! Distribution from file: Allocate and initialize, actual values read in
660 ! at later stage
661 ! ------------------------------------------------------------------------------
662 
663  IF ( ppatch%mixt%distrib == bcdat_distrib ) THEN
664  nbfacestot = ppatch%nBTrisTot + ppatch%nBQuadsTot
665 
666  ALLOCATE(ppatch%mixt%vals(ppatch%mixt%nData,nbfacestot), &
667  stat=errorflag)
668  global%error = errorflag
669  IF ( global%error /= err_none ) THEN
670  CALL errorstop(global,err_allocate,__line__,'pPatch%mixt%vals')
671  END IF ! global
672 
673  DO ifl = 1,nbfacestot
674  DO idata = 1,ppatch%mixt%nData
675  ppatch%mixt%vals(idata,ifl) = REAL(crazy_value_int,kind=rfreal)
676  END DO ! iData
677  END DO ! ifl
678 
679 ! ------------------------------------------------------------------------------
680 ! Constant value
681 ! ------------------------------------------------------------------------------
682 
683  ELSE
684  ALLOCATE(ppatch%mixt%vals(ppatch%mixt%nData,0:1),stat=errorflag)
685  global%error = errorflag
686  IF ( global%error /= err_none ) THEN
687  CALL errorstop(global,err_allocate,__line__,'pPatch%mixt%vals')
688  END IF ! global
689 
690  ppatch%mixt%vals(bcdat_inflow_ptot, 0:1) = vals(3)
691  ppatch%mixt%vals(bcdat_inflow_ttot, 0:1) = vals(4)
692  ppatch%mixt%vals(bcdat_inflow_betah,0:1) = vals(5)*global%deg2rad
693  ppatch%mixt%vals(bcdat_inflow_betav,0:1) = vals(6)*global%deg2rad
694 
695  IF ( switch /= bcopt_subsonic ) THEN
696  ppatch%mixt%vals(bcdat_inflow_mach,0:1) = vals(7)
697  END IF ! switch
698  END IF ! pPatch%mixt%distrib
699 
700  END IF ! pPatch%iPatchGlobal
701  END DO ! iPatch
702 
703 ! ******************************************************************************
704 ! End
705 ! ******************************************************************************
706 
707  CALL deregisterfunction(global)
708 
709  END SUBROUTINE rflu_readbcinflowtotangsection
710 
711 
712 
713 
714 
715 
716 
717 
718 
719 ! ******************************************************************************
720 !
721 ! Purpose: Read in user input related to inflow boundary condition based on
722 ! velocities and temperature.
723 !
724 ! Description: None.
725 !
726 ! Input:
727 ! pRegion Pointer to region
728 !
729 ! Output: None.
730 !
731 ! Notes: None.
732 !
733 ! ******************************************************************************
734 
736 
738 
739  IMPLICIT NONE
740 
741 ! ******************************************************************************
742 ! Declarations and definitions
743 ! ******************************************************************************
744 
745 ! ==============================================================================
746 ! Arguments
747 ! ==============================================================================
748 
749  TYPE(t_region), POINTER :: pregion
750 
751 ! ==============================================================================
752 ! Local variables
753 ! ==============================================================================
754 
755  INTEGER, PARAMETER :: nvals_max = 14
756 
757  LOGICAL :: ifileexists
758  LOGICAL, DIMENSION(NVALS_MAX) :: defined
759  CHARACTER(10) :: keys(nvals_max)
760  CHARACTER(256) :: ifilename
761  CHARACTER(CHRLEN) :: bcname
762  INTEGER :: checksum,distrib,errorflag,i,idata,ifl,ipatch,ireg,nbfacestot, &
763  nvals,ipatchbeg,ipatchend,switch
764  REAL(RFREAL), DIMENSION(NVALS_MAX) :: vals
765  TYPE(t_grid) :: grid
766  TYPE(t_patch), POINTER :: ppatch
767  TYPE(t_global), POINTER :: global
768 
769 ! ******************************************************************************
770 ! Start
771 ! ******************************************************************************
772 
773  global => pregion%global
774 
775  CALL registerfunction(global,'RFLU_ReadBcInflowVelTempSection',&
776  'RFLU_ModReadBcInputFile.F90')
777 
778 ! ******************************************************************************
779 ! Specify keywords and search for them
780 ! ******************************************************************************
781 
782  nvals = nvals_max
783 
784  keys(1) = 'TYPE'
785  keys(2) = 'VELX'
786  keys(3) = 'VELY'
787  keys(4) = 'VELZ'
788  keys(5) = 'TEMP'
789  keys(6) = 'PRESS'
790  keys(7) = 'MVPATCH'
791  keys(8) = 'SMGRID'
792  keys(9) = 'MOVEDIR'
793  keys(10) = 'COUPLED'
794  keys(11) = 'KIND'
795  keys(12) = 'REFLECT'
796  keys(13) = 'THRUSTFLAG'
797  keys(14) = 'ORDER'
798 
799  CALL readpatchsection(global,if_input,nvals,keys,vals,ipatchbeg,ipatchend, &
800  distrib,ifilename,bcname,defined)
801 
802 ! ******************************************************************************
803 ! Check if specified number of patches exceeds available ones
804 ! ******************************************************************************
805 
806  IF ( ipatchend > global%nPatches ) THEN
807  CALL errorstop(global,err_patch_range,__line__)
808  END IF ! iPatchEnd
809 
810 ! ******************************************************************************
811 ! Get switches and check that all necessary values defined
812 ! ******************************************************************************
813 
814  DO ipatch = 1,pregion%grid%nPatches
815  ppatch => pregion%patches(ipatch)
816 
817 ! ==============================================================================
818 ! Check whether this global patch exists in this region
819 ! ==============================================================================
820 
821  IF ( ppatch%iPatchGlobal >= ipatchbeg .AND. &
822  ppatch%iPatchGlobal <= ipatchend ) THEN
823  ppatch%bcType = bc_inflow_veltemp
824  ppatch%bcName = bcname
825 
826 ! pPatch%bcCoupled = BC_NOT_COUPLED
827 ! pPatch%movePatchDir = MOVEPATCH_DIR_NONE
828 
829  ppatch%cReconst = constr_none
830  ppatch%plotStatsFlag = .false.
831 
832 ! TEMPORARY - No longer used, keep for backward compatibility
833  ppatch%movePatch = .false.
834  ppatch%smoothGrid = .false.
835 ! END TEMPORARY
836 
837  ppatch%mixt%distrib = distrib
838 
839 ! ------------------------------------------------------------------------------
840 ! Set switches
841 ! ------------------------------------------------------------------------------
842 
843  ppatch%mixt%nSwitches = 1
844 
845  ALLOCATE(ppatch%mixt%switches(ppatch%mixt%nSwitches), &
846  stat=errorflag)
847  global%error = errorflag
848  IF ( global%error /= err_none ) THEN
849  CALL errorstop(global,err_allocate,__line__)
850  END IF ! global
851 
852 ! ------------------------------------------------------------------------------
853 ! Check if switches defined
854 ! ------------------------------------------------------------------------------
855 
856  IF ( defined(1) .EQV. .true. ) THEN
857  IF ( (nint(vals(1)) >= bcopt_supersonic) .AND. &
858  (nint(vals(1)) <= bcopt_mixed ) ) THEN
859  ppatch%mixt%switches(bcswi_inflow_type) = nint(vals(1))
860  ELSE
861  CALL errorstop(global,err_val_bcswitch,__line__,'(inflow type).')
862  END IF ! NINT
863  ELSE
864  CALL errorstop(global,err_no_bcswitch,__line__,'(inflow type).')
865  END IF ! defined
866 
867 ! ------------------------------------------------------------------------------
868 ! initialize Boundary Condition kind
869 ! ------------------------------------------------------------------------------
870 
871  IF ( defined(11) .EQV. .true. ) THEN
872  IF ( (nint(vals(11)) >= bc_kind_min) .AND. &
873  (nint(vals(11)) <= bc_kind_max) ) THEN
874  ppatch%bcKind = nint(vals(11))
875  ELSE
876 ! TEMPORARY : issue a warning here ...
877  ppatch%bcKind = bc_kind_simple ! Initialize with Default BC Kind
878  END IF ! checking range of vals(11)
879  ELSE
880  ppatch%bcKind = bc_kind_simple ! Default BC Kind
881  END IF ! defined(11)
882 
883 ! ------------------------------------------------------------------------------
884 ! initialize if inflow BC is reflecting or non reflecting
885 ! ------------------------------------------------------------------------------
886 
887  IF ( defined(12) .EQV. .true. ) THEN
888  IF ( nint(vals(12)) == bc_reflecting ) THEN
889  ppatch%reflect = bc_reflecting
890  ELSE
891  ppatch%reflect = bc_nonreflecting
892  END IF !
893  ELSE
894  ppatch%reflect = bc_reflecting
895  END IF ! defined(12)
896 
897 ! ------------------------------------------------------------------------------
898 ! initialize patch thrustFlag
899 ! ------------------------------------------------------------------------------
900 
901  IF ( defined(13) .EQV. .true. ) THEN
902  IF ( (vals(13) > 0.5_rfreal) .AND. &
903  (vals(13) < 1.5_rfreal) ) THEN
904  ppatch%thrustFlag = .true.
905  ELSE
906  ppatch%thrustFlag = .false.
907  END IF !
908  ELSE
909  ppatch%thrustFlag = .false.
910  END IF ! defined(13)
911 
912 ! ------------------------------------------------------------------------------
913 ! Set patch spatial order
914 ! ------------------------------------------------------------------------------
915 
916  IF ( defined(14) .EQV. .true. ) THEN
917  IF ( nint(vals(14)) == 2 ) THEN
918  ppatch%spaceOrder = 2
919  ELSE
920  ppatch%spaceOrder = 1
921  END IF ! NINT(vals(14))
922  ELSE
923  ppatch%spaceOrder = pregion%mixtInput%spaceOrderBFaces
924  END IF ! defined
925 
926 ! ------------------------------------------------------------------------------
927 ! Check whether appropriate values specified: for subsonic inflow need 4
928 ! quantities, for supersonic and mixed inflow need 5 quantities
929 ! ------------------------------------------------------------------------------
930 
931  IF ( ppatch%mixt%switches(bcswi_inflow_type) /= bcopt_subsonic ) THEN
932  ppatch%mixt%nData = 5
933  ELSE
934  ppatch%mixt%nData = 4
935  END IF ! pPatch
936 
937  IF ( ppatch%mixt%distrib == bcdat_constant ) THEN
938  checksum = 0
939 
940  DO i = 0,ppatch%mixt%nData-1
941  IF ( defined(2+i) .EQV. .true. ) THEN
942  checksum = checksum + 1
943  END IF ! defined
944  END DO ! i
945 
946  IF ( checksum /= ppatch%mixt%nData ) THEN
947  CALL errorstop(global,err_bcval_missing,__line__)
948  END IF ! checkSum
949  END IF ! pPatch
950 
951 ! ------------------------------------------------------------------------------
952 ! Set patch motion variable
953 ! ------------------------------------------------------------------------------
954 
955  IF ( defined(9) .EQV. .true. ) THEN
956  ppatch%movePatchDir = vals(9)
957  ELSE
958  ppatch%movePatchDir = movepatch_dir_none
959  END IF ! defined
960 
961 ! ------------------------------------------------------------------------------
962 ! Set coupling variable
963 ! ------------------------------------------------------------------------------
964 
965  IF ( defined(10) .EQV. .true. ) THEN
966  ppatch%bcCoupled = vals(10)
967  ELSE
968  ppatch%bcCoupled = bc_not_coupled
969  END IF ! defined
970 
971  END IF ! pPatch%iPatchGlobal
972  END DO ! iPatch
973 
974 ! ******************************************************************************
975 ! Copy values/distribution to variables for non-adiabatic walls
976 ! ******************************************************************************
977 
978  DO ipatch = 1,pregion%grid%nPatches
979  ppatch => pregion%patches(ipatch)
980 
981 ! ==============================================================================
982 ! Check whether this global patch exists in this region
983 ! ==============================================================================
984 
985  IF ( ppatch%iPatchGlobal >= ipatchbeg .AND. &
986  ppatch%iPatchGlobal <= ipatchend ) THEN
987  switch = ppatch%mixt%switches(bcswi_inflow_type)
988 
989 ! ------------------------------------------------------------------------------
990 ! Distribution from file: Allocate and initialize, actual values read in
991 ! at later stage
992 ! ------------------------------------------------------------------------------
993 
994  IF ( ppatch%mixt%distrib == bcdat_distrib ) THEN
995  nbfacestot = ppatch%nBTrisTot + ppatch%nBQuadsTot
996 
997  ALLOCATE(ppatch%mixt%vals(ppatch%mixt%nData,nbfacestot), &
998  stat=errorflag)
999  global%error = errorflag
1000  IF ( global%error /= err_none ) THEN
1001  CALL errorstop(global,err_allocate,__line__,'pPatch%mixt%vals')
1002  END IF ! global
1003 
1004  DO ifl = 1,nbfacestot
1005  DO idata = 1,ppatch%mixt%nData
1006  ppatch%mixt%vals(idata,ifl) = REAL(crazy_value_int,kind=rfreal)
1007  END DO ! iData
1008  END DO ! ifl
1009 
1010 ! ------------------------------------------------------------------------------
1011 ! Constant value
1012 ! ------------------------------------------------------------------------------
1013 
1014  ELSE
1015  ALLOCATE(ppatch%mixt%vals(ppatch%mixt%nData,0:1),stat=errorflag)
1016  global%error = errorflag
1017  IF ( global%error /= err_none ) THEN
1018  CALL errorstop(global,err_allocate,__line__,'pPatch%mixt%vals')
1019  END IF ! global
1020 
1021  ppatch%mixt%vals(bcdat_inflow_u,0:1) = vals(2)
1022  ppatch%mixt%vals(bcdat_inflow_v,0:1) = vals(3)
1023  ppatch%mixt%vals(bcdat_inflow_w,0:1) = vals(4)
1024  ppatch%mixt%vals(bcdat_inflow_t,0:1) = vals(5)
1025 
1026  IF ( switch /= bcopt_subsonic ) THEN
1027  ppatch%mixt%vals(bcdat_inflow_p,0:1) = vals(6)
1028  END IF ! switch
1029  END IF ! pPatch%mixt%distrib
1030 
1031  END IF ! pPatch%iPatchGlobal
1032  END DO ! iPatch
1033 
1034 ! ******************************************************************************
1035 ! End
1036 ! ******************************************************************************
1037 
1038  CALL deregisterfunction(global)
1039 
1040  END SUBROUTINE rflu_readbcinflowveltempsection
1041 
1042 
1043 
1044 
1045 
1046 
1047 
1048 
1049 
1050 
1051 ! ******************************************************************************
1052 !
1053 ! Purpose: Read in user input related to injection boundary condition.
1054 !
1055 ! Description: None.
1056 !
1057 ! Input:
1058 ! pRegion Pointer to region data
1059 !
1060 ! Output: None.
1061 !
1062 ! Notes: None.
1063 !
1064 ! ******************************************************************************
1065 
1066  SUBROUTINE rflu_readbcinjectsection(pRegion)
1067 
1068  USE modinterfaces, ONLY: readpatchsection
1069 
1070  IMPLICIT NONE
1071 
1072 ! ******************************************************************************
1073 ! Declarations and definitions
1074 ! ******************************************************************************
1075 
1076 ! ==============================================================================
1077 ! Arguments
1078 ! ==============================================================================
1079 
1080  TYPE(t_region), POINTER :: pregion
1081 
1082 ! ==============================================================================
1083 ! Local variables
1084 ! ==============================================================================
1085 
1086  INTEGER, PARAMETER :: nvals_max = 12
1087 
1088  LOGICAL, DIMENSION(NVALS_MAX) :: defined
1089  CHARACTER(10) :: keys(nvals_max)
1090  CHARACTER(256) :: fname
1091  CHARACTER(CHRLEN) :: bcname
1092  INTEGER :: checksum,distrib,errorflag,i,idata,ifl,ipatch,ipatchbeg, &
1093  ipatchend,ireg,nbfacestot,nvals
1094  REAL(RFREAL), DIMENSION(NVALS_MAX) :: vals
1095  TYPE(t_grid) :: grid
1096  TYPE(t_patch), POINTER :: ppatch
1097  TYPE(t_global), POINTER :: global
1098 
1099 ! ******************************************************************************
1100 ! Start
1101 ! ******************************************************************************
1102 
1103  global => pregion%global
1104 
1105  CALL registerfunction(global,'RFLU_ReadBcInjectSection',&
1106  'RFLU_ModReadBcInputFile.F90')
1107 
1108 ! ******************************************************************************
1109 ! Specify keywords and search for them
1110 ! ******************************************************************************
1111 
1112  nvals = nvals_max
1113 
1114  keys(1) = 'MFRATE'
1115  keys(2) = 'TEMP'
1116  keys(3) = 'COUPLED'
1117  keys(4) = 'BFLAG'
1118  keys(5) = 'MVPATCH'
1119  keys(6) = 'SMGRID'
1120  keys(7) = 'MOVEDIR'
1121  keys(8) = 'STATS'
1122  keys(9) = 'CRECONST'
1123  keys(10)= 'KIND'
1124  keys(11)= 'THRUSTFLAG'
1125  keys(12)= 'ORDER'
1126 
1127  CALL readpatchsection(global,if_input,nvals,keys,vals,ipatchbeg,ipatchend, &
1128  distrib,fname,bcname,defined )
1129 
1130 ! ******************************************************************************
1131 ! Check if specified number of patches exceeds available ones
1132 ! ******************************************************************************
1133 
1134  IF ( ipatchend > global%nPatches ) THEN
1135  CALL errorstop(global,err_patch_range,__line__)
1136  END IF ! iPatchEnd
1137 
1138 ! ******************************************************************************
1139 ! Get switches and check that all necessary values defined
1140 ! ******************************************************************************
1141 
1142  DO ipatch = 1,pregion%grid%nPatches
1143  ppatch => pregion%patches(ipatch)
1144 
1145 ! ==============================================================================
1146 ! Check whether this global patch exists in this region
1147 ! ==============================================================================
1148 
1149  IF ( ppatch%iPatchGlobal >= ipatchbeg .AND. &
1150  ppatch%iPatchGlobal <= ipatchend ) THEN
1151  ppatch%bcType = bc_injection
1152  ppatch%bcName = bcname
1153 
1154 ! TEMPORARY - No longer used, keep for backward compatibility
1155  ppatch%movePatch = .false.
1156  ppatch%smoothGrid = .false.
1157 ! END TEMPORARY
1158 
1159  ppatch%mixt%nData = 2
1160  ppatch%mixt%nSwitches = 0
1161 
1162 ! ------------------------------------------------------------------------------
1163 ! initialize Boundary Condition kind
1164 ! ------------------------------------------------------------------------------
1165 
1166  IF ( defined(10) .EQV. .true. ) THEN
1167  IF ( (nint(vals(10)) >= bc_kind_min) .AND. &
1168  (nint(vals(10)) <= bc_kind_max) ) THEN
1169  ppatch%bcKind = nint(vals(10))
1170  ELSE
1171 ! TEMPORARY : issue a warning here ...
1172  ppatch%bcKind = bc_kind_simple ! Initialize with Default BC Kind
1173  END IF ! checking range of vals(10)
1174  ELSE
1175  ppatch%bcKind = bc_kind_simple ! Default BC Kind
1176  END IF ! defined(10)
1177 
1178 ! ------------------------------------------------------------------------------
1179 ! initialize patch thrustFlag
1180 ! ------------------------------------------------------------------------------
1181 
1182  IF ( defined(11) .EQV. .true. ) THEN
1183  IF ( (vals(11) > 0.5_rfreal) .AND. &
1184  (vals(11) < 1.5_rfreal) ) THEN
1185  ppatch%thrustFlag = .true.
1186  ELSE
1187  ppatch%thrustFlag = .false.
1188  END IF !
1189  ELSE
1190  ppatch%thrustFlag = .false.
1191  END IF ! defined(11)
1192 
1193 ! ------------------------------------------------------------------------------
1194 ! Set patch spatial order
1195 ! ------------------------------------------------------------------------------
1196 
1197  IF ( defined(12) .EQV. .true. ) THEN
1198  IF ( nint(vals(12)) == 2 ) THEN
1199  ppatch%spaceOrder = 2
1200  ELSE
1201  ppatch%spaceOrder = 1
1202  END IF ! NINT(vals(12))
1203  ELSE
1204  ppatch%spaceOrder = pregion%mixtInput%spaceOrderBFaces
1205  END IF ! defined
1206 
1207 ! ------------------------------------------------------------------------------
1208 ! Check whether coupling flag defined
1209 ! ------------------------------------------------------------------------------
1210 
1211 #ifdef GENX
1212  IF ( defined(3) .EQV. .true. ) THEN
1213  IF ( nint(vals(3)) == bc_burning ) THEN
1214  ppatch%bcCoupled = nint(vals(3))
1215  ppatch%mixt%distrib = bcdat_distrib ! MUST have distribution
1216  ELSE IF ( nint(vals(3)) == bc_not_burning ) THEN
1217  global%warnCounter = global%warnCounter + 1
1218 
1219  WRITE(stdout,'(A,3X,A,1X,A,I3,A)') solver_name,'*** WARNING ***', &
1220  'Invalid coupling input for patch ',ipatch, &
1221  '. Overriding coupling input.'
1222 
1223  ppatch%bcCoupled = bc_burning
1224  ppatch%mixt%distrib = bcdat_distrib ! MUST have distribution
1225  ELSE IF ( nint(vals(3)) == bc_not_coupled ) THEN
1226  ppatch%bcCoupled = nint(vals(3))
1227  ppatch%mixt%distrib = distrib
1228  ELSE
1229  global%warnCounter = global%warnCounter + 1
1230 
1231  WRITE(stdout,'(A,3X,A,1X,A,I3,A)') solver_name,'*** WARNING ***', &
1232  'Invalid coupling input for patch ',ipatch, &
1233  '. Overriding coupling input.'
1234 
1235  ppatch%bcCoupled = bc_not_coupled
1236  ppatch%mixt%distrib = distrib
1237  END IF ! NINT(vals)
1238  ELSE
1239  ppatch%bcCoupled = bc_not_coupled
1240  ppatch%mixt%distrib = distrib
1241  END IF ! defined
1242 #else
1243  IF ( defined(3) .EQV. .true. ) THEN
1244  IF ( nint(vals(3)) /= bc_not_coupled ) THEN
1245  global%warnCounter = global%warnCounter + 1
1246 
1247  WRITE(stdout,'(A,3X,A,1X,A,I3,A)') solver_name,'*** WARNING ***', &
1248  'Invalid coupling input for patch ',ipatch, &
1249  '. Overriding user input.'
1250 
1251  ppatch%bcCoupled = bc_not_coupled
1252  ELSE
1253  ppatch%bcCoupled = bc_not_coupled
1254  END IF ! NINT(vals(3))
1255 
1256  ppatch%mixt%distrib = distrib
1257  ELSE
1258  ppatch%bcCoupled = bc_not_coupled
1259  ppatch%mixt%distrib = bcdat_constant
1260  END IF ! defined(3)
1261 #endif
1262 
1263 #ifdef GENX
1264 ! ------------------------------------------------------------------------------
1265 ! Check whether bFlagInit defined
1266 ! ------------------------------------------------------------------------------
1267 
1268  IF ( defined(4) .EQV. .true. ) THEN
1269  ppatch%bFlagInit = vals(4)
1270 
1271  IF ( ppatch%bFlagInit < 0 .OR. ppatch%bFlagInit > 1 ) THEN
1272  global%warnCounter = global%warnCounter + 1
1273 
1274  WRITE(stdout,'(A,3X,A,1X,A,I3,A)') solver_name,'*** WARNING ***', &
1275  'Invalid burning flag input for patch ',ipatch, &
1276  '. Overriding burning flag input.'
1277  ppatch%bFlagInit = 1
1278  END IF ! pPatch%bFlagInit
1279  ELSE
1280  global%warnCounter = global%warnCounter + 1
1281 
1282  WRITE(stdout,'(A,3X,A,1X,A,I3,A)') solver_name,'*** WARNING ***', &
1283  'Missing burning flag input for patch ',ipatch, &
1284  '. Setting burning flag input.'
1285  ppatch%bFlagInit = 1
1286  END IF ! defined
1287 #endif
1288 
1289 ! ------------------------------------------------------------------------------
1290 ! Check that all flags were set
1291 ! ------------------------------------------------------------------------------
1292 
1293  IF ( ppatch%mixt%distrib == bcdat_constant ) THEN
1294  checksum = 0
1295 
1296  DO i = 0,ppatch%mixt%nData-1
1297  IF ( defined(1+i) .EQV. .true. ) THEN
1298  checksum = checksum + 1
1299  END IF ! defined
1300  END DO ! i
1301 
1302  IF ( checksum /= ppatch%mixt%nData ) THEN
1303  CALL errorstop(global,err_bcval_missing,__line__)
1304  END IF ! checkSum
1305  END IF ! patch
1306 
1307 ! ------------------------------------------------------------------------------
1308 ! Set patch motion variable
1309 ! ------------------------------------------------------------------------------
1310 
1311  IF ( defined(7) .EQV. .true. ) THEN
1312  ppatch%movePatchDir = vals(7)
1313  ELSE
1314  ppatch%movePatchDir = movepatch_dir_none
1315  END IF ! defined
1316 
1317 ! ------------------------------------------------------------------------------
1318 ! Set patch statistics plotting flag
1319 ! ------------------------------------------------------------------------------
1320 
1321  IF ( defined(8) .EQV. .true. ) THEN
1322  IF ( nint(vals(8)) == 1 ) THEN
1323  ppatch%plotStatsFlag = .true.
1324  ELSE
1325  ppatch%plotStatsFlag = .false.
1326  END IF ! NINT
1327  ELSE
1328  ppatch%plotStatsFlag = .false.
1329  END IF ! defined
1330 
1331 ! ------------------------------------------------------------------------------
1332 ! Set constraint variable
1333 ! ------------------------------------------------------------------------------
1334 
1335  IF ( defined(9) .EQV. .true. ) THEN
1336  IF ( nint(vals(9)) == 1 ) THEN
1337  ppatch%cReconst = constr_weighted
1338  ELSE
1339  ppatch%cReconst = constr_none
1340  END IF ! NINT(vals(9))
1341  ELSE
1342  ppatch%cReconst = constr_none
1343  END IF ! defined
1344  END IF ! pPatch%iPatchGlobal
1345  END DO ! iPatch
1346 
1347 ! ******************************************************************************
1348 ! Copy values/distribution to variables
1349 ! ******************************************************************************
1350 
1351  DO ipatch = 1,pregion%grid%nPatches
1352  ppatch => pregion%patches(ipatch)
1353 
1354 ! ==============================================================================
1355 ! Check whether this global patch exists in this region
1356 ! ==============================================================================
1357 
1358  IF ( ppatch%iPatchGlobal >= ipatchbeg .AND. &
1359  ppatch%iPatchGlobal <= ipatchend ) THEN
1360 
1361 ! ------------------------------------------------------------------------------
1362 ! Distribution from file: Allocate and initialize, actual values read or
1363 ! obtained at later stage
1364 ! ------------------------------------------------------------------------------
1365 
1366  IF ( ppatch%mixt%distrib == bcdat_distrib ) THEN
1367  nbfacestot = ppatch%nBTrisTot + ppatch%nBQuadsTot
1368 
1369  ALLOCATE(ppatch%mixt%vals(ppatch%mixt%nData,nbfacestot), &
1370  stat=errorflag)
1371  global%error = errorflag
1372  IF ( global%error /= err_none ) THEN
1373  CALL errorstop(global,err_allocate,__line__,'pPatch%mixt%vals')
1374  END IF ! global
1375 
1376 ! ------- If not coupled, get boundary data from file --------------------------
1377 
1378  IF ( ppatch%bcCoupled == bc_not_coupled ) THEN
1379  DO ifl = 1,nbfacestot
1380  DO idata = 1,ppatch%mixt%nData
1381  ppatch%mixt%vals(idata,ifl) = &
1382  REAL(crazy_value_int,kind=rfreal)
1383  END DO ! iData
1384  END DO ! ifl
1385 
1386 ! ------- If coupled, get boundary data from Roccom ----------------------------
1387 
1388  ELSE ! Initialize - important for GENX runs from scratch
1389  DO ifl = 1,nbfacestot
1390  DO idata = 1,ppatch%mixt%nData
1391  ppatch%mixt%vals(idata,ifl) = 0.0_rfreal
1392  END DO ! iData
1393  END DO ! ifl
1394  END IF ! pPatch%bcCoupled
1395 
1396 ! ------------------------------------------------------------------------------
1397 ! Constant value
1398 ! ------------------------------------------------------------------------------
1399 
1400  ELSE
1401  ALLOCATE(ppatch%mixt%vals(ppatch%mixt%nData,0:1), &
1402  stat=errorflag)
1403  global%error = errorflag
1404  IF ( global%error /= err_none ) THEN
1405  CALL errorstop(global,err_allocate,__line__,'pPatch%mixt%vals')
1406  END IF ! global
1407 
1408  ppatch%mixt%vals(bcdat_inject_mfrate,0:1) = vals(1)
1409  ppatch%mixt%vals(bcdat_inject_temp ,0:1) = vals(2)
1410  END IF ! pPatch%mixt%distrib
1411 
1412  END IF ! pPatch%iPatchGlobal
1413  END DO ! iPatch
1414 
1415 ! ******************************************************************************
1416 ! End
1417 ! ******************************************************************************
1418 
1419  CALL deregisterfunction(global)
1420 
1421  END SUBROUTINE rflu_readbcinjectsection
1422 
1423 
1424 
1425 
1426 
1427 
1428 
1429 
1430 ! ******************************************************************************
1431 !
1432 ! Purpose: Read in user input related to boundary conditions (done on all
1433 ! processors).
1434 !
1435 ! Description: None.
1436 !
1437 ! Input:
1438 ! pRegion Pointer to region
1439 !
1440 ! Output: None.
1441 !
1442 ! Notes: None.
1443 !
1444 ! ******************************************************************************
1445 
1446  SUBROUTINE rflu_readbcinputfile(pRegion)
1447 
1449 
1450  IMPLICIT NONE
1451 
1452 ! ******************************************************************************
1453 ! Definitions and declarations
1454 ! ******************************************************************************
1455 
1456 ! ==============================================================================
1457 ! Arguments
1458 ! ==============================================================================
1459 
1460  TYPE(t_region), POINTER :: pregion
1461 
1462 ! ==============================================================================
1463 ! Locals
1464 ! ==============================================================================
1465 
1466  CHARACTER(CHRLEN) :: bccoupledstring,ifilename,movestring,smoothstring
1467  CHARACTER(256) :: line
1468  INTEGER :: errorflag,ipatch,loopcounter
1469  TYPE(t_patch), POINTER :: ppatch
1470  TYPE(t_grid) :: grid
1471  TYPE(t_global), POINTER :: global
1472 
1473 ! ******************************************************************************
1474 ! Start
1475 ! ******************************************************************************
1476 
1477  global => pregion%global
1478 
1479  CALL registerfunction(global,'RFLU_ReadBcInputFile',&
1480  'RFLU_ModReadBcInputFile.F90')
1481 
1482  IF ( global%myProcid == masterproc .AND. &
1483  global%verbLevel >= verbose_low ) THEN
1484  WRITE(stdout,'(A,1X,A)') solver_name
1485  WRITE(stdout,'(A,1X,A)') solver_name, &
1486  'Reading Rocflu boundary condition file...'
1487  END IF ! global%verbLevel
1488 
1489 ! ******************************************************************************
1490 ! Open file
1491 ! ******************************************************************************
1492 
1493  CALL buildfilenameplain(global,filedest_indir,'.bc',ifilename)
1494 
1495  OPEN(if_input,file=ifilename,form='FORMATTED',status='OLD',iostat=errorflag)
1496  global%error = errorflag
1497  IF ( global%error /= err_none ) THEN
1498  CALL errorstop(global,err_file_open,__line__,'File: '//trim(ifilename))
1499  END IF ! global%error
1500 
1501 ! ******************************************************************************
1502 ! Read file looking for keywords
1503 ! ******************************************************************************
1504 
1505  loopcounter = 0
1506 
1507  keywordloop: DO
1508  READ(if_input,'(A256)',iostat=errorflag) line
1509 
1510  IF ( errorflag > 0 ) THEN ! Error occurred
1511  CALL errorstop(global,err_file_read,__line__,'File: '//trim(ifilename))
1512  ELSE IF ( errorflag < 0 ) THEN ! Encountered end of file
1513  EXIT keywordloop
1514  END IF ! errorFlag
1515 
1516  SELECT CASE( trim(line) )
1517  CASE ('# BC_FARF')
1518  CALL rflu_readbcfarfsection(pregion)
1519 ! TEMPORARY - Keep this for backward compatibility
1520  CASE ('# BC_INFLOW')
1521  CALL rflu_readbcinflowtotangsection(pregion)
1522 ! END TEMPORARY
1523  CASE ('# BC_INFLOW_TOTANG')
1524  CALL rflu_readbcinflowtotangsection(pregion)
1525  CASE ('# BC_INFLOW_VELTEMP')
1526  CALL rflu_readbcinflowveltempsection(pregion)
1527  CASE ('# BC_INJECT')
1528  CALL rflu_readbcinjectsection(pregion)
1529 ! TEMPORARY - Keep this for backward compatibility
1530  CASE ('# BC_NOSLIP')
1531  CALL rflu_readbcnoslipwallheatsect(pregion)
1532 ! END TEMPORARY
1533  CASE ('# BC_NOSLIP_HFLUX')
1534  CALL rflu_readbcnoslipwallheatsect(pregion)
1535  CASE ('# BC_NOSLIP_TEMP')
1536  CALL rflu_readbcnoslipwalltempsect(pregion)
1537  CASE ('# BC_OUTFLOW')
1538  CALL rflu_readbcoutflowsection(pregion)
1539  CASE ('# BC_PERIODIC')
1540  CALL rflu_readbcperiodicsection(pregion)
1541  CASE ('# BC_SLIPW')
1542  CALL rflu_readbcslipwallsection(pregion)
1543  CASE ('# BC_SYMMETRY')
1544  CALL rflu_readbcsymmetrysection(pregion)
1545  CASE ('# BC_VIRTUAL')
1546  CALL rflu_readbcvirtualsection(pregion)
1547  CASE ('# END')
1548  EXIT keywordloop
1549  END SELECT ! TRIM(line)
1550 
1551  loopcounter = loopcounter + 1
1552 
1553  IF ( loopcounter >= limit_infinite_loop ) THEN ! Prevent infinite loop
1554  CALL errorstop(global,err_infinite_loop ,__line__)
1555  END IF ! loopCounter
1556  END DO keywordloop
1557 
1558 ! ******************************************************************************
1559 ! Close file
1560 ! ******************************************************************************
1561 
1562  CLOSE(if_input,iostat=errorflag)
1563  global%error = errorflag
1564  IF ( global%error /= err_none ) THEN
1565  CALL errorstop(global,err_file_close,__line__,'File: '//trim(ifilename))
1566  END IF ! global%error
1567 
1568 ! ******************************************************************************
1569 ! Write out information
1570 ! ******************************************************************************
1571 
1572  IF ( global%myProcid == masterproc .AND. &
1573  global%verbLevel >= verbose_med ) THEN
1574  WRITE(stdout,'(A,3X,A)') solver_name,'Boundary condition information:'
1575  WRITE(stdout,'(A,5X,A,2X,A,2X,A,2X,A,12X,A,2X,A,3X,A,15X,A)') &
1576  solver_name,'Local','Global','Type','Name','Order','Constr', &
1577  'Coupling','Motion'
1578 
1579  DO ipatch = 1,pregion%grid%nPatches
1580  ppatch => pregion%patches(ipatch)
1581 
1582  IF ( ppatch%bcCoupled == bc_not_coupled ) THEN
1583  bccoupledstring = 'Not coupled'
1584  ELSE IF ( ppatch%bcCoupled == bc_not_burning ) THEN
1585  bccoupledstring = 'Coupled, not burning'
1586  ELSE IF ( ppatch%bcCoupled == bc_burning ) THEN
1587  bccoupledstring = 'Coupled, burning'
1588  ELSE ! Defensive programming
1589  CALL errorstop(global,err_reached_default,__line__)
1590  END IF ! pPatch%bcCoupled
1591 
1592  WRITE(stdout,'(A,4X,I4,4X,I4,4X,I3,3X,A,2X,I2,6X,I2,5X,A,5X,I2)') &
1593  solver_name,ipatch,ppatch%iPatchGlobal,ppatch%bcType, &
1594  ppatch%bcName(1:15),ppatch%spaceOrder,ppatch%cReconst, &
1595  bccoupledstring(1:20),ppatch%movePatchDir
1596  END DO ! iPatch
1597  END IF ! global%verbLevel
1598 
1599 ! ******************************************************************************
1600 ! End
1601 ! ******************************************************************************
1602 
1603  IF ( global%myProcid == masterproc .AND. &
1604  global%verbLevel >= verbose_med ) THEN
1605  WRITE(stdout,'(A,1X,A)') solver_name, &
1606  'Reading Rocflu boundary condition file done.'
1607  WRITE(stdout,'(A,1X,A)') solver_name
1608  END IF ! global%verbLevel
1609 
1610  CALL deregisterfunction(global)
1611 
1612  END SUBROUTINE rflu_readbcinputfile
1613 
1614 
1615 
1616 
1617 
1618 
1619 ! ******************************************************************************
1620 !
1621 ! Purpose: Read in user input related to boundary conditions (done on all
1622 ! processors).
1623 !
1624 ! Description: None.
1625 !
1626 ! Input:
1627 ! pRegion Pointer to region
1628 !
1629 ! Output: None.
1630 !
1631 ! Notes: None.
1632 !
1633 ! ******************************************************************************
1634 
1635  SUBROUTINE rflu_readbcinputfilewrapper(pRegion)
1636 
1637 #ifdef SPEC
1639 #endif
1640 
1641  IMPLICIT NONE
1642 
1643 ! *****************************************************************************
1644 ! Definitions and declarations
1645 ! *****************************************************************************
1646 
1647 ! =============================================================================
1648 ! Arguments
1649 ! =============================================================================
1650 
1651  TYPE(t_region), POINTER :: pregion
1652 
1653 ! =============================================================================
1654 ! Locals
1655 ! =============================================================================
1656 
1657  TYPE(t_global), POINTER :: global
1658 
1659 ! *****************************************************************************
1660 ! Start
1661 ! *****************************************************************************
1662 
1663  global => pregion%global
1664 
1665  CALL registerfunction(global,'RFLU_ReadBcInputFileWrapper',&
1666  'RFLU_ModReadBcInputFile.F90')
1667 
1668 ! *****************************************************************************
1669 ! Call routines to read boundary condition information
1670 ! *****************************************************************************
1671 
1672 ! =============================================================================
1673 ! Mixture
1674 ! =============================================================================
1675 
1676  CALL rflu_readbcinputfile(pregion)
1677 
1678 ! =============================================================================
1679 ! Physical modules
1680 ! =============================================================================
1681 
1682 #ifdef SPEC
1683  IF ( global%specUsed .EQV. .true. ) THEN
1684  CALL spec_rflu_readbcinputfile(pregion)
1685  END IF ! global%specUsed
1686 #endif
1687 
1688 ! *****************************************************************************
1689 ! End
1690 ! *****************************************************************************
1691 
1692  CALL deregisterfunction(global)
1693 
1694  END SUBROUTINE rflu_readbcinputfilewrapper
1695 
1696 
1697 
1698 
1699 
1700 
1701 ! ******************************************************************************
1702 !
1703 ! Purpose: Read in user input related to no slip-wall boundary condition with
1704 ! imposed heat flux.
1705 !
1706 ! Description: None.
1707 !
1708 ! Input:
1709 ! pRegion Pointer to region data
1710 !
1711 ! Output: None.
1712 !
1713 ! Notes: None.
1714 !
1715 ! ******************************************************************************
1716 
1717  SUBROUTINE rflu_readbcnoslipwallheatsect(pRegion)
1718 
1719  USE modinterfaces, ONLY: readpatchsection
1720 
1721  IMPLICIT NONE
1722 
1723 ! ******************************************************************************
1724 ! Declarations and definitions
1725 ! ******************************************************************************
1726 
1727 ! ==============================================================================
1728 ! Arguments
1729 ! ==============================================================================
1730 
1731  TYPE(t_region), POINTER :: pregion
1732 
1733 ! ==============================================================================
1734 ! Local variables
1735 ! ==============================================================================
1736 
1737  INTEGER, PARAMETER :: nvals_max = 10
1738  LOGICAL, DIMENSION(NVALS_MAX) :: defined
1739  CHARACTER(10) :: keys(nvals_max)
1740  CHARACTER(256) :: ifilename
1741  CHARACTER(CHRLEN) :: bcname
1742  INTEGER :: checksum,distrib,errorflag,i,idata,ifl,ipatch,nvals,ipatchbeg, &
1743  ipatchend,nbfacestot
1744  REAL(RFREAL), DIMENSION(NVALS_MAX) :: vals
1745  TYPE(t_grid) :: grid
1746  TYPE(t_patch), POINTER :: ppatch
1747  TYPE(t_global), POINTER :: global
1748 
1749 ! ******************************************************************************
1750 ! Start
1751 ! ******************************************************************************
1752 
1753  global => pregion%global
1754 
1755  CALL registerfunction(global,'RFLU_ReadBcNoSlipWallHeatSect',&
1756  'RFLU_ModReadBcInputFile.F90')
1757 
1758 ! ******************************************************************************
1759 ! Specify keywords and search for them
1760 ! ******************************************************************************
1761 
1762  nvals = nvals_max
1763 
1764  keys(1) = 'HFLUX'
1765  keys(2) = 'COUPLED'
1766  keys(3) = 'MVPATCH'
1767  keys(4) = 'SMGRID'
1768  keys(5) = 'MOVEDIR'
1769  keys(6) = 'STATS'
1770  keys(7) = 'CRECONST'
1771  keys(8) = 'KIND'
1772  keys(9) = 'THRUSTFLAG'
1773  keys(10)= 'ORDER'
1774 
1775  CALL readpatchsection(global,if_input,nvals,keys,vals,ipatchbeg,ipatchend, &
1776  distrib,ifilename,bcname,defined)
1777 
1778 ! ******************************************************************************
1779 ! Check if specified number of patches exceeds available ones
1780 ! ******************************************************************************
1781 
1782  IF ( ipatchend > global%nPatches ) THEN
1783  CALL errorstop(global,err_patch_range,__line__)
1784  END IF ! iPatchEnd
1785 
1786 ! ******************************************************************************
1787 ! Get switches and check that all necessary values defined
1788 ! ******************************************************************************
1789 
1790  DO ipatch = 1,pregion%grid%nPatches
1791  ppatch => pregion%patches(ipatch)
1792 
1793 ! ==============================================================================
1794 ! Check whether this global patch exists in this region
1795 ! ==============================================================================
1796 
1797  IF ( ppatch%iPatchGlobal >= ipatchbeg .AND. &
1798  ppatch%iPatchGlobal <= ipatchend ) THEN
1799  ppatch%bcType = bc_noslipwall_hflux
1800  ppatch%bcName = bcname
1801 
1802 ! TEMPORARY - No longer used, keep for backward compatibility
1803  ppatch%movePatch = .false.
1804  ppatch%smoothGrid = .false.
1805 ! END TEMPORARY
1806 
1807  ppatch%mixt%nData = 1
1808  ppatch%mixt%nSwitches = 0
1809 
1810  ppatch%mixt%distrib = bcdat_constant ! TEMPORARY restriction
1811 
1812 ! ------------------------------------------------------------------------------
1813 ! Check that necessary variables defined
1814 ! ------------------------------------------------------------------------------
1815 
1816  IF ( ppatch%mixt%distrib == bcdat_constant ) THEN
1817  checksum = 0
1818 
1819  DO i = 0,ppatch%mixt%nData-1
1820  IF ( defined(1+i) .EQV. .true. ) THEN
1821  checksum = checksum + 1
1822  END IF ! defined
1823  END DO ! i
1824 
1825  IF ( checksum /= ppatch%mixt%nData ) THEN
1826  CALL errorstop(global,err_bcval_missing,__line__)
1827  END IF ! checkSum
1828  END IF ! pPatch
1829 
1830 ! ------------------------------------------------------------------------------
1831 ! initialize Boundary Condition kind
1832 ! ------------------------------------------------------------------------------
1833 
1834  IF ( defined(8) .EQV. .true. ) THEN
1835  IF ( (nint(vals(8)) >= bc_kind_min) .AND. &
1836  (nint(vals(8)) <= bc_kind_max) ) THEN
1837  ppatch%bcKind = nint(vals(8))
1838  ELSE
1839 ! TEMPORARY : issue a warning here ...
1840  ppatch%bcKind = bc_kind_simple ! Initialize with Default BC Kind
1841  END IF ! checking range of vals(8)
1842  ELSE
1843  ppatch%bcKind = bc_kind_simple ! Default BC Kind
1844  END IF ! defined(8)
1845 
1846 ! ------------------------------------------------------------------------------
1847 ! initialize patch thrustFlag
1848 ! ------------------------------------------------------------------------------
1849 
1850  IF ( defined(9) .EQV. .true. ) THEN
1851  IF ( (vals(9) > 0.5_rfreal) .AND. &
1852  (vals(9) < 1.5_rfreal) ) THEN
1853  ppatch%thrustFlag = .true.
1854  ELSE
1855  ppatch%thrustFlag = .false.
1856  END IF !
1857  ELSE
1858  ppatch%thrustFlag = .false.
1859  END IF ! defined(9)
1860 
1861 ! ------------------------------------------------------------------------------
1862 ! Set patch spatial order
1863 ! ------------------------------------------------------------------------------
1864 
1865  IF ( defined(10) .EQV. .true. ) THEN
1866  IF ( nint(vals(10)) == 2 ) THEN
1867  ppatch%spaceOrder = 2
1868  ELSE
1869  ppatch%spaceOrder = 1
1870  END IF ! NINT(vals(10))
1871  ELSE
1872  ppatch%spaceOrder = pregion%mixtInput%spaceOrderBFaces
1873  END IF ! defined
1874 
1875 ! ------------------------------------------------------------------------------
1876 ! Check whether coupling flag defined
1877 ! ------------------------------------------------------------------------------
1878 
1879 #ifdef GENX
1880  IF ( defined(2) .EQV. .true. ) THEN
1881  IF ( nint(vals(2)) == bc_not_burning ) THEN
1882  ppatch%bcCoupled = nint(vals(2))
1883  ppatch%mixt%distrib = bcdat_distrib ! MUST have distribution
1884  ELSE IF ( nint(vals(2)) == bc_burning ) THEN
1885  global%warnCounter = global%warnCounter + 1
1886 
1887  WRITE(stdout,'(A,3X,A,1X,A,I3,A)') solver_name,'*** WARNING ***', &
1888  'Invalid coupling input for patch ',ipatch, &
1889  '. Overriding user input.'
1890 
1891  ppatch%bcCoupled = bc_not_burning
1892  ppatch%mixt%distrib = bcdat_distrib ! MUST have distribution
1893  ELSE IF ( nint(vals(2)) == bc_not_coupled ) THEN
1894  ppatch%bcCoupled = nint(vals(2))
1895  ppatch%mixt%distrib = distrib
1896  ELSE
1897  global%warnCounter = global%warnCounter + 1
1898 
1899  WRITE(stdout,'(A,3X,A,1X,A,I3,A)') solver_name,'*** WARNING ***', &
1900  'Invalid coupling input for patch ',ipatch, &
1901  '. Overriding user input.'
1902 
1903  ppatch%bcCoupled = bc_not_coupled
1904  ppatch%mixt%distrib = distrib
1905  END IF ! NINT(vals)
1906  ELSE
1907  ppatch%bcCoupled = bc_not_coupled
1908  ppatch%mixt%distrib = distrib
1909  END IF ! defined
1910 #else
1911  IF ( defined(2) .EQV. .true. ) THEN
1912  IF ( nint(vals(2)) /= bc_not_coupled ) THEN
1913  global%warnCounter = global%warnCounter + 1
1914 
1915  WRITE(stdout,'(A,3X,A,1X,A,I3,A)') solver_name,'*** WARNING ***', &
1916  'Invalid coupling input for patch ',ipatch, &
1917  '. Overriding user input.'
1918 
1919  ppatch%bcCoupled = bc_not_coupled
1920  ELSE
1921  ppatch%bcCoupled = bc_not_coupled
1922  END IF ! NINT(vals(2))
1923 
1924  ppatch%mixt%distrib = distrib
1925  ELSE
1926  ppatch%bcCoupled = bc_not_coupled
1927  ppatch%mixt%distrib = bcdat_constant
1928  END IF ! defined(2)
1929 #endif
1930 
1931 ! ------------------------------------------------------------------------------
1932 ! Set patch motion variable
1933 ! ------------------------------------------------------------------------------
1934 
1935  IF ( defined(5) .EQV. .true. ) THEN
1936  ppatch%movePatchDir = vals(5)
1937  ELSE
1938  ppatch%movePatchDir = movepatch_dir_none
1939  END IF ! defined
1940 
1941 ! ------------------------------------------------------------------------------
1942 ! Set patch statistics plotting flag
1943 ! ------------------------------------------------------------------------------
1944 
1945  IF ( defined(6) .EQV. .true. ) THEN
1946  IF ( nint(vals(6)) == 1 ) THEN
1947  ppatch%plotStatsFlag = .true.
1948  ELSE
1949  ppatch%plotStatsFlag = .false.
1950  END IF ! NINT
1951  ELSE
1952  ppatch%plotStatsFlag = .false.
1953  END IF ! defined
1954 
1955 ! ------------------------------------------------------------------------------
1956 ! Set constraint variable
1957 ! ------------------------------------------------------------------------------
1958 
1959  IF ( defined(7) .EQV. .true. ) THEN
1960  IF ( nint(vals(7)) == 1 ) THEN
1961  ppatch%cReconst = constr_weighted
1962  ELSE
1963  ppatch%cReconst = constr_none
1964  END IF ! NINT(vals(7))
1965  ELSE
1966  ppatch%cReconst = constr_none
1967  END IF ! defined
1968  END IF ! pPatch%iPatchGlobal
1969  END DO ! iPatch
1970 
1971 ! ******************************************************************************
1972 ! Copy values/distribution to variables
1973 ! ******************************************************************************
1974 
1975  DO ipatch = 1,pregion%grid%nPatches
1976  ppatch => pregion%patches(ipatch)
1977 
1978 ! ==============================================================================
1979 ! Check whether this global patch exists in this region
1980 ! ==============================================================================
1981 
1982  IF ( ppatch%iPatchGlobal >= ipatchbeg .AND. &
1983  ppatch%iPatchGlobal <= ipatchend ) THEN
1984 
1985 ! ------------------------------------------------------------------------------
1986 ! Distribution from file: Allocate and initialize, actual values read in
1987 ! at later stage
1988 ! ------------------------------------------------------------------------------
1989 
1990  IF ( ppatch%mixt%distrib == bcdat_distrib ) THEN
1991  nbfacestot = ppatch%nBTrisTot + ppatch%nBQuadsTot
1992 
1993  ALLOCATE(ppatch%mixt%vals(ppatch%mixt%nData,nbfacestot), &
1994  stat=errorflag)
1995  global%error = errorflag
1996  IF ( global%error /= err_none ) THEN
1997  CALL errorstop(global,err_allocate,__line__,'pPatch%mixt%vals')
1998  END IF ! global
1999 
2000  DO ifl = 1,nbfacestot
2001  DO idata = 1,ppatch%mixt%nData
2002  ppatch%mixt%vals(idata,ifl) = REAL(crazy_value_int,kind=rfreal)
2003  END DO ! iData
2004  END DO ! ifl
2005 
2006 ! ------------------------------------------------------------------------------
2007 ! Constant value
2008 ! ------------------------------------------------------------------------------
2009 
2010  ELSE
2011  ALLOCATE(ppatch%mixt%vals(ppatch%mixt%nData,0:1), &
2012  stat=errorflag)
2013  global%error = errorflag
2014  IF ( global%error /= err_none ) THEN
2015  CALL errorstop(global,err_allocate,__line__,'pPatch%mixt%vals')
2016  END IF ! global
2017 
2018  ppatch%mixt%vals(bcdat_noslip_q,0:1) = vals(1)
2019  END IF ! pPatch%mixt%distrib
2020  END IF ! pPatch%mixt%switches
2021  END DO ! iPatch
2022 
2023 ! ******************************************************************************
2024 ! End
2025 ! ******************************************************************************
2026 
2027  CALL deregisterfunction(global)
2028 
2029  END SUBROUTINE rflu_readbcnoslipwallheatsect
2030 
2031 
2032 
2033 
2034 
2035 
2036 
2037 
2038 ! ******************************************************************************
2039 !
2040 ! Purpose: Read in user input related to no slip-wall boundary condition with
2041 ! imposed temperature.
2042 !
2043 ! Description: None.
2044 !
2045 ! Input:
2046 ! pRegion Pointer to region data
2047 !
2048 ! Output: None.
2049 !
2050 ! Notes: None.
2051 !
2052 ! ******************************************************************************
2053 
2054  SUBROUTINE rflu_readbcnoslipwalltempsect(pRegion)
2055 
2056  USE modinterfaces, ONLY: readpatchsection
2057 
2058  IMPLICIT NONE
2059 
2060 ! ******************************************************************************
2061 ! Declarations and definitions
2062 ! ******************************************************************************
2063 
2064 ! ==============================================================================
2065 ! Arguments
2066 ! ==============================================================================
2067 
2068  TYPE(t_region), POINTER :: pregion
2069 
2070 ! ==============================================================================
2071 ! Local variables
2072 ! ==============================================================================
2073 
2074  INTEGER, PARAMETER :: nvals_max = 10
2075  LOGICAL, DIMENSION(NVALS_MAX) :: defined
2076  CHARACTER(10) :: keys(nvals_max)
2077  CHARACTER(256) :: ifilename
2078  CHARACTER(CHRLEN) :: bcname
2079  INTEGER :: checksum,distrib,errorflag,i,idata,ifl,ipatch,nbfacestot, &
2080  nvals,ipatchbeg,ipatchend
2081  REAL(RFREAL), DIMENSION(NVALS_MAX) :: vals
2082  TYPE(t_grid) :: grid
2083  TYPE(t_patch), POINTER :: ppatch
2084  TYPE(t_global), POINTER :: global
2085 
2086 ! ******************************************************************************
2087 ! Start
2088 ! ******************************************************************************
2089 
2090  global => pregion%global
2091 
2092  CALL registerfunction(global,'RFLU_ReadBcNoSlipWallTempSect',&
2093  'RFLU_ModReadBcInputFile.F90')
2094 
2095 ! ******************************************************************************
2096 ! Specify keywords and search for them
2097 ! ******************************************************************************
2098 
2099  nvals = nvals_max
2100 
2101  keys(1) = 'TEMP'
2102  keys(2) = 'COUPLED'
2103  keys(3) = 'MVPATCH'
2104  keys(4) = 'SMGRID'
2105  keys(5) = 'MOVEDIR'
2106  keys(6) = 'STATS'
2107  keys(7) = 'CRECONST'
2108  keys(8) = 'KIND'
2109  keys(9) = 'THRUSTFLAG'
2110  keys(10)= 'ORDER'
2111 
2112  CALL readpatchsection(global,if_input,nvals,keys,vals,ipatchbeg,ipatchend, &
2113  distrib,ifilename,bcname,defined)
2114 
2115 ! ******************************************************************************
2116 ! Check if specified number of patches exceeds available ones
2117 ! ******************************************************************************
2118 
2119  IF ( ipatchend > global%nPatches ) THEN
2120  CALL errorstop(global,err_patch_range,__line__)
2121  END IF ! iPatchEnd
2122 
2123 ! ******************************************************************************
2124 ! Get switches and check that all necessary values defined
2125 ! ******************************************************************************
2126 
2127  DO ipatch = 1,pregion%grid%nPatches
2128  ppatch => pregion%patches(ipatch)
2129 
2130 ! ==============================================================================
2131 ! Check whether this global patch exists in this region
2132 ! ==============================================================================
2133 
2134  IF ( ppatch%iPatchGlobal >= ipatchbeg .AND. &
2135  ppatch%iPatchGlobal <= ipatchend ) THEN
2136  ppatch%bcType = bc_noslipwall_temp
2137  ppatch%bcName = bcname
2138 
2139 ! TEMPORARY - No longer used, keep for backward compatibility
2140  ppatch%movePatch = .false.
2141  ppatch%smoothGrid = .false.
2142 ! END TEMPORARY
2143 
2144  ppatch%mixt%nData = 1
2145  ppatch%mixt%nSwitches = 0
2146 
2147 ! ------------------------------------------------------------------------------
2148 ! initialize Boundary Condition kind
2149 ! ------------------------------------------------------------------------------
2150 
2151  IF ( defined(8) .EQV. .true. ) THEN
2152  IF ( (nint(vals(8)) >= bc_kind_min) .AND. &
2153  (nint(vals(8)) <= bc_kind_max) ) THEN
2154  ppatch%bcKind = nint(vals(8))
2155  ELSE
2156 ! TEMPORARY : issue a warning here ...
2157  ppatch%bcKind = bc_kind_simple ! Initialize with Default BC Kind
2158  END IF ! checking range of vals(8)
2159  ELSE
2160  ppatch%bcKind = bc_kind_simple ! Default BC Kind
2161  END IF ! defined(8)
2162 
2163 ! ------------------------------------------------------------------------------
2164 ! initialize patch thrustFlag
2165 ! ------------------------------------------------------------------------------
2166 
2167  IF ( defined(9) .EQV. .true. ) THEN
2168  IF ( (vals(9) > 0.5_rfreal) .AND. &
2169  (vals(9) < 1.5_rfreal) ) THEN
2170  ppatch%thrustFlag = .true.
2171  ELSE
2172  ppatch%thrustFlag = .false.
2173  END IF !
2174  ELSE
2175  ppatch%thrustFlag = .false.
2176  END IF ! defined(9)
2177 
2178 ! ------------------------------------------------------------------------------
2179 ! Set patch spatial order
2180 ! ------------------------------------------------------------------------------
2181 
2182  IF ( defined(10) .EQV. .true. ) THEN
2183  IF ( nint(vals(10)) == 2 ) THEN
2184  ppatch%spaceOrder = 2
2185  ELSE
2186  ppatch%spaceOrder = 1
2187  END IF ! NINT(vals(10))
2188  ELSE
2189  ppatch%spaceOrder = pregion%mixtInput%spaceOrderBFaces
2190  END IF ! defined
2191 
2192 ! ------------------------------------------------------------------------------
2193 ! Check whether coupling flag defined
2194 ! ------------------------------------------------------------------------------
2195 
2196 #ifdef GENX
2197  IF ( defined(2) .EQV. .true. ) THEN
2198  IF ( nint(vals(2)) == bc_not_burning ) THEN
2199  ppatch%bcCoupled = nint(vals(2))
2200  ppatch%mixt%distrib = bcdat_distrib ! MUST have distribution
2201  ELSE IF ( nint(vals(2)) == bc_burning ) THEN
2202  global%warnCounter = global%warnCounter + 1
2203 
2204  WRITE(stdout,'(A,3X,A,1X,A,I3,A)') solver_name,'*** WARNING ***', &
2205  'Invalid coupling input for patch ',ipatch, &
2206  '. Overriding user input.'
2207 
2208  ppatch%bcCoupled = bc_not_burning
2209  ppatch%mixt%distrib = bcdat_distrib ! MUST have distribution
2210  ELSE IF ( nint(vals(2)) == bc_not_coupled ) THEN
2211  ppatch%bcCoupled = nint(vals(2))
2212  ppatch%mixt%distrib = distrib
2213  ELSE
2214  global%warnCounter = global%warnCounter + 1
2215 
2216  WRITE(stdout,'(A,3X,A,1X,A,I3,A)') solver_name,'*** WARNING ***', &
2217  'Invalid coupling input for patch ',ipatch, &
2218  '. Overriding user input.'
2219 
2220  ppatch%bcCoupled = bc_not_coupled
2221  ppatch%mixt%distrib = distrib
2222  END IF ! NINT(vals)
2223  ELSE
2224  ppatch%bcCoupled = bc_not_coupled
2225  ppatch%mixt%distrib = distrib
2226  END IF ! defined
2227 #else
2228  IF ( defined(2) .EQV. .true. ) THEN
2229  IF ( nint(vals(2)) /= bc_not_coupled ) THEN
2230  global%warnCounter = global%warnCounter + 1
2231 
2232  WRITE(stdout,'(A,3X,A,1X,A,I3,A)') solver_name,'*** WARNING ***', &
2233  'Invalid coupling input for patch ',ipatch, &
2234  '. Overriding user input.'
2235 
2236  ppatch%bcCoupled = bc_not_coupled
2237  ELSE
2238  ppatch%bcCoupled = bc_not_coupled
2239  END IF ! NINT(vals(2))
2240 
2241  ppatch%mixt%distrib = distrib
2242  ELSE
2243  ppatch%bcCoupled = bc_not_coupled
2244  ppatch%mixt%distrib = bcdat_constant
2245  END IF ! defined(2)
2246 #endif
2247 
2248 ! ------------------------------------------------------------------------------
2249 ! Check that necessary variables defined
2250 ! ------------------------------------------------------------------------------
2251 
2252  IF ( ppatch%mixt%distrib == bcdat_constant ) THEN
2253  checksum = 0
2254 
2255  DO i = 0,ppatch%mixt%nData-1
2256  IF ( defined(1+i) .EQV. .true. ) THEN
2257  checksum = checksum + 1
2258  END IF ! defined
2259  END DO ! i
2260 
2261  IF ( checksum /= ppatch%mixt%nData ) THEN
2262  CALL errorstop(global,err_bcval_missing,__line__)
2263  END IF ! checkSum
2264  END IF ! pPatch
2265 
2266 ! ------------------------------------------------------------------------------
2267 ! Set patch motion variable
2268 ! ------------------------------------------------------------------------------
2269 
2270  IF ( defined(5) .EQV. .true. ) THEN
2271  ppatch%movePatchDir = vals(5)
2272  ELSE
2273  ppatch%movePatchDir = movepatch_dir_none
2274  END IF ! defined
2275 
2276 ! ------------------------------------------------------------------------------
2277 ! Set patch statistics plotting flag
2278 ! ------------------------------------------------------------------------------
2279 
2280  IF ( defined(6) .EQV. .true. ) THEN
2281  IF ( nint(vals(6)) == 1 ) THEN
2282  ppatch%plotStatsFlag = .true.
2283  ELSE
2284  ppatch%plotStatsFlag = .false.
2285  END IF ! NINT
2286  ELSE
2287  ppatch%plotStatsFlag = .false.
2288  END IF ! defined
2289 
2290 ! ------------------------------------------------------------------------------
2291 ! Set constraint variable
2292 ! ------------------------------------------------------------------------------
2293 
2294  IF ( defined(7) .EQV. .true. ) THEN
2295  IF ( nint(vals(7)) == 1 ) THEN
2296  ppatch%cReconst = constr_weighted
2297  ELSE
2298  ppatch%cReconst = constr_none
2299  END IF ! NINT(vals(7))
2300  ELSE
2301  ppatch%cReconst = constr_none
2302  END IF ! defined
2303  END IF ! pPatch%iPatchGlobal
2304  END DO ! iPatch
2305 
2306 ! ******************************************************************************
2307 ! Copy values/distribution to variables
2308 ! ******************************************************************************
2309 
2310  DO ipatch = 1,pregion%grid%nPatches
2311  ppatch => pregion%patches(ipatch)
2312 
2313 ! ==============================================================================
2314 ! Check whether this global patch exists in this region
2315 ! ==============================================================================
2316 
2317  IF ( ppatch%iPatchGlobal >= ipatchbeg .AND. &
2318  ppatch%iPatchGlobal <= ipatchend ) THEN
2319 
2320 ! ------------------------------------------------------------------------------
2321 ! Distribution from file: Allocate and initialize, actual values read in
2322 ! at later stage
2323 ! ------------------------------------------------------------------------------
2324 
2325  IF ( ppatch%mixt%distrib == bcdat_distrib ) THEN
2326  nbfacestot = ppatch%nBTrisTot + ppatch%nBQuadsTot
2327 
2328  ALLOCATE(ppatch%mixt%vals(ppatch%mixt%nData,nbfacestot), &
2329  stat=errorflag)
2330  global%error = errorflag
2331  IF ( global%error /= err_none ) THEN
2332  CALL errorstop(global,err_allocate,__line__,'pPatch%mixt%vals')
2333  END IF ! global
2334 
2335 ! ------- If not coupled, get boundary data from file --------------------------
2336 
2337  IF ( ppatch%bcCoupled == bc_not_coupled ) THEN
2338  DO ifl = 1,nbfacestot
2339  DO idata = 1,ppatch%mixt%nData
2340  ppatch%mixt%vals(idata,ifl) = &
2341  REAL(crazy_value_int,kind=rfreal)
2342  END DO ! iData
2343  END DO ! ifl
2344 
2345 ! ------- If coupled, get boundary data from Roccom ----------------------------
2346 
2347  ELSE ! Initialize - important for GENX runs from scratch
2348  DO ifl = 1,nbfacestot
2349  DO idata = 1,ppatch%mixt%nData
2350  ppatch%mixt%vals(idata,ifl) = 0.0_rfreal
2351  END DO ! iData
2352  END DO ! ifl
2353  END IF ! pPatch%bcCoupled
2354 
2355 ! ------------------------------------------------------------------------------
2356 ! Constant value
2357 ! ------------------------------------------------------------------------------
2358 
2359  ELSE
2360  ALLOCATE(ppatch%mixt%vals(ppatch%mixt%nData,0:1), &
2361  stat=errorflag)
2362  global%error = errorflag
2363  IF ( global%error /= err_none ) THEN
2364  CALL errorstop(global,err_allocate,__line__,'pPatch%mixt%vals')
2365  END IF ! global
2366 
2367  ppatch%mixt%vals(bcdat_noslip_t,0:1) = vals(1)
2368  END IF ! pPatch%mixt%distrib
2369  END IF ! pPatch%mixt%switches
2370  END DO ! iPatch
2371 
2372 ! ******************************************************************************
2373 ! End
2374 ! ******************************************************************************
2375 
2376  CALL deregisterfunction(global)
2377 
2378  END SUBROUTINE rflu_readbcnoslipwalltempsect
2379 
2380 
2381 
2382 
2383 
2384 
2385 
2386 
2387 
2388 ! ******************************************************************************
2389 !
2390 ! Purpose: Read in user input related to outflow boundary condition.
2391 !
2392 ! Description: None.
2393 !
2394 ! Input:
2395 ! pRegion Pointer to region data
2396 !
2397 ! Output: None.
2398 !
2399 ! Notes: None.
2400 !
2401 ! ******************************************************************************
2402 
2403  SUBROUTINE rflu_readbcoutflowsection(pRegion)
2404 
2405  USE modinterfaces, ONLY: readpatchsection
2406 
2407  IMPLICIT NONE
2408 
2409 ! ******************************************************************************
2410 ! Declarations and definitions
2411 ! ******************************************************************************
2412 
2413 ! ==============================================================================
2414 ! Arguments
2415 ! ==============================================================================
2416 
2417  TYPE(t_region), POINTER :: pregion
2418 
2419 ! ==============================================================================
2420 ! Local variables
2421 ! ==============================================================================
2422 
2423  INTEGER, PARAMETER :: nvals_max = 12
2424 
2425  LOGICAL, DIMENSION(NVALS_MAX) :: defined
2426  CHARACTER(10) :: keys(nvals_max)
2427  CHARACTER(256) :: ifilename
2428  CHARACTER(CHRLEN) :: bcname
2429  INTEGER :: checksum,distrib,errorflag,i,idata,ifl,ipatch,ireg,ipatchbeg, &
2430  ipatchend,nvals
2431  REAL(RFREAL), DIMENSION(NVALS_MAX) :: vals
2432  TYPE(t_grid) :: grid
2433  TYPE(t_patch), POINTER :: ppatch
2434  TYPE(t_global), POINTER :: global
2435 
2436 ! ******************************************************************************
2437 ! Start
2438 ! ******************************************************************************
2439 
2440  global => pregion%global
2441 
2442  CALL registerfunction(global,'RFLU_ReadBcOutflowSection',&
2443  'RFLU_ModReadBcInputFile.F90')
2444 
2445 ! ******************************************************************************
2446 ! Specify keywords and search for them
2447 ! ******************************************************************************
2448 
2449  nvals = nvals_max
2450 
2451  keys(1) = 'TYPE'
2452  keys(2) = 'PRESS'
2453  keys(3) = 'MVPATCH'
2454  keys(4) = 'SMGRID'
2455  keys(5) = 'ORDER'
2456  keys(6) = 'STATS'
2457  keys(7) = 'MOVEDIR'
2458  keys(8) = 'COUPLED'
2459  keys(9) = 'KIND'
2460  keys(10) = 'REFLECT'
2461  keys(11) = 'NSCBCK'
2462  keys(12) = 'THRUSTFLAG'
2463 
2464  CALL readpatchsection(global,if_input,nvals,keys,vals,ipatchbeg,ipatchend, &
2465  distrib,ifilename,bcname,defined )
2466 
2467 ! ******************************************************************************
2468 ! Check if specified number of patches exceeds available ones
2469 ! ******************************************************************************
2470 
2471  IF ( ipatchend > global%nPatches ) THEN
2472  CALL errorstop(global,err_patch_range,__line__)
2473  END IF ! iPatchEnd
2474 
2475 ! ******************************************************************************
2476 ! Get switches and check that all necessary values defined
2477 ! ******************************************************************************
2478 
2479  DO ipatch = 1,pregion%grid%nPatches
2480  ppatch => pregion%patches(ipatch)
2481 
2482 ! ==============================================================================
2483 ! Check whether this global patch exists in this region
2484 ! ==============================================================================
2485 
2486  IF ( ppatch%iPatchGlobal >= ipatchbeg .AND. &
2487  ppatch%iPatchGlobal <= ipatchend ) THEN
2488  ppatch%bcType = bc_outflow
2489  ppatch%bcName = bcname
2490 
2491 ! pPatch%bcCoupled = BC_NOT_COUPLED
2492 ! pPatch%movePatchDir = MOVEPATCH_DIR_NONE
2493 
2494  ppatch%cReconst = constr_none
2495  ppatch%plotStatsFlag = .false.
2496 
2497 ! TEMPORARY - No longer used, keep for backward compatibility
2498  ppatch%movePatch = .false.
2499  ppatch%smoothGrid = .false.
2500 ! END TEMPORARY
2501 
2502 ! ------------------------------------------------------------------------------
2503 ! Set switches
2504 ! ------------------------------------------------------------------------------
2505 
2506  ppatch%mixt%nSwitches = 1
2507  ppatch%mixt%distrib = distrib
2508 
2509  ALLOCATE(ppatch%mixt%switches(ppatch%mixt%nSwitches), &
2510  stat=errorflag)
2511  global%error = errorflag
2512  IF ( global%error /= err_none ) THEN
2513  CALL errorstop(global,err_allocate,__line__,'pPatch%mixt%switches')
2514  END IF ! global
2515 
2516 ! ------------------------------------------------------------------------------
2517 ! initialize Boundary Condition kind
2518 ! ------------------------------------------------------------------------------
2519 
2520  IF ( defined(9) .EQV. .true. ) THEN
2521  IF ( (nint(vals(9)) >= bc_kind_min) .AND. &
2522  (nint(vals(9)) <= bc_kind_max) ) THEN
2523  ppatch%bcKind = nint(vals(9))
2524  ELSE
2525 ! TEMPORARY : issue a warning here ...
2526  ppatch%bcKind = bc_kind_simple ! Initialize with Default BC Kind
2527  END IF ! checking range of vals(9)
2528  ELSE
2529  ppatch%bcKind = bc_kind_simple ! Default BC Kind
2530  END IF ! defined(9)
2531 
2532 ! ------------------------------------------------------------------------------
2533 ! initialize if far field is reflecting or non reflecting
2534 ! ------------------------------------------------------------------------------
2535 
2536  IF ( defined(10) .EQV. .true. ) THEN
2537  IF ( nint(vals(10)) == bc_reflecting ) THEN
2538  ppatch%reflect = bc_reflecting
2539  ELSE
2540  ppatch%reflect = bc_nonreflecting
2541  END IF !
2542  ELSE
2543  ppatch%reflect = bc_reflecting
2544  END IF ! defined(10)
2545 
2546  IF ( defined(11) .EQV. .true. ) THEN
2547  ppatch%nscbcK = vals(11)
2548  END IF ! defined(11)
2549 
2550 ! ------------------------------------------------------------------------------
2551 ! initialize patch thrustFlag
2552 ! ------------------------------------------------------------------------------
2553 
2554  IF ( defined(12) .EQV. .true. ) THEN
2555  IF ( (vals(12) > 0.5_rfreal) .AND. &
2556  (vals(12) < 1.5_rfreal) ) THEN
2557  ppatch%thrustFlag = .true.
2558  ELSE
2559  ppatch%thrustFlag = .false.
2560  END IF !
2561  ELSE
2562  ppatch%thrustFlag = .false.
2563  END IF ! defined(12)
2564 
2565 ! ------------------------------------------------------------------------------
2566 ! Check if switch defined
2567 ! ------------------------------------------------------------------------------
2568 
2569  IF ( defined(1) .EQV. .true. ) THEN
2570  IF ( nint(vals(1)) == 0 ) THEN
2571  ppatch%mixt%switches(bcswi_outflow_type) = bcopt_supersonic
2572  ELSE IF ( nint(vals(1)) == 1 ) THEN
2573  ppatch%mixt%switches(bcswi_outflow_type) = bcopt_subsonic
2574  ELSE IF ( nint(vals(1)) == 2 ) THEN
2575  ppatch%mixt%switches(bcswi_outflow_type) = bcopt_mixed
2576  ELSE
2577  CALL errorstop(global,err_val_bcswitch,__line__,'(outflow type).')
2578  END IF ! NINT
2579  ELSE
2580  CALL errorstop(global,err_no_bcswitch,__line__,'(outflow type).')
2581  END IF ! defined
2582 
2583 ! ------------------------------------------------------------------------------
2584 ! Check whether appropriate values specified
2585 ! ------------------------------------------------------------------------------
2586 
2587  IF ( ppatch%mixt%switches(bcswi_outflow_type) /= &
2588  bcopt_supersonic ) THEN
2589  ppatch%mixt%nData = 1
2590 
2591  IF ( ppatch%mixt%distrib == bcdat_constant ) THEN
2592  IF ( defined(2) .EQV. .false. ) THEN
2593  CALL errorstop(global,err_bcval_missing,__line__)
2594  END IF ! defined
2595  END IF ! patch
2596  ELSE
2597  ppatch%mixt%nData = 0
2598  END IF ! pPatch
2599 
2600 ! ------------------------------------------------------------------------------
2601 ! Set patch spatial order
2602 ! ------------------------------------------------------------------------------
2603 
2604  IF ( defined(5) .EQV. .true. ) THEN
2605  IF ( nint(vals(5)) == 2 ) THEN
2606  ppatch%spaceOrder = 2
2607  ELSE
2608  ppatch%spaceOrder = 1
2609  END IF ! NINT(vals(5))
2610  ELSE
2611  ppatch%spaceOrder = pregion%mixtInput%spaceOrderBFaces
2612  END IF ! defined
2613 
2614 ! ------------------------------------------------------------------------------
2615 ! Set patch statistics plotting flag
2616 ! ------------------------------------------------------------------------------
2617 
2618  IF ( defined(6) .EQV. .true. ) THEN
2619  IF ( nint(vals(6)) == 1 ) THEN
2620  ppatch%plotStatsFlag = .true.
2621  ELSE
2622  ppatch%plotStatsFlag = .false.
2623  END IF ! NINT
2624  ELSE
2625  ppatch%plotStatsFlag = .false.
2626  END IF ! defined
2627 
2628 ! ------------------------------------------------------------------------------
2629 ! Set patch motion variable
2630 ! ------------------------------------------------------------------------------
2631 
2632  IF ( defined(7) .EQV. .true. ) THEN
2633  ppatch%movePatchDir = vals(7)
2634  ELSE
2635  ppatch%movePatchDir = movepatch_dir_none
2636  END IF ! defined
2637 
2638 ! ------------------------------------------------------------------------------
2639 ! Set coupling variable
2640 ! ------------------------------------------------------------------------------
2641 
2642  IF ( defined(8) .EQV. .true. ) THEN
2643  ppatch%bcCoupled = vals(8)
2644  ELSE
2645  ppatch%bcCoupled = bc_not_coupled
2646  END IF ! defined
2647 
2648  END IF ! pPatch%iPatchGlobal
2649  END DO ! iPatch
2650 
2651 ! ******************************************************************************
2652 ! Copy values/distribution to variables for non-adiabatic walls
2653 ! ******************************************************************************
2654 
2655  DO ipatch = 1,pregion%grid%nPatches
2656  ppatch => pregion%patches(ipatch)
2657 
2658 ! ==============================================================================
2659 ! Check whether this global patch exists in this region
2660 ! ==============================================================================
2661 
2662  IF ( ppatch%iPatchGlobal >= ipatchbeg .AND. &
2663  ppatch%iPatchGlobal <= ipatchend ) THEN
2664 
2665  IF ( ppatch%mixt%switches(bcswi_outflow_type) /= &
2666  bcopt_supersonic ) THEN
2667 
2668 ! ------------------------------------------------------------------------------
2669 ! Distribution from file: Allocate and initialize, actual values read in
2670 ! at later stage
2671 ! ------------------------------------------------------------------------------
2672 
2673  IF ( ppatch%mixt%distrib == bcdat_distrib ) THEN
2674  ALLOCATE(ppatch%mixt%vals(ppatch%mixt%nData,ppatch%nBFaces), &
2675  stat=errorflag)
2676  global%error = errorflag
2677  IF ( global%error /= err_none ) THEN
2678  CALL errorstop(global,err_allocate,__line__)
2679  END IF ! global
2680 
2681  DO ifl = 1,ppatch%nBFaces
2682  DO idata = 1,ppatch%mixt%nData
2683  ppatch%mixt%vals(idata,ifl) = &
2684  REAL(crazy_value_int,kind=rfreal)
2685  END DO ! iData
2686  END DO ! ifl
2687 
2688 ! ------------------------------------------------------------------------------
2689 ! Constant value
2690 ! ------------------------------------------------------------------------------
2691 
2692  ELSE
2693  ALLOCATE(ppatch%mixt%vals(ppatch%mixt%nData,0:1), &
2694  stat=errorflag)
2695  global%error = errorflag
2696  IF ( global%error /= err_none ) THEN
2697  CALL errorstop(global,err_allocate,__line__,'pPatch%mixt%vals')
2698  END IF ! global
2699 
2700  ppatch%mixt%vals(bcdat_outflow_press,0:1) = vals(2)
2701  END IF ! pPatch%mixt%distrib
2702  ELSE
2703  nullify(ppatch%mixt%vals)
2704  END IF ! pPatch%mixt%switches
2705 
2706  END IF ! pPatch%iPatchGlobal
2707  END DO ! iPatch
2708 
2709 ! ******************************************************************************
2710 ! End
2711 ! ******************************************************************************
2712 
2713  CALL deregisterfunction(global)
2714 
2715  END SUBROUTINE rflu_readbcoutflowsection
2716 
2717 
2718 
2719 
2720 
2721 
2722 
2723 
2724 
2725 ! ******************************************************************************
2726 !
2727 ! Purpose: Read in user input related to periodic boundary condition.
2728 !
2729 ! Description: None.
2730 !
2731 ! Input:
2732 ! pRegion Pointer to region data
2733 !
2734 ! Output: None.
2735 !
2736 ! Notes: None.
2737 !
2738 ! ******************************************************************************
2739 
2740  SUBROUTINE rflu_readbcperiodicsection(pRegion)
2741 
2742  USE modinterfaces, ONLY: readpatchsection
2743 
2744  IMPLICIT NONE
2745 
2746 ! ******************************************************************************
2747 ! Declarations and definitions
2748 ! ******************************************************************************
2749 
2750 ! ==============================================================================
2751 ! Arguments
2752 ! ==============================================================================
2753 
2754  TYPE(t_region), POINTER :: pregion
2755 
2756 ! ==============================================================================
2757 ! Local variables
2758 ! ==============================================================================
2759 
2760  INTEGER, PARAMETER :: nvals_max = 5
2761 
2762  LOGICAL, DIMENSION(NVALS_MAX) :: defined
2763  CHARACTER(10) :: keys(nvals_max)
2764  CHARACTER(256) :: ifilename
2765  CHARACTER(CHRLEN) :: bcname
2766  INTEGER :: checksum,distrib,errorflag,i,idata,ifl,ipatch,ireg,ipatchbeg, &
2767  ipatchend,nvals
2768  REAL(RFREAL), DIMENSION(NVALS_MAX) :: vals
2769  TYPE(t_grid) :: grid
2770  TYPE(t_patch), POINTER :: ppatch
2771  TYPE(t_global), POINTER :: global
2772 
2773 ! ******************************************************************************
2774 ! Start
2775 ! ******************************************************************************
2776 
2777  global => pregion%global
2778 
2779  CALL registerfunction(global,'RFLU_ReadBcPeriodicSection',&
2780  'RFLU_ModReadBcInputFile.F90')
2781 
2782 ! ******************************************************************************
2783 ! Specify keywords and search for them
2784 ! ******************************************************************************
2785 
2786  nvals = nvals_max
2787 
2788  keys(1) = 'RELPATCH'
2789  keys(2) = 'ANGLE'
2790  keys(3) = 'AXIS'
2791  keys(4) = 'MVPATCH'
2792  keys(5) = 'SMGRID'
2793 
2794  CALL readpatchsection(global,if_input,nvals,keys,vals,ipatchbeg,ipatchend, &
2795  distrib,ifilename,bcname,defined )
2796 
2797 ! ******************************************************************************
2798 ! Check if specified number of patches exceeds available ones
2799 ! ******************************************************************************
2800 
2801  IF ( ipatchend > global%nPatches ) THEN
2802  CALL errorstop(global,err_patch_range,__line__)
2803  END IF ! iPatchEnd
2804 
2805 ! ******************************************************************************
2806 ! Get switches and check that all necessary values defined
2807 ! ******************************************************************************
2808 
2809  DO ipatch = 1,pregion%grid%nPatches
2810  ppatch => pregion%patches(ipatch)
2811 
2812 ! ==============================================================================
2813 ! Check whether this global patch exists in this region
2814 ! ==============================================================================
2815 
2816  IF ( ppatch%iPatchGlobal >= ipatchbeg .AND. &
2817  ppatch%iPatchGlobal <= ipatchend ) THEN
2818  ppatch%bcType = bc_periodic
2819  ppatch%bcName = bcname
2820  ppatch%bcCoupled = bc_not_coupled
2821 
2822  ppatch%mixt%nData = 0
2823  ppatch%mixt%nSwitches = 0
2824  ppatch%mixt%distrib = bcdat_constant
2825 
2826  ppatch%bcKind = bc_kind_simple ! Value immaterial
2827  ppatch%thrustFlag = .false. ! Value immaterial
2828 
2829  ppatch%spaceOrder = pregion%mixtInput%spaceOrderBFaces ! Value immaterial
2830  ppatch%cReconst = constr_none
2831 
2832 ! TEMPORARY - No longer used, keep for backward compatibility
2833  ppatch%movePatch = .false.
2834  ppatch%smoothGrid = .false.
2835 ! END TEMPORARY
2836 
2837  IF ( defined(1) .EQV. .false. ) THEN
2838  CALL errorstop(global,err_bcval_missing,__line__)
2839  ELSE
2840  ppatch%iPatchRelated = nint(vals(1))
2841  END IF ! defined
2842 
2843  IF ( defined(2) .EQV. .false. ) THEN
2844  CALL errorstop(global,err_bcval_missing,__line__)
2845  ELSE
2846  ppatch%angleRelated = vals(2)*global%deg2rad
2847  END IF ! defined
2848 
2849  IF ( defined(3) .EQV. .false. ) THEN
2850  CALL errorstop(global,err_bcval_missing,__line__)
2851  ELSE
2852  ppatch%axisRelated = nint(vals(3))
2853  END IF ! defined
2854  END IF ! pPatch%iPatchGlobal
2855  END DO ! iPatch
2856 
2857 ! ******************************************************************************
2858 ! End
2859 ! ******************************************************************************
2860 
2861  CALL deregisterfunction(global)
2862 
2863  END SUBROUTINE rflu_readbcperiodicsection
2864 
2865 
2866 
2867 
2868 
2869 
2870 
2871 
2872 ! ******************************************************************************
2873 !
2874 ! Purpose: Read in user input related to slip-wall boundary condition.
2875 !
2876 ! Description: None.
2877 !
2878 ! Input:
2879 ! pRegion Pointer to region data
2880 !
2881 ! Output: None.
2882 !
2883 ! Notes: None.
2884 !
2885 ! ******************************************************************************
2886 
2887  SUBROUTINE rflu_readbcslipwallsection(pRegion)
2888 
2889  USE modinterfaces, ONLY: readpatchsection
2890 
2891  IMPLICIT NONE
2892 
2893 ! ******************************************************************************
2894 ! Declarations and definitions
2895 ! ******************************************************************************
2896 
2897 ! ==============================================================================
2898 ! Arguments
2899 ! ==============================================================================
2900 
2901  TYPE(t_region), POINTER :: pregion
2902 
2903 ! ==============================================================================
2904 ! Local variables
2905 ! ==============================================================================
2906 
2907  INTEGER, PARAMETER :: nvals_max = 9
2908 
2909  LOGICAL, DIMENSION(NVALS_MAX) :: defined
2910  CHARACTER(10) :: keys(nvals_max)
2911  CHARACTER(256) :: ifilename
2912  CHARACTER(CHRLEN) :: bcname
2913  INTEGER :: distrib,errorflag,ipatch,nvals,ipatchbeg,ipatchend
2914  REAL(RFREAL), DIMENSION(NVALS_MAX) :: vals
2915  TYPE(t_grid) :: grid
2916  TYPE(t_patch), POINTER :: ppatch
2917  TYPE(t_global), POINTER :: global
2918 
2919 ! ******************************************************************************
2920 ! Start
2921 ! ******************************************************************************
2922 
2923  global => pregion%global
2924 
2925  CALL registerfunction(global,'RFLU_ReadBcSlipWallSection',&
2926  'RFLU_ModReadBcInputFile.F90')
2927 
2928 ! ******************************************************************************
2929 ! Specify keywords and search for them
2930 ! ******************************************************************************
2931 
2932  nvals = nvals_max
2933 
2934  keys(1) = 'COUPLED'
2935  keys(2) = 'MVPATCH'
2936  keys(3) = 'SMGRID'
2937  keys(4) = 'MOVEDIR'
2938  keys(5) = 'STATS'
2939  keys(6) = 'CRECONST'
2940  keys(7) = 'KIND'
2941  keys(8) = 'THRUSTFLAG'
2942  keys(9) = 'ORDER'
2943 
2944  CALL readpatchsection(global,if_input,nvals,keys,vals,ipatchbeg,ipatchend, &
2945  distrib,ifilename,bcname,defined)
2946 
2947 ! ******************************************************************************
2948 ! Check if specified number of patches exceeds available ones
2949 ! ******************************************************************************
2950 
2951  IF ( ipatchend > global%nPatches ) THEN
2952  CALL errorstop(global,err_patch_range,__line__)
2953  END IF ! iPatchEnd
2954 
2955 ! ******************************************************************************
2956 ! Loop over patches and copy values/distribution to variables
2957 ! ******************************************************************************
2958 
2959  DO ipatch = 1,pregion%grid%nPatches
2960  ppatch => pregion%patches(ipatch)
2961 
2962 ! ==============================================================================
2963 ! Check whether this global patch exists in this region
2964 ! ==============================================================================
2965 
2966  IF ( ppatch%iPatchGlobal >= ipatchbeg .AND. &
2967  ppatch%iPatchGlobal <= ipatchend ) THEN
2968  ppatch%bcType = bc_slipwall
2969  ppatch%bcName = bcname
2970 
2971 ! TEMPORARY - No longer used, keep for backward compatibility
2972  ppatch%movePatch = .false.
2973  ppatch%smoothGrid = .false.
2974 ! END TEMPORARY
2975 
2976  ppatch%mixt%nData = 0
2977  ppatch%mixt%nSwitches = 0
2978  ppatch%mixt%distrib = bcdat_constant
2979 
2980  nullify(ppatch%mixt%switches)
2981  nullify(ppatch%mixt%vals)
2982 
2983 ! ------------------------------------------------------------------------------
2984 ! initialize Boundary Condition kind
2985 ! ------------------------------------------------------------------------------
2986 
2987  IF ( defined(7) .EQV. .true. ) THEN
2988  IF ( (nint(vals(7)) >= bc_kind_min) .AND. &
2989  (nint(vals(7)) <= bc_kind_max) ) THEN
2990  ppatch%bcKind = nint(vals(7))
2991  ELSE
2992 ! TEMPORARY : issue a warning here ...
2993  ppatch%bcKind = bc_kind_simple ! Initialize with Default BC Kind
2994  END IF ! checking range of vals(7)
2995  ELSE
2996  ppatch%bcKind = bc_kind_simple ! Default BC Kind
2997  END IF ! defined(7)
2998 
2999 ! ------------------------------------------------------------------------------
3000 ! initialize patch thrustFlag
3001 ! ------------------------------------------------------------------------------
3002 
3003  IF ( defined(8) .EQV. .true. ) THEN
3004  IF ( (vals(8) > 0.5_rfreal) .AND. &
3005  (vals(8) < 1.5_rfreal) ) THEN
3006  ppatch%thrustFlag = .true.
3007  ELSE
3008  ppatch%thrustFlag = .false.
3009  END IF !
3010  ELSE
3011  ppatch%thrustFlag = .false.
3012  END IF ! defined(8)
3013 
3014 ! ------------------------------------------------------------------------------
3015 ! Set patch spatial order
3016 ! ------------------------------------------------------------------------------
3017 
3018  IF ( defined(9) .EQV. .true. ) THEN
3019  IF ( nint(vals(9)) == 2 ) THEN
3020  ppatch%spaceOrder = 2
3021  ELSE
3022  ppatch%spaceOrder = 1
3023  END IF ! NINT(vals(9))
3024  ELSE
3025  ppatch%spaceOrder = pregion%mixtInput%spaceOrderBFaces
3026  END IF ! defined
3027 
3028 ! ------------------------------------------------------------------------------
3029 ! Check whether coupling flag defined
3030 ! ------------------------------------------------------------------------------
3031 
3032 #ifdef GENX
3033  IF ( defined(1) .EQV. .true. ) THEN
3034  IF ( nint(vals(1)) == bc_not_burning ) THEN
3035  ppatch%bcCoupled = nint(vals(1))
3036  ELSE IF ( nint(vals(1)) == bc_burning ) THEN
3037  global%warnCounter = global%warnCounter + 1
3038 
3039  WRITE(stdout,'(A,3X,A,1X,A,I3,A)') solver_name,'*** WARNING ***', &
3040  'Invalid coupling input for patch ',ipatch, &
3041  '. Overriding user input.'
3042 
3043  ppatch%bcCoupled = bc_not_burning
3044  ELSE IF ( nint(vals(1)) == bc_not_coupled ) THEN
3045  ppatch%bcCoupled = nint(vals(1))
3046  ELSE
3047  global%warnCounter = global%warnCounter + 1
3048 
3049  WRITE(stdout,'(A,3X,A,1X,A,I3,A)') solver_name,'*** WARNING ***', &
3050  'Invalid coupling input for patch ',ipatch, &
3051  '. Overriding user input.'
3052 
3053  ppatch%bcCoupled = bc_not_coupled
3054  END IF ! NINT(vals(1))
3055  ELSE
3056  ppatch%bcCoupled = bc_not_coupled
3057  END IF ! defined
3058 #else
3059  IF ( defined(1) .EQV. .true. ) THEN
3060  IF ( nint(vals(1)) /= bc_not_coupled ) THEN
3061  global%warnCounter = global%warnCounter + 1
3062 
3063  WRITE(stdout,'(A,3X,A,1X,A,I3,A)') solver_name,'*** WARNING ***', &
3064  'Invalid coupling input for patch ',ipatch, &
3065  '. Overriding user input.'
3066 
3067  ppatch%bcCoupled = bc_not_coupled
3068  ELSE
3069  ppatch%bcCoupled = bc_not_coupled
3070  END IF ! NINT(vals(1))
3071  ELSE
3072  ppatch%bcCoupled = bc_not_coupled
3073  END IF ! defined(1)
3074 #endif
3075 
3076 ! ------------------------------------------------------------------------------
3077 ! Set patch motion variable
3078 ! ------------------------------------------------------------------------------
3079 
3080  IF ( defined(4) .EQV. .true. ) THEN
3081  ppatch%movePatchDir = vals(4)
3082  ELSE
3083  ppatch%movePatchDir = movepatch_dir_none
3084  END IF ! defined
3085 
3086 ! ------------------------------------------------------------------------------
3087 ! Set patch statistics plotting flag
3088 ! ------------------------------------------------------------------------------
3089 
3090  IF ( defined(5) .EQV. .true. ) THEN
3091  IF ( nint(vals(5)) == 1 ) THEN
3092  ppatch%plotStatsFlag = .true.
3093  ELSE
3094  ppatch%plotStatsFlag = .false.
3095  END IF ! NINT
3096  ELSE
3097  ppatch%plotStatsFlag = .false.
3098  END IF ! defined
3099 
3100 ! ------------------------------------------------------------------------------
3101 ! Set constraint variable
3102 ! ------------------------------------------------------------------------------
3103 
3104  IF ( defined(6) .EQV. .true. ) THEN
3105  IF ( nint(vals(6)) == 1 ) THEN
3106  ppatch%cReconst = constr_weighted
3107  ELSE
3108  ppatch%cReconst = constr_none
3109  END IF ! NINT(vals(6))
3110  ELSE
3111  ppatch%cReconst = constr_none
3112  END IF ! defined
3113  END IF ! pPatch%iPatchGlobal
3114  END DO ! iPatch
3115 
3116 ! ******************************************************************************
3117 ! End
3118 ! ******************************************************************************
3119 
3120  CALL deregisterfunction(global)
3121 
3122  END SUBROUTINE rflu_readbcslipwallsection
3123 
3124 
3125 
3126 
3127 
3128 
3129 
3130 
3131 
3132 
3133 ! ******************************************************************************
3134 !
3135 ! Purpose: Read in user input related to symmetry boundary condition.
3136 !
3137 ! Description: None.
3138 !
3139 ! Input:
3140 ! pRegion Pointer to region data
3141 !
3142 ! Output: None.
3143 !
3144 ! Notes: None.
3145 !
3146 ! ******************************************************************************
3147 
3148  SUBROUTINE rflu_readbcsymmetrysection(pRegion)
3149 
3150  USE modinterfaces, ONLY: readpatchsection
3151 
3152  IMPLICIT NONE
3153 
3154 ! ******************************************************************************
3155 ! Declarations and definitions
3156 ! ******************************************************************************
3157 
3158 ! ==============================================================================
3159 ! Arguments
3160 ! ==============================================================================
3161 
3162  TYPE(t_region), POINTER :: pregion
3163 
3164 ! ==============================================================================
3165 ! Local variables
3166 ! ==============================================================================
3167 
3168  INTEGER, PARAMETER :: nvals_max = 2
3169 
3170  LOGICAL, DIMENSION(NVALS_MAX) :: defined
3171  CHARACTER(10) :: keys(nvals_max)
3172  CHARACTER(256) :: ifilename
3173  CHARACTER(CHRLEN) :: bcname
3174  INTEGER :: distrib,errorflag,ipatch,nvals,ipatchbeg,ipatchend
3175  REAL(RFREAL), DIMENSION(NVALS_MAX) :: vals
3176  TYPE(t_grid) :: grid
3177  TYPE(t_patch), POINTER :: ppatch
3178  TYPE(t_global), POINTER :: global
3179 
3180 ! ******************************************************************************
3181 ! Start
3182 ! ******************************************************************************
3183 
3184  global => pregion%global
3185 
3186  CALL registerfunction(global,'RFLU_ReadBcSymmetrySection',&
3187  'RFLU_ModReadBcInputFile.F90')
3188 
3189 ! ******************************************************************************
3190 ! Specify keywords and search for them
3191 ! ******************************************************************************
3192 
3193  nvals = nvals_max
3194 
3195  keys(1) = 'MVPATCH'
3196  keys(2) = 'SMGRID'
3197 
3198  CALL readpatchsection(global,if_input,nvals,keys,vals,ipatchbeg,ipatchend, &
3199  distrib,ifilename,bcname,defined)
3200 
3201 ! ******************************************************************************
3202 ! Check if specified number of patches exceeds available ones
3203 ! ******************************************************************************
3204 
3205  IF ( ipatchend > global%nPatches ) THEN
3206  CALL errorstop(global,err_patch_range,__line__)
3207  END IF ! iPatchEnd
3208 
3209 ! ******************************************************************************
3210 ! Loop over patches and copy values/distribution to variables
3211 ! ******************************************************************************
3212 
3213  DO ipatch = 1,pregion%grid%nPatches
3214  ppatch => pregion%patches(ipatch)
3215 
3216 ! ==============================================================================
3217 ! Check whether this global patch exists in this region
3218 ! ==============================================================================
3219 
3220  IF ( ppatch%iPatchGlobal >= ipatchbeg .AND. &
3221  ppatch%iPatchGlobal <= ipatchend ) THEN
3222 
3223  ppatch%bcType = bc_symmetry
3224  ppatch%bcName = bcname
3225  ppatch%bcCoupled = bc_not_coupled
3226 
3227  ppatch%iPatchRelated = ipatch
3228 
3229  ppatch%mixt%nData = 0
3230  ppatch%mixt%nSwitches = 0
3231  ppatch%mixt%distrib = bcdat_constant
3232 
3233  ppatch%bcKind = bc_kind_simple ! Value immaterial
3234  ppatch%thrustFlag = .false. ! Value immaterial
3235 
3236  ppatch%spaceOrder = pregion%mixtInput%spaceOrderBFaces ! Value immaterial
3237  ppatch%cReconst = constr_none
3238 
3239 ! TEMPORARY - No longer used, keep for backward compatibility
3240  ppatch%movePatch = .false.
3241  ppatch%smoothGrid = .false.
3242 ! END TEMPORARY
3243 
3244  ALLOCATE(ppatch%mixt%switches(ppatch%mixt%nSwitches), &
3245  stat=errorflag)
3246  global%error = errorflag
3247  IF ( global%error /= err_none ) THEN
3248  CALL errorstop(global,err_allocate,__line__)
3249  END IF ! global
3250 
3251  nullify(ppatch%mixt%vals)
3252  END IF ! pPatch%iPatchGlobal
3253  END DO ! iPatch
3254 
3255 ! ******************************************************************************
3256 ! End
3257 ! ******************************************************************************
3258 
3259  CALL deregisterfunction(global)
3260 
3261  END SUBROUTINE rflu_readbcsymmetrysection
3262 
3263 
3264 
3265 
3266 
3267 
3268 
3269 
3270 
3271 ! ******************************************************************************
3272 !
3273 ! Purpose: Read in user input related to virtual boundary condition.
3274 !
3275 ! Description: None.
3276 !
3277 ! Input:
3278 ! pRegion Pointer to region data
3279 !
3280 ! Output: None.
3281 !
3282 ! Notes: None.
3283 !
3284 ! ******************************************************************************
3285 
3286  SUBROUTINE rflu_readbcvirtualsection(pRegion)
3287 
3288  USE modinterfaces, ONLY: readpatchsection
3289 
3290  IMPLICIT NONE
3291 
3292 ! ******************************************************************************
3293 ! Declarations and definitions
3294 ! ******************************************************************************
3295 
3296 ! ==============================================================================
3297 ! Arguments
3298 ! ==============================================================================
3299 
3300  TYPE(t_region), POINTER :: pregion
3301 
3302 ! ==============================================================================
3303 ! Local variables
3304 ! ==============================================================================
3305 
3306  INTEGER, PARAMETER :: nvals_max = 1
3307 
3308  LOGICAL, DIMENSION(NVALS_MAX) :: defined
3309  CHARACTER(10) :: keys(nvals_max)
3310  CHARACTER(256) :: ifilename
3311  CHARACTER(CHRLEN) :: bcname
3312  INTEGER :: distrib,errorflag,ipatch,nvals,ipatchbeg,ipatchend
3313  REAL(RFREAL), DIMENSION(NVALS_MAX) :: vals
3314  TYPE(t_grid) :: grid
3315  TYPE(t_patch), POINTER :: ppatch
3316  TYPE(t_global), POINTER :: global
3317 
3318 ! ******************************************************************************
3319 ! Start
3320 ! ******************************************************************************
3321 
3322  global => pregion%global
3323 
3324  CALL registerfunction(global,'RFLU_ReadBcVirtualSection',&
3325  'RFLU_ModReadBcInputFile.F90')
3326 
3327 ! ******************************************************************************
3328 ! Specify keywords and search for them
3329 ! ******************************************************************************
3330 
3331  nvals = nvals_max
3332 
3333  keys(1) = 'SMGRID'
3334 
3335  CALL readpatchsection(global,if_input,nvals,keys,vals,ipatchbeg,ipatchend, &
3336  distrib,ifilename,bcname,defined)
3337 
3338 ! ******************************************************************************
3339 ! Check if specified number of patches exceeds available ones
3340 ! ******************************************************************************
3341 
3342  IF ( ipatchend > global%nPatches ) THEN
3343  CALL errorstop(global,err_patch_range,__line__)
3344  END IF ! iPatchEnd
3345 
3346 ! ******************************************************************************
3347 ! Loop over patches and copy values/distribution to variables
3348 ! ******************************************************************************
3349 
3350  DO ipatch = 1,pregion%grid%nPatches
3351  ppatch => pregion%patches(ipatch)
3352 
3353 ! ==============================================================================
3354 ! Check whether this global patch exists in this region
3355 ! ==============================================================================
3356 
3357  IF ( ppatch%iPatchGlobal >= ipatchbeg .AND. &
3358  ppatch%iPatchGlobal <= ipatchend ) THEN
3359  ppatch%bcType = bc_virtual
3360  ppatch%bcName = bcname
3361 
3362  ppatch%bcCoupled = bc_not_coupled
3363  ppatch%movePatchDir = movepatch_dir_none
3364 
3365  ppatch%mixt%nData = 0
3366  ppatch%mixt%nSwitches = 0
3367  ppatch%mixt%distrib = bcdat_constant
3368 
3369  ppatch%bcKind = bc_kind_simple ! Value immaterial
3370  ppatch%thrustFlag = .false. ! Value immaterial
3371 
3372  ppatch%spaceOrder = pregion%mixtInput%spaceOrderBFaces ! Value immaterial
3373  ppatch%cReconst = constr_none
3374  ppatch%plotStatsFlag = .false.
3375 
3376 ! TEMPORARY - No longer used, keep for backward compatibility
3377  ppatch%movePatch = .false.
3378  ppatch%smoothGrid = .false.
3379 ! END TEMPORARY
3380 
3381  nullify(ppatch%mixt%switches)
3382  nullify(ppatch%mixt%vals)
3383  END IF ! pPatch%iPatchGlobal
3384  END DO ! iPatch
3385 
3386 ! ******************************************************************************
3387 ! End
3388 ! ******************************************************************************
3389 
3390  CALL deregisterfunction(global)
3391 
3392  END SUBROUTINE rflu_readbcvirtualsection
3393 
3394 
3395 
3396 
3397 
3398 
3399 
3400 ! ******************************************************************************
3401 ! End
3402 ! ******************************************************************************
3403 
3404 END MODULE rflu_modreadbcinputfile
3405 
3406 
3407 ! ******************************************************************************
3408 !
3409 ! RCS Revision history:
3410 !
3411 ! $Log: RFLU_ModReadBcInputFile.F90,v $
3412 ! Revision 1.27 2008/12/06 08:44:23 mtcampbe
3413 ! Updated license.
3414 !
3415 ! Revision 1.26 2008/11/19 22:17:34 mtcampbe
3416 ! Added Illinois Open Source License/Copyright
3417 !
3418 ! Revision 1.25 2006/10/20 21:19:05 mparmar
3419 ! added reading of THRUSTFLAG and cleaned up reading of NSCBC related keywords
3420 !
3421 ! Revision 1.24 2006/08/19 15:39:12 mparmar
3422 ! Renamed patch variables, added reading of KIND,REFLECT,NSCBCK
3423 !
3424 ! Revision 1.23 2006/08/10 17:19:11 rfiedler
3425 ! Corrected max array size for outflow BC.
3426 !
3427 ! Revision 1.22 2006/08/09 19:19:05 rfiedler
3428 ! Allow COUPLED and MOVEDIR to be specified for far field, inflow, and outflow.
3429 !
3430 ! Revision 1.21 2006/08/08 17:23:35 rfiedler
3431 ! Use MOVEDIR from *.bc to get cnstr_type, not the HDF values.
3432 !
3433 ! Revision 1.20 2006/05/02 17:56:42 haselbac
3434 ! Cosmetics
3435 !
3436 ! Revision 1.19 2006/05/02 17:40:25 fnajjar
3437 ! Added STATS key for outflow bc
3438 !
3439 ! Revision 1.18 2006/04/17 19:55:44 haselbac
3440 ! Bug fix: Added setting of spaceOrder for symmetry and virtual patches
3441 !
3442 ! Revision 1.17 2006/04/15 17:01:39 haselbac
3443 ! Added ORDER and RECONST params
3444 !
3445 ! Revision 1.16 2006/04/07 15:19:20 haselbac
3446 ! Removed tabs
3447 !
3448 ! Revision 1.15 2006/03/25 21:54:38 haselbac
3449 ! Added routines to read input for sype patches
3450 !
3451 ! Revision 1.14 2005/11/10 02:27:58 haselbac
3452 ! Cosmetics only
3453 !
3454 ! Revision 1.13 2005/10/18 02:56:54 haselbac
3455 ! Bug fix: Incorrect setting of bcCoupled for non-GENX computations
3456 !
3457 ! Revision 1.12 2005/10/14 14:07:50 haselbac
3458 ! Significant changes to checks for GENX sims, added GENX support for noslip walls
3459 !
3460 ! Revision 1.11 2005/10/05 16:19:23 haselbac
3461 ! Fixed problems with names longer than 31 chars
3462 !
3463 ! Revision 1.10 2005/10/05 14:04:53 haselbac
3464 ! Split no-slip wall sections, cosmetics
3465 !
3466 ! Revision 1.9 2005/09/23 18:58:03 haselbac
3467 ! Added setting of plotStatsFlag
3468 !
3469 ! Revision 1.8 2005/06/09 20:22:13 haselbac
3470 ! Removed calls to RFLU_CheckMoveGridInput, changed to MOVEDIR keyword
3471 !
3472 ! Revision 1.7 2005/05/04 03:35:18 haselbac
3473 ! Removed setting of pPatch%writeGrid, was not used for some time
3474 !
3475 ! Revision 1.6 2005/04/27 02:11:50 haselbac
3476 ! Added routine to read INFLOW_VELTEMP, made most routines private
3477 !
3478 ! Revision 1.5 2005/03/09 15:05:31 haselbac
3479 ! Added BC_VIRTUAL, some clean-up
3480 !
3481 ! Revision 1.4 2004/12/27 23:29:19 haselbac
3482 ! Added parameter for farfield bc
3483 !
3484 ! Revision 1.3 2004/10/19 19:28:21 haselbac
3485 ! Changed reading of injection boundary input
3486 !
3487 ! Revision 1.2 2004/07/28 15:29:20 jferry
3488 ! created global variable for spec use
3489 !
3490 ! Revision 1.1 2004/07/06 15:14:28 haselbac
3491 ! Initial revision
3492 !
3493 ! ******************************************************************************
3494 
3495 
3496 
3497 
3498 
3499 
3500 
3501 
3502 
3503 
3504 
3505 
3506 
3507 
3508 
3509 
3510 
3511 
3512 
subroutine rflu_readbcoutflowsection(pRegion)
subroutine rflu_readbcinflowveltempsection(pRegion)
CImg< T > & line(const unsigned int y0)
Get a line.
Definition: CImg.h:18421
subroutine registerfunction(global, funName, fileName)
Definition: ModError.F90:449
int status() const
Obtain the status of the attribute.
Definition: Attribute.h:240
subroutine rflu_readbcslipwallsection(pRegion)
subroutine, public rflu_readbcinputfilewrapper(pRegion)
subroutine rflu_readbcvirtualsection(pRegion)
subroutine rflu_readbcfarfsection(pRegion)
subroutine rflu_readbcperiodicsection(pRegion)
subroutine buildfilenameplain(global, dest, ext, fileName)
subroutine readpatchsection(global, fileID, nvals, keys, vals, brbeg, brend, prbeg, prend, distrib, profType, fname, defined)
blockLoc i
Definition: read.cpp:79
subroutine rflu_readbcinputfile(pRegion)
**********************************************************************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
subroutine rflu_readbcnoslipwallheatsect(pRegion)
subroutine rflu_readbcinflowtotangsection(pRegion)
subroutine spec_rflu_readbcinputfile(pRegion)
subroutine rflu_readbcinjectsection(pRegion)
**********************************************************************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 rflu_readbcsymmetrysection(pRegion)
subroutine errorstop(global, errorCode, errorLine, addMessage)
Definition: ModError.F90:483
subroutine rflu_readbcnoslipwalltempsect(pRegion)
subroutine grid(bp)
Definition: setup_py.f90:257
subroutine deregisterfunction(global)
Definition: ModError.F90:469