Rocstar  1.0
Rocstar multiphysics simulation application
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
ReadInputUtil.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: read in a section of a file (until # is encountered), read
26 ! keywords and store the associated numerical values.
27 !
28 ! Description: file contains the following subroutines:
29 !
30 ! - ReadSection = section applies to all regions (reads reals)
31 ! - ReadStringSection = section applies to all regions (reads strings)
32 ! - ReadBothSection = section applies to all regions (reals and strings)
33 ! - ReadRegionSection = section applies to a range of regions
34 ! (brbeg:brend), and reads reals
35 ! - ReadBothRegionSection = section applies to a range of regions
36 ! (brbeg:brend), and reads both reals and strings
37 ! - ReadPatchSection = section applies to a range of patches (prbeg:prend)
38 ! within a range of regions (brbeg:brend)
39 ! - ReadListSection = section contains a list of values below the keyword
40 ! - ReadPrefixedListSection = section contains a list of values below the
41 ! keyword; each list is preceded by a string
42 !
43 ! Input: fileID = file number
44 ! nvals = number of values to search for and to store
45 ! keys = keywords to search for
46 ! nCols = no. of columns in the list
47 !
48 ! Output: vals = values associated with keywords (reals only)
49 ! defined = flag if for certain keyword a value was read in
50 ! brbeg = begin of region range (values set for these regions)
51 ! brend = end of region range
52 ! prbeg = begin of patch range (values set for these patches)
53 ! prend = end of patch range
54 ! distrib = single value for a patch (=0) or distribution (>0)
55 ! fname = file with distribution for a patch
56 ! nRows = no. of rows of the list
57 !
58 ! Notes:
59 !
60 ! In the routines ReadStringSection, ReadBothSection, and
61 ! ReadBothRegionSection a string does not include the possible
62 ! comment given to it in the input deck (comments begin with "!").
63 !
64 !******************************************************************************
65 !
66 ! $Id: ReadInputUtil.F90,v 1.5 2008/12/06 08:44:09 mtcampbe Exp $
67 !
68 ! Copyright: (c) 2001 by the University of Illinois
69 !
70 !******************************************************************************
71 
72 SUBROUTINE readsection( global,fileID,nvals,keys,vals,defined )
73 
74  USE moddatatypes
75  USE modglobal, ONLY : t_global
76  USE moderror
77  IMPLICIT NONE
78 
79 ! ... parameters
80  INTEGER :: fileid, nvals
81  CHARACTER(*) :: keys(nvals)
82  LOGICAL :: defined(nvals)
83  REAL(RFREAL) :: vals(nvals)
84  TYPE(t_global), POINTER :: global
85 
86 ! ... loop variables
87  INTEGER :: ival
88 
89 ! ... local variables
90  CHARACTER(256) :: line
91 
92  INTEGER :: errorflag, nc
93 
94 !******************************************************************************
95 
96  CALL registerfunction( global,'ReadSection',&
97  'ReadInputUtil.F90' )
98 
99 ! read lines from file until # or EOF found
100 
101  defined(:) = .false.
102 
103  DO
104  READ(fileid,'(A256)',iostat=errorflag) line
105  global%error = errorflag
106  IF (global%error /= 0) CALL errorstop( global,err_file_read,__line__ )
107  IF (line(1:1) == '#') EXIT
108 
109  DO ival=1,nvals
110  IF (.NOT. (defined(ival) .eqv. .true.)) THEN
111  nc = len_trim(keys(ival))
112  IF (line(1:nc) == trim(keys(ival))) THEN ! found matching keyword
113  READ(line(nc+1:256),*) vals(ival)
114  defined(ival) = .true.
115  EXIT
116  ENDIF ! line
117  ENDIF ! defined
118  ENDDO ! ival
119  ENDDO ! <empty>
120 
121 ! finalize
122 
123  CALL deregisterfunction( global )
124 
125 END SUBROUTINE readsection
126 
127 ! #############################################################################
128 ! #############################################################################
129 
130 SUBROUTINE readstringsection( global,fileID,nvals,keys,vals,defined )
131 
132  USE moddatatypes
133  USE modglobal, ONLY : t_global
134  USE moderror
135  IMPLICIT NONE
136 
137 ! ... parameters
138  INTEGER :: fileid, nvals
139  CHARACTER(*) :: keys(nvals)
140  LOGICAL :: defined(nvals)
141  CHARACTER(*) :: vals(nvals)
142  TYPE(t_global), POINTER :: global
143 
144 ! ... loop variables
145  INTEGER :: ival
146 
147 ! ... local variables
148  CHARACTER(256) :: line
149 
150  INTEGER :: errorflag, nc, iend
151 
152 !******************************************************************************
153 
154  CALL registerfunction( global,'ReadStringSection',&
155  'ReadInputUtil.F90' )
156 
157 ! read lines from file until # or EOF found
158 
159  defined(:) = .false.
160 
161  DO
162  READ(fileid,'(A256)',iostat=errorflag) line
163  global%error = errorflag
164  IF (global%error /= 0) CALL errorstop( global,err_file_read,__line__ )
165  IF (line(1:1) == '#') EXIT
166 
167  DO ival=1,nvals
168  IF (.NOT. (defined(ival).eqv..true.)) THEN
169  nc = len_trim(keys(ival))
170  IF (line(1:nc) == trim(keys(ival))) THEN ! found matching keyword
171  iend = index(line,'!')-1 ! last character before comment begins
172  IF (iend < 0) iend = 256 ! if no comment, retain entire line
173  vals(ival)=adjustl(line(nc+1:iend))
174  defined(ival) = .true.
175  EXIT
176  ENDIF ! line
177  ENDIF ! defined
178  ENDDO ! ival
179  ENDDO ! <empty>
180 
181 ! finalize
182 
183  CALL deregisterfunction( global )
184 
185 END SUBROUTINE readstringsection
186 
187 ! #############################################################################
188 ! #############################################################################
189 
190 SUBROUTINE readbothsection( global,fileID,nvals,nStrVals,keys,strKeys, &
191  vals,strvals,defined,strdefined )
192 
193  USE moddatatypes
194  USE modglobal, ONLY : t_global
195  USE moderror
196  IMPLICIT NONE
197 
198 ! ... parameters
199  INTEGER :: fileid, nvals, nstrvals
200  CHARACTER(*) :: keys(nvals), strkeys(nstrvals)
201  LOGICAL :: defined(nvals), strdefined(nstrvals)
202  REAL(RFREAL) :: vals(nvals)
203  CHARACTER(*) :: strvals(nstrvals)
204  TYPE(t_global), POINTER :: global
205 
206 ! ... loop variables
207  INTEGER :: ival
208 
209 ! ... local variables
210  CHARACTER(256) :: line
211 
212  INTEGER :: errorflag, nc, iend
213 
214 !******************************************************************************
215 
216  CALL registerfunction( global,'ReadBothSection',&
217  'ReadInputUtil.F90' )
218 
219 ! read lines from file until # or EOF found
220 
221  defined(:) = .false. ! keeps track of values being provided by the user
222  strdefined(:) = .false. ! keeps track of string values
223 
224 o:DO
225  READ(fileid,'(A256)',iostat=errorflag) line
226  global%error = errorflag
227  IF (global%error /= 0) CALL errorstop( global,err_file_read,__line__ )
228  IF (line(1:1) == '#') EXIT o
229 
230  DO ival=1,nvals
231  IF (.NOT. (defined(ival).eqv..true.)) THEN
232  nc = len_trim(keys(ival))
233  IF (line(1:nc) == trim(keys(ival))) THEN ! found matching keyword
234  READ(line(nc+1:256),*) vals(ival)
235  defined(ival) = .true.
236  cycle o
237  ENDIF ! line
238  ENDIF ! defined
239  ENDDO ! ival
240 
241  DO ival=1,nstrvals
242  IF (.NOT. (strdefined(ival).eqv..true.)) THEN
243  nc = len_trim(strkeys(ival))
244  IF (line(1:nc) == trim(strkeys(ival))) THEN ! found matching keyword
245  iend = index(line,'!')-1 ! last character before comment begins
246  IF (iend < 0) iend = 256 ! if no comment, retain entire line
247  strvals(ival)=adjustl(line(nc+1:iend))
248  strdefined(ival) = .true.
249  cycle o
250  ENDIF ! line
251  ENDIF ! strDefined
252  ENDDO ! ival
253 
254  ENDDO o
255 
256 ! finalize
257 
258  CALL deregisterfunction( global )
259 
260 END SUBROUTINE readbothsection
261 
262 ! #############################################################################
263 ! #############################################################################
264 
265 SUBROUTINE readregionsection( global,fileID,nvals,keys,vals, &
266  brbeg,brend,defined )
267 
268  USE moddatatypes
269  USE modglobal, ONLY : t_global
270  USE moderror
271  IMPLICIT NONE
272 
273 ! ... parameters
274  INTEGER :: fileid, nvals, brbeg, brend
275  CHARACTER(*) :: keys(nvals)
276  LOGICAL :: defined(nvals)
277  REAL(RFREAL) :: vals(nvals)
278  TYPE(t_global), POINTER :: global
279 
280 ! ... loop variables
281  INTEGER :: ival
282 
283 ! ... local variables
284  CHARACTER(256) :: line
285 
286  INTEGER :: errorflag, nc
287 
288 !******************************************************************************
289 
290  CALL registerfunction( global,'ReadRegionSection',&
291  'ReadInputUtil.F90' )
292 
293 ! read lines from file until # or EOF found
294 
295  brbeg = 1 ! region range: input applies to all regions (default)
296  brend = global%nRegions
297 
298  defined(:) = .false. ! keeps track of values being provided by the user
299 
300  DO
301  READ(fileid,'(A256)',iostat=errorflag) line
302  global%error = errorflag
303  IF (global%error /= 0) CALL errorstop( global,err_file_read,__line__ )
304  IF (line(1:1) == '#') EXIT
305 
306  IF (line(1:5) == 'BLOCK') THEN
307  READ(line(6:256),*) brbeg,brend
308  brend = min(brend,global%nRegions)
309  IF (brbeg <= 0 ) brbeg = 1
310  IF (brend <= 0 ) brend = global%nRegions
311  IF (brend < brbeg) brend = brbeg
312  ELSE
313  DO ival=1,nvals
314  nc = len_trim(keys(ival))
315  IF (line(1:nc) == trim(keys(ival))) THEN ! found matching keyword
316  READ(line(nc+1:256),*) vals(ival)
317  defined(ival) = .true.
318  ENDIF
319  ENDDO
320  ENDIF
321  ENDDO
322 
323 ! finalize
324 
325  CALL deregisterfunction( global )
326 
327 END SUBROUTINE readregionsection
328 
329 ! #############################################################################
330 ! #############################################################################
331 
332 SUBROUTINE readbothregionsection( global,fileID,nvals,nStrVals,keys,strKeys, &
333  vals,strvals,brbeg,brend,defined,strdefined )
334 
335  USE moddatatypes
336  USE modglobal, ONLY : t_global
337  USE moderror
338  IMPLICIT NONE
339 
340 ! ... parameters
341  INTEGER :: fileid, nvals, nstrvals, brbeg, brend
342  CHARACTER(*) :: keys(nvals), strkeys(nstrvals)
343  LOGICAL :: defined(nvals), strdefined(nstrvals)
344  REAL(RFREAL) :: vals(nvals)
345  CHARACTER(*) :: strvals(nstrvals)
346  TYPE(t_global), POINTER :: global
347 
348 ! ... loop variables
349  INTEGER :: ival
350 
351 ! ... local variables
352  CHARACTER(256) :: line
353 
354  INTEGER :: errorflag, nc, iend
355 
356 !******************************************************************************
357 
358  CALL registerfunction( global,'ReadBothRegionSection',&
359  'ReadInputUtil.F90' )
360 
361 ! read lines from file until # or EOF found
362 
363  brbeg = 1 ! region range: input applies to all regions (default)
364  brend = global%nRegions
365 
366  defined(:) = .false. ! keeps track of values being provided by the user
367  strdefined(:) = .false. ! keeps track of string values
368 
369 o:DO
370  READ(fileid,'(A256)',iostat=errorflag) line
371  global%error = errorflag
372  IF (global%error /= 0) CALL errorstop( global,err_file_read,__line__ )
373  IF (line(1:1) == '#') EXIT o
374 
375  IF (line(1:5) == 'BLOCK') THEN
376  READ(line(6:256),*) brbeg,brend
377  brend = min(brend,global%nRegions)
378  IF (brbeg <= 0 ) brbeg = 1
379  IF (brend <= 0 ) brend = global%nRegions
380  IF (brend < brbeg) brend = brbeg
381  cycle o
382  ENDIF ! line
383 
384  DO ival=1,nvals
385  IF (.NOT. (defined(ival).eqv..true.)) THEN
386  nc = len_trim(keys(ival))
387  IF (line(1:nc) == trim(keys(ival))) THEN ! found matching keyword
388  READ(line(nc+1:256),*) vals(ival)
389  defined(ival) = .true.
390  cycle o
391  ENDIF ! line
392  ENDIF ! defined
393  ENDDO ! ival
394 
395  DO ival=1,nstrvals
396  IF (.NOT. (strdefined(ival).eqv..true.)) THEN
397  nc = len_trim(strkeys(ival))
398  IF (line(1:nc) == trim(strkeys(ival))) THEN ! found matching keyword
399  iend = index(line,'!')-1 ! last character before comment begins
400  IF (iend < 0) iend = 256 ! if no comment, retain entire line
401  strvals(ival)=adjustl(line(nc+1:iend))
402  strdefined(ival) = .true.
403  cycle o
404  ENDIF ! line
405  ENDIF ! strDefined
406  ENDDO ! ival
407 
408  ENDDO o
409 
410 ! finalize
411 
412  CALL deregisterfunction( global )
413 
414 END SUBROUTINE readbothregionsection
415 
416 ! #############################################################################
417 ! #############################################################################
418 
419 #ifdef RFLO
420 SUBROUTINE readpatchsection( global,fileID,nvals,keys,vals,brbeg,brend, &
421  prbeg,prend,distrib,fname,defined )
422 #endif
423 
424 #ifdef RFLU
425 SUBROUTINE readpatchsection( global,fileID,nvals,keys,vals, &
426  prbeg,prend,distrib,fname,bcname,defined )
427 #endif
428 
429 
430  USE moddatatypes
431  USE modglobal, ONLY : t_global
432  USE moderror
433  IMPLICIT NONE
434 
435 ! ... parameters
436 #ifdef RFLO
437  INTEGER :: brbeg, brend
438 #endif
439  INTEGER :: fileid, nvals, prbeg, prend, distrib
440  CHARACTER(*) :: keys(nvals), fname
441 #ifdef RFLU
442  CHARACTER(*) :: bcname
443 #endif
444  LOGICAL :: defined(nvals)
445  REAL(RFREAL) :: vals(nvals)
446  TYPE(t_global), POINTER :: global
447 
448 ! ... loop variables
449  INTEGER :: ival
450 
451 ! ... local variables
452  CHARACTER(256) :: line
453 
454  INTEGER :: errorflag, nc
455 
456 !******************************************************************************
457 
458  CALL registerfunction( global,'ReadPatchSection',&
459  'ReadInputUtil.F90' )
460 
461 ! read lines from file until # or EOF found
462 
463 #ifdef RFLO
464  brbeg = 1 ! region range: input applies to all regions (default)
465  brend = global%nRegions
466 #endif
467 
468  prbeg = 1 ! patch range: input applies to all patches (default)
469  prend = 999999 ! can have different # of patches in each region
470 
471  distrib = 0 ! no distribution as a default
472  fname = '' ! no file name
473 
474  IF ( nvals /= 0 ) THEN
475  defined(:) = .false. ! keeps track of values being provided by the user
476  END IF ! nvals
477 
478 #ifdef RFLU
479  bcname = 'None'
480 #endif
481 
482  DO
483  READ(fileid,'(A256)',iostat=errorflag) line
484  global%error = errorflag
485  IF (global%error /= 0) CALL errorstop( global,err_file_read,__line__ )
486  IF (line(1:1) == '#') EXIT
487 
488 #ifdef RFLO
489  IF (line(1:5) == 'BLOCK') THEN
490  READ(line(6:256),*) brbeg,brend
491  brend = min(brend,global%nRegions)
492  IF (brbeg <= 0 ) brbeg = 1
493  IF (brend <= 0 ) brend = global%nRegions
494  IF (brend < brbeg) brend = brbeg
495  ELSE IF (line(1:5) == 'PATCH') THEN
496 #endif
497 #ifdef RFLU
498  IF (line(1:5) == 'PATCH') THEN
499 #endif
500  READ(line(6:256),*) prbeg,prend
501  IF (prbeg <= 0 ) prbeg = 1
502  IF (prend <= 0 ) prend = 999999
503  IF (prend < prbeg) prend = prbeg
504  ELSE IF (line(1:7) == 'DISTRIB') THEN
505  READ(line(8:256),*) distrib
506  distrib = max(distrib,0)
507  distrib = min(distrib,1)
508 #ifdef RFLO
509  ELSE IF (line(1:4) == 'FILE') THEN
510  READ(line(5:256),*) fname
511 #endif
512 #ifdef RFLU
513  ELSE IF (line(1:4) == 'NAME') THEN
514  READ(line(5:chrlen),*) bcname
515  bcname = adjustl(bcname)
516  ELSE IF (line(1:4) == 'FILE') THEN
517  fname = adjustl(line(5:chrlen))
518 #endif
519  ELSE
520  DO ival=1,nvals
521  nc = len_trim(keys(ival))
522  IF (line(1:nc) == trim(keys(ival))) THEN ! found matching keyword
523  READ(line(nc+1:256),*) vals(ival)
524  defined(ival) = .true.
525  ENDIF
526  ENDDO
527  ENDIF
528  ENDDO
529 
530 ! finalize
531 
532  CALL deregisterfunction( global )
533 
534 END SUBROUTINE readpatchsection
535 
536 ! #############################################################################
537 ! #############################################################################
538 
539 SUBROUTINE readlistsection( global,fileID,key,nCols,nRows,vals,defined )
540 
541  USE moddatatypes
542  USE modglobal, ONLY : t_global
543  USE moderror
544  IMPLICIT NONE
545 
546 ! ... parameters
547  INTEGER :: fileid, ncols, nrows
548  CHARACTER(*) :: key
549  LOGICAL :: defined
550  REAL(RFREAL), POINTER :: vals(:,:)
551  TYPE(t_global), POINTER :: global
552 
553 ! ... loop variables
554  INTEGER :: ival, n
555 
556 ! ... local variables
557  CHARACTER(256) :: line
558 
559  INTEGER :: errorflag, nc
560 
561 !******************************************************************************
562 
563  CALL registerfunction( global,'ReadListSection',&
564  'ReadInputUtil.F90' )
565 
566 ! read lines from file until # or EOF found
567 
568  defined = .false. ! initial status
569  nrows = 0
570 
571  nc = len_trim(key)
572 
573  DO
574  READ(fileid,'(A256)',err=10,end=10) line
575  IF (line(1:1) == '#') EXIT
576 
577  IF (line(1:nc) == trim(key)) THEN
578  READ(line(nc+1:256),*,err=10,end=10) nrows
579  IF (nrows > 0) THEN
580  ALLOCATE( vals(nrows,ncols),stat=errorflag )
581  global%error = errorflag
582  IF (global%error /= 0) CALL errorstop( global,err_allocate,__line__ )
583  vals(:,:) = 0.0_rfreal
584  DO ival=1,nrows
585  READ(fileid,*,err=10,end=10) (vals(ival,n), n=1,ncols)
586  ENDDO
587  defined = .true.
588  ENDIF
589  ENDIF
590  ENDDO
591 
592 ! finalize
593 
594  CALL deregisterfunction( global )
595  goto 999
596 
597 10 CONTINUE
598  CALL errorstop( global,err_file_read,__line__ )
599 
600 999 CONTINUE
601 
602 END SUBROUTINE readlistsection
603 
604 ! #############################################################################
605 ! #############################################################################
606 
607 SUBROUTINE readprefixedlistsection( global,fileID,key,nCols,nRows, &
608  vals,strvals,defined )
609 
610  USE moddatatypes
611  USE modglobal, ONLY : t_global
612  USE moderror
613  IMPLICIT NONE
614 
615 ! ... parameters
616  INTEGER :: fileid, ncols, nrows
617  CHARACTER(*) :: key
618  LOGICAL :: defined
619  REAL(RFREAL), POINTER :: vals(:,:)
620  CHARACTER(*), POINTER :: strvals(:)
621  TYPE(t_global), POINTER :: global
622 
623 ! ... loop variables
624  INTEGER :: ival, n
625 
626 ! ... local variables
627  CHARACTER(256) :: line
628 
629  INTEGER :: errorflag, nc
630 
631 !******************************************************************************
632 
633  CALL registerfunction( global,'ReadListSection',&
634  'ReadInputUtil.F90' )
635 
636 ! read lines from file until # or EOF found
637 
638  defined = .false. ! initial status
639  nrows = 0
640 
641  nc = len_trim(key)
642 
643  DO
644  READ(fileid,'(A256)',err=10,end=10) line
645  IF (line(1:1) == '#') EXIT
646 
647  IF (line(1:nc) == trim(key)) THEN
648  READ(line(nc+1:256),*,err=10,end=10) nrows
649  IF (nrows > 0) THEN
650  ALLOCATE( vals(nrows,ncols),stat=errorflag )
651  global%error = errorflag
652  IF (global%error /= 0) CALL errorstop( global,err_allocate,__line__ )
653  vals(:,:) = 0.0_rfreal
654  ALLOCATE( strvals(nrows),stat=errorflag )
655  global%error = errorflag
656  IF (global%error /= 0) CALL errorstop( global,err_allocate,__line__ )
657  strvals(:) = ""
658  DO ival=1,nrows
659  READ(fileid,*,err=10,end=10) strvals(ival),(vals(ival,n), n=1,ncols)
660  strvals(ival) = adjustl(strvals(ival))
661  ENDDO
662  defined = .true.
663  ENDIF
664  ENDIF
665  ENDDO
666 
667 ! finalize
668 
669  CALL deregisterfunction( global )
670  goto 999
671 
672 10 CONTINUE
673  CALL errorstop( global,err_file_read,__line__ )
674 
675 999 CONTINUE
676 
677 END SUBROUTINE readprefixedlistsection
678 
679 !******************************************************************************
680 !
681 ! RCS Revision history:
682 !
683 ! $Log: ReadInputUtil.F90,v $
684 ! Revision 1.5 2008/12/06 08:44:09 mtcampbe
685 ! Updated license.
686 !
687 ! Revision 1.4 2008/11/19 22:17:23 mtcampbe
688 ! Added Illinois Open Source License/Copyright
689 !
690 ! Revision 1.3 2008/10/23 18:20:55 mtcampbe
691 ! Crazy number of changes to track and fix initialization and
692 ! restart bugs. Many improperly formed logical expressions
693 ! were fixed, and bug in allocation for data associated with
694 ! the BC_INFLOWVELTEMP boundary condition squashed in
695 ! RFLO_ReadBcInflowVelSection.F90.
696 !
697 ! Revision 1.2 2005/05/03 03:27:25 wasistho
698 ! modified RFLO reading fname
699 !
700 ! Revision 1.1 2004/12/01 16:50:31 haselbac
701 ! Initial revision after changing case
702 !
703 ! Revision 1.21 2004/07/23 22:43:15 jferry
704 ! Integrated rocspecies into rocinteract
705 !
706 ! Revision 1.20 2004/01/29 22:52:45 haselbac
707 ! Added RFLU support for FILE string
708 !
709 ! Revision 1.19 2003/12/04 03:23:03 haselbac
710 ! Cosmetic change
711 !
712 ! Revision 1.18 2003/05/15 02:57:02 jblazek
713 ! Inlined index function.
714 !
715 ! Revision 1.17 2003/03/24 23:25:48 jferry
716 ! moved some routines from libfloflu to rocinteract
717 !
718 ! Revision 1.16 2003/03/11 22:50:56 jferry
719 ! Added ReadPrefixedListSection subroutine
720 !
721 ! Revision 1.15 2003/03/11 16:04:19 jferry
722 ! Added ReadBothSection and ReadBothRegionSection subroutines
723 !
724 ! Revision 1.14 2002/10/08 15:48:35 haselbac
725 ! {IO}STAT=global%error replaced by {IO}STAT=errorFlag - SGI problem
726 !
727 ! Revision 1.13 2002/09/20 22:22:35 jblazek
728 ! Finalized integration into GenX.
729 !
730 ! Revision 1.12 2002/09/10 20:32:48 haselbac
731 ! Temporary workaround for SGI compiler bug
732 !
733 ! Revision 1.11 2002/09/09 14:03:08 haselbac
734 ! Initialize vals, otherwise get FPE with pgf90
735 !
736 ! Revision 1.10 2002/09/05 17:40:20 jblazek
737 ! Variable global moved into regions().
738 !
739 ! Revision 1.9 2002/07/25 14:48:51 haselbac
740 ! Fixed bug for nvals=0
741 !
742 ! Revision 1.8 2002/06/14 21:17:01 wasistho
743 ! Added time avg statistics
744 !
745 ! Revision 1.7 2002/03/29 23:15:22 jblazek
746 ! Corrected bug in MPI send.
747 !
748 ! Revision 1.6 2002/03/26 19:05:53 haselbac
749 ! Added ROCFLU functionality, extended ReadSection to deal with similar names
750 !
751 ! Revision 1.5 2002/02/21 23:25:05 jblazek
752 ! Blocks renamed as regions.
753 !
754 ! Revision 1.4 2002/02/09 01:47:01 jblazek
755 ! Added multi-probe option, residual smoothing, physical time step.
756 !
757 ! Revision 1.3 2002/01/08 22:09:16 jblazek
758 ! Added calculation of face vectors and volumes.
759 !
760 ! Revision 1.2 2001/12/22 00:09:38 jblazek
761 ! Added routines to store grid and solution.
762 !
763 ! Revision 1.1.1.1 2001/12/03 21:44:04 jblazek
764 ! Import of RocfluidMP
765 !
766 !******************************************************************************
767 
768 
769 
770 
771 
772 
773 
774 
775 
776 
777 
778 
779 
780 
subroutine readbothsection(global, fileID, nvals, nStrVals, keys, strKeys, vals, strVals, defined, strDefined)
subroutine readbothregionsection(global, fileID, nvals, nStrVals, keys, strKeys, vals, strVals, brbeg, brend, defined, strDefined)
CImg< T > & line(const unsigned int y0)
Get a line.
Definition: CImg.h:18421
Vector_n max(const Array_n_const &v1, const Array_n_const &v2)
Definition: Vector_n.h:354
subroutine readstringsection(global, fileID, nvals, keys, vals, defined)
subroutine registerfunction(global, funName, fileName)
Definition: ModError.F90:449
subroutine readlistsection(global, fileID, key, nCols, nRows, vals, defined)
**********************************************************************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 brbeg
subroutine readprefixedlistsection(global, fileID, key, nCols, nRows, vals, strVals, defined)
subroutine readpatchsection(global, fileID, nvals, keys, vals, brbeg, brend, prbeg, prend, distrib, profType, fname, defined)
**********************************************************************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 knode iend
**********************************************************************Rocstar Simulation Suite Illinois Rocstar LLC All rights reserved ****Illinois Rocstar LLC IL **www illinoisrocstar com **sales illinoisrocstar com WITHOUT WARRANTY OF ANY **EXPRESS OR INCLUDING BUT NOT LIMITED TO THE WARRANTIES **OF FITNESS FOR A PARTICULAR PURPOSE AND **NONINFRINGEMENT IN NO EVENT SHALL THE CONTRIBUTORS OR **COPYRIGHT HOLDERS BE LIABLE FOR ANY DAMAGES OR OTHER WHETHER IN AN ACTION OF TORT OR **Arising OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE **USE OR OTHER DEALINGS WITH THE SOFTWARE **********************************************************************INTERFACE USE ModDataTypes USE prend
const NT & n
subroutine readsection(global, fileID, nvals, keys, vals, defined)
int index() const
**********************************************************************Rocstar Simulation Suite Illinois Rocstar LLC All rights reserved ****Illinois Rocstar LLC IL **www illinoisrocstar com **sales illinoisrocstar com WITHOUT WARRANTY OF ANY **EXPRESS OR INCLUDING BUT NOT LIMITED TO THE WARRANTIES **OF FITNESS FOR A PARTICULAR PURPOSE AND **NONINFRINGEMENT IN NO EVENT SHALL THE CONTRIBUTORS OR **COPYRIGHT HOLDERS BE LIABLE FOR ANY DAMAGES OR OTHER WHETHER IN AN ACTION OF TORT OR **Arising OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE **USE OR OTHER DEALINGS WITH THE SOFTWARE **********************************************************************INTERFACE USE ModDataTypes USE prbeg
Vector_n min(const Array_n_const &v1, const Array_n_const &v2)
Definition: Vector_n.h:346
subroutine readregionsection(global, fileID, nvals, keys, vals, brbeg, brend, defined)
**********************************************************************Rocstar Simulation Suite Illinois Rocstar LLC All rights reserved ****Illinois Rocstar LLC IL **www illinoisrocstar com **sales illinoisrocstar com WITHOUT WARRANTY OF ANY **EXPRESS OR INCLUDING BUT NOT LIMITED TO THE WARRANTIES **OF FITNESS FOR A PARTICULAR PURPOSE AND **NONINFRINGEMENT IN NO EVENT SHALL THE CONTRIBUTORS OR **COPYRIGHT HOLDERS BE LIABLE FOR ANY DAMAGES OR OTHER WHETHER IN AN ACTION OF TORT OR **Arising OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE **USE OR OTHER DEALINGS WITH THE SOFTWARE **********************************************************************INTERFACE USE ModDataTypes USE nvals
subroutine errorstop(global, errorCode, errorLine, addMessage)
Definition: ModError.F90:483
static T_Key key
Definition: vinci_lass.c:76
subroutine deregisterfunction(global)
Definition: ModError.F90:469