OpenCMISS-Iron Internal API Documentation
multi_physics_routines.f90
Go to the documentation of this file.
1 
44 
47 
48  USE base_routines
53  USE fsi_routines
57  USE kinds
61  USE strings
62  USE types
63 
64 #include "macros.h"
65 
66 
67  IMPLICIT NONE
68 
69  PRIVATE
70 
71  !Module parameters
72 
73  !Module types
74 
75  !Module variables
76 
77  !Interfaces
78 
79  PUBLIC multiphysics_finiteelementjacobianevaluate,multiphysics_finiteelementresidualevaluate
80 
81  PUBLIC multiphysics_equationssetspecificationset,multi_physics_finite_element_calculate, &
82  & multi_physics_equations_set_setup,multiphysics_equationssetsolnmethodset, &
83  & multiphysics_problemspecificationset,multi_physics_problem_setup, &
84  & multi_physics_post_solve,multi_physics_pre_solve,multi_physics_control_loop_pre_loop, &
85  & multi_physics_control_loop_post_loop
86 
87 CONTAINS
88 
89  !
90  !================================================================================================================================
91  !
92 
94  SUBROUTINE multiphysics_equationssetspecificationset(equationsSet,specification,err,error,*)
95 
96  !Argument variables
97  TYPE(equations_set_type), POINTER :: equationsSet
98  INTEGER(INTG), INTENT(IN) :: specification(:)
99  INTEGER(INTG), INTENT(OUT) :: err
100  TYPE(varying_string), INTENT(OUT) :: error
101  !Local Variables
102  TYPE(varying_string) :: localError
103 
104  enters("MultiPhysics_EquationsSetSpecificationSet",err,error,*999)
105 
106  !Not that in general, this routine is never used as most multi-physics problems
107  !use standard equations sets and couples them, rather than having a special
108  !multi-physics problem equations set
109 
110  IF(ASSOCIATED(equationsset)) THEN
111  IF(SIZE(specification,1)<2) THEN
112  CALL flagerror("Equations set specification must have at least two entries for a multiphysics equations set.", &
113  & err,error,*999)
114  ENDIF
115  SELECT CASE(specification(2))
117  CALL finelasticityfluidpressure_equationssetspecificationset(equationsset,specification,err,error,*999)
119  CALL flagerror("Not implemented.",err,error,*999)
121  CALL flagerror("Not implemented.",err,error,*999)
123  CALL diffusiondiffusion_equationssetspecificationset(equationsset,specification,err,error,*999)
125  CALL diffusionadvectiondiffusion_equationssetspecset(equationsset,specification,err,error,*999)
126  CASE DEFAULT
127  localerror="The second equations set specification of "//trim(numbertovstring(specification(2),"*",err,error))// &
128  & " is not valid for a multi physics equations set."
129  CALL flagerror(localerror,err,error,*999)
130  END SELECT
131  ELSE
132  CALL flagerror("Equations set is not associated",err,error,*999)
133  ENDIF
134 
135  exits("MultiPhysics_EquationsSetSpecificationSet")
136  RETURN
137 999 errors("MultiPhysics_EquationsSetSpecificationSet",err,error)
138  exits("MultiPhysics_EquationsSetSpecificationSet")
139  RETURN 1
140 
141  END SUBROUTINE multiphysics_equationssetspecificationset
142 
143  !
144  !================================================================================================================================
145  !
146 
148  SUBROUTINE multi_physics_finite_element_calculate(EQUATIONS_SET,ELEMENT_NUMBER,ERR,ERROR,*)
150  !Argument variables
151  TYPE(equations_set_type), POINTER :: EQUATIONS_SET
152  INTEGER(INTG), INTENT(IN) :: ELEMENT_NUMBER
153  INTEGER(INTG), INTENT(OUT) :: ERR
154  TYPE(varying_string), INTENT(OUT) :: ERROR
155  !Local Variables
156  TYPE(varying_string) :: LOCAL_ERROR
157 
158  enters("MULTI_PHYSICS_FINITE_ELEMENT_CALCULATE",err,error,*999)
159 
160  IF(ASSOCIATED(equations_set)) THEN
161  IF(.NOT.ALLOCATED(equations_set%SPECIFICATION)) THEN
162  CALL flagerror("Equations set specification is not allocated.",err,error,*999)
163  ELSE IF(SIZE(equations_set%SPECIFICATION,1)<2) THEN
164  CALL flagerror("Equations set specification must have at least two entries for a "// &
165  & "multi-physics class equations set.",err,error,*999)
166  END IF
167  SELECT CASE(equations_set%SPECIFICATION(2))
169  CALL finelasticityfluidpressure_finiteelementcalculate(equations_set,element_number,err,error,*999)
171  CALL flagerror("Not implemented.",err,error,*999)
173  CALL flagerror("Not implemented.",err,error,*999)
175  CALL diffusiondiffusion_finiteelementcalculate(equations_set,element_number,err,error,*999)
177  CALL diffusionadvectiondiffusion_finiteelementcalculate(equations_set,element_number,err,error,*999)
178  CASE DEFAULT
179  local_error="Equations set type "//trim(number_to_vstring(equations_set%SPECIFICATION(2),"*",err,error))// &
180  & " is not valid for a multi physics equation set class."
181  CALL flagerror(local_error,err,error,*999)
182  END SELECT
183  ELSE
184  CALL flagerror("Equations set is not associated",err,error,*999)
185  ENDIF
186 
187  exits("MULTI_PHYSICS_FINITE_ELEMENT_CALCULATE")
188  RETURN
189 999 errorsexits("MULTI_PHYSICS_FINITE_ELEMENT_CALCULATE",err,error)
190  RETURN 1
191  END SUBROUTINE multi_physics_finite_element_calculate
192 
193  !
194  !================================================================================================================================
195  !
196 
198  SUBROUTINE multiphysics_finiteelementjacobianevaluate(EQUATIONS_SET,ELEMENT_NUMBER,ERR,ERROR,*)
200  !Argument variables
201  TYPE(equations_set_type), POINTER :: EQUATIONS_SET
202  INTEGER(INTG), INTENT(IN) :: ELEMENT_NUMBER
203  INTEGER(INTG), INTENT(OUT) :: ERR
204  TYPE(varying_string), INTENT(OUT) :: ERROR
205  !Local Variables
206  TYPE(varying_string) :: LOCAL_ERROR
207 
208  enters("MultiPhysics_FiniteElementJacobianEvaluate",err,error,*999)
209 
210  IF(ASSOCIATED(equations_set)) THEN
211  IF(.NOT.ALLOCATED(equations_set%SPECIFICATION)) THEN
212  CALL flagerror("Equations set specification is not allocated.",err,error,*999)
213  ELSE IF(SIZE(equations_set%SPECIFICATION,1)<2) THEN
214  CALL flagerror("Equations set specification must have at least two entries for a "// &
215  & "multi-physics class equations set.",err,error,*999)
216  END IF
217  SELECT CASE(equations_set%SPECIFICATION(2))
219  CALL flagerror("Not implemented.",err,error,*999)
221  CALL flagerror("Not implemented.",err,error,*999)
223  CALL flagerror("Not implemented.",err,error,*999)
225  CALL flagerror("Not implemented.",err,error,*999)
227  CALL flagerror("Not implemented.",err,error,*999)
228  CASE DEFAULT
229  local_error="Equations set type "//trim(number_to_vstring(equations_set%SPECIFICATION(2),"*",err,error))// &
230  & " is not valid for a multi physics equation set class."
231  CALL flagerror(local_error,err,error,*999)
232  END SELECT
233  ELSE
234  CALL flagerror("Equations set is not associated",err,error,*999)
235  ENDIF
236 
237  exits("MultiPhysics_FiniteElementJacobianEvaluate")
238  RETURN
239 999 errorsexits("MultiPhysics_FiniteElementJacobianEvaluate",err,error)
240  RETURN 1
241 
242  END SUBROUTINE multiphysics_finiteelementjacobianevaluate
243 
244  !
245  !================================================================================================================================
246  !
247 
249  SUBROUTINE multiphysics_finiteelementresidualevaluate(EQUATIONS_SET,ELEMENT_NUMBER,ERR,ERROR,*)
251  !Argument variables
252  TYPE(equations_set_type), POINTER :: EQUATIONS_SET
253  INTEGER(INTG), INTENT(IN) :: ELEMENT_NUMBER
254  INTEGER(INTG), INTENT(OUT) :: ERR
255  TYPE(varying_string), INTENT(OUT) :: ERROR
256  !Local Variables
257  TYPE(varying_string) :: LOCAL_ERROR
258 
259  enters("MultiPhysics_FiniteElementResidualEvaluate",err,error,*999)
260 
261  IF(ASSOCIATED(equations_set)) THEN
262  IF(.NOT.ALLOCATED(equations_set%SPECIFICATION)) THEN
263  CALL flagerror("Equations set specification is not allocated.",err,error,*999)
264  ELSE IF(SIZE(equations_set%SPECIFICATION,1)<2) THEN
265  CALL flagerror("Equations set specification must have at least two entries for a "// &
266  & "multi-physics class equations set.",err,error,*999)
267  END IF
268  SELECT CASE(equations_set%SPECIFICATION(2))
270 ! CALL ELASTICITY_DARCY_FINITE_ELEMENT_RESIDUAL_EVALUATE(EQUATIONS_SET,ELEMENT_NUMBER,ERR,ERROR,*999)
271  CALL flagerror("Not implemented.",err,error,*999)
273  CALL flagerror("Not implemented.",err,error,*999)
275  CALL flagerror("Not implemented.",err,error,*999)
277  CALL flagerror("Not implemented.",err,error,*999)
279  CALL flagerror("Not implemented.",err,error,*999)
280  CASE DEFAULT
281  local_error="Equations set type "//trim(number_to_vstring(equations_set%SPECIFICATION(2),"*",err,error))// &
282  & " is not valid for a multi physics equation set class."
283  CALL flagerror(local_error,err,error,*999)
284  END SELECT
285  ELSE
286  CALL flagerror("Equations set is not associated",err,error,*999)
287  ENDIF
288 
289  exits("MultiPhysics_FiniteElementResidualEvaluate")
290  RETURN
291 999 errorsexits("MultiPhysics_FiniteElementResidualEvaluate",err,error)
292  RETURN 1
293 
294  END SUBROUTINE multiphysics_finiteelementresidualevaluate
295 
296  !
297  !================================================================================================================================
298  !
299 
301  SUBROUTINE multi_physics_equations_set_setup(EQUATIONS_SET,EQUATIONS_SET_SETUP,ERR,ERROR,*)
303  !Argument variables
304  TYPE(equations_set_type), POINTER :: EQUATIONS_SET
305  TYPE(equations_set_setup_type), INTENT(INOUT) :: EQUATIONS_SET_SETUP
306  INTEGER(INTG), INTENT(OUT) :: ERR
307  TYPE(varying_string), INTENT(OUT) :: ERROR
308  !Local Variables
309  TYPE(varying_string) :: LOCAL_ERROR
310 
311  enters("MULTI_PHYSICS_EQUATIONS_SET_SETUP",err,error,*999)
312 
313  IF(ASSOCIATED(equations_set)) THEN
314  IF(.NOT.ALLOCATED(equations_set%SPECIFICATION)) THEN
315  CALL flagerror("Equations set specification is not allocated.",err,error,*999)
316  ELSE IF(SIZE(equations_set%SPECIFICATION,1)<2) THEN
317  CALL flagerror("Equations set specification must have at least two entries for a "// &
318  & "multi-physics class equations set.",err,error,*999)
319  END IF
320  SELECT CASE(equations_set%SPECIFICATION(2))
322  CALL elasticity_darcy_equations_set_setup(equations_set,equations_set_setup,err,error,*999)
324  CALL flagerror("Not implemented.",err,error,*999)
326  CALL flagerror("Not implemented.",err,error,*999)
328  CALL diffusion_diffusion_equations_set_setup(equations_set,equations_set_setup,err,error,*999)
330  CALL diffusionadvectiondiffusion_equationssetsetup(equations_set,equations_set_setup,err,error,*999)
331  CASE DEFAULT
332  local_error="Equation set type "//trim(number_to_vstring(equations_set%SPECIFICATION(2),"*",err,error))// &
333  & " is not valid for a multi physics equation set class."
334  CALL flagerror(local_error,err,error,*999)
335  END SELECT
336  ELSE
337  CALL flagerror("Equations set is not associated.",err,error,*999)
338  ENDIF
339 
340  exits("MULTI_PHYSICS_EQUATIONS_SET_SETUP")
341  RETURN
342 999 errorsexits("MULTI_PHYSICS_EQUATIONS_SET_SETUP",err,error)
343  RETURN 1
344  END SUBROUTINE multi_physics_equations_set_setup
345 
346 
347  !
348  !================================================================================================================================
349  !
350 
352  SUBROUTINE multiphysics_equationssetsolnmethodset(EQUATIONS_SET,SOLUTION_METHOD,ERR,ERROR,*)
354  !Argument variables
355  TYPE(equations_set_type), POINTER :: EQUATIONS_SET
356  INTEGER(INTG), INTENT(IN) :: SOLUTION_METHOD
357  INTEGER(INTG), INTENT(OUT) :: ERR
358  TYPE(varying_string), INTENT(OUT) :: ERROR
359  !Local Variables
360  TYPE(varying_string) :: LOCAL_ERROR
361 
362  enters("MultiPhysics_EquationsSetSolnMethodSet",err,error,*999)
363 
364  IF(ASSOCIATED(equations_set)) THEN
365  IF(.NOT.ALLOCATED(equations_set%SPECIFICATION)) THEN
366  CALL flagerror("Equations set specification is not allocated.",err,error,*999)
367  ELSE IF(SIZE(equations_set%SPECIFICATION,1)<2) THEN
368  CALL flagerror("Equations set specification must have at least two entries for a "// &
369  & "multi-physics class equations set.",err,error,*999)
370  END IF
371  SELECT CASE(equations_set%SPECIFICATION(2))
373  CALL finelasticityfluidpressure_equationssetsolnmethodset(equations_set,solution_method,err,error,*999)
375  CALL flagerror("Not implemented.",err,error,*999)
377  CALL flagerror("Not implemented.",err,error,*999)
379  CALL diffusiondiffusion_equationssetsolutionmethodset(equations_set,solution_method,err,error,*999)
381  CALL diffusionadvectiondiffusion_equationssetsolnmethodset(equations_set,solution_method,err,error,*999)
382  CASE DEFAULT
383  local_error="Equations set equation type of "//trim(number_to_vstring(equations_set%SPECIFICATION(2),"*",err,error))// &
384  & " is not valid for a multi physics equations set class."
385  CALL flagerror(local_error,err,error,*999)
386  END SELECT
387  ELSE
388  CALL flagerror("Equations set is not associated.",err,error,*999)
389  ENDIF
390 
391  exits("MultiPhysics_EquationsSetSolnMethodSet")
392  RETURN
393 999 errors("MultiPhysics_EquationsSetSolnMethodSet",err,error)
394  exits("MultiPhysics_EquationsSetSolnMethodSet")
395  RETURN 1
396 
397  END SUBROUTINE multiphysics_equationssetsolnmethodset
398 
399  !
400  !================================================================================================================================
401  !
402 
404  SUBROUTINE multiphysics_problemspecificationset(problem,problemSpecification,err,error,*)
406  !Argument variables
407  TYPE(problem_type), POINTER :: problem
408  INTEGER(INTG), INTENT(IN) :: problemSpecification(:)
409  INTEGER(INTG), INTENT(OUT) :: err
410  TYPE(varying_string), INTENT(OUT) :: error
411  !Local Variables
412  TYPE(varying_string) :: localError
413  INTEGER(INTG) :: problemType
414 
415  enters("MultiPhysics_ProblemSpecificationSet",err,error,*999)
416 
417  IF(ASSOCIATED(problem)) THEN
418  IF(SIZE(problemspecification,1)<2) THEN
419  CALL flagerror("Multi physics problem specification requires at least two entries.",err,error,*999)
420  ENDIF
421  problemtype=problemspecification(2)
422  SELECT CASE(problemtype)
424  CALL finiteelasticitydarcy_problemspecificationset(problem,problemspecification,err,error,*999)
426  CALL finelasticityfluidpressure_problemspecificationset(problem,problemspecification,err,error,*999)
428  CALL bioelectricfiniteelasticity_problemspecificationset(problem,problemspecification,err,error,*999)
430  CALL flagerror("Not implemented.",err,error,*999)
432  CALL fsi_problemspecificationset(problem,problemspecification,err,error,*999)
434  CALL diffusiondiffusion_problemspecificationset(problem,problemspecification,err,error,*999)
436  CALL diffusionadvectiondiffusion_problemspecificationset(problem,problemspecification,err,error,*999)
438  CALL multicompartmenttransport_problemspecificationset(problem,problemspecification,err,error,*999)
439  CASE DEFAULT
440  localerror="The second problem specification of "//trim(numbertovstring(problemtype,"*",err,error))// &
441  & " is not valid for a multi physics problem."
442  CALL flagerror(localerror,err,error,*999)
443  END SELECT
444  ELSE
445  CALL flagerror("Problem is not associated.",err,error,*999)
446  ENDIF
447 
448  exits("MultiPhysics_ProblemSpecificationSet")
449  RETURN
450 999 errors("MultiPhysics_ProblemSpecificationSet",err,error)
451  exits("MultiPhysics_ProblemSpecificationSet")
452  RETURN 1
453 
454  END SUBROUTINE multiphysics_problemspecificationset
455 
456  !
457  !================================================================================================================================
458  !
459 
461  SUBROUTINE multi_physics_problem_setup(PROBLEM,PROBLEM_SETUP,ERR,ERROR,*)
463  !Argument variables
464  TYPE(problem_type), POINTER :: PROBLEM
465  TYPE(problem_setup_type), INTENT(INOUT) :: PROBLEM_SETUP
466  INTEGER(INTG), INTENT(OUT) :: ERR
467  TYPE(varying_string), INTENT(OUT) :: ERROR
468  !Local Variables
469  TYPE(varying_string) :: LOCAL_ERROR
470 
471  enters("MULTI_PHYSICS_PROBLEM_SETUP",err,error,*999)
472 
473  IF(ASSOCIATED(problem)) THEN
474  IF(.NOT.ALLOCATED(problem%SPECIFICATION)) THEN
475  CALL flagerror("Problem specification is not allocated.",err,error,*999)
476  ELSE IF(SIZE(problem%SPECIFICATION,1)<2) THEN
477  CALL flagerror("Problem specification must have at least two entries for a multi physics problem.",err,error,*999)
478  END IF
479  SELECT CASE(problem%SPECIFICATION(2))
481  CALL elasticity_darcy_problem_setup(problem,problem_setup,err,error,*999)
483  CALL elasticity_fluid_pressure_problem_setup(problem,problem_setup,err,error,*999)
485  CALL bioelectric_finite_elasticity_problem_setup(problem,problem_setup,err,error,*999)
487  CALL flagerror("Not implemented.",err,error,*999)
489  !CALL FlagError("Not implemented.",ERR,ERROR,*999)
490  CALL fsi_problem_setup(problem,problem_setup,err,error,*999)
492  CALL diffusion_diffusion_problem_setup(problem,problem_setup,err,error,*999)
494  CALL diffusion_advection_diffusion_problem_setup(problem,problem_setup,err,error,*999)
496  CALL multi_compartment_transport_problem_setup(problem,problem_setup,err,error,*999)
497  CASE DEFAULT
498  local_error="Problem type "//trim(number_to_vstring(problem%SPECIFICATION(2),"*",err,error))// &
499  & " is not valid for a multi physics problem class."
500  CALL flagerror(local_error,err,error,*999)
501  END SELECT
502  ELSE
503  CALL flagerror("Problem is not associated.",err,error,*999)
504  ENDIF
505 
506  exits("MULTI_PHYSICS_PROBLEM_SETUP")
507  RETURN
508 999 errorsexits("MULTI_PHYSICS_PROBLEM_SETUP",err,error)
509  RETURN 1
510  END SUBROUTINE multi_physics_problem_setup
511 
512  !
513  !================================================================================================================================
514  !
515 
517  SUBROUTINE multi_physics_post_solve(CONTROL_LOOP,SOLVER,ERR,ERROR,*)
519  !Argument variables
520  TYPE(control_loop_type), POINTER :: CONTROL_LOOP
521  TYPE(solver_type), POINTER :: SOLVER
522  INTEGER(INTG), INTENT(OUT) :: ERR
523  TYPE(varying_string), INTENT(OUT) :: ERROR
524  !Local Variables
525  TYPE(varying_string) :: LOCAL_ERROR
526 
527  enters("MULTI_PHYSICS_POST_SOLVE",err,error,*999)
528 
529  IF(ASSOCIATED(control_loop%PROBLEM)) THEN
530  IF(.NOT.ALLOCATED(control_loop%PROBLEM%SPECIFICATION)) THEN
531  CALL flagerror("Problem specification is not allocated.",err,error,*999)
532  ELSE IF(SIZE(control_loop%PROBLEM%SPECIFICATION,1)<2) THEN
533  CALL flagerror("Problem specification must have at least two entries for a multi physics problem.",err,error,*999)
534  END IF
535  SELECT CASE(control_loop%PROBLEM%SPECIFICATION(2))
537  CALL elasticity_darcy_post_solve(control_loop,solver,err,error,*999)
539  CALL elasticity_fluid_pressure_post_solve(control_loop,solver,err,error,*999)
541  CALL bioelectric_finite_elasticity_post_solve(control_loop,solver,err,error,*999)
543  CALL flagerror("Not implemented.",err,error,*999)
545  CALL fsi_post_solve(control_loop,solver,err,error,*999)
547  CALL diffusion_diffusion_post_solve(control_loop,solver,err,error,*999)
549  !CALL DIFFUSION_ADVECTION_DIFFUSION_POST_SOLVE(CONTROL_LOOP,SOLVER,ERR,ERROR,*999)
551  CALL multi_compartment_transport_post_solve(control_loop,solver,err,error,*999)
552  CASE DEFAULT
553  local_error="Problem type "//trim(number_to_vstring(control_loop%PROBLEM%SPECIFICATION(2),"*",err,error))// &
554  & " is not valid for a multi physics problem class."
555  CALL flagerror(local_error,err,error,*999)
556  END SELECT
557  ELSE
558  CALL flagerror("Problem is not associated.",err,error,*999)
559  ENDIF
560 
561  exits("MULTI_PHYSICS_POST_SOLVE")
562  RETURN
563 999 errorsexits("MULTI_PHYSICS_POST_SOLVE",err,error)
564  RETURN 1
565  END SUBROUTINE multi_physics_post_solve
566 
567  !
568  !================================================================================================================================
569  !
570 
572  SUBROUTINE multi_physics_pre_solve(CONTROL_LOOP,SOLVER,ERR,ERROR,*)
574  !Argument variables
575  TYPE(control_loop_type), POINTER :: CONTROL_LOOP
576  TYPE(solver_type), POINTER :: SOLVER
577  INTEGER(INTG), INTENT(OUT) :: ERR
578  TYPE(varying_string), INTENT(OUT) :: ERROR
579  !Local Variables
580  TYPE(varying_string) :: LOCAL_ERROR
581 
582  enters("MULTI_PHYSICS_PRE_SOLVE",err,error,*999)
583 
584  IF(ASSOCIATED(control_loop%PROBLEM)) THEN
585  IF(.NOT.ALLOCATED(control_loop%PROBLEM%SPECIFICATION)) THEN
586  CALL flagerror("Problem specification is not allocated.",err,error,*999)
587  ELSE IF(SIZE(control_loop%PROBLEM%SPECIFICATION,1)<2) THEN
588  CALL flagerror("Problem specification must have at least two entries for a multi physics problem.",err,error,*999)
589  END IF
590  SELECT CASE(control_loop%PROBLEM%SPECIFICATION(2))
592  CALL elasticity_darcy_pre_solve(control_loop,solver,err,error,*999)
594  CALL elasticity_fluid_pressure_pre_solve(control_loop,solver,err,error,*999)
596  CALL bioelectric_finite_elasticity_pre_solve(control_loop,solver,err,error,*999)
598  CALL flagerror("Not implemented.",err,error,*999)
600  CALL fsi_pre_solve(control_loop,solver,err,error,*999)
602  CALL diffusion_diffusion_pre_solve(control_loop,solver,err,error,*999)
604  CALL diffusion_advection_diffusion_pre_solve(control_loop,solver,err,error,*999)
606  CALL multi_compartment_transport_pre_solve(control_loop,solver,err,error,*999)
607  CASE DEFAULT
608  local_error="Problem type "//trim(number_to_vstring(control_loop%PROBLEM%SPECIFICATION(2),"*",err,error))// &
609  & " is not valid for a multi physics problem class."
610  CALL flagerror(local_error,err,error,*999)
611  END SELECT
612  ELSE
613  CALL flagerror("Problem is not associated.",err,error,*999)
614  ENDIF
615 
616  exits("MULTI_PHYSICS_PRE_SOLVE")
617  RETURN
618 999 errorsexits("MULTI_PHYSICS_PRE_SOLVE",err,error)
619  RETURN 1
620  END SUBROUTINE multi_physics_pre_solve
621 
622  !
623  !================================================================================================================================
624  !
625 
627  SUBROUTINE multi_physics_control_loop_pre_loop(CONTROL_LOOP,ERR,ERROR,*)
629  !Argument variables
630  TYPE(control_loop_type), POINTER :: CONTROL_LOOP
631  INTEGER(INTG), INTENT(OUT) :: ERR
632  TYPE(varying_string), INTENT(OUT) :: ERROR
633  !Local Variables
634  TYPE(varying_string) :: LOCAL_ERROR
635 
636  enters("MULTI_PHYSICS_CONTROL_LOOP_PRE_LOOP",err,error,*999)
637 
638  IF(ASSOCIATED(control_loop%PROBLEM)) THEN
639  IF(.NOT.ALLOCATED(control_loop%PROBLEM%SPECIFICATION)) THEN
640  CALL flagerror("Problem specification is not allocated.",err,error,*999)
641  ELSE IF(SIZE(control_loop%PROBLEM%SPECIFICATION,1)<2) THEN
642  CALL flagerror("Problem specification must have at least two entries for a multi physics problem.",err,error,*999)
643  END IF
644  SELECT CASE(control_loop%PROBLEM%SPECIFICATION(2))
646  CALL elasticity_darcy_control_loop_pre_loop(control_loop,err,error,*999)
648  !do nothing
650  CALL bioelectricfiniteelasticity_controllooppreloop(control_loop,err,error,*999)
652  !do nothing
654  !TODO Store previous data?
656  !do nothing
658  !do nothing
660  !do nothing
661  CASE DEFAULT
662  local_error="Problem type "//trim(number_to_vstring(control_loop%PROBLEM%SPECIFICATION(2),"*",err,error))// &
663  & " is not valid for a multi physics problem class."
664  CALL flagerror(local_error,err,error,*999)
665  END SELECT
666  ELSE
667  CALL flagerror("Problem is not associated.",err,error,*999)
668  ENDIF
669 
670  exits("MULTI_PHYSICS_CONTROL_LOOP_PRE_LOOP")
671  RETURN
672 999 errorsexits("MULTI_PHYSICS_CONTROL_LOOP_PRE_LOOP",err,error)
673  RETURN 1
674  END SUBROUTINE multi_physics_control_loop_pre_loop
675 
676  !
677  !================================================================================================================================
678  !
679 
681  SUBROUTINE multi_physics_control_loop_post_loop(CONTROL_LOOP,ERR,ERROR,*)
683  !Argument variables
684  TYPE(control_loop_type), POINTER :: CONTROL_LOOP
685  INTEGER(INTG), INTENT(OUT) :: ERR
686  TYPE(varying_string), INTENT(OUT) :: ERROR
687  !Local Variables
688  TYPE(varying_string) :: LOCAL_ERROR
689 
690  enters("MULTI_PHYSICS_CONTROL_LOOP_POST_LOOP",err,error,*999)
691 
692  IF(ASSOCIATED(control_loop%PROBLEM)) THEN
693  IF(.NOT.ALLOCATED(control_loop%PROBLEM%SPECIFICATION)) THEN
694  CALL flagerror("Problem specification is not allocated.",err,error,*999)
695  ELSE IF(SIZE(control_loop%PROBLEM%SPECIFICATION,1)<2) THEN
696  CALL flagerror("Problem specification must have at least two entries for a multi physics problem.",err,error,*999)
697  END IF
698  SELECT CASE(control_loop%PROBLEM%SPECIFICATION(2))
700  CALL elasticity_darcy_control_loop_post_loop(control_loop,err,error,*999)
702  !do nothing
704  CALL bioelectricfiniteelasticity_controllooppostloop(control_loop,err,error,*999)
706  !do nothing
708  CALL fsi_control_loop_post_loop(control_loop,err,error,*999)
710  !do nothing
712  !do nothing
714  !do nothing
715  CASE DEFAULT
716  local_error="Problem type "//trim(number_to_vstring(control_loop%PROBLEM%SPECIFICATION(2),"*",err,error))// &
717  & " is not valid for a multi physics problem class."
718  CALL flagerror(local_error,err,error,*999)
719  END SELECT
720  ELSE
721  CALL flagerror("Problem is not associated.",err,error,*999)
722  ENDIF
723 
724  exits("MULTI_PHYSICS_CONTROL_LOOP_POST_LOOP")
725  RETURN
726 999 errorsexits("MULTI_PHYSICS_CONTROL_LOOP_POST_LOOP",err,error)
727  RETURN 1
728  END SUBROUTINE multi_physics_control_loop_post_loop
729 
730  !
731  !================================================================================================================================
732  !
733 
734 END MODULE multi_physics_routines
735 
subroutine, public enters(NAME, ERR, ERROR,)
Records the entry into the named procedure and initialises the error code.
subroutine, public bioelectric_finite_elasticity_post_solve(CONTROL_LOOP, SOLVER, ERR, ERROR,)
Sets up the bioelectrics finite elasticity problem post solve.
integer(intg), parameter problem_diffusion_diffusion_type
integer(intg), parameter equations_set_diffusion_diffusion_type
subroutine, public elasticity_darcy_control_loop_post_loop(CONTROL_LOOP, ERR, ERROR,)
Runs after each control loop iteration.
integer(intg), parameter problem_diffusion_advection_diffusion_type
integer(intg), parameter equations_set_diffusion_advection_diffusion_type
This module handles all problem wide constants.
This module handles all multi physics class routines.
subroutine, public diffusionadvectiondiffusion_equationssetspecset(equationsSet, specification, err, error,)
Sets the equation specification for a coupled diffusion & advection-diffusion equation type of a mult...
Converts a number to its equivalent varying string representation.
Definition: strings.f90:161
subroutine, public diffusion_diffusion_pre_solve(CONTROL_LOOP, SOLVER, ERR, ERROR,)
Sets up the diffusion-diffusion problem pre-solve.
subroutine, public elasticity_darcy_post_solve(CONTROL_LOOP, SOLVER, ERR, ERROR,)
Sets up the finite elasticity Darcy problem post solve.
subroutine, public elasticity_darcy_control_loop_pre_loop(CONTROL_LOOP, ERR, ERROR,)
Runs before each control loop iteration.
Contains information on the type of solver to be used.
Definition: types.f90:2777
subroutine, public diffusionadvectiondiffusion_equationssetsetup(EQUATIONS_SET, EQUATIONS_SET_SETUP, ERR, ERROR,)
Sets up the diffusion & advection-diffusion coupled equation.
integer(intg), parameter problem_bioelectric_finite_elasticity_type
subroutine, public bioelectricfiniteelasticity_controllooppreloop(CONTROL_LOOP, ERR, ERROR,)
Sets up the bioelectrics finite elasticity problem pre-control loop.
Contains information on an equations set.
Definition: types.f90:1941
This module handles all routines pertaining to finite elasticity coupled with Darcy.
This module contains all string manipulation and transformation routines.
Definition: strings.f90:45
subroutine, public fsi_problemspecificationset(problem, problemSpecification, err, error,)
Sets the problem specification for a finite elasticity Navier-Stokes equation type.
subroutine, public fsi_control_loop_post_loop(ControlLoop, Err, Error,)
Runs after each control loop iteration. Updates interface and fluid geometric fields and exports fiel...
subroutine, public diffusion_advection_diffusion_problem_setup(PROBLEM, PROBLEM_SETUP, ERR, ERROR,)
Sets up the coupled diffusion-diffusion equations problem.
subroutine, public diffusiondiffusion_equationssetspecificationset(equationsSet, specification, err, error,)
Sets the equation specification for a coupled diffusion-diffusion equation type of a multi physics eq...
TThis module handles all routines pertaining to diffusion coupled to diffusion.
subroutine, public fsi_post_solve(ControlLoop, Solver, Err, Error,)
Sets up the finite elasticity navier stokes problem post solve.
integer(intg), parameter problem_finite_elasticity_stokes_type
subroutine, public elasticity_darcy_pre_solve(CONTROL_LOOP, SOLVER, ERR, ERROR,)
Sets up the finite elasticity Darcy problem pre-solve.
subroutine, public elasticity_fluid_pressure_post_solve(CONTROL_LOOP, SOLVER, ERR, ERROR,)
Sets up the finite elasticity fluid pressure problem post solve.
subroutine, public bioelectricfiniteelasticity_controllooppostloop(CONTROL_LOOP, ERR, ERROR,)
Sets up the bioelectrics finite elasticity problem post-control loop.
Contains information on a control loop.
Definition: types.f90:3185
subroutine, public fsi_problem_setup(PROBLEM, PROBLEM_SETUP, Err, Error,)
Sets up the finite elasticity navier stokes equations problem.
This module provides an iso_varying_string module, conformant to the API specified in ISO/IEC 1539-2:...
This module handles all routines pertaining to diffusion coupled to diffusion.
subroutine, public elasticity_darcy_equations_set_setup(EQUATIONS_SET, EQUATIONS_SET_SETUP, ERR, ERROR,)
Sets up the finite elasticity Darcy equation.
subroutine, public finelasticityfluidpressure_finiteelementcalculate(EQUATIONS_SET, ELEMENT_NUMBER, ERR, ERROR,)
Calculates the element stiffness matrices and RHS for a finite elasticity fluid pressure equation fin...
subroutine, public finelasticityfluidpressure_equationssetsolnmethodset(EQUATIONS_SET, SOLUTION_METHOD, ERR, ERROR,)
Sets/changes the solution method for a finite elasticity fluid pressure equation type of a multi phys...
subroutine, public bioelectricfiniteelasticity_problemspecificationset(problem, problemSpecification, err, error,)
Sets the problem specification for a bioelectric finite elasticity problem type . ...
subroutine, public diffusiondiffusion_equationssetsolutionmethodset(EQUATIONS_SET, SOLUTION_METHOD, ERR, ERROR,)
Sets/changes the solution method for a diffusion-diffusion equation type of a multi physics equations...
subroutine, public fsi_pre_solve(ControlLoop, Solver, Err, Error,)
Sets up the finite elasticity navier stokes problem pre-solve.
integer(intg), parameter equations_set_finite_elasticity_darcy_type
subroutine, public diffusion_diffusion_post_solve(CONTROL_LOOP, SOLVER, ERR, ERROR,)
Sets up the diffusion-diffusion problem post solve.
integer(intg), parameter problem_finite_elasticity_darcy_type
subroutine, public exits(NAME)
Records the exit out of the named procedure.
This module contains all type definitions in order to avoid cyclic module references.
Definition: types.f90:70
subroutine, public diffusionadvectiondiffusion_problemspecificationset(problem, problemSpecification, err, error,)
Sets the problem specification for a coupled diffusion & advection-diffusion problem.
integer(intg), parameter problem_multi_compartment_transport_type
Problem type for the multi-compartment coupled transport, comprising either/or/both advection-diffusi...
subroutine, public finelasticityfluidpressure_problemspecificationset(problem, problemSpecification, err, error,)
Sets the problem specification for a finite elasticity fluid pressure equation type.
This module contains all the low-level base routines e.g., all debug, control, and low-level communic...
subroutine, public diffusion_diffusion_equations_set_setup(EQUATIONS_SET, EQUATIONS_SET_SETUP, ERR, ERROR,)
Sets up the diffusion-diffusion coupled equation.
TThis module handles all routines pertaining to (advection-)diffusion coupled to (advection-)diffusio...
subroutine, public diffusionadvectiondiffusion_equationssetsolnmethodset(EQUATIONS_SET, SOLUTION_METHOD, ERR, ERROR,)
Sets/changes the solution method for a coupled diffusion & advection-diffusion equation type of a mul...
integer(intg), parameter equations_set_finite_elasticity_stokes_type
subroutine, public diffusion_diffusion_problem_setup(PROBLEM, PROBLEM_SETUP, ERR, ERROR,)
Sets up the coupled diffusion-diffusion equations problem.
subroutine, public diffusiondiffusion_finiteelementcalculate(EQUATIONS_SET, ELEMENT_NUMBER, ERR, ERROR,)
Calculates the element stiffness matrices and RHS for a coupled diffusion-diffusion equation finite e...
subroutine, public finiteelasticitydarcy_problemspecificationset(problem, problemSpecification, err, error,)
Sets the problem specification for a finite elasticity Darcy equation type.
integer(intg), parameter equations_set_finite_elasticity_navier_stokes_type
Contains information for a problem.
Definition: types.f90:3221
subroutine, public bioelectric_finite_elasticity_problem_setup(PROBLEM, PROBLEM_SETUP, ERR, ERROR,)
Sets up the bioelectric finite elasticity problem.
This module handles all routines pertaining to finite elasticity coupled with fluid pressure for poro...
This module handles all routines pertaining to bioelectrics coupled with finite elasticity.
This module handles all Navier-Stokes fluid routines.
subroutine, public diffusiondiffusion_problemspecificationset(problem, problemSpecification, err, error,)
Sets the problem specification for a coupled diffusion-diffusion equation type.
subroutine, public finelasticityfluidpressure_equationssetspecificationset(equationsSet, specification, err, error,)
Sets the equation specification for a finite elasticity fluid pressure equation type of a fluid mecha...
integer(intg), parameter problem_finite_elasticity_navier_stokes_type
subroutine, public diffusion_advection_diffusion_pre_solve(CONTROL_LOOP, SOLVER, ERR, ERROR,)
Sets up the diffusion-diffusion problem pre-solve.
Contains information on the setup information for an equations set.
Definition: types.f90:1866
subroutine, public elasticity_fluid_pressure_pre_solve(CONTROL_LOOP, SOLVER, ERR, ERROR,)
Sets up the finite elasticity fluid pressure problem pre-solve.
subroutine, public errors(NAME, ERR, ERROR)
Records the exiting error of the subroutine.
This module defines all constants shared across equations set routines.
integer(intg), parameter problem_finite_elasticity_fluid_pressure_type
subroutine, public diffusionadvectiondiffusion_finiteelementcalculate(EQUATIONS_SET, ELEMENT_NUMBER, ERR, ERROR,)
Calculates the element stiffness matrices and RHS for a coupled diffusion & advection-diffusion equat...
subroutine, public elasticity_fluid_pressure_problem_setup(PROBLEM, PROBLEM_SETUP, ERR, ERROR,)
Sets up the finite elasticity fluid pressure equations problem.
subroutine, public bioelectric_finite_elasticity_pre_solve(CONTROL_LOOP, SOLVER, ERR, ERROR,)
Sets up the bioelectrics finite elasticity problem pre-solve.
Flags an error condition.
This module handles all routines pertaining to finite elasticity coupled with navier stokes for fsi p...
This module contains all kind definitions.
Definition: kinds.f90:45
subroutine, public elasticity_darcy_problem_setup(PROBLEM, PROBLEM_SETUP, ERR, ERROR,)
Sets up the finite elasticity Darcy equations problem.