Rocstar  1.0
Rocstar multiphysics simulation application
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
RFLU_ModColoring.F90
Go to the documentation of this file.
1 ! *********************************************************************
2 ! * Rocstar Simulation Suite *
3 ! * Copyright@2015, Illinois Rocstar LLC. All rights reserved. *
4 ! * *
5 ! * Illinois Rocstar LLC *
6 ! * Champaign, IL *
7 ! * www.illinoisrocstar.com *
8 ! * sales@illinoisrocstar.com *
9 ! * *
10 ! * License: See LICENSE file in top level of distribution package or *
11 ! * http://opensource.org/licenses/NCSA *
12 ! *********************************************************************
13 ! *********************************************************************
14 ! * THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, *
15 ! * EXPRESS OR IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES *
16 ! * OF MERCHANTABILITY, FITNESS FOR A PARTICULAR PURPOSE AND *
17 ! * NONINFRINGEMENT. IN NO EVENT SHALL THE CONTRIBUTORS OR *
18 ! * COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER *
19 ! * LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, *
20 ! * Arising FROM, OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE *
21 ! * USE OR OTHER DEALINGS WITH THE SOFTWARE. *
22 ! *********************************************************************
23 ! ******************************************************************************
24 !
25 ! Purpose: Suite of routines for coloring.
26 !
27 ! Description: None.
28 !
29 ! Notes:
30 ! 1. Use of overloading.
31 !
32 ! ******************************************************************************
33 !
34 ! $Id: RFLU_ModColoring.F90,v 1.7 2008/12/06 08:44:20 mtcampbe Exp $
35 !
36 ! Copyright: (c) 2005 by the University of Illinois
37 !
38 ! ******************************************************************************
39 
41 
42  USE modglobal, ONLY: t_global
43  USE modparameters
44  USE moddatatypes
45  USE moderror
46  USE moddatastruct, ONLY: t_region
47  USE modgrid, ONLY: t_grid
48  USE modbndpatch, ONLY: t_patch
49  USE modmpi
50 
51  IMPLICIT NONE
52 
53  PRIVATE
54  PUBLIC :: rflu_col_buildcoloring, &
59 
60 ! ******************************************************************************
61 ! Interface declaration for overloaded procedures
62 ! ******************************************************************************
63 
66  END INTERFACE
67 
68 ! ******************************************************************************
69 ! Declarations and definitions
70 ! ******************************************************************************
71 
72  CHARACTER(CHRLEN) :: RCSIdentString = &
73  '$RCSfile: RFLU_ModColoring.F90,v $ $Revision: 1.7 $'
74 
75 ! ******************************************************************************
76 ! Routines
77 ! ******************************************************************************
78 
79  CONTAINS
80 
81 
82 
83 
84 
85 
86 
87 
88 ! ******************************************************************************
89 !
90 ! Purpose: Build coloring.
91 !
92 ! Description: None.
93 !
94 ! Input:
95 ! pRegion Pointer to region
96 ! pRegionSerial Pointer to serial region
97 !
98 ! Output: None.
99 !
100 ! Notes: None.
101 !
102 ! ******************************************************************************
103 
104 SUBROUTINE rflu_col_buildcoloringp(pRegion,pRegionSerial)
105 
107 
108  IMPLICIT NONE
109 
110 ! ******************************************************************************
111 ! Declarations and definitions
112 ! ******************************************************************************
113 
114 ! ==============================================================================
115 ! Arguments
116 ! ==============================================================================
117 
118  TYPE(t_region), POINTER :: pregion,pregionserial
119 
120 ! ==============================================================================
121 ! Locals
122 ! ==============================================================================
123 
124  TYPE(t_global), POINTER :: global
125  TYPE(t_grid), POINTER :: pgrid
126 
127 ! ******************************************************************************
128 ! Start
129 ! ******************************************************************************
130 
131  global => pregion%global
132 
133  CALL registerfunction(global,'RFLU_COL_BuildColoringP', &
134  'RFLU_ModColoring.F90')
135 
136  pgrid => pregion%grid
137 
138 ! ******************************************************************************
139 ! Copy coloring
140 ! ******************************************************************************
141 
142  CALL rflu_copy_celldatas2p_i1d(global,pgrid,pgrid%col,pregionserial%grid%col)
143 
144 ! ******************************************************************************
145 ! End
146 ! ******************************************************************************
147 
148  CALL deregisterfunction(global)
149 
150 END SUBROUTINE rflu_col_buildcoloringp
151 
152 
153 
154 
155 
156 
157 
158 
159 ! ******************************************************************************
160 !
161 ! Purpose: Build coloring.
162 !
163 ! Description: None.
164 !
165 ! Input:
166 ! pRegion Pointer to region
167 !
168 ! Output: None.
169 !
170 ! Notes: None.
171 !
172 ! ******************************************************************************
173 
174 SUBROUTINE rflu_col_buildcolorings(pRegion)
175 
178 
179  USE modsortsearch
180 
181  IMPLICIT NONE
182 
183 ! ******************************************************************************
184 ! Declarations and definitions
185 ! ******************************************************************************
186 
187 ! ==============================================================================
188 ! Arguments
189 ! ==============================================================================
190 
191  TYPE(t_region), POINTER :: pregion
192 
193 ! ==============================================================================
194 ! Locals
195 ! ==============================================================================
196 
197  LOGICAL :: neednewcolor
198  INTEGER :: cntr,errorflag,icg,icg2,icl,iloc,isoc,ncellmembsmin,nsocmax, &
199  offs,rssize,rssizemax
200  INTEGER, DIMENSION(:), ALLOCATABLE :: cellmembstemp,rs
201  TYPE(t_global), POINTER :: global
202  TYPE(t_grid), POINTER :: pgrid
203 
204 
205 ! ******************************************************************************
206 ! Start
207 ! ******************************************************************************
208 
209  global => pregion%global
210 
211  CALL registerfunction(global,'RFLU_COL_BuildColoringS', &
212  'RFLU_ModColoring.F90')
213 
214  IF ( global%myProcid == masterproc .AND. &
215  global%verbLevel > verbose_none ) THEN
216  WRITE(stdout,'(A,1X,A)') solver_name,'Building coloring...'
217  END IF ! global%myProcid
218 
219  pgrid => pregion%grid
220 
221 ! ******************************************************************************
222 ! Initialize
223 ! ******************************************************************************
224 
225  rssizemax = 10000 ! Maximum allowed size of residual support
226  nsocmax = 2048 ! Maximum allowed number of struct orthog columns
227  ncellmembsmin = 100 ! Minimum number of cell members
228 
229  pgrid%nSoc = 0
230  pgrid%nSocMax = nsocmax
231 
232 ! ******************************************************************************
233 ! Allocate temporary memory
234 ! ******************************************************************************
235 
236  ALLOCATE(rs(rssizemax),stat=errorflag)
237  global%error = errorflag
238  IF ( global%error /= err_none ) THEN
239  CALL errorstop(global,err_allocate,__line__,'rs')
240  END IF ! global%errorFlag
241 
242  ALLOCATE(pgrid%soc(pgrid%nSocMax),stat=errorflag)
243  global%error = errorflag
244  IF ( global%error /= err_none ) THEN
245  CALL errorstop(global,err_allocate,__line__,'pGrid%soc')
246  END IF ! global%error
247 
248  DO isoc = 1,nsocmax
249  ALLOCATE(pgrid%soc(isoc)%cellMembs(ncellmembsmin),stat=errorflag)
250  IF ( global%error /= err_none ) THEN
251  CALL errorstop(global,err_allocate,__line__,'pGrid%soc%cellMembs')
252  END IF ! global%error
253  END DO ! iSoc
254 
255 ! ******************************************************************************
256 ! Loop over cells
257 ! ******************************************************************************
258 
259  DO icg = 1,pgrid%nCells
260 
261 ! ==============================================================================
262 ! Get stencil members and sort
263 ! ==============================================================================
264 
265  SELECT CASE ( pregion%mixtInput%spaceOrder )
266  CASE ( 1 )
267  CALL rflu_getresidualsupport1(pregion,icg,rs,rssizemax,rssize)
268  CASE ( 2 )
269 ! TEMPORARY
270 ! CALL RFLU_GetResidualSupport2(pRegion,icg,rs,rsSizeMax,rsSize)
271  CALL rflu_getresidualsupport1(pregion,icg,rs,rssizemax,rssize)
272 ! END TEMPORARY
273  CASE default
274  CALL errorstop(global,err_reached_default,__line__)
275  END SELECT ! pRegion%mixtInput%spaceOrder
276 
277 ! ==============================================================================
278 ! Loop over colors
279 ! ==============================================================================
280 
281  neednewcolor = .true.
282 
283  colorloop: DO isoc = 1,pgrid%nSoc
284 
285 ! ------------------------------------------------------------------------------
286 ! Determine whether stencil members already in this color
287 ! ------------------------------------------------------------------------------
288 
289  cntr = 0
290 
291  neednewcolor = .false.
292 
293  rsloop: DO icl = 1,rssize
294  icg2 = rs(icl)
295 
296  IF ( pgrid%soc(isoc)%nCellMembs > 0 ) THEN
297  CALL binarysearchinteger(pgrid%soc(isoc)%cellMembs(1:pgrid%soc(isoc)%nCellMembs), &
298  pgrid%soc(isoc)%nCellMembs,icg2,iloc)
299  ELSE
300  iloc = element_not_found
301  END IF ! pGrid%soc%nCellMembs
302 
303  IF ( iloc == element_not_found ) THEN
304  cntr = cntr + 1
305  ELSE
306  IF ( isoc /= pgrid%nSoc ) THEN
307  EXIT rsloop
308  ELSE
309  neednewcolor = .true.
310 
311  EXIT colorloop
312  END IF ! iSoc
313  END IF ! iLoc
314  END DO rsloop
315 
316 ! ------------------------------------------------------------------------------
317 ! Add to this color if none of the stencil members already present
318 ! ------------------------------------------------------------------------------
319 
320  IF ( (neednewcolor .EQV. .false.) .AND. (cntr == rssize) ) THEN
321  offs = pgrid%soc(isoc)%nCellMembs
322 
323 ! ----- Array too small, so reallocate -----------------------------------------
324 
325  IF ( (pgrid%soc(isoc)%nCellMembs + rssize) > SIZE(pgrid%soc(isoc)%cellMembs,1) ) THEN
326  ALLOCATE(cellmembstemp(pgrid%soc(isoc)%nCellMembs),stat=errorflag)
327  global%error = errorflag
328  IF ( global%error /= err_none ) THEN
329  CALL errorstop(global,err_allocate,__line__,'cellMembsTemp')
330  END IF !global%error
331 
332  DO icl = 1,pgrid%soc(isoc)%nCellMembs
333  cellmembstemp(icl) = pgrid%soc(isoc)%cellMembs(icl)
334  END DO ! icl
335 
336  DEALLOCATE(pgrid%soc(isoc)%cellMembs,stat=errorflag)
337  global%error = errorflag
338  IF ( global%error /= err_none ) THEN
339  CALL errorstop(global,err_deallocate,__line__,'pGrid%soc%cellMembs')
340  END IF !global%error
341 
342  ncellmembsmin = 2*(pgrid%soc(isoc)%nCellMembs + rssize)
343 
344  ALLOCATE(pgrid%soc(isoc)%cellMembs(ncellmembsmin),stat=errorflag)
345  global%error = errorflag
346  IF ( global%error /= err_none ) THEN
347  CALL errorstop(global,err_deallocate,__line__,'pGrid%soc%cellMembs')
348  END IF !global%error
349 
350  DO icl = 1,pgrid%soc(isoc)%nCellMembs
351  pgrid%soc(isoc)%cellMembs(icl) = cellmembstemp(icl)
352  END DO ! icl
353 
354  DEALLOCATE(cellmembstemp,stat=errorflag)
355  global%error = errorflag
356  IF ( global%error /= err_none ) THEN
357  CALL errorstop(global,err_deallocate,__line__,'cellMembsTemp')
358  END IF !global%error
359  END IF ! pGrid%soc%nCellMembs
360 
361 ! ----- Add stencil members and sort -------------------------------------------
362 
363  pgrid%col(icg) = isoc
364 
365  DO icl = 1,rssize
366  pgrid%soc(isoc)%cellMembs(offs+icl) = rs(icl)
367  END DO ! icl
368 
369  pgrid%soc(isoc)%nCellMembs = pgrid%soc(isoc)%nCellMembs + rssize
370 
371  CALL quicksortinteger(pgrid%soc(isoc)%cellMembs(1:pgrid%soc(isoc)%nCellMembs), &
372  pgrid%soc(isoc)%nCellMembs)
373 
374  EXIT colorloop
375  END IF ! needNewColor
376  END DO colorloop
377 
378 ! ==============================================================================
379 ! Add new color
380 ! ==============================================================================
381 
382  IF ( neednewcolor .EQV. .true. ) THEN
383  IF ( pgrid%nSoc < pgrid%nSocMax ) THEN
384  pgrid%nSoc = pgrid%nSoc + 1
385  ELSE
386 ! TEMPORARY
387  WRITE(*,*) 'ERROR! About to exceed dimensions of soc!'
388  stop
389 ! END TEMPORARY
390  END IF ! nSoc
391 
392  pgrid%col(icg) = pgrid%nSoc
393 
394  IF ( rssize > SIZE(pgrid%soc(pgrid%nSoc)%cellMembs,1) ) THEN
395  DEALLOCATE(pgrid%soc(pgrid%nSoc)%cellMembs,stat=errorflag)
396  global%error = errorflag
397  IF ( global%error /= err_none ) THEN
398  CALL errorstop(global,err_deallocate,__line__,'pGrid%soc%cellMembs')
399  END IF ! global%error
400 
401  ALLOCATE(pgrid%soc(pgrid%nSoc)%cellMembs(2*rssize),stat=errorflag)
402  global%error = errorflag
403  IF ( global%error /= err_none ) THEN
404  CALL errorstop(global,err_allocate,__line__,'pGrid%soc%cellMembs')
405  END IF ! global%error
406  END IF ! rsSize
407 
408  DO icl = 1,rssize
409  pgrid%soc(pgrid%nSoc)%cellMembs(icl) = rs(icl)
410  END DO ! icl
411 
412  pgrid%soc(pgrid%nSoc)%nCellMembs = rssize
413 
414  CALL quicksortinteger(pgrid%soc(pgrid%nSoc)%cellMembs(1:pgrid%soc(pgrid%nSoc)%nCellMembs), &
415  pgrid%soc(pgrid%nSoc)%nCellMembs)
416  END IF ! needNewColor
417  END DO ! icg
418 
419  IF ( global%myProcid == masterproc .AND. &
420  global%verbLevel > verbose_none ) THEN
421  WRITE(stdout,'(A,3X,A,1X,I6)') solver_name,'Number of colors:',pgrid%nSoc
422  END IF ! global%myProcid
423 
424 ! ******************************************************************************
425 ! Deallocate temporary memory
426 ! ******************************************************************************
427 
428  DEALLOCATE(rs,stat=errorflag)
429  global%error = errorflag
430  IF ( global%error /= err_none ) THEN
431  CALL errorstop(global,err_deallocate,__line__,'rs')
432  END IF ! global%errorFlag
433 
434  DO isoc = 1,pgrid%nSocMax
435  DEALLOCATE(pgrid%soc(isoc)%cellMembs,stat=errorflag)
436  IF ( global%error /= err_none ) THEN
437  CALL errorstop(global,err_deallocate,__line__,'pGrid%soc%cellMembs')
438  END IF ! global%error
439  END DO ! iSoc
440 
441  DEALLOCATE(pgrid%soc,stat=errorflag)
442  global%error = errorflag
443  IF ( global%error /= err_none ) THEN
444  CALL errorstop(global,err_deallocate,__line__,'pGrid%soc')
445  END IF ! global%error
446 
447  pgrid%nSoc = 0
448  pgrid%nSocMax = 0
449 
450 ! ******************************************************************************
451 ! End
452 ! ******************************************************************************
453 
454  IF ( global%myProcid == masterproc .AND. &
455  global%verbLevel > verbose_none ) THEN
456  WRITE(stdout,'(A,1X,A)') solver_name,'Building coloring done.'
457  END IF ! global%myProcid
458 
459  CALL deregisterfunction(global)
460 
461 END SUBROUTINE rflu_col_buildcolorings
462 
463 
464 
465 
466 
467 
468 ! ******************************************************************************
469 !
470 ! Purpose: Create coloring.
471 !
472 ! Description: None.
473 !
474 ! Input:
475 ! pRegion Pointer to region
476 !
477 ! Output: None.
478 !
479 ! Notes: None.
480 !
481 ! ******************************************************************************
482 
483 SUBROUTINE rflu_col_createcoloring(pRegion)
484 
485  IMPLICIT NONE
486 
487 ! ******************************************************************************
488 ! Declarations and definitions
489 ! ******************************************************************************
490 
491 ! ==============================================================================
492 ! Arguments
493 ! ==============================================================================
494 
495  TYPE(t_region), POINTER :: pregion
496 
497 ! ==============================================================================
498 ! Locals
499 ! ==============================================================================
500 
501  INTEGER :: errorflag
502  TYPE(t_global), POINTER :: global
503  TYPE(t_grid), POINTER :: pgrid
504 
505 ! ******************************************************************************
506 ! Start
507 ! ******************************************************************************
508 
509  global => pregion%global
510 
511  CALL registerfunction(global,'RFLU_COL_CreateColoring', &
512  'RFLU_ModColoring.F90')
513 
514  pgrid => pregion%grid
515 
516 ! ******************************************************************************
517 ! Allocate memory
518 ! ******************************************************************************
519 
520  ALLOCATE(pgrid%col(pgrid%nCellsTot),stat=errorflag)
521  global%error = errorflag
522  IF ( global%error /= err_none ) THEN
523  CALL errorstop(global,err_allocate,__line__,'pGrid%col')
524  END IF ! global%error
525 
526 ! ******************************************************************************
527 ! End
528 ! ******************************************************************************
529 
530  CALL deregisterfunction(global)
531 
532 END SUBROUTINE rflu_col_createcoloring
533 
534 
535 
536 
537 
538 
539 
540 
541 ! ******************************************************************************
542 !
543 ! Purpose: Destroy coloring.
544 !
545 ! Description: None.
546 !
547 ! Input:
548 ! pRegion Pointer to region
549 !
550 ! Output: None.
551 !
552 ! Notes: None.
553 !
554 ! ******************************************************************************
555 
556 SUBROUTINE rflu_col_destroycoloring(pRegion)
557 
558  IMPLICIT NONE
559 
560 ! ******************************************************************************
561 ! Declarations and definitions
562 ! ******************************************************************************
563 
564 ! ==============================================================================
565 ! Arguments
566 ! ==============================================================================
567 
568  TYPE(t_region), POINTER :: pregion
569 
570 ! ==============================================================================
571 ! Locals
572 ! ==============================================================================
573 
574  INTEGER :: errorflag
575  TYPE(t_global), POINTER :: global
576  TYPE(t_grid), POINTER :: pgrid
577 
578 ! ******************************************************************************
579 ! Start
580 ! ******************************************************************************
581 
582  global => pregion%global
583 
584  CALL registerfunction(global,'RFLU_COL_DestroyColoring', &
585  'RFLU_ModColoring.F90')
586 
587  pgrid => pregion%grid
588 
589 ! ******************************************************************************
590 ! Destroy memory
591 ! ******************************************************************************
592 
593  DEALLOCATE(pgrid%col,stat=errorflag)
594  global%error = errorflag
595  IF ( global%error /= err_none ) THEN
596  CALL errorstop(global,err_deallocate,__line__,'pGrid%col')
597  END IF ! global%error
598 
599 ! ******************************************************************************
600 ! End
601 ! ******************************************************************************
602 
603  CALL deregisterfunction(global)
604 
605 END SUBROUTINE rflu_col_destroycoloring
606 
607 
608 
609 
610 
611 
612 
613 
614 ! ******************************************************************************
615 !
616 ! Purpose: Read coloring.
617 !
618 ! Description: None.
619 !
620 ! Input:
621 ! pRegion Pointer to region
622 !
623 ! Output: None.
624 !
625 ! Notes: None.
626 !
627 ! ******************************************************************************
628 
629  SUBROUTINE rflu_col_readcoloring(pRegion)
630 
632 
633  IMPLICIT NONE
634 
635 ! ******************************************************************************
636 ! Declarations and definitions
637 ! ******************************************************************************
638 
639 ! ==============================================================================
640 ! Arguments
641 ! ==============================================================================
642 
643  TYPE(t_region), POINTER :: pregion
644 
645 ! ==============================================================================
646 ! Local variables
647 ! ==============================================================================
648 
649  INTEGER :: errorflag,icg,ifile,loopcounter,ncellstot
650  CHARACTER(CHRLEN) :: ifilename,sectionstring
651  TYPE(t_grid), POINTER :: pgrid
652  TYPE(t_global), POINTER :: global
653 
654 ! ******************************************************************************
655 ! Start
656 ! ******************************************************************************
657 
658  global => pregion%global
659 
660  CALL registerfunction(global,'RFLU_COL_ReadColoring',&
661  'RFLU_ModColoring.F90')
662 
663  IF ( global%myProcid == masterproc .AND. &
664  global%verbLevel > verbose_none ) THEN
665  WRITE(stdout,'(A,1X,A)') solver_name,'Reading coloring...'
666  END IF ! global%myProcid
667 
668  IF ( global%myProcid == masterproc .AND. &
669  global%verbLevel > verbose_none ) THEN
670  WRITE(stdout,'(A,3X,A,1X,I5.5)') solver_name,'Global region:', &
671  pregion%iRegionGlobal
672  END IF ! global%myProcid
673 
674 ! ==============================================================================
675 ! Open file
676 ! ==============================================================================
677 
678  ifile = if_rnmb
679 
680  CALL buildfilenamebasic(global,filedest_indir,'.col', &
681  pregion%iRegionGlobal,ifilename)
682 
683  OPEN(ifile,file=ifilename,form="FORMATTED",status="OLD",iostat=errorflag)
684  global%error = errorflag
685  IF ( global%error /= err_none ) THEN
686  CALL errorstop(global,err_file_open,__line__,ifilename)
687  END IF ! global%error
688 
689 ! ==============================================================================
690 ! Header and general information
691 ! ==============================================================================
692 
693  IF ( global%myProcid == masterproc .AND. &
694  global%verbLevel > verbose_low ) THEN
695  WRITE(stdout,'(A,3X,A)') solver_name,'Header information...'
696  END IF ! global%myProcid
697 
698  READ(ifile,'(A)') sectionstring
699  IF ( trim(sectionstring) /= '# ROCFLU coloring file' ) THEN
700  CALL errorstop(global,err_invalid_marker,__line__,sectionstring)
701  END IF ! TRIM
702 
703 ! ==============================================================================
704 ! Dimensions
705 ! ==============================================================================
706 
707  pgrid => pregion%grid
708 
709  READ(ifile,'(A)') sectionstring
710  IF ( trim(sectionstring) /= '# Dimensions' ) THEN
711  CALL errorstop(global,err_invalid_marker,__line__,sectionstring)
712  END IF ! TRIM
713 
714  READ(ifile,'(I8)') ncellstot
715 
716 ! ==============================================================================
717 ! Check dimensions (against those read from dimensions file)
718 ! ==============================================================================
719 
720  IF ( ncellstot /= pgrid%nCellsTot ) THEN
721  CALL errorstop(global,err_dimens_invalid,__line__)
722  END IF ! nCellsTot
723 
724 ! ==============================================================================
725 ! Rest of file
726 ! ==============================================================================
727 
728  loopcounter = 0
729 
730  DO ! set up infinite loop
731  loopcounter = loopcounter + 1
732 
733  READ(ifile,'(A)') sectionstring
734 
735  SELECT CASE ( trim(sectionstring) )
736 
737 ! ------------------------------------------------------------------------------
738 ! Vertex renumbering
739 ! ------------------------------------------------------------------------------
740 
741  CASE ( '# Coloring' )
742  IF ( global%myProcid == masterproc .AND. &
743  global%verbLevel > verbose_low ) THEN
744  WRITE(stdout,'(A,3X,A)') solver_name,'Coloring...'
745  END IF ! global%myProcid
746 
747  READ(ifile,'(10(I8))') (pgrid%col(icg),icg=1,pgrid%nCellsTot)
748 
749 ! ------------------------------------------------------------------------------
750 ! End marker
751 ! ------------------------------------------------------------------------------
752 
753  CASE ( '# End' )
754  IF ( global%myProcid == masterproc .AND. &
755  global%verbLevel > verbose_low ) THEN
756  WRITE(stdout,'(A,3X,A)') solver_name,'End marker...'
757  END IF ! global%myProcid
758 
759  EXIT
760 
761 ! ------------------------------------------------------------------------------
762 ! Invalid section string
763 ! ------------------------------------------------------------------------------
764 
765  CASE default
766  IF ( global%myProcid == masterproc .AND. &
767  global%verbLevel > verbose_low ) THEN
768  WRITE(stdout,'(3X,A)') sectionstring
769  END IF ! global%myProcid
770 
771  CALL errorstop(global,err_invalid_marker,__line__,sectionstring)
772  END SELECT ! TRIM
773 
774 ! ==============================================================================
775 ! Guard against infinite loop - might be unnecessary because of read errors?
776 ! ==============================================================================
777 
778  IF ( loopcounter >= limit_infinite_loop ) THEN
779  CALL errorstop(global,err_infinite_loop,__line__)
780  END IF ! loopCounter
781  END DO ! <empty>
782 
783 ! ==============================================================================
784 ! Close file
785 ! ==============================================================================
786 
787  CLOSE(ifile,iostat=errorflag)
788  global%error = errorflag
789  IF ( global%error /= err_none ) THEN
790  CALL errorstop(global,err_file_close,__line__,ifilename)
791  END IF ! global%error
792 
793 ! ******************************************************************************
794 ! End
795 ! ******************************************************************************
796 
797  IF ( global%myProcid == masterproc .AND. &
798  global%verbLevel > verbose_none ) THEN
799  WRITE(stdout,'(A,1X,A)') solver_name,'Reading coloring done.'
800  END IF ! global%myProcid
801 
802  CALL deregisterfunction(global)
803 
804  END SUBROUTINE rflu_col_readcoloring
805 
806 
807 
808 
809 
810 
811 
812 
813 ! ******************************************************************************
814 !
815 ! Purpose: Recreate cell list.
816 !
817 ! Description: None.
818 !
819 ! Input:
820 ! global Pointer to global data
821 ! nVertPerCell Number of vertices per cell
822 ! nCellsMax Maximum number of cells
823 ! x2v Connectivity array
824 ! x2cg Cell mapping array
825 !
826 ! Output:
827 ! nCellsMax Increased maximum number of cells
828 ! x2v Enlarged connectivity array
829 ! x2cg Enlarged cell mapping array
830 !
831 ! Notes: None.
832 !
833 ! ******************************************************************************
834 
835  SUBROUTINE rflu_col_recreatecelllist(global,nVertPerCell,nCellsMax,x2v,x2cg)
836 
837  IMPLICIT NONE
838 
839 ! ******************************************************************************
840 ! Declarations and definitions
841 ! ******************************************************************************
842 
843 ! ==============================================================================
844 ! Arguments
845 ! ==============================================================================
846 
847  INTEGER, INTENT(IN) :: nvertpercell
848  INTEGER, INTENT(INOUT) :: ncellsmax
849  INTEGER, DIMENSION(:), POINTER :: x2cg
850  INTEGER, DIMENSION(:,:), POINTER :: x2v
851  TYPE(t_global), POINTER :: global
852 
853 ! ==============================================================================
854 ! Locals
855 ! ==============================================================================
856 
857  INTEGER :: errorflag,icl,ivl,ncellsmaxold
858  INTEGER, DIMENSION(:), ALLOCATABLE:: x2cgtemp
859  INTEGER, DIMENSION(:,:), ALLOCATABLE :: x2vtemp
860 
861 ! ******************************************************************************
862 ! Start
863 ! ******************************************************************************
864 
865  CALL registerfunction(global,'RFLU_COL_RecreateCellList',&
866  'RFLU_ModColoring.F90')
867 
868 ! ******************************************************************************
869 ! Increase maximum number of cells
870 ! ******************************************************************************
871 
872  ncellsmaxold = ncellsmax
873  ncellsmax = 2*ncellsmax
874 
875 ! ******************************************************************************
876 ! Copy existing arrays into larger arrays
877 ! ******************************************************************************
878 
879 ! ==============================================================================
880 ! Connectivity array
881 ! ==============================================================================
882 
883  ALLOCATE(x2vtemp(nvertpercell,ncellsmaxold),stat=errorflag)
884  global%error = errorflag
885  IF ( global%error /= err_none ) THEN
886  CALL errorstop(global,err_allocate,__line__,'x2vTemp')
887  END IF ! global%error
888 
889  DO icl = 1,ncellsmaxold
890  DO ivl = 1,nvertpercell
891  x2vtemp(ivl,icl) = x2v(ivl,icl)
892  END DO ! ivl
893  END DO ! icl
894 
895  DEALLOCATE(x2v,stat=errorflag)
896  global%error = errorflag
897  IF ( global%error /= err_none ) THEN
898  CALL errorstop(global,err_deallocate,__line__,'x2v')
899  END IF ! global%error
900 
901  ALLOCATE(x2v(nvertpercell,ncellsmax),stat=errorflag)
902  global%error = errorflag
903  IF ( global%error /= err_none ) THEN
904  CALL errorstop(global,err_allocate,__line__,'x2v')
905  END IF ! global%error
906 
907  DO icl = 1,ncellsmaxold
908  DO ivl = 1,nvertpercell
909  x2v(ivl,icl) = x2vtemp(ivl,icl)
910  END DO ! ivl
911  END DO ! icl
912 
913  DEALLOCATE(x2vtemp,stat=errorflag)
914  global%error = errorflag
915  IF ( global%error /= err_none ) THEN
916  CALL errorstop(global,err_deallocate,__line__,'x2vTemp')
917  END IF ! global%error
918 
919 ! ==============================================================================
920 ! Cell mapping array
921 ! ==============================================================================
922 
923  ALLOCATE(x2cgtemp(ncellsmaxold),stat=errorflag)
924  global%error = errorflag
925  IF ( global%error /= err_none ) THEN
926  CALL errorstop(global,err_allocate,__line__,'x2cgTemp')
927  END IF ! global%error
928 
929  DO icl = 1,ncellsmaxold
930  x2cgtemp(icl) = x2cg(icl)
931  END DO ! icl
932 
933  DEALLOCATE(x2cg,stat=errorflag)
934  global%error = errorflag
935  IF ( global%error /= err_none ) THEN
936  CALL errorstop(global,err_deallocate,__line__,'x2cg')
937  END IF ! global%error
938 
939  ALLOCATE(x2cg(ncellsmax),stat=errorflag)
940  global%error = errorflag
941  IF ( global%error /= err_none ) THEN
942  CALL errorstop(global,err_allocate,__line__,'x2cg')
943  END IF ! global%error
944 
945  DO icl = 1,ncellsmaxold
946  x2cg(icl) = x2cgtemp(icl)
947  END DO ! icl
948 
949  DEALLOCATE(x2cgtemp,stat=errorflag)
950  global%error = errorflag
951  IF ( global%error /= err_none ) THEN
952  CALL errorstop(global,err_deallocate,__line__,'x2cgTemp')
953  END IF ! global%error
954 
955 ! ******************************************************************************
956 ! End
957 ! ******************************************************************************
958 
959  CALL deregisterfunction(global)
960 
961  END SUBROUTINE rflu_col_recreatecelllist
962 
963 
964 
965 
966 
967 
968 
969 
970 ! ******************************************************************************
971 !
972 ! Purpose: Write coloring.
973 !
974 ! Description: None.
975 !
976 ! Input:
977 ! pRegion Pointer to region
978 !
979 ! Output: None.
980 !
981 ! Notes: None.
982 !
983 ! ******************************************************************************
984 
985  SUBROUTINE rflu_col_writecoloring(pRegion)
986 
988 
989  IMPLICIT NONE
990 
991 ! ******************************************************************************
992 ! Declarations and definitions
993 ! ******************************************************************************
994 
995 ! ==============================================================================
996 ! Arguments
997 ! ==============================================================================
998 
999  TYPE(t_region), POINTER :: pregion
1000 
1001 ! ==============================================================================
1002 ! Local variables
1003 ! ==============================================================================
1004 
1005  INTEGER :: errorflag,icg,ifile
1006  CHARACTER(CHRLEN) :: ifilename,sectionstring
1007  TYPE(t_grid), POINTER :: pgrid
1008  TYPE(t_global), POINTER :: global
1009 
1010 ! ******************************************************************************
1011 ! Start
1012 ! ******************************************************************************
1013 
1014  global => pregion%global
1015 
1016  CALL registerfunction(global,'RFLU_COL_WriteColoring',&
1017  'RFLU_ModColoring.F90')
1018 
1019  IF ( global%myProcid == masterproc .AND. &
1020  global%verbLevel > verbose_none ) THEN
1021  WRITE(stdout,'(A,1X,A)') solver_name,'Writing coloring...'
1022  END IF ! global%myProcid
1023 
1024  IF ( global%myProcid == masterproc .AND. &
1025  global%verbLevel > verbose_none ) THEN
1026  WRITE(stdout,'(A,3X,A,1X,I5.5)') solver_name,'Global region:', &
1027  pregion%iRegionGlobal
1028  END IF ! global%myProcid
1029 
1030 ! ==============================================================================
1031 ! Open file
1032 ! ==============================================================================
1033 
1034  ifile = if_color
1035 
1036  CALL buildfilenamebasic(global,filedest_indir,'.col', &
1037  pregion%iRegionGlobal,ifilename)
1038 
1039  OPEN(ifile,file=ifilename,form="FORMATTED",status="UNKNOWN", &
1040  iostat=errorflag)
1041  global%error = errorflag
1042  IF ( global%error /= err_none ) THEN
1043  CALL errorstop(global,err_file_open,__line__,ifilename)
1044  END IF ! global%error
1045 
1046 ! ==============================================================================
1047 ! Header and general information
1048 ! ==============================================================================
1049 
1050  IF ( global%myProcid == masterproc .AND. &
1051  global%verbLevel > verbose_low ) THEN
1052  WRITE(stdout,'(A,3X,A)') solver_name,'Header information...'
1053  END IF ! global%myProcid
1054 
1055  sectionstring = '# ROCFLU coloring file'
1056  WRITE(ifile,'(A)') trim(sectionstring)
1057 
1058 ! ==============================================================================
1059 ! Dimensions
1060 ! ==============================================================================
1061 
1062  pgrid => pregion%grid
1063 
1064  IF ( global%myProcid == masterproc .AND. &
1065  global%verbLevel > verbose_low ) THEN
1066  WRITE(stdout,'(A,3X,A)') solver_name,'Dimensions...'
1067  END IF ! global%myProcid
1068 
1069  sectionstring = '# Dimensions'
1070  WRITE(ifile,'(A)') trim(sectionstring)
1071  WRITE(ifile,'(I8)') pgrid%nCellsTot
1072 
1073 ! ==============================================================================
1074 ! Coloring
1075 ! ==============================================================================
1076 
1077  IF ( global%myProcid == masterproc .AND. &
1078  global%verbLevel > verbose_low ) THEN
1079  WRITE(stdout,'(A,3X,A)') solver_name,'Cells...'
1080  END IF ! global%myProcid
1081 
1082  sectionstring = '# Coloring'
1083  WRITE(ifile,'(A)') trim(sectionstring)
1084  WRITE(ifile,'(10(I8))') (pgrid%col(icg),icg=1,pgrid%nCellsTot)
1085 
1086 ! ==============================================================================
1087 ! End marker
1088 ! ==============================================================================
1089 
1090  IF ( global%myProcid == masterproc .AND. &
1091  global%verbLevel > verbose_low ) THEN
1092  WRITE(stdout,'(A,3X,A)') solver_name,'End marker...'
1093  END IF ! global%myProcid
1094 
1095  sectionstring = '# End'
1096  WRITE(ifile,'(A)') trim(sectionstring)
1097 
1098 ! ==============================================================================
1099 ! Close file
1100 ! ==============================================================================
1101 
1102  CLOSE(ifile,iostat=errorflag)
1103  global%error = errorflag
1104  IF ( global%error /= err_none ) THEN
1105  CALL errorstop(global,err_file_close,__line__,ifilename)
1106  END IF ! global%error
1107 
1108 ! ******************************************************************************
1109 ! End
1110 ! ******************************************************************************
1111 
1112  IF ( global%myProcid == masterproc .AND. &
1113  global%verbLevel > verbose_none ) THEN
1114  WRITE(stdout,'(A,1X,A)') solver_name,'Writing coloring done.'
1115  END IF ! global%myProcid
1116 
1117  CALL deregisterfunction(global)
1118 
1119  END SUBROUTINE rflu_col_writecoloring
1120 
1121 
1122 
1123 
1124 
1125 
1126 
1127 
1128 ! ******************************************************************************
1129 ! End
1130 ! ******************************************************************************
1131 
1132 END MODULE rflu_modcoloring
1133 
1134 ! ******************************************************************************
1135 !
1136 ! RCS Revision history:
1137 !
1138 ! $Log: RFLU_ModColoring.F90,v $
1139 ! Revision 1.7 2008/12/06 08:44:20 mtcampbe
1140 ! Updated license.
1141 !
1142 ! Revision 1.6 2008/11/19 22:17:31 mtcampbe
1143 ! Added Illinois Open Source License/Copyright
1144 !
1145 ! Revision 1.5 2006/04/07 15:19:18 haselbac
1146 ! Removed tabs
1147 !
1148 ! Revision 1.4 2005/09/22 17:10:31 hdewey2
1149 ! Modified coloring so the Jacobian is always colored based on the 1st order cell stencil.
1150 !
1151 ! Revision 1.3 2005/08/24 01:36:15 haselbac
1152 ! Fixed bug and extended to second-order
1153 !
1154 ! Revision 1.2 2005/08/19 02:35:26 haselbac
1155 ! Changed for cColors to col, modified existing and added I/O routines
1156 !
1157 ! Revision 1.1 2005/08/17 20:04:52 hdewey2
1158 ! Initial revision
1159 !
1160 ! ******************************************************************************
1161 
1162 
1163 
1164 
1165 
1166 
1167 
1168 
1169 
1170 
1171 
1172 
1173 
subroutine buildfilenamebasic(global, dest, ext, id, fileName)
subroutine rs(nm, n, a, w, matz, z, fv1, fv2, ierr)
subroutine rflu_col_recreatecelllist(global, nVertPerCell, nCellsMax, x2v, x2cg)
subroutine registerfunction(global, funName, fileName)
Definition: ModError.F90:449
int status() const
Obtain the status of the attribute.
Definition: Attribute.h:240
subroutine, public rflu_col_createcoloring(pRegion)
subroutine, public rflu_getresidualsupport1(pRegion, icg, rs, rsSizeMax, rsSize)
subroutine quicksortinteger(a, n)
subroutine binarysearchinteger(a, n, v, i, j)
**********************************************************************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_col_destroycoloring(pRegion)
subroutine, public rflu_col_writecoloring(pRegion)
subroutine, public rflu_getresidualsupport2(pRegion, icg, rs, rsSizeMax, rsSize)
subroutine, public rflu_copy_celldatas2p_i1d(global, pGrid, var, varSerial)
subroutine rflu_col_buildcoloringp(pRegion, pRegionSerial)
subroutine errorstop(global, errorCode, errorLine, addMessage)
Definition: ModError.F90:483
subroutine deregisterfunction(global)
Definition: ModError.F90:469
subroutine, public rflu_col_readcoloring(pRegion)