110     INTEGER(INTG), 
INTENT(IN) :: SOLUTION_METHOD
   111     INTEGER(INTG), 
INTENT(OUT) :: ERR
   116     enters(
"FiniteElasticityDarcy_EquationsSetSolutionMethodSet",err,error,*999)
   118     IF(
ASSOCIATED(equations_set)) 
THEN   119       IF(.NOT.
ALLOCATED(equations_set%SPECIFICATION)) 
THEN   120         CALL flagerror(
"Equations set specification is not allocated.",err,error,*999)
   121       ELSE IF(
SIZE(equations_set%SPECIFICATION,1)/=3) 
THEN   122         CALL flagerror(
"Equations set specification must have three entries for a "// &
   123           & 
"finite elasticity-Darcy type equations set.",err,error,*999)
   125       SELECT CASE(equations_set%SPECIFICATION(3))
   127         SELECT CASE(solution_method)
   131           CALL flagerror(
"Not implemented.",err,error,*999)
   133           CALL flagerror(
"Not implemented.",err,error,*999)
   135           CALL flagerror(
"Not implemented.",err,error,*999)
   137           CALL flagerror(
"Not implemented.",err,error,*999)
   139           CALL flagerror(
"Not implemented.",err,error,*999)
   141           local_error=
"The specified solution method of "//
trim(
number_to_vstring(solution_method,
"*",err,error))//
" is invalid."   142           CALL flagerror(local_error,err,error,*999)
   145         local_error=
"Equations set subtype of "//
trim(
number_to_vstring(equations_set%SPECIFICATION(3),
"*",err,error))// &
   146           & 
" is not valid for a finite elasticity Darcy  equation type of a multi physics equations set class."   147         CALL flagerror(local_error,err,error,*999)
   150       CALL flagerror(
"Equations set is not associated.",err,error,*999)
   153     exits(
"FiniteElasticityDarcy_EquationsSetSolutionMethodSet")
   155 999 
errors(
"FiniteElasticityDarcy_EquationsSetSolutionMethodSet",err,error)
   156     exits(
"FiniteElasticityDarcy_EquationsSetSolutionMethodSet")
   171     INTEGER(INTG), 
INTENT(OUT) :: ERR
   175     enters(
"ELASTICITY_DARCY_EQUATIONS_SET_SETUP",err,error,*999)
   177     CALL flagerror(
"ELASTICITY_DARCY_EQUATIONS_SET_SETUP still needs to be implemented.",err,error,*999)
   188     exits(
"ELASTICITY_DARCY_EQUATIONS_SET_SETUP")
   190 999 errorsexits(
"ELASTICITY_DARCY_EQUATIONS_SET_SETUP",err,error)
   203     INTEGER(INTG), 
INTENT(IN) :: ELEMENT_NUMBER
   204     INTEGER(INTG), 
INTENT(OUT) :: ERR
   208     enters(
"ELASTICITY_DARCY_FINITE_ELEMENT_CALCULATE",err,error,*999)
   210     CALL flagerror(
"ELASTICITY_DARCY_FINITE_ELEMENT_CALCULATE still needs to be implemented.",err,error,*999)
   221   exits(
"ELASTICITY_DARCY_FINITE_ELEMENT_CALCULATE")
   223 999 errorsexits(
"ELASTICITY_DARCY_FINITE_ELEMENT_CALCULATE",err,error)
   236     INTEGER(INTG), 
INTENT(IN) :: specification(:)
   237     INTEGER(INTG), 
INTENT(OUT) :: err
   240     enters(
"FiniteElasticityDarcy_EquationsSetSpecificationSet",err,error,*999)
   242     CALL flagerror(
"FiniteElasticityDarcy_EquationsSetSpecificationSet still needs to be implemented.",err,error,*999)
   252     exits(
"FiniteElasticityDarcy_EquationsSetSpecificationSet")
   254 999 
errors(
"FiniteElasticityDarcy_EquationsSetSpecificationSet",err,error)
   255     exits(
"FiniteElasticityDarcy_EquationsSetSpecificationSet")
   269     INTEGER(INTG), 
INTENT(IN) :: problemSpecification(:)
   270     INTEGER(INTG), 
INTENT(OUT) :: err
   274     INTEGER(INTG) :: problemSubtype
   276     enters(
"FiniteElasticityDarcy_ProblemSpecificationSet",err,error,*999)
   278     IF(
ASSOCIATED(problem)) 
THEN   279       IF(
SIZE(problemspecification,1)==3) 
THEN   280         problemsubtype=problemspecification(3)
   281         SELECT CASE(problemsubtype)
   288           localerror=
