OpenCMISS-Iron Internal API Documentation
finite_elasticity_fluid_pressure_routines.f90
Go to the documentation of this file.
1 
43 
45 
46 
48 
49  USE base_routines
50  USE basis_routines
51  USE constants
58  USE input_output
60  USE kinds
62  USE strings
63  USE solver_routines
64  USE types
65 
66 #include "macros.h"
67 
68  IMPLICIT NONE
69 
73 
76 
78 
81 
83 
84 CONTAINS
85 
86  !
87  !================================================================================================================================
88  !
89 
91  SUBROUTINE finelasticityfluidpressure_equationssetsolnmethodset(EQUATIONS_SET,SOLUTION_METHOD,ERR,ERROR,*)
92 
93  !Argument variables
94  TYPE(equations_set_type), POINTER :: EQUATIONS_SET
95  INTEGER(INTG), INTENT(IN) :: SOLUTION_METHOD
96  INTEGER(INTG), INTENT(OUT) :: ERR
97  TYPE(varying_string), INTENT(OUT) :: ERROR
98  !Local Variables
99  TYPE(varying_string) :: LOCAL_ERROR
100 
101  enters("FinElasticityFluidPressure_EquationsSetSolnMethodSet",err,error,*999)
102 
103  IF(ASSOCIATED(equations_set)) THEN
104  IF(.NOT.ALLOCATED(equations_set%SPECIFICATION)) THEN
105  CALL flagerror("Equations set specification is not allocated.",err,error,*999)
106  ELSE IF(SIZE(equations_set%SPECIFICATION,1)/=3) THEN
107  CALL flagerror("Equations set specification must have three entries for a "// &
108  & "finite elasticity-fluid pressure class equations set.",err,error,*999)
109  END IF
110  SELECT CASE(equations_set%SPECIFICATION(3))
114  SELECT CASE(solution_method)
116  equations_set%SOLUTION_METHOD=equations_set_fem_solution_method
118  CALL flagerror("Not implemented.",err,error,*999)
120  CALL flagerror("Not implemented.",err,error,*999)
122  CALL flagerror("Not implemented.",err,error,*999)
124  CALL flagerror("Not implemented.",err,error,*999)
126  CALL flagerror("Not implemented.",err,error,*999)
127  CASE DEFAULT
128  local_error="The specified solution method of "//trim(number_to_vstring(solution_method,"*",err,error))//" is invalid."
129  CALL flagerror(local_error,err,error,*999)
130  END SELECT
131  CASE DEFAULT
132  local_error="Equations set subtype of "//trim(number_to_vstring(equations_set%SPECIFICATION(3),"*",err,error))// &
133  & " is not valid for a finite elasticity fluid pressure equation type of a multi physics equations set class."
134  CALL flagerror(local_error,err,error,*999)
135  END SELECT
136  ELSE
137  CALL flagerror("Equations set is not associated.",err,error,*999)
138  ENDIF
139 
140  exits("FinElasticityFluidPressure_EquationsSetSolnMethodSet")
141  RETURN
142 999 errors("FinElasticityFluidPressure_EquationsSetSolnMethodSet",err,error)
143  exits("FinElasticityFluidPressure_EquationsSetSolnMethodSet")
144  RETURN 1
145 
147 
148  !
149  !================================================================================================================================
150  !
151 
153  SUBROUTINE finelasticityfluidpressure_equationssetspecificationset(equationsSet,specification,err,error,*)
155  !Argument variables
156  TYPE(equations_set_type), POINTER :: equationsSet
157  INTEGER(INTG), INTENT(IN) :: specification(:)
158  INTEGER(INTG), INTENT(OUT) :: err
159  TYPE(varying_string), INTENT(OUT) :: error
160  !Local Variables
161 
162  enters("FinElasticityFluidPressure_EquationsSetSpecificationSet",err,error,*999)
163 
164  CALL flagerror("FinElasticityFluidPressure_EquationsSetSpecificationSet is not implemented.",err,error,*999)
165 
166  exits("FinElasticityFluidPressure_EquationsSetSpecificationSet")
167  RETURN
168 999 errors("FinElasticityFluidPressure_EquationsSetSpecificationSet",err,error)
169  exits("FinElasticityFluidPressure_EquationsSetSpecificationSet")
170  RETURN 1
171 
173 
174  !
175  !================================================================================================================================
176  !
177 
179  SUBROUTINE finelasticityfluidpressure_equationssetsetup(EQUATIONS_SET,EQUATIONS_SET_SETUP,ERR,ERROR,*)
181  !Argument variables
182  TYPE(equations_set_type), POINTER :: EQUATIONS_SET
183  TYPE(equations_set_setup_type), INTENT(INOUT) :: EQUATIONS_SET_SETUP
184  INTEGER(INTG), INTENT(OUT) :: ERR
185  TYPE(varying_string), INTENT(OUT) :: ERROR
186 
187 
188  enters("FinElasticityFluidPressure_EquationsSetSetup",err,error,*999)
189 
190  CALL flagerror("FinElasticityFluidPressure_EquationsSetSetup is not implemented.",err,error,*999)
191 
192  exits("FinElasticityFluidPressure_EquationsSetSetup")
193  RETURN
194 999 errors("FinElasticityFluidPressure_EquationsSetSetup",err,error)
195  exits("FinElasticityFluidPressure_EquationsSetSetup")
196  RETURN 1
197 
199 
200  !
201  !================================================================================================================================
202  !
203 
205  SUBROUTINE finelasticityfluidpressure_finiteelementcalculate(EQUATIONS_SET,ELEMENT_NUMBER,ERR,ERROR,*)
207  !Argument variables
208  TYPE(equations_set_type), POINTER :: EQUATIONS_SET
209  INTEGER(INTG), INTENT(IN) :: ELEMENT_NUMBER
210  INTEGER(INTG), INTENT(OUT) :: ERR
211  TYPE(varying_string), INTENT(OUT) :: ERROR
212 
213  enters("FinElasticityFluidPressure_FiniteElementCalculate",err,error,*999)
214 
215  CALL flagerror("FinElasticityFluidPressure_FiniteElementCalculate is not implemented.",err,error,*999)
216 
217  exits("FinElasticityFluidPressure_FiniteElementCalculate")
218  RETURN
219 999 errors("FinElasticityFluidPressure_FiniteElementCalculate",err,error)
220  exits("FinElasticityFluidPressure_FiniteElementCalculate")
221  RETURN 1
222 
224 
225  !
226  !================================================================================================================================
227  !
228 
230  SUBROUTINE finelasticityfluidpressure_problemspecificationset(problem,problemSpecification,err,error,*)
232  !Argument variables
233  TYPE(problem_type), POINTER :: problem
234  INTEGER(INTG), INTENT(IN) :: problemSpecification(:)
235  INTEGER(INTG), INTENT(OUT) :: err
236  TYPE(varying_string), INTENT(OUT) :: error
237  !Local Variables
238  TYPE(varying_string) :: localError
239  INTEGER(INTG) :: problemSubtype
240 
241  enters("FinElasticityFluidPressure_ProblemSpecificationSet",err,error,*999)
242 
243  IF(ASSOCIATED(problem)) THEN
244  IF(SIZE(problemspecification,1)==3) THEN
245  problemsubtype=problemspecification(3)
246  SELECT CASE(problemsubtype)
248  !ok
249  CASE DEFAULT
250  localerror="The third problem specification of "//trim(numbertovstring(problemsubtype,"*",err,error))// &
251  & " is not valid for a finite elasticity fluid pressure type of a multi physics problem."
252  CALL flagerror(localerror,err,error,*999)
253  END SELECT
254  IF(ALLOCATED(problem%specification)) THEN
255  CALL flagerror("Problem specification is already allocated.",err,error,*999)
256  ELSE
257  ALLOCATE(problem%specification(3),stat=err)
258  IF(err/=0) CALL flagerror("Could not allocate problem specification.",err,error,*999)
259  END IF
261  & problemsubtype]
262  ELSE
263  CALL flagerror("Finite elasticity fluid pressure problem specificaion must have three entries.",err,error,*999)
264  END IF
265  ELSE
266  CALL flagerror("Problem is not associated.",err,error,*999)
267  END IF
268 
269  exits("FinElasticityFluidPressure_ProblemSpecificationSet")
270  RETURN
271 999 errors("FinElasticityFluidPressure_ProblemSpecificationSet",err,error)
272  exits("FinElasticityFluidPressure_ProblemSpecificationSet")
273  RETURN 1
274 
276 
277  !
278  !================================================================================================================================
279  !
280 
282  SUBROUTINE elasticity_fluid_pressure_problem_setup(PROBLEM,PROBLEM_SETUP,ERR,ERROR,*)
284  !Argument variables
285  TYPE(problem_type), POINTER :: PROBLEM
286  TYPE(problem_setup_type), INTENT(INOUT) :: PROBLEM_SETUP
287  INTEGER(INTG), INTENT(OUT) :: ERR
288  TYPE(varying_string), INTENT(OUT) :: ERROR
289  !Local Variables
290  TYPE(control_loop_type), POINTER :: CONTROL_LOOP,CONTROL_LOOP_ROOT
291  TYPE(solver_type), POINTER :: SOLVER
292  TYPE(solver_equations_type), POINTER :: SOLVER_EQUATIONS
293  TYPE(solvers_type), POINTER :: SOLVERS
294  TYPE(varying_string) :: LOCAL_ERROR
295 
296  enters("ELASTICITY_FLUID_PRESSURE_PROBLEM_SETUP",err,error,*999)
297 
298  NULLIFY(control_loop)
299  NULLIFY(solver)
300  NULLIFY(solvers)
301  NULLIFY(solver_equations)
302  IF(ASSOCIATED(problem)) THEN
303  IF(ALLOCATED(problem%specification)) THEN
304  IF(.NOT.ALLOCATED(problem%specification)) THEN
305  CALL flagerror("Problem specification is not allocated.",err,error,*999)
306  ELSE IF(SIZE(problem%specification,1)<3) THEN
307  CALL flagerror("Problem specification must have three entries for a finite elasticity-Darcy problem.", &
308  & err,error,*999)
309  END IF
310  ELSE
311  CALL flagerror("Problem specification is not allocated.",err,error,*999)
312  END IF
313  SELECT CASE(problem%SPECIFICATION(3))
314 
315  !--------------------------------------------------------------------
316  ! Standard finite elasticity fluid pressure
317  !--------------------------------------------------------------------
319  SELECT CASE(problem_setup%SETUP_TYPE)
321  SELECT CASE(problem_setup%ACTION_TYPE)
323  !Do nothing
325  !Do nothing
326  CASE DEFAULT
327  local_error="The action type of "//trim(number_to_vstring(problem_setup%ACTION_TYPE,"*",err,error))// &
328  & " for a setup type of "//trim(number_to_vstring(problem_setup%SETUP_TYPE,"*",err,error))// &
329  & " is invalid for an finite elasticity ALE fluid pressure equation."
330  CALL flagerror(local_error,err,error,*999)
331  END SELECT
333  SELECT CASE(problem_setup%ACTION_TYPE)
335  !Set up a load increment loop
336  CALL control_loop_create_start(problem,control_loop,err,error,*999)
337  CALL control_loop_type_set(control_loop,problem_control_load_increment_loop_type,err,error,*999)
339  !Finish the control loops
340  control_loop_root=>problem%CONTROL_LOOP
341  CALL control_loop_get(control_loop_root,control_loop_node,control_loop,err,error,*999)
342  CALL control_loop_create_finish(control_loop,err,error,*999)
343  CASE DEFAULT
344  local_error="The action type of "//trim(number_to_vstring(problem_setup%ACTION_TYPE,"*",err,error))// &
345  & " for a setup type of "//trim(number_to_vstring(problem_setup%SETUP_TYPE,"*",err,error))// &
346  & " is invalid for a finite elasticity fluid pressure equation."
347  CALL flagerror(local_error,err,error,*999)
348  END SELECT
350  !Get the control loop
351  control_loop_root=>problem%CONTROL_LOOP
352  CALL control_loop_get(control_loop_root,control_loop_node,control_loop,err,error,*999)
353  SELECT CASE(problem_setup%ACTION_TYPE)
355  !Start the solvers creation for the solver
356  CALL solvers_create_start(control_loop,solvers,err,error,*999)
357  CALL solvers_number_set(solvers,1,err,error,*999)
358  !
359  !Set the first solver to be a nonlinear solver
360  CALL solvers_solver_get(solvers,1,solver,err,error,*999)
361  CALL solver_type_set(solver,solver_nonlinear_type,err,error,*999)
362  CALL solver_library_type_set(solver,solver_petsc_library,err,error,*999)
364  CALL control_loop_solvers_get(control_loop,solvers,err,error,*999)
365  !Finish the solvers creation
366  CALL solvers_create_finish(solvers,err,error,*999)
367  CASE DEFAULT
368  local_error="The action type of "//trim(number_to_vstring(problem_setup%ACTION_TYPE,"*",err,error))// &
369  & " for a setup type of "//trim(number_to_vstring(problem_setup%SETUP_TYPE,"*",err,error))// &
370  & " is invalid for a finite elasticity fluid pressure equation."
371  CALL flagerror(local_error,err,error,*999)
372  END SELECT
374  SELECT CASE(problem_setup%ACTION_TYPE)
376  !Get the control loop and solvers
377  control_loop_root=>problem%CONTROL_LOOP
378  CALL control_loop_get(control_loop_root,control_loop_node,control_loop,err,error,*999)
379  CALL control_loop_solvers_get(control_loop,solvers,err,error,*999)
380  !
381  !Get the nonlinear solver and create the solver equations
382  CALL solvers_solver_get(solvers,1,solver,err,error,*999)
383  CALL solver_equations_create_start(solver,solver_equations,err,error,*999)
384  CALL solver_equations_linearity_type_set(solver_equations,solver_equations_nonlinear,err,error,*999)
385  CALL solver_equations_time_dependence_type_set(solver_equations,solver_equations_static,err,error,*999)
386  CALL solver_equations_sparsity_type_set(solver_equations,solver_sparse_matrices,err,error,*999)
388  !Get the control loop
389  control_loop_root=>problem%CONTROL_LOOP
390  CALL control_loop_get(control_loop_root,control_loop_node,control_loop,err,error,*999)
391  CALL control_loop_solvers_get(control_loop,solvers,err,error,*999)
392  !
393  !Finish the creation of the solver equations
394  CALL solvers_solver_get(solvers,1,solver,err,error,*999)
395  CALL solver_solver_equations_get(solver,solver_equations,err,error,*999)
396  CALL solver_equations_create_finish(solver_equations,err,error,*999)
397  CASE DEFAULT
398  local_error="The action type of "//trim(number_to_vstring(problem_setup%ACTION_TYPE,"*",err,error))// &
399  & " for a setup type of "//trim(number_to_vstring(problem_setup%SETUP_TYPE,"*",err,error))// &
400  & " is invalid for a finite elasticity fluid pressure equation."
401  CALL flagerror(local_error,err,error,*999)
402  END SELECT
403  CASE DEFAULT
404  local_error="The setup type of "//trim(number_to_vstring(problem_setup%SETUP_TYPE,"*",err,error))// &
405  & " is invalid for a finite elasticity ALE fluid pressure equation."
406  CALL flagerror(local_error,err,error,*999)
407  END SELECT
408 
409  CASE DEFAULT
410  local_error="The problem subtype of "//trim(number_to_vstring(problem%SPECIFICATION(3),"*",err,error))// &
411  & " does not equal a standard finite elasticity fluid pressure equation subtype."
412  CALL flagerror(local_error,err,error,*999)
413 
414  END SELECT
415  ELSE
416  CALL flagerror("Problem is not associated.",err,error,*999)
417  ENDIF
418 
419  exits("ELASTICITY_FLUID_PRESSURE_PROBLEM_SETUP")
420  RETURN
421 999 errorsexits("ELASTICITY_FLUID_PRESSURE_PROBLEM_SETUP",err,error)
422  RETURN 1
424 
425  !
426  !================================================================================================================================
427  !
428 
430  SUBROUTINE elasticity_fluid_pressure_pre_solve(CONTROL_LOOP,SOLVER,ERR,ERROR,*)
432  !Argument variables
433  TYPE(control_loop_type), POINTER :: CONTROL_LOOP
434  TYPE(solver_type), POINTER :: SOLVER
435  INTEGER(INTG), INTENT(OUT) :: ERR
436  TYPE(varying_string), INTENT(OUT) :: ERROR
437 
438  !Local Variables
439  TYPE(varying_string) :: LOCAL_ERROR
440 
441  enters("ELASTICITY_FLUID_PRESSURE_PRE_SOLVE",err,error,*999)
442 
443  IF(ASSOCIATED(control_loop)) THEN
444  IF(ASSOCIATED(solver)) THEN
445  IF(ASSOCIATED(control_loop%PROBLEM)) THEN
446  IF(.NOT.ALLOCATED(control_loop%PROBLEM%SPECIFICATION)) THEN
447  CALL flagerror("Problem specification is not allocated.",err,error,*999)
448  ELSE IF(SIZE(control_loop%PROBLEM%SPECIFICATION,1)<3) THEN
449  CALL flagerror("Problem specification must have three entries for an elasticity fluid pressure problem.",err,error,*999)
450  END IF
451  SELECT CASE(control_loop%PROBLEM%SPECIFICATION(3))
453  IF(control_loop%LOOP_TYPE==problem_control_load_increment_loop_type) THEN
454  CALL finite_elasticity_pre_solve(control_loop,solver,err,error,*999)
455  ENDIF
456  CASE DEFAULT
457  local_error="Problem subtype "//trim(number_to_vstring(control_loop%PROBLEM%SPECIFICATION(3),"*",err,error))// &
458  & " is not valid for a fluid pressure fluid type of a multi physics problem class."
459  CALL flagerror(local_error,err,error,*999)
460  END SELECT
461  ELSE
462  CALL flagerror("Problem is not associated.",err,error,*999)
463  ENDIF
464  ELSE
465  CALL flagerror("Solver is not associated.",err,error,*999)
466  ENDIF
467  ELSE
468  CALL flagerror("Control loop is not associated.",err,error,*999)
469  ENDIF
470 
471  exits("ELASTICITY_FLUID_PRESSURE_PRE_SOLVE")
472  RETURN
473 999 errorsexits("ELASTICITY_FLUID_PRESSURE_PRE_SOLVE",err,error)
474  RETURN 1
476 
477  !
478  !================================================================================================================================
479  !
480 
482  SUBROUTINE elasticity_fluid_pressure_post_solve(CONTROL_LOOP,SOLVER,ERR,ERROR,*)
484  !Argument variables
485  TYPE(control_loop_type), POINTER :: CONTROL_LOOP
486  TYPE(solver_type), POINTER :: SOLVER
487  INTEGER(INTG), INTENT(OUT) :: ERR
488  TYPE(varying_string), INTENT(OUT) :: ERROR
489 
490  !Local Variables
491  TYPE(varying_string) :: LOCAL_ERROR
492 
493  enters("ELASTICITY_FLUID_PRESSURE_POST_SOLVE",err,error,*999)
494 
495  IF(ASSOCIATED(control_loop)) THEN
496  IF(ASSOCIATED(solver)) THEN
497  IF(ASSOCIATED(control_loop%PROBLEM)) THEN
498  IF(.NOT.ALLOCATED(control_loop%PROBLEM%SPECIFICATION)) THEN
499  CALL flagerror("Problem specification is not allocated.",err,error,*999)
500  ELSE IF(SIZE(control_loop%PROBLEM%SPECIFICATION,1)<3) THEN
501  CALL flagerror("Problem specification must have three entries for an elasticity fluid pressure problem.",err,error,*999)
502  END IF
503  SELECT CASE(control_loop%PROBLEM%SPECIFICATION(3))
505  CALL finite_elasticity_post_solve(control_loop,solver,err,error,*999)
506  CASE DEFAULT
507  local_error="Problem subtype "//trim(number_to_vstring(control_loop%PROBLEM%SPECIFICATION(3),"*",err,error))// &
508  & " is not valid for a finite elasticity fluid pressure type of a multi physics problem class."
509  CALL flagerror(local_error,err,error,*999)
510  END SELECT
511  ELSE
512  CALL flagerror("Problem is not associated.",err,error,*999)
513  ENDIF
514  ELSE
515  CALL flagerror("Solver is not associated.",err,error,*999)
516  ENDIF
517  ELSE
518  CALL flagerror("Control loop is not associated.",err,error,*999)
519  ENDIF
520 
521  exits("ELASTICITY_FLUID_PRESSURE_POST_SOLVE")
522  RETURN
523 999 errorsexits("ELASTICITY_FLUID_PRESSURE_POST_SOLVE",err,error)
524  RETURN 1
526 
527  !
528  !================================================================================================================================
529  !
530 
532  SUBROUTINE finelasticityfluidpressure_controllooppreloop(CONTROL_LOOP,ERR,ERROR,*)
534  !Argument variables
535  TYPE(control_loop_type), POINTER :: CONTROL_LOOP
536  INTEGER(INTG), INTENT(OUT) :: ERR
537  TYPE(varying_string), INTENT(OUT) :: ERROR
538 
539  !Local Variables
540  TYPE(solver_type), POINTER :: SOLVER_FLUID_PRESSURE
541  TYPE(control_loop_type), POINTER :: CONTROL_LOOP_FLUID_PRESSURE
542 
543  enters("FinElasticityFluidPressure_ControlLoopPreLoop",err,error,*999)
544 
545  NULLIFY(control_loop_fluid_pressure)
546  NULLIFY(solver_fluid_pressure)
547 
548  IF(ASSOCIATED(control_loop)) THEN
549  IF(ASSOCIATED(control_loop%PROBLEM)) THEN
550  ! Eventually we may want to do different things depending on problem type/subtype
551  ! too but for now we can just check the loop type.
552  SELECT CASE(control_loop%LOOP_TYPE)
554  IF(control_loop%OUTPUT_TYPE>=control_loop_progress_output) THEN
555  CALL write_string(general_output_type,"------------------------------------",err,error,*999)
556  CALL write_string(general_output_type,"-- Starting load increment --",err,error,*999)
557  CALL write_string_value(general_output_type,"LOAD INCREMENT NUMBER = ", &
558  & control_loop%LOAD_INCREMENT_LOOP%ITERATION_NUMBER,err,error,*999)
559  CALL write_string(general_output_type,"------------------------------------",err,error,*999)
560  ENDIF
561  IF(diagnostics1) THEN
562  CALL write_string(diagnostic_output_type,"------------------------------------",err,error,*999)
563  CALL write_string(diagnostic_output_type,"-- Starting load increment --",err,error,*999)
564  CALL write_string_value(diagnostic_output_type,"LOAD INCREMENT NUMBER = ", &
565  & control_loop%LOAD_INCREMENT_LOOP%ITERATION_NUMBER,err,error,*999)
566  CALL write_string(diagnostic_output_type,"------------------------------------",err,error,*999)
567  ENDIF
568 
569  CASE DEFAULT
570  !do nothing
571  END SELECT
572  ELSE
573  CALL flagerror("Problem is not associated.",err,error,*999)
574  ENDIF
575  ELSE
576  CALL flagerror("Control loop is not associated.",err,error,*999)
577  ENDIF
578 
579  exits("FinElasticityFluidPressure_ControlLoopPreLoop")
580  RETURN
581 999 errors("FinElasticityFluidPressure_ControlLoopPreLoop",err,error)
582  exits("FinElasticityFluidPressure_ControlLoopPreLoop")
583  RETURN 1
584 
586 
587  !
588  !================================================================================================================================
589  !
590 
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.
Write a string followed by a value to a given output stream.
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.
subroutine, public finite_elasticity_post_solve(CONTROL_LOOP, SOLVER, ERR, ERROR,)
Sets up the finite elasticity problem post solve.
integer(intg), parameter equations_set_gfem_solution_method
Grid-based Finite Element Method solution method.
integer(intg), parameter problem_setup_control_type
Solver setup for a problem.
This module handles all problem wide constants.
integer(intg), parameter, public control_loop_node
The identifier for a each "leaf" node in a control loop.
Converts a number to its equivalent varying string representation.
Definition: strings.f90:161
subroutine, public finelasticityfluidpressure_controllooppreloop(CONTROL_LOOP, ERR, ERROR,)
Runs before each control loop iteration.
Contains information on the type of solver to be used.
Definition: types.f90:2777
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.
This module handles all equations matrix and rhs routines.
subroutine, public solver_type_set(SOLVER, SOLVE_TYPE, ERR, ERROR,)
Sets/changes the type for a solver.
Contains information on an equations set.
Definition: types.f90:1941
This module handles all equations routines.
This module contains all string manipulation and transformation routines.
Definition: strings.f90:45
subroutine, public solvers_create_start(CONTROL_LOOP, SOLVERS, ERR, ERROR,)
Start the creation of a solvers for the control loop.
Contains information on the solvers to be used in a control loop.
Definition: types.f90:2805
integer(intg), parameter solver_equations_static
Solver equations are static.
integer(intg), parameter equations_set_elasticity_fluid_pressure_holmes_mow_subtype
subroutine, public solver_equations_sparsity_type_set(SOLVER_EQUATIONS, SPARSITY_TYPE, ERR, ERROR,)
Sets/changes the sparsity type for solver equations.
subroutine, public elasticity_fluid_pressure_post_solve(CONTROL_LOOP, SOLVER, ERR, ERROR,)
Sets up the finite elasticity fluid pressure problem post solve.
subroutine, public solvers_solver_get(SOLVERS, SOLVER_INDEX, SOLVER, ERR, ERROR,)
Returns a pointer to the specified solver in the list of solvers.
Contains information on a control loop.
Definition: types.f90:3185
This module provides an iso_varying_string module, conformant to the API specified in ISO/IEC 1539-2:...
subroutine, public 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 problem_setup_solvers_type
Solver setup for a problem.
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...
This module contains all program wide constants.
Definition: constants.f90:45
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...
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.
subroutine, public solver_equations_linearity_type_set(SOLVER_EQUATIONS, LINEARITY_TYPE, ERR, ERROR,)
Sets/changes the linearity type for solver equations.
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.
This module contains all type definitions in order to avoid cyclic module references.
Definition: types.f90:70
subroutine, public finelasticityfluidpressure_problemspecificationset(problem, problemSpecification, err, error,)
Sets the problem specification for a finite elasticity fluid pressure equation type.
Write a string to a given output stream.
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.
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.
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.
Definition: types.f90:2452
integer(intg), parameter equations_set_gfv_solution_method
Grid-based Finite Volume solution method.
Contains information for a problem.
Definition: types.f90:3221
This module handles all routines pertaining to finite elasticity coupled with fluid pressure for poro...
logical, save, public diagnostics1
.TRUE. if level 1 diagnostic output is active in the current routine
integer(intg), parameter equations_set_elasticity_fluid_pressure_static_inria_subtype
subroutine, public finelasticityfluidpressure_equationssetspecificationset(equationsSet, specification, err, error,)
Sets the equation specification for a finite elasticity fluid pressure equation type of a fluid mecha...
This module handles all solver routines.
integer(intg), parameter problem_standard_elasticity_fluid_pressure_subtype
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.
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.
Contains information on the setup information for an equations set.
Definition: types.f90:1866
integer(intg), parameter equations_set_elasticity_fluid_pres_holmes_mow_active_subtype
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.
subroutine, public elasticity_fluid_pressure_pre_solve(CONTROL_LOOP, SOLVER, ERR, ERROR,)
Sets up the finite elasticity fluid pressure problem pre-solve.
This module handles all control loop routines.
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
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.
subroutine, public finelasticityfluidpressure_equationssetsetup(EQUATIONS_SET, EQUATIONS_SET_SETUP, ERR, ERROR,)
Sets up the finite elasticity fluid pressure equation.
integer(intg), parameter equations_set_fv_solution_method
Finite Volume solution method.
subroutine, public elasticity_fluid_pressure_problem_setup(PROBLEM, PROBLEM_SETUP, ERR, ERROR,)
Sets up the finite elasticity fluid pressure equations problem.
recursive subroutine, public control_loop_create_finish(CONTROL_LOOP, ERR, ERROR,)
Finish the process of creating a control loop.
Flags an error condition.
This module handles all finite elasticity routines.
This module contains all kind definitions.
Definition: kinds.f90:45
This module handles all formating and input and output.