Rocstar  1.0
Rocstar multiphysics simulation application
 All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Friends Macros Groups Pages
SPEC_RFLU_ModChemistry.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: Simple chemistry model for burning crack application.
26 !
27 ! Description: None.
28 !
29 ! Notes:
30 ! 1. Based on collection of routines developed by Luca Massa.
31 !
32 ! ******************************************************************************
33 !
34 ! $Id: SPEC_RFLU_ModChemistry.F90,v 1.6 2008/12/06 08:44:40 mtcampbe Exp $
35 !
36 ! Copyright: (c) 2004-2005 by the University of Illinois
37 !
38 ! ******************************************************************************
39 
41 
42  USE moddatatypes
43  USE modparameters
44  USE moderror
45  USE modglobal, ONLY: t_global
46  USE modgrid, ONLY: t_grid
47  USE moddatastruct, ONLY: t_region
48 
49  IMPLICIT NONE
50 
51  PRIVATE
53 
54 ! ******************************************************************************
55 ! Declarations and definitions
56 ! ******************************************************************************
57 
58  INTEGER, PARAMETER :: MAXEQN = 2,MAXRCT = 1
59  INTEGER :: nreaction,ntemp_spec,maxnwtn
60  REAL(RFREAL) :: eps,epy,beta,cpGas
61  REAL(RFREAL) :: damkholer(MAXRCT),mx(MAXEQN),mn(MAXEQN),nn(MAXRCT), &
62  pre(MAXRCT),qg(MAXRCT),thetay(MAXRCT),VEC(MAXEQN)
63  REAL(RFREAL) :: MAT(MAXEQN,MAXEQN),yf(MAXEQN,MAXRCT)
64  REAL(RFREAL) :: ratey(MAXRCT)
65 
66 ! ******************************************************************************
67 ! Routines
68 ! ******************************************************************************
69 
70  CONTAINS
71 
72 
73 
74 
75 ! ******************************************************************************
76 !
77 ! Purpose: Integrate source term for mixture and species using ODE solver.
78 !
79 ! Description: None.
80 !
81 ! Input:
82 ! pRegion Pointer to region
83 !
84 ! Output: None.
85 !
86 ! Notes:
87 ! 1. Numerical method is due to Luca Massa and Mark Short.
88 !
89 ! ******************************************************************************
90 
91  SUBROUTINE spec_rflu_integratechemsrcterm(pRegion,CALLFLAG)
92 
93  USE modinterfaces, ONLY: mixtperf_eo_grtuvw, &
95  mixtperf_r_m, &
97 
98 
99 ! ******************************************************************************
100 ! Definitions and declarations
101 ! ******************************************************************************
102 
103 ! ==============================================================================
104 ! Arguments
105 ! ==============================================================================
106 
107  TYPE(t_region), POINTER :: pregion
108 
109 ! ==============================================================================
110 ! Locals
111 ! ==============================================================================
112 
113  CHARACTER(CHRLEN) :: errorstring,rcsidentstring
114  INTEGER :: icg,indcp,indmol,ispec,nout,ncumul,ibc,iec,callflag
115  REAL(RFREAL) :: fact,ggas,ir,molmass,p,r,rgas,t,u,v,w,rvcumul,x,y,aaa,bbb
116  REAL(RFREAL), DIMENSION(MAXEQN) :: f,f_old
117  REAL(RFREAL), DIMENSION(:,:), POINTER :: pcvmixt,pcvspec,pdvmixt,pgvmixt,mrhs,srhs
118  REAL(RFREAL), DIMENSION(:), POINTER :: vol
119  TYPE(t_grid), POINTER :: pgrid
120  TYPE(t_global), POINTER :: global
121 
122 ! ******************************************************************************
123 ! Start
124 ! ******************************************************************************
125 
126  rcsidentstring = '$RCSfile: SPEC_RFLU_ModChemistry.F90,v $ $Revision: 1.6 $'
127 
128  global => pregion%global
129 
130  CALL registerfunction(global,'SPEC_RFLU_IntegrateChemSrcTerm',&
131  'SPEC_RFLU_ModChemistry.F90')
132 
133 ! ******************************************************************************
134 ! Set pointers and variables
135 ! ******************************************************************************
136 
137  pgrid => pregion%grid
138 
139  pcvmixt => pregion%mixt%cv
140  pdvmixt => pregion%mixt%dv
141  pgvmixt => pregion%mixt%gv
142  pcvspec => pregion%spec%cv
143  mrhs => pregion%mixt%rhs
144  srhs => pregion%spec%rhs
145  vol => pregion%grid%vol
146 
147  indcp = pregion%mixtInput%indCp
148  indmol = pregion%mixtInput%indMol
149 
150  fact = 1.0_rfreal
151  nout = 100
152 
153  CALL set_rate(pregion) ! Set rate constants
154 
155 ! ******************************************************************************
156 ! Checks
157 ! ******************************************************************************
158 
159  IF ( pregion%mixt%cvState /= cv_mixt_state_cons ) THEN
160  CALL errorstop(global,err_cv_state_invalid,__line__)
161  END IF ! pRegion%mixt%cvState
162 
163  IF ( pregion%specInput%nSpecies /= maxeqn-1 ) THEN
164  WRITE(errorstring,'(I3)') maxeqn
165  CALL errorstop(global,err_spec_maxeqn,__line__,errorstring)
166  END IF ! pRegion%specInput%nSpecies
167 
168 ! ******************************************************************************
169 ! Loop limits and sum initialization
170 ! ******************************************************************************
171 
172  ibc = 1
173  iec = merge(pgrid%nCellsTot,pgrid%nCells,callflag == 0)
174  ncumul = 0
175  rvcumul = 0.0_rfreal
176 
177 ! ******************************************************************************
178 ! Integrate source term
179 ! ******************************************************************************
180 
181  DO icg = ibc,iec
182  r = pcvmixt(cv_mixt_dens,icg)
183  ir = 1.0_rfreal/r
184 
185  x = pgrid%cofg(xcoord,icg)
186  y = pgrid%cofg(ycoord,icg)
187  t = pdvmixt(dv_mixt_temp,icg)
188  p = pdvmixt(dv_mixt_pres,icg)
189 
190  molmass = pgvmixt(gv_mixt_mol,indmol*icg)
191  cpgas = pgvmixt(gv_mixt_cp ,indcp *icg)
192 
193  rgas = mixtperf_r_m(molmass)
194  ggas = mixtperf_g_cpr(cpgas,rgas)
195 
196 ! ==============================================================================
197 ! Call integration routine
198 ! ==============================================================================
199 
200  !CALL rate_split(f,f_old,r,p,fact,global%dtMin,nout)
201  pre(1) = damkholer(1)*p**nn(1)
202 
203 ! ==============================================================================
204 ! Update state vectors. NOTE have conserved state vector for the mixture,
205 ! so need to update total internal energy because it is affected by the
206 ! temperature. The density is assumed to stay constant during this update.
207 ! The dependent variables will be updated outside this routine.
208 ! ==============================================================================
209 
210  if(callflag == 1) then
211  ratey(1) = pre(1) * pcvspec(1,icg) * exp(-thetay(1)/t) / r * global%dtMin
212  pcvmixt(cv_mixt_ener,icg) = pcvmixt(cv_mixt_ener,icg) + ratey(1)*yf(1,1)
213  pcvspec( 1,icg) = pcvspec( 1,icg) + ratey(1)*yf(2,1)
214  elseif(callflag == 0) then
215  ratey(1) = pre(1) * pcvspec(1,icg) * exp(-thetay(1)/t) / r * vol(icg)
216 
217  mrhs(cv_mixt_ener,icg) = mrhs(cv_mixt_ener,icg) - ratey(1)*yf(1,1)
218  srhs(1,icg) = srhs(1,icg) - ratey(1)*yf(2,1)
219 ! if (abs(pRegion%grid%cofg(YCOORD,icg)) > 4.5200d-3) Mrhs(CV_MIXT_ENER,icg) = 0_RFREAL
220 ! if (abs(pRegion%grid%cofg(YCOORD,icg)) > 4.5200d-3) Srhs(:,icg) = 0_RFREAL
221  endif
222 
223  END DO ! icg
224 
225 ! ******************************************************************************
226 ! End
227 ! ******************************************************************************
228 
229  CALL deregisterfunction(global)
230 
231  END SUBROUTINE spec_rflu_integratechemsrcterm
232 
233 
234 
235 
236 
237 ! *******************************************************************************
238 !
239 ! Purpose: Set rate constants.
240 !
241 ! Description: None.
242 !
243 ! Input:
244 ! pRegion Pointer to region data
245 !
246 ! Output: None.
247 !
248 ! Notes: None.
249 !
250 ! *******************************************************************************
251 
252  SUBROUTINE set_rate(pRegion)
253 
254  IMPLICIT NONE
255 
256 ! ******************************************************************************
257 ! Definitions and declarations
258 ! ******************************************************************************
259 
260 ! ==============================================================================
261 ! Arguments
262 ! ==============================================================================
263 
264  TYPE(t_region), POINTER :: pregion
265 
266 ! ==============================================================================
267 ! Locals
268 ! ==============================================================================
269 
270  INTEGER :: n
271 
272 ! ******************************************************************************
273 ! Start
274 ! ******************************************************************************
275 
276  maxnwtn = 1
277  eps = 1.0e-8_rfreal
278  epy = 2.0e-4_rfreal
279 
280  nreaction = 1
281  ntemp_spec = 1+pregion%specInput%nSpecies
282 
283  beta = 1.0_rfreal
284 
285  thetay(1) = 15000_rfreal
286 
287  qg(1) = 2511600.0_rfreal
288 
289  nn(1) = 0.0_rfreal
290 
291  damkholer(1) = 1174775.7803_rfreal
292 
293 
294 !!!one reaction, one species
295  yf(1,1) = qg(1)
296 
297  yf(2,1) = -1.0_rfreal
298 
299 !TEMPERATURE AND SPECIES BOUNDS !IN REACTION STEP INTEGRATION
300 
301  mx(1) = 6000.0_rfreal
302  mn(1) = 0.0_rfreal
303 
304  DO n = 2,ntemp_spec
305  mn(n) = -10.0_rfreal
306  mx(n) = 1.0_rfreal - mn(n)
307  END DO ! n
308 
309 ! ******************************************************************************
310 ! End
311 ! ******************************************************************************
312 
313  END SUBROUTINE set_rate
314 
315 
316 
317 
318 ! ******************************************************************************
319 !
320 ! Purpose: Integrate source terms using ODE solver.
321 !
322 ! Description: None.
323 !
324 ! Input:
325 ! old_f
326 ! rho
327 ! time_step
328 ! nout
329 !
330 ! Output:
331 ! f
332 !
333 ! Notes: None.
334 !
335 ! ******************************************************************************
336 
337  SUBROUTINE rate_split(f,old_f,rho,press,fact,time_step,nout)
338 
339  IMPLICIT NONE
340 
341 ! ******************************************************************************
342 ! Definitions and declarations
343 ! ******************************************************************************
344 
345 ! ==============================================================================
346 ! Arguments
347 ! ==============================================================================
348 
349  REAL(RFREAL), INTENT(IN) :: fact,press,rho,time_step
350  REAL(RFREAL), DIMENSION(MAXEQN) :: old_f,f
351 
352 ! ==============================================================================
353 ! Locals
354 ! ==============================================================================
355 
356  LOGICAL :: outcome
357  INTEGER :: eqn,i,icnvrgd,nout
358  REAL(RFREAL) :: toll,dt_over_rho
359 
360 ! ******************************************************************************
361 ! Start
362 ! ******************************************************************************
363 
364  dt_over_rho = time_step/rho*fact
365 
366  DO eqn = 1, ntemp_spec
367  old_f(eqn) = f(eqn)
368  END DO ! eqn
369 
370 ! ******************************************************************************
371 ! Integrate
372 ! ******************************************************************************
373 
374  CALL odesolve(old_f(1:ntemp_spec),f(1:ntemp_spec),press, &
375  ntemp_spec,dt_over_rho,nout,outcome)
376 
377  IF ( outcome ) THEN
378  WRITE(*,*)'DIVERGENCE IN RATE',old_f(1:ntemp_spec),f(1:ntemp_spec), &
379  dt_over_rho
380  f(1:ntemp_spec)=old_f(1:ntemp_spec)
381  icnvrgd = 0
382  ELSE
383  icnvrgd = 1
384  END IF ! outcome
385 
386 ! ******************************************************************************
387 ! End
388 ! ******************************************************************************
389 
390  END SUBROUTINE rate_split
391 
392 
393 
394 
395 ! ******************************************************************************
396 !
397 ! Purpose: None.
398 !
399 ! Description: None.
400 !
401 ! Input:
402 ! yin Old solution
403 ! press Pressure
404 ! neqin Number of equations
405 ! dtout Time step
406 ! nout Number of subiterations
407 !
408 ! Output:
409 ! y New solution
410 ! outcome Success flag (TRUE if diverged!!!)
411 !
412 ! Notes: None.
413 !
414 ! ******************************************************************************
415 
416  SUBROUTINE odesolve(yin,y,press,neqin,dtout,nout,outcome)
417 
418  IMPLICIT NONE
419 
420 ! ******************************************************************************
421 ! Definitions and declarations
422 ! ******************************************************************************
423 
424 ! ==============================================================================
425 ! Arguments
426 ! ==============================================================================
427 
428  LOGICAL :: outcome
429  INTEGER, INTENT(IN) :: neqin,nout
430  REAL(RFREAL) :: dtout,press
431  REAL(RFREAL) :: y(neqin),yin(neqin)
432 
433 ! ==============================================================================
434 ! Locals
435 ! ==============================================================================
436 
437  INTEGER :: icol,inwtn,iout,irow
438  REAL(RFREAL) :: t,tout
439  REAL(RFREAL) :: pp(maxeqn),ytmp(maxeqn)
440 
441 ! ******************************************************************************
442 ! Start
443 ! ******************************************************************************
444 
445  dtout = dtout/REAL(nout,kind=rfreal)
446 
447  t = 0.0_rfreal
448  tout = t
449  y = yin
450  ytmp = yin
451  pp = yin
452 
453  DO iout = 1,nout
454  DO inwtn = 1, maxnwtn
455  call rate_stiff(neqin, tout, y, press, vec)
456  call drate_stiff(neqin, tout, y, press, 1,1,mat,neqin)
457 
458  DO irow = 1,neqin
459  vec(irow) = ytmp(irow) - y(irow) + vec(irow)*dtout
460 
461  DO icol = 1,neqin
462  IF ( icol == irow ) THEN
463  mat(irow,irow) = mat(irow,irow)*dtout - 1.0_rfreal
464  ELSE
465  mat(irow,icol) = mat(irow,icol)*dtout
466  END IF ! icol
467  END DO ! icol
468  END DO ! irow
469 
470  CALL lusolve(mat(1:neqin,1:neqin),vec(1:neqin),neqin)
471  y(1:neqin) = y(1:neqin) - vec(1:neqin)
472  END DO ! inwtn
473 
474  tout = tout + dtout
475  ytmp = y
476 
477 ! WRITE(23,*)iout,tout,y(1)
478 ! WRITE(6,*)iout,tout,y(1)
479  END DO ! iout
480 
481  outcome = (.NOT. y(1) < mx(1)) .OR. (.NOT. y(1) > mn(1))
482 
483  IF ( outcome ) THEN
484  DO irow = 1,neqin
485  WRITE (stdout,*)irow,'TXY',yin(irow),y(irow)
486  END DO ! irow
487  END IF ! outcome
488 
489 300 format(////' STATE FLAG =',i3,/,'FAILED INEGRATION')
490 
491 ! ******************************************************************************
492 ! End
493 ! ******************************************************************************
494 
495  END SUBROUTINE odesolve
496 
497 
498 
499 
500 
501 ! ******************************************************************************
502 !
503 ! Purpose: Set up rate for two step kinetics and for fine AP/binder mixture
504 !
505 ! Description: None.
506 !
507 ! Input: None.
508 !
509 ! Output: None.
510 !
511 ! Notes: None.
512 !
513 ! ******************************************************************************
514 
515 ! ***************************************************
516 ! ff(1) = T (gas phase temperature)
517 ! ff(2) = F (gas phase fuel Y)
518 ! ff(3) = OX (gas phase oxidizer X)
519 ! ff(4) = Z (gas phase intermediate Z)
520 ! ********************************************************************
521 
522  SUBROUTINE rate_stiff(neqin,time_stiff,ff,press,rrate)
523 
524  IMPLICIT NONE
525 
526 ! ******************************************************************************
527 ! Definitions and declarations
528 ! ******************************************************************************
529 
530 ! ==============================================================================
531 ! Arguments
532 ! ==============================================================================
533 
534  INTEGER :: neqin
535  REAL(RFREAL) :: press,time_stiff
536  REAL(RFREAL) :: ff(neqin),rrate(neqin)
537 
538 ! ==============================================================================
539 ! Locals
540 ! ==============================================================================
541 
542  INTEGER :: m,n
543  REAL(RFREAL) :: ratey(maxrct)
544  REAL(RFREAL) :: dratey(maxrct,maxeqn)
545 
546 ! ******************************************************************************
547 ! Start
548 ! ******************************************************************************
549 
550  pre(1) = damkholer(1)*press**nn(1)
551 
552  ratey(1) = ff(2)*exp(-thetay(1)/ff(1))
553 
554  ratey(1) = pre(1)*ratey(1)
555 
556 ! yf(species,reaction), m species_eq, n=species_var
557 
558  DO m = 1,neqin
559  rrate(m) = sum(yf(m,1:nreaction)*ratey(1:nreaction))
560  END DO ! m
561 
562 ! ******************************************************************************
563 ! End
564 ! ******************************************************************************
565 
566  END SUBROUTINE rate_stiff
567 
568 
569 
570 
571 
572 
573 ! ******************************************************************************
574 !
575 ! Purpose: None.
576 !
577 ! Description: None.
578 !
579 ! Input: None.
580 !
581 ! Output: None.
582 !
583 ! Notes: None.
584 !
585 ! ******************************************************************************
586 
587  SUBROUTINE drate_stiff(neqin,time_stiff,ff,press,ml,imu,drate,nrowpd)
588 
589  IMPLICIT NONE
590 
591 ! ******************************************************************************
592 ! Definitions and declarations
593 ! ******************************************************************************
594 
595 ! ==============================================================================
596 ! Arguments
597 ! ==============================================================================
598 
599  INTEGER :: neqin,ml,imu
600  REAL(RFREAL) :: press,time_stiff
601  REAL(RFREAL) :: ff(neqin),drate(nrowpd,neqin)
602  REAL(RFREAL) :: dratey(maxrct,maxeqn)
603 
604 ! ==============================================================================
605 ! Locals
606 ! ==============================================================================
607 
608  INTEGER :: m,n,nrowpd
609  REAL(RFREAL) :: tsqinv
610  REAL(RFREAL) :: ratey(maxrct)
611 
612 ! ******************************************************************************
613 ! Start
614 ! ******************************************************************************
615 
616  pre(1) = damkholer(1)*press**nn(1)
617 
618  tsqinv = 1.0_rfreal/(ff(1)*ff(1))
619 
620  ratey(1) = ff(2)*exp(-thetay(1)/ff(1))
621 
622  ratey(1) = pre(1)*ratey(1)
623 
624  dratey(1,1) = thetay(1)*ratey(1)*tsqinv
625  dratey(1,2) = ratey(1)/merge(eps,ff(2),ff(2)==0.0_rfreal)
626 
627 ! yf(species,reaction), m species_eq, n=species_var
628 
629  DO m = 1,neqin
630  DO n = 1,ntemp_spec
631  drate(m,n) = sum(yf(m,1:nreaction)*dratey(1:nreaction,n))
632  END DO ! n
633  END DO ! m
634 
635 ! ******************************************************************************
636 ! End
637 ! ******************************************************************************
638 
639  END SUBROUTINE drate_stiff
640 
641 
642 
643 
644 
645 ! ******************************************************************************
646 !
647 ! Purpose: Solve system of linear equations Ax = f by LU decomposition.
648 !
649 ! Description: None.
650 !
651 ! Input:
652 ! A Matrix of size n by n
653 ! f Vector of size n
654 ! n Size of matrix and vector
655 !
656 ! Output:
657 ! f Solution to Ax=f
658 !
659 ! Notes: None.
660 !
661 ! ******************************************************************************
662 
663  SUBROUTINE lusolve(A,f,n)
664 
665 ! ******************************************************************************
666 ! Definitions and declarations
667 ! ******************************************************************************
668 
669 ! ==============================================================================
670 ! Arguments
671 ! ==============================================================================
672 
673  INTEGER :: n
674  REAL(RFREAL) :: f(n)
675  REAL(RFREAL) :: a(n,n)
676 
677 ! ==============================================================================
678 ! Locals
679 ! ==============================================================================
680 
681  INTEGER :: i,j
682  REAL(RFREAL) :: d
683  REAL(RFREAL), DIMENSION(MAXEQN) :: b,y
684  REAL(RFREAL), DIMENSION(MAXEQN,MAXEQN) :: u,l
685 
686 ! ******************************************************************************
687 ! Start
688 ! ******************************************************************************
689 
690  l = 1.0_rfreal
691  u = 0.0_rfreal
692 
693  u(1,1) = a(1,1)
694  u(1,2:n) = a(1,2:n)
695  l(2:n,1) = a(2:n,1)/a(1,1)
696 
697  DO i = 2,n-1
698  u(i,i) = a(i,i) - sum(l(i,1:i-1)*u(1:i-1,i))
699  d = 1.0_rfreal/u(i,i)
700 
701  DO j = i+1,n
702  u(i,j) = a(i,j) - sum(l(i,1:i-1)*u(1:i-1,j))
703  l(j,i) = (a(j,i) - sum(l(j,1:i-1)*u(1:i-1,i)))*d
704  END DO ! j
705  END DO ! i
706 
707  i=n
708  u(i,i) = a(i,i) - sum(l(i,1:i-1)*u(1:i-1,i))
709 
710  y(1) = f(1)
711 
712  DO i = 2,n
713  y(i) = f(i) - sum(l(i,1:i-1)*y(1:i-1))
714  END DO ! i
715 
716  f(n) = y(n)/u(n,n)
717  DO i = n-1,1,-1
718  f(i) = (y(i) - sum(u(i,i+1:n)*f(i+1:n)))/u(i,i)
719  END DO ! i
720 
721 ! ******************************************************************************
722 ! End
723 ! ******************************************************************************
724 
725  END SUBROUTINE lusolve
726 
727 
728 
729 
730 
731 END MODULE spec_rflu_modchemistry
732 
733 ! ******************************************************************************
734 !
735 ! RCS Revision history:
736 !
737 ! $Log: SPEC_RFLU_ModChemistry.F90,v $
738 ! Revision 1.6 2008/12/06 08:44:40 mtcampbe
739 ! Updated license.
740 !
741 ! Revision 1.5 2008/11/19 22:17:53 mtcampbe
742 ! Added Illinois Open Source License/Copyright
743 !
744 ! Revision 1.4 2006/04/07 15:19:25 haselbac
745 ! Removed tabs
746 !
747 ! Revision 1.3 2005/06/08 16:06:23 haselbac
748 ! Bug fix: Correcting incomplete check-in
749 !
750 ! Revision 1.2 2005/06/06 14:24:11 haselbac
751 ! Adapted to Lucas changes
752 !
753 ! Revision 1.1 2004/04/01 21:22:41 haselbac
754 ! Initial revision
755 !
756 ! ******************************************************************************
757 
758 
759 
760 
761 
762 
763 
764 
unsigned char r() const
Definition: Color.h:68
FT m(int i, int j) const
Tfloat sum() const
Return the sum of all the pixel values in an image.
Definition: CImg.h:13022
subroutine rate_split(f, old_f, rho, press, fact, time_step, nout)
real(rfreal) function mixtperf_r_m(M)
Definition: MixtPerf_R.F90:54
const NT & d
void int int REAL REAL * y
Definition: read.cpp:74
subroutine registerfunction(global, funName, fileName)
Definition: ModError.F90:449
unsigned char b() const
Definition: Color.h:70
real(rfreal) function mixtperf_d_prt(P, R, T)
Definition: MixtPerf_D.F90:71
*********************************************************************Illinois Open Source License ****University of Illinois NCSA **Open Source License University of Illinois All rights reserved ****Developed free of to any person **obtaining a copy of this software and associated documentation to deal with the Software without including without limitation the rights to and or **sell copies of the and to permit persons to whom the **Software is furnished to do subject to the following this list of conditions and the following disclaimers ****Redistributions in binary form must reproduce the above **copyright this list of conditions and the following **disclaimers in the documentation and or other materials **provided with the distribution ****Neither the names of the Center for Simulation of Advanced the University of nor the names of its **contributors may be used to endorse or promote products derived **from this Software without specific prior written permission ****THE SOFTWARE IS PROVIDED AS 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 v
Definition: roccomf90.h:20
blockLoc i
Definition: read.cpp:79
subroutine rate_stiff(neqin, time_stiff, ff, press, rrate)
void int int REAL * x
Definition: read.cpp:74
const NT & n
subroutine drate_stiff(neqin, time_stiff, ff, press, ml, imu, drate, nrowpd)
j indices j
Definition: Indexing.h:6
subroutine, public spec_rflu_integratechemsrcterm(pRegion, CALLFLAG)
subroutine errorstop(global, errorCode, errorLine, addMessage)
Definition: ModError.F90:483
subroutine deregisterfunction(global)
Definition: ModError.F90:469
*********************************************************************Illinois Open Source License ****University of Illinois NCSA **Open Source License University of Illinois All rights reserved ****Developed free of to any person **obtaining a copy of this software and associated documentation to deal with the Software without including without limitation the rights to merge
Definition: roccomf90.h:20
real(rfreal) function mixtperf_g_cpr(Cp, R)
Definition: MixtPerf_G.F90:39
real(rfreal) function mixtperf_eo_grtuvw(G, R, T, U, V, W)
Definition: MixtPerf_E.F90:70
subroutine odesolve(yin, y, press, neqin, dtout, nout, outcome)
RT a() const
Definition: Line_2.h:140