source: palm/trunk/UTIL/chemistry/gasphase_preproc/tmp_kpp4palm/kk_kpp.f90 @ 2698

Last change on this file since 2698 was 2696, checked in by kanani, 7 years ago

Merge of branch palm4u into trunk

File size: 79.2 KB
Line 
1MODULE chem_gasphase_mod
2 
3!------------------------------------------------------------------------------!
4!
5! ******Module chem_gasphase_mod is automatically generated by kpp4palm ******
6!
7!           *********Please do NOT change this Code *********
8!
9!------------------------------------------------------------------------------!
10! This file is part of PALM.
11!
12! PALM is free software: you can redistribute it and/or modify it under the
13! terms of the GNU General Public License as published by the Free Software
14! Foundation,either version 3 of the License,or (at your option) any later
15! version.
16!
17! PALM is distributed in the hope that it will be useful,but WITHOUT ANY
18! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
19! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
20!
21! You should have received a copy of the GNU General Public License along with
22! PALM. If not,see <http://www.gnu.org/licenses/>.
23!
24! Copyright 1997-2017 Leibniz Universitaet Hannover
25!--------------------------------------------------------------------------------!
26!
27! Current revisions:
28! ------------------
29!
30!
31! Former revisions:
32! -----------------
33! $Id: module_header 2460 2017-09-13 14:47:48Z forkel $
34!
35!
36! Variables for photolyis added
37!
38!
39!
40!
41!
42! Nov. 2016: Intial version (Klaus Ketelsen)
43!
44!------------------------------------------------------------------------------!
45!
46
47
48! Set kpp Double Precision to PALM Default Precision
49
50  USE kinds,           ONLY: dp=>wp
51
52  USE pegrid,          ONLY: myid,threads_per_task
53
54  IMPLICIT        NONE
55  PRIVATE
56  !SAVE  ! NOTE: OCCURS AGAIN IN AUTOMATICALLY GENERATED CODE ...
57
58!  PUBLIC :: IERR_NAMES
59 
60! PUBLIC :: SPC_NAMES,EQN_NAMES,EQN_TAGS,REQ_HET,REQ_AEROSOL,REQ_PHOTRAT &
61!         ,REQ_MCFCT,IP_MAX,jname
62
63  PUBLIC :: eqn_names, phot_names,spc_names
64  PUBLIC :: nmaxfixsteps
65  PUBLIC :: atol,rtol
66  PUBLIC :: nspec,nreact
67  PUBLIC :: temp
68  PUBLIC :: phot 
69  PUBLIC :: rconst
70  PUBLIC :: nvar
71  PUBLIC :: nphot
72 
73  PUBLIC :: initialize,integrate,update_rconst
74  PUBLIC :: chem_gasphase_integrate
75  PUBLIC :: initialize_kpp_ctrl
76
77! END OF MODULE HEADER TEMPLATE
78                                                                 
79! Variables used for vector mode                                 
80                                                                 
81  LOGICAL, PARAMETER          :: l_vector = .FALSE.           
82  INTEGER, PARAMETER          :: i_lu_di = 0
83  INTEGER, PARAMETER          :: vl_dim = 1
84  INTEGER                     :: vl                             
85                                                                 
86  INTEGER                     :: vl_glo                         
87  INTEGER                     :: is,ie                           
88                                                                 
89  INTEGER, DIMENSION(vl_dim)  :: kacc,krej                     
90  INTEGER, DIMENSION(vl_dim)  :: ierrv                           
91  LOGICAL                     :: data_loaded = .false.             
92! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
93!
94! Parameter Module File
95!
96! Generated by KPP-2.2.3 symbolic chemistry Kinetics PreProcessor
97!       (http://www.cs.vt.edu/~asandu/Software/KPP)
98! KPP is distributed under GPL,the general public licence
99!       (http://www.gnu.org/copyleft/gpl.html)
100! (C) 1995-1997,V. Damian & A. Sandu,CGRER,Univ. Iowa
101! (C) 1997-2005,A. Sandu,Michigan Tech,Virginia Tech
102!     With important contributions from:
103!        M. Damian,Villanova University,USA
104!        R. Sander,Max-Planck Institute for Chemistry,Mainz,Germany
105!
106! File                 : chem_gasphase_mod_Parameters.f90
107! Time                 : Fri Dec  1 18:10:53 2017
108! Working directory    : /data/kanani/branches/palm4u/GASPHASE_PREPROC/tmp_kpp4palm
109! Equation file        : chem_gasphase_mod.kpp
110! Output root filename : chem_gasphase_mod
111!
112! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
113
114
115
116
117
118
119! NSPEC - Number of chemical species
120  INTEGER,PARAMETER :: nspec = 3 
121! NVAR - Number of Variable species
122  INTEGER,PARAMETER :: nvar = 3 
123! NVARACT - Number of Active species
124  INTEGER,PARAMETER :: nvaract = 3 
125! NFIX - Number of Fixed species
126  INTEGER,PARAMETER :: nfix = 1 
127! NREACT - Number of reactions
128  INTEGER,PARAMETER :: nreact = 3 
129! NVARST - Starting of variables in conc. vect.
130  INTEGER,PARAMETER :: nvarst = 1 
131! NFIXST - Starting of fixed in conc. vect.
132  INTEGER,PARAMETER :: nfixst = 4 
133! NONZERO - Number of nonzero entries in Jacobian
134  INTEGER,PARAMETER :: nonzero = 3 
135! LU_NONZERO - Number of nonzero entries in LU factoriz. of Jacobian
136  INTEGER,PARAMETER :: lu_nonzero = 3 
137! CNVAR - (NVAR+1) Number of elements in compressed row format
138  INTEGER,PARAMETER :: cnvar = 4 
139! CNEQN - (NREACT+1) Number stoicm elements in compressed col format
140  INTEGER,PARAMETER :: cneqn = 4 
141! NHESS - Length of Sparse Hessian
142  INTEGER,PARAMETER :: nhess = 1 
143! NLOOKAT - Number of species to look at
144  INTEGER,PARAMETER :: nlookat = 0 
145! NMONITOR - Number of species to monitor
146  INTEGER,PARAMETER :: nmonitor = 0 
147! NMASS - Number of atoms to check mass balance
148  INTEGER,PARAMETER :: nmass = 1 
149
150! Index declaration for variable species in C and VAR
151!   VAR(ind_spc) = C(ind_spc)
152
153  INTEGER,PARAMETER,PUBLIC :: ind_co = 1 
154  INTEGER,PARAMETER,PUBLIC :: ind_pm10 = 2 
155  INTEGER,PARAMETER,PUBLIC :: ind_pm25 = 3 
156
157! Index declaration for fixed species in C
158!   C(ind_spc)
159
160
161! Index declaration for fixed species in FIX
162!    FIX(indf_spc) = C(ind_spc) = C(NVAR+indf_spc)
163
164
165! NJVRP - Length of sparse Jacobian JVRP
166  INTEGER,PARAMETER :: njvrp = 3 
167
168! NSTOICM - Length of Sparse Stoichiometric Matrix
169  INTEGER,PARAMETER :: nstoicm = 1 
170
171
172! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
173!
174! Global Data Module File
175!
176! Generated by KPP-2.2.3 symbolic chemistry Kinetics PreProcessor
177!       (http://www.cs.vt.edu/~asandu/Software/KPP)
178! KPP is distributed under GPL,the general public licence
179!       (http://www.gnu.org/copyleft/gpl.html)
180! (C) 1995-1997,V. Damian & A. Sandu,CGRER,Univ. Iowa
181! (C) 1997-2005,A. Sandu,Michigan Tech,Virginia Tech
182!     With important contributions from:
183!        M. Damian,Villanova University,USA
184!        R. Sander,Max-Planck Institute for Chemistry,Mainz,Germany
185!
186! File                 : chem_gasphase_mod_Global.f90
187! Time                 : Fri Dec  1 18:10:53 2017
188! Working directory    : /data/kanani/branches/palm4u/GASPHASE_PREPROC/tmp_kpp4palm
189! Equation file        : chem_gasphase_mod.kpp
190! Output root filename : chem_gasphase_mod
191!
192! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
193
194
195
196
197
198
199! Declaration of global variables
200
201! C - Concentration of all species
202  REAL(kind=dp):: c(nspec)
203! VAR - Concentrations of variable species (global)
204  REAL(kind=dp):: var(nvar)
205! FIX - Concentrations of fixed species (global)
206  REAL(kind=dp):: fix(nfix)
207! VAR,FIX are chunks of array C
208      equivalence( c(1),var(1))
209! RCONST - Rate constants (global)
210  REAL(kind=dp):: rconst(nreact)
211! TIME - Current integration time
212  REAL(kind=dp):: time
213! SUN - Sunlight intensity between [0,1]
214  REAL(kind=dp):: sun
215! TEMP - Temperature
216  REAL(dp),dimension(:),allocatable             :: temp
217! RTOLS - (scalar) Relative tolerance
218  REAL(kind=dp):: rtols
219! TSTART - Integration start time
220  REAL(kind=dp):: tstart
221! TEND - Integration end time
222  REAL(kind=dp):: tend
223! DT - Integration step
224  REAL(kind=dp):: dt
225! ATOL - Absolute tolerance
226  REAL(kind=dp):: atol(nvar)
227! RTOL - Relative tolerance
228  REAL(kind=dp):: rtol(nvar)
229! STEPMIN - Lower bound for integration step
230  REAL(kind=dp):: stepmin
231! STEPMAX - Upper bound for integration step
232  REAL(kind=dp):: stepmax
233! CFACTOR - Conversion factor for concentration units
234  REAL(kind=dp):: cfactor
235! DDMTYPE - DDM sensitivity w.r.t.: 0=init.val.,1=params
236  INTEGER :: ddmtype
237
238! INLINED global variable declarations
239
240  !   declaration of global variable declarations for photolysis will come from
241
242! INLINED global variable declarations
243
244
245
246! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
247!
248! Sparse Jacobian Data Structures File
249!
250! Generated by KPP-2.2.3 symbolic chemistry Kinetics PreProcessor
251!       (http://www.cs.vt.edu/~asandu/Software/KPP)
252! KPP is distributed under GPL,the general public licence
253!       (http://www.gnu.org/copyleft/gpl.html)
254! (C) 1995-1997,V. Damian & A. Sandu,CGRER,Univ. Iowa
255! (C) 1997-2005,A. Sandu,Michigan Tech,Virginia Tech
256!     With important contributions from:
257!        M. Damian,Villanova University,USA
258!        R. Sander,Max-Planck Institute for Chemistry,Mainz,Germany
259!
260! File                 : chem_gasphase_mod_JacobianSP.f90
261! Time                 : Fri Dec  1 18:10:53 2017
262! Working directory    : /data/kanani/branches/palm4u/GASPHASE_PREPROC/tmp_kpp4palm
263! Equation file        : chem_gasphase_mod.kpp
264! Output root filename : chem_gasphase_mod
265!
266! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
267
268
269
270
271
272
273! Sparse Jacobian Data
274
275
276  INTEGER,PARAMETER,DIMENSION(3):: lu_irow =  (/ &
277       1, 2, 3 /) 
278
279  INTEGER,PARAMETER,DIMENSION(3):: lu_icol =  (/ &
280       1, 2, 3 /) 
281
282  INTEGER,PARAMETER,DIMENSION(4):: lu_crow =  (/ &
283       1, 2, 3, 4 /) 
284
285  INTEGER,PARAMETER,DIMENSION(4):: lu_diag =  (/ &
286       1, 2, 3, 4 /) 
287
288
289
290! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
291!
292! Utility Data Module File
293!
294! Generated by KPP-2.2.3 symbolic chemistry Kinetics PreProcessor
295!       (http://www.cs.vt.edu/~asandu/Software/KPP)
296! KPP is distributed under GPL,the general public licence
297!       (http://www.gnu.org/copyleft/gpl.html)
298! (C) 1995-1997,V. Damian & A. Sandu,CGRER,Univ. Iowa
299! (C) 1997-2005,A. Sandu,Michigan Tech,Virginia Tech
300!     With important contributions from:
301!        M. Damian,Villanova University,USA
302!        R. Sander,Max-Planck Institute for Chemistry,Mainz,Germany
303!
304! File                 : chem_gasphase_mod_Monitor.f90
305! Time                 : Fri Dec  1 18:10:53 2017
306! Working directory    : /data/kanani/branches/palm4u/GASPHASE_PREPROC/tmp_kpp4palm
307! Equation file        : chem_gasphase_mod.kpp
308! Output root filename : chem_gasphase_mod
309!
310! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
311
312
313
314
315
316  CHARACTER(len=15),PARAMETER,DIMENSION(3):: spc_names =  (/ &
317     'CO             ','PM10           ','PM25           ' /)
318
319  INTEGER,DIMENSION(1):: lookat
320  INTEGER,DIMENSION(1):: monitor
321  CHARACTER(len=15),DIMENSION(1):: smass
322  CHARACTER(len=100),PARAMETER,DIMENSION(3):: eqn_names =  (/ &
323     '  CO --> CO                                                                                         ',&
324     'PM10 --> PM10                                                                                       ',&
325     'PM25 --> PM25                                                                                       ' /)
326
327! INLINED global variables
328
329  !   inline f90_data: declaration of global variables for photolysis
330  !   REAL(kind=dp):: phot(nphot)must eventually be moved to global later for
331  INTEGER,PARAMETER :: nphot = 1
332  !   phot photolysis frequencies
333  REAL(kind=dp):: phot(nphot)
334
335  INTEGER,PARAMETER,PUBLIC :: j_no2 = 1
336
337  CHARACTER(len=15),PARAMETER,DIMENSION(nphot):: phot_names =   (/ &
338     'J_NO2          '/)
339
340! End INLINED global variables
341
342
343! Automatic generated PUBLIC Statements for ip_ and ihs_ variables
344 
345! Automatic generated PUBLIC Statements for ip_ and ihs_ variables
346 
347! Automatic generated PUBLIC Statements for ip_ and ihs_ variables
348 
349! Automatic generated PUBLIC Statements for ip_ and ihs_ variables
350 
351 
352!  variable definations from  individual module headers
353 
354! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
355!
356! Initialization File
357!
358! Generated by KPP-2.2.3 symbolic chemistry Kinetics PreProcessor
359!       (http://www.cs.vt.edu/~asandu/Software/KPP)
360! KPP is distributed under GPL,the general public licence
361!       (http://www.gnu.org/copyleft/gpl.html)
362! (C) 1995-1997,V. Damian & A. Sandu,CGRER,Univ. Iowa
363! (C) 1997-2005,A. Sandu,Michigan Tech,Virginia Tech
364!     With important contributions from:
365!        M. Damian,Villanova University,USA
366!        R. Sander,Max-Planck Institute for Chemistry,Mainz,Germany
367!
368! File                 : chem_gasphase_mod_Initialize.f90
369! Time                 : Fri Dec  1 18:10:53 2017
370! Working directory    : /data/kanani/branches/palm4u/GASPHASE_PREPROC/tmp_kpp4palm
371! Equation file        : chem_gasphase_mod.kpp
372! Output root filename : chem_gasphase_mod
373!
374! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
375
376
377
378
379
380! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
381!
382! Numerical Integrator (Time-Stepping) File
383!
384! Generated by KPP-2.2.3 symbolic chemistry Kinetics PreProcessor
385!       (http://www.cs.vt.edu/~asandu/Software/KPP)
386! KPP is distributed under GPL,the general public licence
387!       (http://www.gnu.org/copyleft/gpl.html)
388! (C) 1995-1997,V. Damian & A. Sandu,CGRER,Univ. Iowa
389! (C) 1997-2005,A. Sandu,Michigan Tech,Virginia Tech
390!     With important contributions from:
391!        M. Damian,Villanova University,USA
392!        R. Sander,Max-Planck Institute for Chemistry,Mainz,Germany
393!
394! File                 : chem_gasphase_mod_Integrator.f90
395! Time                 : Fri Dec  1 18:10:53 2017
396! Working directory    : /data/kanani/branches/palm4u/GASPHASE_PREPROC/tmp_kpp4palm
397! Equation file        : chem_gasphase_mod.kpp
398! Output root filename : chem_gasphase_mod
399!
400! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
401
402
403
404! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
405!
406! INTEGRATE - Integrator routine
407!   Arguments :
408!      TIN       - Start Time for Integration
409!      TOUT      - End Time for Integration
410!
411! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
412
413!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~!
414!  Rosenbrock - Implementation of several Rosenbrock methods:             !
415!               *Ros2                                                    !
416!               *Ros3                                                    !
417!               *Ros4                                                    !
418!               *Rodas3                                                  !
419!               *Rodas4                                                  !
420!  By default the code employs the KPP sparse linear algebra routines     !
421!  Compile with -DFULL_ALGEBRA to use full linear algebra (LAPACK)        !
422!                                                                         !
423!    (C)  Adrian Sandu,August 2004                                       !
424!    Virginia Polytechnic Institute and State University                  !
425!    Contact: sandu@cs.vt.edu                                             !
426!    Revised by Philipp Miehe and Adrian Sandu,May 2006                  !                               !
427!    This implementation is part of KPP - the Kinetic PreProcessor        !
428!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~!
429
430
431  SAVE
432 
433!~~~>  statistics on the work performed by the rosenbrock method
434  INTEGER,PARAMETER :: nfun=1,njac=2,nstp=3,nacc=4,&
435                        nrej=5,ndec=6,nsol=7,nsng=8,&
436                        ntexit=1,nhexit=2,nhnew = 3
437
438! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
439!
440! Linear Algebra Data and Routines File
441!
442! Generated by KPP-2.2.3 symbolic chemistry Kinetics PreProcessor
443!       (http://www.cs.vt.edu/~asandu/Software/KPP)
444! KPP is distributed under GPL,the general public licence
445!       (http://www.gnu.org/copyleft/gpl.html)
446! (C) 1995-1997,V. Damian & A. Sandu,CGRER,Univ. Iowa
447! (C) 1997-2005,A. Sandu,Michigan Tech,Virginia Tech
448!     With important contributions from:
449!        M. Damian,Villanova University,USA
450!        R. Sander,Max-Planck Institute for Chemistry,Mainz,Germany
451!
452! File                 : chem_gasphase_mod_LinearAlgebra.f90
453! Time                 : Fri Dec  1 18:10:53 2017
454! Working directory    : /data/kanani/branches/palm4u/GASPHASE_PREPROC/tmp_kpp4palm
455! Equation file        : chem_gasphase_mod.kpp
456! Output root filename : chem_gasphase_mod
457!
458! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
459
460
461
462
463
464
465! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
466!
467! The ODE Jacobian of Chemical Model File
468!
469! Generated by KPP-2.2.3 symbolic chemistry Kinetics PreProcessor
470!       (http://www.cs.vt.edu/~asandu/Software/KPP)
471! KPP is distributed under GPL,the general public licence
472!       (http://www.gnu.org/copyleft/gpl.html)
473! (C) 1995-1997,V. Damian & A. Sandu,CGRER,Univ. Iowa
474! (C) 1997-2005,A. Sandu,Michigan Tech,Virginia Tech
475!     With important contributions from:
476!        M. Damian,Villanova University,USA
477!        R. Sander,Max-Planck Institute for Chemistry,Mainz,Germany
478!
479! File                 : chem_gasphase_mod_Jacobian.f90
480! Time                 : Fri Dec  1 18:10:53 2017
481! Working directory    : /data/kanani/branches/palm4u/GASPHASE_PREPROC/tmp_kpp4palm
482! Equation file        : chem_gasphase_mod.kpp
483! Output root filename : chem_gasphase_mod
484!
485! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
486
487
488
489
490
491
492! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
493!
494! The ODE Function of Chemical Model File
495!
496! Generated by KPP-2.2.3 symbolic chemistry Kinetics PreProcessor
497!       (http://www.cs.vt.edu/~asandu/Software/KPP)
498! KPP is distributed under GPL,the general public licence
499!       (http://www.gnu.org/copyleft/gpl.html)
500! (C) 1995-1997,V. Damian & A. Sandu,CGRER,Univ. Iowa
501! (C) 1997-2005,A. Sandu,Michigan Tech,Virginia Tech
502!     With important contributions from:
503!        M. Damian,Villanova University,USA
504!        R. Sander,Max-Planck Institute for Chemistry,Mainz,Germany
505!
506! File                 : chem_gasphase_mod_Function.f90
507! Time                 : Fri Dec  1 18:10:53 2017
508! Working directory    : /data/kanani/branches/palm4u/GASPHASE_PREPROC/tmp_kpp4palm
509! Equation file        : chem_gasphase_mod.kpp
510! Output root filename : chem_gasphase_mod
511!
512! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
513
514
515
516
517
518! A - Rate for each equation
519  REAL(kind=dp):: a(nreact)
520
521! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
522!
523! The Reaction Rates File
524!
525! Generated by KPP-2.2.3 symbolic chemistry Kinetics PreProcessor
526!       (http://www.cs.vt.edu/~asandu/Software/KPP)
527! KPP is distributed under GPL,the general public licence
528!       (http://www.gnu.org/copyleft/gpl.html)
529! (C) 1995-1997,V. Damian & A. Sandu,CGRER,Univ. Iowa
530! (C) 1997-2005,A. Sandu,Michigan Tech,Virginia Tech
531!     With important contributions from:
532!        M. Damian,Villanova University,USA
533!        R. Sander,Max-Planck Institute for Chemistry,Mainz,Germany
534!
535! File                 : chem_gasphase_mod_Rates.f90
536! Time                 : Fri Dec  1 18:10:53 2017
537! Working directory    : /data/kanani/branches/palm4u/GASPHASE_PREPROC/tmp_kpp4palm
538! Equation file        : chem_gasphase_mod.kpp
539! Output root filename : chem_gasphase_mod
540!
541! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
542
543
544
545
546
547! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
548!
549! Auxiliary Routines File
550!
551! Generated by KPP-2.2.3 symbolic chemistry Kinetics PreProcessor
552!       (http://www.cs.vt.edu/~asandu/Software/KPP)
553! KPP is distributed under GPL,the general public licence
554!       (http://www.gnu.org/copyleft/gpl.html)
555! (C) 1995-1997,V. Damian & A. Sandu,CGRER,Univ. Iowa
556! (C) 1997-2005,A. Sandu,Michigan Tech,Virginia Tech
557!     With important contributions from:
558!        M. Damian,Villanova University,USA
559!        R. Sander,Max-Planck Institute for Chemistry,Mainz,Germany
560!
561! File                 : chem_gasphase_mod_Util.f90
562! Time                 : Fri Dec  1 18:10:53 2017
563! Working directory    : /data/kanani/branches/palm4u/GASPHASE_PREPROC/tmp_kpp4palm
564! Equation file        : chem_gasphase_mod.kpp
565! Output root filename : chem_gasphase_mod
566!
567! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
568
569
570
571
572
573
574  ! header MODULE initialize_kpp_ctrl_template
575
576  ! notes:
577  ! -  l_vector is automatically defined by kp4
578  ! -  vl_dim is automatically defined by kp4
579  ! -  i_lu_di is automatically defined by kp4
580  ! -  wanted is automatically defined by xmecca
581  ! -  icntrl rcntrl are automatically defined by kpp
582  ! -  "USE messy_main_tools" is in MODULE_header of messy_mecca_kpp.f90
583  ! -  SAVE will be automatically added by kp4
584
585  !SAVE
586
587  ! for fixed time step control
588  ! ... max. number of fixed time steps (sum must be 1)
589  INTEGER,PARAMETER         :: nmaxfixsteps = 50
590  ! ... switch for fixed time stepping
591  LOGICAL,PUBLIC            :: l_fixed_step = .false.
592  INTEGER,PUBLIC            :: nfsteps = 1
593  ! ... number of kpp control PARAMETERs
594  INTEGER,PARAMETER,PUBLIC :: nkppctrl = 20
595  !
596  INTEGER, DIMENSION(nkppctrl),PUBLIC     :: icntrl = 0
597  REAL(dp),DIMENSION(nkppctrl),PUBLIC     :: rcntrl = 0.0_dp
598  REAL(dp),DIMENSION(nmaxfixsteps),PUBLIC :: t_steps = 0.0_dp
599
600  ! END header MODULE initialize_kpp_ctrl_template
601
602 
603! Interface Block
604 
605  INTERFACE            initialize
606    MODULE PROCEDURE   initialize
607  END INTERFACE        initialize
608 
609  INTERFACE            integrate
610    MODULE PROCEDURE   integrate
611  END INTERFACE        integrate
612 
613  INTERFACE            fun
614    MODULE PROCEDURE   fun
615  END INTERFACE        fun
616 
617  INTERFACE            kppsolve
618    MODULE PROCEDURE   kppsolve
619  END INTERFACE        kppsolve
620 
621  INTERFACE            kppdecomp
622    MODULE PROCEDURE   kppdecomp
623  END INTERFACE        kppdecomp
624 
625  INTERFACE            wlamch
626    MODULE PROCEDURE   wlamch
627  END INTERFACE        wlamch
628 
629  INTERFACE            wlamch_add
630    MODULE PROCEDURE   wlamch_add
631  END INTERFACE        wlamch_add
632 
633  INTERFACE            jac_sp
634    MODULE PROCEDURE   jac_sp
635  END INTERFACE        jac_sp
636 
637  INTERFACE            k_arr
638    MODULE PROCEDURE   k_arr
639  END INTERFACE        k_arr
640 
641  INTERFACE            update_rconst
642    MODULE PROCEDURE   update_rconst
643  END INTERFACE        update_rconst
644 
645  INTERFACE            arr2
646    MODULE PROCEDURE   arr2
647  END INTERFACE        arr2
648 
649  INTERFACE            initialize_kpp_ctrl
650    MODULE PROCEDURE   initialize_kpp_ctrl
651  END INTERFACE        initialize_kpp_ctrl
652 
653  INTERFACE            error_output
654    MODULE PROCEDURE   error_output
655  END INTERFACE        error_output
656 
657!interface not working  INTERFACE            wcopy
658!interface not working    MODULE PROCEDURE   wcopy
659!interface not working  END INTERFACE        wcopy
660 
661  INTERFACE            wscal
662    MODULE PROCEDURE   wscal
663  END INTERFACE        wscal
664 
665!interface not working  INTERFACE            waxpy
666!interface not working    MODULE PROCEDURE   waxpy
667!interface not working  END INTERFACE        waxpy
668 
669  INTERFACE            rosenbrock
670    MODULE PROCEDURE   rosenbrock
671  END INTERFACE        rosenbrock
672 
673  INTERFACE            funtemplate
674    MODULE PROCEDURE   funtemplate
675  END INTERFACE        funtemplate
676 
677  INTERFACE            jactemplate
678    MODULE PROCEDURE   jactemplate
679  END INTERFACE        jactemplate
680 
681  INTERFACE            chem_gasphase_integrate
682    MODULE PROCEDURE   chem_gasphase_integrate
683  END INTERFACE        chem_gasphase_integrate
684 
685  INTERFACE            fill_temp
686    MODULE PROCEDURE   fill_temp
687  END INTERFACE        fill_temp
688  PUBLIC               fill_temp
689 
690 
691 CONTAINS
692 
693SUBROUTINE initialize()
694
695
696
697  INTEGER :: i
698  REAL(kind=dp):: x
699
700  cfactor = 1.000000e+00_dp
701
702  x = (0.)*cfactor
703  DO i = 1,nvar
704    var(i) = x
705  ENDDO
706
707  x = (0.)*cfactor
708  DO i = 1,nfix
709    fix(i) = x
710  ENDDO
711
712! constant rate coefficients
713! END constant rate coefficients
714
715! INLINED initializations
716
717! End INLINED initializations
718
719     
720END SUBROUTINE initialize
721 
722SUBROUTINE integrate( tin,tout,&
723  icntrl_u,rcntrl_u,istatus_u,rstatus_u,ierr_u)
724
725
726   REAL(kind=dp),INTENT(in):: tin  ! start time
727   REAL(kind=dp),INTENT(in):: tout ! END time
728   ! OPTIONAL input PARAMETERs and statistics
729   INTEGER,      INTENT(in), OPTIONAL :: icntrl_u(20)
730   REAL(kind=dp),INTENT(in), OPTIONAL :: rcntrl_u(20)
731   INTEGER,      INTENT(out),OPTIONAL :: istatus_u(20)
732   REAL(kind=dp),INTENT(out),OPTIONAL :: rstatus_u(20)
733   INTEGER,      INTENT(out),OPTIONAL :: ierr_u
734
735   REAL(kind=dp):: rcntrl(20),rstatus(20)
736   INTEGER       :: icntrl(20),istatus(20),ierr
737
738   INTEGER,SAVE :: ntotal = 0
739
740   icntrl(:) = 0
741   rcntrl(:) = 0.0_dp
742   istatus(:) = 0
743   rstatus(:) = 0.0_dp
744
745    !~~~> fine-tune the integrator:
746   icntrl(1) = 0        ! 0 -  non- autonomous,1 -  autonomous
747   icntrl(2) = 0        ! 0 -  vector tolerances,1 -  scalars
748
749   ! IF OPTIONAL PARAMETERs are given,and IF they are >0,
750   ! THEN they overwrite default settings.
751   IF (present(icntrl_u))THEN
752     where(icntrl_u(:)> 0)icntrl(:) = icntrl_u(:)
753   ENDIF
754   IF (present(rcntrl_u))THEN
755     where(rcntrl_u(:)> 0)rcntrl(:) = rcntrl_u(:)
756   ENDIF
757
758
759   CALL rosenbrock(nvar,var,tin,tout,  &
760         atol,rtol,               &
761         rcntrl,icntrl,rstatus,istatus,ierr)
762
763   !~~~> debug option: show no of steps
764   ! ntotal = ntotal + istatus(nstp)
765   ! PRINT*,'NSTEPS=',ISTATUS(Nstp),' (',Ntotal,')','  O3=',VAR(ind_O3)
766
767   stepmin = rstatus(nhexit)
768   ! IF OPTIONAL PARAMETERs are given for output they
769   ! are updated with the RETURN information
770   IF (present(istatus_u))istatus_u(:) = istatus(:)
771   IF (present(rstatus_u))rstatus_u(:) = rstatus(:)
772   IF (present(ierr_u))   ierr_u       = ierr
773
774END SUBROUTINE integrate
775 
776SUBROUTINE fun(v,f,rct,vdot)
777
778! V - Concentrations of variable species (local)
779  REAL(kind=dp):: v(nvar)
780! F - Concentrations of fixed species (local)
781  REAL(kind=dp):: f(nfix)
782! RCT - Rate constants (local)
783  REAL(kind=dp):: rct(nreact)
784! Vdot - Time derivative of variable species concentrations
785  REAL(kind=dp):: vdot(nvar)
786
787
788! Computation of equation rates
789
790! Aggregate function
791  vdot(1) = 0
792  vdot(2) = 0
793  vdot(3) = 0
794     
795END SUBROUTINE fun
796 
797SUBROUTINE kppsolve(jvs,x)
798
799! JVS - sparse Jacobian of variables
800  REAL(kind=dp):: jvs(lu_nonzero)
801! X - Vector for variables
802  REAL(kind=dp):: x(nvar)
803
804  x(3) = x(3)/ jvs(3)
805  x(2) = x(2)/ jvs(2)
806  x(1) = x(1)/ jvs(1)
807     
808END SUBROUTINE kppsolve
809 
810SUBROUTINE kppdecomp( jvs,ier)
811! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
812!        Sparse LU factorization
813! ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
814
815
816      INTEGER  :: ier
817      REAL(kind=dp):: jvs(lu_nonzero),w(nvar),a
818      INTEGER  :: k,kk,j,jj
819
820      a = 0. ! mz_rs_20050606
821      ier = 0
822      DO k=1,nvar
823        ! mz_rs_20050606: don't check if real value == 0
824        ! IF(jvs( lu_diag(k)).eq. 0.)THEN
825        IF(abs(jvs(lu_diag(k)))< tiny(a))THEN
826            ier = k
827            RETURN
828        ENDIF
829        DO kk = lu_crow(k),lu_crow(k+ 1)- 1
830              w( lu_icol(kk)) = jvs(kk)
831        ENDDO
832        DO kk = lu_crow(k),lu_diag(k)- 1
833            j = lu_icol(kk)
834            a = - w(j)/ jvs( lu_diag(j))
835            w(j) = - a
836            DO jj = lu_diag(j)+ 1,lu_crow(j+ 1)- 1
837               w( lu_icol(jj)) = w( lu_icol(jj))+ a*jvs(jj)
838            ENDDO
839         ENDDO
840         DO kk = lu_crow(k),lu_crow(k+ 1)- 1
841            jvs(kk) = w( lu_icol(kk))
842         ENDDO
843      ENDDO
844     
845END SUBROUTINE kppdecomp
846 
847      REAL(kind=dp)FUNCTION wlamch( c)
848!- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
849!     returns epsilon machine
850!     after LAPACK
851!     replace this by the function from the optimized LAPACK implementation:
852!          CALL SLAMCH('E') or CALL DLAMCH('E')
853!- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
854!      USE chem_gasphase_mod_Precision
855
856      CHARACTER ::  c
857      INTEGER    :: i
858      REAL(kind=dp),SAVE  ::  eps
859      REAL(kind=dp) ::  suma
860      REAL(kind=dp),PARAMETER  ::  one=1.0_dp, half=0.5_dp
861      LOGICAL,SAVE   ::  first=.true.
862     
863      IF (first)THEN
864        first = .false.
865        eps = half**(16)
866        DO i = 17,80
867          eps = eps*half
868          CALL wlamch_add(one,eps,suma)
869          IF (suma.le.one)goto 10
870        ENDDO
871        PRINT*,'ERROR IN WLAMCH. EPS < ',Eps
872        RETURN
87310      eps = eps*2
874        i = i- 1     
875      ENDIF
876
877      wlamch = eps
878
879      END FUNCTION wlamch
880 
881      SUBROUTINE wlamch_add( a,b,suma)
882!      USE chem_gasphase_mod_Precision
883     
884      REAL(kind=dp)a,b,suma
885      suma = a + b
886
887      END SUBROUTINE wlamch_add
888 
889SUBROUTINE jac_sp(v,f,rct,jvs)
890
891! V - Concentrations of variable species (local)
892  REAL(kind=dp):: v(nvar)
893! F - Concentrations of fixed species (local)
894  REAL(kind=dp):: f(nfix)
895! RCT - Rate constants (local)
896  REAL(kind=dp):: rct(nreact)
897! JVS - sparse Jacobian of variables
898  REAL(kind=dp):: jvs(lu_nonzero)
899
900
901! Local variables
902! B - Temporary array
903  REAL(kind=dp):: b(3)
904
905! B(1) = dA(1)/dV(1)
906  b(1) = rct(1)
907! B(2) = dA(2)/dV(2)
908  b(2) = rct(2)
909! B(3) = dA(3)/dV(3)
910  b(3) = rct(3)
911
912! Construct the Jacobian terms from B's
913! JVS(1) = Jac_FULL(1,1)
914  jvs(1) = 0
915! JVS(2) = Jac_FULL(2,2)
916  jvs(2) = 0
917! JVS(3) = Jac_FULL(3,3)
918  jvs(3) = 0
919     
920END SUBROUTINE jac_sp
921 
922  elemental REAL(kind=dp)FUNCTION k_arr (k_298,tdep,temp)
923    ! arrhenius FUNCTION
924
925    REAL,    INTENT(in):: k_298 ! k at t = 298.15k
926    REAL,    INTENT(in):: tdep  ! temperature dependence
927    REAL(kind=dp),INTENT(in):: temp  ! temperature
928
929    intrinsic exp
930
931    k_arr = k_298 *exp(tdep*(1._dp/temp- 3.3540e-3_dp))! 1/298.15=3.3540e-3
932
933  END FUNCTION k_arr
934 
935SUBROUTINE update_rconst()
936 INTEGER         :: j,k
937
938  k = is
939
940! Begin INLINED RCONST
941
942
943! End INLINED RCONST
944
945  rconst(1) = (1.0_wp)
946  rconst(2) = (1.0_wp)
947  rconst(3) = (1.0_wp)
948     
949END SUBROUTINE update_rconst
950 
951REAL(kind=dp)FUNCTION arr2( a0,b0,temp)
952    REAL(kind=dp):: temp
953    REAL(kind=dp):: a0,b0
954    arr2 = a0 *exp( - b0 / temp)
955END FUNCTION arr2
956 
957SUBROUTINE initialize_kpp_ctrl(status,iou,modstr)
958
959
960  ! i/o
961  INTEGER,         INTENT(out):: status
962  INTEGER,         INTENT(in) :: iou     ! LOGICAL i/o unit
963  CHARACTER(len=*),INTENT(in) :: modstr  ! read <modstr>.nml
964
965  ! local
966  REAL(dp):: tsum
967  INTEGER  :: i
968
969  ! check fixed time steps
970  tsum = 0.0_dp
971  DO i=1,nmaxfixsteps
972     IF (t_steps(i)< tiny(0.0_dp))exit
973     tsum = tsum + t_steps(i)
974  ENDDO
975
976  nfsteps = i- 1
977
978  l_fixed_step = (nfsteps > 0).and.((tsum - 1.0)< tiny(0.0_dp))
979
980  IF (l_vector)THEN
981     WRITE(*,*) ' MODE             : VECTOR (LENGTH=',VL_DIM,')'
982  ELSE
983     WRITE(*,*) ' MODE             : SCALAR'
984  ENDIF
985  !
986  WRITE(*,*) ' DE-INDEXING MODE :',I_LU_DI
987  !
988  WRITE(*,*) ' ICNTRL           : ',icntrl
989  WRITE(*,*) ' RCNTRL           : ',rcntrl
990  !
991  ! note: this is only meaningful for vectorized (kp4)rosenbrock- methods
992  IF (l_vector)THEN
993     IF (l_fixed_step)THEN
994        WRITE(*,*) ' TIME STEPS       : FIXED (',t_steps(1:nfsteps),')'
995     ELSE
996        WRITE(*,*) ' TIME STEPS       : AUTOMATIC'
997     ENDIF
998  ELSE
999     WRITE(*,*) ' TIME STEPS       : AUTOMATIC '//&
1000          &'(t_steps (CTRL_KPP) ignored in SCALAR MODE)'
1001  ENDIF
1002  ! mz_pj_20070531-
1003
1004  status = 0
1005
1006
1007END SUBROUTINE initialize_kpp_ctrl
1008 
1009SUBROUTINE error_output(c,ierr,pe)
1010
1011
1012  INTEGER,INTENT(in):: ierr
1013  INTEGER,INTENT(in):: pe
1014  REAL(dp),DIMENSION(:),INTENT(in):: c
1015
1016  write(6,*) 'ERROR in chem_gasphase_mod ',ierr,C(1)
1017
1018
1019END SUBROUTINE error_output
1020 
1021      SUBROUTINE wcopy(n,x,incx,y,incy)
1022!- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
1023!     copies a vector,x,to a vector,y:  y <- x
1024!     only for incX=incY=1
1025!     after BLAS
1026!     replace this by the function from the optimized BLAS implementation:
1027!         CALL  SCOPY(N,X,1,Y,1)   or   CALL  DCOPY(N,X,1,Y,1)
1028!- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
1029!     USE chem_gasphase_mod_Precision
1030     
1031      INTEGER  :: i,incx,incy,m,mp1,n
1032      REAL(kind=dp):: x(n),y(n)
1033
1034      IF (n.le.0)RETURN
1035
1036      m = mod(n,8)
1037      IF( m .ne. 0)THEN
1038        DO i = 1,m
1039          y(i) = x(i)
1040        ENDDO
1041        IF( n .lt. 8)RETURN
1042      ENDIF   
1043      mp1 = m+ 1
1044      DO i = mp1,n,8
1045        y(i) = x(i)
1046        y(i + 1) = x(i + 1)
1047        y(i + 2) = x(i + 2)
1048        y(i + 3) = x(i + 3)
1049        y(i + 4) = x(i + 4)
1050        y(i + 5) = x(i + 5)
1051        y(i + 6) = x(i + 6)
1052        y(i + 7) = x(i + 7)
1053      ENDDO
1054
1055      END SUBROUTINE wcopy
1056 
1057      SUBROUTINE wscal(n,alpha,x,incx)
1058!- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
1059!     constant times a vector: x(1:N) <- Alpha*x(1:N)
1060!     only for incX=incY=1
1061!     after BLAS
1062!     replace this by the function from the optimized BLAS implementation:
1063!         CALL SSCAL(N,Alpha,X,1) or  CALL DSCAL(N,Alpha,X,1)
1064!- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
1065
1066      INTEGER  :: i,incx,m,mp1,n
1067      REAL(kind=dp) :: x(n),alpha
1068      REAL(kind=dp),PARAMETER  :: zero=0.0_dp, one=1.0_dp
1069
1070      IF (alpha .eq. one)RETURN
1071      IF (n .le. 0)RETURN
1072
1073      m = mod(n,5)
1074      IF( m .ne. 0)THEN
1075        IF (alpha .eq. (- one))THEN
1076          DO i = 1,m
1077            x(i) = - x(i)
1078          ENDDO
1079        ELSEIF (alpha .eq. zero)THEN
1080          DO i = 1,m
1081            x(i) = zero
1082          ENDDO
1083        ELSE
1084          DO i = 1,m
1085            x(i) = alpha*x(i)
1086          ENDDO
1087        ENDIF
1088        IF( n .lt. 5)RETURN
1089      ENDIF
1090      mp1 = m + 1
1091      IF (alpha .eq. (- one))THEN
1092        DO i = mp1,n,5
1093          x(i)    = - x(i)
1094          x(i + 1) = - x(i + 1)
1095          x(i + 2) = - x(i + 2)
1096          x(i + 3) = - x(i + 3)
1097          x(i + 4) = - x(i + 4)
1098        ENDDO
1099      ELSEIF (alpha .eq. zero)THEN
1100        DO i = mp1,n,5
1101          x(i)    = zero
1102          x(i + 1) = zero
1103          x(i + 2) = zero
1104          x(i + 3) = zero
1105          x(i + 4) = zero
1106        ENDDO
1107      ELSE
1108        DO i = mp1,n,5
1109          x(i)    = alpha*x(i)
1110          x(i + 1) = alpha*x(i + 1)
1111          x(i + 2) = alpha*x(i + 2)
1112          x(i + 3) = alpha*x(i + 3)
1113          x(i + 4) = alpha*x(i + 4)
1114        ENDDO
1115      ENDIF
1116
1117      END SUBROUTINE wscal
1118 
1119      SUBROUTINE waxpy(n,alpha,x,incx,y,incy)
1120!- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
1121!     constant times a vector plus a vector: y <- y + Alpha*x
1122!     only for incX=incY=1
1123!     after BLAS
1124!     replace this by the function from the optimized BLAS implementation:
1125!         CALL SAXPY(N,Alpha,X,1,Y,1) or  CALL DAXPY(N,Alpha,X,1,Y,1)
1126!- - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - - -
1127
1128      INTEGER  :: i,incx,incy,m,mp1,n
1129      REAL(kind=dp):: x(n),y(n),alpha
1130      REAL(kind=dp),PARAMETER :: zero = 0.0_dp
1131
1132      IF (alpha .eq. zero)RETURN
1133      IF (n .le. 0)RETURN
1134
1135      m = mod(n,4)
1136      IF( m .ne. 0)THEN
1137        DO i = 1,m
1138          y(i) = y(i)+ alpha*x(i)
1139        ENDDO
1140        IF( n .lt. 4)RETURN
1141      ENDIF
1142      mp1 = m + 1
1143      DO i = mp1,n,4
1144        y(i) = y(i)+ alpha*x(i)
1145        y(i + 1) = y(i + 1)+ alpha*x(i + 1)
1146        y(i + 2) = y(i + 2)+ alpha*x(i + 2)
1147        y(i + 3) = y(i + 3)+ alpha*x(i + 3)
1148      ENDDO
1149     
1150      END SUBROUTINE waxpy
1151 
1152SUBROUTINE rosenbrock(n,y,tstart,tend,&
1153           abstol,reltol,             &
1154           rcntrl,icntrl,rstatus,istatus,ierr)
1155!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
1156!
1157!    Solves the system y'=F(t,y) using a Rosenbrock method defined by:
1158!
1159!     G = 1/(H*gamma(1)) - Jac(t0,Y0)
1160!     T_i = t0 + Alpha(i)*H
1161!     Y_i = Y0 + \sum_{j=1}^{i-1} A(i,j)*K_j
1162!     G *K_i = Fun( T_i,Y_i)+ \sum_{j=1}^S C(i,j)/H *K_j +
1163!         gamma(i)*dF/dT(t0,Y0)
1164!     Y1 = Y0 + \sum_{j=1}^S M(j)*K_j
1165!
1166!    For details on Rosenbrock methods and their implementation consult:
1167!      E. Hairer and G. Wanner
1168!      "Solving ODEs II. Stiff and differential-algebraic problems".
1169!      Springer series in computational mathematics,Springer-Verlag,1996.
1170!    The codes contained in the book inspired this implementation.
1171!
1172!    (C)  Adrian Sandu,August 2004
1173!    Virginia Polytechnic Institute and State University
1174!    Contact: sandu@cs.vt.edu
1175!    Revised by Philipp Miehe and Adrian Sandu,May 2006                 
1176!    This implementation is part of KPP - the Kinetic PreProcessor
1177!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
1178!
1179!~~~>   input arguments:
1180!
1181!-      y(n)   = vector of initial conditions (at t=tstart)
1182!-     [tstart,tend]  = time range of integration
1183!     (if Tstart>Tend the integration is performed backwards in time)
1184!-     reltol,abstol = user precribed accuracy
1185!-  SUBROUTINE  fun( t,y,ydot) = ode FUNCTION,
1186!                       returns Ydot = Y' = F(T,Y)
1187!-  SUBROUTINE  jac( t,y,jcb) = jacobian of the ode FUNCTION,
1188!                       returns Jcb = dFun/dY
1189!-     icntrl(1:20)   = INTEGER inputs PARAMETERs
1190!-     rcntrl(1:20)   = REAL inputs PARAMETERs
1191!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
1192!
1193!~~~>     output arguments:
1194!
1195!-     y(n)   - > vector of final states (at t- >tEND)
1196!-     istatus(1:20)  - > INTEGER output PARAMETERs
1197!-     rstatus(1:20)  - > REAL output PARAMETERs
1198!-     ierr            - > job status upon RETURN
1199!                        success (positive value) or
1200!                        failure (negative value)
1201!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
1202!
1203!~~~>     input PARAMETERs:
1204!
1205!    Note: For input parameters equal to zero the default values of the
1206!       corresponding variables are used.
1207!
1208!    ICNTRL(1) = 1: F = F(y)   Independent of T (AUTONOMOUS)
1209!              = 0: F = F(t,y) Depends on T (NON-AUTONOMOUS)
1210!
1211!    ICNTRL(2) = 0: AbsTol,RelTol are N-dimensional vectors
1212!              = 1: AbsTol,RelTol are scalars
1213!
1214!    ICNTRL(3)  -> selection of a particular Rosenbrock method
1215!        = 0 :    Rodas3 (default)
1216!        = 1 :    Ros2
1217!        = 2 :    Ros3
1218!        = 3 :    Ros4
1219!        = 4 :    Rodas3
1220!        = 5 :    Rodas4
1221!
1222!    ICNTRL(4)  -> maximum number of integration steps
1223!        For ICNTRL(4) =0) the default value of 100000 is used
1224!
1225!    RCNTRL(1)  -> Hmin,lower bound for the integration step size
1226!          It is strongly recommended to keep Hmin = ZERO
1227!    RCNTRL(2)  -> Hmax,upper bound for the integration step size
1228!    RCNTRL(3)  -> Hstart,starting value for the integration step size
1229!
1230!    RCNTRL(4)  -> FacMin,lower bound on step decrease factor (default=0.2)
1231!    RCNTRL(5)  -> FacMax,upper bound on step increase factor (default=6)
1232!    RCNTRL(6)  -> FacRej,step decrease factor after multiple rejections
1233!                          (default=0.1)
1234!    RCNTRL(7)  -> FacSafe,by which the new step is slightly smaller
1235!         than the predicted value  (default=0.9)
1236!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
1237!
1238!
1239!    OUTPUT ARGUMENTS:
1240!    -----------------
1241!
1242!    T           -> T value for which the solution has been computed
1243!                     (after successful return T=Tend).
1244!
1245!    Y(N)        -> Numerical solution at T
1246!
1247!    IDID        -> Reports on successfulness upon return:
1248!                    = 1 for success
1249!                    < 0 for error (value equals error code)
1250!
1251!    ISTATUS(1)  -> No. of function calls
1252!    ISTATUS(2)  -> No. of jacobian calls
1253!    ISTATUS(3)  -> No. of steps
1254!    ISTATUS(4)  -> No. of accepted steps
1255!    ISTATUS(5)  -> No. of rejected steps (except at very beginning)
1256!    ISTATUS(6)  -> No. of LU decompositions
1257!    ISTATUS(7)  -> No. of forward/backward substitutions
1258!    ISTATUS(8)  -> No. of singular matrix decompositions
1259!
1260!    RSTATUS(1)  -> Texit,the time corresponding to the
1261!                     computed Y upon return
1262!    RSTATUS(2)  -> Hexit,last accepted step before exit
1263!    RSTATUS(3)  -> Hnew,last predicted step (not yet taken)
1264!                   For multiple restarts,use Hnew as Hstart
1265!                     in the subsequent run
1266!
1267!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
1268
1269
1270!~~~>  arguments
1271   INTEGER,      INTENT(in)   :: n
1272   REAL(kind=dp),INTENT(inout):: y(n)
1273   REAL(kind=dp),INTENT(in)   :: tstart,tend
1274   REAL(kind=dp),INTENT(in)   :: abstol(n),reltol(n)
1275   INTEGER,      INTENT(in)   :: icntrl(20)
1276   REAL(kind=dp),INTENT(in)   :: rcntrl(20)
1277   INTEGER,      INTENT(inout):: istatus(20)
1278   REAL(kind=dp),INTENT(inout):: rstatus(20)
1279   INTEGER,INTENT(out)  :: ierr
1280!~~~>  PARAMETERs of the rosenbrock method,up to 6 stages
1281   INTEGER ::  ros_s,rosmethod
1282   INTEGER,PARAMETER :: rs2=1,rs3=2,rs4=3,rd3=4,rd4=5,rg3=6
1283   REAL(kind=dp):: ros_a(15),ros_c(15),ros_m(6),ros_e(6),&
1284                    ros_alpha(6),ros_gamma(6),ros_elo
1285   LOGICAL :: ros_newf(6)
1286   CHARACTER(len=12):: ros_name
1287!~~~>  local variables
1288   REAL(kind=dp):: roundoff,facmin,facmax,facrej,facsafe
1289   REAL(kind=dp):: hmin,hmax,hstart
1290   REAL(kind=dp):: texit
1291   INTEGER       :: i,uplimtol,max_no_steps
1292   LOGICAL       :: autonomous,vectortol
1293!~~~>   PARAMETERs
1294   REAL(kind=dp),PARAMETER :: zero = 0.0_dp, one  = 1.0_dp
1295   REAL(kind=dp),PARAMETER :: deltamin = 1.0e-5_dp
1296
1297!~~~>  initialize statistics
1298   istatus(1:8) = 0
1299   rstatus(1:3) = zero
1300
1301!~~~>  autonomous or time dependent ode. default is time dependent.
1302   autonomous = .not.(icntrl(1) == 0)
1303
1304!~~~>  for scalar tolerances (icntrl(2).ne.0) the code uses abstol(1)and reltol(1)
1305!   For Vector tolerances (ICNTRL(2) == 0) the code uses AbsTol(1:N) and RelTol(1:N)
1306   IF (icntrl(2) == 0)THEN
1307      vectortol = .true.
1308      uplimtol  = n
1309   ELSE
1310      vectortol = .false.
1311      uplimtol  = 1
1312   ENDIF
1313
1314!~~~>   initialize the particular rosenbrock method selected
1315   select CASE (icntrl(3))
1316     CASE (1)
1317       CALL ros2
1318     CASE (2)
1319       CALL ros3
1320     CASE (3)
1321       CALL ros4
1322     CASE (0,4)
1323       CALL rodas3
1324     CASE (5)
1325       CALL rodas4
1326     CASE (6)
1327       CALL rang3
1328     CASE default
1329       PRINT *,'Unknown Rosenbrock method: ICNTRL(3) =',ICNTRL(3) 
1330       CALL ros_errormsg(- 2,tstart,zero,ierr)
1331       RETURN
1332   END select
1333
1334!~~~>   the maximum number of steps admitted
1335   IF (icntrl(4) == 0)THEN
1336      max_no_steps = 200000
1337   ELSEIF (icntrl(4)> 0)THEN
1338      max_no_steps=icntrl(4)
1339   ELSE
1340      PRINT *,'User-selected max no. of steps: ICNTRL(4) =',ICNTRL(4)
1341      CALL ros_errormsg(- 1,tstart,zero,ierr)
1342      RETURN
1343   ENDIF
1344
1345!~~~>  unit roundoff (1+ roundoff>1)
1346   Roundoff = WLAMCH('E')
1347
1348!~~~>  lower bound on the step size: (positive value)
1349   IF (rcntrl(1) == zero)THEN
1350      hmin = zero
1351   ELSEIF (rcntrl(1)> zero)THEN
1352      hmin = rcntrl(1)
1353   ELSE
1354      PRINT *,'User-selected Hmin: RCNTRL(1) =',RCNTRL(1)
1355      CALL ros_errormsg(- 3,tstart,zero,ierr)
1356      RETURN
1357   ENDIF
1358!~~~>  upper bound on the step size: (positive value)
1359   IF (rcntrl(2) == zero)THEN
1360      hmax = abs(tend-tstart)
1361   ELSEIF (rcntrl(2)> zero)THEN
1362      hmax = min(abs(rcntrl(2)),abs(tend-tstart))
1363   ELSE
1364      PRINT *,'User-selected Hmax: RCNTRL(2) =',RCNTRL(2)
1365      CALL ros_errormsg(- 3,tstart,zero,ierr)
1366      RETURN
1367   ENDIF
1368!~~~>  starting step size: (positive value)
1369   IF (rcntrl(3) == zero)THEN
1370      hstart = max(hmin,deltamin)
1371   ELSEIF (rcntrl(3)> zero)THEN
1372      hstart = min(abs(rcntrl(3)),abs(tend-tstart))
1373   ELSE
1374      PRINT *,'User-selected Hstart: RCNTRL(3) =',RCNTRL(3)
1375      CALL ros_errormsg(- 3,tstart,zero,ierr)
1376      RETURN
1377   ENDIF
1378!~~~>  step size can be changed s.t.  facmin < hnew/hold < facmax
1379   IF (rcntrl(4) == zero)THEN
1380      facmin = 0.2_dp
1381   ELSEIF (rcntrl(4)> zero)THEN
1382      facmin = rcntrl(4)
1383   ELSE
1384      PRINT *,'User-selected FacMin: RCNTRL(4) =',RCNTRL(4)
1385      CALL ros_errormsg(- 4,tstart,zero,ierr)
1386      RETURN
1387   ENDIF
1388   IF (rcntrl(5) == zero)THEN
1389      facmax = 6.0_dp
1390   ELSEIF (rcntrl(5)> zero)THEN
1391      facmax = rcntrl(5)
1392   ELSE
1393      PRINT *,'User-selected FacMax: RCNTRL(5) =',RCNTRL(5)
1394      CALL ros_errormsg(- 4,tstart,zero,ierr)
1395      RETURN
1396   ENDIF
1397!~~~>   facrej: factor to decrease step after 2 succesive rejections
1398   IF (rcntrl(6) == zero)THEN
1399      facrej = 0.1_dp
1400   ELSEIF (rcntrl(6)> zero)THEN
1401      facrej = rcntrl(6)
1402   ELSE
1403      PRINT *,'User-selected FacRej: RCNTRL(6) =',RCNTRL(6)
1404      CALL ros_errormsg(- 4,tstart,zero,ierr)
1405      RETURN
1406   ENDIF
1407!~~~>   facsafe: safety factor in the computation of new step size
1408   IF (rcntrl(7) == zero)THEN
1409      facsafe = 0.9_dp
1410   ELSEIF (rcntrl(7)> zero)THEN
1411      facsafe = rcntrl(7)
1412   ELSE
1413      PRINT *,'User-selected FacSafe: RCNTRL(7) =',RCNTRL(7)
1414      CALL ros_errormsg(- 4,tstart,zero,ierr)
1415      RETURN
1416   ENDIF
1417!~~~>  check IF tolerances are reasonable
1418    DO i=1,uplimtol
1419      IF((abstol(i)<= zero).or. (reltol(i)<= 10.0_dp*roundoff)&
1420         .or. (reltol(i)>= 1.0_dp))THEN
1421        PRINT *,' AbsTol(',i,') = ',AbsTol(i)
1422        PRINT *,' RelTol(',i,') = ',RelTol(i)
1423        CALL ros_errormsg(- 5,tstart,zero,ierr)
1424        RETURN
1425      ENDIF
1426    ENDDO
1427
1428
1429!~~~>  CALL rosenbrock method
1430   CALL ros_integrator(y,tstart,tend,texit,  &
1431        abstol,reltol,                         &
1432!  Integration parameters
1433        autonomous,vectortol,max_no_steps,    &
1434        roundoff,hmin,hmax,hstart,           &
1435        facmin,facmax,facrej,facsafe,        &
1436!  Error indicator
1437        ierr)
1438
1439!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
1440CONTAINS !  SUBROUTINEs internal to rosenbrock
1441!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
1442   
1443!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~   
1444 SUBROUTINE ros_errormsg(code,t,h,ierr)
1445!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~   
1446!    Handles all error messages
1447!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~   
1448 
1449   REAL(kind=dp),INTENT(in):: t,h
1450   INTEGER,INTENT(in) :: code
1451   INTEGER,INTENT(out):: ierr
1452   
1453   ierr = code
1454   print *,&
1455     'Forced exit from Rosenbrock due to the following error:' 
1456     
1457   select CASE (code)
1458    CASE (- 1)   
1459      PRINT *,'--> Improper value for maximal no of steps'
1460    CASE (- 2)   
1461      PRINT *,'--> Selected Rosenbrock method not implemented'
1462    CASE (- 3)   
1463      PRINT *,'--> Hmin/Hmax/Hstart must be positive'
1464    CASE (- 4)   
1465      PRINT *,'--> FacMin/FacMax/FacRej must be positive'
1466    CASE (- 5)
1467      PRINT *,'--> Improper tolerance values'
1468    CASE (- 6)
1469      PRINT *,'--> No of steps exceeds maximum bound'
1470    CASE (- 7)
1471      PRINT *,'--> Step size too small: T + 10*H = T',&
1472            ' or H < Roundoff'
1473    CASE (- 8)   
1474      PRINT *,'--> Matrix is repeatedly singular'
1475    CASE default
1476      PRINT *,'Unknown Error code: ',Code
1477   END select
1478   
1479   print *,"t=",t,"and h=",h
1480     
1481 END SUBROUTINE ros_errormsg
1482
1483!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
1484 SUBROUTINE ros_integrator (y,tstart,tend,t, &
1485        abstol,reltol,                         &
1486!~~~> integration PARAMETERs
1487        autonomous,vectortol,max_no_steps,    &
1488        roundoff,hmin,hmax,hstart,           &
1489        facmin,facmax,facrej,facsafe,        &
1490!~~~> error indicator
1491        ierr)
1492!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
1493!   Template for the implementation of a generic Rosenbrock method
1494!      defined by ros_S (no of stages)
1495!      and its coefficients ros_{A,C,M,E,Alpha,Gamma}
1496!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
1497
1498
1499!~~~> input: the initial condition at tstart; output: the solution at t
1500   REAL(kind=dp),INTENT(inout):: y(n)
1501!~~~> input: integration interval
1502   REAL(kind=dp),INTENT(in):: tstart,tend
1503!~~~> output: time at which the solution is RETURNed (t=tENDIF success)
1504   REAL(kind=dp),INTENT(out)::  t
1505!~~~> input: tolerances
1506   REAL(kind=dp),INTENT(in)::  abstol(n),reltol(n)
1507!~~~> input: integration PARAMETERs
1508   LOGICAL,INTENT(in):: autonomous,vectortol
1509   REAL(kind=dp),INTENT(in):: hstart,hmin,hmax
1510   INTEGER,INTENT(in):: max_no_steps
1511   REAL(kind=dp),INTENT(in):: roundoff,facmin,facmax,facrej,facsafe
1512!~~~> output: error indicator
1513   INTEGER,INTENT(out):: ierr
1514! ~~~~ Local variables
1515   REAL(kind=dp):: ynew(n),fcn0(n),fcn(n)
1516   REAL(kind=dp):: k(n*ros_s),dfdt(n)
1517#ifdef full_algebra   
1518   REAL(kind=dp):: jac0(n,n),ghimj(n,n)
1519#else
1520   REAL(kind=dp):: jac0(lu_nonzero),ghimj(lu_nonzero)
1521#endif
1522   REAL(kind=dp):: h,hnew,hc,hg,fac,tau
1523   REAL(kind=dp):: err,yerr(n)
1524   INTEGER :: pivot(n),direction,ioffset,j,istage
1525   LOGICAL :: rejectlasth,rejectmoreh,singular
1526!~~~>  local PARAMETERs
1527   REAL(kind=dp),PARAMETER :: zero = 0.0_dp, one  = 1.0_dp
1528   REAL(kind=dp),PARAMETER :: deltamin = 1.0e-5_dp
1529!~~~>  locally called FUNCTIONs
1530!    REAL(kind=dp) WLAMCH
1531!    EXTERNAL WLAMCH
1532!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
1533
1534
1535!~~~>  initial preparations
1536   t = tstart
1537   rstatus(nhexit) = zero
1538   h = min( max(abs(hmin),abs(hstart)),abs(hmax))
1539   IF (abs(h)<= 10.0_dp*roundoff)h = deltamin
1540
1541   IF (tEND  >=  tstart)THEN
1542     direction = + 1
1543   ELSE
1544     direction = - 1
1545   ENDIF
1546   h = direction*h
1547
1548   rejectlasth=.false.
1549   rejectmoreh=.false.
1550
1551!~~~> time loop begins below
1552
1553timeloop: DO WHILE((direction > 0).and.((t- tEND)+ roundoff <= zero)&
1554       .or. (direction < 0).and.((tend-t)+ roundoff <= zero))
1555
1556   IF(istatus(nstp)> max_no_steps)THEN  ! too many steps
1557      CALL ros_errormsg(- 6,t,h,ierr)
1558      RETURN
1559   ENDIF
1560   IF(((t+ 0.1_dp*h) == t).or.(h <= roundoff))THEN  ! step size too small
1561      CALL ros_errormsg(- 7,t,h,ierr)
1562      RETURN
1563   ENDIF
1564
1565!~~~>  limit h IF necessary to avoid going beyond tend
1566   h = min(h,abs(tend-t))
1567
1568!~~~>   compute the FUNCTION at current time
1569   CALL funtemplate(t,y,fcn0)
1570   istatus(nfun) = istatus(nfun)+ 1
1571
1572!~~~>  compute the FUNCTION derivative with respect to t
1573   IF (.not.autonomous)THEN
1574      CALL ros_funtimederivative(t,roundoff,y,&
1575                fcn0,dfdt)
1576   ENDIF
1577
1578!~~~>   compute the jacobian at current time
1579   CALL jactemplate(t,y,jac0)
1580   istatus(njac) = istatus(njac)+ 1
1581
1582!~~~>  repeat step calculation until current step accepted
1583untilaccepted: do
1584
1585   CALL ros_preparematrix(h,direction,ros_gamma(1),&
1586          jac0,ghimj,pivot,singular)
1587   IF (singular)THEN ! more than 5 consecutive failed decompositions
1588       CALL ros_errormsg(- 8,t,h,ierr)
1589       RETURN
1590   ENDIF
1591
1592!~~~>   compute the stages
1593stage: DO istage = 1,ros_s
1594
1595      ! current istage offset. current istage vector is k(ioffset+ 1:ioffset+ n)
1596       ioffset = n*(istage-1)
1597
1598      ! for the 1st istage the FUNCTION has been computed previously
1599       IF(istage == 1)THEN
1600         !slim: CALL wcopy(n,fcn0,1,fcn,1)
1601         fcn(1:n) = fcn0(1:n)
1602      ! istage>1 and a new FUNCTION evaluation is needed at the current istage
1603       ELSEIF(ros_newf(istage))THEN
1604         !slim: CALL wcopy(n,y,1,ynew,1)
1605         ynew(1:n) = y(1:n)
1606         DO j = 1,istage-1
1607           CALL waxpy(n,ros_a((istage-1)*(istage-2)/2+ j),&
1608            k(n*(j- 1)+ 1),1,ynew,1)
1609         ENDDO
1610         tau = t + ros_alpha(istage)*direction*h
1611         CALL funtemplate(tau,ynew,fcn)
1612         istatus(nfun) = istatus(nfun)+ 1
1613       ENDIF ! IF istage == 1 ELSEIF ros_newf(istage)
1614       !slim: CALL wcopy(n,fcn,1,k(ioffset+ 1),1)
1615       k(ioffset+ 1:ioffset+ n) = fcn(1:n)
1616       DO j = 1,istage-1
1617         hc = ros_c((istage-1)*(istage-2)/2+ j)/(direction*h)
1618         CALL waxpy(n,hc,k(n*(j- 1)+ 1),1,k(ioffset+ 1),1)
1619       ENDDO
1620       IF ((.not. autonomous).and.(ros_gamma(istage).ne.zero))THEN
1621         hg = direction*h*ros_gamma(istage)
1622         CALL waxpy(n,hg,dfdt,1,k(ioffset+ 1),1)
1623       ENDIF
1624       CALL ros_solve(ghimj,pivot,k(ioffset+ 1))
1625
1626   END DO stage
1627
1628
1629!~~~>  compute the new solution
1630   !slim: CALL wcopy(n,y,1,ynew,1)
1631   ynew(1:n) = y(1:n)
1632   DO j=1,ros_s
1633         CALL waxpy(n,ros_m(j),k(n*(j- 1)+ 1),1,ynew,1)
1634   ENDDO
1635
1636!~~~>  compute the error estimation
1637   !slim: CALL wscal(n,zero,yerr,1)
1638   yerr(1:n) = zero
1639   DO j=1,ros_s
1640        CALL waxpy(n,ros_e(j),k(n*(j- 1)+ 1),1,yerr,1)
1641   ENDDO
1642   err = ros_errornorm(y,ynew,yerr,abstol,reltol,vectortol)
1643
1644!~~~> new step size is bounded by facmin <= hnew/h <= facmax
1645   fac  = min(facmax,max(facmin,facsafe/err**(one/ros_elo)))
1646   hnew = h*fac
1647
1648!~~~>  check the error magnitude and adjust step size
1649   istatus(nstp) = istatus(nstp)+ 1
1650   IF((err <= one).or.(h <= hmin))THEN  !~~~> accept step
1651      istatus(nacc) = istatus(nacc)+ 1
1652      !slim: CALL wcopy(n,ynew,1,y,1)
1653      y(1:n) = ynew(1:n)
1654      t = t + direction*h
1655      hnew = max(hmin,min(hnew,hmax))
1656      IF (rejectlasth)THEN  ! no step size increase after a rejected step
1657         hnew = min(hnew,h)
1658      ENDIF
1659      rstatus(nhexit) = h
1660      rstatus(nhnew) = hnew
1661      rstatus(ntexit) = t
1662      rejectlasth = .false.
1663      rejectmoreh = .false.
1664      h = hnew
1665      exit untilaccepted ! exit the loop: WHILE step not accepted
1666   ELSE           !~~~> reject step
1667      IF (rejectmoreh)THEN
1668         hnew = h*facrej
1669      ENDIF
1670      rejectmoreh = rejectlasth
1671      rejectlasth = .true.
1672      h = hnew
1673      IF (istatus(nacc)>= 1) istatus(nrej) = istatus(nrej)+ 1
1674   ENDIF ! err <= 1
1675
1676   END DO untilaccepted
1677
1678   END DO timeloop
1679
1680!~~~> succesful exit
1681   ierr = 1  !~~~> the integration was successful
1682
1683  END SUBROUTINE ros_integrator
1684
1685
1686!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
1687  REAL(kind=dp)FUNCTION ros_errornorm(y,ynew,yerr,&
1688                               abstol,reltol,vectortol)
1689!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
1690!~~~> computes the "scaled norm" of the error vector yerr
1691!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
1692
1693! Input arguments
1694   REAL(kind=dp),INTENT(in):: y(n),ynew(n),&
1695          yerr(n),abstol(n),reltol(n)
1696   LOGICAL,INTENT(in)::  vectortol
1697! Local variables
1698   REAL(kind=dp):: err,scale,ymax
1699   INTEGER  :: i
1700   REAL(kind=dp),PARAMETER :: zero = 0.0_dp
1701
1702   err = zero
1703   DO i=1,n
1704     ymax = max(abs(y(i)),abs(ynew(i)))
1705     IF (vectortol)THEN
1706       scale = abstol(i)+ reltol(i)*ymax
1707     ELSE
1708       scale = abstol(1)+ reltol(1)*ymax
1709     ENDIF
1710     err = err+(yerr(i)/scale)**2
1711   ENDDO
1712   err  = sqrt(err/n)
1713
1714   ros_errornorm = max(err,1.0d-10)
1715
1716  END FUNCTION ros_errornorm
1717
1718
1719!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
1720  SUBROUTINE ros_funtimederivative(t,roundoff,y,&
1721                fcn0,dfdt)
1722!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
1723!~~~> the time partial derivative of the FUNCTION by finite differences
1724!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
1725
1726!~~~> input arguments
1727   REAL(kind=dp),INTENT(in):: t,roundoff,y(n),fcn0(n)
1728!~~~> output arguments
1729   REAL(kind=dp),INTENT(out):: dfdt(n)
1730!~~~> local variables
1731   REAL(kind=dp):: delta
1732   REAL(kind=dp),PARAMETER :: one = 1.0_dp, deltamin = 1.0e-6_dp
1733
1734   delta = sqrt(roundoff)*max(deltamin,abs(t))
1735   CALL funtemplate(t+ delta,y,dfdt)
1736   istatus(nfun) = istatus(nfun)+ 1
1737   CALL waxpy(n,(- one),fcn0,1,dfdt,1)
1738   CALL wscal(n,(one/delta),dfdt,1)
1739
1740  END SUBROUTINE ros_funtimederivative
1741
1742
1743!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
1744  SUBROUTINE ros_preparematrix(h,direction,gam,&
1745             jac0,ghimj,pivot,singular)
1746! --- --- --- --- --- --- --- --- --- --- --- --- ---
1747!  Prepares the LHS matrix for stage calculations
1748!  1.  Construct Ghimj = 1/(H*ham) - Jac0
1749!      "(Gamma H) Inverse Minus Jacobian"
1750!  2.  Repeat LU decomposition of Ghimj until successful.
1751!       -half the step size if LU decomposition fails and retry
1752!       -exit after 5 consecutive fails
1753! --- --- --- --- --- --- --- --- --- --- --- --- ---
1754
1755!~~~> input arguments
1756#ifdef full_algebra   
1757   REAL(kind=dp),INTENT(in)::  jac0(n,n)
1758#else
1759   REAL(kind=dp),INTENT(in)::  jac0(lu_nonzero)
1760#endif   
1761   REAL(kind=dp),INTENT(in)::  gam
1762   INTEGER,INTENT(in)::  direction
1763!~~~> output arguments
1764#ifdef full_algebra   
1765   REAL(kind=dp),INTENT(out):: ghimj(n,n)
1766#else
1767   REAL(kind=dp),INTENT(out):: ghimj(lu_nonzero)
1768#endif   
1769   LOGICAL,INTENT(out)::  singular
1770   INTEGER,INTENT(out)::  pivot(n)
1771!~~~> inout arguments
1772   REAL(kind=dp),INTENT(inout):: h   ! step size is decreased when lu fails
1773!~~~> local variables
1774   INTEGER  :: i,ising,nconsecutive
1775   REAL(kind=dp):: ghinv
1776   REAL(kind=dp),PARAMETER :: one  = 1.0_dp, half = 0.5_dp
1777
1778   nconsecutive = 0
1779   singular = .true.
1780
1781   DO WHILE (singular)
1782
1783!~~~>    construct ghimj = 1/(h*gam)-  jac0
1784#ifdef full_algebra   
1785     !slim: CALL wcopy(n*n,jac0,1,ghimj,1)
1786     !slim: CALL wscal(n*n,(- one),ghimj,1)
1787     ghimj = - jac0
1788     ghinv = one/(direction*h*gam)
1789     DO i=1,n
1790       ghimj(i,i) = ghimj(i,i)+ ghinv
1791     ENDDO
1792#else
1793     !slim: CALL wcopy(lu_nonzero,jac0,1,ghimj,1)
1794     !slim: CALL wscal(lu_nonzero,(- one),ghimj,1)
1795     ghimj(1:lu_nonzero) = - jac0(1:lu_nonzero)
1796     ghinv = one/(direction*h*gam)
1797     DO i=1,n
1798       ghimj(lu_diag(i)) = ghimj(lu_diag(i))+ ghinv
1799     ENDDO
1800#endif   
1801!~~~>    compute lu decomposition
1802     CALL ros_decomp( ghimj,pivot,ising)
1803     IF (ising == 0)THEN
1804!~~~>    IF successful done
1805        singular = .false.
1806     ELSE ! ising .ne. 0
1807!~~~>    IF unsuccessful half the step size; IF 5 consecutive fails THEN RETURN
1808        istatus(nsng) = istatus(nsng)+ 1
1809        nconsecutive = nconsecutive+1
1810        singular = .true.
1811        PRINT*,'Warning: LU Decomposition returned ISING = ',ISING
1812        IF (nconsecutive <= 5)THEN ! less than 5 consecutive failed decompositions
1813           h = h*half
1814        ELSE  ! more than 5 consecutive failed decompositions
1815           RETURN
1816        ENDIF  ! nconsecutive
1817      ENDIF    ! ising
1818
1819   END DO ! WHILE singular
1820
1821  END SUBROUTINE ros_preparematrix
1822
1823
1824!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
1825  SUBROUTINE ros_decomp( a,pivot,ising)
1826!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
1827!  Template for the LU decomposition
1828!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
1829!~~~> inout variables
1830#ifdef full_algebra   
1831   REAL(kind=dp),INTENT(inout):: a(n,n)
1832#else   
1833   REAL(kind=dp),INTENT(inout):: a(lu_nonzero)
1834#endif
1835!~~~> output variables
1836   INTEGER,INTENT(out):: pivot(n),ising
1837
1838#ifdef full_algebra   
1839   CALL  dgetrf( n,n,a,n,pivot,ising)
1840#else   
1841   CALL kppdecomp(a,ising)
1842   pivot(1) = 1
1843#endif
1844   istatus(ndec) = istatus(ndec)+ 1
1845
1846  END SUBROUTINE ros_decomp
1847
1848
1849!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
1850  SUBROUTINE ros_solve( a,pivot,b)
1851!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
1852!  Template for the forward/backward substitution (using pre-computed LU decomposition)
1853!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
1854!~~~> input variables
1855#ifdef full_algebra   
1856   REAL(kind=dp),INTENT(in):: a(n,n)
1857   INTEGER :: ising
1858#else   
1859   REAL(kind=dp),INTENT(in):: a(lu_nonzero)
1860#endif
1861   INTEGER,INTENT(in):: pivot(n)
1862!~~~> inout variables
1863   REAL(kind=dp),INTENT(inout):: b(n)
1864
1865#ifdef full_algebra   
1866   CALL  DGETRS( 'N',N ,1,A,N,Pivot,b,N,ISING)
1867   IF(info < 0)THEN
1868      print*,"error in dgetrs. ising=",ising
1869   ENDIF 
1870#else   
1871   CALL kppsolve( a,b)
1872#endif
1873
1874   istatus(nsol) = istatus(nsol)+ 1
1875
1876  END SUBROUTINE ros_solve
1877
1878
1879
1880!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
1881  SUBROUTINE ros2
1882!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
1883! --- AN L-STABLE METHOD,2 stages,order 2
1884!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
1885
1886   double precision g
1887
1888    g = 1.0_dp + 1.0_dp/sqrt(2.0_dp)
1889    rosmethod = rs2
1890!~~~> name of the method
1891    ros_Name = 'ROS-2'
1892!~~~> number of stages
1893    ros_s = 2
1894
1895!~~~> the coefficient matrices a and c are strictly lower triangular.
1896!   The lower triangular (subdiagonal) elements are stored in row-wise order:
1897!   A(2,1) = ros_A(1),A(3,1) =ros_A(2),A(3,2) =ros_A(3),etc.
1898!   The general mapping formula is:
1899!       A(i,j) = ros_A( (i-1)*(i-2)/2 + j)
1900!       C(i,j) = ros_C( (i-1)*(i-2)/2 + j)
1901
1902    ros_a(1) = (1.0_dp)/g
1903    ros_c(1) = (- 2.0_dp)/g
1904!~~~> does the stage i require a new FUNCTION evaluation (ros_newf(i) =true)
1905!   or does it re-use the function evaluation from stage i-1 (ros_NewF(i) =FALSE)
1906    ros_newf(1) = .true.
1907    ros_newf(2) = .true.
1908!~~~> m_i = coefficients for new step solution
1909    ros_m(1) = (3.0_dp)/(2.0_dp*g)
1910    ros_m(2) = (1.0_dp)/(2.0_dp*g)
1911! E_i = Coefficients for error estimator
1912    ros_e(1) = 1.0_dp/(2.0_dp*g)
1913    ros_e(2) = 1.0_dp/(2.0_dp*g)
1914!~~~> ros_elo = estimator of local order -  the minimum between the
1915!    main and the embedded scheme orders plus one
1916    ros_elo = 2.0_dp
1917!~~~> y_stage_i ~ y( t + h*alpha_i)
1918    ros_alpha(1) = 0.0_dp
1919    ros_alpha(2) = 1.0_dp
1920!~~~> gamma_i = \sum_j  gamma_{i,j}
1921    ros_gamma(1) = g
1922    ros_gamma(2) =- g
1923
1924 END SUBROUTINE ros2
1925
1926
1927!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
1928  SUBROUTINE ros3
1929!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
1930! --- AN L-STABLE METHOD,3 stages,order 3,2 function evaluations
1931!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
1932
1933   rosmethod = rs3
1934!~~~> name of the method
1935   ros_Name = 'ROS-3'
1936!~~~> number of stages
1937   ros_s = 3
1938
1939!~~~> the coefficient matrices a and c are strictly lower triangular.
1940!   The lower triangular (subdiagonal) elements are stored in row-wise order:
1941!   A(2,1) = ros_A(1),A(3,1) =ros_A(2),A(3,2) =ros_A(3),etc.
1942!   The general mapping formula is:
1943!       A(i,j) = ros_A( (i-1)*(i-2)/2 + j)
1944!       C(i,j) = ros_C( (i-1)*(i-2)/2 + j)
1945
1946   ros_a(1) = 1.0_dp
1947   ros_a(2) = 1.0_dp
1948   ros_a(3) = 0.0_dp
1949
1950   ros_c(1) = - 0.10156171083877702091975600115545e+01_dp
1951   ros_c(2) =  0.40759956452537699824805835358067e+01_dp
1952   ros_c(3) =  0.92076794298330791242156818474003e+01_dp
1953!~~~> does the stage i require a new FUNCTION evaluation (ros_newf(i) =true)
1954!   or does it re-use the function evaluation from stage i-1 (ros_NewF(i) =FALSE)
1955   ros_newf(1) = .true.
1956   ros_newf(2) = .true.
1957   ros_newf(3) = .false.
1958!~~~> m_i = coefficients for new step solution
1959   ros_m(1) =  0.1e+01_dp
1960   ros_m(2) =  0.61697947043828245592553615689730e+01_dp
1961   ros_m(3) = - 0.42772256543218573326238373806514_dp
1962! E_i = Coefficients for error estimator
1963   ros_e(1) =  0.5_dp
1964   ros_e(2) = - 0.29079558716805469821718236208017e+01_dp
1965   ros_e(3) =  0.22354069897811569627360909276199_dp
1966!~~~> ros_elo = estimator of local order -  the minimum between the
1967!    main and the embedded scheme orders plus 1
1968   ros_elo = 3.0_dp
1969!~~~> y_stage_i ~ y( t + h*alpha_i)
1970   ros_alpha(1) = 0.0_dp
1971   ros_alpha(2) = 0.43586652150845899941601945119356_dp
1972   ros_alpha(3) = 0.43586652150845899941601945119356_dp
1973!~~~> gamma_i = \sum_j  gamma_{i,j}
1974   ros_gamma(1) = 0.43586652150845899941601945119356_dp
1975   ros_gamma(2) = 0.24291996454816804366592249683314_dp
1976   ros_gamma(3) = 0.21851380027664058511513169485832e+01_dp
1977
1978  END SUBROUTINE ros3
1979
1980!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
1981
1982
1983!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
1984  SUBROUTINE ros4
1985!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
1986!     L-STABLE ROSENBROCK METHOD OF ORDER 4,WITH 4 STAGES
1987!     L-STABLE EMBEDDED ROSENBROCK METHOD OF ORDER 3
1988!
1989!      E. HAIRER AND G. WANNER,SOLVING ORDINARY DIFFERENTIAL
1990!      EQUATIONS II. STIFF AND DIFFERENTIAL-ALGEBRAIC PROBLEMS.
1991!      SPRINGER SERIES IN COMPUTATIONAL MATHEMATICS,
1992!      SPRINGER-VERLAG (1990)
1993!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
1994
1995
1996   rosmethod = rs4
1997!~~~> name of the method
1998   ros_Name = 'ROS-4'
1999!~~~> number of stages
2000   ros_s = 4
2001
2002!~~~> the coefficient matrices a and c are strictly lower triangular.
2003!   The lower triangular (subdiagonal) elements are stored in row-wise order:
2004!   A(2,1) = ros_A(1),A(3,1) =ros_A(2),A(3,2) =ros_A(3),etc.
2005!   The general mapping formula is:
2006!       A(i,j) = ros_A( (i-1)*(i-2)/2 + j)
2007!       C(i,j) = ros_C( (i-1)*(i-2)/2 + j)
2008
2009   ros_a(1) = 0.2000000000000000e+01_dp
2010   ros_a(2) = 0.1867943637803922e+01_dp
2011   ros_a(3) = 0.2344449711399156_dp
2012   ros_a(4) = ros_a(2)
2013   ros_a(5) = ros_a(3)
2014   ros_a(6) = 0.0_dp
2015
2016   ros_c(1) =- 0.7137615036412310e+01_dp
2017   ros_c(2) = 0.2580708087951457e+01_dp
2018   ros_c(3) = 0.6515950076447975_dp
2019   ros_c(4) =- 0.2137148994382534e+01_dp
2020   ros_c(5) =- 0.3214669691237626_dp
2021   ros_c(6) =- 0.6949742501781779_dp
2022!~~~> does the stage i require a new FUNCTION evaluation (ros_newf(i) =true)
2023!   or does it re-use the function evaluation from stage i-1 (ros_NewF(i) =FALSE)
2024   ros_newf(1) = .true.
2025   ros_newf(2) = .true.
2026   ros_newf(3) = .true.
2027   ros_newf(4) = .false.
2028!~~~> m_i = coefficients for new step solution
2029   ros_m(1) = 0.2255570073418735e+01_dp
2030   ros_m(2) = 0.2870493262186792_dp
2031   ros_m(3) = 0.4353179431840180_dp
2032   ros_m(4) = 0.1093502252409163e+01_dp
2033!~~~> e_i  = coefficients for error estimator
2034   ros_e(1) =- 0.2815431932141155_dp
2035   ros_e(2) =- 0.7276199124938920e-01_dp
2036   ros_e(3) =- 0.1082196201495311_dp
2037   ros_e(4) =- 0.1093502252409163e+01_dp
2038!~~~> ros_elo  = estimator of local order -  the minimum between the
2039!    main and the embedded scheme orders plus 1
2040   ros_elo  = 4.0_dp
2041!~~~> y_stage_i ~ y( t + h*alpha_i)
2042   ros_alpha(1) = 0.0_dp
2043   ros_alpha(2) = 0.1145640000000000e+01_dp
2044   ros_alpha(3) = 0.6552168638155900_dp
2045   ros_alpha(4) = ros_alpha(3)
2046!~~~> gamma_i = \sum_j  gamma_{i,j}
2047   ros_gamma(1) = 0.5728200000000000_dp
2048   ros_gamma(2) =- 0.1769193891319233e+01_dp
2049   ros_gamma(3) = 0.7592633437920482_dp
2050   ros_gamma(4) =- 0.1049021087100450_dp
2051
2052  END SUBROUTINE ros4
2053
2054!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
2055  SUBROUTINE rodas3
2056!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
2057! --- A STIFFLY-STABLE METHOD,4 stages,order 3
2058!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
2059
2060
2061   rosmethod = rd3
2062!~~~> name of the method
2063   ros_Name = 'RODAS-3'
2064!~~~> number of stages
2065   ros_s = 4
2066
2067!~~~> the coefficient matrices a and c are strictly lower triangular.
2068!   The lower triangular (subdiagonal) elements are stored in row-wise order:
2069!   A(2,1) = ros_A(1),A(3,1) =ros_A(2),A(3,2) =ros_A(3),etc.
2070!   The general mapping formula is:
2071!       A(i,j) = ros_A( (i-1)*(i-2)/2 + j)
2072!       C(i,j) = ros_C( (i-1)*(i-2)/2 + j)
2073
2074   ros_a(1) = 0.0_dp
2075   ros_a(2) = 2.0_dp
2076   ros_a(3) = 0.0_dp
2077   ros_a(4) = 2.0_dp
2078   ros_a(5) = 0.0_dp
2079   ros_a(6) = 1.0_dp
2080
2081   ros_c(1) = 4.0_dp
2082   ros_c(2) = 1.0_dp
2083   ros_c(3) =- 1.0_dp
2084   ros_c(4) = 1.0_dp
2085   ros_c(5) =- 1.0_dp
2086   ros_c(6) =- (8.0_dp/3.0_dp)
2087
2088!~~~> does the stage i require a new FUNCTION evaluation (ros_newf(i) =true)
2089!   or does it re-use the function evaluation from stage i-1 (ros_NewF(i) =FALSE)
2090   ros_newf(1) = .true.
2091   ros_newf(2) = .false.
2092   ros_newf(3) = .true.
2093   ros_newf(4) = .true.
2094!~~~> m_i = coefficients for new step solution
2095   ros_m(1) = 2.0_dp
2096   ros_m(2) = 0.0_dp
2097   ros_m(3) = 1.0_dp
2098   ros_m(4) = 1.0_dp
2099!~~~> e_i  = coefficients for error estimator
2100   ros_e(1) = 0.0_dp
2101   ros_e(2) = 0.0_dp
2102   ros_e(3) = 0.0_dp
2103   ros_e(4) = 1.0_dp
2104!~~~> ros_elo  = estimator of local order -  the minimum between the
2105!    main and the embedded scheme orders plus 1
2106   ros_elo  = 3.0_dp
2107!~~~> y_stage_i ~ y( t + h*alpha_i)
2108   ros_alpha(1) = 0.0_dp
2109   ros_alpha(2) = 0.0_dp
2110   ros_alpha(3) = 1.0_dp
2111   ros_alpha(4) = 1.0_dp
2112!~~~> gamma_i = \sum_j  gamma_{i,j}
2113   ros_gamma(1) = 0.5_dp
2114   ros_gamma(2) = 1.5_dp
2115   ros_gamma(3) = 0.0_dp
2116   ros_gamma(4) = 0.0_dp
2117
2118  END SUBROUTINE rodas3
2119
2120!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
2121  SUBROUTINE rodas4
2122!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
2123!     STIFFLY-STABLE ROSENBROCK METHOD OF ORDER 4,WITH 6 STAGES
2124!
2125!      E. HAIRER AND G. WANNER,SOLVING ORDINARY DIFFERENTIAL
2126!      EQUATIONS II. STIFF AND DIFFERENTIAL-ALGEBRAIC PROBLEMS.
2127!      SPRINGER SERIES IN COMPUTATIONAL MATHEMATICS,
2128!      SPRINGER-VERLAG (1996)
2129!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
2130
2131
2132    rosmethod = rd4
2133!~~~> name of the method
2134    ros_Name = 'RODAS-4'
2135!~~~> number of stages
2136    ros_s = 6
2137
2138!~~~> y_stage_i ~ y( t + h*alpha_i)
2139    ros_alpha(1) = 0.000_dp
2140    ros_alpha(2) = 0.386_dp
2141    ros_alpha(3) = 0.210_dp
2142    ros_alpha(4) = 0.630_dp
2143    ros_alpha(5) = 1.000_dp
2144    ros_alpha(6) = 1.000_dp
2145
2146!~~~> gamma_i = \sum_j  gamma_{i,j}
2147    ros_gamma(1) = 0.2500000000000000_dp
2148    ros_gamma(2) =- 0.1043000000000000_dp
2149    ros_gamma(3) = 0.1035000000000000_dp
2150    ros_gamma(4) =- 0.3620000000000023e-01_dp
2151    ros_gamma(5) = 0.0_dp
2152    ros_gamma(6) = 0.0_dp
2153
2154!~~~> the coefficient matrices a and c are strictly lower triangular.
2155!   The lower triangular (subdiagonal) elements are stored in row-wise order:
2156!   A(2,1) = ros_A(1),A(3,1) =ros_A(2),A(3,2) =ros_A(3),etc.
2157!   The general mapping formula is:  A(i,j) = ros_A( (i-1)*(i-2)/2 + j)
2158!                  C(i,j) = ros_C( (i-1)*(i-2)/2 + j)
2159
2160    ros_a(1) = 0.1544000000000000e+01_dp
2161    ros_a(2) = 0.9466785280815826_dp
2162    ros_a(3) = 0.2557011698983284_dp
2163    ros_a(4) = 0.3314825187068521e+01_dp
2164    ros_a(5) = 0.2896124015972201e+01_dp
2165    ros_a(6) = 0.9986419139977817_dp
2166    ros_a(7) = 0.1221224509226641e+01_dp
2167    ros_a(8) = 0.6019134481288629e+01_dp
2168    ros_a(9) = 0.1253708332932087e+02_dp
2169    ros_a(10) =- 0.6878860361058950_dp
2170    ros_a(11) = ros_a(7)
2171    ros_a(12) = ros_a(8)
2172    ros_a(13) = ros_a(9)
2173    ros_a(14) = ros_a(10)
2174    ros_a(15) = 1.0_dp
2175
2176    ros_c(1) =- 0.5668800000000000e+01_dp
2177    ros_c(2) =- 0.2430093356833875e+01_dp
2178    ros_c(3) =- 0.2063599157091915_dp
2179    ros_c(4) =- 0.1073529058151375_dp
2180    ros_c(5) =- 0.9594562251023355e+01_dp
2181    ros_c(6) =- 0.2047028614809616e+02_dp
2182    ros_c(7) = 0.7496443313967647e+01_dp
2183    ros_c(8) =- 0.1024680431464352e+02_dp
2184    ros_c(9) =- 0.3399990352819905e+02_dp
2185    ros_c(10) = 0.1170890893206160e+02_dp
2186    ros_c(11) = 0.8083246795921522e+01_dp
2187    ros_c(12) =- 0.7981132988064893e+01_dp
2188    ros_c(13) =- 0.3152159432874371e+02_dp
2189    ros_c(14) = 0.1631930543123136e+02_dp
2190    ros_c(15) =- 0.6058818238834054e+01_dp
2191
2192!~~~> m_i = coefficients for new step solution
2193    ros_m(1) = ros_a(7)
2194    ros_m(2) = ros_a(8)
2195    ros_m(3) = ros_a(9)
2196    ros_m(4) = ros_a(10)
2197    ros_m(5) = 1.0_dp
2198    ros_m(6) = 1.0_dp
2199
2200!~~~> e_i  = coefficients for error estimator
2201    ros_e(1) = 0.0_dp
2202    ros_e(2) = 0.0_dp
2203    ros_e(3) = 0.0_dp
2204    ros_e(4) = 0.0_dp
2205    ros_e(5) = 0.0_dp
2206    ros_e(6) = 1.0_dp
2207
2208!~~~> does the stage i require a new FUNCTION evaluation (ros_newf(i) =true)
2209!   or does it re-use the function evaluation from stage i-1 (ros_NewF(i) =FALSE)
2210    ros_newf(1) = .true.
2211    ros_newf(2) = .true.
2212    ros_newf(3) = .true.
2213    ros_newf(4) = .true.
2214    ros_newf(5) = .true.
2215    ros_newf(6) = .true.
2216
2217!~~~> ros_elo  = estimator of local order -  the minimum between the
2218!        main and the embedded scheme orders plus 1
2219    ros_elo = 4.0_dp
2220
2221  END SUBROUTINE rodas4
2222!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
2223  SUBROUTINE rang3
2224!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
2225! STIFFLY-STABLE W METHOD OF ORDER 3,WITH 4 STAGES
2226!
2227! J. RANG and L. ANGERMANN
2228! NEW ROSENBROCK W-METHODS OF ORDER 3
2229! FOR PARTIAL DIFFERENTIAL ALGEBRAIC
2230!        EQUATIONS OF INDEX 1                                             
2231! BIT Numerical Mathematics (2005) 45: 761-787
2232!  DOI: 10.1007/s10543-005-0035-y
2233! Table 4.1-4.2
2234!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
2235
2236
2237    rosmethod = rg3
2238!~~~> name of the method
2239    ros_Name = 'RANG-3'
2240!~~~> number of stages
2241    ros_s = 4
2242
2243    ros_a(1) = 5.09052051067020d+00;
2244    ros_a(2) = 5.09052051067020d+00;
2245    ros_a(3) = 0.0d0;
2246    ros_a(4) = 4.97628111010787d+00;
2247    ros_a(5) = 2.77268164715849d-02;
2248    ros_a(6) = 2.29428036027904d-01;
2249
2250    ros_c(1) = - 1.16790812312283d+01;
2251    ros_c(2) = - 1.64057326467367d+01;
2252    ros_c(3) = - 2.77268164715850d-01;
2253    ros_c(4) = - 8.38103960500476d+00;
2254    ros_c(5) = - 8.48328409199343d-01;
2255    ros_c(6) =  2.87009860433106d-01;
2256
2257    ros_m(1) =  5.22582761233094d+00;
2258    ros_m(2) = - 5.56971148154165d-01;
2259    ros_m(3) =  3.57979469353645d-01;
2260    ros_m(4) =  1.72337398521064d+00;
2261
2262    ros_e(1) = - 5.16845212784040d+00;
2263    ros_e(2) = - 1.26351942603842d+00;
2264    ros_e(3) = - 1.11022302462516d-16;
2265    ros_e(4) =  2.22044604925031d-16;
2266
2267    ros_alpha(1) = 0.0d00;
2268    ros_alpha(2) = 2.21878746765329d+00;
2269    ros_alpha(3) = 2.21878746765329d+00;
2270    ros_alpha(4) = 1.55392337535788d+00;
2271
2272    ros_gamma(1) =  4.35866521508459d-01;
2273    ros_gamma(2) = - 1.78292094614483d+00;
2274    ros_gamma(3) = - 2.46541900496934d+00;
2275    ros_gamma(4) = - 8.05529997906370d-01;
2276
2277
2278!~~~> does the stage i require a new FUNCTION evaluation (ros_newf(i) =true)
2279!   or does it re-use the function evaluation from stage i-1 (ros_NewF(i) =FALSE)
2280    ros_newf(1) = .true.
2281    ros_newf(2) = .true.
2282    ros_newf(3) = .true.
2283    ros_newf(4) = .true.
2284
2285!~~~> ros_elo  = estimator of local order -  the minimum between the
2286!        main and the embedded scheme orders plus 1
2287    ros_elo = 3.0_dp
2288
2289  END SUBROUTINE rang3
2290!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
2291
2292!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
2293!   End of the set of internal Rosenbrock subroutines
2294!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
2295END SUBROUTINE rosenbrock
2296 
2297SUBROUTINE funtemplate( t,y,ydot)
2298!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
2299!  Template for the ODE function call.
2300!  Updates the rate coefficients (and possibly the fixed species) at each call
2301!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
2302!~~~> input variables
2303   REAL(kind=dp):: t,y(nvar)
2304!~~~> output variables
2305   REAL(kind=dp):: ydot(nvar)
2306!~~~> local variables
2307   REAL(kind=dp):: told
2308
2309   told = time
2310   time = t
2311   CALL fun( y,fix,rconst,ydot)
2312   time = told
2313
2314END SUBROUTINE funtemplate
2315 
2316SUBROUTINE jactemplate( t,y,jcb)
2317!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
2318!  Template for the ODE Jacobian call.
2319!  Updates the rate coefficients (and possibly the fixed species) at each call
2320!~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
2321!~~~> input variables
2322    REAL(kind=dp):: t,y(nvar)
2323!~~~> output variables
2324#ifdef full_algebra   
2325    REAL(kind=dp):: jv(lu_nonzero),jcb(nvar,nvar)
2326#else
2327    REAL(kind=dp):: jcb(lu_nonzero)
2328#endif   
2329!~~~> local variables
2330    REAL(kind=dp):: told
2331#ifdef full_algebra   
2332    INTEGER :: i,j
2333#endif   
2334
2335    told = time
2336    time = t
2337#ifdef full_algebra   
2338    CALL jac_sp(y,fix,rconst,jv)
2339    DO j=1,nvar
2340      DO i=1,nvar
2341         jcb(i,j) = 0.0_dp
2342      ENDDO
2343    ENDDO
2344    DO i=1,lu_nonzero
2345       jcb(lu_irow(i),lu_icol(i)) = jv(i)
2346    ENDDO
2347#else
2348    CALL jac_sp( y,fix,rconst,jcb)
2349#endif   
2350    time = told
2351
2352END SUBROUTINE jactemplate
2353 
2354SUBROUTINE chem_gasphase_integrate (time_step_len,conc,tempk,photo,ierrf,xnacc,xnrej,istatus,l_debug,pe) 
2355                                                                   
2356  IMPLICIT NONE                                                     
2357                                                                   
2358  REAL(dp), INTENT(IN)                    :: time_step_len           
2359  REAL(dp), DIMENSION(:,:), INTENT(INOUT) :: conc                   
2360  REAL(dp), DIMENSION(:,:), INTENT(INOUT) :: photo                   
2361  REAL(dp), DIMENSION(:), INTENT(IN)      :: tempk                   
2362  INTEGER, INTENT(OUT), OPTIONAL          :: ierrf(:)               
2363  INTEGER, INTENT(OUT), OPTIONAL          :: xnacc(:)               
2364  INTEGER, INTENT(OUT), OPTIONAL          :: xnrej(:)               
2365  INTEGER, INTENT(INOUT), OPTIONAL        :: istatus(:)             
2366  INTEGER, INTENT(IN), OPTIONAL           :: pe                     
2367  LOGICAL, INTENT(IN), OPTIONAL           :: l_debug                 
2368                                                                   
2369  INTEGER                                 :: k   ! loop variable     
2370  REAL(dp)                                :: dt                     
2371  INTEGER, DIMENSION(20)                  :: istatus_u               
2372  INTEGER                                 :: ierr_u                 
2373                                                                   
2374                                                                   
2375  if (present (istatus)) istatus = 0                             
2376                                                                   
2377  DO k=1,vl_glo,vl_dim                                             
2378    is = k                                                         
2379    ie = min(k+vl_dim-1,vl_glo)                                     
2380    vl = ie-is+1                                                   
2381                                                                   
2382    c(:) = conc(is,:)                                             
2383                                                                   
2384    temp = tempk(is)                                             
2385                                                                   
2386    phot(:) = photo(is,:)                                             
2387                                                                   
2388    CALL update_rconst                                             
2389                                                                   
2390    dt = time_step_len                                             
2391                                                                   
2392    ! integrate from t=0 to t=dt                                   
2393    CALL integrate(0._dp, dt,icntrl,rcntrl,istatus_u = istatus_u,ierr_u=ierr_u)
2394                                                                   
2395                                                                   
2396    IF (PRESENT(l_debug) .AND. PRESENT(pe)) THEN                       
2397       IF (l_debug) CALL error_output(conc(is,:),ierr_u,pe)           
2398    ENDIF                                                             
2399    conc(is,:) = c(:)                                                 
2400                                                                   
2401    ! Return Diagnostic Information                                 
2402                                                                   
2403    if(PRESENT(ierrf))    ierrf(is) = ierr_u                     
2404    if(PRESENT(xnacc))    xnacc(is) = istatus_u(4)               
2405    if(PRESENT(xnrej))    xnrej(is) = istatus_u(5)               
2406                                                                   
2407    if (PRESENT (istatus)) then                                   
2408      istatus(1:8) = istatus(1:8) + istatus_u(1:8)                 
2409    ENDIF                                                         
2410                                                                   
2411  END DO                                                           
2412 
2413                                                                   
2414! Deallocate input arrays                                           
2415                                                                   
2416  if (ALLOCATED(temp))   DEALLOCATE(temp)   
2417                                                                   
2418  data_loaded = .false.                                             
2419                                                                   
2420  RETURN                                                           
2421END SUBROUTINE chem_gasphase_integrate                                       
2422 
2423  SUBROUTINE fill_temp(status,array) 
2424 
2425    INTEGER, INTENT(OUT)               :: status 
2426    REAL(dp), INTENT(IN), DIMENSION(:) :: array
2427 
2428    status = 0
2429    IF (.not. ALLOCATED(temp)) & 
2430       ALLOCATE(temp(size(array))) 
2431 
2432    IF (data_loaded .AND. (vl_glo /= size(array,1))) THEN
2433       status = 1 
2434       RETURN
2435    END IF
2436 
2437    vl_glo = size(array,1) 
2438    temp = array
2439    data_loaded = .TRUE. 
2440 
2441    RETURN
2442 
2443  END   SUBROUTINE fill_temp
2444
2445END MODULE chem_gasphase_mod
2446 
Note: See TracBrowser for help on using the repository browser.