Rocstar  1.0
Rocstar multiphysics simulation application
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
ModStatsRoutines.F90
Go to the documentation of this file.
1 ! *********************************************************************
2 ! * Rocstar Simulation Suite *
3 ! * Copyright@2015, Illinois Rocstar LLC. All rights reserved. *
4 ! * *
5 ! * Illinois Rocstar LLC *
6 ! * Champaign, IL *
7 ! * www.illinoisrocstar.com *
8 ! * sales@illinoisrocstar.com *
9 ! * *
10 ! * License: See LICENSE file in top level of distribution package or *
11 ! * http://opensource.org/licenses/NCSA *
12 ! *********************************************************************
13 ! *********************************************************************
14 ! * THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, *
15 ! * EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES *
16 ! * OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND *
17 ! * NONINFRINGEMENT. IN NO EVENT SHALL THE CONTRIBUTORS OR *
18 ! * COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER *
19 ! * LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, *
20 ! * Arising FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE *
21 ! * USE OR OTHER DEALINGS WITH THE SOFTWARE. *
22 ! *********************************************************************
23 ! ******************************************************************************
24 !
25 ! Purpose: Suite of statistics routines.
26 !
27 ! Description: None.
28 !
29 ! Notes: None.
30 !
31 ! ******************************************************************************
32 !
33 ! $Id: ModStatsRoutines.F90,v 1.11 2008/12/06 08:44:19 mtcampbe Exp $
34 !
35 ! Copyright: (c) 2004 by the University of Illinois
36 !
37 ! ******************************************************************************
38 
40 
41  USE modglobal, ONLY: t_global
42  USE modparameters
43  USE moddatatypes
44  USE moderror
45  USE moddatastruct, ONLY: t_region
46  USE modgrid, ONLY: t_grid
47  USE modmpi
48 
49 #ifdef PLAG
51 #endif
52 
53  IMPLICIT NONE
54 
55  PRIVATE
56  PUBLIC :: statbuildversionstring, &
57  getstatistics, &
62  statmapping, &
65 
66 ! ******************************************************************************
67 ! Declarations and definitions
68 ! ******************************************************************************
69 
70  CHARACTER(CHRLEN) :: RCSIdentString = &
71  '$RCSfile: ModStatsRoutines.F90,v $ $Revision: 1.11 $'
72 
73 ! ******************************************************************************
74 ! Routines
75 ! ******************************************************************************
76 
77  CONTAINS
78 
79 !******************************************************************************
80 !
81 ! Purpose: Build version string for printing in header.
82 !
83 ! Description: none.
84 !
85 ! Input: none.
86 !
87 ! Output:
88 ! versionString = string containing version number and date.
89 !
90 ! Notes:
91 ! 1. The strings are NOT to be edited by anyone except the developer of
92 ! this physical module.
93 !
94 !******************************************************************************
95 
96 SUBROUTINE statbuildversionstring( versionString )
97 
98  IMPLICIT NONE
99 
100 ! ... parameters
101  CHARACTER(*) :: versionstring
102 
103 ! ... local variables
104  CHARACTER(LEN=2) :: major, minor, patch
105  CHARACTER(CHRLEN) :: date
106 
107 !******************************************************************************
108 ! set strings: DO NOT EDIT UNLESS YOU ARE STATS DEVELOPER
109 
110  major = '1'
111  minor = '0'
112  patch = '0'
113 
114  date = '11/30/04'
115 
116 ! write into string
117 
118  WRITE(versionstring,'(A)') trim(major)//'.'//trim(minor)//'.'//trim(patch)
119  WRITE(versionstring,'(A)') 'Version: '//trim(versionstring)
120  WRITE(versionstring,'(A)') trim(versionstring)//', Date: '//trim(date)
121 
122 END SUBROUTINE statbuildversionstring
123 
124 !******************************************************************************
125 !
126 ! Purpose: calling data sampling routines for time averaged statistics
127 !
128 ! Description: data sampling for time averaged statistics of gas mixture
129 ! and other physical module if desired; in addition
130 ! averaging time interval is integrated
131 !
132 ! Input: regions = data of all regions
133 !
134 ! Output: StatDataSampling and StatTimeAccumulation called
135 !
136 ! Notes: none.
137 !
138 !******************************************************************************
139 
140 SUBROUTINE getstatistics( regions )
141 
142  IMPLICIT NONE
143 
144 ! ... parameters
145  TYPE(t_region), POINTER :: regions(:)
146 
147 ! ... loop variables
148  INTEGER :: ireg
149 
150 ! ... local variables
151  TYPE(t_global), POINTER :: global
152 
153 #ifdef PLAG
154  TYPE(t_region), POINTER :: pregion
155 #endif
156 
157 !******************************************************************************
158 
159  global => regions(1)%global
160 
161  CALL registerfunction( global,'GetStatistics',&
162  'ModStatsRoutines.F90' )
163 
164 ! perform data sampling --------------------------------------------------------
165 
166  IF (global%doStat == active) THEN
167 #ifdef RFLO
168  DO ireg=1,global%nRegions
169  IF (regions(ireg)%procid==global%myProcid .AND. & ! region active and
170  regions(ireg)%active==active) THEN ! on my processor
171 #endif
172 #ifdef RFLU
173  DO ireg=1,global%nRegionsLocal
174 #endif
175  IF (global%mixtNStat>0) CALL statdatasampling( regions(ireg),ftype_mixt )
176 #ifdef TURB
177  IF (global%turbNStat>0) THEN
178  IF ((regions(ireg)%mixtInput%flowModel == flow_navst) .AND. &
179  (regions(ireg)%mixtInput%turbModel /= turb_model_none)) THEN
180  CALL statdatasampling( regions(ireg),ftype_turb )
181  ENDIF
182  ENDIF
183 #endif
184 #ifdef PLAG
185  IF ( global%plagUsed .EQV. .true. ) THEN
186  pregion => regions(ireg)
187 
188  CALL plag_calceulerianfield( pregion )
189  IF ( global%plagNStat>0 ) &
190  CALL statdatasampling( regions(ireg),ftype_plag )
191  ENDIF ! plagUsed
192 #endif
193 #ifdef RFLO
194  ENDIF
195 #endif
196 
197  ENDDO
198  CALL stattimeaccumulation( global )
199  ENDIF
200 
201 ! finalize --------------------------------------------------------------------
202 
203  CALL deregisterfunction( global )
204 
205 END SUBROUTINE getstatistics
206 
207 !******************************************************************************
208 !
209 ! Purpose: initiation of time averaged statistics
210 !
211 ! Description: initiation proceeds for gas mixture and other physical
212 ! module if desired; it is initiated by zero for new
213 ! time averaging and by old values for restarting from
214 ! the previous process
215 !
216 ! Input: regions = data of all regions
217 !
218 ! Output: regions%levels%mixt%tav = time averaged mixture variables
219 ! regions%levels%turb%tav = time averaged TURB variables
220 !
221 ! Notes: none.
222 !
223 !******************************************************************************
224 
225 SUBROUTINE initstatistics( regions )
226 
227 #ifdef RFLO
228  USE modinterfaces, ONLY : rflo_readstat
229 #ifdef PLAG
231 #endif
232 #endif
233 #ifdef RFLU
234  USE modinterfaces, ONLY : rflu_readstat
235 #ifdef GENX
237 #endif
238 #endif
239  IMPLICIT NONE
240 
241 ! ... parameters
242  TYPE(t_region), POINTER :: regions(:)
243 
244 ! ... loop variables
245  INTEGER :: ireg
246 
247 ! ... local variables
248  INTEGER :: ilev
249 
250  TYPE(t_global), POINTER :: global
251 #ifdef RFLU
252  TYPE(t_region), POINTER :: pregion
253 #endif
254 
255 !******************************************************************************
256 
257  global => regions(1)%global
258 
259  CALL registerfunction( global,'InitStatistics',&
260  'ModStatsRoutines.F90' )
261 
262 ! check if the flow is unsteady -----------------------------------------------
263 
264  IF (global%flowType == flow_steady) THEN
265  global%doStat = off
266  ENDIF
267 
268 ! initialization of time averaging statistics ---------------------------------
269 
270  global%statBc = 0
271 
272  IF (global%doStat == active) THEN
273 
274 ! - restart from previous statistics
275 
276  IF (global%reStat == active) THEN
277 
278  IF (global%myProcid==masterproc .AND. global%verbLevel/=verbose_none) &
279  WRITE(stdout,'(A)') solver_name//' Restart statistics ...'
280 #ifndef GENX
281 #ifdef RFLO
282  CALL rflo_readstat( regions )
283 #ifdef PLAG
284  IF ( global%plagUsed .EQV. .true. ) &
285  CALL plag_rflo_readstat( regions )
286 #endif
287 #endif
288 #ifdef RFLU
289  DO ireg=1,global%nRegionsLocal
290  CALL rflu_readstat( regions(ireg) )
291  ENDDO
292 #endif
293 
294 #else
295 
296 #ifdef RFLU
297  DO ireg=1,global%nRegionsLocal
298  pregion => regions(ireg)
299  CALL stat_rflu_genxgetdata( pregion )
300  ENDDO
301 #endif
302 #endif
303 
304 ! - initialize new statistics
305 
306  ELSE
307 
308  IF (global%myProcid==masterproc .AND. global%verbLevel/=verbose_none) &
309  WRITE(stdout,'(A)') solver_name//' Start new statistics ...'
310  global%integrTime = 0._rfreal
311 #ifdef RFLO
312  DO ireg=1,global%nRegions
313  IF (regions(ireg)%procid==global%myProcid .AND. & ! region active and
314  regions(ireg)%active==active) THEN ! on my processor
315  ilev = regions(ireg)%currLevel
316  IF (global%mixtNStat > 0) THEN
317  regions(ireg)%levels(ilev)%mixt%tav = 0._rfreal
318  ENDIF
319 #ifdef TURB
320  IF ((regions(ireg)%mixtInput%flowModel == flow_navst) .AND. &
321  (regions(ireg)%mixtInput%turbModel /= turb_model_none) .AND. &
322  (global%turbNStat > 0)) THEN
323  regions(ireg)%levels(ilev)%turb%tav = 0._rfreal
324  ENDIF
325 #endif
326 #ifdef PLAG
327  IF ((global%plagUsed .EQV. .true.) .AND. &
328  (global%plagNStat > 0)) THEN
329  regions(ireg)%levels(ilev)%plag%tav = 0._rfreal
330  ENDIF
331 #endif
332  ENDIF ! region on this processor and active
333  ENDDO ! iReg
334 #endif
335 #ifdef RFLU
336  DO ireg=1,global%nRegionsLocal
337  IF (global%mixtNStat > 0) THEN
338  regions(ireg)%mixt%tav = 0._rfreal
339  ENDIF
340 #ifdef TURB
341  IF ((regions(ireg)%mixtInput%flowModel == flow_navst) .AND. &
342  (regions(ireg)%mixtInput%turbModel /= turb_model_none) .AND. &
343  (global%turbNStat > 0)) THEN
344  regions(ireg)%turb%tav = 0._rfreal
345  ENDIF
346 #endif
347 #ifdef PLAG
348  IF ((global%plagUsed .EQV. .true.) .AND. &
349  (global%plagNStat > 0)) THEN
350  regions(ireg)%plag%tav = 0._rfreal
351  ENDIF
352 #endif
353  ENDDO ! iReg
354 #endif
355 
356  ENDIF
357  ENDIF
358 
359 ! finalize --------------------------------------------------------------------
360 
361  CALL deregisterfunction( global )
362 
363 END SUBROUTINE initstatistics
364 
365 !******************************************************************************
366 !
367 ! Purpose: accumulate selected instantaneous quantities in time
368 !
369 ! Description: this file containes two routines:
370 ! 1st routine, StatDataAccumulation1, for first moment variables
371 ! 2nd routine, StatDataAccumulation2, for second moment variables
372 !
373 ! Input 1st routine: ijkbeg, ijkend = begin and end cell indices
374 ! id = index of variable var
375 ! idtav = index of time-accumulated quantity
376 ! dTime = time step
377 ! var = variable to be time accumulated
378 !
379 ! Input 2nd routine: ijkbeg, ijkend = begin and end cell indices
380 ! id1 = index of first component variable
381 ! id2 = index of second component variable
382 ! idtav = index of time-accumulated quantity
383 ! dTime = time step
384 ! var1 = 1st component of 2nd moment variable
385 ! var2 = 2nd component of 2nd moment variable
386 !
387 ! Output of 1st and 2nd routine: qavg = quantity accumulated in time
388 !
389 ! Notes: none.
390 !
391 !******************************************************************************
392 
393 SUBROUTINE statdataaccumulation1( ijkbeg,ijkend,id,idtav,dTime,var,qavg )
394 
395  IMPLICIT NONE
396 
397 ! ... parameters
398  INTEGER :: ijkbeg, ijkend, id, idtav
399  REAL(RFREAL) :: dtime
400  REAL(RFREAL), POINTER :: var(:,:), qavg(:,:)
401 
402 ! ... loop variables
403  INTEGER :: ijk
404 
405 !******************************************************************************
406 
407  DO ijk=ijkbeg,ijkend
408  qavg(idtav,ijk) = qavg(idtav,ijk) + dtime*var(id,ijk)
409  ENDDO
410 
411 END SUBROUTINE statdataaccumulation1
412 
413 ! #############################################################################
414 
415 SUBROUTINE statdataaccumulation2( ijkbeg,ijkend,id1,id2,idtav, &
416  dtime,var1,var2,qavg )
417 
418  IMPLICIT NONE
419 
420 ! ... parameters
421  INTEGER :: ijkbeg, ijkend, id1, id2, idtav
422  REAL(RFREAL) :: dtime
423  REAL(RFREAL), POINTER :: var1(:,:), var2(:,:), qavg(:,:)
424 
425 ! ... loop variables
426  INTEGER :: ijk
427 
428 !******************************************************************************
429 
430  DO ijk=ijkbeg,ijkend
431  qavg(idtav,ijk) = qavg(idtav,ijk) + dtime*var1(id1,ijk)*var2(id2,ijk)
432  ENDDO
433 
434 END SUBROUTINE statdataaccumulation2
435 
436 !******************************************************************************
437 !
438 ! Purpose: sorting variables to be time averaged
439 !
440 ! Description: sorting procedure based on selection taken by user
441 ! stored in statId and mapped into statCode.
442 !
443 ! Input: region = data of current region
444 ! fluidType = mixture, turb, plag, etc
445 ! cv, dv, tv, gv = variables to be time averaged
446 ! statCode = mapping identifiers
447 !
448 ! Output: tav = quantities accumulated in time
449 !
450 ! Notes: none.
451 !
452 !******************************************************************************
453 
454 SUBROUTINE statdatasampling( region,fluidType )
455 
456 #ifdef RFLO
458 
459 #include "Indexing.h"
460 #endif
461  IMPLICIT NONE
462 
463 ! ... parameters
464  TYPE(t_region) :: region
465  INTEGER :: fluidtype
466 
467 ! ... loop variables
468  INTEGER :: l
469 
470 ! ... local variables
471  INTEGER :: ilev, ioff, ijoff
472  INTEGER :: idcbeg, jdcbeg, kdcbeg, idcend, jdcend, kdcend, ijkbeg, ijkend
473  INTEGER :: nstat, id1, id2
474  INTEGER, POINTER :: statcode(:,:,:)
475 
476  REAL(RFREAL), POINTER :: cv(:,:),dv(:,:),tv(:,:),gv(:,:),ev(:,:),tav(:,:)
477  REAL(RFREAL), POINTER :: sv(:,:),st(:,:)
478  REAL(RFREAL), POINTER :: var1(:,:),var2(:,:)
479 
480 !******************************************************************************
481 
482  CALL registerfunction( region%global,'StatDataSampling',&
483  'ModStatsRoutines.F90' )
484 
485 ! get dimensions and pointers -------------------------------------------------
486 
487 #ifdef RFLO
488  ilev = region%currLevel
489 #endif
490 
491  IF (fluidtype == ftype_mixt) THEN
492  nstat = region%global%mixtNStat
493  statcode => region%global%mixtStatCode
494 #ifdef RFLO
495  cv => region%levels(ilev)%mixt%cv
496  dv => region%levels(ilev)%mixt%dv
497  tv => region%levels(ilev)%mixt%tv
498  gv => region%levels(ilev)%mixt%gv
499  tav => region%levels(ilev)%mixt%tav
500 #endif
501 #ifdef RFLU
502  cv => region%mixt%cv
503  dv => region%mixt%dv
504  tv => region%mixt%tv
505  gv => region%mixt%gv
506  tav => region%mixt%tav
507 #endif
508  ELSEIF (fluidtype == ftype_turb) THEN
509 #ifdef TURB
510  nstat = region%global%turbNStat
511  statcode => region%global%turbStatCode
512 #ifdef RFLO
513  tv => region%levels(ilev)%mixt%tv
514  dv => region%levels(ilev)%turb%dv
515  sv => region%levels(ilev)%turb%sv
516  st => region%levels(ilev)%turb%st
517  tav => region%levels(ilev)%turb%tav
518 #endif
519 #ifdef RFLU
520  tv => region%mixt%tv
521  dv => region%turb%dv
522  sv => region%turb%sv
523  st => region%turb%st
524  tav => region%turb%tav
525 #endif
526 #endif
527  ELSEIF (fluidtype == ftype_plag) THEN
528 #ifdef PLAG
529  nstat = region%global%plagNStat
530  statcode => region%global%plagStatCode
531 #ifdef RFLO
532  ev => region%levels(ilev)%plag%ev
533  tav => region%levels(ilev)%plag%tav
534 #endif
535 #ifdef RFLU
536  ev => region%plag%ev
537  tav => region%plag%tav
538 #endif
539 #endif
540  ELSEIF (fluidtype == ftype_peul) THEN
541 #ifdef PEUL
542  nstat = region%global%peulNStat
543  statcode => region%global%peulStatCode
544 #ifdef RFLO
545 ! cv => region%levels(iLev)%peul%cv
546 ! dv => region%levels(iLev)%peul%dv
547 ! tav => region%levels(iLev)%peul%tav
548 #endif
549 #ifdef RFLU
550 ! cv => region%peul%cv
551 ! dv => region%peul%dv
552 ! tav => region%peul%tav
553 #endif
554 #endif
555  ENDIF
556 
557 #ifdef RFLO
558  CALL rflo_getdimensdummy( region,ilev,idcbeg,idcend, &
559  jdcbeg,jdcend,kdcbeg,kdcend )
560  CALL rflo_getcelloffset( region,ilev,ioff,ijoff )
561  ijkbeg = indijk(idcbeg,jdcbeg,kdcbeg,ioff,ijoff)
562  ijkend = indijk(idcend,jdcend,kdcend,ioff,ijoff)
563 #endif
564 #ifdef RFLU
565  ijkbeg = 1
566  ijkend = region%grid%nCells
567 #endif
568 
569 ! Quantities to be time-averaged is determined from the index selected by user.
570 ! Data accumulation proceeds afterwards for each quantity.
571 
572  DO l=1,nstat
573 
574  IF ((statcode(1,1,l)==stat_none).AND.(statcode(2,1,l)==stat_none)) &
575  goto 999
576 
577  IF (statcode(1,1,l)==stat_cv) THEN
578  var1 => cv
579  ELSEIF (statcode(1,1,l)==stat_dv) THEN
580  var1 => dv
581  ELSEIF (statcode(1,1,l)==stat_tv) THEN
582  var1 => tv
583  ELSEIF (statcode(1,1,l)==stat_gv) THEN
584  var1 => gv
585  ELSEIF (statcode(1,1,l)==stat_sv) THEN
586  var1 => sv
587  ELSEIF (statcode(1,1,l)==stat_st) THEN
588  var1 => st
589  ELSEIF (statcode(1,1,l)==stat_plagev) THEN
590  var1 => ev
591  ENDIF
592 
593  IF (statcode(2,1,l)==stat_cv) THEN
594  var2 => cv
595  ELSEIF (statcode(2,1,l)==stat_dv) THEN
596  var2 => dv
597  ELSEIF (statcode(2,1,l)==stat_tv) THEN
598  var2 => tv
599  ELSEIF (statcode(2,1,l)==stat_gv) THEN
600  var2 => gv
601  ELSEIF (statcode(2,1,l)==stat_sv) THEN
602  var2 => sv
603  ELSEIF (statcode(2,1,l)==stat_st) THEN
604  var2 => st
605  ELSEIF (statcode(2,1,l)==stat_plagev) THEN
606  var2 => ev
607  ENDIF
608 
609  id1 = statcode(1,2,l)
610  id2 = statcode(2,2,l)
611 
612  IF (statcode(1,1,l)==stat_none) THEN
613  CALL statdataaccumulation1( ijkbeg,ijkend,id2,l, &
614  region%global%dtMin,var2,tav )
615  ELSEIF (statcode(2,1,l)==stat_none) THEN
616  CALL statdataaccumulation1( ijkbeg,ijkend,id1,l, &
617  region%global%dtMin,var1,tav )
618  ELSE
619  CALL statdataaccumulation2( ijkbeg,ijkend,id1,id2,l, &
620  region%global%dtMin,var1,var2,tav )
621  ENDIF
622 
623  ENDDO
624 
625 ! finalize --------------------------------------------------------------------
626 
627 999 CONTINUE
628 
629  CALL deregisterfunction( region%global )
630 
631 END SUBROUTINE statdatasampling
632 
633 !******************************************************************************
634 !
635 ! Purpose: mapping from mixture and physical module ID to statistics ID
636 !
637 ! Description: mapping based on parameter mixtStatId, turbStatId, etc
638 ! input by user
639 !
640 ! Input: global%mixtStatId : mixture statistics ID from user input
641 ! global%turbStatId : TURB statistics ID from user input
642 !
643 ! Output: global%mixtStatCode : mapped mixture statistics ID
644 ! global%turbStatCode : mapped TURB statistics ID
645 !
646 ! Notes: none.
647 !
648 !******************************************************************************
649 
650 SUBROUTINE statmapping( global )
651 
652 #ifdef GENX
654 #endif
655 #ifdef TURB
657 #endif
658 #ifdef PLAG
660 #endif
661 #ifdef PEUL
662 ! USE ModInterfacesEulerian, ONLY : PEUL_StatMapping
663 #endif
664  IMPLICIT NONE
665 
666 ! ... parameters
667  TYPE(t_global), POINTER :: global
668 
669 ! ... loop variables
670  INTEGER :: l, n
671 
672 ! ... local variables
673 #ifdef GENX
674  CHARACTER(CHRLEN), POINTER :: statname(:,:,:)
675 #endif
676  INTEGER :: errorflag
677  INTEGER, POINTER :: statid(:,:), statcode(:,:,:)
678 
679 !******************************************************************************
680 
681  CALL registerfunction( global,'StatMapping',&
682  'ModStatsRoutines.F90' )
683 
684 ! allocate mixture variables and set pointers ---------------------------------
685 
686  IF (global%mixtNStat <= 0) goto 111
687 
688  ALLOCATE( global%mixtStatCode(2,2,global%mixtNStat),stat=errorflag )
689  global%error = errorflag
690  IF (global%error /= 0) CALL errorstop( global,err_allocate,__line__ )
691 
692  statid => global%mixtStatId
693  statcode => global%mixtStatCode
694 
695 #ifdef GENX
696  ALLOCATE( global%mixtStatNm(2,2,global%mixtNStat),stat=errorflag )
697  global%error = errorflag
698  IF (global%error /= 0) CALL errorstop( global,err_allocate,__line__ )
699 
700  statname => global%mixtStatNm
701 #endif
702 
703 ! set mixture mapping ---------------------------------------------------------
704 
705  DO l=1,global%mixtNStat
706  DO n=1,2
707  IF (statid(n,l)==0) THEN
708  statcode(n,:,l) = stat_none
709  ELSE IF (statid(n,l)==1) THEN
710  statcode(n,1,l) = stat_cv
711  statcode(n,2,l) = cv_mixt_dens
712 #ifdef GENX
713  statname(n,1,l) = 'rho'
714  statname(n,2,l) = 'kg/m^3'
715 #endif
716  ELSE IF (statid(n,l)==2) THEN
717 #ifdef RFLO
718  statcode(n,1,l) = stat_dv
719  statcode(n,2,l) = dv_mixt_uvel
720 #endif
721 #ifdef RFLU
722  statcode(n,1,l) = stat_cv
723  statcode(n,2,l) = cv_mixt_xvel
724 #endif
725 #ifdef GENX
726  statname(n,1,l) = 'u'
727  statname(n,2,l) = 'm/s'
728 #endif
729  ELSE IF (statid(n,l)==3) THEN
730 #ifdef RFLO
731  statcode(n,1,l) = stat_dv
732  statcode(n,2,l) = dv_mixt_vvel
733 #endif
734 #ifdef RFLU
735  statcode(n,1,l) = stat_cv
736  statcode(n,2,l) = cv_mixt_yvel
737 #endif
738 #ifdef GENX
739  statname(n,1,l) = 'v'
740  statname(n,2,l) = 'm/s'
741 #endif
742  ELSE IF (statid(n,l)==4) THEN
743 #ifdef RFLO
744  statcode(n,1,l) = stat_dv
745  statcode(n,2,l) = dv_mixt_wvel
746 #endif
747 #ifdef RFLU
748  statcode(n,1,l) = stat_cv
749  statcode(n,2,l) = cv_mixt_zvel
750 #endif
751 #ifdef GENX
752  statname(n,1,l) = 'w'
753  statname(n,2,l) = 'm/s'
754 #endif
755  ELSE IF (statid(n,l)==5) THEN
756  statcode(n,1,l) = stat_dv
757  statcode(n,2,l) = dv_mixt_temp
758 #ifdef GENX
759  statname(n,1,l) = 'T'
760  statname(n,2,l) = 'K'
761 #endif
762  ELSE IF (statid(n,l)==6) THEN
763  statcode(n,1,l) = stat_dv
764  statcode(n,2,l) = dv_mixt_pres
765 #ifdef GENX
766  statname(n,1,l) = 'p'
767  statname(n,2,l) = 'N/m^2'
768 #endif
769  ELSE IF (statid(n,l)==7) THEN
770  statcode(n,1,l) = stat_dv
771  statcode(n,2,l) = dv_mixt_soun
772 #ifdef GENX
773  statname(n,1,l) = 'c'
774  statname(n,2,l) = 'm/s'
775 #endif
776  ELSE IF (statid(n,l)==8) THEN
777  statcode(n,1,l) = stat_tv
778  statcode(n,2,l) = tv_mixt_muel
779 #ifdef GENX
780  statname(n,1,l) = 'mul'
781  statname(n,2,l) = 'kg/ms'
782 #endif
783  ELSE IF (statid(n,l)==9) THEN
784  statcode(n,1,l) = stat_tv
785  statcode(n,2,l) = tv_mixt_tcol
786 #ifdef GENX
787  statname(n,1,l) = 'tcol'
788  statname(n,2,l) = 'kg m/Ks^3'
789 #endif
790  ELSE
791  CALL errorstop( global,err_stats_indexing,__line__, &
792  'mixture index out of range.' )
793  ENDIF
794  ENDDO
795  ENDDO
796 
797 #ifdef GENX
798 ! defined names and units of mixture statistics
799 
800  CALL genxstatnaming( global, ftype_mixt )
801 #endif
802 
803 111 CONTINUE
804 
805 #ifdef TURB
806 ! allocate TURB variables and set pointers ---------------------------------
807 
808  IF (global%turbNStat <= 0) goto 222
809 
810 ! set TURB mapping ---------------------------------------------------------
811 
812  CALL turb_statmapping( global )
813 
814 222 CONTINUE
815 #endif
816 
817 #ifdef PLAG
818 ! allocate PLAG variables and set pointers ---------------------------------
819 
820  IF (global%plagNStat <= 0) goto 333
821 
822 ! set PLAG mapping ---------------------------------------------------------
823 
824  CALL plag_statmapping( global )
825 
826 333 CONTINUE
827 #endif
828 
829 #ifdef PEUL
830 ! allocate PEUL variables and set pointers ---------------------------------
831 
832  IF (global%peulNStat <= 0) goto 444
833 
834 ! set PEUL mapping ---------------------------------------------------------
835 
836 ! CALL PEUL_StatMapping( global )
837 
838 444 CONTINUE
839 #endif
840 
841 #ifdef RFLO
842 ! check with regard to inlet turbulence recycling -----------------------------
843 ! stats id 01-06 must exist and lined up in the same order
844 
845  IF (global%infloNijk < nijk_inflow_init) THEN
846  DO l=1,global%mixtNStat
847  IF (statid(1,l)==0) THEN
848  IF (statid(2,l) /= l) THEN
849  CALL errorstop( global,err_stats_indexing,__line__, &
850  'For recycturb inflow, set stats Id 01-06 in the given order.' )
851  ENDIF
852  ENDIF
853  ENDDO
854  ENDIF
855 #endif
856 
857 ! finalize --------------------------------------------------------------------
858 
859  CALL deregisterfunction( global )
860 
861 END SUBROUTINE statmapping
862 
863 !******************************************************************************
864 !
865 ! Purpose: accumulation of time during time averaging process
866 !
867 ! Description: time integration proceeds from STARTTIME to MAXTIME set by user
868 ! if statistics RESTART (global%reStat) active, the process is
869 ! continuation from previous process
870 !
871 ! Input: global%dtMin = global minimum time advancement.
872 !
873 ! Output: global%integrTime = accumulated time.
874 !
875 ! Notes: none.
876 !
877 !******************************************************************************
878 
879 SUBROUTINE stattimeaccumulation( global )
880 
881  IMPLICIT NONE
882 
883 ! ... parameters
884  TYPE(t_global), POINTER :: global
885 
886 ! ... local variables
887 
888 !******************************************************************************
889 
890  CALL registerfunction( global,'StatTimeAccumulation',&
891  'ModStatsRoutines.F90' )
892 
893 ! accumulate time steps used in time-weighted averaging process
894 
895  global%integrTime = global%integrTime + global%dtMin
896 
897 ! finalize --------------------------------------------------------------------
898 
899  CALL deregisterfunction( global )
900 
901 END SUBROUTINE stattimeaccumulation
902 
903 !******************************************************************************
904 !
905 ! Purpose: update bc and write time averaged solution for all active physical
906 ! modules
907 !
908 ! Description: none.
909 !
910 ! Input: regions = tav of all physical modules in all regions
911 !
912 ! Output: to file
913 !
914 ! Notes: none.
915 !
916 !******************************************************************************
917 !
918 ! $Id: ModStatsRoutines.F90,v 1.11 2008/12/06 08:44:19 mtcampbe Exp $
919 !
920 ! Copyright: (c) 2001 by the University of Illinois
921 !
922 !******************************************************************************
923 
924 SUBROUTINE statwritemp( regions )
925 
926  USE moddatatypes
927  USE moddatastruct, ONLY : t_region
928  USE modglobal, ONLY : t_global
929 #ifdef RFLO
930  USE modinterfaces, ONLY : rflo_writestat
932 #ifdef PLAG
935 #endif
936 #endif
937  USE moderror
938  USE modparameters
939  IMPLICIT NONE
940 
941 #ifdef RFLO
942 #include "Indexing.h"
943 #endif
944 
945 ! ... parameters
946  TYPE(t_region), POINTER :: regions(:)
947 
948 ! ... loop variables
949 
950 ! ... local variables
951 
952  TYPE(t_global), POINTER :: global
953 
954 !******************************************************************************
955 
956  global => regions(1)%global
957 
958  CALL registerfunction( global,'StatWriteMP',&
959  'ModStatsRoutines.F90' )
960 
961 ! start -----------------------------------------------------------------------
962 
963 #ifdef RFLO
964 #ifdef PLAG
965  CALL plag_rflo_commstatbuffwrapper( regions )
966 #endif
967  CALL rflo_statboundaryconditionsset( regions )
968 
969  CALL rflo_writestat( regions )
970 #ifdef PLAG
971  CALL plag_rflo_writestat( regions )
972 #endif
973 #endif
974 
975 ! finalize --------------------------------------------------------------------
976 
977  CALL deregisterfunction( global )
978 
979 END SUBROUTINE statwritemp
980 
981 ! ******************************************************************************
982 ! End
983 ! ******************************************************************************
984 
985 END MODULE modstatsroutines
986 
987 ! ******************************************************************************
988 !
989 ! RCS Revision history:
990 !
991 ! $Log: ModStatsRoutines.F90,v $
992 ! Revision 1.11 2008/12/06 08:44:19 mtcampbe
993 ! Updated license.
994 !
995 ! Revision 1.10 2008/11/19 22:17:30 mtcampbe
996 ! Added Illinois Open Source License/Copyright
997 !
998 ! Revision 1.9 2006/01/10 05:02:34 wasistho
999 ! Get statistics Genx data in RFLU
1000 !
1001 ! Revision 1.8 2005/12/20 20:42:39 wasistho
1002 ! added ifdef RFLO around kernel using global%Nijk
1003 !
1004 ! Revision 1.7 2005/12/01 09:00:10 wasistho
1005 ! sanity check stats Id with inlet turbulence
1006 !
1007 ! Revision 1.6 2005/06/16 03:52:18 wasistho
1008 ! activated RFLO_ModStatsBc
1009 !
1010 ! Revision 1.5 2005/05/21 07:07:50 wasistho
1011 ! backout RFLO_ModStatsBoundaryConditions temporarily
1012 !
1013 ! Revision 1.4 2005/05/21 01:42:47 wasistho
1014 ! added statWriteMP
1015 !
1016 ! Revision 1.3 2005/01/11 01:28:33 wasistho
1017 ! fixed bugs, PLAG data sampling was outside regions loop
1018 !
1019 ! Revision 1.2 2005/01/08 20:36:44 fnajjar
1020 ! Added statistics infrastructure for PLAG and activated datastructure appropriately
1021 !
1022 ! Revision 1.1 2004/12/29 23:28:21 wasistho
1023 ! moved ModStatisticsRoutines from libfloflu to modfloflu
1024 !
1025 ! Revision 1.1 2004/12/28 20:30:00 wasistho
1026 ! moved statistics routines into module ModStatsRoutines
1027 !
1028 !
1029 ! ******************************************************************************
1030 
1031 
1032 
1033 
1034 
1035 
1036 
1037 
1038 
1039 
1040 
1041 
**********************************************************************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 idcend
subroutine, public statbuildversionstring(versionString)
subroutine, public plag_rflo_commstatbuffwrapper(regions)
subroutine, public stattimeaccumulation(global)
subroutine, public plag_calceulerianfield(pRegion)
subroutine, public initstatistics(regions)
subroutine genxstatnaming(global, fluidType)
subroutine registerfunction(global, funName, fileName)
Definition: ModError.F90:449
subroutine, public statdataaccumulation1(ijkbeg, ijkend, id, idtav, dTime, var, qavg)
subroutine rflo_writestat(regions)
subroutine, public statdatasampling(region, fluidType)
subroutine plag_statmapping(global)
subroutine, public rflo_statboundaryconditionsset(regions)
subroutine, public stat_rflu_genxgetdata(pRegion)
subroutine rflo_readstat(regions)
subroutine rflo_getdimensdummy(region, iLev, idcbeg, idcend, jdcbeg, jdcend, kdcbeg, kdcend)
Definition: patch.h:74
**********************************************************************Rocstar Simulation Suite Illinois Rocstar LLC All rights reserved ****Illinois Rocstar LLC IL **www illinoisrocstar com **sales illinoisrocstar com WITHOUT WARRANTY OF ANY **EXPRESS OR INCLUDING BUT NOT LIMITED TO THE WARRANTIES **OF FITNESS FOR A PARTICULAR PURPOSE AND **NONINFRINGEMENT IN NO EVENT SHALL THE CONTRIBUTORS OR **COPYRIGHT HOLDERS BE LIABLE FOR ANY DAMAGES OR OTHER WHETHER IN AN ACTION OF TORT OR **Arising OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE **USE OR OTHER DEALINGS WITH THE SOFTWARE **********************************************************************INTERFACE SUBROUTINE kdcbeg
subroutine, public getstatistics(regions)
subroutine, public statmapping(global)
subroutine rflo_getcelloffset(region, iLev, iCellOffset, ijCellOffset)
subroutine, public statwritemp(regions)
**********************************************************************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 idcbeg
const NT & n
subroutine rflu_readstat(region)
**********************************************************************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 jdcend
unsigned long id(const Leda_like_handle &x)
Definition: Handle.h:107
**********************************************************************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 jdcbeg
subroutine errorstop(global, errorCode, errorLine, addMessage)
Definition: ModError.F90:483
subroutine, public plag_rflo_readstat(regions)
subroutine, public statdataaccumulation2(ijkbeg, ijkend, id1, id2, idtav, dTime, var1, var2, qavg)
subroutine, public plag_rflo_writestat(regions)
subroutine deregisterfunction(global)
Definition: ModError.F90:469
subroutine turb_statmapping(global)