timedisc_cashkarp.f90
Go to the documentation of this file.
1!#############################################################################
2!# #
3!# fosite - 3D hydrodynamical simulation program #
4!# module: timedisc_cashkarp.f90 #
5!# #
6!# Copyright (C) 2011-2018 #
7!# Björn Sperling <sperling@astrophysik.uni-kiel.de> #
8!# Tobias Illenseer <tillense@astrophysik.uni-kiel.de> #
9!# #
10!# This program is free software; you can redistribute it and/or modify #
11!# it under the terms of the GNU General Public License as published by #
12!# the Free Software Foundation; either version 2 of the License, or (at #
13!# your option) any later version. #
14!# #
15!# This program is distributed in the hope that it will be useful, but #
16!# WITHOUT ANY WARRANTY; without even the implied warranty of #
17!# MERCHANTABILITY OR FITNESS FOR A PARTICULAR PURPOSE, GOOD TITLE or #
18!# NON INFRINGEMENT. See the GNU General Public License for more #
19!# details. #
20!# #
21!# You should have received a copy of the GNU General Public License #
22!# along with this program; if not, write to the Free Software #
23!# Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA. #
24!# #
25!#############################################################################
26
27!----------------------------------------------------------------------------!
42!----------------------------------------------------------------------------!
51 USE common_dict
52 IMPLICIT NONE
53 !--------------------------------------------------------------------------!
54 PRIVATE
56 CONTAINS
58 PROCEDURE :: setbutchertableau
59 PROCEDURE :: finalize
60 END TYPE timedisc_cashkarp
61 !--------------------------------------------------------------------------!
62 CHARACTER(LEN=32), PARAMETER :: odesolver_name = "Cash-Karp method"
63
64 !--------------------------------------------------------------------------!
65 PUBLIC :: &
66 ! types
68 !--------------------------------------------------------------------------!
69
70CONTAINS
71
72 SUBROUTINE inittimedisc_cashkarp(this,Mesh,Physics,config,IO)
73 IMPLICIT NONE
74 !------------------------------------------------------------------------!
75 CLASS(timedisc_cashkarp), INTENT(INOUT) :: this
76 CLASS(mesh_base), INTENT(INOUT) :: Mesh
77 CLASS(physics_base), INTENT(IN) :: Physics
78 TYPE(dict_typ), POINTER :: config, IO
79 !------------------------------------------------------------------------!
80 ! set default order
81 CALL getattr(config, "order", this%order, 5)
82
83 !set number of coefficients
84 SELECT CASE(this%GetOrder())
85 CASE(5)
86 this%m = 6
87 CASE DEFAULT
88 CALL this%Error("InitTimedisc_cashkarp","time order must be 5")
89 END SELECT
90
91 CALL this%InitTimedisc(mesh,physics,config,io,cash_karp,odesolver_name)
92 END SUBROUTINE inittimedisc_cashkarp
93
95 SUBROUTINE setbutchertableau(this)
96 IMPLICIT NONE
97 !------------------------------------------------------------------------!
98 CLASS(timedisc_cashkarp) :: this
99 !------------------------------------------------------------------------!
100 SELECT CASE(this%GetOrder())
101 CASE(5)
102 this%b_high = (/ 37.0/378.0, 0.0, 250.0/621.0, 125.0/594.0, 0.0, 512.0/1771.0 /)
103 this%b_low = (/ 2825.0/27648.0, 0.0, 18575.0/48384.0, 13525.0/55296.0, &
104 277.0/14336.0, 0.25 /)
105 this%c = (/ 0.0, 0.2, 0.3, 0.6, 1.0, 7.0/8.0 /)
106 this%a = transpose(reshape((/ &
107 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, &
108 0.2, 0.0, 0.0, 0.0, 0.0, 0.0, &
109 0.075, 0.225, 0.0, 0.0, 0.0, 0.0, &
110 0.3, -0.9, 1.2, 0.0, 0.0, 0.0, &
111 -11.0/54.0 , 2.5, -70.0/27.0, 35.0/27.0, 0.0, 0.0, &
112 1631.0/55296.0, 175.0/512.0, 575.0/13824.0, &
113 44275.0/110592.0, 253.0/4096.0, 0.0/),(/this%m,this%m/)))
114 CASE DEFAULT
115 CALL this%Error("timedisc_cashkarp::SetButcherTableau","only order 5 supported")
116 END SELECT
117 END SUBROUTINE setbutchertableau
118
119 SUBROUTINE finalize(this)
120 IMPLICIT NONE
121 !-----------------------------------------------------------------------!
122 CLASS(timedisc_cashkarp) :: this
123 !-----------------------------------------------------------------------!
124 CALL this%timedisc_rkfehlberg%Finalize()
125 END SUBROUTINE
126END MODULE timedisc_cashkarp_mod
Dictionary for generic data types.
Definition: common_dict.f90:61
base module for numerical flux functions
Definition: fluxes_base.f90:39
basic mesh module
Definition: mesh_base.f90:72
Basic physics module.
generic source terms module providing functionaly common to all source terms
integer, parameter, public cash_karp
subroutines for embedded Runge-Kutta method
subroutine setbutchertableau(this)
set coefficients for Cash-Karp scheme
character(len=32), parameter odesolver_name
subroutine inittimedisc_cashkarp(this, Mesh, Physics, config, IO)
subroutines for Runge-Kutta Fehlberg method
mesh data structure
Definition: mesh_base.f90:122