OpenCMISS-Iron Internal API Documentation
bioelectric_routines.f90
Go to the documentation of this file.
1 
43 
46 
47  USE base_routines
51  USE kinds
54  USE strings
55  USE types
56 
57 #include "macros.h"
58 
59  IMPLICIT NONE
60 
61  PRIVATE
62 
63  !Module parameters
64 
65  !Module types
66 
67  !Module variables
68 
69  !Interfaces
70 
72 
74 
76 
78 
80 
82 
84 
86 
87 CONTAINS
88 
89  !
90  !================================================================================================================================
91  !
92 
94  SUBROUTINE bioelectric_control_loop_post_loop(CONTROL_LOOP,ERR,ERROR,*)
95 
96  !Argument variables
97  TYPE(control_loop_type), POINTER :: CONTROL_LOOP
98  INTEGER(INTG), INTENT(OUT) :: ERR
99  TYPE(varying_string), INTENT(OUT) :: ERROR
100  !Local Variables
101  TYPE(problem_type), POINTER :: PROBLEM
102  TYPE(varying_string) :: LOCAL_ERROR
103 
104  enters("BIOELECTRIC_CONTROL_LOOP_POST_LOOP",err,error,*999)
105 
106  IF(ASSOCIATED(control_loop)) THEN
107  problem=>control_loop%PROBLEM
108  IF(ASSOCIATED(problem)) THEN
109  SELECT CASE(control_loop%LOOP_TYPE)
111  IF(.NOT.ALLOCATED(control_loop%PROBLEM%SPECIFICATION)) THEN
112  CALL flagerror("Problem specification is not allocated.",err,error,*999)
113  ELSE IF(SIZE(control_loop%PROBLEM%SPECIFICATION,1)<2) THEN
114  CALL flagerror("Problem specification must have at least two entries for a bioelectric problem.",err,error,*999)
115  END IF
116  SELECT CASE(problem%SPECIFICATION(2))
118  CALL biodomain_control_loop_post_loop(control_loop,err,error,*999)
120  CALL monodomain_control_loop_post_loop(control_loop,err,error,*999)
121  CASE DEFAULT
122  local_error="Problem type "//trim(number_to_vstring(problem%SPECIFICATION(2),"*",err,error))// &
123  & " is not valid for a bioelectric problem class."
124  CALL flagerror(local_error,err,error,*999)
125  END SELECT
126  CASE DEFAULT
127  !do nothing
128  END SELECT
129  ELSE
130  CALL flagerror("Control loop problem is not associated.",err,error,*999)
131  ENDIF
132  ELSE
133  CALL flagerror("Control loop is not associated.",err,error,*999)
134  ENDIF
135 
136  exits("BIOELECTRIC_CONTROL_LOOP_POST_LOOP")
137  RETURN
138 999 errorsexits("BIOELECTRIC_CONTROL_LOOP_POST_LOOP",err,error)
139  RETURN 1
140 
142 
143  !
144  !================================================================================================================================
145  !
146 
148  SUBROUTINE bioelectric_equationssetspecificationset(equationsSet,specification,err,error,*)
150  !Argument variables
151  TYPE(equations_set_type), POINTER :: equationsSet
152  INTEGER(INTG), INTENT(IN) :: specification(:)
153  INTEGER(INTG), INTENT(OUT) :: err
154  TYPE(varying_string), INTENT(OUT) :: error
155  !Local Variables
156  TYPE(varying_string) :: localError
157 
158  enters("Bioelectric_EquationsSetSpecificationSet",err,error,*999)
159 
160  IF(ASSOCIATED(equationsset)) THEN
161  IF(SIZE(specification,1)<2) THEN
162  CALL flagerror("Equations set specification must have at least two entries for a bioelectric equations set.", &
163  & err,error,*999)
164  END IF
165  SELECT CASE(specification(2))
167  CALL biodomain_equationssetspecificationset(equationsset,specification,err,error,*999)
169  CALL biodomain_equationssetspecificationset(equationsset,specification,err,error,*999)
170  CASE DEFAULT
171  localerror="The second equations set specification of "//trim(numbertovstring(specification(2),"*",err,error))// &
172  & " is not valid for a bioelectric equations set."
173  CALL flagerror(localerror,err,error,*999)
174  END SELECT
175  ELSE
176  CALL flagerror("Equations set is not associated.",err,error,*999)
177  END IF
178 
179  exits("Bioelectric_EquationsSetSpecificationSet")
180  RETURN
181 999 errors("Bioelectric_EquationsSetSpecificationSet",err,error)
182  exits("Bioelectric_EquationsSetSpecificationSet")
183  RETURN 1
184 
186 
187  !
188  !================================================================================================================================
189  !
190 
192  SUBROUTINE bioelectric_finite_element_calculate(EQUATIONS_SET,ELEMENT_NUMBER,ERR,ERROR,*)
194  !Argument variables
195  TYPE(equations_set_type), POINTER :: EQUATIONS_SET
196  INTEGER(INTG), INTENT(IN) :: ELEMENT_NUMBER
197  INTEGER(INTG), INTENT(OUT) :: ERR
198  TYPE(varying_string), INTENT(OUT) :: ERROR
199  !Local Variables
200  TYPE(varying_string) :: LOCAL_ERROR
201 
202  enters("BIOELECTRIC_FINITE_ELEMENT_CALCULATE",err,error,*999)
203 
204  IF(ASSOCIATED(equations_set)) THEN
205  IF(.NOT.ALLOCATED(equations_set%SPECIFICATION)) THEN
206  CALL flagerror("Equations set specification is not allocated.",err,error,*999)
207  ELSE IF(SIZE(equations_set%SPECIFICATION,1)<2) THEN
208  CALL flagerror("Equations set specification must have at least two entries for a bioelectric type equations set.", &
209  & err,error,*999)
210  END IF
211  SELECT CASE(equations_set%SPECIFICATION(2))
213  CALL biodomain_equation_finite_element_calculate(equations_set,element_number,err,error,*999)
215  CALL biodomain_equation_finite_element_calculate(equations_set,element_number,err,error,*999)
216  CASE DEFAULT
217  local_error="Equations set type "//trim(number_to_vstring(equations_set%SPECIFICATION(2),"*",err,error))// &
218  & " is not valid for a bioelectric equation set class."
219  CALL flagerror(local_error,err,error,*999)
220  END SELECT
221  ELSE
222  CALL flagerror("Equations set is not associated",err,error,*999)
223  ENDIF
224 
225  exits("BIOELECTRIC_FINITE_ELEMENT_CALCULATE")
226  RETURN
227 999 errorsexits("BIOELECTRIC_FINITE_ELEMENT_CALCULATE",err,error)
228  RETURN 1
230 
231  !
232  !================================================================================================================================
233  !
234 
236  SUBROUTINE bioelectric_equations_set_setup(EQUATIONS_SET,EQUATIONS_SET_SETUP,ERR,ERROR,*)
238  !Argument variables
239  TYPE(equations_set_type), POINTER :: EQUATIONS_SET
240  TYPE(equations_set_setup_type), INTENT(INOUT) :: EQUATIONS_SET_SETUP
241  INTEGER(INTG), INTENT(OUT) :: ERR
242  TYPE(varying_string), INTENT(OUT) :: ERROR
243  !Local Variables
244  TYPE(varying_string) :: LOCAL_ERROR
245 
246  enters("BIOELECTRIC_EQUATIONS_SET_SETUP",err,error,*999)
247 
248  IF(ASSOCIATED(equations_set)) THEN
249  IF(.NOT.ALLOCATED(equations_set%SPECIFICATION)) THEN
250  CALL flagerror("Equations set specification is not allocated.",err,error,*999)
251  ELSE IF(SIZE(equations_set%SPECIFICATION,1)<2) THEN
252  CALL flagerror("Equations set specification must have at least two entries for a bioelectric type equations set.", &
253  & err,error,*999)
254  END IF
255  SELECT CASE(equations_set%SPECIFICATION(2))
257  CALL biodomain_equationssetsetup(equations_set,equations_set_setup,err,error,*999)
259  CALL biodomain_equationssetsetup(equations_set,equations_set_setup,err,error,*999)
260  CASE DEFAULT
261  local_error="Equation set type "//trim(number_to_vstring(equations_set%SPECIFICATION(2),"*",err,error))// &
262  & " is not valid for a bioelectric equation set class."
263  CALL flagerror(local_error,err,error,*999)
264  END SELECT
265  ELSE
266  CALL flagerror("Equations set is not associated.",err,error,*999)
267  ENDIF
268 
269  exits("BIOELECTRIC_EQUATIONS_SET_SETUP")
270  RETURN
271 999 errorsexits("BIOELECTRIC_EQUATIONS_SET_SETUP",err,error)
272  RETURN 1
273  END SUBROUTINE bioelectric_equations_set_setup
274 
275  !
276  !================================================================================================================================
277  !
278 
280  SUBROUTINE bioelectric_equationssetsolutionmethodset(EQUATIONS_SET,SOLUTION_METHOD,ERR,ERROR,*)
282  !Argument variables
283  TYPE(equations_set_type), POINTER :: EQUATIONS_SET
284  INTEGER(INTG), INTENT(IN) :: SOLUTION_METHOD
285  INTEGER(INTG), INTENT(OUT) :: ERR
286  TYPE(varying_string), INTENT(OUT) :: ERROR
287  !Local Variables
288  TYPE(varying_string) :: LOCAL_ERROR
289 
290  enters("Bioelectric_EquationsSetSolutionMethodSet",err,error,*999)
291 
292  IF(ASSOCIATED(equations_set)) THEN
293  IF(.NOT.ALLOCATED(equations_set%SPECIFICATION)) THEN
294  CALL flagerror("Equations set specification is not allocated.",err,error,*999)
295  ELSE IF(SIZE(equations_set%SPECIFICATION,1)<2) THEN
296  CALL flagerror("Equations set specification must have at least two entries for a bioelectric type equations set.", &
297  & err,error,*999)
298  END IF
299  SELECT CASE(equations_set%SPECIFICATION(2))
301  CALL biodomain_equationssetsolutionmethodset(equations_set,solution_method,err,error,*999)
303  CALL biodomain_equationssetsolutionmethodset(equations_set,solution_method,err,error,*999)
304  CASE DEFAULT
305  local_error="Equations set equation type of "//trim(number_to_vstring(equations_set%SPECIFICATION(2),"*",err,error))// &
306  & " is not valid for a bioelectric equations set class."
307  CALL flagerror(local_error,err,error,*999)
308  END SELECT
309  ELSE
310  CALL flagerror("Equations set is not associated.",err,error,*999)
311  ENDIF
312 
313  exits("Bioelectric_EquationsSetSolutionMethodSet")
314  RETURN
315 999 errorsexits("Bioelectric_EquationsSetSolutionMethodSet",err,error)
316  RETURN 1
317 
319 
320  !
321  !================================================================================================================================
322  !
323 
325  SUBROUTINE bioelectric_pre_solve(SOLVER,ERR,ERROR,*)
327  !Argument variables
328  TYPE(solver_type), POINTER :: SOLVER
329  INTEGER(INTG), INTENT(OUT) :: ERR
330  TYPE(varying_string), INTENT(OUT) :: ERROR
331  !Local Variables
332  TYPE(control_loop_type), POINTER :: CONTROL_LOOP
333  TYPE(problem_type), POINTER :: PROBLEM
334  TYPE(solvers_type), POINTER :: SOLVERS
335  TYPE(varying_string) :: LOCAL_ERROR
336 
337  enters("BIOELECTRIC_PRE_SOLVE",err,error,*999)
338 
339  IF(ASSOCIATED(solver)) THEN
340  solvers=>solver%SOLVERS
341  IF(ASSOCIATED(solvers)) THEN
342  control_loop=>solvers%CONTROL_LOOP
343  IF(ASSOCIATED(control_loop)) THEN
344  problem=>control_loop%PROBLEM
345  IF(ASSOCIATED(problem)) THEN
346  IF(.NOT.ALLOCATED(problem%SPECIFICATION)) THEN
347  CALL flagerror("Problem specification is not allocated.",err,error,*999)
348  ELSE IF(SIZE(problem%SPECIFICATION,1)<2) THEN
349  CALL flagerror("Problem specification must have at least two entries for a bioelectric problem.",err,error,*999)
350  END IF
351  SELECT CASE(problem%SPECIFICATION(2))
353  CALL biodomain_pre_solve(solver,err,error,*999)
355  CALL monodomain_pre_solve(control_loop,solver,err,error,*999)
356  CASE DEFAULT
357  local_error="Problem type "//trim(number_to_vstring(problem%SPECIFICATION(2),"*",err,error))// &
358  & " is not valid for a bioelectrics problem class."
359  CALL flagerror(local_error,err,error,*999)
360  END SELECT
361  ELSE
362  CALL flagerror("Control loop problem is not associated.",err,error,*999)
363  ENDIF
364  ELSE
365  CALL flagerror("Solvers control loop is not associated.",err,error,*999)
366  ENDIF
367  ELSE
368  CALL flagerror("Solver solvers is not associated.",err,error,*999)
369  ENDIF
370  ELSE
371  CALL flagerror("Solver is not associated.",err,error,*999)
372  ENDIF
373 
374  exits("BIOELECTRIC_PRE_SOLVE")
375  RETURN
376 999 errorsexits("BIOELECTRIC_PRE_SOLVE",err,error)
377  RETURN 1
378  END SUBROUTINE bioelectric_pre_solve
379 
380  !
381  !================================================================================================================================
382  !
383 
385  SUBROUTINE bioelectric_post_solve(SOLVER,ERR,ERROR,*)
387  !Argument variables
388  TYPE(solver_type), POINTER :: SOLVER
389  INTEGER(INTG), INTENT(OUT) :: ERR
390  TYPE(varying_string), INTENT(OUT) :: ERROR
391  !Local Variables
392  TYPE(control_loop_type), POINTER :: CONTROL_LOOP
393  TYPE(problem_type), POINTER :: PROBLEM
394  TYPE(solvers_type), POINTER :: SOLVERS
395  TYPE(varying_string) :: LOCAL_ERROR
396 
397  enters("BIOELECTRIC_POST_SOLVE",err,error,*999)
398 
399  IF(ASSOCIATED(solver)) THEN
400  solvers=>solver%SOLVERS
401  IF(ASSOCIATED(solvers)) THEN
402  control_loop=>solvers%CONTROL_LOOP
403  IF(ASSOCIATED(control_loop)) THEN
404  problem=>control_loop%PROBLEM
405  IF(ASSOCIATED(problem)) THEN
406  IF(.NOT.ALLOCATED(problem%SPECIFICATION)) THEN
407  CALL flagerror("Problem specification is not allocated.",err,error,*999)
408  ELSE IF(SIZE(problem%SPECIFICATION,1)<2) THEN
409  CALL flagerror("Problem specification must have at least two entries for a bioelectric problem.",err,error,*999)
410  END IF
411  SELECT CASE(problem%SPECIFICATION(2))
413  !Do nothing???
415  CALL monodomain_post_solve(control_loop,solver,err,error,*999)
416  CASE DEFAULT
417  local_error="Problem type "//trim(number_to_vstring(problem%SPECIFICATION(2),"*",err,error))// &
418  & " is not valid for a bioelectrics problem class."
419  CALL flagerror(local_error,err,error,*999)
420  END SELECT
421  ELSE
422  CALL flagerror("Control loop problem is not associated.",err,error,*999)
423  ENDIF
424  ELSE
425  CALL flagerror("Solvers control loop is not associated.",err,error,*999)
426  ENDIF
427  ELSE
428  CALL flagerror("Solver solvers is not associated.",err,error,*999)
429  ENDIF
430  ELSE
431  CALL flagerror("Solver is not associated.",err,error,*999)
432  ENDIF
433 
434  exits("BIOELECTRIC_POST_SOLVE")
435  RETURN
436 999 errorsexits("BIOELECTRIC_POST_SOLVE",err,error)
437  RETURN 1
438 
439  END SUBROUTINE bioelectric_post_solve
440 
441  !
442  !================================================================================================================================
443  !
444 
446  SUBROUTINE bioelectric_problemspecificationset(problem,problemSpecification,err,error,*)
448  !Argument variables
449  TYPE(problem_type), POINTER :: problem
450  INTEGER(INTG), INTENT(IN) :: problemSpecification(:)
451  INTEGER(INTG), INTENT(OUT) :: err
452  TYPE(varying_string), INTENT(OUT) :: error
453  !Local Variables
454  TYPE(varying_string) :: localError
455  INTEGER(INTG) :: problemType
456 
457  enters("Bioelectric_ProblemSpecificationSet",err,error,*999)
458 
459  IF(ASSOCIATED(problem)) THEN
460  IF(SIZE(problemspecification,1)>=2) THEN
461  problemtype=problemspecification(2)
462  SELECT CASE(problemtype)
464  CALL biodomain_problemspecificationset(problem,problemspecification,err,error,*999)
466  CALL monodomain_problemspecificationset(problem,problemspecification,err,error,*999)
467  CASE DEFAULT
468  localerror="The second problem specification of "//trim(numbertovstring(problemtype,"*",err,error))// &
469  & " is not valid for a bioelectric problem."
470  CALL flagerror(localerror,err,error,*999)
471  END SELECT
472  ELSE
473  CALL flagerror("Bioelectric problem specification must have a type set.",err,error,*999)
474  END IF
475  ELSE
476  CALL flagerror("Problem is not associated.",err,error,*999)
477  END IF
478 
479  exits("Bioelectric_ProblemSpecificationSet")
480  RETURN
481 999 errors("Bioelectric_ProblemSpecificationSet",err,error)
482  exits("Bioelectric_ProblemSpecificationSet")
483  RETURN 1
484 
486 
487  !
488  !================================================================================================================================
489  !
490 
492  SUBROUTINE bioelectric_problem_setup(PROBLEM,PROBLEM_SETUP,ERR,ERROR,*)
494  !Argument variables
495  TYPE(problem_type), POINTER :: PROBLEM
496  TYPE(problem_setup_type), INTENT(INOUT) :: PROBLEM_SETUP
497  INTEGER(INTG), INTENT(OUT) :: ERR
498  TYPE(varying_string), INTENT(OUT) :: ERROR
499  !Local Variables
500  TYPE(varying_string) :: LOCAL_ERROR
501 
502  enters("BIOELECTRIC_PROBLEM_SETUP",err,error,*999)
503 
504  IF(ASSOCIATED(problem)) THEN
505  IF(.NOT.ALLOCATED(problem%SPECIFICATION)) THEN
506  CALL flagerror("Problem specification is not allocated.",err,error,*999)
507  ELSE IF(SIZE(problem%SPECIFICATION,1)<2) THEN
508  CALL flagerror("Problem specification must have at least two entries for a bioelectric problem.",err,error,*999)
509  END IF
510  SELECT CASE(problem%SPECIFICATION(2))
512  CALL biodomain_equation_problem_setup(problem,problem_setup,err,error,*999)
514  CALL biodomain_equation_problem_setup(problem,problem_setup,err,error,*999)
516  CALL monodomain_equation_problem_setup(problem,problem_setup,err,error,*999)
517  CASE DEFAULT
518  local_error="Problem type "//trim(number_to_vstring(problem%SPECIFICATION(2),"*",err,error))// &
519  & " is not valid for a bioelectric problem class."
520  CALL flagerror(local_error,err,error,*999)
521  END SELECT
522  ELSE
523  CALL flagerror("Problem is not associated.",err,error,*999)
524  ENDIF
525 
526  exits("BIOELECTRIC_PROBLEM_SETUP")
527  RETURN
528 999 errorsexits("BIOELECTRIC_PROBLEM_SETUP",err,error)
529  RETURN 1
530  END SUBROUTINE bioelectric_problem_setup
531 
532  !
533  !================================================================================================================================
534  !
535 
536 END MODULE bioelectric_routines
537 
subroutine, public enters(NAME, ERR, ERROR,)
Records the entry into the named procedure and initialises the error code.
subroutine, public bioelectric_pre_solve(SOLVER, ERR, ERROR,)
Perform pre-solve actions for the bioelectrics problem class.
integer(intg), parameter problem_control_time_loop_type
Time control loop.
This module handles all problem wide constants.
Converts a number to its equivalent varying string representation.
Definition: strings.f90:161
subroutine, public biodomain_equationssetsolutionmethodset(EQUATIONS_SET, SOLUTION_METHOD, ERR, ERROR,)
Sets/changes the solution method for a bioelectric domain equation type of an bioelectrics equations ...
Contains information on the type of solver to be used.
Definition: types.f90:2777
integer(intg), parameter problem_bioelectric_finite_elasticity_type
Contains information on an equations set.
Definition: types.f90:1941
subroutine, public bioelectric_control_loop_post_loop(CONTROL_LOOP, ERR, ERROR,)
Executes after each loop of a control loop for bioelectric problems, i.e., after each time step for a...
This module contains all string manipulation and transformation routines.
Definition: strings.f90:45
subroutine, public biodomain_equation_problem_setup(PROBLEM, PROBLEM_SETUP, ERR, ERROR,)
Sets up the bioelectric domain problem.
integer(intg), parameter problem_monodomain_equation_type
Contains information on the solvers to be used in a control loop.
Definition: types.f90:2805
integer(intg), parameter problem_bidomain_equation_type
subroutine, public biodomain_equationssetspecificationset(equationsSet, specification, err, error,)
Sets the equation specification for a bioelectric domain equation type of a bioelectric equations set...
Contains information on a control loop.
Definition: types.f90:3185
This module provides an iso_varying_string module, conformant to the API specified in ISO/IEC 1539-2:...
subroutine, public biodomain_problemspecificationset(problem, problemSpecification, err, error,)
Sets the problem specification for a bioelectric domain problem class.
integer(intg), parameter problem_monodomain_strang_splitting_equation_type
subroutine, public biodomain_equationssetsetup(EQUATIONS_SET, EQUATIONS_SET_SETUP, ERR, ERROR,)
Sets up the bioelectric domain equation type of a bioelectric equations set class.
subroutine, public exits(NAME)
Records the exit out of the named procedure.
subroutine, public bioelectric_equationssetspecificationset(equationsSet, specification, err, error,)
Sets the problem specification for a bioelectric equation set class.
This module contains all type definitions in order to avoid cyclic module references.
Definition: types.f90:70
subroutine, public bioelectric_equationssetsolutionmethodset(EQUATIONS_SET, SOLUTION_METHOD, ERR, ERROR,)
Sets/changes the solution method for a bioelectric equation set class.
subroutine, public bioelectric_problemspecificationset(problem, problemSpecification, err, error,)
Sets the problem specification for a bioelectric problem class.
This module contains all the low-level base routines e.g., all debug, control, and low-level communic...
integer(intg), parameter equations_set_monodomain_equation_type
subroutine, public bioelectric_post_solve(SOLVER, ERR, ERROR,)
Performs post solve actions for a bioelectrics problem class.
Contains information for a problem.
Definition: types.f90:3221
subroutine, public biodomain_equation_finite_element_calculate(EQUATIONS_SET, ELEMENT_NUMBER, ERR, ERROR,)
Calculates the element stiffness matrices and RHS for a bioelectric domain equation finite element eq...
subroutine, public biodomain_pre_solve(SOLVER, ERR, ERROR,)
Performs pre-solve actions for mono- and bi-domain problems.
Contains information on the setup information for an equations set.
Definition: types.f90:1866
subroutine, public bioelectric_problem_setup(PROBLEM, PROBLEM_SETUP, ERR, ERROR,)
Sets up the problem for a bioelectric problem class.
This module handles all bioelectric domain equation routines.
subroutine, public errors(NAME, ERR, ERROR)
Records the exiting error of the subroutine.
This module defines all constants shared across equations set routines.
This module handles all bioelectric class routines.
subroutine, public bioelectric_finite_element_calculate(EQUATIONS_SET, ELEMENT_NUMBER, ERR, ERROR,)
Calculates the element stiffness matries and rhs vector for the given element number for a bioelectri...
Flags an error condition.
This module handles all Monodomain equations routines.
subroutine, public bioelectric_equations_set_setup(EQUATIONS_SET, EQUATIONS_SET_SETUP, ERR, ERROR,)
Sets up the equations set for a bioelectric equations set class.
integer(intg), parameter equations_set_bidomain_equation_type
This module contains all kind definitions.
Definition: kinds.f90:45
subroutine, public biodomain_control_loop_post_loop(CONTROL_LOOP, ERR, ERROR,)
Runs after each control loop iteration.