"The third problem specification of "//
trim(
numbertovstring(problemsubtype,
"*",err,error))// &
   289             & 
" is not valid for a finite elasticity Darcy type of a multi physics problem."   290           CALL flagerror(localerror,err,error,*999)
   292         IF(
ALLOCATED(problem%specification)) 
THEN   293           CALL flagerror(
"Problem specification is already allocated.",err,error,*999)
   295           ALLOCATE(problem%specification(3),stat=err)
   296           IF(err/=0) 
CALL flagerror(
"Could not allocate problem specification.",err,error,*999)
   301         CALL flagerror(
"Finite elasticity Darcy problem specification must have three entries",err,error,*999)
   304       CALL flagerror(
"Problem is not associated.",err,error,*999)
   307     exits(
"FiniteElasticityDarcy_ProblemSpecificationSet")
   309 999 
errors(
"FiniteElasticityDarcy_ProblemSpecificationSet",err,error)
   310     exits(
"FiniteElasticityDarcy_ProblemSpecificationSet")
   325     INTEGER(INTG), 
INTENT(OUT) :: ERR
   328     TYPE(
control_loop_type), 
POINTER :: CONTROL_LOOP,CONTROL_LOOP_ROOT,SOLID_SUB_LOOP,FLUID_SUB_LOOP,SUBITERATION_LOOP
   329     TYPE(
solver_type), 
POINTER :: SOLVER, SOLVER_MAT_PROPERTIES, SOLVER_SOLID
   330     TYPE(
solver_equations_type), 
POINTER :: SOLVER_EQUATIONS, SOLVER_EQUATIONS_MAT_PROPERTIES, SOLVER_EQUATIONS_SOLID
   331     TYPE(
solvers_type), 
POINTER :: SOLID_SOLVERS,FLUID_SOLVERS
   334     enters(
"ELASTICITY_DARCY_PROBLEM_SETUP",err,error,*999)
   336     NULLIFY(control_loop)
   337     NULLIFY(subiteration_loop)
   338     NULLIFY(solid_sub_loop)
   339     NULLIFY(fluid_sub_loop)
   340     NULLIFY(solid_solvers)
   341     NULLIFY(fluid_solvers)
   343     NULLIFY(solver_mat_properties)
   344     NULLIFY(solver_solid)
   345     NULLIFY(solver_equations)
   346     NULLIFY(solver_equations_mat_properties)
   347     NULLIFY(solver_equations_solid)
   348     IF(
ASSOCIATED(problem)) 
THEN   349       IF(.NOT.
ALLOCATED(problem%specification)) 
THEN   350         CALL flagerror(
"Problem specification is not allocated.",err,error,*999)
   351       ELSE IF(
SIZE(problem%specification,1)<3) 
THEN   352         CALL flagerror(
"Problem specification must have three entries for a finite elasticity-Darcy problem.", &
   355       SELECT CASE(problem%SPECIFICATION(3))
   361         SELECT CASE(problem_setup%SETUP_TYPE)
   363           SELECT CASE(problem_setup%ACTION_TYPE)
   369             local_error=
"The action type of "//
trim(
number_to_vstring(problem_setup%ACTION_TYPE,
"*",err,error))// &
   371               & 
" is invalid for an finite elasticity ALE Darcy  equation."   372             CALL flagerror(local_error,err,error,*999)
   375           SELECT CASE(problem_setup%ACTION_TYPE)
   389             control_loop_root=>problem%CONTROL_LOOP
   394             local_error=
"The action type of "//
trim(
number_to_vstring(problem_setup%ACTION_TYPE,
"*",err,error))// &
   396               & 
" is invalid for a finite elasticity ALE Darcy equation."   397             CALL flagerror(local_error,err,error,*999)
   401           control_loop_root=>problem%CONTROL_LOOP
   403           SELECT CASE(problem_setup%ACTION_TYPE)
   441             local_error=
"The action type of "//
trim(
number_to_vstring(problem_setup%ACTION_TYPE,
"*",err,error))// &
   443                 & 
" is invalid for a finite elasticity ALE Darcy equation."   444             CALL flagerror(local_error,err,error,*999)
   447           SELECT CASE(problem_setup%ACTION_TYPE)
   450             control_loop_root=>problem%CONTROL_LOOP
   482             control_loop_root=>problem%CONTROL_LOOP
   505             local_error=
"The action type of "//
trim(
number_to_vstring(problem_setup%ACTION_TYPE,
"*",err,error))// &
   507               & 
" is invalid for a finite elasticity ALE Darcy equation."   508             CALL flagerror(local_error,err,error,*999)
   511           local_error=
"The setup type of "//
trim(
number_to_vstring(problem_setup%SETUP_TYPE,
"*",err,error))// &
   512             & 
" is invalid for a finite elasticity ALE Darcy equation."   513           CALL flagerror(local_error,err,error,*999)
   520         SELECT CASE(problem_setup%SETUP_TYPE)
   522           SELECT CASE(problem_setup%ACTION_TYPE)
   528             local_error=
"The action type of "//
trim(
number_to_vstring(problem_setup%ACTION_TYPE,
"*",err,error))// &
   530               & 
" is invalid for an finite elasticity ALE Darcy  equation."   531             CALL flagerror(local_error,err,error,*999)
   534           SELECT CASE(problem_setup%ACTION_TYPE)
   568             control_loop_root=>problem%CONTROL_LOOP
   573             local_error=
"The action type of "//
trim(
number_to_vstring(problem_setup%ACTION_TYPE,
"*",err,error))// &
   575               & 
" is invalid for a finite elasticity ALE Darcy equation."   576             CALL flagerror(local_error,err,error,*999)
   580           control_loop_root=>problem%CONTROL_LOOP
   582           SELECT CASE(problem_setup%ACTION_TYPE)
   622             local_error=
"The action type of "//
trim(
number_to_vstring(problem_setup%ACTION_TYPE,
"*",err,error))// &
   624                 & 
" is invalid for a finite elasticity ALE Darcy equation."   625             CALL flagerror(local_error,err,error,*999)
   628           SELECT CASE(problem_setup%ACTION_TYPE)
   631             control_loop_root=>problem%CONTROL_LOOP
   656             control_loop_root=>problem%CONTROL_LOOP
   675             local_error=
"The action type of "//
trim(
number_to_vstring(problem_setup%ACTION_TYPE,
"*",err,error))// &
   677               & 
" is invalid for a finite elasticity ALE Darcy equation."   678             CALL flagerror(local_error,err,error,*999)
   681           local_error=
"The setup type of "//
trim(
number_to_vstring(problem_setup%SETUP_TYPE,
"*",err,error))// &
   682             & 
" is invalid for a finite elasticity ALE Darcy equation."   683           CALL flagerror(local_error,err,error,*999)
   690         SELECT CASE(problem_setup%SETUP_TYPE)
   692           SELECT CASE(problem_setup%ACTION_TYPE)
   698             local_error=
"The action type of "//
trim(
number_to_vstring(problem_setup%ACTION_TYPE,
"*",err,error))// &
   700               & 
" is invalid for an finite elasticity ALE Darcy  equation."   701             CALL flagerror(local_error,err,error,*999)
   704           SELECT CASE(problem_setup%ACTION_TYPE)
   735             control_loop_root=>problem%CONTROL_LOOP
   740             local_error=
"The action type of "//
trim(
number_to_vstring(problem_setup%ACTION_TYPE,
"*",err,error))// &
   742               & 
" is invalid for a finite elasticity ALE Darcy equation."   743             CALL flagerror(local_error,err,error,*999)
   747           control_loop_root=>problem%CONTROL_LOOP
   749           SELECT CASE(problem_setup%ACTION_TYPE)
   794             local_error=
"The action type of "//
trim(
number_to_vstring(problem_setup%ACTION_TYPE,
"*",err,error))// &
   796                 & 
" is invalid for a finite elasticity ALE Darcy equation."   797             CALL flagerror(local_error,err,error,*999)
   800           SELECT CASE(problem_setup%ACTION_TYPE)
   803             control_loop_root=>problem%CONTROL_LOOP
   836             control_loop_root=>problem%CONTROL_LOOP
   860             local_error=
"The action type of "//
trim(
number_to_vstring(problem_setup%ACTION_TYPE,
"*",err,error))// &
   862               & 
" is invalid for a finite elasticity ALE Darcy equation."   863             CALL flagerror(local_error,err,error,*999)
   866           local_error=
"The setup type of "//
trim(
number_to_vstring(problem_setup%SETUP_TYPE,
"*",err,error))// &
   867             & 
" is invalid for a finite elasticity ALE Darcy equation."   868           CALL flagerror(local_error,err,error,*999)
   875         local_error=
"The problem subtype of "//
trim(
number_to_vstring(problem%SPECIFICATION(3),
"*",err,error))// &
   876           & 
" does not equal a standard finite elasticity Darcy equation subtype."   877         CALL flagerror(local_error,err,error,*999)
   881       CALL flagerror(
"Problem is not associated.",err,error,*999)
   884     exits(
"ELASTICITY_DARCY_PROBLEM_SETUP")
   886 999 errorsexits(
"ELASTICITY_DARCY_PROBLEM_SETUP",err,error)
   900     INTEGER(INTG), 
INTENT(OUT) :: ERR
   906     enters(
"ELASTICITY_DARCY_PRE_SOLVE",err,error,*999)
   908     IF(
ASSOCIATED(control_loop)) 
THEN   909       IF(
ASSOCIATED(solver)) 
THEN   910         IF(
ASSOCIATED(control_loop%PROBLEM)) 
THEN   911           IF(.NOT.
ALLOCATED(control_loop%problem%specification)) 
THEN   912             CALL flagerror(
"Problem specification is not allocated.",err,error,*999)
   913           ELSE IF(
SIZE(control_loop%problem%specification,1)<3) 
THEN   914             CALL flagerror(
"Problem specification must have three entries for a finite elasticity-Darcy problem.", &
   917           SELECT CASE(control_loop%PROBLEM%SPECIFICATION(3))
   922                 IF(solver%GLOBAL_NUMBER==1) 
THEN   926                 ELSE IF(solver%GLOBAL_NUMBER==2) 
THEN   940                 IF(solver%GLOBAL_NUMBER==1) 
THEN   944                 ELSE IF(solver%GLOBAL_NUMBER==2) 
THEN   955               local_error=
"Problem subtype "//
trim(
number_to_vstring(control_loop%PROBLEM%SPECIFICATION(3),
"*",err,error))// &
   956                 & 
" is not valid for a Darcy fluid type of a multi physics problem class."   957               CALL flagerror(local_error,err,error,*999)
   960           CALL flagerror(
"Problem is not associated.",err,error,*999)
   963         CALL flagerror(
"Solver is not associated.",err,error,*999)
   966       CALL flagerror(
"Control loop is not associated.",err,error,*999)
   969     exits(
"ELASTICITY_DARCY_PRE_SOLVE")
   971 999 errorsexits(
"ELASTICITY_DARCY_PRE_SOLVE",err,error)
   985     INTEGER(INTG), 
INTENT(OUT) :: ERR
   991     enters(
"ELASTICITY_DARCY_POST_SOLVE",err,error,*999)
   993     IF(
ASSOCIATED(control_loop)) 
THEN   994       IF(
ASSOCIATED(solver)) 
THEN   995         IF(
ASSOCIATED(control_loop%PROBLEM)) 
THEN    996           IF(.NOT.
ALLOCATED(control_loop%problem%specification)) 
THEN   997             CALL flagerror(
"Problem specification is not allocated.",err,error,*999)
   998           ELSE IF(
SIZE(control_loop%problem%specification,1)<3) 
THEN   999             CALL flagerror(
"Problem specification must have three entries for a finite elasticity-Darcy problem.", &
  1002           SELECT CASE(control_loop%PROBLEM%SPECIFICATION(3))
  1009               local_error=
"Problem subtype "//
trim(
number_to_vstring(control_loop%PROBLEM%SPECIFICATION(3),
"*",err,error))// &
  1010                 & 
" is not valid for a finite elasticity Darcy type of a multi physics problem class."  1011               CALL flagerror(local_error,err,error,*999)
  1014           CALL flagerror(
"Problem is not associated.",err,error,*999)
  1017         CALL flagerror(
"Solver is not associated.",err,error,*999)
  1020       CALL flagerror(
"Control loop is not associated.",err,error,*999)
  1023     exits(
"ELASTICITY_DARCY_POST_SOLVE")
  1025 999 errorsexits(
"ELASTICITY_DARCY_POST_SOLVE",err,error)
  1038     INTEGER(INTG), 
INTENT(OUT) :: ERR
  1042     REAL(DP) :: CURRENT_TIME,TIME_INCREMENT
  1047     enters(
"ELASTICITY_DARCY_CONTROL_LOOP_PRE_LOOP",err,error,*999)
  1049     NULLIFY(control_loop_darcy)
  1050     NULLIFY(solver_darcy)
  1052     IF(
ASSOCIATED(control_loop)) 
THEN  1053       IF(
ASSOCIATED(control_loop%PROBLEM)) 
THEN  1056         SELECT CASE(control_loop%LOOP_TYPE)
  1082                 & control_loop%WHILE_LOOP%ITERATION_NUMBER,err,error,*999)
  1089                 & control_loop%WHILE_LOOP%ITERATION_NUMBER,err,error,*999)
  1094             IF(.NOT.
ALLOCATED(control_loop%problem%specification)) 
THEN  1095               CALL flagerror(
"Problem specification is not allocated.",err,error,*999)
  1096             ELSE IF(
SIZE(control_loop%problem%specification,1)<3) 
THEN  1097               CALL flagerror(
"Problem specification must have three entries for a finite elasticity-Darcy problem.", &
  1100             SELECT CASE(control_loop%PROBLEM%SPECIFICATION(3))
  1106                 local_error=
"Problem subtype "//
trim(
number_to_vstring(control_loop%PROBLEM%SPECIFICATION(3),
"*",err,error))// &
  1107                   & 
" is not valid for ELASTICITY_DARCY_CONTROL_LOOP_PRE_LOOP."  1108                 CALL flagerror(local_error,err,error,*999)
  1130                 & control_loop%LOAD_INCREMENT_LOOP%ITERATION_NUMBER,err,error,*999)
  1137                 & control_loop%LOAD_INCREMENT_LOOP%ITERATION_NUMBER,err,error,*999)
  1145         CALL flagerror(
"Problem is not associated.",err,error,*999)
  1148       CALL flagerror(
"Control loop is not associated.",err,error,*999)
  1151     exits(
"ELASTICITY_DARCY_CONTROL_LOOP_PRE_LOOP")
  1153 999 errorsexits(
"ELASTICITY_DARCY_CONTROL_LOOP_PRE_LOOP",err,error)
  1166     INTEGER(INTG), 
