Choral
ode_cardio_0d.f90
Go to the documentation of this file.
1 
30 
32 
34  use choral
35 
36  implicit none
37 
38  !! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
39  !! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
40  !!
41  !! VARAIBLE DEFINITION : BEGIN
42  !!
43  !!
44 
45  !! verbosity level
46  integer, parameter :: verb = 3
47 
48  !! MODEL EESCIPTION
49  !!
50  !! IONIC MODEL DEF.
51  !! im_type = type of ionic model
52  !! im = definition of the ionic model
53  !!
54  integer, parameter :: im_type = ionic_tnnp
55  type(ionicmodel) :: im
56  !!
57  !! STIMULATION DEF.
58  !! stim_base = base function for the stimulation
59  !! stim_time = mid-time for the stimulation
60  !! stim_time_radius = mid stimulation duration
61  !!
62  procedure(rtor), pointer :: stim_base => f_c3
63  real(RP) , parameter :: stim_time = 20._rp
64  real(RP) , parameter :: stim_time_radius = 1._rp
65  !!
66  !! OUTPUT DEF.
67  !! co = definition of the output
68  type(ode_output) :: co
69 
70 
71  !! TIME DISCRETISATION
72  !!
73  !! t0 = initial time
74  !! T = final time
75  !! dt = time step
76  !! slv_type = solver type (multistep, onestep)
77  !! NL_meth = method for the non-ilinear system
78  !!
79  real(RP), parameter :: t0 = 0.0_rp
80  real(RP), parameter :: T = 400.0_rp
81  !! first choice of method (stable)
82  ! integer , parameter :: slv_type = ODE_SLV_MS
83  ! integer , parameter :: NL_meth = ODE_RL3
84  ! real(RP), parameter :: dt = .05_RP
85  !! second choice of method (less stable)
86  integer , parameter :: slv_type = ode_slv_1s
87  integer , parameter :: NL_meth = ode_modif_erk2_b
88  real(RP), parameter :: dt = 0.4_rp
89  !!
90  !! pb = definition of the ode problem
91  !! slv = definition of the ode solver
92  !! sol = data structure for the ode solution
93  !!
94  type(ode_solution) :: sol
95  type(ode_problem) :: pb
96  type(ode_solver) :: slv
97 
98 
99  !!
100  !! VARAIBLE DEFINITION : END
101  !!
102  !! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
103  !! !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
104 
105 
106  call choral_init(verb=verb)
107  write(*,*) "ode_cardio_0D : start"
108 
109 
110  !!!!!!!!!!!!!!!!!!!!!!! MODEL DEFINITION
111  !!
112  write(*,*) ""
113  write(*,*) "================================== MODEL DEFINITION"
114  !!
115  !! ionic model
116  !!
117  im = ionicmodel(im_type)
118  if (verb>0) call print(im)
119 
120 
121  !! !!!!!!!!!!!!!!!!!!!!! TIME DISCRETISATION
122  !!
123  write(*,*) ""
124  write(*,*) "================================== TIME DISCRETISATION"
125  !!
126  !! ODE PROBLEM DEF.
127  !!
128  pb = ode_problem(ode_pb_nl, &
129  & dim=0, ab=ode_reaction, n=im%N, na=im%Na)
130  if (verb>0) call print(pb)
131  !!
132  !! ODE SOLVER DEF.
133  !!
134  slv = ode_solver(pb, slv_type, nl_meth=nl_meth, verb=1)
135  if (verb>0) call print(slv)
136  !!
137  !! ODE SOLUTION DEF.
138  !!
139  sol = ode_solution(slv, pb)
140  if (verb>0) call print(sol)
141  !!
142  !! ODE OUTPUT DEF.
143  !!
144  co = ode_output(t0, t, im%N)
145  call set(co, verb=1)
146  call set(co, vxn_period = 1._rp, vxn_plot=.true.)
147  if (verb>0) call print(co)
148 
149 
150  !!!!!!!!!!!!!!!!!!!!!!! NUMERICAL RESOLUTION
151  !!
152  write(*,*) ""
153  write(*,*) "================================== NUMERICAL RESOLUTION"
154  !!
155  !! finalise the output definition
156  call assemble(co, dt)
157  !!
158  !! initial condition
159  call initialcond(sol, pb, slv, t0, im%y0)
160  !!
161  !! numerical resolution
162  call solve(sol, slv, pb, t0, t, dt, output=co)
163 
164  write(*,*) "ode_cardio_0D : end"
165 
166 contains
167 
168 
169  !! !!!!!!!!!!!!!!!!!!!!! SOURCE TERM
170  !!
171  function stim(x, t) result(res)
172  real(RP) :: res
173  real(RP), dimension(3), intent(in) :: x
174  real(RP) , intent(in) :: t
175 
176  real(RP) :: t2
177 
178  t2 = abs( t - stim_time)/stim_time_radius
179 
180  res = stim_base(t2) * im%Ist
181 
182  end function stim
183 
184 
185 
186  !! !!!!!!!!!!!!!!!!!!!!! REACTION TERMS
187  !!
188  subroutine ode_reaction(a, b, x, t, y, N, Na)
189  real(RP), dimension(Na), intent(out) :: a
190  real(RP), dimension(N) , intent(out) :: b
191  real(RP), dimension(3) , intent(in) :: x
192  real(RP) , intent(in) :: t
193  real(RP), dimension(N) , intent(in) :: y
194  integer , intent(in) :: N, Na
195 
196  real(RP) :: I_app
197 
198  i_app = stim(x, t)
199  call im%AB(a, b, i_app, y, n, na)
200 
201  end subroutine ode_reaction
202 
203 end program ode_cardio_0d
subroutine, public choral_init(verb)
Initialisation for the CHORAL library
Definition: choral.F90:166
TOP-LEVEL MODULE FOR THE LIBRARY CHORAL
Definition: choral.F90:27
real(rp) function stim(x, t)
integer, parameter ode_modif_erk2_b
modified ERK2_B
subroutine ode_reaction(a, b, x, t, y, N, Na)
CHORAL CONSTANTS
program ode_cardio_0d
RESOLUTION OF the MEMBRANE EQUATION in cardiac-electrophysiology
integer, parameter na
integer, parameter ode_pb_nl
Non-Linear ODE system: , .
integer, parameter ode_slv_1s
onestep
integer, parameter ionic_tnnp