Rocstar  1.0
Rocstar multiphysics simulation application
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
RFLU_ModPlottingVars.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 for handling plotting variables.
26 !
27 ! Description: None.
28 !
29 ! Notes: None.
30 !
31 ! ******************************************************************************
32 !
33 ! $Id: RFLU_ModPlottingVars.F90,v 1.15 2008/12/06 08:45:06 mtcampbe Exp $
34 !
35 ! Copyright: (c) 2005 by the University of Illinois
36 !
37 ! ******************************************************************************
38 
40 
41  USE moddatatypes
42  USE modparameters
43  USE moderror
44  USE modglobal, ONLY: t_global
45  USE modgrid, ONLY: t_grid
46  USE modbndpatch, ONLY: t_patch
47  USE moddatastruct, ONLY: t_region
48 
50 
51  IMPLICIT NONE
52 
53 ! ******************************************************************************
54 ! Definitions and declarations
55 ! ******************************************************************************
56 
57  PRIVATE
58 
59 ! ==============================================================================
60 ! Private data
61 ! ==============================================================================
62 
63  CHARACTER(CHRLEN), PARAMETER, PRIVATE :: &
64  RCSIdentString = '$RCSfile: RFLU_ModPlottingVars.F90,v $ $Revision: 1.15 $'
65 
66 ! ==============================================================================
67 ! Public data
68 ! ==============================================================================
69 
70 
71 ! ==============================================================================
72 ! Public procedures
73 ! ==============================================================================
74 
75  PUBLIC :: rflu_buildplottingvarmaps, &
86 
87 ! ******************************************************************************
88 ! Subroutines and functions
89 ! ******************************************************************************
90 
91  CONTAINS
92 
93 
94 
95 
96 
97 
98 ! ******************************************************************************
99 !
100 ! Purpose: Build plotting variable maps.
101 !
102 ! Description: None.
103 !
104 ! Input:
105 ! pRegion Pointer to region
106 !
107 ! Output: None.
108 !
109 ! Notes: None.
110 !
111 ! ******************************************************************************
112 
113 SUBROUTINE rflu_buildplottingvarmaps(pRegion)
114 
115  IMPLICIT NONE
116 
117 ! ******************************************************************************
118 ! Declarations and definitions
119 ! ******************************************************************************
120 
121 ! ==============================================================================
122 ! Arguments
123 ! ==============================================================================
124 
125  TYPE(t_region), POINTER :: pregion
126 
127 ! ==============================================================================
128 ! Locals
129 ! ==============================================================================
130 
131  INTEGER :: errorflag,ipv,ipv2,npv
132  TYPE(t_global), POINTER :: global
133 
134 ! ******************************************************************************
135 ! Start
136 ! ******************************************************************************
137 
138  global => pregion%global
139 
140  CALL registerfunction(global,'RFLU_BuildPlottingVarMaps', &
141  'RFLU_ModPlottingVars.F90')
142 
143  IF ( global%verbLevel > verbose_low ) THEN
144  WRITE(stdout,'(A,1X,A)') solver_name,'Building plotting variable maps...'
145  END IF ! global%verbLevel
146 
147 ! ******************************************************************************
148 ! Build map
149 ! ******************************************************************************
150 
151  npv = 0
152 
153  DO ipv = 1,pv_xxxx_nvar
154  ipv2 = pregion%plot%pv2pvi(ipv)
155 
156  IF ( ipv2 /= crazy_value_int ) THEN
157  npv = npv + 1
158 
159  pregion%plot%pvi2pv(ipv2) = ipv
160  END IF ! iPv2
161  END DO ! iPv
162 
163  IF ( npv /= pregion%plot%nPv ) THEN
164 ! TEMPORARY
165  WRITE(*,*) 'ERROR!!!'
166  stop
167 ! END TEMPORARY
168  END IF ! nPv
169 
170 ! ******************************************************************************
171 ! End
172 ! ******************************************************************************
173 
174  IF ( global%verbLevel > verbose_low ) THEN
175  WRITE(stdout,'(A,1X,A)') solver_name,'Building plotting variable maps done.'
176  END IF ! global%verbLevel
177 
178  CALL deregisterfunction(global)
179 
180 END SUBROUTINE rflu_buildplottingvarmaps
181 
182 
183 
184 
185 
186 ! ******************************************************************************
187 !
188 ! Purpose: Set plotting variable names.
189 !
190 ! Description: None.
191 !
192 ! Input:
193 ! pRegion Pointer to region
194 !
195 ! Output: None.
196 !
197 ! Notes: None.
198 !
199 ! ******************************************************************************
200 
201 SUBROUTINE rflu_buildplottingvarnames(pRegion)
202 
203 #ifdef PLAG
205 #endif
206 
207  IMPLICIT NONE
208 
209 ! ******************************************************************************
210 ! Declarations and definitions
211 ! ******************************************************************************
212 
213 ! ==============================================================================
214 ! Arguments
215 ! ==============================================================================
216 
217  TYPE(t_region), POINTER :: pregion
218 
219 ! ==============================================================================
220 ! Locals
221 ! ==============================================================================
222 
223  INTEGER :: errorflag,ivar
224  TYPE(t_global), POINTER :: global
225 
226 ! ******************************************************************************
227 ! Start
228 ! ******************************************************************************
229 
230  global => pregion%global
231 
232  CALL registerfunction(global,'RFLU_BuildPlottingVarNames', &
233  'RFLU_ModPlottingVars.F90')
234 
235 ! ******************************************************************************
236 ! Set names of plotting variables
237 ! ******************************************************************************
238 
239 ! ==============================================================================
240 ! Mixture
241 ! ==============================================================================
242 
243 ! ------------------------------------------------------------------------------
244 ! Discontinuity variables
245 ! ------------------------------------------------------------------------------
246 
247  pregion%plot%pvNameShort(pv_mixt_schl) = "schl"
248  pregion%plot%pvNameShort(pv_mixt_shad) = "shad"
249  pregion%plot%pvNameShort(pv_mixt_intf) = "intf"
250 
251  pregion%plot%pvNameLong(pv_mixt_schl) = "Schlieren variable"
252  pregion%plot%pvNameLong(pv_mixt_shad) = "Shadowgraph variable"
253  pregion%plot%pvNameLong(pv_mixt_intf) = "Interferogram variable"
254 
255 ! ------------------------------------------------------------------------------
256 ! Vorticity
257 ! ------------------------------------------------------------------------------
258 
259  pregion%plot%pvNameShort(pv_mixt_xvor) = "vorx"
260  pregion%plot%pvNameShort(pv_mixt_yvor) = "vory"
261  pregion%plot%pvNameShort(pv_mixt_zvor) = "vorz"
262 
263  pregion%plot%pvNameLong(pv_mixt_xvor) = "Vorticity x-component"
264  pregion%plot%pvNameLong(pv_mixt_yvor) = "Vorticity y-component"
265  pregion%plot%pvNameLong(pv_mixt_zvor) = "Vorticity z-component"
266 
267 ! ------------------------------------------------------------------------------
268 ! Vortex core variables
269 ! ------------------------------------------------------------------------------
270 
271  pregion%plot%pvNameShort(pv_mixt_vci2) = "vci2"
272  pregion%plot%pvNameShort(pv_mixt_vcl2) = "vcl2"
273  pregion%plot%pvNameShort(pv_mixt_vcli) = "vcli"
274  pregion%plot%pvNameShort(pv_mixt_vclr) = "vclr"
275 
276  pregion%plot%pvNameLong(pv_mixt_vci2) = "TBD"
277  pregion%plot%pvNameLong(pv_mixt_vcl2) = "TBD"
278  pregion%plot%pvNameLong(pv_mixt_vcli) = "TBD"
279  pregion%plot%pvNameLong(pv_mixt_vclr) = "TBD"
280 
281 ! ------------------------------------------------------------------------------
282 ! Gradient error
283 ! ------------------------------------------------------------------------------
284 
285  pregion%plot%pvNameShort(pv_mixt_grex) = "grex"
286  pregion%plot%pvNameShort(pv_mixt_grey) = "grey"
287  pregion%plot%pvNameShort(pv_mixt_grez) = "grez"
288 
289  pregion%plot%pvNameLong(pv_mixt_grex) = "Gradient error x-component"
290  pregion%plot%pvNameLong(pv_mixt_grey) = "Gradient error y-component"
291  pregion%plot%pvNameLong(pv_mixt_grez) = "Gradient error z-component"
292 
293 ! ==============================================================================
294 ! Physics modules
295 ! ==============================================================================
296 
297 #ifdef PLAG
298 ! ------------------------------------------------------------------------------
299 ! Particles
300 ! ------------------------------------------------------------------------------
301 
302  pregion%plot%pvNameShort(pv_plag_dia3) = "dp3"
303  pregion%plot%pvNameShort(pv_plag_dia4) = "dp4"
304  pregion%plot%pvNameShort(pv_plag_ndns) = "ndp"
305  pregion%plot%pvNameShort(pv_plag_xvel) = "up"
306  pregion%plot%pvNameShort(pv_plag_yvel) = "vp"
307  pregion%plot%pvNameShort(pv_plag_zvel) = "wp"
308  pregion%plot%pvNameShort(pv_plag_temp) = "Tp"
309  pregion%plot%pvNameShort(pv_plag_mass) = "mp"
310 
311  pregion%plot%pvNameLong(pv_plag_dia3) = "Particle mean diameter (3)"
312  pregion%plot%pvNameLong(pv_plag_dia4) = "Particle mean diameter (4)"
313  pregion%plot%pvNameLong(pv_plag_ndns) = "Particle number density"
314  pregion%plot%pvNameLong(pv_plag_xvel) = "Particle mean x-velocity"
315  pregion%plot%pvNameLong(pv_plag_yvel) = "Particle mean y-velocity"
316  pregion%plot%pvNameLong(pv_plag_zvel) = "Particle mean z-velocity"
317  pregion%plot%pvNameLong(pv_plag_temp) = "Particle mean temperature"
318  pregion%plot%pvNameLong(pv_plag_mass) = "Particle mean mass"
319 #endif
320 
321 ! ******************************************************************************
322 ! End
323 ! ******************************************************************************
324 
325  CALL deregisterfunction(global)
326 
327 END SUBROUTINE rflu_buildplottingvarnames
328 
329 
330 
331 
332 
333 
334 ! ******************************************************************************
335 !
336 ! Purpose: Compute vortex-core plotting variables.
337 !
338 ! Description: None.
339 !
340 ! Input:
341 ! pRegion Pointer to region
342 !
343 ! Output: None.
344 !
345 ! Notes:
346 ! 1. Assumes that stencils and differentiation weights are accessible.
347 !
348 ! ******************************************************************************
349 
350 SUBROUTINE rflu_computeplottingvarscore(pRegion)
351 
352  IMPLICIT NONE
353 
354 ! ******************************************************************************
355 ! Declarations and definitions
356 ! ******************************************************************************
357 
358 ! ==============================================================================
359 ! Arguments
360 ! ==============================================================================
361 
362  TYPE(t_region), POINTER :: pregion
363 
364 ! ==============================================================================
365 ! Locals
366 ! ==============================================================================
367 
368  INTEGER :: errorflag,icg,ilocvci2,ilocvcli,ilocvclr,ilocvcl2,info,lwork,ndim
369  INTEGER, DIMENSION(:), ALLOCATABLE :: varinfo
370  REAL(RFREAL) :: dudx,dudy,dudz,dvdx,dvdy,dvdz,dwdx,dwdy,dwdz
371  REAL(RFREAL), DIMENSION(:), ALLOCATABLE :: wi,work,wr
372  REAL(RFREAL), DIMENSION(:,:), ALLOCATABLE :: a,o,s,vl,vr
373  REAL(RFREAL), DIMENSION(:,:), POINTER :: pcv,ppv
374  REAL(RFREAL), DIMENSION(:,:,:), POINTER :: grad
375  TYPE(t_global), POINTER :: global
376  TYPE(t_grid), POINTER :: pgrid
377 
378 ! ******************************************************************************
379 ! Start
380 ! ******************************************************************************
381 
382  global => pregion%global
383 
384  CALL registerfunction(global,'RFLU_ComputePlottingVarsCore', &
385  'RFLU_ModPlottingVars.F90')
386 
387  IF ( global%verbLevel > verbose_none ) THEN
388  WRITE(stdout,'(A,1X,A)') solver_name, &
389  'Computing vortex-core plotting variables...'
390  END IF ! global%verbLevel
391 
392 ! ******************************************************************************
393 ! Set pointers
394 ! ******************************************************************************
395 
396  pgrid => pregion%grid
397 
398  pcv => pregion%mixt%cv
399  ppv => pregion%plot%pv
400 
401  ndim = pregion%mixtInput%dimens
402  lwork = 3*ndim
403 
404 ! ******************************************************************************
405 ! Get plotting variable locations
406 ! ******************************************************************************
407 
408  ilocvci2 = pregion%plot%pv2pvi(pv_mixt_vci2)
409  ilocvcl2 = pregion%plot%pv2pvi(pv_mixt_vcl2)
410  ilocvcli = pregion%plot%pv2pvi(pv_mixt_vcli)
411  ilocvclr = pregion%plot%pv2pvi(pv_mixt_vclr)
412 
413 ! ******************************************************************************
414 ! Allocate temporary memory
415 ! ******************************************************************************
416 
417  ALLOCATE(grad(xcoord:zcoord,3,pgrid%nCellsTot),stat=errorflag)
418  global%error = errorflag
419  IF (global%error /= err_none) THEN
420  CALL errorstop(global,err_allocate,__line__,'grad')
421  END IF ! global%error
422 
423  ALLOCATE(a(ndim,ndim),stat=errorflag)
424  global%error = errorflag
425  IF (global%error /= err_none) THEN
426  CALL errorstop(global,err_allocate,__line__,'a')
427  END IF ! global%error
428 
429  ALLOCATE(o(ndim,ndim),stat=errorflag)
430  global%error = errorflag
431  IF (global%error /= err_none) THEN
432  CALL errorstop(global,err_allocate,__line__,'o')
433  END IF ! global%error
434 
435  ALLOCATE(s(ndim,ndim),stat=errorflag)
436  global%error = errorflag
437  IF (global%error /= err_none) THEN
438  CALL errorstop(global,err_allocate,__line__,'s')
439  END IF ! global%error
440 
441  ALLOCATE(wr(ndim),stat=errorflag)
442  global%error = errorflag
443  IF (global%error /= err_none) THEN
444  CALL errorstop(global,err_allocate,__line__,'wr')
445  END IF ! global%error
446 
447  ALLOCATE(wi(ndim),stat=errorflag)
448  global%error = errorflag
449  IF (global%error /= err_none) THEN
450  CALL errorstop(global,err_allocate,__line__,'wi')
451  END IF ! global%error
452 
453  ALLOCATE(vl(ndim,ndim),stat=errorflag)
454  global%error = errorflag
455  IF (global%error /= err_none) THEN
456  CALL errorstop(global,err_allocate,__line__,'vl')
457  END IF ! global%error
458 
459  ALLOCATE(vr(ndim,ndim),stat=errorflag)
460  global%error = errorflag
461  IF (global%error /= err_none) THEN
462  CALL errorstop(global,err_allocate,__line__,'vr')
463  END IF ! global%error
464 
465  ALLOCATE(work(lwork),stat=errorflag)
466  global%error = errorflag
467  IF (global%error /= err_none) THEN
468  CALL errorstop(global,err_allocate,__line__,'work')
469  END IF ! global%error
470 
471 ! ******************************************************************************
472 ! Compute plotting variables
473 ! ******************************************************************************
474 
475 ! ==============================================================================
476 ! Compute velocity gradients
477 ! ==============================================================================
478 
479  ALLOCATE(varinfo(cv_mixt_xvel:cv_mixt_zvel),stat=errorflag)
480  global%error = errorflag
481  IF (global%error /= err_none) THEN
482  CALL errorstop(global,err_allocate,__line__,'varInfo')
483  END IF ! global%error
484 
485  varinfo(cv_mixt_xvel) = cv_mixt_xvel
486  varinfo(cv_mixt_yvel) = cv_mixt_yvel
487  varinfo(cv_mixt_zvel) = cv_mixt_zvel
488 
489  CALL rflu_computegradcellswrapper(pregion,cv_mixt_xvel,cv_mixt_zvel,1,3, &
490  varinfo,pcv,grad)
491 
492  DEALLOCATE(varinfo,stat=errorflag)
493  global%error = errorflag
494  IF (global%error /= err_none) THEN
495  CALL errorstop(global,err_deallocate,__line__,'varInfo')
496  END IF ! global%error
497 
498 ! ==============================================================================
499 ! Compute eigenvalues: NOTE does not make sense for 1d.
500 ! ==============================================================================
501 
502  SELECT CASE ( pregion%mixtInput%dimens )
503  CASE ( 2 )
504  DO icg = 1,pgrid%nCellsTot
505  dudx = grad(xcoord,1,icg)
506  dudy = grad(ycoord,1,icg)
507 
508  dvdx = grad(xcoord,2,icg)
509  dvdy = grad(ycoord,2,icg)
510 
511  a(1,1) = dudx
512  a(1,2) = dudy
513 
514  a(2,1) = dvdx
515  a(2,2) = dvdy
516 
517  CALL dgeev('N','N',ndim,a,ndim,wr,wi,vl,ndim,vr,ndim,work,lwork,info)
518 
519  ppv(ilocvci2,icg) = wr(1)*wr(2)
520  ppv(ilocvcli,icg) = wi(1)
521  ppv(ilocvclr,icg) = wr(1)/(wi(1)+1.0e-12_rfreal)
522 
523  s(1,1) = dudx
524  s(1,2) = 0.5_rfreal*(dudy + dvdx)
525 
526  s(2,1) = s(1,2)
527  s(2,2) = dvdy
528 
529  o(1,1) = 0.0_rfreal
530  o(1,2) = 0.5_rfreal*(dudy - dvdx)
531 
532  o(2,1) = -o(1,2)
533  o(2,2) = 0.0_rfreal
534 
535  a = matmul(s,s) + matmul(o,o)
536 
537  CALL dgeev('N','N',ndim,a,ndim,wr,wi,vl,ndim,vr,ndim,work,lwork,info)
538 
539  ppv(ilocvcl2,icg) = wr(1)
540  END DO ! icg
541  CASE ( 3 )
542  DO icg = 1,pgrid%nCellsTot
543  dudx = grad(xcoord,1,icg)
544  dudy = grad(ycoord,1,icg)
545  dudz = grad(zcoord,1,icg)
546 
547  dvdx = grad(xcoord,2,icg)
548  dvdy = grad(ycoord,2,icg)
549  dvdz = grad(zcoord,2,icg)
550 
551  dwdx = grad(xcoord,3,icg)
552  dwdy = grad(ycoord,3,icg)
553  dwdz = grad(zcoord,3,icg)
554 
555  a(1,1) = dudx
556  a(1,2) = dudy
557  a(1,3) = dudz
558 
559  a(2,1) = dvdx
560  a(2,2) = dvdy
561  a(2,3) = dvdz
562 
563  a(3,1) = dwdx
564  a(3,2) = dwdy
565  a(3,3) = dwdz
566 
567  CALL dgeev('N','N',ndim,a,ndim,wr,wi,vl,ndim,vr,ndim,work,lwork,info)
568 
569  ppv(ilocvci2,icg) = wr(1)*wr(2) + wr(1)*wr(3) + wr(2)*wr(3)
570  ppv(ilocvcli,icg) = wi(1)
571  ppv(ilocvclr,icg) = wr(1)/(wi(1)+1.0e-12_rfreal)
572 
573  s(1,1) = dudx
574  s(1,2) = 0.5_rfreal*(dudy + dvdx)
575  s(1,3) = 0.5_rfreal*(dudz + dwdx)
576 
577  s(2,1) = s(1,2)
578  s(2,2) = dvdy
579  s(2,3) = 0.5_rfreal*(dvdz + dwdy)
580 
581  s(3,1) = s(1,3)
582  s(3,2) = s(2,3)
583  s(3,3) = dwdz
584 
585  o(1,1) = 0.0_rfreal
586  o(1,2) = 0.5_rfreal*(dudy - dvdx)
587  o(1,3) = 0.5_rfreal*(dudz - dwdx)
588 
589  o(2,1) = -o(1,2)
590  o(2,2) = 0.0_rfreal
591  o(2,3) = 0.5_rfreal*(dvdz - dwdy)
592 
593  o(3,1) = -o(1,3)
594  o(3,2) = -o(2,3)
595  o(3,3) = 0.0_rfreal
596 
597  a = matmul(s,s) + matmul(o,o)
598 
599  CALL dgeev('N','N',ndim,a,ndim,wr,wi,vl,ndim,vr,ndim,work,lwork,info)
600 
601  ppv(ilocvcl2,icg) = wr(2)
602  END DO ! icg
603  CASE default
604  CALL errorstop(global,err_reached_default,__line__)
605  END SELECT ! pRegion%mixtInput%dimens
606 
607 ! ==============================================================================
608 ! Deallocate temporary memory
609 ! ==============================================================================
610 
611  DEALLOCATE(grad,stat=errorflag)
612  global%error = errorflag
613  IF (global%error /= err_none) THEN
614  CALL errorstop(global,err_deallocate,__line__,'grad')
615  END IF ! global%error
616 
617  DEALLOCATE(a,stat=errorflag)
618  global%error = errorflag
619  IF (global%error /= err_none) THEN
620  CALL errorstop(global,err_deallocate,__line__,'a')
621  END IF ! global%error
622 
623  DEALLOCATE(o,stat=errorflag)
624  global%error = errorflag
625  IF (global%error /= err_none) THEN
626  CALL errorstop(global,err_deallocate,__line__,'o')
627  END IF ! global%error
628 
629  DEALLOCATE(s,stat=errorflag)
630  global%error = errorflag
631  IF (global%error /= err_none) THEN
632  CALL errorstop(global,err_deallocate,__line__,'s')
633  END IF ! global%error
634 
635  DEALLOCATE(wr,stat=errorflag)
636  global%error = errorflag
637  IF (global%error /= err_none) THEN
638  CALL errorstop(global,err_deallocate,__line__,'wr')
639  END IF ! global%error
640 
641  DEALLOCATE(wi,stat=errorflag)
642  global%error = errorflag
643  IF (global%error /= err_none) THEN
644  CALL errorstop(global,err_deallocate,__line__,'wi')
645  END IF ! global%error
646 
647  DEALLOCATE(vl,stat=errorflag)
648  global%error = errorflag
649  IF (global%error /= err_none) THEN
650  CALL errorstop(global,err_deallocate,__line__,'vl')
651  END IF ! global%error
652 
653  DEALLOCATE(vr,stat=errorflag)
654  global%error = errorflag
655  IF (global%error /= err_none) THEN
656  CALL errorstop(global,err_deallocate,__line__,'vr')
657  END IF ! global%error
658 
659  DEALLOCATE(work,stat=errorflag)
660  global%error = errorflag
661  IF (global%error /= err_none) THEN
662  CALL errorstop(global,err_deallocate,__line__,'work')
663  END IF ! global%error
664 
665 ! ******************************************************************************
666 ! End
667 ! ******************************************************************************
668 
669  IF ( global%verbLevel > verbose_none ) THEN
670  WRITE(stdout,'(A,1X,A)') solver_name, &
671  'Computing vortex-core plotting variables done.'
672  END IF ! global%verbLevel
673 
674  CALL deregisterfunction(global)
675 
676 END SUBROUTINE rflu_computeplottingvarscore
677 
678 
679 
680 
681 
682 
683 
684 
685 ! ******************************************************************************
686 !
687 ! Purpose: Compute plotting variables related to discontinuities.
688 !
689 ! Description: None.
690 !
691 ! Input:
692 ! pRegion Pointer to region
693 !
694 ! Output: None.
695 !
696 ! Notes:
697 ! 1. Assumes that stencils and differentiation weights are accessible.
698 !
699 ! ******************************************************************************
700 
701 SUBROUTINE rflu_computeplottingvarsdisc(pRegion)
702 
703  IMPLICIT NONE
704 
705 ! ******************************************************************************
706 ! Declarations and definitions
707 ! ******************************************************************************
708 
709 ! ==============================================================================
710 ! Arguments
711 ! ==============================================================================
712 
713  TYPE(t_region), POINTER :: pregion
714 
715 ! ==============================================================================
716 ! Locals
717 ! ==============================================================================
718 
719  INTEGER :: errorflag,icg,ilocintf,ilocschl,ilocshad,termint
720  INTEGER :: varinfo(cv_mixt_dens:cv_mixt_dens)
721  REAL(RFREAL) :: gradmax,rmax,rmin,term
722  REAL(RFREAL), DIMENSION(:,:), POINTER :: pcv,ppv
723  REAL(RFREAL), DIMENSION(:,:,:), POINTER :: grad
724  TYPE(t_global), POINTER :: global
725  TYPE(t_grid), POINTER :: pgrid
726 
727 ! ******************************************************************************
728 ! Start
729 ! ******************************************************************************
730 
731  global => pregion%global
732 
733  CALL registerfunction(global,'RFLU_ComputePlottingVarsDisc', &
734  'RFLU_ModPlottingVars.F90')
735 
736  IF ( global%verbLevel > verbose_none ) THEN
737  WRITE(stdout,'(A,1X,A)') solver_name, &
738  'Computing discontinuity plotting variables...'
739  END IF ! global%verbLevel
740 
741 ! ******************************************************************************
742 ! Set pointers
743 ! ******************************************************************************
744 
745  pgrid => pregion%grid
746 
747  pcv => pregion%mixt%cv
748  ppv => pregion%plot%pv
749 
750 ! ******************************************************************************
751 ! Get and set plotting variable locations
752 ! ******************************************************************************
753 
754  ilocschl = pregion%plot%pv2pvi(pv_mixt_schl)
755  ilocshad = pregion%plot%pv2pvi(pv_mixt_shad)
756  ilocintf = pregion%plot%pv2pvi(pv_mixt_intf)
757 
758 ! ******************************************************************************
759 ! Compute plotting variables used to visualize discontinuities
760 ! ******************************************************************************
761 
762 ! ==============================================================================
763 ! Schlieren and Shadowgraph
764 ! ==============================================================================
765 
766 ! ------------------------------------------------------------------------------
767 ! Allocate temporary memory
768 ! ------------------------------------------------------------------------------
769 
770  ALLOCATE(grad(xcoord:zcoord,1,pgrid%nCellsTot),stat=errorflag)
771  global%error = errorflag
772  IF (global%error /= err_none) THEN
773  CALL errorstop(global,err_allocate,__line__,'grad')
774  END IF ! global%error
775 
776 ! ------------------------------------------------------------------------------
777 ! Compute gradients
778 ! ------------------------------------------------------------------------------
779 
780  varinfo(cv_mixt_dens) = cv_mixt_dens
781 
782  CALL rflu_computegradcellswrapper(pregion,cv_mixt_dens,cv_mixt_dens,1,1, &
783  varinfo,pcv,grad)
784 
785 ! ------------------------------------------------------------------------------
786 ! Compute Schlieren and Shadowgraph variables. NOTE when using scaled Schlieren,
787 ! will only be computed correctly for single region or merged regions.
788 ! ------------------------------------------------------------------------------
789 
790  DO icg = 1,pgrid%nCellsTot
791  ppv(ilocschl,icg) = sqrt(grad(xcoord,1,icg)**2 &
792  + grad(ycoord,1,icg)**2 &
793  + grad(zcoord,1,icg)**2)
794  ppv(ilocshad,icg) = 0.0_rfreal ! TEMPORARY
795  END DO ! icg
796 
797  IF ( global%postSchType /= 0 ) THEN
798  gradmax = maxval(ppv(ilocschl,1:pgrid%nCellsTot))
799 
800  DO icg = 1,pgrid%nCellsTot
801  ppv(ilocschl,icg) = exp(-global%postSchExp*ppv(ilocschl,icg)/gradmax)
802  END DO ! icg
803  END IF ! global%postSchType
804 
805 ! ------------------------------------------------------------------------------
806 ! Deallocate temporary memory
807 ! ------------------------------------------------------------------------------
808 
809  DEALLOCATE(grad,stat=errorflag)
810  global%error = errorflag
811  IF (global%error /= err_none) THEN
812  CALL errorstop(global,err_deallocate,__line__,'grad')
813  END IF ! global%error
814 
815 ! ==============================================================================
816 ! Interferogram - NOTE will only be computed correctly for single region or
817 ! merged regions.
818 ! ==============================================================================
819 
820  rmax = maxval(pcv(cv_mixt_dens,1:pgrid%nCells))
821  rmin = minval(pcv(cv_mixt_dens,1:pgrid%nCells))
822 
823  DO icg = 1,pgrid%nCellsTot
824  term = (pcv(cv_mixt_dens,icg)-rmin)/(rmax-rmin)
825  termint = int(global%postNFringes*term + 0.5_rfreal)
826 
827  ppv(ilocintf,icg) = mod(termint,2)
828  END DO ! icg
829 
830 ! ******************************************************************************
831 ! End
832 ! ******************************************************************************
833 
834  IF ( global%verbLevel > verbose_none ) THEN
835  WRITE(stdout,'(A,1X,A)') solver_name, &
836  'Computing discontinuity plotting variables done.'
837  END IF ! global%verbLevel
838 
839  CALL deregisterfunction(global)
840 
841 END SUBROUTINE rflu_computeplottingvarsdisc
842 
843 
844 
845 
846 
847 
848 ! ******************************************************************************
849 !
850 ! Purpose: Compute gradient-error plotting variables.
851 !
852 ! Description: None.
853 !
854 ! Input:
855 ! pRegion Pointer to region
856 !
857 ! Output: None.
858 !
859 ! Notes:
860 ! 1. Assumes that stencils and differentiation weights are accessible.
861 !
862 ! ******************************************************************************
863 
865 
868 
869  IMPLICIT NONE
870 
871 ! ******************************************************************************
872 ! Declarations and definitions
873 ! ******************************************************************************
874 
875 ! ==============================================================================
876 ! Arguments
877 ! ==============================================================================
878 
879  TYPE(t_region), POINTER :: pregion
880 
881 ! ==============================================================================
882 ! Locals
883 ! ==============================================================================
884 
885  INTEGER :: errorflag,icg,ilocxerr,ilocyerr,iloczerr,ivar,ivarbeg,ivarend
886  INTEGER, DIMENSION(:), ALLOCATABLE :: varinfo
887  REAL(RFREAL) :: gxe,gye,gze,nx,ny,nz,var,x,y,z
888  REAL(RFREAL), DIMENSION(:,:), POINTER :: pcv,ppv
889  REAL(RFREAL), DIMENSION(:,:,:), POINTER :: grad
890  TYPE(t_global), POINTER :: global
891  TYPE(t_grid), POINTER :: pgrid
892 
893 ! ******************************************************************************
894 ! Start
895 ! ******************************************************************************
896 
897  global => pregion%global
898 
899  CALL registerfunction(global,'RFLU_ComputePlottingVarsGradErr', &
900  'RFLU_ModPlottingVars.F90')
901 
902  IF ( global%verbLevel > verbose_none ) THEN
903  WRITE(stdout,'(A,1X,A)') solver_name, &
904  'Computing gradient-error plotting variables...'
905  END IF ! global%verbLevel
906 
907 ! ******************************************************************************
908 ! Set pointers and variables
909 ! ******************************************************************************
910 
911  pgrid => pregion%grid
912 
913  pcv => pregion%mixt%cv
914  ppv => pregion%plot%pv
915 
916  ivarbeg = cv_mixt_dens ! NOTE at present works only for 1 var
917  ivarend = ivarbeg
918 
919 ! ******************************************************************************
920 ! Get and set plotting variable locations
921 ! ******************************************************************************
922 
923  ilocxerr = pregion%plot%pv2pvi(pv_mixt_grex)
924  ilocyerr = pregion%plot%pv2pvi(pv_mixt_grey)
925  iloczerr = pregion%plot%pv2pvi(pv_mixt_grez)
926 
927 ! ******************************************************************************
928 ! Compute plotting variables
929 ! ******************************************************************************
930 
931 ! ==============================================================================
932 ! Allocate temporary memory
933 ! ==============================================================================
934 
935  ALLOCATE(grad(xcoord:zcoord,ivarbeg:ivarend,pgrid%nCellsTot),stat=errorflag)
936  global%error = errorflag
937  IF (global%error /= err_none) THEN
938  CALL errorstop(global,err_allocate,__line__,'grad')
939  END IF ! global%error
940 
941 ! ==============================================================================
942 ! Compute gradients
943 ! ==============================================================================
944 
945  ALLOCATE(varinfo(ivarbeg:ivarend),stat=errorflag)
946  global%error = errorflag
947  IF (global%error /= err_none) THEN
948  CALL errorstop(global,err_allocate,__line__,'varInfo')
949  END IF ! global%error
950 
951  varinfo(ivarbeg:ivarend) = ivarbeg ! NOTE at present works only for 1 var
952 
953  CALL rflu_computegradcellswrapper(pregion,ivarbeg,ivarend,ivarbeg,ivarend, &
954  varinfo,pcv,grad)
955 
956  DEALLOCATE(varinfo,stat=errorflag)
957  global%error = errorflag
958  IF (global%error /= err_none) THEN
959  CALL errorstop(global,err_deallocate,__line__,'varInfo')
960  END IF ! global%error
961 
962 ! ==============================================================================
963 ! Compute error
964 ! ==============================================================================
965 
966  SELECT CASE ( global%casename )
967 
968 ! ------------------------------------------------------------------------------
969 ! Linear function
970 ! ------------------------------------------------------------------------------
971 
972  CASE ( "gtlin" )
973  SELECT CASE ( pregion%mixtInput%dimens )
974  CASE ( 1 )
975  DO icg = 1,pgrid%nCellsTot
976  x = pgrid%cofg(xcoord,icg)
977  y = pgrid%cofg(ycoord,icg)
978  z = pgrid%cofg(zcoord,icg)
979 
980  DO ivar = ivarbeg,ivarend
981  CALL rflu_setexactflowlinear(x,y,z,ivar,var,gxe,gye,gze)
982 
983  ppv(ilocxerr,icg) = grad(xcoord,ivar,icg)/gxe - 1.0_rfreal
984  ppv(ilocyerr,icg) = 0.0_rfreal
985  ppv(iloczerr,icg) = 0.0_rfreal
986  END DO ! iVar
987  END DO ! icg
988  CASE ( 2 )
989  DO icg = 1,pgrid%nCellsTot
990  x = pgrid%cofg(xcoord,icg)
991  y = pgrid%cofg(ycoord,icg)
992  z = pgrid%cofg(zcoord,icg)
993 
994  DO ivar = ivarbeg,ivarend
995  CALL rflu_setexactflowlinear(x,y,z,ivar,var,gxe,gye,gze)
996 
997  ppv(ilocxerr,icg) = grad(xcoord,ivar,icg)/gxe - 1.0_rfreal
998  ppv(ilocyerr,icg) = grad(ycoord,ivar,icg)/gye - 1.0_rfreal
999  ppv(iloczerr,icg) = 0.0_rfreal
1000  END DO ! iVar
1001  END DO ! icg
1002  CASE ( 3 )
1003  DO icg = 1,pgrid%nCellsTot
1004  x = pgrid%cofg(xcoord,icg)
1005  y = pgrid%cofg(ycoord,icg)
1006  z = pgrid%cofg(zcoord,icg)
1007 
1008  DO ivar = ivarbeg,ivarend
1009  CALL rflu_setexactflowlinear(x,y,z,ivar,var,gxe,gye,gze)
1010 
1011  ppv(ilocxerr,icg) = grad(xcoord,ivar,icg)/gxe - 1.0_rfreal
1012  ppv(ilocyerr,icg) = grad(ycoord,ivar,icg)/gye - 1.0_rfreal
1013  ppv(iloczerr,icg) = grad(zcoord,ivar,icg)/gze - 1.0_rfreal
1014  END DO ! iVar
1015  END DO ! icg
1016  CASE default ! Defensive coding
1017  CALL errorstop(global,err_reached_default,__line__)
1018  END SELECT ! pRegion%mixtInput%dimens
1019 
1020 ! ------------------------------------------------------------------------------
1021 ! Trigonometric function
1022 ! ------------------------------------------------------------------------------
1023 
1024  CASE ( "gttri" )
1025  nx = pregion%mixtInput%prepRealVal1
1026  ny = pregion%mixtInput%prepRealVal2
1027  nz = pregion%mixtInput%prepRealVal3
1028 
1029  SELECT CASE ( pregion%mixtInput%dimens )
1030  CASE ( 1 )
1031  DO icg = 1,pgrid%nCellsTot
1032  x = pgrid%cofg(xcoord,icg)
1033  y = pgrid%cofg(ycoord,icg)
1034  z = pgrid%cofg(zcoord,icg)
1035 
1036  DO ivar = ivarbeg,ivarend
1037  CALL rflu_setexactflowtrig(global,nx,ny,nz,x,y,z,ivar,var, &
1038  gxe,gye,gze)
1039 
1040  ppv(ilocxerr,icg) = grad(xcoord,ivar,icg)/gxe - 1.0_rfreal
1041  ppv(ilocyerr,icg) = 0.0_rfreal
1042  ppv(iloczerr,icg) = 0.0_rfreal
1043  END DO ! iVar
1044  END DO ! icg
1045  CASE ( 2 )
1046  DO icg = 1,pgrid%nCellsTot
1047  x = pgrid%cofg(xcoord,icg)
1048  y = pgrid%cofg(ycoord,icg)
1049  z = pgrid%cofg(zcoord,icg)
1050 
1051  DO ivar = ivarbeg,ivarend
1052  CALL rflu_setexactflowtrig(global,nx,ny,nz,x,y,z,ivar,var, &
1053  gxe,gye,gze)
1054 
1055  ppv(ilocxerr,icg) = grad(xcoord,ivar,icg)/gxe - 1.0_rfreal
1056  ppv(ilocyerr,icg) = grad(ycoord,ivar,icg)/gye - 1.0_rfreal
1057  ppv(iloczerr,icg) = 0.0_rfreal
1058  END DO ! iVar
1059  END DO ! icg
1060  CASE ( 3 )
1061  DO icg = 1,pgrid%nCellsTot
1062  x = pgrid%cofg(xcoord,icg)
1063  y = pgrid%cofg(ycoord,icg)
1064  z = pgrid%cofg(zcoord,icg)
1065 
1066  DO ivar = ivarbeg,ivarend
1067  CALL rflu_setexactflowtrig(global,nx,ny,nz,x,y,z,ivar,var, &
1068  gxe,gye,gze)
1069 
1070  ppv(ilocxerr,icg) = grad(xcoord,ivar,icg)/gxe - 1.0_rfreal
1071  ppv(ilocyerr,icg) = grad(ycoord,ivar,icg)/gye - 1.0_rfreal
1072  ppv(iloczerr,icg) = grad(zcoord,ivar,icg)/gze - 1.0_rfreal
1073  END DO ! iVar
1074  END DO ! icg
1075  CASE default
1076  CALL errorstop(global,err_reached_default,__line__)
1077  END SELECT ! pRegion%mixtInput%dimens
1078 
1079 ! ------------------------------------------------------------------------------
1080 ! Default
1081 ! ------------------------------------------------------------------------------
1082 
1083  CASE default
1084  CALL errorstop(global,err_reached_default,__line__)
1085  END SELECT ! global%casename
1086 
1087 ! ==============================================================================
1088 ! Deallocate temporary memory
1089 ! ==============================================================================
1090 
1091  DEALLOCATE(grad,stat=errorflag)
1092  global%error = errorflag
1093  IF (global%error /= err_none) THEN
1094  CALL errorstop(global,err_deallocate,__line__,'grad')
1095  END IF ! global%error
1096 
1097 ! ******************************************************************************
1098 ! End
1099 ! ******************************************************************************
1100 
1101  IF ( global%verbLevel > verbose_none ) THEN
1102  WRITE(stdout,'(A,1X,A)') solver_name, &
1103  'Computing gradient-error plotting variables done.'
1104  END IF ! global%verbLevel
1105 
1106  CALL deregisterfunction(global)
1107 
1108 END SUBROUTINE rflu_computeplottingvarsgraderr
1109 
1110 
1111 
1112 
1113 
1114 
1115 ! ******************************************************************************
1116 !
1117 ! Purpose: Compute vorticity plotting variables.
1118 !
1119 ! Description: None.
1120 !
1121 ! Input:
1122 ! pRegion Pointer to region
1123 !
1124 ! Output: None.
1125 !
1126 ! Notes:
1127 ! 1. Assumes that stencils and differentiation weights are accessible.
1128 !
1129 ! ******************************************************************************
1130 
1131 SUBROUTINE rflu_computeplottingvarsvort(pRegion)
1132 
1133  IMPLICIT NONE
1134 
1135 ! ******************************************************************************
1136 ! Declarations and definitions
1137 ! ******************************************************************************
1138 
1139 ! ==============================================================================
1140 ! Arguments
1141 ! ==============================================================================
1142 
1143  TYPE(t_region), POINTER :: pregion
1144 
1145 ! ==============================================================================
1146 ! Locals
1147 ! ==============================================================================
1148 
1149  INTEGER :: errorflag,icg,ilocxvor,ilocyvor,iloczvor
1150  INTEGER, DIMENSION(:), ALLOCATABLE :: varinfo
1151  REAL(RFREAL) :: dudx,dudy,dudz,dvdx,dvdy,dvdz,dwdx,dwdy,dwdz
1152  REAL(RFREAL), DIMENSION(:,:), POINTER :: pcv,ppv
1153  REAL(RFREAL), DIMENSION(:,:,:), POINTER :: grad
1154  TYPE(t_global), POINTER :: global
1155  TYPE(t_grid), POINTER :: pgrid
1156 
1157 ! ******************************************************************************
1158 ! Start
1159 ! ******************************************************************************
1160 
1161  global => pregion%global
1162 
1163  CALL registerfunction(global,'RFLU_ComputePlottingVarsVort', &
1164  'RFLU_ModPlottingVars.F90')
1165 
1166  IF ( global%verbLevel > verbose_none ) THEN
1167  WRITE(stdout,'(A,1X,A)') solver_name, &
1168  'Computing vorticity plotting variables...'
1169  END IF ! global%verbLevel
1170 
1171 ! ******************************************************************************
1172 ! Set pointers
1173 ! ******************************************************************************
1174 
1175  pgrid => pregion%grid
1176 
1177  pcv => pregion%mixt%cv
1178  ppv => pregion%plot%pv
1179 
1180 ! ******************************************************************************
1181 ! Get and set plotting variable locations
1182 ! ******************************************************************************
1183 
1184  ilocxvor = pregion%plot%pv2pvi(pv_mixt_xvor)
1185  ilocyvor = pregion%plot%pv2pvi(pv_mixt_yvor)
1186  iloczvor = pregion%plot%pv2pvi(pv_mixt_zvor)
1187 
1188 ! ******************************************************************************
1189 ! Compute plotting variables
1190 ! ******************************************************************************
1191 
1192 ! ==============================================================================
1193 ! Allocate temporary memory
1194 ! ==============================================================================
1195 
1196  ALLOCATE(grad(xcoord:zcoord,3,pgrid%nCellsTot),stat=errorflag)
1197  global%error = errorflag
1198  IF (global%error /= err_none) THEN
1199  CALL errorstop(global,err_allocate,__line__,'grad')
1200  END IF ! global%error
1201 
1202 ! ==============================================================================
1203 ! Compute gradients
1204 ! ==============================================================================
1205 
1206  ALLOCATE(varinfo(cv_mixt_xvel:cv_mixt_zvel),stat=errorflag)
1207  global%error = errorflag
1208  IF (global%error /= err_none) THEN
1209  CALL errorstop(global,err_allocate,__line__,'varInfo')
1210  END IF ! global%error
1211 
1212  varinfo(cv_mixt_xvel) = cv_mixt_xvel
1213  varinfo(cv_mixt_yvel) = cv_mixt_yvel
1214  varinfo(cv_mixt_zvel) = cv_mixt_zvel
1215 
1216  CALL rflu_computegradcellswrapper(pregion,cv_mixt_xvel,cv_mixt_zvel,1,3, &
1217  varinfo,pcv,grad)
1218 
1219  DEALLOCATE(varinfo,stat=errorflag)
1220  global%error = errorflag
1221  IF (global%error /= err_none) THEN
1222  CALL errorstop(global,err_deallocate,__line__,'varInfo')
1223  END IF ! global%error
1224 
1225 ! ==============================================================================
1226 ! Compute vorticity
1227 ! ==============================================================================
1228 
1229  DO icg = 1,pgrid%nCellsTot
1230  dudx = grad(xcoord,1,icg)
1231  dudy = grad(ycoord,1,icg)
1232  dudz = grad(zcoord,1,icg)
1233 
1234  dvdx = grad(xcoord,2,icg)
1235  dvdy = grad(ycoord,2,icg)
1236  dvdz = grad(zcoord,2,icg)
1237 
1238  dwdx = grad(xcoord,3,icg)
1239  dwdy = grad(ycoord,3,icg)
1240  dwdz = grad(zcoord,3,icg)
1241 
1242  ppv(ilocxvor,icg) = dwdy - dvdz
1243  ppv(ilocyvor,icg) = dudz - dwdx
1244  ppv(iloczvor,icg) = dvdx - dudy
1245  END DO ! icg
1246 
1247 ! ==============================================================================
1248 ! Deallocate temporary memory
1249 ! ==============================================================================
1250 
1251  DEALLOCATE(grad,stat=errorflag)
1252  global%error = errorflag
1253  IF (global%error /= err_none) THEN
1254  CALL errorstop(global,err_deallocate,__line__,'grad')
1255  END IF ! global%error
1256 
1257 ! ******************************************************************************
1258 ! End
1259 ! ******************************************************************************
1260 
1261  IF ( global%verbLevel > verbose_none ) THEN
1262  WRITE(stdout,'(A,1X,A)') solver_name, &
1263  'Computing vorticity plotting variables done.'
1264  END IF ! global%verbLevel
1265 
1266  CALL deregisterfunction(global)
1267 
1268 END SUBROUTINE rflu_computeplottingvarsvort
1269 
1270 
1271 
1272 
1273 
1274 
1275 
1276 
1277 
1278 ! ******************************************************************************
1279 !
1280 ! Purpose: Wrapper for computing plotting variables.
1281 !
1282 ! Description: None.
1283 !
1284 ! Input:
1285 ! pRegion Pointer to region
1286 !
1287 ! Output: None.
1288 !
1289 ! Notes:
1290 ! 1. Assumes that stencils and differentiation weights are accessible.
1291 !
1292 ! ******************************************************************************
1293 
1295 
1298 
1299 #ifdef PLAG
1300  USE plag_modeulerian
1301 #endif
1302 
1303  IMPLICIT NONE
1304 
1305 ! ******************************************************************************
1306 ! Declarations and definitions
1307 ! ******************************************************************************
1308 
1309 ! ==============================================================================
1310 ! Arguments
1311 ! ==============================================================================
1312 
1313  TYPE(t_region), POINTER :: pregion
1314 
1315 ! ==============================================================================
1316 ! Locals
1317 ! ==============================================================================
1318 
1319  INTEGER :: icgbeg,icgend,ipvbeg,ipvend
1320  TYPE(t_global), POINTER :: global
1321 
1322 ! ******************************************************************************
1323 ! Start
1324 ! ******************************************************************************
1325 
1326  global => pregion%global
1327 
1328  CALL registerfunction(global,'RFLU_ComputePlottingVarsWrapper', &
1329  'RFLU_ModPlottingVars.F90')
1330 
1331 ! ******************************************************************************
1332 ! Mixture
1333 ! ******************************************************************************
1334 
1335  IF ( global%postDiscFlag .EQV. .true. ) THEN
1336  CALL rflu_computeplottingvarsdisc(pregion)
1337  END IF ! global%postDiscFlag
1338 
1339  CALL rflu_convertcvcons2prim(pregion,cv_mixt_state_duvwp)
1340 
1341  IF ( global%postGradFlag .EQV. .true. ) THEN
1342  CALL rflu_computeplottingvarsgraderr(pregion)
1343  END IF ! global%postGradFlag
1344 
1345  IF ( global%postVortFlag .EQV. .true. ) THEN
1346  CALL rflu_computeplottingvarsvort(pregion)
1347  END IF ! global%postVortFlag
1348 
1349  IF ( global%postVortCoreFlag .EQV. .true. ) THEN
1350  CALL rflu_computeplottingvarscore(pregion)
1351  END IF ! global%postVortCoreFlag
1352 
1353  CALL rflu_convertcvprim2cons(pregion,cv_mixt_state_cons)
1354 
1355 ! ******************************************************************************
1356 ! Physics modules
1357 ! ******************************************************************************
1358 
1359 #ifdef PLAG
1360  IF ( global%plagUsed .EQV. .true. ) THEN
1361  IF ( global%postLag2EulFlag .EQV. .true. ) THEN
1362  ipvbeg = pregion%plot%pv2pvi(pv_plag_dia3)
1363  ipvend = pregion%plot%pv2pvi(pv_plag_mass)
1364  icgbeg = 1
1365  icgend = pregion%grid%nCells
1366 
1367  CALL plag_rflu_calceulerianfield(pregion, &
1368  pregion%plot%pv(ipvbeg:ipvend,icgbeg:icgend))
1369  END IF ! global%postLag2EulFlag
1370  END IF ! global%plagUsed
1371 #endif
1372 
1373 ! ******************************************************************************
1374 ! End
1375 ! ******************************************************************************
1376 
1377  CALL deregisterfunction(global)
1378 
1379 END SUBROUTINE rflu_computeplottingvarswrapper
1380 
1381 
1382 
1383 
1384 
1385 
1386 
1387 
1388 
1389 
1390 ! ******************************************************************************
1391 !
1392 ! Purpose: Count plotting variables.
1393 !
1394 ! Description: None.
1395 !
1396 ! Input:
1397 ! pRegion Pointer to region
1398 !
1399 ! Output: None.
1400 !
1401 ! Notes: None.
1402 !
1403 ! ******************************************************************************
1404 
1405 SUBROUTINE rflu_countplottingvars(pRegion)
1406 
1407 #ifdef PLAG
1408  USE plag_modparameters
1409 #endif
1410 
1411  IMPLICIT NONE
1412 
1413 ! ******************************************************************************
1414 ! Declarations and definitions
1415 ! ******************************************************************************
1416 
1417 ! ==============================================================================
1418 ! Arguments
1419 ! ==============================================================================
1420 
1421  TYPE(t_region), POINTER :: pregion
1422 
1423 ! ==============================================================================
1424 ! Locals
1425 ! ==============================================================================
1426 
1427  INTEGER :: errorflag,ipv
1428  TYPE(t_global), POINTER :: global
1429 
1430 ! ******************************************************************************
1431 ! Start
1432 ! ******************************************************************************
1433 
1434  global => pregion%global
1435 
1436  CALL registerfunction(global,'RFLU_CountPlottingVars', &
1437  'RFLU_ModPlottingVars.F90')
1438 
1439  IF ( global%verbLevel > verbose_none ) THEN
1440  WRITE(stdout,'(A,1X,A)') solver_name,'Counting plotting variables...'
1441  END IF ! global%verbLevel
1442 
1443 ! ******************************************************************************
1444 ! Initialize
1445 ! ******************************************************************************
1446 
1447  DO ipv = 1,pv_xxxx_nvar
1448  pregion%plot%pv2pvi(ipv) = crazy_value_int ! Important
1449  END DO ! iPv
1450 
1451 ! ******************************************************************************
1452 ! Count number of plotting variables
1453 ! ******************************************************************************
1454 
1455  pregion%plot%nPv = 0
1456 
1457 ! ==============================================================================
1458 ! Mixture
1459 ! ==============================================================================
1460 
1461 ! ------------------------------------------------------------------------------
1462 ! Variables to visualize discontinuities
1463 ! ------------------------------------------------------------------------------
1464 
1465  IF ( global%postDiscFlag .EQV. .true. ) THEN
1466  pregion%plot%pv2pvi(pv_mixt_schl) = pregion%plot%nPv + 1
1467  pregion%plot%pv2pvi(pv_mixt_shad) = pregion%plot%nPv + 2
1468  pregion%plot%pv2pvi(pv_mixt_intf) = pregion%plot%nPv + 3
1469 
1470  pregion%plot%nPv = pregion%plot%nPv + 3
1471  END IF ! global%postDiscFlag
1472 
1473 ! ------------------------------------------------------------------------------
1474 ! Vorticity
1475 ! ------------------------------------------------------------------------------
1476 
1477  IF ( global%postVortFlag .EQV. .true. ) THEN
1478  pregion%plot%pv2pvi(pv_mixt_xvor) = pregion%plot%nPv + 1
1479  pregion%plot%pv2pvi(pv_mixt_yvor) = pregion%plot%nPv + 2
1480  pregion%plot%pv2pvi(pv_mixt_zvor) = pregion%plot%nPv + 3
1481 
1482  pregion%plot%nPv = pregion%plot%nPv + 3
1483  END IF ! global%postVortFlag
1484 
1485 ! ------------------------------------------------------------------------------
1486 ! Vortex core
1487 ! ------------------------------------------------------------------------------
1488 
1489  IF ( global%postVortCoreFlag .EQV. .true. ) THEN
1490  pregion%plot%pv2pvi(pv_mixt_vci2) = pregion%plot%nPv + 1
1491  pregion%plot%pv2pvi(pv_mixt_vcl2) = pregion%plot%nPv + 2
1492  pregion%plot%pv2pvi(pv_mixt_vcli) = pregion%plot%nPv + 3
1493  pregion%plot%pv2pvi(pv_mixt_vclr) = pregion%plot%nPv + 4
1494 
1495  pregion%plot%nPv = pregion%plot%nPv + 4
1496  END IF ! global%postVortCoreFlag
1497 
1498 ! ------------------------------------------------------------------------------
1499 ! Variables to visualize gradient error
1500 ! ------------------------------------------------------------------------------
1501 
1502  IF ( global%postGradFlag .EQV. .true. ) THEN
1503  pregion%plot%pv2pvi(pv_mixt_grex) = pregion%plot%nPv + 1
1504  pregion%plot%pv2pvi(pv_mixt_grey) = pregion%plot%nPv + 2
1505  pregion%plot%pv2pvi(pv_mixt_grez) = pregion%plot%nPv + 3
1506 
1507  pregion%plot%nPv = pregion%plot%nPv + 3
1508  END IF ! global%postGradFlag
1509 
1510 ! ==============================================================================
1511 ! Physics modules
1512 ! ==============================================================================
1513 
1514 #ifdef PLAG
1515  IF ( global%plagUsed .EQV. .true. ) THEN
1516  IF ( global%postLag2EulFlag .EQV. .true. ) THEN
1517  pregion%plot%pv2pvi(pv_plag_dia3) = pregion%plot%nPv + 1
1518  pregion%plot%pv2pvi(pv_plag_dia4) = pregion%plot%nPv + 2
1519  pregion%plot%pv2pvi(pv_plag_ndns) = pregion%plot%nPv + 3
1520  pregion%plot%pv2pvi(pv_plag_xvel) = pregion%plot%nPv + 4
1521  pregion%plot%pv2pvi(pv_plag_yvel) = pregion%plot%nPv + 5
1522  pregion%plot%pv2pvi(pv_plag_zvel) = pregion%plot%nPv + 6
1523  pregion%plot%pv2pvi(pv_plag_temp) = pregion%plot%nPv + 7
1524  pregion%plot%pv2pvi(pv_plag_mass) = pregion%plot%nPv + 8
1525 
1526  pregion%plot%nPv = pregion%plot%nPv + ev_plag_last
1527  END IF ! global%postLag2EulFlag
1528  END IF ! global%plagUsed
1529 #endif
1530 
1531 ! ******************************************************************************
1532 ! Print information and build names
1533 ! ******************************************************************************
1534 
1535  IF ( global%verbLevel > verbose_low ) THEN
1536  WRITE(stdout,'(A,3X,A,1X,I2)') solver_name, &
1537  'Number of plotting variables:', &
1538  pregion%plot%nPv
1539  END IF ! global%verbLevel
1540 
1541  CALL rflu_buildplottingvarnames(pregion)
1542 
1543 ! ******************************************************************************
1544 ! End
1545 ! ******************************************************************************
1546 
1547  IF ( global%verbLevel > verbose_none ) THEN
1548  WRITE(stdout,'(A,1X,A)') solver_name,'Counting plotting variables done.'
1549  END IF ! global%verbLevel
1550 
1551  CALL deregisterfunction(global)
1552 
1553 END SUBROUTINE rflu_countplottingvars
1554 
1555 
1556 
1557 
1558 
1559 
1560 
1561 ! ******************************************************************************
1562 !
1563 ! Purpose: Create plotting variable maps.
1564 !
1565 ! Description: None.
1566 !
1567 ! Input:
1568 ! pRegion Pointer to region
1569 !
1570 ! Output: None.
1571 !
1572 ! Notes: None.
1573 !
1574 ! ******************************************************************************
1575 
1576 SUBROUTINE rflu_createplottingvarmaps(pRegion)
1577 
1578  IMPLICIT NONE
1579 
1580 ! ******************************************************************************
1581 ! Declarations and definitions
1582 ! ******************************************************************************
1583 
1584 ! ==============================================================================
1585 ! Arguments
1586 ! ==============================================================================
1587 
1588  TYPE(t_region), POINTER :: pregion
1589 
1590 ! ==============================================================================
1591 ! Locals
1592 ! ==============================================================================
1593 
1594  INTEGER :: errorflag
1595  TYPE(t_global), POINTER :: global
1596 
1597 ! ******************************************************************************
1598 ! Start
1599 ! ******************************************************************************
1600 
1601  global => pregion%global
1602 
1603  CALL registerfunction(global,'RFLU_CreatePlottingVarMaps', &
1604  'RFLU_ModPlottingVars.F90')
1605 
1606  IF ( global%verbLevel > verbose_low ) THEN
1607  WRITE(stdout,'(A,1X,A)') solver_name,'Creating plotting variable maps...'
1608  END IF ! global%verbLevel
1609 
1610 ! ******************************************************************************
1611 ! Allocate memory
1612 ! ******************************************************************************
1613 
1614  IF ( pregion%plot%nPv > 0 ) THEN
1615  ALLOCATE(pregion%plot%pvi2pv(pregion%plot%nPv),stat=errorflag)
1616  global%error = errorflag
1617  IF ( global%error /= err_none ) THEN
1618  CALL errorstop(global,err_allocate,__line__,'pRegion%plot%pvi2pv')
1619  END IF ! global%error
1620  ELSE
1621  CALL rflu_nullifyplottingvarmaps(pregion)
1622  END IF ! pRegion%plot%nPv
1623 
1624 ! ******************************************************************************
1625 ! End
1626 ! ******************************************************************************
1627 
1628  IF ( global%verbLevel > verbose_none ) THEN
1629  WRITE(stdout,'(A,1X,A)') solver_name,'Creating plotting variable maps done.'
1630  END IF ! global%verbLevel
1631 
1632  CALL deregisterfunction(global)
1633 
1634 END SUBROUTINE rflu_createplottingvarmaps
1635 
1636 
1637 
1638 
1639 
1640 
1641 
1642 ! ******************************************************************************
1643 !
1644 ! Purpose: Create plotting variables.
1645 !
1646 ! Description: None.
1647 !
1648 ! Input:
1649 ! pRegion Pointer to region
1650 !
1651 ! Output: None.
1652 !
1653 ! Notes: None.
1654 !
1655 ! ******************************************************************************
1656 
1657 SUBROUTINE rflu_createplottingvars(pRegion)
1658 
1659  IMPLICIT NONE
1660 
1661 ! ******************************************************************************
1662 ! Declarations and definitions
1663 ! ******************************************************************************
1664 
1665 ! ==============================================================================
1666 ! Arguments
1667 ! ==============================================================================
1668 
1669  TYPE(t_region), POINTER :: pregion
1670 
1671 ! ==============================================================================
1672 ! Locals
1673 ! ==============================================================================
1674 
1675  INTEGER :: errorflag
1676  TYPE(t_global), POINTER :: global
1677 
1678 ! ******************************************************************************
1679 ! Start
1680 ! ******************************************************************************
1681 
1682  global => pregion%global
1683 
1684  CALL registerfunction(global,'RFLU_CreatePlottingVars', &
1685  'RFLU_ModPlottingVars.F90')
1686 
1687  IF ( global%verbLevel > verbose_none ) THEN
1688  WRITE(stdout,'(A,1X,A)') solver_name,'Creating plotting variables...'
1689  END IF ! global%verbLevel
1690 
1691 ! ******************************************************************************
1692 ! Allocate memory
1693 ! ******************************************************************************
1694 
1695  IF ( pregion%plot%nPv > 0 ) THEN
1696  ALLOCATE(pregion%plot%pv(pregion%plot%nPv,pregion%grid%nCellsTot), &
1697  stat=errorflag)
1698  global%error = errorflag
1699  IF ( global%error /= err_none ) THEN
1700  CALL errorstop(global,err_allocate,__line__,'pRegion%plot%pv')
1701  END IF ! global%error
1702 
1703  CALL rflu_initplottingvars(pregion)
1704  ELSE
1705  CALL rflu_nullifyplottingvars(pregion)
1706  END IF ! pRegion%plot%nPv
1707 
1708 ! ******************************************************************************
1709 ! End
1710 ! ******************************************************************************
1711 
1712  IF ( global%verbLevel > verbose_none ) THEN
1713  WRITE(stdout,'(A,1X,A)') solver_name,'Creating plotting variables done.'
1714  END IF ! global%verbLevel
1715 
1716  CALL deregisterfunction(global)
1717 
1718 END SUBROUTINE rflu_createplottingvars
1719 
1720 
1721 
1722 
1723 
1724 
1725 
1726 
1727 ! ******************************************************************************
1728 !
1729 ! Purpose: Create plotting variables at vertices.
1730 !
1731 ! Description: None.
1732 !
1733 ! Input:
1734 ! pRegion Pointer to region
1735 !
1736 ! Output: None.
1737 !
1738 ! Notes: None.
1739 !
1740 ! ******************************************************************************
1741 
1742 SUBROUTINE rflu_createplottingvarsvert(pRegion)
1743 
1744  IMPLICIT NONE
1745 
1746 ! ******************************************************************************
1747 ! Declarations and definitions
1748 ! ******************************************************************************
1749 
1750 ! ==============================================================================
1751 ! Arguments
1752 ! ==============================================================================
1753 
1754  TYPE(t_region), POINTER :: pregion
1755 
1756 ! ==============================================================================
1757 ! Locals
1758 ! ==============================================================================
1759 
1760  INTEGER :: errorflag
1761  TYPE(t_global), POINTER :: global
1762 
1763 ! ******************************************************************************
1764 ! Start
1765 ! ******************************************************************************
1766 
1767  global => pregion%global
1768 
1769  CALL registerfunction(global,'RFLU_CreatePlottingVarsVert', &
1770  'RFLU_ModPlottingVars.F90')
1771 
1772 ! ******************************************************************************
1773 ! Create plotting variables
1774 ! ******************************************************************************
1775 
1776  IF ( pregion%plot%nPv > 0 ) THEN
1777  ALLOCATE(pregion%plot%pvVert(pregion%plot%nPv,pregion%grid%nVertTot), &
1778  stat=errorflag)
1779  global%error = errorflag
1780  IF ( global%error /= err_none ) THEN
1781  CALL errorstop(global,err_allocate,__line__,'pRegion%plot%pvVert')
1782  END IF ! global%error
1783 
1784  CALL rflu_initplottingvarsvert(pregion)
1785  ELSE
1786  CALL rflu_nullifyplottingvarsvert(pregion)
1787  END IF ! pRegion%plot%nPv
1788 
1789 ! ******************************************************************************
1790 ! End
1791 ! ******************************************************************************
1792 
1793  CALL deregisterfunction(global)
1794 
1795 END SUBROUTINE rflu_createplottingvarsvert
1796 
1797 
1798 
1799 
1800 
1801 
1802 
1803 
1804 ! ******************************************************************************
1805 !
1806 ! Purpose: Decide whether plotting vars to be computed.
1807 !
1808 ! Description: None.
1809 !
1810 ! Input:
1811 ! pRegion Pointer to region
1812 !
1813 ! Output: None.
1814 !
1815 ! Notes: None.
1816 !
1817 ! ******************************************************************************
1818 
1819 LOGICAL FUNCTION rflu_decidecomputeplottingvars(pRegion)
1820 
1821  IMPLICIT NONE
1822 
1823 ! ******************************************************************************
1824 ! Declarations and definitions
1825 ! ******************************************************************************
1826 
1827 ! ==============================================================================
1828 ! Arguments
1829 ! ==============================================================================
1830 
1831  TYPE(t_region), POINTER :: pregion
1832 
1833 ! ==============================================================================
1834 ! Locals
1835 ! ==============================================================================
1836 
1837  TYPE(t_global), POINTER :: global
1838 
1839 ! ******************************************************************************
1840 ! Start
1841 ! ******************************************************************************
1842 
1843  global => pregion%global
1844 
1845 ! ******************************************************************************
1846 ! Initialize
1847 ! ******************************************************************************
1848 
1850 
1851 ! ******************************************************************************
1852 ! Decide whether plotting vars to be computed
1853 ! ******************************************************************************
1854 
1855  IF ( pregion%mixtInput%fluidModel == fluid_model_comp ) THEN
1856  IF ( (global%postDiscFlag .EQV. .true.) .OR. &
1857  (global%postGradFlag .EQV. .true.) .OR. &
1858  (global%postVortFlag .EQV. .true.) .OR. &
1859  (global%postVortCoreFlag .EQV. .true.) .OR. &
1860  (global%postLag2EulFlag .EQV. .true.) ) THEN
1862  END IF ! global%postDiscFlag
1863  END IF ! pRegion%mixtInput%fluidModel
1864 
1865 ! ******************************************************************************
1866 ! End
1867 ! ******************************************************************************
1868 
1869 END FUNCTION rflu_decidecomputeplottingvars
1870 
1871 
1872 
1873 
1874 
1875 
1876 
1877 ! ******************************************************************************
1878 !
1879 ! Purpose: Destroy plotting variable maps.
1880 !
1881 ! Description: None.
1882 !
1883 ! Input:
1884 ! pRegion Pointer to region
1885 !
1886 ! Output: None.
1887 !
1888 ! Notes: None.
1889 !
1890 ! ******************************************************************************
1891 
1892 SUBROUTINE rflu_destroyplottingvarmaps(pRegion)
1893 
1894  IMPLICIT NONE
1895 
1896 ! ******************************************************************************
1897 ! Declarations and definitions
1898 ! ******************************************************************************
1899 
1900 ! ==============================================================================
1901 ! Arguments
1902 ! ==============================================================================
1903 
1904  TYPE(t_region), POINTER :: pregion
1905 
1906 ! ==============================================================================
1907 ! Locals
1908 ! ==============================================================================
1909 
1910  INTEGER :: errorflag
1911  TYPE(t_global), POINTER :: global
1912 
1913 ! ******************************************************************************
1914 ! Start
1915 ! ******************************************************************************
1916 
1917  global => pregion%global
1918 
1919  CALL registerfunction(global,'RFLU_DestroyPlottingVarMaps', &
1920  'RFLU_ModPlottingVars.F90')
1921 
1922  IF ( global%verbLevel > verbose_low ) THEN
1923  WRITE(stdout,'(A,1X,A)') solver_name,'Destroying plotting variable maps...'
1924  END IF ! global%verbLevel
1925 
1926 ! ******************************************************************************
1927 ! Allocate memory
1928 ! ******************************************************************************
1929 
1930  IF ( pregion%plot%nPv > 0 ) THEN
1931  DEALLOCATE(pregion%plot%pvi2pv,stat=errorflag)
1932  global%error = errorflag
1933  IF ( global%error /= err_none ) THEN
1934  CALL errorstop(global,err_deallocate,__line__,'pRegion%plot%pvi2pv')
1935  END IF ! global%error
1936  END IF ! pRegion%plot%nPv
1937 
1938  CALL rflu_nullifyplottingvarmaps(pregion)
1939 
1940 ! ******************************************************************************
1941 ! End
1942 ! ******************************************************************************
1943 
1944  IF ( global%verbLevel > verbose_none ) THEN
1945  WRITE(stdout,'(A,1X,A)') solver_name, &
1946  'Destroying plotting variable maps done.'
1947  END IF ! global%verbLevel
1948 
1949  CALL deregisterfunction(global)
1950 
1951 END SUBROUTINE rflu_destroyplottingvarmaps
1952 
1953 
1954 
1955 
1956 
1957 
1958 
1959 ! ******************************************************************************
1960 !
1961 ! Purpose: Destroy plotting variables.
1962 !
1963 ! Description: None.
1964 !
1965 ! Input:
1966 ! pRegion Pointer to region
1967 !
1968 ! Output: None.
1969 !
1970 ! Notes: None.
1971 !
1972 ! ******************************************************************************
1973 
1974 SUBROUTINE rflu_destroyplottingvars(pRegion)
1975 
1976  IMPLICIT NONE
1977 
1978 ! ******************************************************************************
1979 ! Declarations and definitions
1980 ! ******************************************************************************
1981 
1982 ! ==============================================================================
1983 ! Arguments
1984 ! ==============================================================================
1985 
1986  TYPE(t_region), POINTER :: pregion
1987 
1988 ! ==============================================================================
1989 ! Locals
1990 ! ==============================================================================
1991 
1992  INTEGER :: errorflag
1993  TYPE(t_global), POINTER :: global
1994 
1995 ! ******************************************************************************
1996 ! Start
1997 ! ******************************************************************************
1998 
1999  global => pregion%global
2000 
2001  CALL registerfunction(global,'RFLU_DestroyPlottingVars', &
2002  'RFLU_ModPlottingVars.F90')
2003 
2004  IF ( global%verbLevel > verbose_none ) THEN
2005  WRITE(stdout,'(A,1X,A)') solver_name,'Destroying plotting variables...'
2006  END IF ! global%verbLevel
2007 
2008 ! ******************************************************************************
2009 ! Deallocate memory
2010 ! ******************************************************************************
2011 
2012  IF ( pregion%plot%nPv > 0 ) THEN
2013  DEALLOCATE(pregion%plot%pv,stat=errorflag)
2014  global%error = errorflag
2015  IF ( global%error /= err_none ) THEN
2016  CALL errorstop(global,err_deallocate,__line__,'pRegion%plot%pv')
2017  END IF ! global%error
2018  END IF ! pRegion%plot%nPv
2019 
2020  CALL rflu_nullifyplottingvars(pregion)
2021 
2022 ! ******************************************************************************
2023 ! End
2024 ! ******************************************************************************
2025 
2026  IF ( global%verbLevel > verbose_none ) THEN
2027  WRITE(stdout,'(A,1X,A)') solver_name,'Destroying plotting variables done.'
2028  END IF ! global%verbLevel
2029 
2030  CALL deregisterfunction(global)
2031 
2032 END SUBROUTINE rflu_destroyplottingvars
2033 
2034 
2035 
2036 
2037 
2038 
2039 
2040 
2041 ! ******************************************************************************
2042 !
2043 ! Purpose: Destroy plotting variables at vertices.
2044 !
2045 ! Description: None.
2046 !
2047 ! Input:
2048 ! pRegion Pointer to region
2049 !
2050 ! Output: None.
2051 !
2052 ! Notes: None.
2053 !
2054 ! ******************************************************************************
2055 
2056 SUBROUTINE rflu_destroyplottingvarsvert(pRegion)
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 ! Locals
2072 ! ==============================================================================
2073 
2074  INTEGER :: errorflag
2075  TYPE(t_global), POINTER :: global
2076 
2077 ! ******************************************************************************
2078 ! Start
2079 ! ******************************************************************************
2080 
2081  global => pregion%global
2082 
2083  CALL registerfunction(global,'RFLU_DestroyPlottingVarsVert', &
2084  'RFLU_ModPlottingVars.F90')
2085 
2086 ! ******************************************************************************
2087 ! Destroy plotting variables
2088 ! ******************************************************************************
2089 
2090  IF ( pregion%plot%nPv > 0 ) THEN
2091  DEALLOCATE(pregion%plot%pvVert,stat=errorflag)
2092  global%error = errorflag
2093  IF ( global%error /= err_none ) THEN
2094  CALL errorstop(global,err_deallocate,__line__,'pRegion%plot%pvVert')
2095  END IF ! global%error
2096  END IF ! pRegion%plot%nPv
2097 
2098  CALL rflu_nullifyplottingvarsvert(pregion)
2099 
2100 ! ******************************************************************************
2101 ! End
2102 ! ******************************************************************************
2103 
2104  CALL deregisterfunction(global)
2105 
2106 END SUBROUTINE rflu_destroyplottingvarsvert
2107 
2108 
2109 
2110 
2111 
2112 
2113 ! ******************************************************************************
2114 !
2115 ! Purpose: Initialize plotting variables.
2116 !
2117 ! Description: None.
2118 !
2119 ! Input:
2120 ! pRegion Pointer to region
2121 !
2122 ! Output: None.
2123 !
2124 ! Notes: None.
2125 !
2126 ! ******************************************************************************
2127 
2128 SUBROUTINE rflu_initplottingvars(pRegion)
2129 
2130  IMPLICIT NONE
2131 
2132 ! ******************************************************************************
2133 ! Declarations and definitions
2134 ! ******************************************************************************
2135 
2136 ! ==============================================================================
2137 ! Arguments
2138 ! ==============================================================================
2139 
2140  TYPE(t_region), POINTER :: pregion
2141 
2142 ! ==============================================================================
2143 ! Locals
2144 ! ==============================================================================
2145 
2146  INTEGER :: icg,ivar
2147  TYPE(t_global), POINTER :: global
2148 
2149 ! ******************************************************************************
2150 ! Start
2151 ! ******************************************************************************
2152 
2153  global => pregion%global
2154 
2155  CALL registerfunction(global,'RFLU_InitPlottingVars', &
2156  'RFLU_ModPlottingVars.F90')
2157 
2158  IF ( global%verbLevel > verbose_low ) THEN
2159  WRITE(stdout,'(A,1X,A)') solver_name,'Initializing plotting variables...'
2160  END IF ! global%verbLevel
2161 
2162 ! ******************************************************************************
2163 ! Initialize plotting variables
2164 ! ******************************************************************************
2165 
2166  DO ivar = 1,pregion%plot%nPv
2167  DO icg = 1,pregion%grid%nCellsTot
2168  pregion%plot%pv(ivar,icg) = 0.0_rfreal
2169  END DO ! icg
2170  END DO ! iVar
2171 
2172 ! ******************************************************************************
2173 ! End
2174 ! ******************************************************************************
2175 
2176  IF ( global%verbLevel > verbose_low ) THEN
2177  WRITE(stdout,'(A,1X,A)') solver_name,'Initializing plotting variables done.'
2178  END IF ! global%verbLevel
2179 
2180  CALL deregisterfunction(global)
2181 
2182 END SUBROUTINE rflu_initplottingvars
2183 
2184 
2185 
2186 
2187 
2188 
2189 
2190 ! ******************************************************************************
2191 !
2192 ! Purpose: Initialize vertex plotting variables.
2193 !
2194 ! Description: None.
2195 !
2196 ! Input:
2197 ! pRegion Pointer to region
2198 !
2199 ! Output: None.
2200 !
2201 ! Notes: None.
2202 !
2203 ! ******************************************************************************
2204 
2205 SUBROUTINE rflu_initplottingvarsvert(pRegion)
2206 
2207  IMPLICIT NONE
2208 
2209 ! ******************************************************************************
2210 ! Declarations and definitions
2211 ! ******************************************************************************
2212 
2213 ! ==============================================================================
2214 ! Arguments
2215 ! ==============================================================================
2216 
2217  TYPE(t_region), POINTER :: pregion
2218 
2219 ! ==============================================================================
2220 ! Locals
2221 ! ==============================================================================
2222 
2223  INTEGER :: ivg,ivar
2224  TYPE(t_global), POINTER :: global
2225 
2226 ! ******************************************************************************
2227 ! Start
2228 ! ******************************************************************************
2229 
2230  global => pregion%global
2231 
2232  CALL registerfunction(global,'RFLU_InitPlottingVarsVert', &
2233  'RFLU_ModPlottingVars.F90')
2234 
2235  IF ( global%verbLevel > verbose_low ) THEN
2236  WRITE(stdout,'(A,1X,A)') solver_name, &
2237  'Initializing vertex plotting variables...'
2238  END IF ! global%verbLevel
2239 
2240 ! ******************************************************************************
2241 ! Initialize vertex plotting variables
2242 ! ******************************************************************************
2243 
2244  DO ivar = 1,pregion%plot%nPv
2245  DO ivg = 1,pregion%grid%nVertTot
2246  pregion%plot%pvVert(ivar,ivg) = 0.0_rfreal
2247  END DO ! ivg
2248  END DO ! iVar
2249 
2250 ! ******************************************************************************
2251 ! End
2252 ! ******************************************************************************
2253 
2254  IF ( global%verbLevel > verbose_low ) THEN
2255  WRITE(stdout,'(A,1X,A)') solver_name, &
2256  'Initializing vertex plotting variables done.'
2257  END IF ! global%verbLevel
2258 
2259  CALL deregisterfunction(global)
2260 
2261 END SUBROUTINE rflu_initplottingvarsvert
2262 
2263 
2264 
2265 
2266 
2267 
2268 
2269 ! ******************************************************************************
2270 !
2271 ! Purpose: Nullify plotting variable maps.
2272 !
2273 ! Description: None.
2274 !
2275 ! Input:
2276 ! pRegion Pointer to region
2277 !
2278 ! Output: None.
2279 !
2280 ! Notes: None.
2281 !
2282 ! ******************************************************************************
2283 
2284 SUBROUTINE rflu_nullifyplottingvarmaps(pRegion)
2285 
2286  IMPLICIT NONE
2287 
2288 ! ******************************************************************************
2289 ! Declarations and definitions
2290 ! ******************************************************************************
2291 
2292 ! ==============================================================================
2293 ! Arguments
2294 ! ==============================================================================
2295 
2296  TYPE(t_region), POINTER :: pregion
2297 
2298 ! ==============================================================================
2299 ! Locals
2300 ! ==============================================================================
2301 
2302  INTEGER :: errorflag
2303  TYPE(t_global), POINTER :: global
2304 
2305 ! ******************************************************************************
2306 ! Start
2307 ! ******************************************************************************
2308 
2309  global => pregion%global
2310 
2311  CALL registerfunction(global,'RFLU_NullifyPlottingVarMaps', &
2312  'RFLU_ModPlottingVars.F90')
2313 
2314 ! ******************************************************************************
2315 ! Nullify plotting variables
2316 ! ******************************************************************************
2317 
2318  nullify(pregion%plot%pvi2pv)
2319 
2320 ! ******************************************************************************
2321 ! End
2322 ! ******************************************************************************
2323 
2324  CALL deregisterfunction(global)
2325 
2326 END SUBROUTINE rflu_nullifyplottingvarmaps
2327 
2328 
2329 
2330 
2331 
2332 ! ******************************************************************************
2333 !
2334 ! Purpose: Nullify plotting variables.
2335 !
2336 ! Description: None.
2337 !
2338 ! Input:
2339 ! pRegion Pointer to region
2340 !
2341 ! Output: None.
2342 !
2343 ! Notes: None.
2344 !
2345 ! ******************************************************************************
2346 
2347 SUBROUTINE rflu_nullifyplottingvars(pRegion)
2348 
2349  IMPLICIT NONE
2350 
2351 ! ******************************************************************************
2352 ! Declarations and definitions
2353 ! ******************************************************************************
2354 
2355 ! ==============================================================================
2356 ! Arguments
2357 ! ==============================================================================
2358 
2359  TYPE(t_region), POINTER :: pregion
2360 
2361 ! ==============================================================================
2362 ! Locals
2363 ! ==============================================================================
2364 
2365  INTEGER :: errorflag
2366  TYPE(t_global), POINTER :: global
2367 
2368 ! ******************************************************************************
2369 ! Start
2370 ! ******************************************************************************
2371 
2372  global => pregion%global
2373 
2374  CALL registerfunction(global,'RFLU_NullifyPlottingVars', &
2375  'RFLU_ModPlottingVars.F90')
2376 
2377 ! ******************************************************************************
2378 ! Nullify plotting variables
2379 ! ******************************************************************************
2380 
2381  nullify(pregion%plot%pv)
2382 
2383 ! ******************************************************************************
2384 ! End
2385 ! ******************************************************************************
2386 
2387  CALL deregisterfunction(global)
2388 
2389 END SUBROUTINE rflu_nullifyplottingvars
2390 
2391 
2392 
2393 
2394 
2395 
2396 ! ******************************************************************************
2397 !
2398 ! Purpose: Nullify plotting variables at vertices.
2399 !
2400 ! Description: None.
2401 !
2402 ! Input:
2403 ! pRegion Pointer to region
2404 !
2405 ! Output: None.
2406 !
2407 ! Notes: None.
2408 !
2409 ! ******************************************************************************
2410 
2411 SUBROUTINE rflu_nullifyplottingvarsvert(pRegion)
2412 
2413  IMPLICIT NONE
2414 
2415 ! ******************************************************************************
2416 ! Declarations and definitions
2417 ! ******************************************************************************
2418 
2419 ! ==============================================================================
2420 ! Arguments
2421 ! ==============================================================================
2422 
2423  TYPE(t_region), POINTER :: pregion
2424 
2425 ! ==============================================================================
2426 ! Locals
2427 ! ==============================================================================
2428 
2429  INTEGER :: errorflag
2430  TYPE(t_global), POINTER :: global
2431 
2432 ! ******************************************************************************
2433 ! Start
2434 ! ******************************************************************************
2435 
2436  global => pregion%global
2437 
2438  CALL registerfunction(global,'RFLU_NullifyPlottingVarsVert', &
2439  'RFLU_ModPlottingVars.F90')
2440 
2441 ! ******************************************************************************
2442 ! Nullify plotting variables
2443 ! ******************************************************************************
2444 
2445  nullify(pregion%plot%pvVert)
2446 
2447 ! ******************************************************************************
2448 ! End
2449 ! ******************************************************************************
2450 
2451  CALL deregisterfunction(global)
2452 
2453 END SUBROUTINE rflu_nullifyplottingvarsvert
2454 
2455 
2456 
2457 
2458 
2459 
2460 ! ******************************************************************************
2461 !
2462 ! Purpose: Print plotting variable info.
2463 !
2464 ! Description: None.
2465 !
2466 ! Input:
2467 ! pRegion Pointer to region
2468 !
2469 ! Output: None.
2470 !
2471 ! Notes: None.
2472 !
2473 ! ******************************************************************************
2474 
2475 SUBROUTINE rflu_printplottingvarsinfo(pRegion)
2476 
2477  IMPLICIT NONE
2478 
2479 ! ******************************************************************************
2480 ! Declarations and definitions
2481 ! ******************************************************************************
2482 
2483 ! ==============================================================================
2484 ! Arguments
2485 ! ==============================================================================
2486 
2487  TYPE(t_region), POINTER :: pregion
2488 
2489 ! ==============================================================================
2490 ! Locals
2491 ! ==============================================================================
2492 
2493  INTEGER :: errorflag,ipv,ipv2
2494  TYPE(t_global), POINTER :: global
2495 
2496 ! ******************************************************************************
2497 ! Start
2498 ! ******************************************************************************
2499 
2500  global => pregion%global
2501 
2502  CALL registerfunction(global,'RFLU_PrintPlottingVarsInfo', &
2503  'RFLU_ModPlottingVars.F90')
2504 
2505  IF ( global%verbLevel > verbose_low ) THEN
2506  WRITE(stdout,'(A,1X,A)') solver_name, &
2507  'Printing information on plotting variables...'
2508  END IF ! global%verbLevel
2509 
2510 ! ******************************************************************************
2511 ! Print names of plotting variables
2512 ! ******************************************************************************
2513 
2514  IF ( global%verbLevel > verbose_low ) THEN
2515  WRITE(stdout,'(A,5X,A,2X,A,2X,A,26X,A)') solver_name,'#','Index', &
2516  'Long name','Short name'
2517 
2518  DO ipv = 1,pregion%plot%nPv
2519  ipv2 = pregion%plot%pvi2pv(ipv)
2520 
2521  WRITE(stdout,'(A,4X,I2,4X,I2,3X,A32,3X,A6)') solver_name,ipv,ipv2, &
2522  adjustl(pregion%plot%pvNameLong(ipv2)), &
2523  adjustl(pregion%plot%pvNameShort(ipv2))
2524  END DO ! iPv
2525  END IF ! global%verbLevel
2526 
2527 ! ******************************************************************************
2528 ! End
2529 ! ******************************************************************************
2530 
2531  IF ( global%verbLevel > verbose_low ) THEN
2532  WRITE(stdout,'(A,1X,A)') solver_name, &
2533  'Printing information on plotting variables done.'
2534  END IF ! global%verbLevel
2535 
2536  CALL deregisterfunction(global)
2537 
2538 END SUBROUTINE rflu_printplottingvarsinfo
2539 
2540 
2541 
2542 
2543 
2544 END MODULE rflu_modplottingvars
2545 
2546 ! ******************************************************************************
2547 !
2548 ! RCS Revision history:
2549 !
2550 ! $Log: RFLU_ModPlottingVars.F90,v $
2551 ! Revision 1.15 2008/12/06 08:45:06 mtcampbe
2552 ! Updated license.
2553 !
2554 ! Revision 1.14 2008/11/19 22:18:16 mtcampbe
2555 ! Added Illinois Open Source License/Copyright
2556 !
2557 ! Revision 1.13 2007/03/19 21:44:05 haselbac
2558 ! Significant reorganization with move of pv from mixt to plot
2559 !
2560 ! Revision 1.12 2007/02/27 13:24:36 haselbac
2561 ! Enabled 1d computations
2562 !
2563 ! Revision 1.11 2006/04/07 15:19:26 haselbac
2564 ! Removed tabs
2565 !
2566 ! Revision 1.10 2006/01/06 22:20:15 haselbac
2567 ! Added routine to compute grad error
2568 !
2569 ! Revision 1.9 2005/12/10 16:56:36 haselbac
2570 ! Added decide and init routines
2571 !
2572 ! Revision 1.8 2005/11/30 22:25:25 fnajjar
2573 ! Added call to compute Eulerian vars for PLAG
2574 !
2575 ! Revision 1.7 2005/10/05 16:20:49 haselbac
2576 ! Bug fix in USE statement
2577 !
2578 ! Revision 1.6 2005/08/10 00:38:18 haselbac
2579 ! Added routine for vortex core extraction and wrapper
2580 !
2581 ! Revision 1.5 2005/07/25 12:24:32 haselbac
2582 ! Added vorticity plotting vars, moved stencil and weights out for efficiency
2583 ! and commonality
2584 !
2585 ! Revision 1.4 2005/07/05 19:24:03 haselbac
2586 ! Added exponential Schlieren indicator
2587 !
2588 ! Revision 1.3 2005/07/01 21:29:28 haselbac
2589 ! Bug fix: Allocate pv memory for nCellsTot
2590 !
2591 ! Revision 1.2 2005/05/03 20:38:22 haselbac
2592 ! Removed DEBUG code
2593 !
2594 ! Revision 1.1 2005/05/01 14:17:11 haselbac
2595 ! Initial revision
2596 !
2597 ! ******************************************************************************
2598 
2599 
2600 
2601 
2602 
2603 
2604 
2605 
2606 
2607 
2608 
2609 
2610 
2611 
2612 
2613 
2614 
2615 
2616 
2617 
2618 
2619 
2620 
2621 
2622 
2623 
void int int REAL REAL * y
Definition: read.cpp:74
double s
Definition: blastest.C:80
subroutine rflu_nullifyplottingvarsvert(pRegion)
subroutine registerfunction(global, funName, fileName)
Definition: ModError.F90:449
double sqrt(double d)
Definition: double.h:73
subroutine, public rflu_printplottingvarsinfo(pRegion)
subroutine rflu_computeplottingvarsdisc(pRegion)
subroutine rflu_initplottingvarsvert(pRegion)
subroutine rflu_nullifyplottingvars(pRegion)
subroutine rflu_buildplottingvarnames(pRegion)
subroutine, public rflu_convertcvcons2prim(pRegion, cvStateFuture)
subroutine rflu_nullifyplottingvarmaps(pRegion)
subroutine, public rflu_countplottingvars(pRegion)
subroutine, public rflu_destroyplottingvarsvert(pRegion)
void int int int REAL REAL REAL * z
Definition: write.cpp:76
subroutine, public rflu_convertcvprim2cons(pRegion, cvStateFuture)
subroutine rflu_computeplottingvarsvort(pRegion)
void int int REAL * x
Definition: read.cpp:74
LOGICAL function, public rflu_decidecomputeplottingvars(pRegion)
subroutine, public rflu_destroyplottingvars(pRegion)
subroutine, public rflu_buildplottingvarmaps(pRegion)
subroutine, public rflu_computegradcellswrapper(pRegion, iBegVar, iEndVar, iBegGrad, iEndGrad, varInfo, var, grad)
subroutine, public rflu_setexactflowtrig(global, nx, ny, nz, x, y, z, iVar, var, gx, gy, gz)
subroutine errorstop(global, errorCode, errorLine, addMessage)
Definition: ModError.F90:483
subroutine, public rflu_computeplottingvarswrapper(pRegion)
subroutine, public rflu_destroyplottingvarmaps(pRegion)
subroutine, public rflu_createplottingvars(pRegion)
subroutine rflu_computeplottingvarscore(pRegion)
subroutine deregisterfunction(global)
Definition: ModError.F90:469
subroutine, public rflu_createplottingvarsvert(pRegion)
subroutine rflu_initplottingvars(pRegion)
subroutine, public rflu_setexactflowlinear(x, y, z, iVar, var, gx, gy, gz)
subroutine rflu_computeplottingvarsgraderr(pRegion)
subroutine, public rflu_createplottingvarmaps(pRegion)
RT a() const
Definition: Line_2.h:140