INTENT(OUT) :: ERR
  1174     NULLIFY(solver_darcy)
  1175     NULLIFY(control_loop_darcy)
  1177     enters(
"ELASTICITY_DARCY_CONTROL_LOOP_POST_LOOP",err,error,*999)
  1179     IF(
ASSOCIATED(control_loop)) 
THEN  1180       IF(
ASSOCIATED(control_loop%PROBLEM)) 
THEN   1181         SELECT CASE(control_loop%LOOP_TYPE)
  1187           IF(.NOT.
ALLOCATED(control_loop%problem%specification)) 
THEN  1188             CALL flagerror(
"Problem specification is not allocated.",err,error,*999)
  1189           ELSE IF(
SIZE(control_loop%problem%specification,1)<3) 
THEN  1190             CALL flagerror(
"Problem specification must have three entries for a finite elasticity-Darcy problem.", &
  1193           SELECT CASE(control_loop%PROBLEM%SPECIFICATION(3))
  1215             local_error=
"Problem subtype "//
trim(
number_to_vstring(control_loop%PROBLEM%SPECIFICATION(3),
"*",err,error))// &
  1216               & 
" is not valid for a Darcy fluid type of a multi physics problem class with a while control loop."  1217             CALL flagerror(local_error,err,error,*999)
  1231         CALL flagerror(
"Problem is not associated.",err,error,*999)
  1234       CALL flagerror(
"Control loop is not associated.",err,error,*999)
  1237     exits(
"ELASTICITY_DARCY_CONTROL_LOOP_POST_LOOP")
  1239 999 errorsexits(
"ELASTICITY_DARCY_CONTROL_LOOP_POST_LOOP",err,error)
  1253     INTEGER(INTG), 
INTENT(OUT) :: ERR
  1259     enters(
"ELASTICITY_DARCY_POST_SOLVE_OUTPUT_DATA",err,error,*999)
  1261     IF(
ASSOCIATED(control_loop)) 
THEN  1262       IF(
ASSOCIATED(solver)) 
THEN  1263         IF(
ASSOCIATED(control_loop%PROBLEM)) 
THEN  1264           IF(.NOT.
ALLOCATED(control_loop%problem%specification)) 
THEN  1265             CALL flagerror(
"Problem specification is not allocated.",err,error,*999)
  1266           ELSE IF(
SIZE(control_loop%problem%specification,1)<3) 
THEN  1267             CALL flagerror(
"Problem specification must have three entries for a finite elasticity-Darcy problem.", &
  1270           SELECT CASE(control_loop%PROBLEM%SPECIFICATION(3))
  1274               IF(solver%GLOBAL_NUMBER==1) 
THEN  1276               ELSE IF(solver%GLOBAL_NUMBER==2.OR.solver%GLOBAL_NUMBER==3) 
THEN  1281               local_error=
"Problem subtype "//
trim(
number_to_vstring(control_loop%PROBLEM%SPECIFICATION(3),
"*",err,error))// &
  1282                 & 
" is not valid for a Darcy fluid type of a multi physics problem class."  1283               CALL flagerror(local_error,err,error,*999)
  1286           CALL flagerror(
"Problem is not associated.",err,error,*999)
  1289         CALL flagerror(
"Solver is not associated.",err,error,*999)
  1292       CALL flagerror(
"Control loop is not associated.",err,error,*999)
  1295     exits(
"ELASTICITY_DARCY_POST_SOLVE_OUTPUT_DATA")
  1297 999 errorsexits(
"ELASTICITY_DARCY_POST_SOLVE_OUTPUT_DATA",err,error)
 integer(intg), parameter equations_set_fem_solution_method
Finite Element Method solution method. 
This module contains all basis function routines. 
subroutine, public enters(NAME, ERR, ERROR,)
Records the entry into the named procedure and initialises the error code. 
subroutine, public solvers_create_finish(SOLVERS, ERR, ERROR,)
Finish the creation of solvers. 
integer(intg), parameter, public control_loop_progress_output
Progress output from control loop. 
This module contains all coordinate transformation and support routines. 
subroutine, public finite_elasticity_post_solve(CONTROL_LOOP, SOLVER, ERR, ERROR,)
Sets up the finite elasticity problem post solve. 
subroutine, public elasticity_darcy_control_loop_post_loop(CONTROL_LOOP, ERR, ERROR,)
Runs after each control loop iteration. 
integer(intg), parameter equations_set_gfem_solution_method
Grid-based Finite Element Method solution method. 
integer(intg), parameter problem_control_time_loop_type
Time control loop. 
integer(intg), parameter problem_setup_control_type
Solver setup for a problem. 
subroutine, public finite_elasticity_post_solve_output_data(CONTROL_LOOP, SOLVER, ERR, ERROR,)
Sets up the finite elasticity problem post solve output data. 
This module handles all problem wide constants. 
integer(intg), parameter solver_equations_first_order_dynamic
Solver equations are first order dynamic. 
integer(intg), parameter, public control_loop_node
The identifier for a each "leaf" node in a control loop. 
subroutine, public solver_dynamic_order_set(SOLVER, ORDER, ERR, ERROR,)
Sets/changes the order for a dynamic solver. 
subroutine, public control_loop_maximum_iterations_set(CONTROL_LOOP, MAXIMUM_ITERATIONS, ERR, ERROR,)
Sets the maximum number of iterations for a while or load increment control loop. ...
Converts a number to its equivalent varying string representation. 
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. 
subroutine, public control_loop_sub_loop_get(CONTROL_LOOP, SUB_LOOP_INDEX, SUB_LOOP, ERR, ERROR,)
Gets/returns a pointer to the sub loops as specified by the sub loop index for a control loop...
Contains information on the type of solver to be used. 
integer(intg), parameter, public solver_petsc_library
PETSc solver library. 
subroutine, public solvers_number_set(SOLVERS, NUMBER_OF_SOLVERS, ERR, ERROR,)
Sets/changes the number of solvers. 
integer(intg), parameter, public solver_dynamic_crank_nicolson_scheme
Crank-Nicolson dynamic solver. 
subroutine, public solver_dynamic_degree_set(SOLVER, DEGREE, ERR, ERROR,)
Sets/changes the degree of the polynomial used to interpolate time for a dynamic solver. 
This module handles all equations matrix and rhs routines. 
integer(intg), parameter, public solver_dynamic_first_order
Dynamic solver has first order terms. 
subroutine, public solver_type_set(SOLVER, SOLVE_TYPE, ERR, ERROR,)
Sets/changes the type for a solver. 
Contains information on an equations set. 
This module handles all equations routines. 
This module handles all routines pertaining to finite elasticity coupled with Darcy. 
integer(intg), parameter equations_set_standard_elasticity_darcy_subtype
This module contains all string manipulation and transformation routines. 
subroutine, public solvers_create_start(CONTROL_LOOP, SOLVERS, ERR, ERROR,)
Start the creation of a solvers for the control loop. 
subroutine, public darcy_control_time_loop_pre_loop(CONTROL_LOOP, ERR, ERROR,)
Contains information on the solvers to be used in a control loop. 
integer(intg), parameter problem_control_simple_type
Simple, one iteration control loop. 
This module contains routines for timing the program. 
subroutine, public control_loop_current_times_get(CONTROL_LOOP, CURRENT_TIME, TIME_INCREMENT, ERR, ERROR,)
Gets the current time parameters for a time control loop. 
subroutine, public elasticity_darcy_pre_solve(CONTROL_LOOP, SOLVER, ERR, ERROR,)
Sets up the finite elasticity Darcy problem pre-solve. 
integer(intg), parameter solver_equations_static
Solver equations are static. 
subroutine, public solver_equations_sparsity_type_set(SOLVER_EQUATIONS, SPARSITY_TYPE, ERR, ERROR,)
Sets/changes the sparsity type for solver equations. 
This module contains all mathematics support routines. 
subroutine, public solvers_solver_get(SOLVERS, SOLVER_INDEX, SOLVER, ERR, ERROR,)
Returns a pointer to the specified solver in the list of solvers. 
integer(intg), parameter solver_equations_linear
Solver equations are linear. 
Contains information on a control loop. 
This module provides an iso_varying_string module, conformant to the API specified in ISO/IEC 1539-2:...
subroutine, public solver_equations_create_finish(SOLVER_EQUATIONS, ERR, ERROR,)
Finishes the process of creating solver equations. 
integer(intg), parameter, public solver_sparse_matrices
Use sparse solver matrices. 
subroutine, public solver_equations_create_start(SOLVER, SOLVER_EQUATIONS, ERR, ERROR,)
Starts the process of creating solver equations. 
integer(intg), parameter, public solver_dynamic_type
A dynamic solver. 
integer(intg), parameter problem_setup_solvers_type
Solver setup for a problem. 
subroutine, public elasticity_darcy_equations_set_setup(EQUATIONS_SET, EQUATIONS_SET_SETUP, ERR, ERROR,)
Sets up the finite elasticity Darcy equation. 
This module contains all program wide constants. 
integer(intg), parameter solver_equations_nonlinear
Solver equations are nonlinear. 
subroutine, public solver_library_type_set(SOLVER, SOLVER_LIBRARY_TYPE, ERR, ERROR,)
Sets/changes the type of library type to use for the solver. 
integer(intg), parameter problem_setup_initial_type
Initial setup for a problem. 
This module handles all Darcy equations routines. 
subroutine, public darcy_equation_monitor_convergence(CONTROL_LOOP, SOLVER, ERR, ERROR,)
Monitor convergence of the Darcy solution. 
integer(intg), parameter solver_equations_quasistatic
Solver equations are quasistatic. 
integer(intg), parameter problem_finite_elasticity_darcy_type
subroutine, public solver_equations_linearity_type_set(SOLVER_EQUATIONS, LINEARITY_TYPE, ERR, ERROR,)
Sets/changes the linearity type for solver equations. 
subroutine, public darcy_presolvestorepreviousiterate(CONTROL_LOOP, SOLVER, ERR, ERROR,)
Store solution of previous subiteration iterate. 
integer(intg), parameter problem_quasistatic_elasticity_transient_darcy_subtype
subroutine, public exits(NAME)
Records the exit out of the named procedure. 
recursive subroutine, public control_loop_solvers_get(CONTROL_LOOP, SOLVERS, ERR, ERROR,)
Returns a pointer to the solvers for a control loop. 
subroutine, public darcy_equation_post_solve_output_data(CONTROL_LOOP, SOLVER, err, error,)
Sets up the Darcy problem post solve output data. 
This module contains all type definitions in order to avoid cyclic module references. 
integer(intg), parameter problem_standard_elasticity_darcy_subtype
This module contains all the low-level base routines e.g., all debug, control, and low-level communic...
integer(intg), parameter, public general_output_type
General output type. 
subroutine, public finiteelasticitydarcy_equationssetspecificationset(equationsSet, specification, err, error,)
Sets the equation specification for a finite elasticity Darcy equation type of a multi physics equati...
Returns the specified control loop as indexed by the control loop identifier from the control loop ro...
subroutine, public control_loop_type_set(CONTROL_LOOP, LOOP_TYPE, ERR, ERROR,)
Sets/changes the control loop type. 
integer(intg), parameter problem_multi_physics_class
integer(intg), parameter, public solver_nonlinear_type
A nonlinear solver. 
This module handles all domain mappings routines. 
integer(intg), parameter problem_setup_finish_action
Finish setup action. 
This module handles all equations mapping routines. 
Contains information about the solver equations for a solver. 
subroutine, public finiteelasticitydarcy_problemspecificationset(problem, problemSpecification, err, error,)
Sets the problem specification for a finite elasticity Darcy equation type. 
subroutine, public finiteelasticitydarcy_equationssetsolutionmethodset(EQUATIONS_SET, SOLUTION_METHOD, ERR, ERROR,)
Sets/changes the solution method for a finite elasticity Darcy equation type of a multi physics equat...
integer(intg), parameter equations_set_gfv_solution_method
Grid-based Finite Volume solution method. 
Contains information for a problem. 
integer(intg), parameter, public solver_progress_output
Progress output from solver routines. 
subroutine, public darcy_equation_pre_solve(CONTROL_LOOP, SOLVER, ERR, ERROR,)
Sets up the Darcy problem pre-solve. 
logical, save, public diagnostics1
.TRUE. if level 1 diagnostic output is active in the current routine 
This module handles all distributed matrix vector routines. 
subroutine elasticity_darcy_post_solve_output_data(CONTROL_LOOP, SOLVER, ERR, ERROR,)
Sets up the finite elasticity Darcy problem post solve output data. 
This module handles all boundary conditions routines. 
This module handles all solver routines. 
This module contains all routines dealing with (non-distributed) matrix and vectors types...
subroutine, public darcy_equation_post_solve(CONTROL_LOOP, SOLVER, ERR, ERROR,)
Sets up the Darcy problem post solve. 
subroutine, public control_loop_create_start(PROBLEM, CONTROL_LOOP, ERR, ERROR,)
Start the process of creating a control loop for a problem. 
integer(intg), parameter problem_setup_solver_equations_type
Solver equations setup for a problem. 
integer(intg), parameter, public diagnostic_output_type
Diagnostic output type. 
integer(intg), parameter problem_pgm_elasticity_darcy_subtype
subroutine, public control_loop_output_type_set(CONTROL_LOOP, OUTPUT_TYPE, ERR, ERROR,)
Sets/changes the output type for a control loop. 
subroutine, public solver_dynamic_scheme_set(SOLVER, SCHEME, ERR, ERROR,)
Sets/changes the scheme for a dynamic solver. 
subroutine, public finite_elasticity_pre_solve(CONTROL_LOOP, SOLVER, ERR, ERROR,)
Sets up the finite elasticity problem pre-solve. 
integer(intg), parameter equations_set_fd_solution_method
Finite Difference solution method. 
integer(intg), parameter problem_control_load_increment_loop_type
Load increment control loop. 
integer(intg), parameter problem_quasistatic_elast_trans_darcy_mat_solve_subtype
Contains information on the setup information for an equations set. 
integer(intg), parameter problem_setup_start_action
Start setup action. 
subroutine, public solver_equations_time_dependence_type_set(SOLVER_EQUATIONS, TIME_DEPENDENCE_TYPE, ERR, ERROR,)
Sets/changes the time dependence type for solver equations. 
This module handles all control loop routines. 
integer(intg), parameter, public solver_cmiss_library
CMISS (internal) solver library. 
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 equations_set_bem_solution_method
Boundary Element Method solution method. 
subroutine, public solver_solver_equations_get(SOLVER, SOLVER_EQUATIONS, ERR, ERROR,)
Returns a pointer to the solver equations for a solver. 
integer(intg), parameter equations_set_fv_solution_method
Finite Volume solution method. 
integer(intg), parameter, public solver_dynamic_first_degree
Dynamic solver uses a first degree polynomial for time interpolation. 
subroutine, public elasticity_darcy_finite_element_calculate(EQUATIONS_SET, ELEMENT_NUMBER, ERR, ERROR,)
Calculates the element stiffness matrices and RHS for a finite elasticity Darcy equation finite eleme...
recursive subroutine, public control_loop_create_finish(CONTROL_LOOP, ERR, ERROR,)
Finish the process of creating a control loop. 
subroutine, public control_loop_number_of_sub_loops_set(CONTROL_LOOP, NUMBER_OF_SUB_LOOPS, ERR, ERROR,)
Sets/changes the number of sub loops in a control loop. 
Flags an error condition. 
subroutine, public finiteelasticity_controltimelooppreloop(CONTROL_LOOP, ERR, ERROR,)
Runs before each time loop for a finite elasticity problem. 
integer(intg), parameter problem_control_while_loop_type
While control loop. 
integer(intg), parameter, public solver_linear_type
A linear solver. 
This module handles all finite elasticity routines. 
This module contains all kind definitions. 
Temporary IO routines for fluid mechanics. 
subroutine, public elasticity_darcy_problem_setup(PROBLEM, PROBLEM_SETUP, ERR, ERROR,)
Sets up the finite elasticity Darcy equations problem.