Rocstar  1.0
Rocstar multiphysics simulation application
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
RFLU_ModTECPLOT.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: Collect routines to write TECPLOT file.
26 !
27 ! Description: None.
28 !
29 ! Input: None.
30 !
31 ! Output: None.
32 !
33 ! Notes:
34 ! 1. Note the various array format required by TECPLOT - e.g., coordinate-
35 ! array must first be converted.
36 ! 2. Routines were separated so that can open TECPLOT file and write several
37 ! zones to it. This is useful to visualize parallel results.
38 !
39 ! ******************************************************************************
40 !
41 ! $Id: RFLU_ModTECPLOT.F90,v 1.38 2008/12/06 08:45:06 mtcampbe Exp $
42 !
43 ! Copyright: (c) 2003-2005 by the University of Illinois
44 !
45 ! ******************************************************************************
46 
48 
49  USE moddatatypes
50  USE modparameters
51  USE moderror
52  USE modglobal, ONLY: t_global
53  USE modgrid, ONLY: t_grid
54  USE modbndpatch, ONLY: t_patch
55  USE moddatastruct, ONLY: t_region
56 
57 #ifdef SPEC
58 ! USE SPEC_ModParameters
59 #endif
60 
62 
63  IMPLICIT NONE
64 
65 ! ******************************************************************************
66 ! Definitions and declarations
67 ! ******************************************************************************
68 
69 ! ==============================================================================
70 ! Private data
71 ! ==============================================================================
72 
73  CHARACTER(CHRLEN), PARAMETER, PRIVATE :: &
74  RCSIdentString = '$RCSfile: RFLU_ModTECPLOT.F90,v $ $Revision: 1.38 $'
75 
76 ! ==============================================================================
77 ! Public functions
78 ! ==============================================================================
79 
80  PUBLIC :: rflu_tec_builddatafieldsurf, &
91  rflu_tec_init, &
100 
101 ! ==============================================================================
102 ! Private functions
103 ! ==============================================================================
104 
105  PRIVATE :: rflu_tec_buildheaderfield, &
108 
109 ! ******************************************************************************
110 ! Subroutines and functions
111 ! ******************************************************************************
112 
113  CONTAINS
114 
115 
116 
117 
118 
119 ! ******************************************************************************
120 !
121 ! Purpose: Collect surface data for writing to TECPLOT field file.
122 !
123 ! Description: None.
124 !
125 ! Input:
126 ! pRegion Pointer to region data
127 ! pPatch Pointer to patch data
128 !
129 ! Output: None.
130 !
131 ! Notes:
132 ! 1. Isolated this code so that can easily add data for writing to file.
133 !
134 ! ******************************************************************************
135 
136 SUBROUTINE rflu_tec_builddatafieldsurf(pRegion,pPatch)
137 
138  IMPLICIT NONE
139 
140 ! ******************************************************************************
141 ! Declarations and definitions
142 ! ******************************************************************************
143 
144 ! ==============================================================================
145 ! Arguments
146 ! ==============================================================================
147 
148  TYPE(t_patch), POINTER :: ppatch
149  TYPE(t_region), POINTER :: pregion
150 
151 ! ==============================================================================
152 ! Locals
153 ! ==============================================================================
154 
155  INTEGER :: errorflag,icg,ifl,ipatch,ivar,ivarfacetot,ivartot,ivarverttot, &
156  ivg,ivl,nvarsfacetot,nvarsfacetotsave,nvarsverttot, &
157  nvarsverttotsave
158  REAL(RFREAL), DIMENSION(:,:), POINTER :: pvar
159  TYPE(t_global), POINTER :: global
160  TYPE(t_grid), POINTER :: pgrid
161 
162 ! ==============================================================================
163 ! Externals: TECPLOT functions
164 ! ==============================================================================
165 
166  INTEGER, EXTERNAL :: tecfil100
167 
168 ! ******************************************************************************
169 ! Start
170 ! ******************************************************************************
171 
172  global => pregion%global
173 
174  CALL registerfunction(global,'RFLU_TEC_BuildDataFieldSurf', &
175  'RFLU_ModTECPLOT.F90')
176 
177  IF ( global%verbLevel > verbose_none ) THEN
178  WRITE(stdout,'(A,1X,A)') solver_name, &
179  'Building surface data for TECPLOT field file...'
180  END IF ! global%verbLevel
181 
182 
183 ! ******************************************************************************
184 ! Set pointers
185 ! ******************************************************************************
186 
187  pgrid => pregion%grid
188 
189 ! ******************************************************************************
190 ! Set TECPLOT file context to field file
191 ! ******************************************************************************
192 
193  errorflag = tecfil100(filetype2cntrtec(file_type_field))
194  global%error = errorflag
195  IF ( global%error /= err_none ) THEN
196  CALL errorstop(global,err_tecplot_output,__line__)
197  END IF ! global%error
198 
199 ! ******************************************************************************
200 ! Count number of variables
201 ! ******************************************************************************
202 
203 ! ==============================================================================
204 ! Coordinates. NOTE do not add any data before coordinates!
205 ! ==============================================================================
206 
207  nvarstec = 3
208 
209 ! ==============================================================================
210 ! Solution
211 ! ==============================================================================
212 
213  IF ( global%postPlotType == plot_grid_flow ) THEN
214 
215 ! ------------------------------------------------------------------------------
216 ! Mixture
217 ! ------------------------------------------------------------------------------
218 
219  nvarstec = nvarstec + pregion%mixtInput%nCv &
220  + pregion%mixtInput%nDv &
221  + pregion%mixtInput%nGvAct &
222  + pregion%plot%nPv
223 
224 ! ------------------------------------------------------------------------------
225 ! Physical modules
226 ! ------------------------------------------------------------------------------
227 
228 #ifdef SPEC
229  IF ( global%specUsed .EQV. .true. ) THEN
230  nvarstec = nvarstec + pregion%specInput%nSpecies &
231 ! + pRegion%specInput%nSpeciesEE*EEV_SPEC_NVAR
232  + pregion%specInput%nSpeciesEE*4
233  END IF ! global%specUsed
234 #endif
235  END IF ! global%postPlotType
236 
237 ! ******************************************************************************
238 ! Set position of variables
239 ! ******************************************************************************
240 
241  ALLOCATE(postec(nvarstec),stat=errorflag)
242  global%error = errorflag
243  IF ( global%error /= err_none ) THEN
244  CALL errorstop(global,err_allocate,__line__,'posTEC')
245  END IF ! global%error
246 
247 ! ==============================================================================
248 ! Coordinates. NOTE do not add any data before coordinates!
249 ! ==============================================================================
250 
251  ivartot = 0
252 
253  DO ivar = 1,3
254  ivartot = ivartot + 1
255  postec(ivartot) = var_pos_vert
256  END DO ! iVar
257 
258 ! ==============================================================================
259 ! Mixture
260 ! ==============================================================================
261 
262  IF ( global%postPlotType == plot_grid_flow ) THEN
263 
264 ! ------------------------------------------------------------------------------
265 ! Vertex data
266 ! ------------------------------------------------------------------------------
267 
268  IF ( global%postInterpType /= interp_type_none ) THEN
269  DO ivar = 1,pregion%mixtInput%nCv
270  ivartot = ivartot + 1
271  postec(ivartot) = var_pos_vert
272  END DO ! iVar
273 
274  DO ivar = 1,pregion%mixtInput%nDv
275  ivartot = ivartot + 1
276  postec(ivartot) = var_pos_vert
277  END DO ! iVar
278 
279  DO ivar = 1,pregion%mixtInput%nGvAct
280  ivartot = ivartot + 1
281  postec(ivartot) = var_pos_vert
282  END DO ! iVar
283 
284  DO ivar = 1,pregion%plot%nPv
285  ivartot = ivartot + 1
286  postec(ivartot) = var_pos_vert
287  END DO ! iVar
288 
289 ! ------------------------------------------------------------------------------
290 ! Face data
291 ! ------------------------------------------------------------------------------
292 
293  ELSE
294  DO ivar = 1,pregion%mixtInput%nCv
295  ivartot = ivartot + 1
296  postec(ivartot) = var_pos_face
297  END DO ! iVar
298 
299  DO ivar = 1,pregion%mixtInput%nDv
300  ivartot = ivartot + 1
301  postec(ivartot) = var_pos_face
302  END DO ! iVar
303 
304  DO ivar = 1,pregion%mixtInput%nGvAct
305  ivartot = ivartot + 1
306  postec(ivartot) = var_pos_face
307  END DO ! iVar
308 
309  DO ivar = 1,pregion%plot%nPv
310  ivartot = ivartot + 1
311  postec(ivartot) = var_pos_face
312  END DO ! iVar
313  END IF ! global%postInterpType
314  END IF ! global%postPlotType
315 
316 ! ==============================================================================
317 ! Physical modules
318 ! ==============================================================================
319 
320  IF ( global%postPlotType == plot_grid_flow ) THEN
321 
322 ! ------------------------------------------------------------------------------
323 ! Vertex data
324 ! ------------------------------------------------------------------------------
325 
326  IF ( global%postInterpType /= interp_type_none ) THEN
327 #ifdef SPEC
328  IF ( global%specUsed .EQV. .true. ) THEN
329  DO ivar = 1,pregion%specInput%nSpecies
330  ivartot = ivartot + 1
331  postec(ivartot) = var_pos_vert
332  END DO ! iVar
333 
334 ! DO iVar = 1,pRegion%specInput%nSpeciesEE*EEV_SPEC_NVAR
335  DO ivar = 1,pregion%specInput%nSpeciesEE*4
336  ivartot = ivartot + 1
337  postec(ivartot) = var_pos_vert
338  END DO ! iVar
339  END IF ! global%specUsed
340 #endif
341 
342 ! ------------------------------------------------------------------------------
343 ! Face data
344 ! ------------------------------------------------------------------------------
345 
346  ELSE
347 #ifdef SPEC
348  IF ( global%specUsed .EQV. .true. ) THEN
349  DO ivar = 1,pregion%specInput%nSpecies
350  ivartot = ivartot + 1
351  postec(ivartot) = var_pos_face
352  END DO ! iVar
353 
354 ! DO iVar = 1,pRegion%specInput%nSpeciesEE*EEV_SPEC_NVAR
355  DO ivar = 1,pregion%specInput%nSpeciesEE*4
356  ivartot = ivartot + 1
357  postec(ivartot) = var_pos_face
358  END DO ! iVar
359  END IF ! global%specUsed
360 #endif
361  END IF ! global%postInterpType
362  END IF ! global%postPlotType
363 
364 ! ******************************************************************************
365 ! Determine how many variables of each position
366 ! ******************************************************************************
367 
368  nvarsfacetec = 0
369  nvarsverttec = 0
370 
371  DO ivar = 1,nvarstec
372  IF ( postec(ivar) == var_pos_face ) THEN
373  nvarsfacetec = nvarsfacetec + 1
374  ELSE IF ( postec(ivar) == var_pos_vert ) THEN
375  nvarsverttec = nvarsverttec + 1
376  ELSE
377  CALL errorstop(global,err_reached_default,__line__)
378  END IF ! posTEC
379  END DO ! iVar
380 
381 ! ******************************************************************************
382 ! Allocate memory
383 ! ******************************************************************************
384 
385  ALLOCATE(ppatch%varVertTEC(ppatch%nBVertTot,nvarsverttec),stat=errorflag)
386  global%error = errorflag
387  IF ( global%error /= err_none ) THEN
388  CALL errorstop(global,err_allocate,__line__,'pPatch%varVertTEC')
389  END IF ! global%error
390 
391  IF ( nvarsfacetec > 0 ) THEN
392  ALLOCATE(ppatch%varFaceTEC(ppatch%nBFacesTot,nvarsfacetec),stat=errorflag)
393  global%error = errorflag
394  IF ( global%error /= err_none ) THEN
395  CALL errorstop(global,err_allocate,__line__,'pPatch%varFaceTEC')
396  END IF ! global%error
397  ELSE
398  nullify(ppatch%varFaceTEC)
399  END IF ! nVarsFace
400 
401 ! ******************************************************************************
402 ! Assemble data
403 ! ******************************************************************************
404 
405  nvarsfacetot = 0
406  nvarsverttot = 0
407 
408 ! ==============================================================================
409 ! Coordinates. NOTE do not add any data before coordinates!
410 ! ==============================================================================
411 
412  DO ivl = 1,ppatch%nBVertTot
413  ivg = ppatch%bv(ivl)
414 
415  ppatch%varVertTEC(ivl,1) = pgrid%xyz(xcoord,ivg)
416  ppatch%varVertTEC(ivl,2) = pgrid%xyz(ycoord,ivg)
417  ppatch%varVertTEC(ivl,3) = pgrid%xyz(zcoord,ivg)
418  END DO ! ivl
419 
420  nvarsverttot = 3
421 
422 ! ==============================================================================
423 ! Variables
424 ! ==============================================================================
425 
426  IF ( global%postPlotType == plot_grid_flow ) THEN
427 
428 ! ------------------------------------------------------------------------------
429 ! Mixture
430 ! ------------------------------------------------------------------------------
431 
432 ! - Vertex data ----------------------------------------------------------------
433 
434  IF ( global%postInterpType /= interp_type_none ) THEN
435  DO ivl = 1,ppatch%nBVertTot
436  ivg = ppatch%bv(ivl)
437 
438  ivarverttot = nvarsverttot
439 
440  DO ivar = 1,pregion%mixtInput%nCv
441  ppatch%varVertTEC(ivl,ivarverttot+ivar) = &
442  pregion%mixt%cvVert(ivar,ivg)
443  END DO ! iVar
444 
445  ivarverttot = nvarsverttot + pregion%mixtInput%nCv
446 
447  DO ivar = 1,pregion%mixtInput%nDv
448  ppatch%varVertTEC(ivl,ivarverttot+ivar) = &
449  pregion%mixt%dvVert(ivar,ivg)
450  END DO ! iVar
451 
452  ivarverttot = nvarsverttot + pregion%mixtInput%nCv &
453  + pregion%mixtInput%nDv
454 
455  DO ivar = 1,pregion%mixtInput%nGvAct
456  ppatch%varVertTEC(ivl,ivarverttot+ivar) = &
457  pregion%mixt%gvVert(ivar,ivg)
458  END DO ! iVar
459 
460  ivarverttot = nvarsverttot + pregion%mixtInput%nCv &
461  + pregion%mixtInput%nDv &
462  + pregion%mixtInput%nGvAct
463 
464  DO ivar = 1,pregion%plot%nPv
465  ppatch%varVertTEC(ivl,ivarverttot+ivar) = &
466  pregion%plot%pvVert(ivar,ivg)
467  END DO ! iVar
468  END DO ! ivl
469 
470 ! - Face data ------------------------------------------------------------------
471 
472  ELSE
473  DO ifl = 1,ppatch%nBFacesTot
474  icg = ppatch%bf2c(ifl)
475 
476  ivarfacetot = nvarsfacetot
477 
478  DO ivar = 1,pregion%mixtInput%nCv
479  ppatch%varFaceTEC(ifl,ivarfacetot+ivar) = pregion%mixt%cv(ivar,icg)
480  END DO ! iVar
481 
482  ivarfacetot = nvarsfacetot + pregion%mixtInput%nCv
483 
484  DO ivar = 1,pregion%mixtInput%nDv
485  ppatch%varFaceTEC(ifl,ivarfacetot+ivar) = pregion%mixt%dv(ivar,icg)
486  END DO ! iVar
487 
488  ivarfacetot = nvarsfacetot + pregion%mixtInput%nCv &
489  + pregion%mixtInput%nDv
490 
491  DO ivar = 1,pregion%mixtInput%nGvAct
492  ppatch%varFaceTEC(ifl,ivarfacetot+ivar) = pregion%mixt%gv(ivar,icg)
493  END DO ! iVar
494 
495  ivarfacetot = nvarsfacetot + pregion%mixtInput%nCv &
496  + pregion%mixtInput%nDv &
497  + pregion%mixtInput%nGvAct
498 
499  DO ivar = 1,pregion%plot%nPv
500  ppatch%varFaceTEC(ifl,ivarfacetot+ivar) = pregion%plot%pv(ivar,icg)
501  END DO ! iVar
502  END DO ! ifl
503  END IF ! global%postInterpType
504 
505  IF ( global%postInterpType /= interp_type_none ) THEN
506  nvarsverttot = nvarsverttot + pregion%mixtInput%nCv &
507  + pregion%mixtInput%nDv &
508  + pregion%mixtInput%nGvAct &
509  + pregion%plot%nPv
510  ELSE
511  nvarsfacetot = nvarsfacetot + pregion%mixtInput%nCv &
512  + pregion%mixtInput%nDv &
513  + pregion%mixtInput%nGvAct &
514  + pregion%plot%nPv
515  END IF ! global%postInterpType
516 
517 ! ------------------------------------------------------------------------------
518 ! Physical modules
519 ! ------------------------------------------------------------------------------
520 
521  nvarsfacetotsave = nvarsfacetot
522  nvarsverttotsave = nvarsverttot
523 
524  IF ( global%postInterpType /= interp_type_none ) THEN
525 
526 ! --- Vertex data --------------------------------------------------------------
527 
528  nvarsverttot = nvarsverttotsave
529 
530 #ifdef SPEC
531  IF ( global%specUsed .EQV. .true. ) THEN
532  DO ivl = 1,ppatch%nBVertTot
533  ivg = ppatch%bv(ivl)
534 
535  ivarverttot = nvarsverttot
536 
537  DO ivar = 1,pregion%specInput%nSpecies
538  ppatch%varVertTEC(ivl,ivarverttot+ivar) &
539  = pregion%spec%cvVert(ivar,ivg)
540  END DO ! iVar
541  END DO ! ivl
542 
543  nvarsverttot = nvarsverttot + pregion%specInput%nSpecies
544 
545  DO ivl = 1,ppatch%nBVertTot
546  ivg = ppatch%bv(ivl)
547 
548  DO ivar = 1,pregion%specInput%nSpeciesEE
549  ivarverttot = nvarsverttot
550 
551 ! pPatch%varVertTEC(ivl,iVarVertTot+EEV_SPEC_NVAR*(iVar-1)+1) &
552 ! = pRegion%spec%eevVert(EEV_SPEC_XVEL,iVar,ivg)
553 ! pPatch%varVertTEC(ivl,iVarVertTot+EEV_SPEC_NVAR*(iVar-1)+2) &
554 ! = pRegion%spec%eevVert(EEV_SPEC_YVEL,iVar,ivg)
555 ! pPatch%varVertTEC(ivl,iVarVertTot+EEV_SPEC_NVAR*(iVar-1)+3) &
556 ! = pRegion%spec%eevVert(EEV_SPEC_ZVEL,iVar,ivg)
557 ! pPatch%varVertTEC(ivl,iVarVertTot+EEV_SPEC_NVAR*(iVar-1)+4) &
558 ! = pRegion%spec%eevVert(EEV_SPEC_TEMP,iVar,ivg)
559  ppatch%varVertTEC(ivl,ivarverttot+4*(ivar-1)+1) &
560  = pregion%spec%eevVert(1,ivar,ivg)
561  ppatch%varVertTEC(ivl,ivarverttot+4*(ivar-1)+2) &
562  = pregion%spec%eevVert(2,ivar,ivg)
563  ppatch%varVertTEC(ivl,ivarverttot+4*(ivar-1)+3) &
564  = pregion%spec%eevVert(3,ivar,ivg)
565  ppatch%varVertTEC(ivl,ivarverttot+4*(ivar-1)+4) &
566  = pregion%spec%eevVert(4,ivar,ivg)
567  END DO ! iVar
568  END DO ! ivl
569 
570 ! nVarsVertTot = nVarsVertTot + pRegion%specInput%nSpecies*EEV_SPEC_NVAR
571  nvarsverttot = nvarsverttot + pregion%specInput%nSpecies*4
572  END IF ! global%specUsed
573 #endif
574 
575 ! - Face data ------------------------------------------------------------------
576 
577  ELSE
578  nvarsfacetot = nvarsfacetotsave
579 
580 #ifdef SPEC
581  IF ( global%specUsed .EQV. .true. ) THEN
582  DO ifl = 1,ppatch%nBFacesTot
583  icg = ppatch%bf2c(ifl)
584 
585  ivarfacetot = nvarsfacetot
586 
587  DO ivar = 1,pregion%specInput%nSpecies
588  ppatch%varFaceTEC(ifl,ivarfacetot+ivar) &
589  = pregion%spec%cv(ivar,icg)
590  END DO ! iVar
591  END DO ! ifl
592 
593  nvarsfacetot = nvarsfacetot + pregion%specInput%nSpecies
594 
595  DO ifl = 1,ppatch%nBFacesTot
596  icg = ppatch%bf2c(ifl)
597 
598  DO ivar = 1,pregion%specInput%nSpeciesEE
599  ivarfacetot = nvarsfacetot
600 
601 ! pPatch%varFaceTEC(ifl,iVarFaceTot+EEV_SPEC_NVAR*(iVar-1)+1) &
602 ! = pRegion%spec%eev(EEV_SPEC_XVEL,iVar,icg)
603 ! pPatch%varFaceTEC(ifl,iVarFaceTot+EEV_SPEC_NVAR*(iVar-1)+2) &
604 ! = pRegion%spec%eev(EEV_SPEC_YVEL,iVar,icg)
605 ! pPatch%varFaceTEC(ifl,iVarFaceTot+EEV_SPEC_NVAR*(iVar-1)+3) &
606 ! = pRegion%spec%eev(EEV_SPEC_ZVEL,iVar,icg)
607 ! pPatch%varFaceTEC(ifl,iVarFaceTot+EEV_SPEC_NVAR*(iVar-1)+4) &
608 ! = pRegion%spec%eev(EEV_SPEC_TEMP,iVar,icg)
609  ppatch%varFaceTEC(ifl,ivarfacetot+4*(ivar-1)+1) &
610  = pregion%spec%eev(1,ivar,icg)
611  ppatch%varFaceTEC(ifl,ivarfacetot+4*(ivar-1)+2) &
612  = pregion%spec%eev(2,ivar,icg)
613  ppatch%varFaceTEC(ifl,ivarfacetot+4*(ivar-1)+3) &
614  = pregion%spec%eev(3,ivar,icg)
615  ppatch%varFaceTEC(ifl,ivarfacetot+4*(ivar-1)+4) &
616  = pregion%spec%eev(4,ivar,icg)
617  END DO ! iVar
618  END DO ! ifl
619 
620 ! nVarsFaceTot = nVarsFaceTot + pRegion%specInput%nSpecies*EEV_SPEC_NVAR
621  nvarsfacetot = nvarsfacetot + pregion%specInput%nSpecies*4
622  END IF ! global%specUsed
623 #endif
624  END IF ! global%postInterpType
625 
626  IF ( global%postInterpType /= interp_type_none ) THEN
627  nvarsverttot = nvarsverttot + pregion%specInput%nSpecies
628  ELSE
629  nvarsfacetot = nvarsfacetot + pregion%specInput%nSpecies
630  END IF ! global%postInterpType
631  END IF ! global%postPlotType
632 
633 ! ******************************************************************************
634 ! End
635 ! ******************************************************************************
636 
637  IF ( global%verbLevel > verbose_none ) THEN
638  WRITE(stdout,'(A,1X,A)') solver_name,'Building surface data for '// &
639  'TECPLOT field file done.'
640  END IF ! global%verbLevel
641 
642  CALL deregisterfunction(global)
643 
644 END SUBROUTINE rflu_tec_builddatafieldsurf
645 
646 
647 
648 
649 
650 
651 
652 ! ******************************************************************************
653 !
654 ! Purpose: Collect volume data for writing to TECPLOT field file.
655 !
656 ! Description: None.
657 !
658 ! Input:
659 ! pRegion Pointer to region
660 !
661 ! Output: None.
662 !
663 ! Notes:
664 ! 1. Isolated this code so that can easily add data for writing to file.
665 !
666 ! ******************************************************************************
667 
668 SUBROUTINE rflu_tec_builddatafieldvol(pRegion)
669 
670  IMPLICIT NONE
671 
672 ! ******************************************************************************
673 ! Declarations and definitions
674 ! ******************************************************************************
675 
676 ! ==============================================================================
677 ! Arguments
678 ! ==============================================================================
679 
680  TYPE(t_region), POINTER :: pregion
681 
682 ! ==============================================================================
683 ! Locals
684 ! ==============================================================================
685 
686  INTEGER :: errorflag,icg,ivar,ivartot,ivarcelltot,ivarverttot,ivg, &
687  nvarscelltot,nvarsverttot
688  TYPE(t_global), POINTER :: global
689  TYPE(t_grid), POINTER :: pgrid
690 
691 ! ==============================================================================
692 ! Externals: TECPLOT functions
693 ! ==============================================================================
694 
695  INTEGER, EXTERNAL :: tecfil100
696 
697 ! ******************************************************************************
698 ! Start
699 ! ******************************************************************************
700 
701  global => pregion%global
702 
703  CALL registerfunction(global,'RFLU_TEC_BuildDataFieldVol', &
704  'RFLU_ModTECPLOT.F90')
705 
706  IF ( global%verbLevel > verbose_none ) THEN
707  WRITE(stdout,'(A,1X,A)') solver_name, &
708  'Building volume data for TECPLOT field file...'
709  END IF ! global%verbLevel
710 
711 ! ******************************************************************************
712 ! Set pointers
713 ! ******************************************************************************
714 
715  pgrid => pregion%grid
716 
717 ! ******************************************************************************
718 ! Set TECPLOT file context to field file
719 ! ******************************************************************************
720 
721  errorflag = tecfil100(filetype2cntrtec(file_type_field))
722  global%error = errorflag
723  IF ( global%error /= err_none ) THEN
724  CALL errorstop(global,err_tecplot_output,__line__)
725  END IF ! global%error
726 
727 ! ******************************************************************************
728 ! Count number of variables
729 ! ******************************************************************************
730 
731 ! ==============================================================================
732 ! Coordinates. NOTE do not add any data before coordinates!
733 ! ==============================================================================
734 
735  nvarstec = 3
736 
737 ! ==============================================================================
738 ! Solution
739 ! ==============================================================================
740 
741  IF ( global%postPlotType == plot_grid_flow ) THEN
742 
743 ! ------------------------------------------------------------------------------
744 ! Mixture
745 ! ------------------------------------------------------------------------------
746 
747  nvarstec = nvarstec + pregion%mixtInput%nCv &
748  + pregion%mixtInput%nDv &
749  + pregion%mixtInput%nGvAct &
750  + pregion%plot%nPv
751 
752 ! ------------------------------------------------------------------------------
753 ! Physical modules
754 ! ------------------------------------------------------------------------------
755 
756 #ifdef SPEC
757  IF ( global%specUsed .EQV. .true. ) THEN
758  nvarstec = nvarstec + pregion%specInput%nSpecies &
759 ! + pRegion%specInput%nSpeciesEE*EEV_SPEC_NVAR
760  + pregion%specInput%nSpeciesEE*4
761  END IF ! global%specUsed
762 #endif
763  END IF ! global%postPlotType
764 
765 ! ******************************************************************************
766 ! Set position of variables
767 ! ******************************************************************************
768 
769  ALLOCATE(postec(nvarstec),stat=errorflag)
770  global%error = errorflag
771  IF ( global%error /= err_none ) THEN
772  CALL errorstop(global,err_allocate,__line__,'posTEC')
773  END IF ! global%error
774 
775 ! ==============================================================================
776 ! Coordinates. NOTE do not add any data before coordinates!
777 ! ==============================================================================
778 
779  ivartot = 0
780 
781  DO ivar = 1,3
782  ivartot = ivartot + 1
783  postec(ivartot) = var_pos_vert
784  END DO ! iVar
785 
786 ! ==============================================================================
787 ! Mixture
788 ! ==============================================================================
789 
790  IF ( global%postPlotType == plot_grid_flow ) THEN
791 
792 ! ------------------------------------------------------------------------------
793 ! Vertex data
794 ! ------------------------------------------------------------------------------
795 
796  IF ( global%postInterpType /= interp_type_none ) THEN
797  DO ivar = 1,pregion%mixtInput%nCv
798  ivartot = ivartot + 1
799  postec(ivartot) = var_pos_vert
800  END DO ! iVar
801 
802  DO ivar = 1,pregion%mixtInput%nDv
803  ivartot = ivartot + 1
804  postec(ivartot) = var_pos_vert
805  END DO ! iVar
806 
807  DO ivar = 1,pregion%mixtInput%nGvAct
808  ivartot = ivartot + 1
809  postec(ivartot) = var_pos_vert
810  END DO ! iVar
811 
812  DO ivar = 1,pregion%plot%nPv
813  ivartot = ivartot + 1
814  postec(ivartot) = var_pos_vert
815  END DO ! iVar
816 
817 ! ------------------------------------------------------------------------------
818 ! Cell data
819 ! ------------------------------------------------------------------------------
820 
821  ELSE
822  DO ivar = 1,pregion%mixtInput%nCv
823  ivartot = ivartot + 1
824  postec(ivartot) = var_pos_cell
825  END DO ! iVar
826 
827  DO ivar = 1,pregion%mixtInput%nDv
828  ivartot = ivartot + 1
829  postec(ivartot) = var_pos_cell
830  END DO ! iVar
831 
832  DO ivar = 1,pregion%mixtInput%nGvAct
833  ivartot = ivartot + 1
834  postec(ivartot) = var_pos_cell
835  END DO ! iVar
836 
837  DO ivar = 1,pregion%plot%nPv
838  ivartot = ivartot + 1
839  postec(ivartot) = var_pos_cell
840  END DO ! iVar
841  END IF ! global%postInterpType
842  END IF ! global%postPlotType
843 
844 ! ==============================================================================
845 ! Physical modules
846 ! ==============================================================================
847 
848  IF ( global%postPlotType == plot_grid_flow ) THEN
849 
850 ! ------------------------------------------------------------------------------
851 ! Vertex data
852 ! ------------------------------------------------------------------------------
853 
854  IF ( global%postInterpType /= interp_type_none ) THEN
855 #ifdef SPEC
856  IF ( global%specUsed .EQV. .true. ) THEN
857  DO ivar = 1,pregion%specInput%nSpecies
858  ivartot = ivartot + 1
859  postec(ivartot) = var_pos_vert
860  END DO ! iVar
861 
862 ! DO iVar = 1,pRegion%specInput%nSpeciesEE*EEV_SPEC_NVAR
863  DO ivar = 1,pregion%specInput%nSpeciesEE*4
864  ivartot = ivartot + 1
865  postec(ivartot) = var_pos_vert
866  END DO ! iVar
867  END IF ! global%specUsed
868 #endif
869 
870 ! ------------------------------------------------------------------------------
871 ! Vertex data
872 ! ------------------------------------------------------------------------------
873 
874  ELSE
875 #ifdef SPEC
876  IF ( global%specUsed .EQV. .true. ) THEN
877  DO ivar = 1,pregion%specInput%nSpecies
878  ivartot = ivartot + 1
879  postec(ivartot) = var_pos_cell
880  END DO ! iVar
881 
882 ! DO iVar = 1,pRegion%specInput%nSpeciesEE*EEV_SPEC_NVAR
883  DO ivar = 1,pregion%specInput%nSpeciesEE*4
884  ivartot = ivartot + 1
885  postec(ivartot) = var_pos_cell
886  END DO ! iVar
887  END IF ! global%specUsed
888 #endif
889  END IF ! global%postInterpType
890  END IF ! global%postPlotType
891 
892 ! ******************************************************************************
893 ! Determine how many variables of each position
894 ! ******************************************************************************
895 
896  nvarscelltec = 0
897  nvarsverttec = 0
898 
899  DO ivar = 1,nvarstec
900  IF ( postec(ivar) == var_pos_cell ) THEN
901  nvarscelltec = nvarscelltec + 1
902  ELSE IF ( postec(ivar) == var_pos_vert ) THEN
903  nvarsverttec = nvarsverttec + 1
904  ELSE
905  CALL errorstop(global,err_reached_default,__line__)
906  END IF ! posTEC
907  END DO ! iVar
908 
909 ! ******************************************************************************
910 ! Allocate memory
911 ! ******************************************************************************
912 
913  ALLOCATE(pregion%varVertTEC(pgrid%nVertTot,nvarsverttec),stat=errorflag)
914  global%error = errorflag
915  IF ( global%error /= err_none ) THEN
916  CALL errorstop(global,err_allocate,__line__,'pRegion%varVertTEC')
917  END IF ! global%error
918 
919  IF ( nvarscelltec > 0 ) THEN
920  ALLOCATE(pregion%varCellTEC(pgrid%nCellsTot,nvarscelltec),stat=errorflag)
921  global%error = errorflag
922  IF ( global%error /= err_none ) THEN
923  CALL errorstop(global,err_allocate,__line__,'pRegion%varCellTEC')
924  END IF ! global%error
925  ELSE
926  nullify(pregion%varCellTEC)
927  END IF ! nVarsCellTEC
928 
929 ! ******************************************************************************
930 ! Assemble data
931 ! ******************************************************************************
932 
933  nvarscelltot = 0
934  nvarsverttot = 0
935 
936 ! ==============================================================================
937 ! Coordinates. NOTE do not add any data before coordinates!
938 ! ==============================================================================
939 
940  DO ivg = 1,pgrid%nVertTot
941  pregion%varVertTEC(ivg,1) = pgrid%xyz(xcoord,ivg)
942  pregion%varVertTEC(ivg,2) = pgrid%xyz(ycoord,ivg)
943  pregion%varVertTEC(ivg,3) = pgrid%xyz(zcoord,ivg)
944  END DO ! ivg
945 
946  nvarsverttot = 3
947 
948 ! ==============================================================================
949 ! Variables
950 ! ==============================================================================
951 
952  IF ( global%postPlotType == plot_grid_flow ) THEN
953 
954 ! ------------------------------------------------------------------------------
955 ! Mixture
956 ! ------------------------------------------------------------------------------
957 
958 ! - Vertex data ----------------------------------------------------------------
959 
960  IF ( global%postInterpType /= interp_type_none ) THEN
961  DO ivg = 1,pgrid%nVertTot
962  ivarverttot = nvarsverttot
963 
964  DO ivar = 1,pregion%mixtInput%nCv
965  pregion%varVertTEC(ivg,ivarverttot+ivar) &
966  = pregion%mixt%cvVert(ivar,ivg)
967  END DO ! iVar
968 
969  ivarverttot = nvarsverttot + pregion%mixtInput%nCv
970 
971  DO ivar = 1,pregion%mixtInput%nDv
972  pregion%varVertTEC(ivg,ivarverttot+ivar) &
973  = pregion%mixt%dvVert(ivar,ivg)
974  END DO ! iVar
975 
976  ivarverttot = nvarsverttot + pregion%mixtInput%nCv &
977  + pregion%mixtInput%nDv
978 
979  DO ivar = 1,pregion%mixtInput%nGvAct
980  pregion%varVertTEC(ivg,ivarverttot+ivar) &
981  = pregion%mixt%gvVert(ivar,ivg)
982  END DO ! iVar
983 
984  ivarverttot = nvarsverttot + pregion%mixtInput%nCv &
985  + pregion%mixtInput%nDv &
986  + pregion%mixtInput%nGvAct
987 
988  DO ivar = 1,pregion%plot%nPv
989  pregion%varVertTEC(ivg,ivarverttot+ivar) &
990  = pregion%plot%pvVert(ivar,ivg)
991  END DO ! iVar
992  END DO ! ivg
993 
994  nvarsverttot = nvarsverttot + pregion%mixtInput%nCv &
995  + pregion%mixtInput%nDv &
996  + pregion%mixtInput%nGvAct &
997  + pregion%plot%nPv
998 
999 ! - Cell data ------------------------------------------------------------------
1000 
1001  ELSE
1002  DO icg = 1,pgrid%nCellsTot
1003  ivarcelltot = nvarscelltot
1004 
1005  DO ivar = 1,pregion%mixtInput%nCv
1006  pregion%varCellTEC(icg,ivarcelltot+ivar) = pregion%mixt%cv(ivar,icg)
1007  END DO ! iVar
1008 
1009  ivarcelltot = nvarscelltot + pregion%mixtInput%nCv
1010 
1011  DO ivar = 1,pregion%mixtInput%nDv
1012  pregion%varCellTEC(icg,ivarcelltot+ivar) = pregion%mixt%dv(ivar,icg)
1013  END DO ! iVar
1014 
1015  ivarcelltot = nvarscelltot + pregion%mixtInput%nCv &
1016  + pregion%mixtInput%nDv
1017 
1018  DO ivar = 1,pregion%mixtInput%nGvAct
1019  pregion%varCellTEC(icg,ivarcelltot+ivar) = pregion%mixt%gv(ivar,icg)
1020  END DO ! iVar
1021 
1022  ivarcelltot = nvarscelltot + pregion%mixtInput%nCv &
1023  + pregion%mixtInput%nDv &
1024  + pregion%mixtInput%nGvAct
1025 
1026  DO ivar = 1,pregion%plot%nPv
1027  pregion%varCellTEC(icg,ivarcelltot+ivar) = pregion%plot%pv(ivar,icg)
1028  END DO ! iVar
1029  END DO ! icg
1030 
1031  nvarscelltot = nvarscelltot + pregion%mixtInput%nCv &
1032  + pregion%mixtInput%nDv &
1033  + pregion%mixtInput%nGvAct &
1034  + pregion%plot%nPv
1035  END IF ! global%postInterpType
1036 
1037 ! ------------------------------------------------------------------------------
1038 ! Physical modules
1039 ! ------------------------------------------------------------------------------
1040 
1041 ! - Vertex data ----------------------------------------------------------------
1042 
1043  IF ( global%postInterpType /= interp_type_none ) THEN
1044 #ifdef SPEC
1045  IF ( global%specUsed .EQV. .true. ) THEN
1046  DO ivg = 1,pgrid%nVertTot
1047  DO ivar = 1,pregion%specInput%nSpecies
1048  ivarverttot = nvarsverttot
1049 
1050  pregion%varVertTEC(ivg,ivarverttot+ivar) &
1051  = pregion%spec%cvVert(ivar,ivg)
1052  END DO ! iVar
1053  END DO ! ivg
1054 
1055  nvarsverttot = nvarsverttot + pregion%specInput%nSpecies
1056 
1057  DO ivg = 1,pgrid%nVertTot
1058  DO ivar = 1,pregion%specInput%nSpeciesEE
1059  ivarverttot = nvarsverttot
1060 
1061 ! pRegion%varVertTEC(ivg,iVarVertTot+EEV_SPEC_NVAR*(iVar-1)+1) &
1062 ! = pRegion%spec%eevVert(EEV_SPEC_XVEL,iVar,ivg)
1063 ! pRegion%varVertTEC(ivg,iVarVertTot+EEV_SPEC_NVAR*(iVar-1)+2) &
1064 ! = pRegion%spec%eevVert(EEV_SPEC_YVEL,iVar,ivg)
1065 ! pRegion%varVertTEC(ivg,iVarVertTot+EEV_SPEC_NVAR*(iVar-1)+3) &
1066 ! = pRegion%spec%eevVert(EEV_SPEC_ZVEL,iVar,ivg)
1067 ! pRegion%varVertTEC(ivg,iVarVertTot+EEV_SPEC_NVAR*(iVar-1)+4) &
1068 ! = pRegion%spec%eevVert(EEV_SPEC_TEMP,iVar,ivg)
1069  pregion%varVertTEC(ivg,ivarverttot+4*(ivar-1)+1) &
1070  = pregion%spec%eevVert(1,ivar,ivg)
1071  pregion%varVertTEC(ivg,ivarverttot+4*(ivar-1)+2) &
1072  = pregion%spec%eevVert(2,ivar,ivg)
1073  pregion%varVertTEC(ivg,ivarverttot+4*(ivar-1)+3) &
1074  = pregion%spec%eevVert(3,ivar,ivg)
1075  pregion%varVertTEC(ivg,ivarverttot+4*(ivar-1)+4) &
1076  = pregion%spec%eevVert(4,ivar,ivg)
1077  END DO ! iVar
1078  END DO ! ivg
1079 
1080 ! nVarsVertTot = nVarsVertTot + pRegion%specInput%nSpecies*EEV_SPEC_NVAR
1081  nvarsverttot = nvarsverttot + pregion%specInput%nSpecies*4
1082  END IF ! global%specUsed
1083 #endif
1084  ELSE
1085 #ifdef SPEC
1086  IF ( global%specUsed .EQV. .true. ) THEN
1087  DO icg = 1,pgrid%nCellsTot
1088  DO ivar = 1,pregion%specInput%nSpecies
1089  ivarcelltot = nvarscelltot
1090 
1091  pregion%varCellTEC(icg,ivarcelltot+ivar) = pregion%spec%cv(ivar,icg)
1092  END DO ! iVar
1093  END DO ! icg
1094 
1095  nvarscelltot = nvarscelltot + pregion%specInput%nSpecies
1096 
1097  DO icg = 1,pgrid%nCellsTot
1098  DO ivar = 1,pregion%specInput%nSpeciesEE
1099  ivarcelltot = nvarscelltot
1100 
1101 ! pRegion%varCellTEC(icg,iVarCellTot+EEV_SPEC_NVAR*(iVar-1)+1) &
1102 ! = pRegion%spec%eev(EEV_SPEC_XVEL,iVar,icg)
1103 ! pRegion%varCellTEC(icg,iVarCellTot+EEV_SPEC_NVAR*(iVar-1)+2) &
1104 ! = pRegion%spec%eev(EEV_SPEC_YVEL,iVar,icg)
1105 ! pRegion%varCellTEC(icg,iVarCellTot+EEV_SPEC_NVAR*(iVar-1)+3) &
1106 ! = pRegion%spec%eev(EEV_SPEC_ZVEL,iVar,icg)
1107 ! pRegion%varCellTEC(icg,iVarCellTot+EEV_SPEC_NVAR*(iVar-1)+4) &
1108 ! = pRegion%spec%eev(EEV_SPEC_TEMP,iVar,icg)
1109  pregion%varCellTEC(icg,ivarcelltot+4*(ivar-1)+1) &
1110  = pregion%spec%eev(1,ivar,icg)
1111  pregion%varCellTEC(icg,ivarcelltot+4*(ivar-1)+2) &
1112  = pregion%spec%eev(2,ivar,icg)
1113  pregion%varCellTEC(icg,ivarcelltot+4*(ivar-1)+3) &
1114  = pregion%spec%eev(3,ivar,icg)
1115  pregion%varCellTEC(icg,ivarcelltot+4*(ivar-1)+4) &
1116  = pregion%spec%eev(4,ivar,icg)
1117  END DO ! iVar
1118  END DO ! icg
1119 
1120 ! nVarsCellTot = nVarsCellTot + pRegion%specInput%nSpecies*EEV_SPEC_NVAR
1121  nvarscelltot = nvarscelltot + pregion%specInput%nSpecies*4
1122  END IF ! global%specUsed
1123 #endif
1124  END IF ! global%postInterpType
1125 
1126  END IF ! global%postPlotType
1127 
1128 ! ******************************************************************************
1129 ! End
1130 ! ******************************************************************************
1131 
1132  IF ( global%verbLevel > verbose_none ) THEN
1133  WRITE(stdout,'(A,1X,A)') solver_name, &
1134  'Building volume data for TECPLOT field file done.'
1135  END IF ! global%verbLevel
1136 
1137  CALL deregisterfunction(global)
1138 
1139 END SUBROUTINE rflu_tec_builddatafieldvol
1140 
1141 
1142 
1143 
1144 
1145 
1146 
1147 ! ******************************************************************************
1148 !
1149 ! Purpose: Collect patch data for writing to TECPLOT patch file.
1150 !
1151 ! Description: None.
1152 !
1153 ! Input:
1154 ! pRegion Pointer to region data
1155 ! pPatch Pointer to patch data
1156 !
1157 ! Output: None.
1158 !
1159 ! Notes:
1160 ! 1. Isolated this code so that can easily add data for writing to file.
1161 !
1162 ! ******************************************************************************
1163 
1164 SUBROUTINE rflu_tec_builddatapatch(pRegion,pPatch)
1165 
1166  IMPLICIT NONE
1167 
1168 ! ******************************************************************************
1169 ! Declarations and definitions
1170 ! ******************************************************************************
1171 
1172 ! ==============================================================================
1173 ! Arguments
1174 ! ==============================================================================
1175 
1176  TYPE(t_patch), POINTER :: ppatch
1177  TYPE(t_region), POINTER :: pregion
1178 
1179 ! ==============================================================================
1180 ! Locals
1181 ! ==============================================================================
1182 
1183  INTEGER :: errorflag,ifg,ifl,ipatch,ivar,ivarfacetot,ivarverttot,ivartot, &
1184  ivg,ivl,nvarsfacetot,nvarsverttot
1185  TYPE(t_global), POINTER :: global
1186  TYPE(t_grid), POINTER :: pgrid
1187 
1188 ! ==============================================================================
1189 ! Externals: TECPLOT functions
1190 ! ==============================================================================
1191 
1192  INTEGER, EXTERNAL :: tecfil100
1193 
1194 ! ******************************************************************************
1195 ! Start
1196 ! ******************************************************************************
1197 
1198  global => pregion%global
1199 
1200  CALL registerfunction(global,'RFLU_TEC_BuildDataPatch', &
1201  'RFLU_ModTECPLOT.F90')
1202 
1203  IF ( global%verbLevel > verbose_none ) THEN
1204  WRITE(stdout,'(A,1X,A)') solver_name, &
1205  'Building data for TECPLOT patch file...'
1206  END IF ! global%verbLevel
1207 
1208 ! ******************************************************************************
1209 ! Set pointers
1210 ! ******************************************************************************
1211 
1212  pgrid => pregion%grid
1213 
1214 ! ******************************************************************************
1215 ! Set TECPLOT file context to patch file
1216 ! ******************************************************************************
1217 
1218  errorflag = tecfil100(filetype2cntrtec(file_type_patch))
1219  global%error = errorflag
1220  IF ( global%error /= err_none ) THEN
1221  CALL errorstop(global,err_tecplot_output,__line__)
1222  END IF ! global%error
1223 
1224 ! ******************************************************************************
1225 ! Count number of variables
1226 ! ******************************************************************************
1227 
1228 ! ==============================================================================
1229 ! Coordinates. NOTE do not add any data before coordinates!
1230 ! ==============================================================================
1231 
1232  nvarstec = 3
1233 
1234 ! ==============================================================================
1235 ! Mixture
1236 ! ==============================================================================
1237 
1238  IF ( global%postPlotType == plot_grid_flow ) THEN
1239  nvarstec = nvarstec + 5
1240  END IF ! global%postPlotType
1241 
1242 ! ==============================================================================
1243 ! Physical modules
1244 ! ==============================================================================
1245 
1246 ! ******************************************************************************
1247 ! Set position of variables
1248 ! ******************************************************************************
1249 
1250  ALLOCATE(postec(nvarstec),stat=errorflag)
1251  global%error = errorflag
1252  IF ( global%error /= err_none ) THEN
1253  CALL errorstop(global,err_allocate,__line__,'posTEC')
1254  END IF ! global%error
1255 
1256 ! ==============================================================================
1257 ! Coordinates. NOTE do not add any data before coordinates!
1258 ! ==============================================================================
1259 
1260  ivartot = 0
1261 
1262  DO ivar = 1,3
1263  ivartot = ivartot + 1
1264  postec(ivartot) = var_pos_vert
1265  END DO ! iVar
1266 
1267 ! ==============================================================================
1268 ! Mixture
1269 ! ==============================================================================
1270 
1271  IF ( global%postPlotType == plot_grid_flow ) THEN
1272  DO ivar = 1,5
1273  ivartot = ivartot + 1
1274  postec(ivartot) = var_pos_face
1275  END DO ! iVar
1276  END IF ! global%postPlotType
1277 
1278 ! ==============================================================================
1279 ! Physical modules
1280 ! ==============================================================================
1281 
1282 ! ******************************************************************************
1283 ! Determine how many variables of each position
1284 ! ******************************************************************************
1285 
1286  nvarsfacetec = 0
1287  nvarsverttec = 0
1288 
1289  DO ivar = 1,nvarstec
1290  IF ( postec(ivar) == var_pos_face ) THEN
1291  nvarsfacetec = nvarsfacetec + 1
1292  ELSE IF ( postec(ivar) == var_pos_vert ) THEN
1293  nvarsverttec = nvarsverttec + 1
1294  ELSE
1295  CALL errorstop(global,err_reached_default,__line__)
1296  END IF ! posTEC
1297  END DO ! iVar
1298 
1299 ! ******************************************************************************
1300 ! Allocate memory
1301 ! ******************************************************************************
1302 
1303  ALLOCATE(ppatch%varVertTEC(ppatch%nBVert,nvarsverttec),stat=errorflag)
1304  global%error = errorflag
1305  IF ( global%error /= err_none ) THEN
1306  CALL errorstop(global,err_allocate,__line__,'pPatch%varVertTEC')
1307  END IF ! global%error
1308 
1309  IF ( nvarsfacetec > 0 ) THEN
1310  ALLOCATE(ppatch%varFaceTEC(ppatch%nBFaces,nvarsfacetec),stat=errorflag)
1311  global%error = errorflag
1312  IF ( global%error /= err_none ) THEN
1313  CALL errorstop(global,err_allocate,__line__,'pPatch%varFaceTEC')
1314  END IF ! global%error
1315  ELSE
1316  nullify(ppatch%varFaceTEC)
1317  END IF ! nVarsFaceTEC
1318 
1319 ! ******************************************************************************
1320 ! Assemble data
1321 ! ******************************************************************************
1322 
1323 ! ==============================================================================
1324 ! Coordinates. NOTE do not add any data before coordinates!
1325 ! ==============================================================================
1326 
1327  DO ivl = 1,ppatch%nBVert
1328  ivg = ppatch%bv(ivl)
1329 
1330  ppatch%varVertTEC(ivl,1) = pgrid%xyz(xcoord,ivg)
1331  ppatch%varVertTEC(ivl,2) = pgrid%xyz(ycoord,ivg)
1332  ppatch%varVertTEC(ivl,3) = pgrid%xyz(zcoord,ivg)
1333  END DO ! ivl
1334 
1335  nvarsfacetot = 0
1336  nvarsverttot = 3
1337 
1338 ! ==============================================================================
1339 ! Variables
1340 ! ==============================================================================
1341 
1342  IF ( global%postPlotType == plot_grid_flow ) THEN
1343  nvarsfacetot = 0
1344 
1345 ! ------------------------------------------------------------------------------
1346 ! Mixture
1347 ! ------------------------------------------------------------------------------
1348 
1349  DO ifl = 1,ppatch%nBFaces
1350  ivarfacetot = nvarsfacetot
1351 
1352  ppatch%varFaceTEC(ifl,ivarfacetot+1) = ppatch%cp(ifl)
1353  ppatch%varFaceTEC(ifl,ivarfacetot+2) = ppatch%cf(xcoord,ifl)
1354  ppatch%varFaceTEC(ifl,ivarfacetot+3) = ppatch%cf(ycoord,ifl)
1355  ppatch%varFaceTEC(ifl,ivarfacetot+4) = ppatch%cf(zcoord,ifl)
1356  ppatch%varFaceTEC(ifl,ivarfacetot+5) = ppatch%ch(ifl)
1357  END DO ! ifl
1358 
1359  nvarsfacetot = nvarsfacetot + 5
1360 
1361 ! ------------------------------------------------------------------------------
1362 ! Physical modules
1363 ! ------------------------------------------------------------------------------
1364 
1365  END IF ! global%postPlotType
1366 
1367 ! ******************************************************************************
1368 ! End
1369 ! ******************************************************************************
1370 
1371  IF ( global%verbLevel > verbose_none ) THEN
1372  WRITE(stdout,'(A,1X,A)') solver_name, &
1373  'Building data for TECPLOT patch file done.'
1374  END IF ! global%verbLevel
1375 
1376  CALL deregisterfunction(global)
1377 
1378 END SUBROUTINE rflu_tec_builddatapatch
1379 
1380 
1381 
1382 
1383 
1384 
1385 
1386 
1387 
1388 ! ******************************************************************************
1389 !
1390 ! Purpose: Collect patch statistics data for writing to TECPLOT patch file.
1391 !
1392 ! Description: None.
1393 !
1394 ! Input:
1395 ! pRegion Pointer to region data
1396 ! pPatch Pointer to patch data
1397 !
1398 ! Output: None.
1399 !
1400 ! Notes:
1401 ! 1. Isolated this code so that can easily add data for writing to file.
1402 !
1403 ! ******************************************************************************
1404 
1405 SUBROUTINE rflu_tec_builddatapatchstats(pRegion,pPatch)
1406 
1407 #ifdef PLAG
1408  USE modpartlag, ONLY: t_surfstats_plag
1409 #endif
1410 
1411  IMPLICIT NONE
1412 
1413 ! ******************************************************************************
1414 ! Declarations and definitions
1415 ! ******************************************************************************
1416 
1417 ! ==============================================================================
1418 ! Arguments
1419 ! ==============================================================================
1420 
1421  TYPE(t_patch), POINTER :: ppatch
1422  TYPE(t_region), POINTER :: pregion
1423 
1424 ! ==============================================================================
1425 ! Locals
1426 ! ==============================================================================
1427 
1428  INTEGER :: errorflag,ifg,ifl,ipatch,ivar,ivarfacetot,ivarverttot,ivartot, &
1429  ivg,ivl,nvarsfacetot,nvarsverttot
1430  TYPE(t_global), POINTER :: global
1431  TYPE(t_grid), POINTER :: pgrid
1432 #ifdef PLAG
1433  INTEGER :: nbins
1434  TYPE(t_surfstats_plag), DIMENSION(:), POINTER :: pstatsplag
1435 #endif
1436 
1437 ! ==============================================================================
1438 ! Externals: TECPLOT functions
1439 ! ==============================================================================
1440 
1441  INTEGER, EXTERNAL :: tecfil100
1442 
1443 ! ******************************************************************************
1444 ! Start
1445 ! ******************************************************************************
1446 
1447  global => pregion%global
1448 
1449  CALL registerfunction(global,'RFLU_TEC_BuildDataPatchStats', &
1450  'RFLU_ModTECPLOT.F90')
1451 
1452  IF ( global%verbLevel > verbose_none ) THEN
1453  WRITE(stdout,'(A,1X,A)') solver_name, &
1454  'Building data for TECPLOT patch statistics file...'
1455  END IF ! global%verbLevel
1456 
1457 ! ******************************************************************************
1458 ! Set pointers
1459 ! ******************************************************************************
1460 
1461  pgrid => pregion%grid
1462 
1463 ! ******************************************************************************
1464 ! Set TECPLOT file context to patch statistics file
1465 ! ******************************************************************************
1466 
1467  errorflag = tecfil100(filetype2cntrtec(file_type_patch_stats))
1468  global%error = errorflag
1469  IF ( global%error /= err_none ) THEN
1470  CALL errorstop(global,err_tecplot_output,__line__)
1471  END IF ! global%error
1472 
1473 ! ******************************************************************************
1474 ! Count number of variables
1475 ! ******************************************************************************
1476 
1477 ! ==============================================================================
1478 ! Coordinates. NOTE do not add any data before coordinates!
1479 ! ==============================================================================
1480 
1481  nvarstec = 3
1482 
1483 ! ==============================================================================
1484 ! Mixture
1485 ! ==============================================================================
1486 
1487 ! ==============================================================================
1488 ! Physical modules
1489 ! ==============================================================================
1490 
1491 ! ------------------------------------------------------------------------------
1492 ! Lagrangian particle statistics
1493 ! ------------------------------------------------------------------------------
1494 
1495 #ifdef PLAG
1496  IF ( global%postPlotType == plot_grid_flow ) THEN
1497 ! TEMPORARY
1498  nbins = 20
1499 ! nBins = pRegion%plagInput%nBins
1500 ! END TEMPORARY
1501  nvarstec = nvarstec + nbins
1502  END IF ! global%postPlotType
1503 #endif
1504 
1505 ! ******************************************************************************
1506 ! Set position of variables
1507 ! ******************************************************************************
1508 
1509  ALLOCATE(postec(nvarstec),stat=errorflag)
1510  global%error = errorflag
1511  IF ( global%error /= err_none ) THEN
1512  CALL errorstop(global,err_allocate,__line__,'posTEC')
1513  END IF ! global%error
1514 
1515 ! ==============================================================================
1516 ! Coordinates. NOTE do not add any data before coordinates!
1517 ! ==============================================================================
1518 
1519  ivartot = 0
1520 
1521  DO ivar = 1,3
1522  ivartot = ivartot + 1
1523  postec(ivartot) = var_pos_vert
1524  END DO ! iVar
1525 
1526 ! ==============================================================================
1527 ! Mixture
1528 ! ==============================================================================
1529 
1530 ! ==============================================================================
1531 ! Physical modules
1532 ! ==============================================================================
1533 
1534 ! ------------------------------------------------------------------------------
1535 ! Lagrangian particle statistics
1536 ! ------------------------------------------------------------------------------
1537 
1538 #ifdef PLAG
1539  IF ( global%postPlotType == plot_grid_flow ) THEN
1540  DO ivar = 1,nbins
1541  ivartot = ivartot + 1
1542  postec(ivartot) = var_pos_face
1543  END DO ! iVar
1544  END IF ! global%postPlotType
1545 #endif
1546 
1547 ! ******************************************************************************
1548 ! Determine how many variables of each position
1549 ! ******************************************************************************
1550 
1551  nvarsfacetec = 0
1552  nvarsverttec = 0
1553 
1554  DO ivar = 1,nvarstec
1555  IF ( postec(ivar) == var_pos_face ) THEN
1556  nvarsfacetec = nvarsfacetec + 1
1557  ELSE IF ( postec(ivar) == var_pos_vert ) THEN
1558  nvarsverttec = nvarsverttec + 1
1559  ELSE
1560  CALL errorstop(global,err_reached_default,__line__)
1561  END IF ! posTEC
1562  END DO ! iVar
1563 
1564 ! ******************************************************************************
1565 ! Allocate memory
1566 ! ******************************************************************************
1567 
1568  ALLOCATE(ppatch%varVertTEC(ppatch%nBVert,nvarsverttec),stat=errorflag)
1569  global%error = errorflag
1570  IF ( global%error /= err_none ) THEN
1571  CALL errorstop(global,err_allocate,__line__,'pPatch%varVertTEC')
1572  END IF ! global%error
1573 
1574  IF ( nvarsfacetec > 0 ) THEN
1575  ALLOCATE(ppatch%varFaceTEC(ppatch%nBFaces,nvarsfacetec),stat=errorflag)
1576  global%error = errorflag
1577  IF ( global%error /= err_none ) THEN
1578  CALL errorstop(global,err_allocate,__line__,'pPatch%varFaceTEC')
1579  END IF ! global%error
1580  ELSE
1581  nullify(ppatch%varFaceTEC)
1582  END IF ! nVarsFaceTEC
1583 
1584 ! ******************************************************************************
1585 ! Assemble data
1586 ! ******************************************************************************
1587 
1588 ! ==============================================================================
1589 ! Coordinates. NOTE do not add any data before coordinates!
1590 ! ==============================================================================
1591 
1592  DO ivl = 1,ppatch%nBVert
1593  ivg = ppatch%bv(ivl)
1594 
1595  ppatch%varVertTEC(ivl,1) = pgrid%xyz(xcoord,ivg)
1596  ppatch%varVertTEC(ivl,2) = pgrid%xyz(ycoord,ivg)
1597  ppatch%varVertTEC(ivl,3) = pgrid%xyz(zcoord,ivg)
1598  END DO ! ivl
1599 
1600  nvarsfacetot = 0
1601  nvarsverttot = 3
1602 
1603 ! ==============================================================================
1604 ! Variables
1605 ! ==============================================================================
1606 
1607  IF ( global%postPlotType == plot_grid_flow ) THEN
1608  nvarsfacetot = 0
1609 
1610 ! ------------------------------------------------------------------------------
1611 ! Mixture
1612 ! ------------------------------------------------------------------------------
1613 
1614 ! ------------------------------------------------------------------------------
1615 ! Physical modules
1616 ! ------------------------------------------------------------------------------
1617 
1618 ! - Lagrangian particle statistics ---------------------------------------------
1619 
1620 #ifdef PLAG
1621  pstatsplag => ppatch%statsPlag
1622 
1623  DO ifl = 1,ppatch%nBFaces
1624  ivarfacetot = nvarsfacetot
1625 
1626  DO ivar = 1,nbins
1627  ppatch%varFaceTEC(ifl,ivarfacetot+ivar) = &
1628  REAL(pStatsPlag(ifl)%nHits(iVar),kind=rfreal)
1629  END DO ! iVar
1630  END DO ! ifl
1631 #endif
1632  END IF ! global%postPlotType
1633 
1634 ! ******************************************************************************
1635 ! End
1636 ! ******************************************************************************
1637 
1638  IF ( global%verbLevel > verbose_none ) THEN
1639  WRITE(stdout,'(A,1X,A)') solver_name, &
1640  'Building data for TECPLOT patch statistics file done.'
1641  END IF ! global%verbLevel
1642 
1643  CALL deregisterfunction(global)
1644 
1645 END SUBROUTINE rflu_tec_builddatapatchstats
1646 
1647 
1648 
1649 
1650 
1651 
1652 
1653 ! ******************************************************************************
1654 !
1655 ! Purpose: Build header for field data.
1656 !
1657 ! Description: None.
1658 !
1659 ! Input:
1660 ! pRegion Pointer to region
1661 !
1662 ! Output: None.
1663 !
1664 ! Notes: None.
1665 !
1666 ! ******************************************************************************
1667 
1668 SUBROUTINE rflu_tec_buildheaderfield(pRegion)
1669 
1670  IMPLICIT NONE
1671 
1672 ! ******************************************************************************
1673 ! Declarations and definitions
1674 ! ******************************************************************************
1675 
1676 ! ==============================================================================
1677 ! Arguments
1678 ! ==============================================================================
1679 
1680  TYPE(t_region), POINTER :: pregion
1681 
1682 ! ==============================================================================
1683 ! Locals
1684 ! ==============================================================================
1685 
1686  INTEGER :: ipv,ipv2,ivar
1687  TYPE(t_global), POINTER :: global
1688 
1689 ! ******************************************************************************
1690 ! Start
1691 ! ******************************************************************************
1692 
1693  global => pregion%global
1694 
1695  CALL registerfunction(global,'RFLU_TEC_BuildHeaderField', &
1696  'RFLU_ModTECPLOT.F90')
1697 
1698  IF ( global%verbLevel > verbose_low ) THEN
1699  WRITE(stdout,'(A,1X,A)') solver_name, &
1700  'Building header for TECPLOT field file...'
1701  END IF ! global%verbLevel
1702 
1703 ! ******************************************************************************
1704 ! Build header
1705 ! ******************************************************************************
1706 
1707 ! ==============================================================================
1708 ! Write grid only
1709 ! ==============================================================================
1710 
1711  IF ( global%postPlotType == plot_grid_only ) THEN
1712  WRITE(headertec,'(3(1X,A))') 'x','y','z'
1713  ELSE
1714 
1715 ! ==============================================================================
1716 ! Write grid and solution depending on fluid model
1717 ! ==============================================================================
1718 
1719  SELECT CASE ( pregion%mixtInput%fluidModel )
1720 
1721 ! ------------------------------------------------------------------------------
1722 ! Incompressible fluid model
1723 ! ------------------------------------------------------------------------------
1724 
1725  CASE ( fluid_model_incomp )
1726  WRITE(headertec,'(7(1X,A))') 'x','y','z', &
1727  'u','v','w','p'
1728 
1729 ! ------------------------------------------------------------------------------
1730 ! Compressible fluid model
1731 ! ------------------------------------------------------------------------------
1732 
1733  CASE ( fluid_model_comp )
1734  WRITE(headertec,'(11(1X,A))') 'x','y','z', &
1735  'r','ru','rv','rw','rE', &
1736  'p','T','a'
1737 
1738  DO ivar = 1,pregion%mixtInput%nGvAct
1739  WRITE(headertec,'(A,1X,A,I2.2)') trim(headertec),'GV',ivar
1740  END DO ! iVar
1741 
1742  DO ipv = 1,pregion%plot%nPv
1743  ipv2 = pregion%plot%pvi2pv(ipv)
1744 
1745  WRITE(headertec,'(A,1X,A)') trim(headertec), &
1746  trim(pregion%plot%pvNameShort(ipv2))
1747  END DO ! iPv
1748 
1749 #ifdef SPEC
1750  DO ivar = 1,pregion%specInput%nSpecies
1751  WRITE(headertec,'(A,1X,A,I2.2)') trim(headertec),'rY',ivar
1752  END DO ! iVar
1753 
1754  DO ivar = 1,pregion%specInput%nSpeciesEE
1755  WRITE(headertec,'(A,1X,A,I2.2)') trim(headertec),'u',ivar
1756  WRITE(headertec,'(A,1X,A,I2.2)') trim(headertec),'v',ivar
1757  WRITE(headertec,'(A,1X,A,I2.2)') trim(headertec),'w',ivar
1758  WRITE(headertec,'(A,1X,A,I2.2)') trim(headertec),'T',ivar
1759  END DO ! iVar
1760 #endif
1761 
1762 ! ------------------------------------------------------------------------------
1763 ! Default
1764 ! ------------------------------------------------------------------------------
1765 
1766  CASE default
1767  CALL errorstop(global,err_reached_default,__line__)
1768  END SELECT ! pRegion%mixtInput%fluidModel
1769  END IF ! global%postPlotType
1770 
1771 ! ******************************************************************************
1772 ! End
1773 ! ******************************************************************************
1774 
1775  IF ( global%verbLevel > verbose_low ) THEN
1776  WRITE(stdout,'(A,1X,A)') solver_name, &
1777  'Building header for TECPLOT field file done.'
1778  END IF ! global%verbLevel
1779 
1780  CALL deregisterfunction(global)
1781 
1782 END SUBROUTINE rflu_tec_buildheaderfield
1783 
1784 
1785 
1786 
1787 
1788 
1789 ! ******************************************************************************
1790 !
1791 ! Purpose: Build header for patch data.
1792 !
1793 ! Description: None.
1794 !
1795 ! Input:
1796 ! pRegion Pointer to region
1797 !
1798 ! Output: None.
1799 !
1800 ! Notes: None.
1801 !
1802 ! ******************************************************************************
1803 
1804 SUBROUTINE rflu_tec_buildheaderpatch(pRegion)
1805 
1806  IMPLICIT NONE
1807 
1808 ! ******************************************************************************
1809 ! Declarations and definitions
1810 ! ******************************************************************************
1811 
1812 ! ==============================================================================
1813 ! Arguments
1814 ! ==============================================================================
1815 
1816  TYPE(t_region), POINTER :: pregion
1817 
1818 ! ==============================================================================
1819 ! Locals
1820 ! ==============================================================================
1821 
1822  INTEGER :: ivar
1823  TYPE(t_global), POINTER :: global
1824 
1825 ! ******************************************************************************
1826 ! Start
1827 ! ******************************************************************************
1828 
1829  global => pregion%global
1830 
1831  CALL registerfunction(global,'RFLU_TEC_BuildHeaderPatch', &
1832  'RFLU_ModTECPLOT.F90')
1833 
1834  IF ( global%verbLevel > verbose_low ) THEN
1835  WRITE(stdout,'(A,1X,A)') solver_name, &
1836  'Building header for TECPLOT patch file...'
1837  END IF ! global%verbLevel
1838 
1839 ! ******************************************************************************
1840 ! Build header
1841 ! ******************************************************************************
1842 
1843 ! ==============================================================================
1844 ! Mixture
1845 ! ==============================================================================
1846 
1847  IF ( global%postPlotType == plot_grid_only ) THEN
1848  WRITE(headertec,'(3(1X,A))') 'x','y','z'
1849  ELSE
1850  WRITE(headertec,'(8(1X,A))') 'x','y','z', &
1851  'Cp','Cfx','Cfy','Cfz','Ch'
1852  END IF ! global%postPlotType
1853 
1854 ! ==============================================================================
1855 ! Physical modules
1856 ! ==============================================================================
1857 
1858 ! ******************************************************************************
1859 ! End
1860 ! ******************************************************************************
1861 
1862  IF ( global%verbLevel > verbose_low ) THEN
1863  WRITE(stdout,'(A,1X,A)') solver_name, &
1864  'Building header for TECPLOT patch file done.'
1865  END IF ! global%verbLevel
1866 
1867  CALL deregisterfunction(global)
1868 
1869 END SUBROUTINE rflu_tec_buildheaderpatch
1870 
1871 
1872 
1873 
1874 
1875 
1876 
1877 
1878 ! ******************************************************************************
1879 !
1880 ! Purpose: Build header for patch statistics data.
1881 !
1882 ! Description: None.
1883 !
1884 ! Input:
1885 ! pRegion Pointer to region
1886 !
1887 ! Output: None.
1888 !
1889 ! Notes: None.
1890 !
1891 ! ******************************************************************************
1892 
1894 
1895  IMPLICIT NONE
1896 
1897 ! ******************************************************************************
1898 ! Declarations and definitions
1899 ! ******************************************************************************
1900 
1901 ! ==============================================================================
1902 ! Arguments
1903 ! ==============================================================================
1904 
1905  TYPE(t_region), POINTER :: pregion
1906 
1907 ! ==============================================================================
1908 ! Locals
1909 ! ==============================================================================
1910 
1911  INTEGER :: ivar
1912 #ifdef PLAG
1913  INTEGER :: nbins
1914 #endif
1915  TYPE(t_global), POINTER :: global
1916 
1917 ! ******************************************************************************
1918 ! Start
1919 ! ******************************************************************************
1920 
1921  global => pregion%global
1922 
1923  CALL registerfunction(global,'RFLU_TEC_BuildHeaderPatchStats', &
1924  'RFLU_ModTECPLOT.F90')
1925 
1926  IF ( global%verbLevel > verbose_low ) THEN
1927  WRITE(stdout,'(A,1X,A)') solver_name, &
1928  'Building header for TECPLOT patch statistics file...'
1929  END IF ! global%verbLevel
1930 
1931 ! ******************************************************************************
1932 ! Build header
1933 ! ******************************************************************************
1934 
1935 ! ==============================================================================
1936 ! Mixture
1937 ! ==============================================================================
1938 
1939  WRITE(headertec,'(3(1X,A))') 'x','y','z'
1940 
1941 ! ==============================================================================
1942 ! Physical modules
1943 ! ==============================================================================
1944 
1945 ! ------------------------------------------------------------------------------
1946 ! Lagrangian particle statistics
1947 ! ------------------------------------------------------------------------------
1948 
1949 #ifdef PLAG
1950  IF ( global%postPlotType == plot_grid_flow ) THEN
1951 ! TEMPORARY
1952  nbins = 20
1953 ! nBins = pRegion%plagInput%nBins
1954 ! END TEMPORARY
1955 
1956  DO ivar = 1,nbins
1957  WRITE(headertec,'(A,1X,A,I2.2)') trim(headertec),'nH',ivar
1958  END DO ! iVar
1959  END IF ! global%postPlotType
1960 #endif
1961 
1962 ! ******************************************************************************
1963 ! End
1964 ! ******************************************************************************
1965 
1966  IF ( global%verbLevel > verbose_low ) THEN
1967  WRITE(stdout,'(A,1X,A)') solver_name, &
1968  'Building header for TECPLOT patch statistics file done.'
1969  END IF ! global%verbLevel
1970 
1971  CALL deregisterfunction(global)
1972 
1973 END SUBROUTINE rflu_tec_buildheaderpatchstats
1974 
1975 
1976 
1977 
1978 
1979 
1980 
1981 
1982 ! ******************************************************************************
1983 !
1984 ! Purpose: Close TECPLOT field file.
1985 !
1986 ! Description: None.
1987 !
1988 ! Input:
1989 ! global Pointer to global type
1990 !
1991 ! Output: None.
1992 !
1993 ! Notes:
1994 ! 1. Isolated into separate routine so that can write several zones to same
1995 ! TECPLOT file.
1996 !
1997 ! ******************************************************************************
1998 
1999 SUBROUTINE rflu_tec_closefilefield(global)
2000 
2001 ! ******************************************************************************
2002 ! Declarations and definitions
2003 ! ******************************************************************************
2004 
2005 ! ==============================================================================
2006 ! Arguments
2007 ! ==============================================================================
2008 
2009  TYPE(t_global), POINTER :: global
2010 
2011 ! ==============================================================================
2012 ! Locals
2013 ! ==============================================================================
2014 
2015  INTEGER :: errorflag
2016 
2017 ! ==============================================================================
2018 ! Externals: TECPLOT functions
2019 ! ==============================================================================
2020 
2021  INTEGER, EXTERNAL :: tecfil100
2022 
2023 ! ******************************************************************************
2024 ! Start
2025 ! ******************************************************************************
2026 
2027  CALL registerfunction(global,'RFLU_TEC_CloseFileField', &
2028  'RFLU_ModTECPLOT.F90')
2029 
2030  IF ( global%verbLevel > verbose_none ) THEN
2031  WRITE(stdout,'(A,1X,A)') solver_name,'Closing TECPLOT field file...'
2032  WRITE(stdout,'(A,3X,A)') solver_name,'Be patient, this may take a while...'
2033  END IF ! global%verbLevel
2034 
2035 ! ******************************************************************************
2036 ! Set TECPLOT file context to field file
2037 ! ******************************************************************************
2038 
2039  errorflag = tecfil100(filetype2cntrtec(file_type_field))
2040  global%error = errorflag
2041  IF ( global%error /= err_none ) THEN
2042  CALL errorstop(global,err_tecplot_output,__line__)
2043  END IF ! global%error
2044 
2045 ! ******************************************************************************
2046 ! Close file
2047 ! ******************************************************************************
2048 
2049  CALL rflu_tec_closefile(global)
2050 
2051  filecntrtec = filecntrtec - 1
2052 
2053 ! ******************************************************************************
2054 ! End
2055 ! ******************************************************************************
2056 
2057  IF ( global%verbLevel > verbose_none ) THEN
2058  WRITE(stdout,'(A,1X,A)') solver_name,'Closing TECPLOT field file done.'
2059  END IF ! global%verbLevel
2060 
2061  CALL deregisterfunction(global)
2062 
2063 END SUBROUTINE rflu_tec_closefilefield
2064 
2065 
2066 
2067 
2068 
2069 
2070 
2071 ! ******************************************************************************
2072 !
2073 ! Purpose: Close TECPLOT patch file.
2074 !
2075 ! Description: None.
2076 !
2077 ! Input:
2078 ! global Pointer to global type
2079 !
2080 ! Output: None.
2081 !
2082 ! Notes:
2083 ! 1. Isolated into separate routine so that can write several zones to same
2084 ! TECPLOT file.
2085 !
2086 ! ******************************************************************************
2087 
2088 SUBROUTINE rflu_tec_closefilepatch(global)
2089 
2090 ! ******************************************************************************
2091 ! Declarations and definitions
2092 ! ******************************************************************************
2093 
2094 ! ==============================================================================
2095 ! Locals
2096 ! ==============================================================================
2097 
2098  INTEGER :: errorflag
2099 
2100 ! ==============================================================================
2101 ! Arguments
2102 ! ==============================================================================
2103 
2104  TYPE(t_global), POINTER :: global
2105 
2106 ! ==============================================================================
2107 ! Externals: TECPLOT functions
2108 ! ==============================================================================
2109 
2110  INTEGER, EXTERNAL :: tecfil100
2111 
2112 ! ******************************************************************************
2113 ! Start
2114 ! ******************************************************************************
2115 
2116  CALL registerfunction(global,'RFLU_TEC_CloseFilePatch', &
2117  'RFLU_ModTECPLOT.F90')
2118 
2119  IF ( global%verbLevel > verbose_none ) THEN
2120  WRITE(stdout,'(A,1X,A)') solver_name,'Closing TECPLOT patch file...'
2121  WRITE(stdout,'(A,3X,A)') solver_name,'Be patient, this may take a while...'
2122  END IF ! global%verbLevel
2123 
2124 ! ******************************************************************************
2125 ! Set TECPLOT file context to field file
2126 ! ******************************************************************************
2127 
2128  errorflag = tecfil100(filetype2cntrtec(file_type_patch))
2129  global%error = errorflag
2130  IF ( global%error /= err_none ) THEN
2131  CALL errorstop(global,err_tecplot_output,__line__)
2132  END IF ! global%error
2133 
2134 ! ******************************************************************************
2135 ! Close file
2136 ! ******************************************************************************
2137 
2138  CALL rflu_tec_closefile(global)
2139 
2140  filecntrtec = filecntrtec - 1
2141 
2142 ! ******************************************************************************
2143 ! End
2144 ! ******************************************************************************
2145 
2146  IF ( global%verbLevel > verbose_none ) THEN
2147  WRITE(stdout,'(A,1X,A)') solver_name,'Closing TECPLOT patch file done.'
2148  END IF ! global%verbLevel
2149 
2150  CALL deregisterfunction(global)
2151 
2152 END SUBROUTINE rflu_tec_closefilepatch
2153 
2154 
2155 
2156 
2157 
2158 
2159 ! ******************************************************************************
2160 !
2161 ! Purpose: Close TECPLOT patch statistics file.
2162 !
2163 ! Description: None.
2164 !
2165 ! Input:
2166 ! global Pointer to global type
2167 !
2168 ! Output: None.
2169 !
2170 ! Notes:
2171 ! 1. Isolated into separate routine so that can write several zones to same
2172 ! TECPLOT file.
2173 !
2174 ! ******************************************************************************
2175 
2177 
2178 ! ******************************************************************************
2179 ! Declarations and definitions
2180 ! ******************************************************************************
2181 
2182 ! ==============================================================================
2183 ! Locals
2184 ! ==============================================================================
2185 
2186  INTEGER :: errorflag
2187 
2188 ! ==============================================================================
2189 ! Arguments
2190 ! ==============================================================================
2191 
2192  TYPE(t_global), POINTER :: global
2193 
2194 ! ==============================================================================
2195 ! Externals: TECPLOT functions
2196 ! ==============================================================================
2197 
2198  INTEGER, EXTERNAL :: tecfil100
2199 
2200 ! ******************************************************************************
2201 ! Start
2202 ! ******************************************************************************
2203 
2204  CALL registerfunction(global,'RFLU_TEC_CloseFilePatchStats', &
2205  'RFLU_ModTECPLOT.F90')
2206 
2207  IF ( global%verbLevel > verbose_none ) THEN
2208  WRITE(stdout,'(A,1X,A)') solver_name, &
2209  'Closing TECPLOT patch statistics file...'
2210  WRITE(stdout,'(A,3X,A)') solver_name,'Be patient, this may take a while...'
2211  END IF ! global%verbLevel
2212 
2213 ! ******************************************************************************
2214 ! Set TECPLOT file context to field file
2215 ! ******************************************************************************
2216 
2217  errorflag = tecfil100(filetype2cntrtec(file_type_patch_stats))
2218  global%error = errorflag
2219  IF ( global%error /= err_none ) THEN
2220  CALL errorstop(global,err_tecplot_output,__line__)
2221  END IF ! global%error
2222 
2223 ! ******************************************************************************
2224 ! Close file
2225 ! ******************************************************************************
2226 
2227  CALL rflu_tec_closefile(global)
2228 
2229  filecntrtec = filecntrtec - 1
2230 
2231 ! ******************************************************************************
2232 ! End
2233 ! ******************************************************************************
2234 
2235  IF ( global%verbLevel > verbose_none ) THEN
2236  WRITE(stdout,'(A,1X,A)') solver_name, &
2237  'Closing TECPLOT patch statistics file done.'
2238  END IF ! global%verbLevel
2239 
2240  CALL deregisterfunction(global)
2241 
2242 END SUBROUTINE rflu_tec_closefilepatchstats
2243 
2244 
2245 
2246 
2247 
2248 
2249 
2250 ! ******************************************************************************
2251 !
2252 ! Purpose: Close TECPLOT point file.
2253 !
2254 ! Description: None.
2255 !
2256 ! Input:
2257 ! global Pointer to global type
2258 !
2259 ! Output: None.
2260 !
2261 ! Notes:
2262 ! 1. Isolated into separate routine so that can write several zones to same
2263 ! TECPLOT file.
2264 !
2265 ! ******************************************************************************
2266 
2267 SUBROUTINE rflu_tec_closefilepnt(global)
2268 
2269 ! ******************************************************************************
2270 ! Declarations and definitions
2271 ! ******************************************************************************
2272 
2273 ! ==============================================================================
2274 ! Arguments
2275 ! ==============================================================================
2276 
2277  TYPE(t_global), POINTER :: global
2278 
2279 ! ==============================================================================
2280 ! Locals
2281 ! ==============================================================================
2282 
2283  INTEGER :: errorflag
2284 
2285 ! ******************************************************************************
2286 ! Start
2287 ! ******************************************************************************
2288 
2289  CALL registerfunction(global,'RFLU_TEC_CloseFilePnt', &
2290  'RFLU_ModTECPLOT.F90')
2291 
2292  IF ( global%verbLevel > verbose_none ) THEN
2293  WRITE(stdout,'(A,1X,A)') solver_name,'Closing TECPLOT point file...'
2294  WRITE(stdout,'(A,3X,A)') solver_name,'Be patient, this may take a while...'
2295  END IF ! global%verbLevel
2296 
2297 ! ******************************************************************************
2298 ! Close file
2299 ! ******************************************************************************
2300 
2301  CLOSE(if_plot,iostat=errorflag)
2302  global%error = errorflag
2303  IF ( global%error /= err_none ) THEN
2304  CALL errorstop(global,err_file_close,__line__)
2305  END IF ! global%error
2306 
2307 ! ******************************************************************************
2308 ! End
2309 ! ******************************************************************************
2310 
2311  IF ( global%verbLevel > verbose_none ) THEN
2312  WRITE(stdout,'(A,1X,A)') solver_name,'Closing TECPLOT point file done.'
2313  END IF ! global%verbLevel
2314 
2315  CALL deregisterfunction(global)
2316 
2317 END SUBROUTINE rflu_tec_closefilepnt
2318 
2319 
2320 
2321 
2322 
2323 
2324 
2325 
2326 ! ******************************************************************************
2327 !
2328 ! Purpose: Destroy surface field data for writing to TECPLOT file.
2329 !
2330 ! Description: None.
2331 !
2332 ! Input:
2333 ! pRegion Pointer to region data
2334 ! pPatch Pointer to patch data
2335 !
2336 ! Output: None.
2337 !
2338 ! Notes: None.
2339 !
2340 ! ******************************************************************************
2341 
2342 SUBROUTINE rflu_tec_destroydatafieldsurf(pRegion,pPatch)
2343 
2344  IMPLICIT NONE
2345 
2346 ! ******************************************************************************
2347 ! Declarations and definitions
2348 ! ******************************************************************************
2349 
2350 ! ==============================================================================
2351 ! Arguments
2352 ! ==============================================================================
2353 
2354  TYPE(t_patch), POINTER :: ppatch
2355  TYPE(t_region), POINTER :: pregion
2356 
2357 ! ==============================================================================
2358 ! Locals
2359 ! ==============================================================================
2360 
2361  INTEGER :: errorflag
2362  TYPE(t_global), POINTER :: global
2363 
2364 ! ******************************************************************************
2365 ! Start
2366 ! ******************************************************************************
2367 
2368  global => pregion%global
2369 
2370  CALL registerfunction(global,'RFLU_TEC_DestroyDataFieldSurf', &
2371  'RFLU_ModTECPLOT.F90')
2372 
2373  IF ( global%verbLevel > verbose_none ) THEN
2374  WRITE(stdout,'(A,1X,A)') solver_name, &
2375  'Destroying TECPLOT surface field data...'
2376  END IF ! global%verbLevel
2377 
2378 ! ******************************************************************************
2379 ! Deallocate memory
2380 ! ******************************************************************************
2381 
2382  DEALLOCATE(postec,stat=errorflag)
2383  global%error = errorflag
2384  IF ( global%error /= err_none ) THEN
2385  CALL errorstop(global,err_deallocate,__line__,'posTEC')
2386  END IF ! global%error
2387 
2388  DEALLOCATE(ppatch%varVertTEC,stat=errorflag)
2389  global%error = errorflag
2390  IF ( global%error /= err_none ) THEN
2391  CALL errorstop(global,err_deallocate,__line__,'pPatch%varVertTEC')
2392  END IF ! global%error
2393 
2394  IF ( ASSOCIATED(ppatch%varFaceTEC) .EQV. .true. ) THEN
2395  DEALLOCATE(ppatch%varFaceTEC,stat=errorflag)
2396  global%error = errorflag
2397  IF ( global%error /= err_none ) THEN
2398  CALL errorstop(global,err_deallocate,__line__,'pPatch%varFaceTEC')
2399  END IF ! global%error
2400  END IF ! ASSOCIATED
2401 
2402 ! ******************************************************************************
2403 ! End
2404 ! ******************************************************************************
2405 
2406  IF ( global%verbLevel > verbose_none ) THEN
2407  WRITE(stdout,'(A,1X,A)') solver_name, &
2408  'Destroying TECPLOT surface field data done.'
2409  END IF ! global%verbLevel
2410 
2411  CALL deregisterfunction(global)
2412 
2413 END SUBROUTINE rflu_tec_destroydatafieldsurf
2414 
2415 
2416 
2417 
2418 
2419 
2420 
2421 ! ******************************************************************************
2422 !
2423 ! Purpose: Destroy volume field data for writing to TECPLOT file.
2424 !
2425 ! Description: None.
2426 !
2427 ! Input:
2428 ! pRegion Pointer to region
2429 !
2430 ! Output: None.
2431 !
2432 ! Notes: None.
2433 !
2434 ! ******************************************************************************
2435 
2436 SUBROUTINE rflu_tec_destroydatafieldvol(pRegion)
2437 
2438  IMPLICIT NONE
2439 
2440 ! ******************************************************************************
2441 ! Declarations and definitions
2442 ! ******************************************************************************
2443 
2444 ! ==============================================================================
2445 ! Arguments
2446 ! ==============================================================================
2447 
2448  TYPE(t_global), POINTER :: global
2449  TYPE(t_region), POINTER :: pregion
2450 
2451 ! ==============================================================================
2452 ! Locals
2453 ! ==============================================================================
2454 
2455  INTEGER :: errorflag
2456 
2457 ! ******************************************************************************
2458 ! Start
2459 ! ******************************************************************************
2460 
2461  global => pregion%global
2462 
2463  CALL registerfunction(global,'RFLU_TEC_DestroyDataFieldVol', &
2464  'RFLU_ModTECPLOT.F90')
2465 
2466  IF ( global%verbLevel > verbose_none ) THEN
2467  WRITE(stdout,'(A,1X,A)') solver_name, &
2468  'Destroying TECPLOT volume field data...'
2469  END IF ! global%verbLevel
2470 
2471 ! ******************************************************************************
2472 ! Deallocate memory
2473 ! ******************************************************************************
2474 
2475  DEALLOCATE(postec,stat=errorflag)
2476  global%error = errorflag
2477  IF ( global%error /= err_none ) THEN
2478  CALL errorstop(global,err_deallocate,__line__,'posTEC')
2479  END IF ! global%error
2480 
2481  DEALLOCATE(pregion%varVertTEC,stat=errorflag)
2482  global%error = errorflag
2483  IF ( global%error /= err_none ) THEN
2484  CALL errorstop(global,err_deallocate,__line__,'pRegion%varVertTEC')
2485  END IF ! global%error
2486 
2487  IF ( ASSOCIATED(pregion%varCellTEC) .EQV. .true. ) THEN
2488  DEALLOCATE(pregion%varCellTEC,stat=errorflag)
2489  global%error = errorflag
2490  IF ( global%error /= err_none ) THEN
2491  CALL errorstop(global,err_deallocate,__line__,'pRegion%varCellTEC')
2492  END IF ! global%error
2493  END IF ! ASSOCIATED
2494 
2495 ! ******************************************************************************
2496 ! End
2497 ! ******************************************************************************
2498 
2499  IF ( global%verbLevel > verbose_none ) THEN
2500  WRITE(stdout,'(A,1X,A)') solver_name, &
2501  'Destroying TECPLOT volume field data done.'
2502  END IF ! global%verbLevel
2503 
2504  CALL deregisterfunction(global)
2505 
2506 END SUBROUTINE rflu_tec_destroydatafieldvol
2507 
2508 
2509 
2510 
2511 
2512 
2513 
2514 ! ******************************************************************************
2515 !
2516 ! Purpose: Destroy patch data for writing to TECPLOT file.
2517 !
2518 ! Description: None.
2519 !
2520 ! Input:
2521 ! pRegion Pointer to region data
2522 ! pPatch Pointer to patch data
2523 !
2524 ! Output: None.
2525 !
2526 ! Notes: None.
2527 !
2528 ! ******************************************************************************
2529 
2530 SUBROUTINE rflu_tec_destroydatapatch(pRegion,pPatch)
2531 
2532  IMPLICIT NONE
2533 
2534 ! ******************************************************************************
2535 ! Declarations and definitions
2536 ! ******************************************************************************
2537 
2538 ! ==============================================================================
2539 ! Arguments
2540 ! ==============================================================================
2541 
2542  TYPE(t_patch), POINTER :: ppatch
2543  TYPE(t_region), POINTER :: pregion
2544 
2545 ! ==============================================================================
2546 ! Locals
2547 ! ==============================================================================
2548 
2549  INTEGER :: errorflag,ipatch
2550  TYPE(t_global), POINTER :: global
2551 
2552 ! ******************************************************************************
2553 ! Start
2554 ! ******************************************************************************
2555 
2556  global => pregion%global
2557 
2558  CALL registerfunction(global,'RFLU_TEC_DestroyDataPatch', &
2559  'RFLU_ModTECPLOT.F90')
2560 
2561  IF ( global%verbLevel > verbose_none ) THEN
2562  WRITE(stdout,'(A,1X,A)') solver_name,'Destroying TECPLOT patch data...'
2563  END IF ! global%verbLevel
2564 
2565 ! ******************************************************************************
2566 ! Deallocate memory
2567 ! ******************************************************************************
2568 
2569  DEALLOCATE(postec,stat=errorflag)
2570  global%error = errorflag
2571  IF ( global%error /= err_none ) THEN
2572  CALL errorstop(global,err_deallocate,__line__,'posTEC')
2573  END IF ! global%error
2574 
2575  DEALLOCATE(ppatch%varVertTEC,stat=errorflag)
2576  global%error = errorflag
2577  IF ( global%error /= err_none ) THEN
2578  CALL errorstop(global,err_deallocate,__line__,'pPatch%varVertTEC')
2579  END IF ! global%error
2580 
2581  IF ( ASSOCIATED(ppatch%varFaceTEC) .EQV. .true. ) THEN
2582  DEALLOCATE(ppatch%varFaceTEC,stat=errorflag)
2583  global%error = errorflag
2584  IF ( global%error /= err_none ) THEN
2585  CALL errorstop(global,err_deallocate,__line__,'pPatch%varFaceTEC')
2586  END IF ! global%error
2587  END IF ! ASSOCIATED
2588 
2589 ! ******************************************************************************
2590 ! End
2591 ! ******************************************************************************
2592 
2593  IF ( global%verbLevel > verbose_none ) THEN
2594  WRITE(stdout,'(A,1X,A)') solver_name, &
2595  'Destroying TECPLOT patch data done.'
2596  END IF ! global%verbLevel
2597 
2598  CALL deregisterfunction(global)
2599 
2600 END SUBROUTINE rflu_tec_destroydatapatch
2601 
2602 
2603 
2604 
2605 
2606 
2607 ! ******************************************************************************
2608 !
2609 ! Purpose: Initialize TECPLOT interface
2610 !
2611 ! Description: None.
2612 !
2613 ! Input:
2614 ! global Pointer to global data
2615 !
2616 ! Output: None.
2617 !
2618 ! Notes:
2619 ! 1. Needed because TECPLOT interface has some global data which needs to be
2620 ! initialized once.
2621 ! 2. Must be called before first TECPLOT file opened.
2622 !
2623 ! ******************************************************************************
2624 
2625 SUBROUTINE rflu_tec_init(global)
2626 
2627  IMPLICIT NONE
2628 
2629 ! ******************************************************************************
2630 ! Declarations and definitions
2631 ! ******************************************************************************
2632 
2633 ! ==============================================================================
2634 ! Arguments
2635 ! ==============================================================================
2636 
2637  TYPE(t_global), POINTER :: global
2638 
2639 ! ******************************************************************************
2640 ! Start
2641 ! ******************************************************************************
2642 
2643  CALL registerfunction(global,'RFLU_TEC_Init', &
2644  'RFLU_ModTECPLOT.F90')
2645 
2646  IF ( global%verbLevel > verbose_low ) THEN
2647  WRITE(stdout,'(A,1X,A)') solver_name,'Initializing TECPLOT...'
2648  END IF ! global%verbLevel
2649 
2650 ! ******************************************************************************
2651 ! Initialize data
2652 ! ******************************************************************************
2653 
2654  filecntrtec = 0
2655 
2656 ! ******************************************************************************
2657 ! End
2658 ! ******************************************************************************
2659 
2660  IF ( global%verbLevel > verbose_low ) THEN
2661  WRITE(stdout,'(A,1X,A)') solver_name,'Initializing TECPLOT done...'
2662  END IF ! global%verbLevel
2663 
2664  CALL deregisterfunction(global)
2665 
2666 END SUBROUTINE rflu_tec_init
2667 
2668 
2669 
2670 
2671 
2672 
2673 ! ******************************************************************************
2674 !
2675 ! Purpose: Open TECPLOT field file
2676 !
2677 ! Description: None.
2678 !
2679 ! Input:
2680 ! pRegion Pointer to region
2681 !
2682 ! Output: None.
2683 !
2684 ! Notes:
2685 ! 1. Isolated into separate routine so that can write several zones to same
2686 ! TECPLOT file.
2687 ! 2. Need pointer to region because need to know how many variables are
2688 ! to be written to file, and hence need to know about number of species
2689 ! (as an example). Passing the global does not allow for this kind of
2690 ! information because the user input is under the region data structure.
2691 !
2692 ! ******************************************************************************
2693 
2694 SUBROUTINE rflu_tec_openfilefield(pRegion)
2695 
2698 
2699  IMPLICIT NONE
2700 
2701 ! ******************************************************************************
2702 ! Declarations and definitions
2703 ! ******************************************************************************
2704 
2705 ! ==============================================================================
2706 ! Arguments
2707 ! ==============================================================================
2708 
2709  TYPE(t_region), POINTER :: pregion
2710 
2711 ! ==============================================================================
2712 ! Locals
2713 ! ==============================================================================
2714 
2715  CHARACTER(CHRLEN) :: ifilename,title
2716  INTEGER :: errorflag
2717  TYPE(t_global), POINTER :: global
2718 
2719 ! ******************************************************************************
2720 ! Start
2721 ! ******************************************************************************
2722 
2723  global => pregion%global
2724 
2725  CALL registerfunction(global,'RFLU_TEC_OpenFileField', &
2726  'RFLU_ModTECPLOT.F90')
2727 
2728  IF ( global%verbLevel > verbose_none ) THEN
2729  WRITE(stdout,'(A,1X,A)') solver_name,'Opening TECPLOT field file...'
2730  END IF ! global%verbLevel
2731 
2732 ! ******************************************************************************
2733 ! Build header
2734 ! ******************************************************************************
2735 
2736  CALL rflu_tec_buildheaderfield(pregion)
2737 
2738 ! ******************************************************************************
2739 ! Open file
2740 ! ******************************************************************************
2741 
2742  title = global%caseName
2743 
2744  IF ( global%flowType == flow_unsteady ) THEN
2745  CALL buildfilenameplainunsteady(global,filedest_indir,'.plt', &
2746  global%currentTime,ifilename)
2747  ELSE IF ( global%flowType == flow_steady ) THEN
2748  CALL buildfilenameplainsteady(global,filedest_indir,'.plt', &
2749  global%currentIter,ifilename)
2750  ELSE ! defensive coding
2751  CALL errorstop(global,err_reached_default,__line__)
2752  END IF ! global%flowType
2753 
2754  filecntrtec = filecntrtec + 1
2755 
2756  IF ( filecntrtec > file_cntr_tec_max ) THEN
2757  CALL errorstop(global,err_tecplot_filecntr,__line__)
2758  END IF ! fileCntrTEC
2759 
2760  CALL rflu_tec_openfile(global,title,ifilename)
2761 
2762  filetype2cntrtec(file_type_field) = filecntrtec
2763 
2764 ! ==============================================================================
2765 ! Write info
2766 ! ==============================================================================
2767 
2768  IF ( global%verbLevel > verbose_low ) THEN
2769  WRITE(stdout,'(A,3X,A,1X,A)') solver_name,'File name:',trim(ifilename)
2770  WRITE(stdout,'(A,3X,A,1X,I2)') solver_name,'File counter:',filecntrtec
2771  END IF ! global%verbLevel
2772 
2773 ! ******************************************************************************
2774 ! End
2775 ! ******************************************************************************
2776 
2777  IF ( global%verbLevel > verbose_none ) THEN
2778  WRITE(stdout,'(A,1X,A)') solver_name,'Opening TECPLOT field file done.'
2779  END IF ! global%verbLevel
2780 
2781  CALL deregisterfunction(global)
2782 
2783 END SUBROUTINE rflu_tec_openfilefield
2784 
2785 
2786 
2787 
2788 
2789 
2790 ! ******************************************************************************
2791 !
2792 ! Purpose: Open TECPLOT patch file
2793 !
2794 ! Description: None.
2795 !
2796 ! Input:
2797 ! pRegion Pointer to region
2798 !
2799 ! Output: None.
2800 !
2801 ! Notes:
2802 ! 1. Isolated into separate routine so that can write several zones to same
2803 ! TECPLOT file.
2804 ! 2. Need pointer to region because need to know how many variables are
2805 ! to be written to file, and hence need to know about number of species
2806 ! (as an example). Passing the global does not allow for this kind of
2807 ! information because the user input is under the region data structure.
2808 !
2809 ! ******************************************************************************
2810 
2811 SUBROUTINE rflu_tec_openfilepatch(pRegion)
2812 
2815 
2816  IMPLICIT NONE
2817 
2818 ! ******************************************************************************
2819 ! Declarations and definitions
2820 ! ******************************************************************************
2821 
2822 ! ==============================================================================
2823 ! Arguments
2824 ! ==============================================================================
2825 
2826  TYPE(t_region), POINTER :: pregion
2827 
2828 ! ==============================================================================
2829 ! Locals
2830 ! ==============================================================================
2831 
2832  CHARACTER(CHRLEN) :: ifilename,title
2833  INTEGER :: errorflag
2834  TYPE(t_global), POINTER :: global
2835 
2836 ! ******************************************************************************
2837 ! Start
2838 ! ******************************************************************************
2839 
2840  global => pregion%global
2841 
2842  CALL registerfunction(global,'RFLU_TEC_OpenFilePatch', &
2843  'RFLU_ModTECPLOT.F90')
2844 
2845  IF ( global%verbLevel > verbose_none ) THEN
2846  WRITE(stdout,'(A,1X,A)') solver_name,'Opening TECPLOT patch file...'
2847  END IF ! global%verbLevel
2848 
2849 ! ******************************************************************************
2850 ! Build header
2851 ! ******************************************************************************
2852 
2853  CALL rflu_tec_buildheaderpatch(pregion)
2854 
2855 ! ******************************************************************************
2856 ! Open file
2857 ! ******************************************************************************
2858 
2859  title = global%caseName
2860 
2861  IF ( global%flowType == flow_unsteady ) THEN
2862  CALL buildfilenameplainunsteady(global,filedest_indir,'.pat.plt', &
2863  global%currentTime,ifilename)
2864  ELSE IF ( global%flowType == flow_steady ) THEN
2865  CALL buildfilenameplainsteady(global,filedest_indir,'.pat.plt', &
2866  global%currentIter,ifilename)
2867  ELSE ! defensive coding
2868  CALL errorstop(global,err_reached_default,__line__)
2869  END IF ! global%flowType
2870 
2871  filecntrtec = filecntrtec + 1
2872 
2873  IF ( filecntrtec > file_cntr_tec_max ) THEN
2874  CALL errorstop(global,err_tecplot_filecntr,__line__)
2875  END IF ! fileCntrTEC
2876 
2877  CALL rflu_tec_openfile(global,title,ifilename)
2878 
2879  filetype2cntrtec(file_type_patch) = filecntrtec
2880 
2881 ! ==============================================================================
2882 ! Write info
2883 ! ==============================================================================
2884 
2885  IF ( global%verbLevel > verbose_low ) THEN
2886  WRITE(stdout,'(A,3X,A,1X,A)') solver_name,'File name:',trim(ifilename)
2887  WRITE(stdout,'(A,3X,A,1X,I2)') solver_name,'File counter:',filecntrtec
2888  END IF ! global%verbLevel
2889 
2890 ! ******************************************************************************
2891 ! End
2892 ! ******************************************************************************
2893 
2894  IF ( global%verbLevel > verbose_none ) THEN
2895  WRITE(stdout,'(A,1X,A)') solver_name,'Opening TECPLOT patch file done.'
2896  END IF ! global%verbLevel
2897 
2898  CALL deregisterfunction(global)
2899 
2900 END SUBROUTINE rflu_tec_openfilepatch
2901 
2902 
2903 
2904 
2905 
2906 
2907 
2908 
2909 ! ******************************************************************************
2910 !
2911 ! Purpose: Open TECPLOT patch statistics file
2912 !
2913 ! Description: None.
2914 !
2915 ! Input:
2916 ! pRegion Pointer to region
2917 !
2918 ! Output: None.
2919 !
2920 ! Notes:
2921 ! 1. Isolated into separate routine so that can write several zones to same
2922 ! TECPLOT file.
2923 ! 2. Need pointer to region because need to know how many variables are
2924 ! to be written to file, and hence need to know about number of species
2925 ! (as an example). Passing the global does not allow for this kind of
2926 ! information because the user input is under the region data structure.
2927 !
2928 ! ******************************************************************************
2929 
2930 SUBROUTINE rflu_tec_openfilepatchstats(pRegion)
2931 
2934 
2935  IMPLICIT NONE
2936 
2937 ! ******************************************************************************
2938 ! Declarations and definitions
2939 ! ******************************************************************************
2940 
2941 ! ==============================================================================
2942 ! Arguments
2943 ! ==============================================================================
2944 
2945  TYPE(t_region), POINTER :: pregion
2946 
2947 ! ==============================================================================
2948 ! Locals
2949 ! ==============================================================================
2950 
2951  CHARACTER(CHRLEN) :: ifilename,title
2952  INTEGER :: errorflag
2953  TYPE(t_global), POINTER :: global
2954 
2955 ! ******************************************************************************
2956 ! Start
2957 ! ******************************************************************************
2958 
2959  global => pregion%global
2960 
2961  CALL registerfunction(global,'RFLU_TEC_OpenFilePatchStats', &
2962  'RFLU_ModTECPLOT.F90')
2963 
2964  IF ( global%verbLevel > verbose_none ) THEN
2965  WRITE(stdout,'(A,1X,A)') solver_name, &
2966  'Opening TECPLOT patch statistics file...'
2967  END IF ! global%verbLevel
2968 
2969 ! ******************************************************************************
2970 ! Build header
2971 ! ******************************************************************************
2972 
2973  CALL rflu_tec_buildheaderpatchstats(pregion)
2974 
2975 ! ******************************************************************************
2976 ! Open file
2977 ! ******************************************************************************
2978 
2979  title = global%caseName
2980 
2981  IF ( global%flowType == flow_unsteady ) THEN
2982  CALL buildfilenameplainunsteady(global,filedest_indir,'.stats.plt', &
2983  global%currentTime,ifilename)
2984  ELSE IF ( global%flowType == flow_steady ) THEN
2985  CALL buildfilenameplainsteady(global,filedest_indir,'.stats.plt', &
2986  global%currentIter,ifilename)
2987  ELSE ! defensive coding
2988  CALL errorstop(global,err_reached_default,__line__)
2989  END IF ! global%flowType
2990 
2991  filecntrtec = filecntrtec + 1
2992 
2993  IF ( filecntrtec > file_cntr_tec_max ) THEN
2994  CALL errorstop(global,err_tecplot_filecntr,__line__)
2995  END IF ! fileCntrTEC
2996 
2997  CALL rflu_tec_openfile(global,title,ifilename)
2998 
2999  filetype2cntrtec(file_type_patch_stats) = filecntrtec
3000 
3001 ! ==============================================================================
3002 ! Write info
3003 ! ==============================================================================
3004 
3005  IF ( global%verbLevel > verbose_low ) THEN
3006  WRITE(stdout,'(A,3X,A,1X,A)') solver_name,'File name:',trim(ifilename)
3007  WRITE(stdout,'(A,3X,A,1X,I2)') solver_name,'File counter:',filecntrtec
3008  END IF ! global%verbLevel
3009 
3010 ! ******************************************************************************
3011 ! End
3012 ! ******************************************************************************
3013 
3014  IF ( global%verbLevel > verbose_none ) THEN
3015  WRITE(stdout,'(A,1X,A)') solver_name, &
3016  'Opening TECPLOT patch statistics file done.'
3017  END IF ! global%verbLevel
3018 
3019  CALL deregisterfunction(global)
3020 
3021 END SUBROUTINE rflu_tec_openfilepatchstats
3022 
3023 
3024 
3025 
3026 
3027 
3028 ! ******************************************************************************
3029 !
3030 ! Purpose: Open TECPLOT point file
3031 !
3032 ! Description: None.
3033 !
3034 ! Input:
3035 ! pRegion Pointer to region
3036 !
3037 ! Output: None.
3038 !
3039 ! Notes:
3040 ! 1. Isolated into separate routine so that can write several zones to same
3041 ! TECPLOT file.
3042 ! 2. Need pointer to region because need to know how many variables are
3043 ! to be written to file, and hence need to know about number of species
3044 ! (as an example). Passing the global does not allow for this kind of
3045 ! information because the user input is under the region data structure.
3046 !
3047 ! ******************************************************************************
3048 
3049 SUBROUTINE rflu_tec_openfilepnt(pRegion)
3050 
3052 
3053  IMPLICIT NONE
3054 
3055 ! ******************************************************************************
3056 ! Declarations and definitions
3057 ! ******************************************************************************
3058 
3059 ! ==============================================================================
3060 ! Arguments
3061 ! ==============================================================================
3062 
3063  TYPE(t_region), POINTER :: pregion
3064 
3065 ! ==============================================================================
3066 ! Locals
3067 ! ==============================================================================
3068 
3069  CHARACTER(CHRLEN) :: ifilename
3070  INTEGER :: errorflag,ifile
3071  TYPE(t_global), POINTER :: global
3072 
3073 ! ******************************************************************************
3074 ! Start
3075 ! ******************************************************************************
3076 
3077  global => pregion%global
3078 
3079  CALL registerfunction(global,'RFLU_TEC_OpenFilePnt', &
3080  'RFLU_ModTECPLOT.F90')
3081 
3082  IF ( global%verbLevel > verbose_none ) THEN
3083  WRITE(stdout,'(A,1X,A)') solver_name,'Opening TECPLOT point file...'
3084  END IF ! global%verbLevel
3085 
3086 ! ******************************************************************************
3087 ! Open file
3088 ! ******************************************************************************
3089 
3090  IF ( global%flowType == flow_unsteady ) THEN
3091  CALL buildfilenameplainunsteady(global,filedest_indir,'.plag.dat', &
3092  global%currentTime,ifilename)
3093  ELSE ! defensive coding
3094  CALL errorstop(global,err_reached_default,__line__)
3095  END IF ! global%flowType
3096 
3097  ifile = if_plot
3098  OPEN(ifile,file=ifilename,form="FORMATTED",status="UNKNOWN", &
3099  iostat=errorflag)
3100  global%error = errorflag
3101  IF ( global%error /= err_none ) THEN
3102  CALL errorstop(global,err_file_open,__line__,trim(ifilename))
3103  END IF ! global%error
3104 
3105 ! ******************************************************************************
3106 ! Write header
3107 ! ******************************************************************************
3108 
3109  WRITE(ifile,'(1X,A)') 'TITLE="'//trim(global%casename)//'"'
3110  WRITE(ifile,'(1X,A)') 'VARIABLES="x" "y" "z" "diam"'
3111 
3112 ! ******************************************************************************
3113 ! Write info
3114 ! ******************************************************************************
3115 
3116  IF ( global%verbLevel > verbose_low ) THEN
3117  WRITE(stdout,'(A,3X,A,1X,A)') solver_name,'File name:',trim(ifilename)
3118  END IF ! global%verbLevel
3119 
3120 ! ******************************************************************************
3121 ! End
3122 ! ******************************************************************************
3123 
3124  IF ( global%verbLevel > verbose_none ) THEN
3125  WRITE(stdout,'(A,1X,A)') solver_name,'Opening TECPLOT point file done.'
3126  END IF ! global%verbLevel
3127 
3128  CALL deregisterfunction(global)
3129 
3130 END SUBROUTINE rflu_tec_openfilepnt
3131 
3132 
3133 
3134 
3135 
3136 
3137 
3138 ! ******************************************************************************
3139 !
3140 ! Purpose: Write surface data to TECPLOT field file.
3141 !
3142 ! Description: None.
3143 !
3144 ! Input:
3145 ! pRegion Pointer to region data
3146 ! pPatch Pointer to patch data
3147 !
3148 ! Output: None.
3149 !
3150 ! Notes: None.
3151 !
3152 ! ******************************************************************************
3153 
3154 SUBROUTINE rflu_tec_writefilefieldsurf(pRegion,pPatch)
3155 
3156  IMPLICIT NONE
3157 
3158 ! ******************************************************************************
3159 ! Declarations and definitions
3160 ! ******************************************************************************
3161 
3162 ! ==============================================================================
3163 ! Arguments
3164 ! ==============================================================================
3165 
3166  TYPE(t_patch), POINTER :: ppatch
3167  TYPE(t_region), POINTER :: pregion
3168 
3169 ! ==============================================================================
3170 ! Locals
3171 ! ==============================================================================
3172 
3173  TYPE(t_global), POINTER :: global
3174 
3175 ! ******************************************************************************
3176 ! Start
3177 ! ******************************************************************************
3178 
3179  global => pregion%global
3180 
3181  CALL registerfunction(global,'RFLU_TEC_WriteFileFieldSurf', &
3182  'RFLU_ModTECPLOT.F90')
3183 
3184  IF ( global%verbLevel > verbose_none ) THEN
3185  WRITE(stdout,'(A,1X,A)') solver_name, &
3186  'Writing surface data to TECPLOT file...'
3187  WRITE(stdout,'(A,3X,A,1X,I5.5)') solver_name,'Global region:', &
3188  pregion%iRegionGlobal
3189  WRITE(stdout,'(A,3X,A,1X,I5)') solver_name,'Global patch:', &
3190  ppatch%iPatchGlobal
3191  END IF ! global%verbLevel
3192 
3193 ! ******************************************************************************
3194 ! Triangles
3195 ! ******************************************************************************
3196 
3197  IF ( ppatch%nBTris > 0 ) THEN
3198  IF ( global%verbLevel > verbose_none ) THEN
3199  WRITE(stdout,'(A,5X,A)') solver_name,'Actual triangles...'
3200  END IF ! global%verbLevel
3201 
3202  CALL rflu_tec_writezonesurf(pregion,ppatch,face_type_tri,face_kind_ab)
3203  ENDIF ! pPatch%nBTris
3204 
3205  IF ( ppatch%nBTrisTot > ppatch%nBTris ) THEN
3206  IF ( global%verbLevel > verbose_none ) THEN
3207  WRITE(stdout,'(A,5X,A)') solver_name,'Virtual triangles...'
3208  END IF ! global%verbLevel
3209 
3210  CALL rflu_tec_writezonesurf(pregion,ppatch,face_type_tri,face_kind_vb)
3211  ENDIF ! pPatch%nBTrisTot
3212 
3213 ! ******************************************************************************
3214 ! Quadrilaterals
3215 ! ******************************************************************************
3216 
3217  IF ( ppatch%nBQuads > 0 ) THEN
3218  IF ( global%verbLevel > verbose_none ) THEN
3219  WRITE(stdout,'(A,5X,A)') solver_name,'Actual quadrilaterals...'
3220  END IF ! global%verbLevel
3221 
3222  CALL rflu_tec_writezonesurf(pregion,ppatch,face_type_quad,face_kind_ab)
3223  END IF ! pPatch%nBQuads
3224 
3225  IF ( ppatch%nBQuadsTot > ppatch%nBQuads ) THEN
3226  IF ( global%verbLevel > verbose_none ) THEN
3227  WRITE(stdout,'(A,5X,A)') solver_name,'Virtual quadrilaterals...'
3228  END IF ! global%verbLevel
3229 
3230  CALL rflu_tec_writezonesurf(pregion,ppatch,face_type_quad,face_kind_vb)
3231  END IF ! pPatch%nBQuads
3232 
3233 ! ******************************************************************************
3234 ! End
3235 ! ******************************************************************************
3236 
3237  IF ( global%verbLevel > verbose_none ) THEN
3238  WRITE(stdout,'(A,1X,A)') solver_name, &
3239  'Writing surface data to TECPLOT field file done.'
3240  END IF ! global%verbLevel
3241 
3242  CALL deregisterfunction(global)
3243 
3244 END SUBROUTINE rflu_tec_writefilefieldsurf
3245 
3246 
3247 
3248 
3249 
3250 
3251 
3252 ! ******************************************************************************
3253 !
3254 ! Purpose: Write volume data to TECPLOT field file
3255 !
3256 ! Description: None.
3257 !
3258 ! Input:
3259 ! pRegion Pointer to region data
3260 !
3261 ! Output: None.
3262 !
3263 ! Notes:
3264 ! 1. Write partition boundary faces here because they access field volume
3265 ! data.
3266 !
3267 ! ******************************************************************************
3268 
3269 SUBROUTINE rflu_tec_writefilefieldvol(pRegion)
3270 
3271  IMPLICIT NONE
3272 
3273 ! ******************************************************************************
3274 ! Declarations and definitions
3275 ! ******************************************************************************
3276 
3277 ! ==============================================================================
3278 ! Locals
3279 ! ==============================================================================
3280 
3281  TYPE(t_grid), POINTER :: pgrid
3282  TYPE(t_global), POINTER :: global
3283 
3284 ! ==============================================================================
3285 ! Arguments
3286 ! ==============================================================================
3287 
3288  TYPE(t_region), POINTER :: pregion
3289 
3290 ! ******************************************************************************
3291 ! Start
3292 ! ******************************************************************************
3293 
3294  global => pregion%global
3295 
3296  CALL registerfunction(global,'RFLU_TEC_WriteFileFieldVol', &
3297  'RFLU_ModTECPLOT.F90')
3298 
3299  IF ( global%verbLevel > verbose_none ) THEN
3300  WRITE(stdout,'(A,1X,A)') solver_name, &
3301  'Writing volume data to TECPLOT field file...'
3302  WRITE(stdout,'(A,3X,A,1X,I5.5)') solver_name,'Global region:', &
3303  pregion%iRegionGlobal
3304  END IF ! global%verbLevel
3305 
3306 ! ******************************************************************************
3307 ! Set pointer to grid
3308 ! ******************************************************************************
3309 
3310  pgrid => pregion%grid
3311 
3312 ! ******************************************************************************
3313 ! Tetrahedra
3314 ! ******************************************************************************
3315 
3316  IF ( pgrid%nTets > 0 ) THEN
3317  IF ( global%verbLevel > verbose_none ) THEN
3318  WRITE(stdout,'(A,3X,A)') solver_name,'Actual tetrahedra...'
3319  END IF ! global%verbLevel
3320 
3321  CALL rflu_tec_writezonevol(pregion,cell_type_tet,cell_kind_actual)
3322  ENDIF ! pGrid%nTets
3323 
3324  IF ( pgrid%nTetsTot > pgrid%nTets ) THEN
3325  IF ( global%verbLevel > verbose_none ) THEN
3326  WRITE(stdout,'(A,3X,A)') solver_name,'Virtual tetrahedra...'
3327  END IF ! global%verbLevel
3328 
3329  CALL rflu_tec_writezonevol(pregion,cell_type_tet,cell_kind_virtual)
3330  ENDIF ! pGrid%nTetsTot
3331 
3332 ! ******************************************************************************
3333 ! Hexahedra
3334 ! ******************************************************************************
3335 
3336  IF ( pgrid%nHexs > 0 ) THEN
3337  IF ( global%verbLevel > verbose_none ) THEN
3338  WRITE(stdout,'(A,3X,A)') solver_name,'Actual hexahedra...'
3339  END IF ! global%verbLevel
3340 
3341  CALL rflu_tec_writezonevol(pregion,cell_type_hex,cell_kind_actual)
3342  ENDIF ! pGrid%nHexs
3343 
3344  IF ( pgrid%nHexsTot > pgrid%nHexs ) THEN
3345  IF ( global%verbLevel > verbose_none ) THEN
3346  WRITE(stdout,'(A,3X,A)') solver_name,'Virtual hexahedra...'
3347  END IF ! global%verbLevel
3348 
3349  CALL rflu_tec_writezonevol(pregion,cell_type_hex,cell_kind_virtual)
3350  ENDIF ! pGrid%nHexsTot
3351 
3352 ! ******************************************************************************
3353 ! Prisms
3354 ! ******************************************************************************
3355 
3356  IF ( pgrid%nPris > 0 ) THEN
3357  IF ( global%verbLevel > verbose_none ) THEN
3358  WRITE(stdout,'(A,3X,A)') solver_name,'Actual prisms...'
3359  END IF ! global%verbLevel
3360 
3361  CALL rflu_tec_writezonevol(pregion,cell_type_pri,cell_kind_actual)
3362  ENDIF ! pGrid%nPris
3363 
3364 
3365  IF ( pgrid%nPrisTot > pgrid%nPris ) THEN
3366  IF ( global%verbLevel > verbose_none ) THEN
3367  WRITE(stdout,'(A,3X,A)') solver_name,'Virtual prisms...'
3368  END IF ! global%verbLevel
3369 
3370  CALL rflu_tec_writezonevol(pregion,cell_type_pri,cell_kind_virtual)
3371  ENDIF ! pGrid%nPrisTot
3372 
3373 ! ******************************************************************************
3374 ! Pyramids
3375 ! ******************************************************************************
3376 
3377  IF ( pgrid%nPyrs > 0 ) THEN
3378  IF ( global%verbLevel > verbose_none ) THEN
3379  WRITE(stdout,'(A,3X,A)') solver_name,'Actual pyramids...'
3380  END IF ! global%verbLevel
3381 
3382  CALL rflu_tec_writezonevol(pregion,cell_type_pyr,cell_kind_actual)
3383  ENDIF ! pGrid%nPyrs
3384 
3385  IF ( pgrid%nPyrsTot > pgrid%nPyrs ) THEN
3386  IF ( global%verbLevel > verbose_none ) THEN
3387  WRITE(stdout,'(A,3X,A)') solver_name,'Virtual pyramids...'
3388  END IF ! global%verbLevel
3389 
3390  CALL rflu_tec_writezonevol(pregion,cell_type_pyr,cell_kind_virtual)
3391  ENDIF ! pGrid%nPyrsTot
3392 
3393 ! ******************************************************************************
3394 ! Writing special cells and faces
3395 ! ******************************************************************************
3396 
3397  IF ( pgrid%nCellsSpecial > 0 ) THEN
3398  IF ( global%verbLevel > verbose_none ) THEN
3399  WRITE(stdout,'(A,3X,A)') solver_name,'Special cells...'
3400  END IF ! global%verbLevel
3401 
3402  CALL rflu_tec_writezonecellsspecial(pregion)
3403  END IF ! pGrid%nCellsSpecial
3404 
3405  IF ( pgrid%nFacesSpecial > 0 ) THEN
3406  IF ( global%verbLevel > verbose_none ) THEN
3407  WRITE(stdout,'(A,3X,A)') solver_name,'Special faces...'
3408  END IF ! global%verbLevel
3409 
3410  CALL rflu_tec_writezonefacesspecial(pregion)
3411  END IF ! pGrid%nFacesSpecial
3412 
3413 ! ******************************************************************************
3414 ! Partition boundaries. NOTE can only write these faces if have no cell data
3415 ! because cannot easily access cell data for these faces.
3416 ! ******************************************************************************
3417 
3418  IF ( (pgrid%nFaces /= pgrid%nFacesTot) .AND. (nvarscelltec == 0) ) THEN
3419  IF ( global%verbLevel > verbose_none ) THEN
3420  WRITE(stdout,'(A,3X,A)') solver_name,'Interpartition faces...'
3421  END IF ! global%verbLevel
3422 
3423  CALL rflu_tec_writezoneinterf(pregion)
3424  END IF ! pGrid%nFaces
3425 
3426 ! ******************************************************************************
3427 ! End
3428 ! ******************************************************************************
3429 
3430  IF ( global%verbLevel > verbose_none ) THEN
3431  WRITE(stdout,'(A,1X,A)') solver_name, &
3432  'Writing volume data to TECPLOT field file done.'
3433  END IF ! global%verbLevel
3434 
3435  CALL deregisterfunction(global)
3436 
3437 END SUBROUTINE rflu_tec_writefilefieldvol
3438 
3439 
3440 
3441 
3442 
3443 
3444 
3445 ! ******************************************************************************
3446 !
3447 ! Purpose: Write data to TECPLOT patch file.
3448 !
3449 ! Description: None.
3450 !
3451 ! Input:
3452 ! pRegion Pointer to region data
3453 ! pPatch Pointer to patch data
3454 !
3455 ! Output: None.
3456 !
3457 ! Notes:
3458 ! 1. Only write data for actual faces because patch data only stored for
3459 ! actual faces.
3460 !
3461 ! ******************************************************************************
3462 
3463 SUBROUTINE rflu_tec_writefilepatch(pRegion,pPatch)
3464 
3465  IMPLICIT NONE
3466 
3467 ! ******************************************************************************
3468 ! Declarations and definitions
3469 ! ******************************************************************************
3470 
3471 ! ==============================================================================
3472 ! Arguments
3473 ! ==============================================================================
3474 
3475  TYPE(t_patch), POINTER :: ppatch
3476  TYPE(t_region), POINTER :: pregion
3477 
3478 ! ==============================================================================
3479 ! Locals
3480 ! ==============================================================================
3481 
3482  TYPE(t_global), POINTER :: global
3483 
3484 ! ******************************************************************************
3485 ! Start
3486 ! ******************************************************************************
3487 
3488  global => pregion%global
3489 
3490  CALL registerfunction(global,'RFLU_TEC_WriteFilePatch', &
3491  'RFLU_ModTECPLOT.F90')
3492 
3493  IF ( global%verbLevel > verbose_none ) THEN
3494  WRITE(stdout,'(A,1X,A)') solver_name,'Writing data to TECPLOT patch file...'
3495  WRITE(stdout,'(A,3X,A,1X,I5.5)') solver_name,'Global region:', &
3496  pregion%iRegionGlobal
3497  WRITE(stdout,'(A,3X,A,1X,I5)') solver_name,'Global patch:', &
3498  ppatch%iPatchGlobal
3499  END IF ! global%verbLevel
3500 
3501 ! ******************************************************************************
3502 ! Loop over patches
3503 ! ******************************************************************************
3504 
3505  IF ( ppatch%nBFaces > 0 ) THEN
3506  CALL rflu_tec_writezonesurfmixed(pregion,ppatch)
3507  END IF ! pPatch%nBFaces
3508 
3509 ! ******************************************************************************
3510 ! End
3511 ! ******************************************************************************
3512 
3513  IF ( global%verbLevel > verbose_none ) THEN
3514  WRITE(stdout,'(A,1X,A)') solver_name, &
3515  'Writing data to TECPLOT patch file done.'
3516  END IF ! global%verbLevel
3517 
3518  CALL deregisterfunction(global)
3519 
3520 END SUBROUTINE rflu_tec_writefilepatch
3521 
3522 
3523 
3524 
3525 
3526 
3527 
3528 ! ******************************************************************************
3529 !
3530 ! Purpose: Write point data to TECPLOT file
3531 !
3532 ! Description: None.
3533 !
3534 ! Input:
3535 ! pRegion Pointer to region data
3536 !
3537 ! Output: None.
3538 !
3539 ! Notes:
3540 ! 1. At present hard-wired for Rocpart. Will be extended eventually to allow
3541 ! arbitrary point data to be written.
3542 !
3543 ! ******************************************************************************
3544 
3545 SUBROUTINE rflu_tec_writefilepnt(pRegion)
3546 
3547 #ifdef PLAG
3548  USE modpartlag, ONLY: t_plag
3549 
3550  USE plag_modparameters
3551 #endif
3552 
3553  IMPLICIT NONE
3554 
3555 ! ******************************************************************************
3556 ! Declarations and definitions
3557 ! ******************************************************************************
3558 
3559 ! ==============================================================================
3560 ! Locals
3561 ! ==============================================================================
3562 
3563  INTEGER :: errorflag,ipcl
3564  TYPE(t_grid), POINTER :: pgrid
3565  TYPE(t_global), POINTER :: global
3566 #ifdef PLAG
3567  TYPE(t_plag), POINTER :: pplag
3568 #endif
3569 
3570 ! ==============================================================================
3571 ! Arguments
3572 ! ==============================================================================
3573 
3574  TYPE(t_region), POINTER :: pregion
3575 
3576 ! ******************************************************************************
3577 ! Start
3578 ! ******************************************************************************
3579 
3580  global => pregion%global
3581 
3582  CALL registerfunction(global,'RFLU_TEC_WriteFilePnt', &
3583  'RFLU_ModTECPLOT.F90')
3584 
3585 #ifdef PLAG
3586  IF ( global%verbLevel > verbose_none ) THEN
3587  WRITE(stdout,'(A,1X,A)') solver_name,'Writing to TECPLOT point file...'
3588  WRITE(stdout,'(A,3X,A,1X,I5.5)') solver_name,'Global region:', &
3589  pregion%iRegionGlobal
3590  END IF ! global%verbLevel
3591 
3592 ! ==============================================================================
3593 ! Set pointers
3594 ! ==============================================================================
3595 
3596  pgrid => pregion%grid
3597  pplag => pregion%plag
3598 
3599 ! ==============================================================================
3600 ! Write header and data
3601 ! ==============================================================================
3602 
3603  IF ( pplag%nPcls > 0 ) THEN
3604  WRITE(if_plot,'(A,1X,I5.5,1X,A,I8,1X,A)') 'ZONE T="', &
3605  pregion%iRegionGlobal, &
3606  '", I=',pplag%nPcls,', F=POINT'
3607 
3608  DO ipcl = 1,pplag%nPcls
3609  WRITE(if_plot,'(4(1X,E13.6))') pplag%cv(cv_plag_xpos,ipcl), &
3610  pplag%cv(cv_plag_ypos,ipcl), &
3611  pplag%cv(cv_plag_zpos,ipcl), &
3612  pplag%dv(dv_plag_diam,ipcl)
3613  END DO ! iPcl
3614  END IF ! pPlag%nPcls
3615 #endif
3616 
3617 ! ******************************************************************************
3618 ! End
3619 ! ******************************************************************************
3620 
3621  IF ( global%verbLevel > verbose_none ) THEN
3622  WRITE(stdout,'(A,1X,A)') solver_name,'Writing to TECPLOT point file done.'
3623  END IF ! global%verbLevel
3624 
3625  CALL deregisterfunction(global)
3626 
3627 END SUBROUTINE rflu_tec_writefilepnt
3628 
3629 
3630 
3631 
3632 
3633 
3634 
3635 END MODULE rflu_modtecplot
3636 
3637 ! ******************************************************************************
3638 !
3639 ! RCS Revision history:
3640 !
3641 ! $Log: RFLU_ModTECPLOT.F90,v $
3642 ! Revision 1.38 2008/12/06 08:45:06 mtcampbe
3643 ! Updated license.
3644 !
3645 ! Revision 1.37 2008/11/19 22:18:16 mtcampbe
3646 ! Added Illinois Open Source License/Copyright
3647 !
3648 ! Revision 1.36 2007/03/19 21:44:24 haselbac
3649 ! Adapted to changes related to plotting variables
3650 !
3651 ! Revision 1.35 2006/05/02 18:23:33 fnajjar
3652 ! Reverting to original code for correctness
3653 !
3654 ! Revision 1.34 2006/05/02 17:48:09 fnajjar
3655 ! Allowed surface statistics to be written on active patches
3656 !
3657 ! Revision 1.33 2006/04/07 15:19:26 haselbac
3658 ! Removed tabs
3659 !
3660 ! Revision 1.32 2006/03/26 20:22:34 haselbac
3661 ! Removed error trap for GL model
3662 !
3663 ! Revision 1.31 2005/12/13 23:30:53 haselbac
3664 ! Cosmetics
3665 !
3666 ! Revision 1.30 2005/12/13 23:11:46 fnajjar
3667 ! Added if statement to write Tecplot header for non-null nPcls
3668 !
3669 ! Revision 1.29 2005/11/27 02:01:53 haselbac
3670 ! Added support for EEv
3671 !
3672 ! Revision 1.28 2005/11/17 22:33:21 haselbac
3673 ! Bug fixes to allow only geometry to be postprocd with SPEC
3674 !
3675 ! Revision 1.27 2005/11/10 02:52:23 haselbac
3676 ! Added writing of gv for variable properties cases
3677 !
3678 ! Revision 1.26 2005/09/23 19:01:31 haselbac
3679 ! Added capability to write patch stats files
3680 !
3681 ! Revision 1.25 2005/08/10 00:38:48 haselbac
3682 ! Modified writing of PV labels into header
3683 !
3684 ! Revision 1.24 2005/08/09 01:11:47 haselbac
3685 ! Rewrote field surf routines to operate on one patch at a time
3686 !
3687 ! Revision 1.23 2005/05/18 22:24:57 fnajjar
3688 ! ACH: Adapted point files to multiple regions
3689 !
3690 ! Revision 1.22 2005/05/01 14:23:10 haselbac
3691 ! Added processing of plotting vars
3692 !
3693 ! Revision 1.21 2005/01/06 04:42:51 haselbac
3694 ! Now write partition boundaries only if have no cell data
3695 !
3696 ! Revision 1.20 2004/12/27 23:34:41 haselbac
3697 ! Added writing of field cell and face data
3698 !
3699 ! Revision 1.19 2004/12/21 15:09:54 fnajjar
3700 ! Added PLAG surface statistics to Tecplot file
3701 !
3702 ! Revision 1.18 2004/11/14 19:59:31 haselbac
3703 ! Added code for incompressible fluid model
3704 !
3705 ! Revision 1.17 2004/09/27 01:42:24 haselbac
3706 ! Added call to write zone with special faces
3707 !
3708 ! Revision 1.16 2004/07/28 15:29:21 jferry
3709 ! created global variable for spec use
3710 !
3711 ! Revision 1.15 2004/07/20 03:11:58 haselbac
3712 ! Bug fix when writing surface data with species
3713 !
3714 ! Revision 1.14 2004/07/07 01:00:27 haselbac
3715 ! Added NULLIFY statements to fix problems on Blue Pacific
3716 !
3717 ! Revision 1.13 2004/07/02 03:05:56 haselbac
3718 ! Added message for closing patch file
3719 !
3720 ! Revision 1.12 2004/06/16 20:01:43 haselbac
3721 ! Complete rewrite of module, adaptation to TEC10 and surface data
3722 !
3723 ! Revision 1.11 2004/03/05 23:23:23 haselbac
3724 ! Added RFLU_WriteFileTECPLOTPoint, removed superfluous dupList
3725 !
3726 ! Revision 1.10 2003/11/25 21:03:59 haselbac
3727 ! Extended module to deal with arbitrary number of variables
3728 !
3729 ! Revision 1.9 2003/08/07 15:36:39 haselbac
3730 ! Changed var names
3731 !
3732 ! Revision 1.8 2003/05/05 18:42:51 haselbac
3733 ! Replaced plotTypeTEC by global%plotType
3734 !
3735 ! Revision 1.7 2003/05/02 21:44:50 haselbac
3736 ! Fixed bug: pGrid not set in surface data routine
3737 !
3738 ! Revision 1.6 2003/05/02 16:41:12 haselbac
3739 ! Added check for zero boundary vertices for surface data file
3740 !
3741 ! Revision 1.5 2003/04/28 22:46:04 haselbac
3742 ! Added function to write out surface data only
3743 !
3744 ! Revision 1.4 2003/04/01 16:41:34 haselbac
3745 ! Removed getting of special cells
3746 !
3747 ! Revision 1.3 2003/03/25 19:18:44 haselbac
3748 ! Fixed bug, now case with single face (only AV face) works
3749 !
3750 ! Revision 1.2 2003/03/20 20:07:19 haselbac
3751 ! Modified RegFun call to avoid probs with
3752 ! long 'RFLU_ModTECPLOT.F90' names
3753 !
3754 ! Revision 1.1 2003/03/15 19:16:54 haselbac
3755 ! Initial revision
3756 !
3757 ! ******************************************************************************
3758 
3759 
3760 
3761 
3762 
3763 
3764 
3765 
3766 
3767 
3768 
3769 
3770 
3771 
3772 
3773 
3774 
3775 
3776 
3777 
3778 
3779 
3780 
3781 
3782 
3783 
3784 
3785 
3786 
3787 
subroutine, private rflu_tec_buildheaderpatchstats(pRegion)
subroutine, public rflu_tec_destroydatapatch(pRegion, pPatch)
subroutine, public rflu_tec_writezonesurf(pRegion, pPatch, faceType, faceKind)
subroutine, public rflu_tec_destroydatafieldsurf(pRegion, pPatch)
subroutine, public rflu_tec_openfilefield(pRegion)
subroutine registerfunction(global, funName, fileName)
Definition: ModError.F90:449
subroutine, public buildfilenameplainsteady(global, dest, ext, it, fileName)
subroutine, public rflu_tec_builddatafieldvol(pRegion)
int status() const
Obtain the status of the attribute.
Definition: Attribute.h:240
subroutine, public rflu_tec_builddatapatchstats(pRegion, pPatch)
subroutine, public rflu_tec_closefilepatch(global)
subroutine, public rflu_tec_init(global)
subroutine, private rflu_tec_buildheaderpatch(pRegion)
subroutine, public rflu_tec_openfilepnt(pRegion)
subroutine, public rflu_tec_writezonefacesspecial(pRegion)
subroutine, private rflu_tec_buildheaderfield(pRegion)
subroutine, public rflu_tec_writefilefieldvol(pRegion)
subroutine, public rflu_tec_writefilepatch(pRegion, pPatch)
subroutine, public rflu_tec_closefilefield(global)
subroutine, public rflu_tec_writezoneinterf(pRegion)
subroutine, public buildfilenameplainunsteady(global, dest, ext, tm, fileName)
**********************************************************************Rocstar Simulation Suite Illinois Rocstar LLC All rights reserved ****Illinois Rocstar LLC IL **www illinoisrocstar com **sales illinoisrocstar com WITHOUT WARRANTY OF ANY **EXPRESS OR INCLUDING BUT NOT LIMITED TO THE WARRANTIES **OF FITNESS FOR A PARTICULAR PURPOSE AND **NONINFRINGEMENT IN NO EVENT SHALL THE CONTRIBUTORS OR **COPYRIGHT HOLDERS BE LIABLE FOR ANY DAMAGES OR OTHER WHETHER IN AN ACTION OF TORT OR **Arising OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE **USE OR OTHER DEALINGS WITH THE SOFTWARE **********************************************************************INTERFACE SUBROUTINE form
subroutine, public rflu_tec_openfilepatch(pRegion)
subroutine, public rflu_tec_closefilepatchstats(global)
subroutine, public rflu_tec_destroydatafieldvol(pRegion)
subroutine, public rflu_tec_closefile(global)
subroutine, public rflu_tec_writefilefieldsurf(pRegion, pPatch)
subroutine, public rflu_tec_openfile(global, title, fileName)
subroutine, public rflu_tec_openfilepatchstats(pRegion)
subroutine, public rflu_tec_closefilepnt(global)
subroutine, public rflu_tec_writezonesurfmixed(pRegion, pPatch)
subroutine, public rflu_tec_writefilepnt(pRegion)
subroutine errorstop(global, errorCode, errorLine, addMessage)
Definition: ModError.F90:483
subroutine deregisterfunction(global)
Definition: ModError.F90:469
subroutine, public rflu_tec_writezonecellsspecial(pRegion)
subroutine, public rflu_tec_builddatafieldsurf(pRegion, pPatch)
subroutine, public rflu_tec_builddatapatch(pRegion, pPatch)
subroutine, public rflu_tec_writezonevol(pRegion, cellType, cellKind)