Rocstar  1.0
Rocstar multiphysics simulation application
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
ModError.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: define error messages and provide an error handling function.
26 !
27 ! Description: none
28 !
29 ! Notes: none
30 !
31 ! ******************************************************************************
32 !
33 ! $Id: ModError.F90,v 1.151 2008/12/06 08:44:18 mtcampbe Exp $
34 !
35 ! Copyright: (c) 2001-2006 by the University of Illinois
36 !
37 ! ******************************************************************************
38 
39 MODULE moderror
40 
41  IMPLICIT NONE
42 
43 ! ******************************************************************************
44 ! Error codes
45 ! ******************************************************************************
46 
47 ! ==============================================================================
48 ! Common
49 ! ==============================================================================
50 
51  INTEGER, PARAMETER :: ERR_NONE = 0, & ! basics
52  ERR_REGISTER_FUN = 1, &
53  ERR_REACHED_DEFAULT = 2, &
54  ERR_PREVIOUS_ERRORS = 3, &
55  ERR_EXTERNAL_FUNCT = 4, &
56  ERR_EXCEEDS_DECL_MEM = 5, &
57  ERR_UNKNOWN_OPTION = 6, &
58  ERR_ILLEGAL_VALUE = 7, &
59  ERR_SYSTEM_COMMAND = 8, &
60  ERR_COMPILE_OPTION = 9
61 
62  INTEGER, PARAMETER :: ERR_ALLOCATE = 10, & ! memory allocation
63  ERR_DEALLOCATE = 11, &
64  ERR_ASSOCIATED = 12, &
65  ERR_ALLOCATED = 13
66 
67  INTEGER, PARAMETER :: ERR_DEPENDENT_INPUT = 15 ! input parameters
68 
69  INTEGER, PARAMETER :: ERR_FILE_OPEN = 20, & ! I/O
70  ERR_FILE_CLOSE = 21, &
71  ERR_FILE_READ = 22, &
72  ERR_FILE_WRITE = 23, &
73  ERR_FILE_EXIST = 24, &
74  ERR_UNKNOWN_FORMAT = 25, &
75  ERR_PROBE_LOCATION = 26, &
76  ERR_PROBE_SPECIFIED = 27, &
77  ERR_VAL_UNDEFINED = 28, &
78  ERR_STOPFILE_FOUND = 29
79 
80  INTEGER, PARAMETER :: ERR_UNKNOWN_BC = 30, & ! boundary conditions
81  ERR_NO_BCSPECIFIED = 31, &
82  ERR_BCVAL_MISSING = 32, &
83  ERR_NO_BCSWITCH = 33, &
84  ERR_VAL_BCSWITCH = 34, &
85  ERR_PATCH_RANGE = 35, &
86  ERR_BC_VARNAME = 36, &
87  ERR_VAL_BCVAL = 37, &
88  ERR_TBC_NONINIT = 38, &
89  ERR_BCVAL_EXTRA = 39
90 
91  INTEGER, PARAMETER :: ERR_TIME_GRID = 40, & ! time stepping
92  ERR_TIME_SOLUTION = 41, &
93  ERR_TIME_GLOBAL = 42, &
94  ERR_DTIME_NEGATIVE = 43, &
95  ERR_DITER_NEGATIVE = 44, &
96  ERR_STEADY = 45
97 
98  INTEGER, PARAMETER :: ERR_MPI_TROUBLE = 50, & ! MPI
99  ERR_NO_PROCMAP = 51, &
100  ERR_NO_PROCMATCH = 52, &
101  ERR_PATCH_OFFSET = 53, &
102  ERR_PROC_MISMATCH = 54
103 
104  INTEGER, PARAMETER :: ERR_GRID_LEVEL = 60 ! multigrid
105 
106  INTEGER, PARAMETER :: ERR_GRAD_INDEX = 65 ! Vel. and T gradients
107 
108  INTEGER, PARAMETER :: ERR_FACEVEC_SUM = 70, & ! CV geometry
109  ERR_VOLUME_SIZE = 71, &
110  ERR_FACE_SPLIT = 72, &
111  ERR_FACE_INVERTED = 73
112 
113 #ifdef STATS
114  INTEGER, PARAMETER :: ERR_STATS_INPUT = 75, & ! time avg statistics
115  ERR_STATS_RESTART = 76, &
116  ERR_STATS_INDEXING = 77, &
117  ERR_STATS_TECPLOT = 78 ! std tecplot stats
118 #endif
119 
120  INTEGER, PARAMETER :: ERR_OPTION_TYPE = 80 ! multi-physics
121 
122  INTEGER, PARAMETER :: ERR_MERGE_SORTED = 90, & ! sorting and searching
123  ERR_BINARY_SEARCH = 91
124 
125  INTEGER, PARAMETER :: ERR_GRAD_MISMATCH = 100 ! solution algorithm
126 
127  INTEGER, PARAMETER :: ERR_NEGATIVE_POSDEF = 200, &
128  ERR_INVALID_VALUE = 201
129 
130  INTEGER, PARAMETER :: ERR_SEC_READ_TWICE = 240 ! reading sections
131 
132  INTEGER, PARAMETER :: ERR_MP_ALLORNONE = 250 ! MP module use
133 
134  INTEGER, PARAMETER :: ERR_MISSING_VALUE = 260 ! IO value missing
135 
136  INTEGER, PARAMETER :: ERR_UNKNOWN_VISCMODEL = 300, & ! viscosity model
137  ERR_RK_SCHEME_INVALID = 301
138 
139  INTEGER, PARAMETER :: ERR_RAND_SEED_TYPE_INVALID = 400 ! random number generator
140 
141 ! ==============================================================================
142 ! ROCFLO specific errors
143 ! ==============================================================================
144 
145  INTEGER, PARAMETER :: ERR_REGION_RANGE = 500, & ! regions & patches
146  ERR_PATCH_2ALIGN = 501, &
147  ERR_PATCH_NOALIGN = 502, &
148  ERR_PATCH_NOSOURCE = 503, &
149  ERR_PATCH_DIMENS = 504, &
150  ERR_PATCH_NOTCOVERED = 505, &
151  ERR_WRONG_REGIONFACE = 506, &
152  ERR_PATCH_OVERLAP = 507, &
153  ERR_PATCH_OVERSPEC = 508, &
154  ERR_GRID_DIMENSIONS = 509, &
155  ERR_GRID_DUMCELLS = 510, &
156  ERR_SRCREGION_OFF = 511, &
157  ERR_NUMBER_CELLS = 512, &
158  ERR_REGION_NUMBER = 513, &
159  ERR_PATCH_NUMBER = 514
160 
161  INTEGER, PARAMETER :: ERR_VOLUME_EDGES = 900, & ! CV topology
162  ERR_VOLUME_CORNERS = 901
163 
164 ! ==============================================================================
165 ! ROCFLU specific errors
166 ! ==============================================================================
167 
168  INTEGER, PARAMETER :: LIMIT_INFINITE_LOOP = 1E6
169 
170  INTEGER, PARAMETER :: ERR_VERTEX_NUMBER = 1000, & ! data structure
171  ERR_NBFACES_WRONG = 1001, &
172  ERR_PATCH_NUMBERING = 1002, &
173  ERR_CELL_TYPE = 1003, &
174  ERR_HASHTABLE = 1004, &
175  ERR_NFACES_WRONG = 1005, &
176  ERR_NEDGES_ESTIMATE = 1006, &
177  ERR_NFACES_ESTIMATE = 1007, &
178  ERR_NCELLS_WRONG = 1008, &
179  ERR_VOLUME_DIFF = 1009, &
180  ERR_VOLUME_NEGATIVE = 1010, &
181  ERR_FACESUM = 1011, &
182  ERR_NBVERT_ESTIMATE = 1012, &
183  ERR_NBVERT_EXTREMA = 1013, &
184  ERR_BFACE_LIST_EXTREMA = 1014, &
185  ERR_FACELIST_INVALID = 1015, &
186  ERR_DIMENS_INVALID = 1016, &
187  ERR_MOVEPATCH_BC_INVALID = 1017, &
188  ERR_NEDGES_WRONG = 1018, &
189  ERR_CELL_KIND_CHECK = 1019, &
190  ERR_FACE_NVERT_INVALID = 1020, &
191  ERR_PATCH_RENUMFLAG = 1021, &
192  ERR_BVERT_LIST_INVALID = 1022, &
193  ERR_EDGELIST_INVALID = 1023, &
194  ERR_SVERT_LIST_INVALID = 1024, &
195  ERR_MOVEPATCH_BC_NOTSET = 1025, &
196  ERR_NCELLS_SPECIAL_MAX = 1026, &
197  ERR_NFACES_SPECIAL_MAX = 1027, &
198  ERR_C2FLIST_INVALID = 1028, &
199  ERR_FACE_KIND = 1029, &
200  ERR_BFACEMEMBS_INVALID = 1030, &
201  ERR_CELLGRAD_UNAVAILABLE = 1031, &
202  ERR_BF2BG_INCONSISTENT = 1032, &
203  ERR_C2CSKEY_INCONSISTENT = 1033, &
204  ERR_DISTRIB_INVALID = 1034, &
205  ERR_BCDATA_VALUE_INVALID = 1035, &
206  ERR_INDMFMIXT_INVALID = 1036, &
207  ERR_DENUMBER_LIST = 1037, &
208  ERR_PROC2REG_MAPPING = 1038, &
209  ERR_OPTIONAL_MISSING = 1039, &
210  ERR_NVERT_ESTIMATE = 1040, &
211  ERR_NFACESCUT_INVALID = 1041, &
212  ERR_CELL_NOT_FOUND = 1042, &
213  ERR_VERTEX_NOT_FOUND = 1043, &
214  ERR_NBORDERS_INVALID = 1044, &
215  ERR_REGION_IDS_INVALID = 1045, &
216  ERR_CELL_KIND_INVALID = 1046, &
217  ERR_CELL_TYPE_INVALID = 1047, &
218  ERR_VERTEX_KIND_INVALID = 1048, &
219  ERR_PARTITION_INVALID = 1049, &
220  ERR_DATADIM_MISMATCH = 1050, &
221  ERR_BUFFERDIM_MISMATCH = 1051, &
222  ERR_NREGIONS_MISMATCH = 1052, &
223  ERR_NPROCS_MISMATCH = 1053, &
224  ERR_NUM_BC_VIRTUAL = 1054, &
225  ERR_NVERTSHARED_MISMATCH = 1055, &
226  ERR_LUBOUND_MISMATCH = 1056, &
227  ERR_ALLOCATE_ADAPTIVE = 1057, &
228  ERR_RECONST_INVALID = 1058, &
229  ERR_DISCR_INVALID = 1059, &
230  ERR_ORDER_INVALID = 1060, &
231  ERR_SOLVER_TYPE_INVALID = 1061, &
232  ERR_BF2CSORTED_INVALID = 1062, &
233  ERR_CONSTR_INVALID = 1063, &
234  ERR_GASMODEL_INVALID = 1064, &
235  ERR_GASMODEL_DISCR_MISMATCH = 1065, &
236  ERR_FACE_NORMAL_INVALID = 1066, &
237  ERR_TOLERICT_INVALID = 1067, &
238  ERR_STENCILDIMENS_INVALID = 1068, &
239  ERR_STENCILMEMBER_INVALID = 1069, &
240  ERR_BC_INVALID = 1070, &
241  ERR_PATCH_BC_INCONSISTENT = 1071, &
242  ERR_REGION_ID_INVALID = 1072, &
243  ERR_FLATFLAG_INCONSISTENT = 1073, &
244  ERR_VERTEX_MATCH_FAILED = 1074, &
245  ERR_BORDER_INDEX_INVALID = 1075, &
246  ERR_REGION_ID_NOT_FOUND = 1076, &
247  ERR_PATCH_NOT_FLAT = 1077, &
248  ERR_PATCH_NOT_ALIGNED = 1078, &
249  ERR_VIRTUALCELLS_NOTDB2 = 1079, &
250  ERR_BCVAR_VALUE_INVALID = 1080
251 
252  INTEGER, PARAMETER :: ERR_INVALID_MARKER = 1100, & ! I/O
253  ERR_INVALID_NCELLS = 1101, &
254  ERR_INVALID_NVARS = 1102
255 
256  INTEGER, PARAMETER :: ERR_OLES_STENCIL = 1200, & ! Optimal LES
257  ERR_OLES_FLOWMODEL = 1201
258 
259 #ifdef GENX
260  INTEGER, PARAMETER :: ERR_BCCOUPLED_NONE = 1300, & ! GENx
261  ERR_MDOT_NEGATIVE = 1301, &
262  ERR_TFLM_NEGATIVE = 1302, &
263  ERR_TB_NEGATIVE = 1303
264 #endif
265 
266  INTEGER, PARAMETER :: ERR_NDIMENS_INVALID = 1400, & ! Grid conversion
267  ERR_NZONES_INVALID = 1401, &
268  ERR_FACETYPE_INVALID = 1402, &
269  ERR_C2VLIST_INVALID = 1403, &
270  ERR_FACE_ORIENT = 1404, &
271  ERR_STRING_INVALID = 1405, &
272  ERR_NTYPE_INVALID = 1406, &
273  ERR_NDP_INVALID = 1407
274 
275  INTEGER, PARAMETER :: ERR_LAPACK_OUTPUT = 1500, & ! LAPACK
276  ERR_DCUHRE_OUTPUT = 1510, & ! DCUHRE
277  ERR_TECPLOT_OUTPUT = 1520, & ! TECPLOT
278  ERR_TECPLOT_FILECNTR = 1521, &
279  ERR_PETSC_OUTPUT = 1530, & ! PETSC
280  ERR_MPI_OUTPUT = 1540, &
281  ERR_MPI_TAGMAX = 1541
282 
283  INTEGER, PARAMETER :: ERR_INFINITE_LOOP = 1900, & ! Miscellaneous
284  ERR_PREC_RANGE = 1901, &
285  ERR_CV_STATE_INVALID = 1902, &
286  ERR_FILEDEST_INVALID = 1903, &
287  ERR_POST_OUTPUT_FORMAT_INVALID = 1904, &
288  ERR_POST_NSERVERS_INVALID = 1905, &
289  ERR_EXCEED_DIMENS = 1906, &
290  ERR_STRING_READ = 1907
291 
292 ! ==============================================================================
293 ! ROCTURB specific errors
294 ! ==============================================================================
295 
296  INTEGER, PARAMETER :: ERR_TURB_MODULE = 2001 ! TURB-module activation
297 
298 #ifdef TURB
299  INTEGER, PARAMETER :: ERR_TURB_MODEL = 2005, & ! turbulence model
300  ERR_TURB_FIXPARAM = 2006, & ! fixed parameters
301  ERR_TURB_INPUT = 2007, & ! general turb.input
302  ERR_TURB_STATSINPUT = 2008, & ! turb statistics input
303  ERR_TURB_LESINPUT = 2009, & ! LES input-options
304  ERR_TURB_RANSINPUT = 2010, & ! RANS input-options
305  ERR_TURB_DESINPUT = 2011, & ! DES input-options
306  ERR_TURB_WLMINPUT = 2012, & ! WLM input-options
307  ERR_TURB_WLMMETRIC = 2013 ! WLM metric
308 
309  INTEGER, PARAMETER :: ERR_TURB_REGION = 2020 ! TURB-active regions
310 
311  INTEGER, PARAMETER :: ERR_TURB_WORKSPACE = 2100 ! rocturb workspace
312 #endif
313 
314 ! ==============================================================================
315 ! ROCPERI specific errors
316 ! ==============================================================================
317 
318 #ifdef PERI
319  INTEGER, PARAMETER :: ERR_PERI_INPUT = 2501, & ! periodic flow input
320  ERR_PERI_CPRBC = 2502, & ! cpr boundary condition
321  ERR_PERI_GEO = 2503, & ! geometry
322  ERR_PERI_FIXPARAM = 2504, & ! fixed parameters
323  ERR_PERI_PHYSPARAM = 2505, & ! physical parameters
324  ERR_PERI_MPI = 2506 ! MPI related errors
325 
326  INTEGER, PARAMETER :: ERR_PERI_LAST = 2600 ! upperbound error id
327 #endif
328 
329 ! ==============================================================================
330 ! ROCRAD specific errors
331 ! ==============================================================================
332 
333 #ifdef RADI
334  INTEGER, PARAMETER :: ERR_RADI_INPUT = 2601, & ! radiation user input
335  ERR_RADI_BC = 2602, & ! boundary conditions
336  ERR_RADI_FIXPARAM = 2603, & ! fixed parameters
337  ERR_RADI_METRIC = 2604, & ! radiation metric
338  ERR_RADI_MULPHASE = 2605, & ! multiphase
339  ERR_RADI_FLDINPUT = 2606, & ! FLD input option
340  ERR_RADI_REGION = 2610 ! RADI-active regions
341 
342  INTEGER, PARAMETER :: ERR_RADI_LAST = 2700 ! upperbound error id
343 #endif
344 
345 ! ==============================================================================
346 ! ROCPART specific errors
347 ! ==============================================================================
348 
349  INTEGER, PARAMETER :: ERR_PLAG_MODULE = 3001 ! PLAG-module activation
350 
351 #ifdef PLAG
352  INTEGER, PARAMETER :: ERR_PLAG_INTRPLMODEL = 3007, & ! interpolation model
353  ERR_PLAG_CELLINDEX = 3008, & ! cell indices
354  ERR_PLAG_TILESIZE = 3009, & ! tile size
355  ERR_PLAG_BREAKUPMODEL = 3010, & ! breakup model
356  ERR_PLAG_BREAKUPFAC = 3011, & ! breakup factor
357  ERR_PLAG_BREAKUPWEBSWI = 3012, & ! breakup Weber switch
358  ERR_PLAG_INJCDIAMDIST = 3013, & ! injection diameter dist model
359  ERR_PLAG_INJCDIAM = 3014, & ! injection diameter
360  ERR_PLAG_INVALID_NPCLS = 3015, &
361  ERR_PLAG_PCL_NOT_FOUND = 3016, &
362  ERR_PLAG_NCONT_INVALID = 3017, &
363  ERR_PLAG_EJECMODEL = 3018, & ! ejection model
364  ERR_PLAG_MEMOVERFLOW = 3019, & ! memory overflow
365  ERR_PLAG_FINDPCL = 3020, & ! find cell method
366  ERR_PLAG_IPCLSEND_OVERFLOW = 3021, & ! iPclSend memory overflow
367  ERR_PLAG_DSTR_INVALID = 3022
368 #endif
369 
370 ! ==============================================================================
371 ! ROCSMOKE specific errors
372 ! ==============================================================================
373 
374  INTEGER, PARAMETER :: ERR_PEUL_MODULE = 4001 ! PEUL-module activation
375 
376 #ifdef PEUL
377  INTEGER, PARAMETER :: ERR_PEUL_NPTYPES = 4010, & ! input Errors
378  ERR_PEUL_PTYPE = 4011, &
379  ERR_PEUL_BADVAL = 4013, &
380  ERR_PEUL_NPMISMATCH = 4020, &
381  ERR_PEUL_BCVAL_EXTRA = 4030, &
382  ERR_PEUL_EXTERNAL = 4900, & ! non-implementations
383  ERR_PEUL_DISTRIB = 4901, &
384  ERR_PEUL_MOVEGRID = 4902
385 #endif
386 
387 ! ==============================================================================
388 ! ROCINTERACT specific errors
389 ! ==============================================================================
390 
391  INTEGER, PARAMETER :: ERR_INRT_MODULE = 5001 ! INRT-module activation
392 
393 #ifdef INRT
394  INTEGER, PARAMETER :: ERR_INRT_DEFREAD = 5010, &
395  ERR_INRT_DEFUNREAD = 5011, &
396  ERR_INRT_READ = 5015, &
397  ERR_INRT_MULTPLAGMAT = 5020, &
398  ERR_INRT_MISSPLAGMAT = 5021, &
399  ERR_INRT_MISSINGMAT = 5025, &
400  ERR_INRT_ALLOCRANGE = 5030, &
401  ERR_INRT_INDEXRANGE = 5031, &
402  ERR_INRT_BADSWITCH = 5040, &
403  ERR_INRT_BADACTV = 5041, &
404  ERR_INRT_BADPERM = 5042, &
405  ERR_INRT_BADVAL = 5043, &
406  ERR_INRT_BADMAT = 5044, &
407  ERR_INRT_MISSINGVAL = 5045, &
408  ERR_INRT_ACTVPLAG = 5050, &
409  ERR_INRT_ACTVSMOKE = 5055, &
410  ERR_INRT_ACTVDSMOKE = 5056, &
411  ERR_INRT_PARAMETER = 5060, &
412  ERR_INRT_NINTL = 5070, &
413  ERR_INRT_NINPUTEDGES = 5071, &
414  ERR_INRT_CONNECTINTL = 5072, &
415  ERR_INRT_PERMINTL = 5073, &
416  ERR_INRT_PERMLEVINTL = 5074, &
417  ERR_INRT_BURNING1 = 5080, &
418  ERR_INRT_ONLY1 = 5081, &
419  ERR_INRT_OX_ACTV = 5082, &
420  ERR_INRT_BOIL_ACTV = 5083, &
421  ERR_INRT_BOIL_SAME = 5084, &
422  ERR_INRT_NPCLS = 5090, &
423  ERR_INRT_ENERVAPOR = 5100, &
424  ERR_INRT_NOINRT = 5900 ! non-implementations
425 #endif
426 
427 
428 ! ==============================================================================
429 ! ROCSPECIES specific errors
430 ! ==============================================================================
431 
432  INTEGER, PARAMETER :: ERR_SPEC_MODULE = 6001, &
433  ERR_SPEC_NTYPES = 6002, &
434  ERR_SPEC_MAXEQN = 6003, &
435  ERR_SPEC_PROPS_INVALID = 6004, &
436  ERR_SPEC_NSPEC_INVALID = 6005, &
437  ERR_SPEC_SOURCE_TYPE_INVALID = 6006
438 
439 ! ******************************************************************************
440 ! Error & debug functions
441 ! ******************************************************************************
442 
443  CONTAINS
444 
445 ! ==============================================================================
446 ! Register new function call
447 ! ==============================================================================
448 
449  SUBROUTINE registerfunction( global,funName,fileName )
450  USE modglobal, ONLY : t_global
451  TYPE(t_global), POINTER :: global
452  CHARACTER(*) :: funname, filename
453 
454  IF (global%nFunTree<0 .OR. &
455  global%nFunTree>=ubound(global%functionTree,2)) THEN ! wrong dimension
456  CALL errorstop( global,err_register_fun,__line__ )
457  ENDIF
458 
459  global%nFunTree = global%nFunTree + 1
460 
461  global%functionTree(1,global%nFunTree) = funname
462  global%functionTree(2,global%nFunTree) = filename
463  END SUBROUTINE registerfunction
464 
465 ! ==============================================================================
466 ! Deregister function call
467 ! ==============================================================================
468 
469  SUBROUTINE deregisterfunction( global )
470  USE modglobal, ONLY : t_global
471  TYPE(t_global), POINTER :: global
472 
473  global%functionTree(1,global%nFunTree) = ''
474  global%functionTree(2,global%nFunTree) = ''
475 
476  global%nFunTree = global%nFunTree - 1
477  END SUBROUTINE deregisterfunction
478 
479 ! ==============================================================================
480 ! Error function
481 ! ==============================================================================
482 
483  SUBROUTINE errorstop( global,errorCode,errorLine,addMessage )
484  USE moddatatypes
485  USE modglobal, ONLY : t_global
486  USE modmpi
487  USE modparameters
488 
489  LOGICAL :: flag
490  INTEGER :: errorcode,errorcode2,errorflag,errorline
491  INTEGER :: i, error
492  CHARACTER(*), OPTIONAL :: addmessage
493  CHARACTER(2*CHRLEN) :: message
494  TYPE(t_global), POINTER :: global
495 
496  errorcode2 = 1
497 
498  SELECT CASE (errorcode)
499 
500 ! ------------------------------------------------------------------------------
501 ! Basics
502 ! ------------------------------------------------------------------------------
503 
504  CASE (err_register_fun)
505  message = 'dimension of <global%functionTree> out of bounds.'
506  CASE (err_reached_default)
507  message = 'reached default statement in select construct.'
508  CASE (err_previous_errors)
509  message = 'aborting due to previous errors.'
510  CASE (err_external_funct)
511  message = 'you have to link to an external function.'
512  CASE (err_exceeds_decl_mem)
513  message = 'array index or size exceeds declared memory.'
514  CASE (err_unknown_option)
515  message = 'option unknown or not yet implemented.'
516  CASE (err_illegal_value)
517  message = 'variable has illegal value.'
518  CASE (err_system_command)
519  message = 'fail to execute system command:'
520  CASE (err_compile_option)
521  message = 'incorrect compilation option.'
522 
523 ! ------------------------------------------------------------------------------
524 ! Memory allocation
525 ! ------------------------------------------------------------------------------
526 
527  CASE (err_allocate)
528  message = 'cannot allocate memory.'
529  CASE (err_deallocate)
530  message = 'cannot deallocate memory.'
531  CASE (err_associated)
532  message = 'pointer not associated.'
533  CASE (err_allocated)
534  message = 'variable already allocated.'
535 
536 ! ------------------------------------------------------------------------------
537 ! Input parameters
538 ! ------------------------------------------------------------------------------
539 
540  CASE (err_dependent_input)
541  message = 'inconsistent dependent input.'
542 
543 ! ------------------------------------------------------------------------------
544 ! I/O
545 ! ------------------------------------------------------------------------------
546 
547  CASE (err_file_open)
548  message = 'cannot open file:'
549  CASE (err_file_close)
550  message = 'cannot close file:'
551  CASE (err_file_read)
552  message = 'cannot read from file:'
553  CASE (err_file_write)
554  message = 'cannot write to file:'
555  CASE (err_file_exist)
556  message = 'file does not exist:'
557  CASE (err_unknown_format)
558  message = 'unknown file format.'
559  CASE (err_probe_location)
560  message = 'probe located outside the flow domain.'
561  CASE (err_probe_specified)
562  message = 'probe(s) already specified.'
563  CASE (err_val_undefined)
564  message = 'value undefined:'
565  CASE (err_stopfile_found)
566  message = 'File STOP found. Delete and restart run.'
567 
568 ! ------------------------------------------------------------------------------
569 ! Boundary conditions
570 ! ------------------------------------------------------------------------------
571 
572  CASE (err_unknown_bc)
573  message = 'unknown type of boundary condition.'
574  CASE (err_no_bcspecified)
575  message = 'boundary condition not specified.'
576  CASE (err_bcval_missing)
577  message = 'boundary value(s) missing.'
578  CASE (err_no_bcswitch)
579  message = 'BC switch not specified.'
580  CASE (err_val_bcswitch)
581  message = 'BC switch value is not valid.'
582  CASE (err_patch_range)
583  message = 'patch indices outside of region`s dimensions.'
584  CASE (err_bc_varname)
585  message = 'invalid variable name for BC type:'
586  CASE (err_val_bcval)
587  message = 'BC value is not valid.'
588  CASE (err_tbc_noninit)
589  message = 'TBC not initialized.'
590 
591 ! ------------------------------------------------------------------------------
592 ! Time stepping
593 ! ------------------------------------------------------------------------------
594 
595  CASE (err_time_grid)
596  message = 'wrong physical time in grid file.'
597  CASE (err_time_solution)
598  message = 'wrong physical time in solution file.'
599  CASE (err_time_global)
600  message = 'physical time differs between processors.'
601  CASE (err_dtime_negative)
602  message = 'current time is later than the max. simulation time.'
603  CASE (err_diter_negative)
604  message = 'iteration number is higher than the max. allowed one.'
605  CASE (err_steady)
606  message = 'steady flow not allowed.'
607 
608 ! ------------------------------------------------------------------------------
609 ! MPI
610 ! ------------------------------------------------------------------------------
611 
612  CASE (err_mpi_trouble)
613  message = 'MPI does not work.'
614  CASE (err_no_procmap)
615  message = 'no mapping to processors.'
616  CASE (err_no_procmatch)
617  message = 'no. of regions does not match no. of processors.'
618  CASE (err_patch_offset)
619  message = 'no. of regions on processor > MPI_PATCHOFF.'
620  CASE (err_proc_mismatch)
621  message = 'no. of procs does not match specified no. of procs.'
622 
623 ! ------------------------------------------------------------------------------
624 ! Multigrid
625 ! ------------------------------------------------------------------------------
626 
627  CASE (err_grid_level)
628  message = 'no such grid level possible.'
629 
630 ! ------------------------------------------------------------------------------
631 ! Velocity/temperature gradients
632 ! ------------------------------------------------------------------------------
633 
634  CASE (err_grad_index)
635  message = 'inconsistent velocity/temperature gradient indexing.'
636 
637 ! ------------------------------------------------------------------------------
638 ! Geometry of control volume
639 ! ------------------------------------------------------------------------------
640 
641  CASE (err_facevec_sum)
642  message = 'sum of face vectors > 0.'
643  CASE (err_volume_size)
644  message = 'volume size below threshold or negative.'
645  CASE (err_face_split)
646  message = 'face splitting detected negative dotproduct of split face vectors.'
647  CASE (err_face_inverted)
648  message = 'inverted cell-face detected.'
649 
650 #ifdef STATS
651 ! ------------------------------------------------------------------------------
652 ! Time averaged statistics
653 ! ------------------------------------------------------------------------------
654 
655  CASE (err_stats_input)
656  message = 'required statistics input parameter not found:'
657  CASE (err_stats_restart)
658  message = 'inconsistent statistics restart parameters.'
659  CASE (err_stats_indexing)
660  message = 'inconsistent statistics indexing.'
661  CASE (err_stats_tecplot)
662  message = 'violation of fixed nStat and/or statId for tecplot.'
663 #endif
664 
665 ! ------------------------------------------------------------------------------
666 ! Multi-physics
667 ! ------------------------------------------------------------------------------
668  CASE (err_option_type)
669  message = 'unknown or unimplemented option.'
670 
671 ! ------------------------------------------------------------------------------
672 ! Sorting and searching
673 ! ------------------------------------------------------------------------------
674 
675  CASE (err_merge_sorted)
676  message = 'Error in merging sorted lists.'
677  CASE (err_binary_search)
678  message = 'Error in binary search.'
679 
680 ! ------------------------------------------------------------------------------
681 ! Solution algorithm
682 ! ------------------------------------------------------------------------------
683 
684  CASE (err_grad_mismatch)
685  message = 'mismatch of no of variables and gradients'
686 
687 ! ------------------------------------------------------------------------------
688 ! Posivity/validity checking
689 ! ------------------------------------------------------------------------------
690 
691  CASE (err_negative_posdef)
692  message = 'Negative positive-definite quantity detected.'
693  CASE (err_invalid_value)
694  message = 'Invalid quantity detected.'
695 
696 ! ------------------------------------------------------------------------------
697 ! Reading sections
698 ! ------------------------------------------------------------------------------
699 
700  CASE (err_sec_read_twice)
701  message = 'Attempted two different input sections for same region.'
702  CASE (err_missing_value)
703  message = 'Value expected in input but found missing.'
704 
705 ! ------------------------------------------------------------------------------
706 ! MP module usage
707 ! ------------------------------------------------------------------------------
708 
709  CASE (err_mp_allornone)
710  message = 'MP modules must be used in all regions or in none.'
711 
712 ! ------------------------------------------------------------------------------
713 ! Miscellaneous
714 ! ------------------------------------------------------------------------------
715 
716  CASE (err_unknown_viscmodel)
717  message = 'Unknown or unimplemented viscosity model.'
718  CASE (err_rk_scheme_invalid)
719  message = 'Chosen RK scheme invalid.'
720  CASE (err_rand_seed_type_invalid)
721  message = 'Chosen random seed type invalid.'
722 
723 ! ------------------------------------------------------------------------------
724 ! ROCFLO
725 ! ------------------------------------------------------------------------------
726 
727 ! ----- Regions & patches ------------------------------------------------------
728 
729  CASE (err_region_range)
730  message = 'number of source region out of range.'
731  CASE (err_patch_2align)
732  message = 'both patch coordinates aligned.'
733  CASE (err_patch_noalign)
734  message = 'none of patch coordinates aligned.'
735  CASE (err_patch_nosource)
736  message = 'cannot find matching source patch.'
737  CASE (err_patch_dimens)
738  message = 'patch dimension does not match distribution.'
739  CASE (err_patch_notcovered)
740  message = 'no boundary condition for some faces of a patch.'
741  CASE (err_wrong_regionface)
742  message = 'face number for a region outside 1-6'
743  CASE (err_patch_overlap)
744  message = 'boundary patches do overlap.'
745  CASE (err_patch_overspec)
746  message = 'boundary conditions already defined for this patch.'
747  CASE (err_grid_dimensions)
748  message = 'grid dimensions not the same as in topology file.'
749  CASE (err_grid_dumcells)
750  message = 'solution file contains different number of dummy cells.'
751  CASE (err_srcregion_off)
752  message = 'source region is inactive.'
753  CASE (err_number_cells)
754  message = 'not enough cells to contain dummy cells of adjacent region.'
755  CASE (err_region_number)
756  message = 'got different region number from file.'
757  CASE (err_patch_number)
758  message = 'got different patch number from file.'
759 
760 ! ----- Topology of control volume ----------------------------------------------
761 
762  CASE (err_volume_edges)
763  message = 'number of edges out of range (1-12).'
764  CASE (err_volume_corners)
765  message = 'number of corners out of range (1-8).'
766 
767 ! ------------------------------------------------------------------------------
768 ! ROCFLU
769 ! ------------------------------------------------------------------------------
770 
771  CASE (err_vertex_number)
772  message = 'invalid vertex number in array.'
773  CASE (err_nbfaces_wrong)
774  message = 'computed number of boundary faces inconsistent.'
775  CASE (err_patch_numbering)
776  message = 'patch numbering inconsistent.'
777  CASE (err_cell_type)
778  message = 'invalid cell type:'
779  CASE (err_hashtable)
780  message = 'internal inconsistency in hash table.'
781  CASE (err_nfaces_wrong)
782  message = 'computed number of internal faces inconsistent.'
783  CASE (err_nedges_estimate)
784  message = 'Estimate of number of edges too low.'
785  CASE (err_nfaces_estimate)
786  message = 'Estimate of number of faces too low.'
787  CASE (err_ncells_wrong)
788  message = 'computed number of cells inconsistent.'
789  CASE (err_volume_diff)
790  message = 'absolute difference in volumes larger than specified '// &
791  'limit.'
792  CASE (err_volume_negative)
793  message = 'Negative volume(s) detected.'
794  CASE (err_facesum)
795  message = 'face sum greater than minimum face area.'
796  CASE (err_nbvert_estimate)
797  message = 'Estimate of number of boundary vertices too low.'
798  CASE (err_nbvert_extrema)
799  message = 'Boundary vertex list has invalid extrema.'
800  CASE (err_bface_list_extrema)
801  message = 'Locally-numbered boundary-face list has invalid extrema.'
802  CASE (err_facelist_invalid)
803  message = 'Face list is invalid.'
804  CASE (err_dimens_invalid)
805  message = 'Dimension invalid'
806  CASE (err_movepatch_bc_invalid)
807  message = 'Invalid patch-motion boundary condition.'
808  CASE (err_nedges_wrong)
809  message = 'Computed number of edges inconsistent.'
810  CASE (err_cell_kind_check)
811  message = 'Actual cell touches at least one virtual vertex.'
812  CASE (err_face_nvert_invalid)
813  message = 'Number of vertices in face inconsistent.'
814  CASE (err_patch_renumflag)
815  message = 'Patch vertex renumbering flag is invalid.'
816  CASE (err_bvert_list_invalid)
817  message = 'Patch vertex list is invalid.'
818  CASE (err_edgelist_invalid)
819  message = 'Edge list is invalid.'
820  CASE (err_svert_list_invalid)
821  message = 'Special vertex list is invalid.'
822  CASE (err_movepatch_bc_notset)
823  message = 'One or more patches without boundary grid-motion bc.'
824  CASE (err_ncells_special_max)
825  message = 'Exceeded maximum allowed number of special cells.'
826  CASE (err_nfaces_special_max)
827  message = 'Exceeded maximum allowed number of special faces.'
828  CASE (err_c2flist_invalid)
829  message = 'Cell-to-face list is invalid.'
830  CASE (err_face_kind)
831  message = 'Invalid face kind:'
832  CASE (err_bfacemembs_invalid)
833  message = 'List of boundary faces for boundary gradients invalid.'
834  CASE (err_cellgrad_unavailable)
835  message = 'Cell-gradients not available.'
836  CASE (err_bf2bg_inconsistent)
837  message = 'Boundary-face gradient-access list inconsistent.'
838  CASE (err_c2cskey_inconsistent)
839  message = 'Cell-to-cell stencil access list inconsistent.'
840  CASE (err_distrib_invalid)
841  message = 'Distribution parameter invalid:'
842  CASE (err_bcdata_value_invalid)
843  message = 'Invalid value read:'
844  CASE (err_bcvar_value_invalid)
845  message = 'Invalid value read for boundary variables:'
846  CASE (err_indmfmixt_invalid)
847  message = 'Invalid value for indMfMixt.'
848  CASE (err_denumber_list)
849  message = 'Denumbering index invalid.'
850  CASE (err_proc2reg_mapping)
851  message = 'Process-to-region mapping invalid.'
852  CASE (err_optional_missing)
853  message = 'Optional argument missing.'
854  CASE (err_nvert_estimate)
855  message = 'Estimate of number of vertices too low.'
856  CASE (err_nfacescut_invalid)
857  message = 'Computed number of cut faces invalid:'
858  CASE (err_cell_not_found)
859  message = 'Cell not found during search.'
860  CASE (err_vertex_not_found)
861  message = 'Vertex not found during search.'
862  CASE (err_nborders_invalid)
863  message = 'Computed number of borders invalid:'
864  CASE (err_region_ids_invalid)
865  message = 'Region indices invalid:'
866  CASE (err_cell_kind_invalid)
867  message = 'Cell kind invalid.'
868  CASE (err_cell_type_invalid)
869  message = 'Cell type invalid:'
870  CASE (err_vertex_kind_invalid)
871  message = 'Vertex kind invalid.'
872  CASE (err_partition_invalid)
873  message = 'Partitioning invalid.'
874  CASE (err_datadim_mismatch)
875  message = 'Data dimensions mismatch.'
876  CASE (err_bufferdim_mismatch)
877  message = 'Data dimensions mismatch.'
878  CASE (err_nregions_mismatch)
879  message = 'Numbers of regions do not match.'
880  CASE (err_nprocs_mismatch)
881  message = 'Numbers of processors do not match.'
882  CASE (err_num_bc_virtual)
883  message = 'Number of virtual boundaries incorrect.'
884  CASE (err_nvertshared_mismatch)
885  message = 'Number of shared vertices does not match.'
886  CASE (err_lubound_mismatch)
887  message = 'Lower and/or upper bounds do not match.'
888  CASE (err_allocate_adaptive)
889  message = 'Adaptive memory allocation failed.'
890  CASE (err_reconst_invalid)
891  message = 'Reconstruction method invalid.'
892  CASE (err_discr_invalid)
893  message = 'Discretization method invalid.'
894  CASE (err_order_invalid)
895  message = 'Order invalid.'
896  CASE (err_solver_type_invalid)
897  message = 'Invalid solver type.'
898  CASE (err_bf2csorted_invalid)
899  message = 'Boundary-face-to-cell list invalid.'
900  CASE (err_constr_invalid)
901  message = 'Constraint method invalid.'
902  CASE (err_gasmodel_invalid)
903  message = 'Gas model invalid:'
904  CASE (err_gasmodel_discr_mismatch)
905  message = 'Gas model and discretization method do not match.'
906  CASE (err_face_normal_invalid)
907  message = 'Face normal invalid.'
908  CASE (err_tolerict_invalid)
909  message = 'In-cell test tolerance invalid.'
910  CASE (err_stencildimens_invalid)
911  message = 'Stencil dimensionality invalid.'
912  CASE (err_stencilmember_invalid)
913  message = 'Stencil member invalid.'
914  CASE (err_bc_invalid)
915  message = 'Invalid boundary condition.'
916  CASE (err_patch_bc_inconsistent)
917  message = 'Boundary condition inconsistent with patch geometry.'
918  CASE (err_region_id_invalid)
919  message = 'Region index invalid.'
920  CASE (err_flatflag_inconsistent)
921  message = 'Patch flatness flags inconsistent.'
922  CASE (err_vertex_match_failed)
923  message = 'Vertex matching failed.'
924  CASE (err_border_index_invalid)
925  message = 'Border index invalid.'
926  CASE (err_region_id_not_found)
927  message = 'Region index not found.'
928  CASE (err_patch_not_flat)
929  message = 'Patch not flat.'
930  CASE (err_patch_not_aligned)
931  message = 'Patch not aligned with coordinate axes.'
932  CASE (err_virtualcells_notdb2)
933  message = 'Virtual cells not divisible by 2.'
934 
935  CASE (err_invalid_marker)
936  message = 'invalid section marker:'
937  CASE (err_invalid_ncells)
938  message = 'number of cells invalid.'
939  CASE (err_invalid_nvars)
940  message = 'number of variables invalid.'
941 
942  CASE (err_oles_stencil)
943  message = 'inconsistency in stencil construction.'
944  CASE (err_oles_flowmodel)
945  message = 'Optimal LES approach needs Navier-Stokes flow model.'
946 
947 #ifdef GENX
948  CASE (err_bccoupled_none)
949  message = 'No coupled boundaries defined.'
950  CASE (err_mdot_negative)
951  message = 'Received negative mass flux on burning patch.'
952  CASE (err_tflm_negative)
953  message = 'Received negative flame temperature on burning patch.'
954  CASE (err_tb_negative)
955  message = 'Received negative temperature on non-burning patch.'
956 #endif
957 
958  CASE (err_ndimens_invalid)
959  message = 'Number of dimensions invalid.'
960  CASE (err_nzones_invalid)
961  message = 'Number of zones invalid.'
962  CASE (err_facetype_invalid)
963  message = 'Face type invalid.'
964  CASE (err_c2vlist_invalid)
965  message = 'Cell-to-vertex list is invalid.'
966  CASE (err_face_orient)
967  message = 'Face-orientation check failed.'
968  CASE (err_string_invalid)
969  message = 'Section string invalid.'
970  CASE (err_ntype_invalid)
971  message = 'Element type invalid.'
972  CASE (err_ndp_invalid)
973  message = 'Number of nodes invalid for given element type.'
974 
975  CASE (err_lapack_output)
976  message = 'LAPACK routine returned non-zero info variable.'
977  CASE (err_dcuhre_output)
978  message = 'DCUHRE routine returned non-zero error variable.'
979  CASE (err_tecplot_output)
980  message = 'TECPLOT routine returned non-zero error variable.'
981  CASE (err_tecplot_filecntr)
982  message = 'TECPLOT file counter exceeds maximum.'
983  CASE (err_petsc_output)
984  message = 'PETSc routine returned non-zero error variable.'
985  CASE (err_mpi_output)
986  message = 'MPI routine returned non-zero error variable.'
987  CASE (err_mpi_tagmax)
988  message = 'Exceeded maximum tag value allowed by MPI.'
989 
990  CASE (err_infinite_loop)
991  message = 'detected what appears to be an infinite loop.'
992  CASE (err_prec_range)
993  message = 'incompatible precision and range of file data.'
994  CASE (err_cv_state_invalid)
995  message = 'State of solution vector invalid.'
996  CASE (err_filedest_invalid)
997  message = 'File destination invalid.'
998  CASE (err_post_output_format_invalid)
999  message = 'Postprocessing output format invalid.'
1000  CASE (err_post_nservers_invalid)
1001  message = 'Number of servers invalid.'
1002  CASE (err_exceed_dimens)
1003  message = 'Exceeding dimensions of array:'
1004  CASE (err_string_read)
1005  message = 'Cannot read string.'
1006 
1007 ! ------------------------------------------------------------------------------
1008 ! ROCTURB specific errors
1009 ! ------------------------------------------------------------------------------
1010 
1011  CASE (err_turb_module) ! reserved for RFLO/U_CheckUserInput
1012  message = 'inconsistency of flow model and Rocturb module.'
1013 #ifdef TURB
1014  CASE (err_turb_model)
1015  message = 'undefined turbulence model selected.'
1016  CASE (err_turb_fixparam)
1017  message = 'incorrect fixed parameters setting.'
1018  CASE (err_turb_input)
1019  message = 'violation in general turbulence input:'
1020  CASE (err_turb_statsinput)
1021  message = 'violation in turbulence statistics input:'
1022  CASE (err_turb_lesinput)
1023  message = 'violation of LES input-options:'
1024  CASE (err_turb_ransinput)
1025  message = 'violation of RANS input-options:'
1026  CASE (err_turb_desinput)
1027  message = 'violation of DES input-options:'
1028  CASE (err_turb_wlminput)
1029  message = 'violation of WLM input-options:'
1030  CASE (err_turb_wlmmetric)
1031  message = 'violation of WLM metric values:'
1032  CASE (err_turb_region)
1033  message = 'turbulence model is not active in this region.'
1034  CASE (err_turb_workspace)
1035  message = 'reserved workspace being used.'
1036 #endif
1037 
1038 ! ------------------------------------------------------------------------------
1039 ! ROCPERI specific errors
1040 ! ------------------------------------------------------------------------------
1041 
1042 #ifdef PERI
1043  CASE (err_peri_input)
1044  message = 'inconsistency in PERI input parameters.'
1045  CASE (err_peri_cprbc)
1046  message = 'inconsistency in CPR boundary conditions.'
1047  CASE (err_peri_geo)
1048  message = 'inconsistency in PERI geometry.'
1049  CASE (err_peri_fixparam)
1050  message = 'inconsistency in PERI fixed parameters.'
1051  CASE (err_peri_physparam)
1052  message = 'inconsistency in PERI physical parameters.'
1053  CASE (err_peri_mpi)
1054  message = 'MPI related error.'
1055 #endif
1056 
1057 ! ------------------------------------------------------------------------------
1058 ! ROCRAD specific errors
1059 ! ------------------------------------------------------------------------------
1060 
1061 #ifdef RADI
1062  CASE (err_radi_input)
1063  message = 'violation of radiation input-options:'
1064  CASE (err_radi_bc)
1065  message = 'inconsistency in radiation bc:'
1066  CASE (err_radi_fixparam)
1067  message = 'incorrect fixed parameters setting.'
1068  CASE (err_radi_metric)
1069  message = 'inconsistency in radiation metric:'
1070  CASE (err_radi_mulphase)
1071  message = 'multiphase inconsistency from other physics modules:'
1072  CASE (err_radi_fldinput)
1073  message = 'violation of FLD radiation input-options:'
1074  CASE (err_radi_region)
1075  message = 'radiation model is not active in this region.'
1076 #endif
1077 
1078 ! -------------------------------------------------------------------------------
1079 ! ROCPART specific errors
1080 ! ------------------------------------------------------------------------------
1081 
1082  CASE (err_plag_module) ! used in PLAG_CheckUserInput
1083  message = 'inconsistency of flow model and RocPart module.'
1084 #ifdef PLAG
1085  CASE (err_plag_intrplmodel)
1086  message = 'undefined interpolation mixture model selected.'
1087  CASE (err_plag_cellindex)
1088  message = 'unable to locate particle in cell.'
1089  CASE (err_plag_tilesize)
1090  message = 'got different tile size from file.'
1091  CASE (err_plag_breakupmodel)
1092  message = 'undefined breakup model selected.'
1093  CASE (err_plag_breakupfac)
1094  message = 'inconsistent breakup factor selected.'
1095  CASE (err_plag_breakupwebswi)
1096  message = 'inconsistent breakup Weber switch selected.'
1097  CASE (err_plag_injcdiamdist)
1098  message = 'undefined injection diameter distribution model selected.'
1099  CASE (err_plag_injcdiam)
1100  message = 'inconsistent injection diameters selected.'
1101  CASE (err_plag_invalid_npcls)
1102  message = 'number of particles invalid:'
1103  CASE (err_plag_pcl_not_found)
1104  message = 'Could not find particle:'
1105  CASE (err_plag_ncont_invalid)
1106  message = 'Number of constituents invalid.'
1107  CASE (err_plag_ejecmodel)
1108  message = 'undefined ejection model selected.'
1109  CASE (err_plag_memoverflow)
1110  message = 'Maximum dimension exceeded.'
1111  CASE (err_plag_findpcl)
1112  message = 'undefined find particle cell method selected.'
1113  CASE (err_plag_ipclsend_overflow)
1114  message = 'Maximum dimension of pBorder%iPclSend exceeded.'
1115  CASE (err_plag_dstr_invalid)
1116  message = 'Data structure invalid.'
1117 #endif
1118 
1119 ! ------------------------------------------------------------------------------
1120 ! ROCSMOKE specific errors
1121 ! ------------------------------------------------------------------------------
1122 
1123  CASE (err_peul_module)
1124  message = 'inconsistency of flow model and Rocsmoke module.'
1125 #ifdef PEUL
1126  CASE (err_peul_nptypes)
1127  message = 'number of Eulerian particle types not constant.'
1128  CASE (err_peul_ptype)
1129  message = 'a CONPART_PTYPE section occurs before any CONPART.'
1130  CASE (err_peul_badval)
1131  message = 'invalid input value for Eulerian particles.'
1132  CASE (err_peul_npmismatch)
1133  message = 'number of particle types not equal to nCv.'
1134  CASE (err_peul_bcval_extra)
1135  message = 'boundary value specified for non-existent smoke type.'
1136  CASE (err_peul_external)
1137  message = 'external boundaries not yet implemented for PEUL.'
1138  CASE (err_peul_distrib)
1139  message = 'distribution boundaries not yet implemented for PEUL.'
1140  CASE (err_peul_movegrid)
1141  message = 'moving grids not yet implemented for PEUL.'
1142 #endif
1143 
1144 ! ------------------------------------------------------------------------------
1145 ! ROCINTERACT specific errors
1146 ! ------------------------------------------------------------------------------
1147 
1148  CASE (err_inrt_module)
1149  message = 'inconsistency of flow model and Rocinteract module.'
1150 #ifdef INRT
1151  CASE (err_inrt_defread)
1152  message = 'cannot read INRT_DEFAULT section twice for a region.'
1153  CASE (err_inrt_defunread)
1154  message = 'cannot read an interaction without an INRT_DEFAULT.'
1155  CASE (err_inrt_read)
1156  message = 'cannot read an interaction section twice for a region.'
1157  CASE (err_inrt_multplagmat)
1158  message = 'two distinct PLAG constituents are the same material.'
1159  CASE (err_inrt_missplagmat)
1160  message = 'material name read does not match any PLAG material.'
1161  CASE (err_inrt_missingmat)
1162  message = 'missing material name in input deck.'
1163  CASE (err_inrt_allocrange)
1164  message = 'array allocated to the wrong size.'
1165  CASE (err_inrt_indexrange)
1166  message = 'index out of range.'
1167  CASE (err_inrt_badswitch)
1168  message = 'invalid input value for an interaction switch.'
1169  CASE (err_inrt_badactv)
1170  message = 'invalid value for Activeness.'
1171  CASE (err_inrt_badperm)
1172  message = 'invalid value for Permission level.'
1173  CASE (err_inrt_badval)
1174  message = 'invalid input value for an interaction.'
1175  CASE (err_inrt_badmat)
1176  message = 'invalid input name for a material.'
1177  CASE (err_inrt_missingval)
1178  message = 'missing input data for an interaction.'
1179  CASE (err_inrt_actvplag)
1180  message = 'Lagrangian particle constituents differ in Activeness.'
1181  CASE (err_inrt_actvsmoke)
1182  message = 'Smoke type cannot be more active than Gas.'
1183  CASE (err_inrt_actvdsmoke)
1184  message = 'whether is as active as Gas was altered for interaction.'
1185  CASE (err_inrt_parameter)
1186  message = 'inconsistent values assigned to parameters.'
1187  CASE (err_inrt_nintl)
1188  message = 'number of Internal Nodes must be 0 or 1.'
1189  CASE (err_inrt_ninputedges)
1190  message = 'Internal Node needs least one input and one output Edge.'
1191  CASE (err_inrt_connectintl)
1192  message = 'Node is misconnected to Internal Node.'
1193  CASE (err_inrt_permintl)
1194  message = 'invalid Permission token on Internal Node.'
1195  CASE (err_inrt_permlevintl)
1196  message = 'invalid Permission Level for Internal Node.'
1197  CASE (err_inrt_burning1)
1198  message = 'inconsistency in Activeness for Burning interaction.'
1199  CASE (err_inrt_only1)
1200  message = 'only one oxidizer or boiling product smoke type allowed.'
1201  CASE (err_inrt_ox_actv)
1202  message = 'oxidizer smoke type cannot be active.'
1203  CASE (err_inrt_boil_actv)
1204  message = 'boiling product smoke type must be active.'
1205  CASE (err_inrt_boil_same)
1206  message = 'boiling input and output need same physical properties.'
1207  CASE (err_inrt_npcls)
1208  message = 'interactions with particles exist, but not particles.'
1209  CASE (err_inrt_enervapor)
1210  message = 'vapor energy positive, but nothing should be creating it.'
1211  CASE (err_inrt_noinrt)
1212  message = 'interaction not implemented.'
1213 #endif
1214 
1215 ! ------------------------------------------------------------------------------
1216 ! ROCSPECIES specific errors
1217 ! ------------------------------------------------------------------------------
1218 
1219  CASE (err_spec_module)
1220  message = 'Inconsistency of flow model and Rocspecies module.'
1221  CASE (err_spec_ntypes)
1222  message = 'Number of SPECIES_TYPE sections unequal to NSPECIES'
1223  CASE (err_spec_maxeqn)
1224  message = 'NSPECIES inconsistent with MAXEQN:'
1225  CASE (err_spec_props_invalid)
1226  message = 'MOLW and SPHT invalid: gamma out of bounds'
1227  CASE (err_spec_nspec_invalid)
1228  message = 'Number of species invalid:'
1229  CASE (err_spec_source_type_invalid)
1230  message = 'Source type invalid.'
1231 
1232 ! ------------------------------------------------------------------------------
1233 ! If everything fails...
1234 ! ------------------------------------------------------------------------------
1235 
1236  CASE default
1237  message = 'reason unknown.'
1238  END SELECT
1239 
1240 ! ------------------------------------------------------------------------------
1241 ! Write error message
1242 ! ------------------------------------------------------------------------------
1243 
1244  IF (present(addmessage)) THEN
1245  message = trim(message)//' '//trim(addmessage)
1246  ENDIF ! PRESENT
1247 
1248  WRITE(stderr,'(A)') solver_name
1249  WRITE(stderr,'(A,1X,A,I5.5,A,A)') solver_name,'ERROR (proc. ', &
1250  global%myProcid,') - ',trim(message)
1251 
1252  WRITE(stderr,'(A,1X,5(A),I4)') &
1253  solver_name,'Function: ',trim(global%functionTree(1,global%nFunTree)), &
1254  ', file: ',trim(global%functionTree(2,global%nFunTree)), &
1255  ', line: ',errorline
1256 
1257  DO i=global%nFunTree-1,1,-1 ! write out call tree
1258  WRITE(stderr,'(A,1X,4(A))') &
1259  solver_name,'Called from: ',trim(global%functionTree(1,i)), &
1260  ', file: ',trim(global%functionTree(2,i))
1261  ENDDO
1262 
1263  WRITE(stderr,'(A)') solver_name
1264 
1265 ! ------------------------------------------------------------------------------
1266 ! Stop the run
1267 ! ------------------------------------------------------------------------------
1268 
1269 #ifdef RFLU
1270  CALL mpi_initialized(flag,errorflag)
1271 
1272  IF ( flag .EQV. .true. ) THEN
1273  IF ( global%nProcAlloc == 1 ) THEN
1274  CALL mpi_finalize(errorflag)
1275  ELSE
1276  CALL mpi_abort(global%mpiComm,errorcode2,errorflag)
1277  END IF ! global%nProcAlloc
1278  END IF ! flag
1279 
1280  stop 1
1281 #endif
1282 
1283 #ifdef RFLO
1284 #ifdef MPI
1285  IF (global%nProcAlloc == 1) THEN
1286  CALL mpi_finalize( error )
1287  ELSE
1288  CALL mpi_abort( error )
1289  ENDIF
1290 #endif
1291  stop 1
1292 #endif
1293  END SUBROUTINE errorstop
1294 
1295 END MODULE moderror
1296 
1297 ! ******************************************************************************
1298 !
1299 ! RCS Revision history:
1300 !
1301 ! $Log: ModError.F90,v $
1302 ! Revision 1.151 2008/12/06 08:44:18 mtcampbe
1303 ! Updated license.
1304 !
1305 ! Revision 1.150 2008/11/19 22:17:29 mtcampbe
1306 ! Added Illinois Open Source License/Copyright
1307 !
1308 ! Revision 1.149 2007/03/27 00:18:07 haselbac
1309 ! Added new error condition for PLAG
1310 !
1311 ! Revision 1.148 2006/10/20 21:29:54 mparmar
1312 ! Added ERR_BCVAR_VALUE_INVALID for NSCBC
1313 !
1314 ! Revision 1.147 2006/08/21 16:46:01 haselbac
1315 ! Added error condition
1316 !
1317 ! Revision 1.146 2006/04/07 15:19:18 haselbac
1318 ! Removed tabs
1319 !
1320 ! Revision 1.145 2006/04/07 14:45:03 haselbac
1321 ! Added new error cases for patch flatness and orientation
1322 !
1323 ! Revision 1.144 2006/03/30 20:48:39 haselbac
1324 ! Added error treatment of spec src terms
1325 !
1326 ! Revision 1.143 2006/03/26 20:21:49 haselbac
1327 ! Removed ifdefs on SPEC, required for error checking
1328 !
1329 ! Revision 1.142 2006/03/25 21:45:24 haselbac
1330 ! Added error conditions for sype patches
1331 !
1332 ! Revision 1.141 2006/03/24 23:34:10 wasistho
1333 ! added ERR_DEPENDENT_INPUT
1334 !
1335 ! Revision 1.140 2006/03/22 03:04:08 wasistho
1336 ! added ERR_PATCH_NUMBER
1337 !
1338 ! Revision 1.139 2006/01/06 22:07:49 haselbac
1339 ! Added stencil error conditions, changed ERR_ASSOCIATED message
1340 !
1341 ! Revision 1.138 2005/12/24 21:27:00 haselbac
1342 ! Added error treatment for ICT tolerance
1343 !
1344 ! Revision 1.137 2005/12/01 18:37:54 fnajjar
1345 ! Added error trap for missing value
1346 !
1347 ! Revision 1.136 2005/12/01 17:11:37 fnajjar
1348 ! Added error trap for randSeedType
1349 !
1350 ! Revision 1.135 2005/11/14 16:56:35 haselbac
1351 ! Modified message for invalid gas model
1352 !
1353 ! Revision 1.134 2005/11/10 02:20:54 haselbac
1354 ! Added error treatment for gas model and species
1355 !
1356 ! Revision 1.133 2005/11/04 14:08:35 haselbac
1357 ! Added face normal error treatment
1358 !
1359 ! Revision 1.132 2005/10/31 19:26:31 haselbac
1360 ! Added error treatment for gas model
1361 !
1362 ! Revision 1.131 2005/10/27 18:57:18 haselbac
1363 ! Added err treatment of invalid constraints
1364 !
1365 ! Revision 1.130 2005/10/14 14:03:31 haselbac
1366 ! Added ERR_TB_NEGATIVE
1367 !
1368 ! Revision 1.129 2005/10/05 20:04:02 haselbac
1369 ! Added error treatment for ENSIGHT filter
1370 !
1371 ! Revision 1.128 2005/09/20 15:47:53 fnajjar
1372 ! Added error definition for iPclSend memory overflow
1373 !
1374 ! Revision 1.127 2005/08/05 15:27:04 haselbac
1375 ! Added new condition, cleaned up
1376 !
1377 ! Revision 1.126 2005/08/03 18:54:12 hdewey2
1378 ! Added parameter for invalid solver type
1379 !
1380 ! Revision 1.125 2005/07/14 21:40:26 haselbac
1381 ! Added new error conditions for invalid DISCR and ORDER
1382 !
1383 ! Revision 1.124 2005/07/11 19:24:54 mparmar
1384 ! Aded error treatment for invalid reconst option
1385 !
1386 ! Revision 1.123 2005/07/04 17:20:46 haselbac
1387 ! Bug fix: Proper error treatment depending on MPI
1388 !
1389 ! Revision 1.122 2005/06/14 17:46:14 haselbac
1390 ! Added ERR_ALLOCATE_ADAPTIVE parameter and treatment
1391 !
1392 ! Revision 1.121 2005/05/26 22:01:29 haselbac
1393 ! Fixed bug: MPI_Abort expects three arguments
1394 !
1395 ! Revision 1.120 2005/05/16 20:41:35 haselbac
1396 ! Changed calling of MPI_Finalize and MPI_Abort
1397 !
1398 ! Revision 1.119 2005/04/27 18:36:30 fnajjar
1399 ! Added trap error for findPclMethod
1400 !
1401 ! Revision 1.118 2005/04/25 04:58:27 wasistho
1402 ! added ERR_FACE_INVERTED
1403 !
1404 ! Revision 1.117 2005/04/20 02:49:25 wasistho
1405 ! added ERR_COMPILE_OPTION
1406 !
1407 ! Revision 1.116 2005/04/15 15:06:27 haselbac
1408 ! Removed Charm/FEM error parameters, added MPI error parameters
1409 !
1410 ! Revision 1.115 2005/03/09 23:16:20 gzheng
1411 ! when compiled under charm (CHARM=1), ErrorStop should also call MPI_Abort instead of calling STOP.
1412 !
1413 ! Revision 1.114 2005/03/09 14:54:18 haselbac
1414 ! Added error treatment for virtual boundaries
1415 !
1416 ! Revision 1.113 2005/01/17 19:55:56 haselbac
1417 ! Added error condition and treatment
1418 !
1419 ! Revision 1.112 2005/01/14 21:12:49 haselbac
1420 ! Added error condition for MPI
1421 !
1422 ! Revision 1.111 2004/12/19 15:44:15 haselbac
1423 ! Added PETSC error condition
1424 !
1425 ! Revision 1.110 2004/12/04 03:22:57 haselbac
1426 ! Added error condition for estimate of number of vertices
1427 !
1428 ! Revision 1.109 2004/11/30 20:10:50 fnajjar
1429 ! Added error definition for RK schemes
1430 !
1431 ! Revision 1.108 2004/11/11 14:50:45 haselbac
1432 ! Removed CHARM section for writing error message, broken on popovich in serial
1433 !
1434 ! Revision 1.107 2004/11/09 10:55:28 wasistho
1435 ! added error option due to inclusion statistics in rflopost
1436 !
1437 ! Revision 1.106 2004/11/03 16:59:23 haselbac
1438 ! Removed error treatment related to HACK_PERIODIC
1439 !
1440 ! Revision 1.105 2004/11/03 14:54:53 haselbac
1441 ! Added error conditions for GAMBIT grid conversion
1442 !
1443 ! Revision 1.104 2004/10/19 19:28:40 haselbac
1444 ! Added new error conditions, cosmetics
1445 !
1446 ! Revision 1.103 2004/09/29 00:52:29 wasistho
1447 ! added Radiation error-msg: flux limited diffusion input
1448 !
1449 ! Revision 1.102 2004/09/27 01:36:13 haselbac
1450 ! Added error message for special faces
1451 !
1452 ! Revision 1.101 2004/07/28 18:54:57 fnajjar
1453 ! Added overflow memory error trap for PLAG
1454 !
1455 ! Revision 1.100 2004/07/23 22:43:43 wasistho
1456 ! added ERR_SYSTEM_COMMAND
1457 !
1458 ! Revision 1.99 2004/06/17 15:18:14 fnajjar
1459 ! Included proper error trapping for ejection model
1460 !
1461 ! Revision 1.98 2004/06/17 14:30:56 fnajjar
1462 ! Redefined error parameter from ERR_PLAG_INJCMODEL to ERR_PLAG_INCJDIAMDIST
1463 !
1464 ! Revision 1.97 2004/06/16 20:00:49 haselbac
1465 ! Added Tecplot error condition
1466 !
1467 ! Revision 1.96 2004/04/01 21:27:22 haselbac
1468 ! Added error condition ERR_SPEC_MAXEQN
1469 !
1470 ! Revision 1.95 2004/03/05 23:21:27 haselbac
1471 ! Added two new PLAG error conditions
1472 !
1473 ! Revision 1.94 2004/03/05 22:09:01 jferry
1474 ! created global variables for peul, plag, and inrt use
1475 !
1476 ! Revision 1.93 2004/03/02 21:47:28 jferry
1477 ! Added After Update interactions
1478 !
1479 ! Revision 1.92 2004/02/26 21:01:56 haselbac
1480 ! Improved readability and added PLAG error conditions
1481 !
1482 ! Revision 1.91 2004/01/29 22:57:20 haselbac
1483 ! Added three new error conditions
1484 !
1485 ! Revision 1.90 2003/12/05 16:53:54 haselbac
1486 ! Added and changed error parameters
1487 !
1488 ! Revision 1.89 2003/12/04 03:28:23 haselbac
1489 ! Added various error conditions
1490 !
1491 ! Revision 1.88 2003/11/25 21:03:09 haselbac
1492 ! Added error support for rocspecies
1493 !
1494 ! Revision 1.87 2003/11/21 22:38:57 fnajjar
1495 ! Added generic error messages
1496 !
1497 ! Revision 1.86 2003/09/25 15:48:43 jferry
1498 ! implemented Boiling Regulation interaction
1499 !
1500 ! Revision 1.85 2003/09/19 20:35:25 jferry
1501 ! Implemented oxidizer species for burning interaction
1502 !
1503 ! Revision 1.84 2003/09/17 21:06:25 fnajjar
1504 ! Included error traps for injection model
1505 !
1506 ! Revision 1.83 2003/09/13 20:16:50 fnajjar
1507 ! Added error traps for Breakup model
1508 !
1509 ! Revision 1.82 2003/09/10 23:36:24 fnajjar
1510 ! Removed flags that are subsumed with Rocinteract
1511 !
1512 ! Revision 1.81 2003/08/19 22:45:46 haselbac
1513 ! Added code for COBALT conversion errors
1514 !
1515 ! Revision 1.80 2003/08/06 15:50:36 wasistho
1516 ! added turb. input error code
1517 !
1518 ! Revision 1.79 2003/07/30 22:19:54 wasistho
1519 ! enter part and smoke data into radiation
1520 !
1521 ! Revision 1.78 2003/07/17 01:00:18 wasistho
1522 ! initial activation rocrad
1523 !
1524 ! Revision 1.77 2003/07/08 21:21:37 jblazek
1525 ! Modified start up procedure for dual-time stepping.
1526 !
1527 ! Revision 1.76 2003/05/31 01:42:57 wasistho
1528 ! installed turb. wall layer model
1529 !
1530 ! Revision 1.75 2003/05/24 02:13:51 wasistho
1531 ! turbulence statistics expanded
1532 !
1533 ! Revision 1.74 2003/05/13 23:48:14 haselbac
1534 ! Added error treatment for negative flame temperature
1535 !
1536 ! Revision 1.73 2003/05/01 20:44:55 haselbac
1537 ! Added ERR_MDOT_NEGATIVE and corresponding CASE
1538 !
1539 ! Revision 1.72 2003/04/10 23:18:07 fnajjar
1540 ! Included error trap for unknown viscosity model
1541 !
1542 ! Revision 1.71 2003/04/09 22:51:44 jferry
1543 ! removed peul_save and peul_verify structures
1544 !
1545 ! Revision 1.70 2003/04/07 14:21:53 haselbac
1546 ! Added param and message for c2f list
1547 !
1548 ! Revision 1.69 2003/04/03 21:10:17 jferry
1549 ! implemented additional safety checks for rocinteract
1550 !
1551 ! Revision 1.68 2003/04/02 22:32:03 jferry
1552 ! codified Activeness and Permission structures for rocinteract
1553 !
1554 ! Revision 1.67 2003/04/01 17:03:24 haselbac
1555 ! Added error condition for special cells
1556 !
1557 ! Revision 1.66 2003/03/29 03:27:18 wasistho
1558 ! install ROCPERI
1559 !
1560 ! Revision 1.65 2003/03/24 23:30:52 jferry
1561 ! overhauled rocinteract to allow interaction design to use user input
1562 !
1563 ! Revision 1.64 2003/03/15 18:48:04 haselbac
1564 ! Added error for gm
1565 !
1566 ! Revision 1.63 2003/03/15 17:44:10 haselbac
1567 ! Added several new error conditions
1568 !
1569 ! Revision 1.62 2003/03/04 22:12:34 jferry
1570 ! Initial import of Rocinteract
1571 !
1572 ! Revision 1.61 2003/02/25 21:11:11 fnajjar
1573 ! Added Error for PLAG Tile size
1574 !
1575 ! Revision 1.60 2003/02/20 19:48:32 haselbac
1576 ! Added error conditions
1577 !
1578 ! Revision 1.59 2003/02/12 20:49:51 jferry
1579 ! Moved Rocsmoke range to 4000-4999
1580 !
1581 ! Revision 1.58 2003/02/11 22:52:50 jferry
1582 ! Initial import of Rocsmoke
1583 !
1584 ! Revision 1.57 2003/02/06 19:30:24 haselbac
1585 ! Added ERR_MOVEPATCH_BC_INVALID
1586 !
1587 ! Revision 1.56 2003/01/28 16:40:12 haselbac
1588 ! Added three new error conditions
1589 !
1590 ! Revision 1.55 2002/10/27 19:01:01 haselbac
1591 ! Added several error conditions
1592 !
1593 ! Revision 1.54 2002/10/25 14:03:51 f-najjar
1594 ! Define PLAG Error Message
1595 !
1596 ! Revision 1.53 2002/10/17 14:12:10 haselbac
1597 ! Added error condition for number of coupled boundaries
1598 !
1599 ! Revision 1.52 2002/10/12 19:11:20 haselbac
1600 ! Added new message and fixed bug
1601 !
1602 ! Revision 1.51 2002/10/07 14:10:14 haselbac
1603 ! Removed tab
1604 !
1605 ! Revision 1.50 2002/10/05 18:58:03 haselbac
1606 ! Added error condition for boundary vertex list
1607 !
1608 ! Revision 1.49 2002/10/04 20:36:05 jblazek
1609 ! Extended range check of nFunTree.
1610 !
1611 ! Revision 1.48 2002/09/25 18:29:57 jferry
1612 ! simplified TBC parameter lists
1613 !
1614 ! Revision 1.47 2002/09/20 22:22:35 jblazek
1615 ! Finalized integration into GenX.
1616 !
1617 ! Revision 1.46 2002/09/17 22:49:44 jferry
1618 ! Deleted tabs
1619 !
1620 ! Revision 1.45 2002/09/17 13:43:00 jferry
1621 ! Added Time-dependent boundary conditions
1622 !
1623 ! Revision 1.44 2002/09/13 14:54:09 haselbac
1624 ! Whoops. Deleted a few lines too many last time...
1625 !
1626 ! Revision 1.43 2002/09/09 14:52:42 haselbac
1627 ! Added several error flags and proper output for parallel runs with FEM FW
1628 !
1629 ! Revision 1.42 2002/09/05 17:40:20 jblazek
1630 ! Variable global moved into regions().
1631 !
1632 ! Revision 1.41 2002/08/30 01:47:58 jblazek
1633 ! Added support for moving grids.
1634 !
1635 ! Revision 1.40 2002/08/23 03:16:29 wasistho
1636 ! modify ERR_TURB_MODULE
1637 !
1638 ! Revision 1.39 2002/08/18 02:23:23 wasistho
1639 ! Added some error msg pertinent to TURB
1640 !
1641 ! Revision 1.38 2002/08/15 19:48:05 jblazek
1642 ! Implemented grid deformation capability.
1643 !
1644 ! Revision 1.37 2002/07/29 17:10:45 jblazek
1645 ! Put TURB stuff into #ifdef.
1646 !
1647 ! Revision 1.36 2002/07/27 08:08:42 wasistho
1648 ! prepared for rocturb preliminary stage
1649 !
1650 ! Revision 1.35 2002/07/25 15:13:11 haselbac
1651 ! Added various new error conditions for OLES, DCUHRE, and gradients
1652 !
1653 ! Revision 1.34 2002/06/30 00:01:44 jblazek
1654 ! Removed TAB characters. Grrrrr ...
1655 !
1656 ! Revision 1.33 2002/06/27 15:54:48 haselbac
1657 ! Added ERR_NCELLS_WRONG
1658 !
1659 ! Revision 1.32 2002/06/22 01:13:37 jblazek
1660 ! Modified interfaces to BC routines.
1661 !
1662 ! Revision 1.31 2002/06/17 15:39:09 haselbac
1663 ! Prefixed SOLVER_NAME to all screen output
1664 !
1665 ! Revision 1.30 2002/06/17 15:20:30 jblazek
1666 ! Added ERR_PREVIOUS_ERRORS flag.
1667 !
1668 ! Revision 1.29 2002/06/14 21:34:32 wasistho
1669 ! Added time avg statistics
1670 !
1671 ! Revision 1.28 2002/06/07 16:40:37 jblazek
1672 ! Grid & solution for all regions in one file.
1673 !
1674 ! Revision 1.27 2002/06/05 18:50:22 haselbac
1675 ! Added treatment for CHARM errors
1676 !
1677 ! Revision 1.26 2002/05/28 13:52:00 haselbac
1678 ! Added FEM framework error message
1679 !
1680 ! Revision 1.25 2002/05/21 01:48:22 wasistho
1681 ! add viscous terms
1682 !
1683 ! Revision 1.24 2002/05/04 16:58:32 haselbac
1684 ! Added ERR_PROC_MISMATCH and file name for file errors
1685 !
1686 ! Revision 1.23 2002/04/11 18:55:42 haselbac
1687 ! Added various new error codes
1688 !
1689 ! Revision 1.22 2002/03/26 19:16:01 haselbac
1690 ! Added ROCFLU error conditions
1691 !
1692 ! Revision 1.21 2002/03/21 18:07:15 jblazek
1693 ! Added check of MPI_PATCHOFF (for tags).
1694 !
1695 ! Revision 1.20 2002/03/18 23:07:19 jblazek
1696 ! Finished multiblock and MPI.
1697 !
1698 ! Revision 1.19 2002/03/01 16:42:53 haselbac
1699 ! Added some more error conditions
1700 !
1701 ! Revision 1.18 2002/02/21 23:25:05 jblazek
1702 ! Blocks renamed as regions.
1703 !
1704 ! Revision 1.17 2002/02/09 01:47:01 jblazek
1705 ! Added multi-probe option, residual smoothing, physical time step.
1706 !
1707 ! Revision 1.16 2002/02/08 15:06:26 haselbac
1708 ! Added data structure errors
1709 !
1710 ! Revision 1.15 2002/01/31 20:23:59 jblazek
1711 ! Added treatment of edge & corner cells.
1712 !
1713 ! Revision 1.14 2002/01/12 00:02:48 jblazek
1714 ! Added postprocessor.
1715 !
1716 ! Revision 1.13 2002/01/11 17:20:19 jblazek
1717 ! Added time stamp or iteration number to file names.
1718 !
1719 ! Revision 1.12 2002/01/10 18:21:29 jblazek
1720 ! Added iteration number and initial residual to solution file.
1721 !
1722 ! Revision 1.11 2002/01/10 00:02:07 jblazek
1723 ! Added calculation of mixture properties.
1724 !
1725 ! Revision 1.10 2002/01/08 22:09:16 jblazek
1726 ! Added calculation of face vectors and volumes.
1727 !
1728 ! Revision 1.9 2002/01/02 16:20:19 jblazek
1729 ! Added flow initialization and dummy cell geometry.
1730 !
1731 ! Revision 1.8 2001/12/22 00:09:38 jblazek
1732 ! Added routines to store grid and solution.
1733 !
1734 ! Revision 1.7 2001/12/21 23:04:54 haselbac
1735 ! Added ROCFLU error parameters
1736 !
1737 ! Revision 1.6 2001/12/19 23:09:21 jblazek
1738 ! Added routines to read grid and solution.
1739 !
1740 ! Revision 1.5 2001/12/10 15:28:26 jblazek
1741 ! Fix to output format.
1742 !
1743 ! Revision 1.4 2001/12/08 00:18:41 jblazek
1744 ! Added routines to read BC input file.
1745 !
1746 ! Revision 1.3 2001/12/07 18:36:42 jblazek
1747 ! Update of ModError and ModParameters.
1748 !
1749 ! Revision 1.2 2001/12/07 16:47:44 jblazek
1750 ! ModError and ModParameters updated.
1751 !
1752 ! Revision 1.1.1.1 2001/12/03 21:44:05 jblazek
1753 ! Import of RocfluidMP
1754 !
1755 ! ******************************************************************************
1756 
1757 
1758 
1759 
1760 
1761 
subroutine registerfunction(global, funName, fileName)
Definition: ModError.F90:449
blockLoc i
Definition: read.cpp:79
subroutine errorstop(global, errorCode, errorLine, addMessage)
Definition: ModError.F90:483
subroutine deregisterfunction(global)
Definition: ModError.F90:469