source: palm/trunk/UTIL/chemistry/gasphase_preproc/mechanisms/def_passive1/chem_gasphase_mod.f90 @ 4841

Last change on this file since 4841 was 4841, checked in by forkel, 3 years ago

updated copyright statements for chem_gasphase_mod.f90. This must be done in UTIL/chemistry/gasphase_preproc/kpp4palm/templates/module_header and NOT in SOURCE/chem_gasphase_mod.f90.

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