79 PUBLIC multiphysics_finiteelementjacobianevaluate,multiphysics_finiteelementresidualevaluate
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
94 SUBROUTINE multiphysics_equationssetspecificationset(equationsSet,specification,err,error,*)
98 INTEGER(INTG),
INTENT(IN) :: specification(:)
99 INTEGER(INTG),
INTENT(OUT) :: err
104 enters(
"MultiPhysics_EquationsSetSpecificationSet",err,error,*999)
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.", &
115 SELECT CASE(specification(2))
119 CALL flagerror(
"Not implemented.",err,error,*999)
121 CALL flagerror(
"Not implemented.",err,error,*999)
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)
132 CALL flagerror(
"Equations set is not associated",err,error,*999)
135 exits(
"MultiPhysics_EquationsSetSpecificationSet")
137 999
errors(
"MultiPhysics_EquationsSetSpecificationSet",err,error)
138 exits(
"MultiPhysics_EquationsSetSpecificationSet")
141 END SUBROUTINE multiphysics_equationssetspecificationset
148 SUBROUTINE multi_physics_finite_element_calculate(EQUATIONS_SET,ELEMENT_NUMBER,ERR,ERROR,*)
152 INTEGER(INTG),
INTENT(IN) :: ELEMENT_NUMBER
153 INTEGER(INTG),
INTENT(OUT) :: ERR
158 enters(
"MULTI_PHYSICS_FINITE_ELEMENT_CALCULATE",err,error,*999)
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)
167 SELECT CASE(equations_set%SPECIFICATION(2))
171 CALL flagerror(
"Not implemented.",err,error,*999)
173 CALL flagerror(
"Not implemented.",err,error,*999)
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)
184 CALL flagerror(
"Equations set is not associated",err,error,*999)
187 exits(
"MULTI_PHYSICS_FINITE_ELEMENT_CALCULATE")
189 999 errorsexits(
"MULTI_PHYSICS_FINITE_ELEMENT_CALCULATE",err,error)
191 END SUBROUTINE multi_physics_finite_element_calculate
198 SUBROUTINE multiphysics_finiteelementjacobianevaluate(EQUATIONS_SET,ELEMENT_NUMBER,ERR,ERROR,*)
202 INTEGER(INTG),
INTENT(IN) :: ELEMENT_NUMBER
203 INTEGER(INTG),
INTENT(OUT) :: ERR
208 enters(
"MultiPhysics_FiniteElementJacobianEvaluate",err,error,*999)
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)
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)
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)
234 CALL flagerror(
"Equations set is not associated",err,error,*999)
237 exits(
"MultiPhysics_FiniteElementJacobianEvaluate")
239 999 errorsexits(
"MultiPhysics_FiniteElementJacobianEvaluate",err,error)
242 END SUBROUTINE multiphysics_finiteelementjacobianevaluate
249 SUBROUTINE multiphysics_finiteelementresidualevaluate(EQUATIONS_SET,ELEMENT_NUMBER,ERR,ERROR,*)
253 INTEGER(INTG),
INTENT(IN) :: ELEMENT_NUMBER
254 INTEGER(INTG),
INTENT(OUT) :: ERR
259 enters(
"MultiPhysics_FiniteElementResidualEvaluate",err,error,*999)
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)
268 SELECT CASE(equations_set%SPECIFICATION(2))
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)
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)
286 CALL flagerror(
"Equations set is not associated",err,error,*999)
289 exits(
"MultiPhysics_FiniteElementResidualEvaluate")
291 999 errorsexits(
"MultiPhysics_FiniteElementResidualEvaluate",err,error)
294 END SUBROUTINE multiphysics_finiteelementresidualevaluate
301 SUBROUTINE multi_physics_equations_set_setup(EQUATIONS_SET,EQUATIONS_SET_SETUP,ERR,ERROR,*)
306 INTEGER(INTG),
INTENT(OUT) :: ERR
311 enters(
"MULTI_PHYSICS_EQUATIONS_SET_SETUP",err,error,*999)
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)
320 SELECT CASE(equations_set%SPECIFICATION(2))
324 CALL flagerror(
"Not implemented.",err,error,*999)
326 CALL flagerror(
"Not implemented.",err,error,*999)
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)
337 CALL flagerror(
"Equations set is not associated.",err,error,*999)
340 exits(
"MULTI_PHYSICS_EQUATIONS_SET_SETUP")
342 999 errorsexits(
"MULTI_PHYSICS_EQUATIONS_SET_SETUP",err,error)
344 END SUBROUTINE multi_physics_equations_set_setup
352 SUBROUTINE multiphysics_equationssetsolnmethodset(EQUATIONS_SET,SOLUTION_METHOD,ERR,ERROR,*)
356 INTEGER(INTG),
INTENT(IN) :: SOLUTION_METHOD
357 INTEGER(INTG),
INTENT(OUT) :: ERR
362 enters(
"MultiPhysics_EquationsSetSolnMethodSet",err,error,*999)
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)
371 SELECT CASE(equations_set%SPECIFICATION(2))
375 CALL flagerror(
"Not implemented.",err,error,*999)
377 CALL flagerror(
"Not implemented.",err,error,*999)
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)
388 CALL flagerror(
"Equations set is not associated.",err,error,*999)
391 exits(
"MultiPhysics_EquationsSetSolnMethodSet")
393 999
errors(
"MultiPhysics_EquationsSetSolnMethodSet",err,error)
394 exits(
"MultiPhysics_EquationsSetSolnMethodSet")
397 END SUBROUTINE multiphysics_equationssetsolnmethodset
404 SUBROUTINE multiphysics_problemspecificationset(problem,problemSpecification,err,error,*)
408 INTEGER(INTG),
INTENT(IN) :: problemSpecification(:)
409 INTEGER(INTG),
INTENT(OUT) :: err
413 INTEGER(INTG) :: problemType
415 enters(
"MultiPhysics_ProblemSpecificationSet",err,error,*999)
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)
421 problemtype=problemspecification(2)
422 SELECT CASE(problemtype)
430 CALL flagerror(
"Not implemented.",err,error,*999)
438 CALL multicompartmenttransport_problemspecificationset(problem,problemspecification,err,error,*999)
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)
445 CALL flagerror(
"Problem is not associated.",err,error,*999)
448 exits(
"MultiPhysics_ProblemSpecificationSet")
450 999
errors(
"MultiPhysics_ProblemSpecificationSet",err,error)
451 exits(
"MultiPhysics_ProblemSpecificationSet")
454 END SUBROUTINE multiphysics_problemspecificationset
461 SUBROUTINE multi_physics_problem_setup(PROBLEM,PROBLEM_SETUP,ERR,ERROR,*)
466 INTEGER(INTG),
INTENT(OUT) :: ERR
471 enters(
"MULTI_PHYSICS_PROBLEM_SETUP",err,error,*999)
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)
479 SELECT CASE(problem%SPECIFICATION(2))
487 CALL flagerror(
"Not implemented.",err,error,*999)
496 CALL multi_compartment_transport_problem_setup(problem,problem_setup,err,error,*999)
499 &
" is not valid for a multi physics problem class." 500 CALL flagerror(local_error,err,error,*999)
503 CALL flagerror(
"Problem is not associated.",err,error,*999)
506 exits(
"MULTI_PHYSICS_PROBLEM_SETUP")
508 999 errorsexits(
"MULTI_PHYSICS_PROBLEM_SETUP",err,error)
510 END SUBROUTINE multi_physics_problem_setup
517 SUBROUTINE multi_physics_post_solve(CONTROL_LOOP,SOLVER,ERR,ERROR,*)
522 INTEGER(INTG),
INTENT(OUT) :: ERR
527 enters(
"MULTI_PHYSICS_POST_SOLVE",err,error,*999)
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)
535 SELECT CASE(control_loop%PROBLEM%SPECIFICATION(2))
543 CALL flagerror(
"Not implemented.",err,error,*999)
551 CALL multi_compartment_transport_post_solve(control_loop,solver,err,error,*999)
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)
558 CALL flagerror(
"Problem is not associated.",err,error,*999)
561 exits(
"MULTI_PHYSICS_POST_SOLVE")
563 999 errorsexits(
"MULTI_PHYSICS_POST_SOLVE",err,error)
565 END SUBROUTINE multi_physics_post_solve
572 SUBROUTINE multi_physics_pre_solve(CONTROL_LOOP,SOLVER,ERR,ERROR,*)
577 INTEGER(INTG),
INTENT(OUT) :: ERR
582 enters(
"MULTI_PHYSICS_PRE_SOLVE",err,error,*999)
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)
590 SELECT CASE(control_loop%PROBLEM%SPECIFICATION(2))
598 CALL flagerror(
"Not implemented.",err,error,*999)
606 CALL multi_compartment_transport_pre_solve(control_loop,solver,err,error,*999)
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)
613 CALL flagerror(
"Problem is not associated.",err,error,*999)
616 exits(
"MULTI_PHYSICS_PRE_SOLVE")
618 999 errorsexits(
"MULTI_PHYSICS_PRE_SOLVE",err,error)
620 END SUBROUTINE multi_physics_pre_solve
627 SUBROUTINE multi_physics_control_loop_pre_loop(CONTROL_LOOP,ERR,ERROR,*)
631 INTEGER(INTG),
INTENT(OUT) :: ERR
636 enters(
"MULTI_PHYSICS_CONTROL_LOOP_PRE_LOOP",err,error,*999)
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)
644 SELECT CASE(control_loop%PROBLEM%SPECIFICATION(2))
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)
667 CALL flagerror(
"Problem is not associated.",err,error,*999)
670 exits(
"MULTI_PHYSICS_CONTROL_LOOP_PRE_LOOP")
672 999 errorsexits(
"MULTI_PHYSICS_CONTROL_LOOP_PRE_LOOP",err,error)
674 END SUBROUTINE multi_physics_control_loop_pre_loop
681 SUBROUTINE multi_physics_control_loop_post_loop(CONTROL_LOOP,ERR,ERROR,*)
685 INTEGER(INTG),
INTENT(OUT) :: ERR
690 enters(
"MULTI_PHYSICS_CONTROL_LOOP_POST_LOOP",err,error,*999)
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)
698 SELECT CASE(control_loop%PROBLEM%SPECIFICATION(2))
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)
721 CALL flagerror(
"Problem is not associated.",err,error,*999)
724 exits(
"MULTI_PHYSICS_CONTROL_LOOP_POST_LOOP")
726 999 errorsexits(
"MULTI_PHYSICS_CONTROL_LOOP_POST_LOOP",err,error)
728 END SUBROUTINE multi_physics_control_loop_post_loop
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.
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.
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.
This module handles all routines pertaining to finite elasticity coupled with Darcy.
This module contains all string manipulation and transformation routines.
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.
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.
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.
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.
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.
subroutine, public elasticity_darcy_problem_setup(PROBLEM, PROBLEM_SETUP, ERR, ERROR,)
Sets up the finite elasticity Darcy equations problem.