OpenCMISS-Iron Internal API Documentation
finite_elasticity_Darcy_routines.f90
Go to the documentation of this file.
1 
43 
45 
46 
48 
49  USE base_routines
50  USE basis_routines
52  USE constants
57  USE domain_mappings
62  USE field_routines
65 ! USE FITTING_ROUTINES !also in makefiles
66  USE input_output
68  USE kinds
69  USE maths
70  USE matrix_vector
71  USE mesh_routines
72  USE node_routines
74  USE strings
75  USE solver_routines
76  USE timer
77  USE types
78 
79 #include "macros.h"
80 
81 
82  IMPLICIT NONE
83 
87 
90 
92 
95 
98 
99 CONTAINS
100 
101  !
102  !================================================================================================================================
103  !
104 
106  SUBROUTINE finiteelasticitydarcy_equationssetsolutionmethodset(EQUATIONS_SET,SOLUTION_METHOD,ERR,ERROR,*)
108  !Argument variables
109  TYPE(equations_set_type), POINTER :: EQUATIONS_SET
110  INTEGER(INTG), INTENT(IN) :: SOLUTION_METHOD
111  INTEGER(INTG), INTENT(OUT) :: ERR
112  TYPE(varying_string), INTENT(OUT) :: ERROR
113  !Local Variables
114  TYPE(varying_string) :: LOCAL_ERROR
115 
116  enters("FiniteElasticityDarcy_EquationsSetSolutionMethodSet",err,error,*999)
117 
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)
124  END IF
125  SELECT CASE(equations_set%SPECIFICATION(3))
127  SELECT CASE(solution_method)
129  equations_set%SOLUTION_METHOD=equations_set_fem_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)
140  CASE DEFAULT
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)
143  END SELECT
144  CASE DEFAULT
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)
148  END SELECT
149  ELSE
150  CALL flagerror("Equations set is not associated.",err,error,*999)
151  ENDIF
152 
153  exits("FiniteElasticityDarcy_EquationsSetSolutionMethodSet")
154  RETURN
155 999 errors("FiniteElasticityDarcy_EquationsSetSolutionMethodSet",err,error)
156  exits("FiniteElasticityDarcy_EquationsSetSolutionMethodSet")
157  RETURN 1
158 
160 
161  !
162  !================================================================================================================================
163  !
164 
166  SUBROUTINE elasticity_darcy_equations_set_setup(EQUATIONS_SET,EQUATIONS_SET_SETUP,ERR,ERROR,*)
168  !Argument variables
169  TYPE(equations_set_type), POINTER :: EQUATIONS_SET
170  TYPE(equations_set_setup_type), INTENT(INOUT) :: EQUATIONS_SET_SETUP
171  INTEGER(INTG), INTENT(OUT) :: ERR
172  TYPE(varying_string), INTENT(OUT) :: ERROR
173 
174 
175  enters("ELASTICITY_DARCY_EQUATIONS_SET_SETUP",err,error,*999)
176 
177  CALL flagerror("ELASTICITY_DARCY_EQUATIONS_SET_SETUP still needs to be implemented.",err,error,*999)
178 
179  !=================================================================
180  ! This routine still needs to be implemented.
181  ! It will be used to setup the equations set of a monolithic
182  ! finite-elasticity Darcy system.
183  ! For the partitioned solution this routine is not called,
184  ! since EQUATIONS_SET_SETUP of respective equations_set is called.
185  !=================================================================
186 
187 
188  exits("ELASTICITY_DARCY_EQUATIONS_SET_SETUP")
189  RETURN
190 999 errorsexits("ELASTICITY_DARCY_EQUATIONS_SET_SETUP",err,error)
191  RETURN 1
193 
194  !
195  !================================================================================================================================
196  !
197 
199  SUBROUTINE elasticity_darcy_finite_element_calculate(EQUATIONS_SET,ELEMENT_NUMBER,ERR,ERROR,*)
201  !Argument variables
202  TYPE(equations_set_type), POINTER :: EQUATIONS_SET
203  INTEGER(INTG), INTENT(IN) :: ELEMENT_NUMBER
204  INTEGER(INTG), INTENT(OUT) :: ERR
205  TYPE(varying_string), INTENT(OUT) :: ERROR
206 
207 
208  enters("ELASTICITY_DARCY_FINITE_ELEMENT_CALCULATE",err,error,*999)
209 
210  CALL flagerror("ELASTICITY_DARCY_FINITE_ELEMENT_CALCULATE still needs to be implemented.",err,error,*999)
211 
212  !=================================================================
213  ! This routine still needs to be implemented.
214  ! It will be used to calculate the finite-element matrices and vectors
215  ! of a monolithic finite-elasticity Darcy system.
216  ! For the partitioned solution this routine is not called,
217  ! since FINITE_ELEMENT_CALCULATE of respective equations_set is called.
218  !=================================================================
219 
220 
221  exits("ELASTICITY_DARCY_FINITE_ELEMENT_CALCULATE")
222  RETURN
223 999 errorsexits("ELASTICITY_DARCY_FINITE_ELEMENT_CALCULATE",err,error)
224  RETURN 1
226 
227  !
228  !================================================================================================================================
229  !
230 
232  SUBROUTINE finiteelasticitydarcy_equationssetspecificationset(equationsSet,specification,err,error,*)
234  !Argument variables
235  TYPE(equations_set_type), POINTER :: equationsSet
236  INTEGER(INTG), INTENT(IN) :: specification(:)
237  INTEGER(INTG), INTENT(OUT) :: err
238  TYPE(varying_string), INTENT(OUT) :: error
239 
240  enters("FiniteElasticityDarcy_EquationsSetSpecificationSet",err,error,*999)
241 
242  CALL flagerror("FiniteElasticityDarcy_EquationsSetSpecificationSet still needs to be implemented.",err,error,*999)
243 
244  !=================================================================
245  ! This routine still needs to be implemented.
246  ! It will be used to set the equations_set_subtype
247  ! of a monolithic finite-elasticity Darcy system.
248  ! For the partitioned solution this routine is not called,
249  ! since EQUATIONS_SET_SUBTYPE_SET of respective equations_set is called.
250  !=================================================================
251 
252  exits("FiniteElasticityDarcy_EquationsSetSpecificationSet")
253  RETURN
254 999 errors("FiniteElasticityDarcy_EquationsSetSpecificationSet",err,error)
255  exits("FiniteElasticityDarcy_EquationsSetSpecificationSet")
256  RETURN 1
257 
259 
260  !
261  !================================================================================================================================
262  !
263 
265  SUBROUTINE finiteelasticitydarcy_problemspecificationset(problem,problemSpecification,err,error,*)
267  !Argument variables
268  TYPE(problem_type), POINTER :: problem
269  INTEGER(INTG), INTENT(IN) :: problemSpecification(:)
270  INTEGER(INTG), INTENT(OUT) :: err
271  TYPE(varying_string), INTENT(OUT) :: error
272  !Local Variables
273  TYPE(varying_string) :: localError
274  INTEGER(INTG) :: problemSubtype
275 
276  enters("FiniteElasticityDarcy_ProblemSpecificationSet",err,error,*999)
277 
278  IF(ASSOCIATED(problem)) THEN
279  IF(SIZE(problemspecification,1)==3) THEN
280  problemsubtype=problemspecification(3)
281  SELECT CASE(problemsubtype)
286  !ok
287  CASE DEFAULT
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)
291  END SELECT
292  IF(ALLOCATED(problem%specification)) THEN
293  CALL flagerror("Problem specification is already allocated.",err,error,*999)
294  ELSE
295  ALLOCATE(problem%specification(3),stat=err)
296  IF(err/=0) CALL flagerror("Could not allocate problem specification.",err,error,*999)
297  END IF
299  & problemsubtype]
300  ELSE
301  CALL flagerror("Finite elasticity Darcy problem specification must have three entries",err,error,*999)
302  END IF
303  ELSE
304  CALL flagerror("Problem is not associated.",err,error,*999)
305  END IF
306 
307  exits("FiniteElasticityDarcy_ProblemSpecificationSet")
308  RETURN
309 999 errors("FiniteElasticityDarcy_ProblemSpecificationSet",err,error)
310  exits("FiniteElasticityDarcy_ProblemSpecificationSet")
311  RETURN 1
312 
314 
315  !
316  !================================================================================================================================
317  !
318 
320  SUBROUTINE elasticity_darcy_problem_setup(PROBLEM,PROBLEM_SETUP,ERR,ERROR,*)
322  !Argument variables
323  TYPE(problem_type), POINTER :: PROBLEM
324  TYPE(problem_setup_type), INTENT(INOUT) :: PROBLEM_SETUP
325  INTEGER(INTG), INTENT(OUT) :: ERR
326  TYPE(varying_string), INTENT(OUT) :: ERROR
327  !Local Variables
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
332  TYPE(varying_string) :: LOCAL_ERROR
333 
334  enters("ELASTICITY_DARCY_PROBLEM_SETUP",err,error,*999)
335 
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)
342  NULLIFY(solver)
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.", &
353  & err,error,*999)
354  END IF
355  SELECT CASE(problem%SPECIFICATION(3))
356 
357  !--------------------------------------------------------------------
358  ! s t a n d a r d f i n i t e e l a s t i c i t y D a r c y
359  !--------------------------------------------------------------------
361  SELECT CASE(problem_setup%SETUP_TYPE)
363  SELECT CASE(problem_setup%ACTION_TYPE)
365  !Do nothing????
367  !Do nothing???
368  CASE DEFAULT
369  local_error="The action type of "//trim(number_to_vstring(problem_setup%ACTION_TYPE,"*",err,error))// &
370  & " for a setup type of "//trim(number_to_vstring(problem_setup%SETUP_TYPE,"*",err,error))// &
371  & " is invalid for an finite elasticity ALE Darcy equation."
372  CALL flagerror(local_error,err,error,*999)
373  END SELECT
375  SELECT CASE(problem_setup%ACTION_TYPE)
377  !Set up a time control loop
378  CALL control_loop_create_start(problem,control_loop,err,error,*999)
379  CALL control_loop_type_set(control_loop,problem_control_time_loop_type,err,error,*999)
380  CALL control_loop_number_of_sub_loops_set(control_loop,2,err,error,*999)
381  !Solid, load incremented control loop
382  CALL control_loop_sub_loop_get(control_loop,1,solid_sub_loop,err,error,*999)
383  CALL control_loop_type_set(solid_sub_loop,problem_control_load_increment_loop_type,err,error,*999)
384  !Fluid control loop
385  CALL control_loop_sub_loop_get(control_loop,2,fluid_sub_loop,err,error,*999)
386  CALL control_loop_type_set(fluid_sub_loop,problem_control_simple_type,err,error,*999)
388  !Finish the control loops
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_create_finish(control_loop,err,error,*999)
392  !Sub-loops are finished when parent is finished
393  CASE DEFAULT
394  local_error="The action type of "//trim(number_to_vstring(problem_setup%ACTION_TYPE,"*",err,error))// &
395  & " for a setup type of "//trim(number_to_vstring(problem_setup%SETUP_TYPE,"*",err,error))// &
396  & " is invalid for a finite elasticity ALE Darcy equation."
397  CALL flagerror(local_error,err,error,*999)
398  END SELECT
400  !Get the control loop
401  control_loop_root=>problem%CONTROL_LOOP
402  CALL control_loop_get(control_loop_root,control_loop_node,control_loop,err,error,*999)
403  SELECT CASE(problem_setup%ACTION_TYPE)
405  !Start the solvers creation for the solid solver
406  CALL control_loop_sub_loop_get(control_loop,1,solid_sub_loop,err,error,*999)
407  CALL solvers_create_start(solid_sub_loop,solid_solvers,err,error,*999)
408  CALL solvers_number_set(solid_solvers,1,err,error,*999)
409  !
410  !Set the first solver to be a nonlinear solver for the finite elasticity
411  CALL solvers_solver_get(solid_solvers,1,solver_solid,err,error,*999)
412  CALL solver_type_set(solver_solid,solver_nonlinear_type,err,error,*999)
413  CALL solver_library_type_set(solver_solid,solver_petsc_library,err,error,*999)
414  !
415  !Start the solvers creation for the fluid solvers
416  CALL control_loop_sub_loop_get(control_loop,2,fluid_sub_loop,err,error,*999)
417  CALL solvers_create_start(fluid_sub_loop,fluid_solvers,err,error,*999)
418  CALL solvers_number_set(fluid_solvers,2,err,error,*999)
419  !
420  !Set the second solver to be a linear solver for the material update
421  CALL solvers_solver_get(fluid_solvers,1,solver_mat_properties,err,error,*999)
422  CALL solver_type_set(solver_mat_properties,solver_linear_type,err,error,*999)
423  CALL solver_library_type_set(solver_mat_properties,solver_petsc_library,err,error,*999)
424  !
425  !Set the third solver to be a linear solver for ALE Darcy
426  CALL solvers_solver_get(fluid_solvers,2,solver,err,error,*999)
427  CALL solver_type_set(solver,solver_linear_type,err,error,*999)
428  CALL solver_library_type_set(solver,solver_petsc_library,err,error,*999)
430  !Get the solid solvers
431  CALL control_loop_sub_loop_get(control_loop,1,solid_sub_loop,err,error,*999)
432  CALL control_loop_solvers_get(solid_sub_loop,solid_solvers,err,error,*999)
433  !Finish the solvers creation
434  CALL solvers_create_finish(solid_solvers,err,error,*999)
435  !Get the fluid solvers
436  CALL control_loop_sub_loop_get(control_loop,2,fluid_sub_loop,err,error,*999)
437  CALL control_loop_solvers_get(fluid_sub_loop,fluid_solvers,err,error,*999)
438  !Finish the solvers creation
439  CALL solvers_create_finish(fluid_solvers,err,error,*999)
440  CASE DEFAULT
441  local_error="The action type of "//trim(number_to_vstring(problem_setup%ACTION_TYPE,"*",err,error))// &
442  & " for a setup type of "//trim(number_to_vstring(problem_setup%SETUP_TYPE,"*",err,error))// &
443  & " is invalid for a finite elasticity ALE Darcy equation."
444  CALL flagerror(local_error,err,error,*999)
445  END SELECT
447  SELECT CASE(problem_setup%ACTION_TYPE)
449  !Get the control loop and solvers
450  control_loop_root=>problem%CONTROL_LOOP
451  CALL control_loop_get(control_loop_root,control_loop_node,control_loop,err,error,*999)
452  !
453  CALL control_loop_sub_loop_get(control_loop,1,solid_sub_loop,err,error,*999)
454  CALL control_loop_solvers_get(solid_sub_loop,solid_solvers,err,error,*999)
455  !
456  !Get the finite elasticity solver and create the finite elasticity solver equations
457  CALL solvers_solver_get(solid_solvers,1,solver_solid,err,error,*999)
458  CALL solver_equations_create_start(solver_solid,solver_equations_solid,err,error,*999)
459  CALL solver_equations_linearity_type_set(solver_equations_solid,solver_equations_nonlinear,err,error,*999)
460  CALL solver_equations_time_dependence_type_set(solver_equations_solid,solver_equations_static,err,error,*999)
461  CALL solver_equations_sparsity_type_set(solver_equations_solid,solver_sparse_matrices,err,error,*999)
462  !
463  CALL control_loop_sub_loop_get(control_loop,2,fluid_sub_loop,err,error,*999)
464  CALL control_loop_solvers_get(fluid_sub_loop,fluid_solvers,err,error,*999)
465  !
466  !Get the material-properties solver and create the material-properties solver equations
467  CALL solvers_solver_get(fluid_solvers,1,solver_mat_properties,err,error,*999)
468  CALL solver_equations_create_start(solver_mat_properties,solver_equations_mat_properties,err,error,*999)
469  CALL solver_equations_linearity_type_set(solver_equations_mat_properties,solver_equations_linear,err,error,*999)
470  CALL solver_equations_time_dependence_type_set(solver_equations_mat_properties,solver_equations_quasistatic, &
471  & err,error,*999)
472  CALL solver_equations_sparsity_type_set(solver_equations_mat_properties,solver_sparse_matrices,err,error,*999)
473  !
474  !Get the Darcy-ALE solver and create the Darcy-ALE solver equations
475  CALL solvers_solver_get(fluid_solvers,2,solver,err,error,*999)
476  CALL solver_equations_create_start(solver,solver_equations,err,error,*999)
477  CALL solver_equations_linearity_type_set(solver_equations,solver_equations_linear,err,error,*999)
478  CALL solver_equations_time_dependence_type_set(solver_equations,solver_equations_quasistatic,err,error,*999)
479  CALL solver_equations_sparsity_type_set(solver_equations,solver_sparse_matrices,err,error,*999)
481  !Get the control loop
482  control_loop_root=>problem%CONTROL_LOOP
483  CALL control_loop_get(control_loop_root,control_loop_node,control_loop,err,error,*999)
484  CALL control_loop_sub_loop_get(control_loop,1,solid_sub_loop,err,error,*999)
485  CALL control_loop_solvers_get(solid_sub_loop,solid_solvers,err,error,*999)
486  !
487  !Finish the creation of the finite elasticity solver equations
488  CALL solvers_solver_get(solid_solvers,1,solver_solid,err,error,*999)
489  CALL solver_solver_equations_get(solver_solid,solver_equations_solid,err,error,*999)
490  CALL solver_equations_create_finish(solver_equations_solid,err,error,*999)
491  !
492  CALL control_loop_sub_loop_get(control_loop,2,fluid_sub_loop,err,error,*999)
493  CALL control_loop_solvers_get(fluid_sub_loop,fluid_solvers,err,error,*999)
494  !
495  !Finish the creation of the material-properties solver equations
496  CALL solvers_solver_get(fluid_solvers,1,solver_mat_properties,err,error,*999)
497  CALL solver_solver_equations_get(solver_mat_properties,solver_equations_mat_properties,err,error,*999)
498  CALL solver_equations_create_finish(solver_equations_mat_properties,err,error,*999)
499  !
500  !Finish the creation of the Darcy-ALE solver equations
501  CALL solvers_solver_get(fluid_solvers,2,solver,err,error,*999)
502  CALL solver_solver_equations_get(solver,solver_equations,err,error,*999)
503  CALL solver_equations_create_finish(solver_equations,err,error,*999)
504  CASE DEFAULT
505  local_error="The action type of "//trim(number_to_vstring(problem_setup%ACTION_TYPE,"*",err,error))// &
506  & " for a setup type of "//trim(number_to_vstring(problem_setup%SETUP_TYPE,"*",err,error))// &
507  & " is invalid for a finite elasticity ALE Darcy equation."
508  CALL flagerror(local_error,err,error,*999)
509  END SELECT
510  CASE DEFAULT
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)
514  END SELECT
515 
516  !--------------------------------------------------------------------
517  ! q u a s i s t a t i c f i n i t e e l a s t i c i t y t r a n s i e n t D a r c y
518  !--------------------------------------------------------------------
520  SELECT CASE(problem_setup%SETUP_TYPE)
522  SELECT CASE(problem_setup%ACTION_TYPE)
524  !Do nothing????
526  !Do nothing???
527  CASE DEFAULT
528  local_error="The action type of "//trim(number_to_vstring(problem_setup%ACTION_TYPE,"*",err,error))// &
529  & " for a setup type of "//trim(number_to_vstring(problem_setup%SETUP_TYPE,"*",err,error))// &
530  & " is invalid for an finite elasticity ALE Darcy equation."
531  CALL flagerror(local_error,err,error,*999)
532  END SELECT
534  SELECT CASE(problem_setup%ACTION_TYPE)
536  !Set up a time control loop
537  CALL control_loop_create_start(problem,control_loop,err,error,*999)
538  CALL control_loop_type_set(control_loop,problem_control_time_loop_type,err,error,*999)
539  CALL control_loop_number_of_sub_loops_set(control_loop,1,err,error,*999)
540  CALL control_loop_output_type_set(control_loop,control_loop_progress_output,err,error,*999)
541 
542  !Set up a subiteration loop
543  CALL control_loop_sub_loop_get(control_loop,1,subiteration_loop,err,error,*999)
544  CALL control_loop_label_set(subiteration_loop,'SUBITERATION_LOOP',err,error,*999)
545  CALL control_loop_type_set(subiteration_loop,problem_control_while_loop_type,err,error,*999)
546  CALL control_loop_maximum_iterations_set(subiteration_loop,9,err,error,*999)
547  CALL control_loop_number_of_sub_loops_set(subiteration_loop,2,err,error,*999)
548  CALL control_loop_output_type_set(subiteration_loop,control_loop_progress_output,err,error,*999)
549 
550  !Set up load incremented control loop for Solid
551  CALL control_loop_sub_loop_get(subiteration_loop,1,solid_sub_loop,err,error,*999)
552  CALL control_loop_label_set(solid_sub_loop,'FINITE_ELASTICITY_LOAD_INCREMENT_LOOP',err,error,*999)
553  CALL control_loop_type_set(solid_sub_loop,problem_control_load_increment_loop_type,err,error,*999)
554  !For problems that require it, the user can get the solid subloop using:
555  !CALL CMISSProblemControlLoopGet(Problem,[1,1,CMISSControlLoopNode],ControlLoopSolid,Err)
556  !And then set the number of load increments to 3 for example with:
557  !CALL CMISSControlLoopMaximumIterationsSet(ControlLoopSolid,3,Err)
558  CALL control_loop_maximum_iterations_set(solid_sub_loop,1,err,error,*999)
559  CALL control_loop_output_type_set(solid_sub_loop,control_loop_progress_output,err,error,*999)
560 
561  !Set up control loop for Fluid
562  CALL control_loop_sub_loop_get(subiteration_loop,2,fluid_sub_loop,err,error,*999)
563  CALL control_loop_label_set(fluid_sub_loop,'DARCY_SIMPLE_LOOP',err,error,*999)
564  CALL control_loop_type_set(fluid_sub_loop,problem_control_simple_type,err,error,*999)
565  CALL control_loop_output_type_set(fluid_sub_loop,control_loop_progress_output,err,error,*999)
567  !Finish the control loops
568  control_loop_root=>problem%CONTROL_LOOP
569  CALL control_loop_get(control_loop_root,control_loop_node,control_loop,err,error,*999)
570  CALL control_loop_create_finish(control_loop,err,error,*999)
571  !Sub-loops are finished when parent is finished
572  CASE DEFAULT
573  local_error="The action type of "//trim(number_to_vstring(problem_setup%ACTION_TYPE,"*",err,error))// &
574  & " for a setup type of "//trim(number_to_vstring(problem_setup%SETUP_TYPE,"*",err,error))// &
575  & " is invalid for a finite elasticity ALE Darcy equation."
576  CALL flagerror(local_error,err,error,*999)
577  END SELECT
579  !Get the control loop
580  control_loop_root=>problem%CONTROL_LOOP
581  CALL control_loop_get(control_loop_root,control_loop_node,control_loop,err,error,*999)
582  SELECT CASE(problem_setup%ACTION_TYPE)
584  !Start the solvers creation for the solid solver
585  CALL control_loop_sub_loop_get(control_loop,1,subiteration_loop,err,error,*999)
586  CALL control_loop_sub_loop_get(subiteration_loop,1,solid_sub_loop,err,error,*999)
587  CALL solvers_create_start(solid_sub_loop,solid_solvers,err,error,*999)
588  CALL solvers_number_set(solid_solvers,1,err,error,*999)
589  !
590  !Set the solid solver to be a nonlinear solver for the finite elasticity
591  CALL solvers_solver_get(solid_solvers,1,solver_solid,err,error,*999)
592  CALL solver_type_set(solver_solid,solver_nonlinear_type,err,error,*999)
593  CALL solver_library_type_set(solver_solid,solver_petsc_library,err,error,*999)
594  !
595  !Start the solvers creation for the fluid solvers
596  CALL control_loop_sub_loop_get(subiteration_loop,2,fluid_sub_loop,err,error,*999)
597  CALL solvers_create_start(fluid_sub_loop,fluid_solvers,err,error,*999)
598  CALL solvers_number_set(fluid_solvers,1,err,error,*999)
599  !
600  !Set the solver to be a first-order dynamic solver for Darcy
601  CALL solvers_solver_get(fluid_solvers,1,solver,err,error,*999)
602  CALL solver_type_set(solver,solver_dynamic_type,err,error,*999)
603  CALL solver_dynamic_order_set(solver,solver_dynamic_first_order,err,error,*999)
604  !Set solver defaults
605  CALL solver_dynamic_degree_set(solver,solver_dynamic_first_degree,err,error,*999)
607  CALL solver_library_type_set(solver,solver_cmiss_library,err,error,*999)
609  !Get the solid solvers
610  CALL control_loop_sub_loop_get(control_loop,1,subiteration_loop,err,error,*999)
611  CALL control_loop_sub_loop_get(subiteration_loop,1,solid_sub_loop,err,error,*999)
612  CALL control_loop_solvers_get(solid_sub_loop,solid_solvers,err,error,*999)
613  !Finish the solvers creation
614  CALL solvers_create_finish(solid_solvers,err,error,*999)
615 
616  !Get the fluid solvers
617  CALL control_loop_sub_loop_get(subiteration_loop,2,fluid_sub_loop,err,error,*999)
618  CALL control_loop_solvers_get(fluid_sub_loop,fluid_solvers,err,error,*999)
619  !Finish the solvers creation
620  CALL solvers_create_finish(fluid_solvers,err,error,*999)
621  CASE DEFAULT
622  local_error="The action type of "//trim(number_to_vstring(problem_setup%ACTION_TYPE,"*",err,error))// &
623  & " for a setup type of "//trim(number_to_vstring(problem_setup%SETUP_TYPE,"*",err,error))// &
624  & " is invalid for a finite elasticity ALE Darcy equation."
625  CALL flagerror(local_error,err,error,*999)
626  END SELECT
628  SELECT CASE(problem_setup%ACTION_TYPE)
630  !Get the control loop and solvers
631  control_loop_root=>problem%CONTROL_LOOP
632  CALL control_loop_get(control_loop_root,control_loop_node,control_loop,err,error,*999)
633  !
634  CALL control_loop_sub_loop_get(control_loop,1,subiteration_loop,err,error,*999)
635  CALL control_loop_sub_loop_get(subiteration_loop,1,solid_sub_loop,err,error,*999)
636  CALL control_loop_solvers_get(solid_sub_loop,solid_solvers,err,error,*999)
637  !
638  !Get the finite elasticity solver and create the finite elasticity solver equations
639  CALL solvers_solver_get(solid_solvers,1,solver_solid,err,error,*999)
640  CALL solver_equations_create_start(solver_solid,solver_equations_solid,err,error,*999)
641  CALL solver_equations_linearity_type_set(solver_equations_solid,solver_equations_nonlinear,err,error,*999)
642  CALL solver_equations_time_dependence_type_set(solver_equations_solid,solver_equations_static,err,error,*999)
643  CALL solver_equations_sparsity_type_set(solver_equations_solid,solver_sparse_matrices,err,error,*999)
644  !
645  CALL control_loop_sub_loop_get(subiteration_loop,2,fluid_sub_loop,err,error,*999)
646  CALL control_loop_solvers_get(fluid_sub_loop,fluid_solvers,err,error,*999)
647  !
648  !Get the Darcy-ALE solver and create the Darcy-ALE solver equations
649  CALL solvers_solver_get(fluid_solvers,1,solver,err,error,*999)
650  CALL solver_equations_create_start(solver,solver_equations,err,error,*999)
651  CALL solver_equations_linearity_type_set(solver_equations,solver_equations_linear,err,error,*999)
653  CALL solver_equations_sparsity_type_set(solver_equations,solver_sparse_matrices,err,error,*999)
655  !Get the control loop
656  control_loop_root=>problem%CONTROL_LOOP
657  CALL control_loop_get(control_loop_root,control_loop_node,control_loop,err,error,*999)
658  CALL control_loop_sub_loop_get(control_loop,1,subiteration_loop,err,error,*999)
659  CALL control_loop_sub_loop_get(subiteration_loop,1,solid_sub_loop,err,error,*999)
660  CALL control_loop_solvers_get(solid_sub_loop,solid_solvers,err,error,*999)
661  !
662  !Finish the creation of the finite elasticity solver equations
663  CALL solvers_solver_get(solid_solvers,1,solver_solid,err,error,*999)
664  CALL solver_solver_equations_get(solver_solid,solver_equations_solid,err,error,*999)
665  CALL solver_equations_create_finish(solver_equations_solid,err,error,*999)
666  !
667  CALL control_loop_sub_loop_get(subiteration_loop,2,fluid_sub_loop,err,error,*999)
668  CALL control_loop_solvers_get(fluid_sub_loop,fluid_solvers,err,error,*999)
669  !
670  !Finish the creation of the Darcy-ALE solver equations
671  CALL solvers_solver_get(fluid_solvers,1,solver,err,error,*999)
672  CALL solver_solver_equations_get(solver,solver_equations,err,error,*999)
673  CALL solver_equations_create_finish(solver_equations,err,error,*999)
674  CASE DEFAULT
675  local_error="The action type of "//trim(number_to_vstring(problem_setup%ACTION_TYPE,"*",err,error))// &
676  & " for a setup type of "//trim(number_to_vstring(problem_setup%SETUP_TYPE,"*",err,error))// &
677  & " is invalid for a finite elasticity ALE Darcy equation."
678  CALL flagerror(local_error,err,error,*999)
679  END SELECT
680  CASE DEFAULT
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)
684  END SELECT
685 
686  !--------------------------------------------------------------------
687  ! q u a s i s t a t i c e l a s t i c i t y t r a n s i e n t D a r c y M A T E R I A L S O L V E
688  !--------------------------------------------------------------------
690  SELECT CASE(problem_setup%SETUP_TYPE)
692  SELECT CASE(problem_setup%ACTION_TYPE)
694  !Do nothing????
696  !Do nothing???
697  CASE DEFAULT
698  local_error="The action type of "//trim(number_to_vstring(problem_setup%ACTION_TYPE,"*",err,error))// &
699  & " for a setup type of "//trim(number_to_vstring(problem_setup%SETUP_TYPE,"*",err,error))// &
700  & " is invalid for an finite elasticity ALE Darcy equation."
701  CALL flagerror(local_error,err,error,*999)
702  END SELECT
704  SELECT CASE(problem_setup%ACTION_TYPE)
706  !Set up a time control loop
707  CALL control_loop_create_start(problem,control_loop,err,error,*999)
708  CALL control_loop_type_set(control_loop,problem_control_time_loop_type,err,error,*999)
709  CALL control_loop_number_of_sub_loops_set(control_loop,1,err,error,*999)
710  CALL control_loop_output_type_set(control_loop,control_loop_progress_output,err,error,*999)
711 
712  !Set up a subiteration loop
713  CALL control_loop_sub_loop_get(control_loop,1,subiteration_loop,err,error,*999)
714  CALL control_loop_type_set(subiteration_loop,problem_control_while_loop_type,err,error,*999)
715  CALL control_loop_maximum_iterations_set(subiteration_loop,9,err,error,*999)
716  CALL control_loop_number_of_sub_loops_set(subiteration_loop,2,err,error,*999)
717  CALL control_loop_output_type_set(subiteration_loop,control_loop_progress_output,err,error,*999)
718 
719  !Set up load incremented control loop for Solid
720  CALL control_loop_sub_loop_get(subiteration_loop,1,solid_sub_loop,err,error,*999)
721  CALL control_loop_type_set(solid_sub_loop,problem_control_load_increment_loop_type,err,error,*999)
722  !For problems that require it, the user can get the solid subloop using:
723  !CALL CMISSProblemControlLoopGet(Problem,[1,1,CMISSControlLoopNode],ControlLoopSolid,Err)
724  !And then set the number of load increments to 3 for example with:
725  !CALL CMISSControlLoopMaximumIterationsSet(ControlLoopSolid,3,Err)
726  CALL control_loop_maximum_iterations_set(solid_sub_loop,1,err,error,*999)
727  CALL control_loop_output_type_set(solid_sub_loop,control_loop_progress_output,err,error,*999)
728 
729  !Set up control loop for Fluid
730  CALL control_loop_sub_loop_get(subiteration_loop,2,fluid_sub_loop,err,error,*999)
731  CALL control_loop_type_set(fluid_sub_loop,problem_control_simple_type,err,error,*999)
732  CALL control_loop_output_type_set(fluid_sub_loop,control_loop_progress_output,err,error,*999)
734  !Finish the control loops
735  control_loop_root=>problem%CONTROL_LOOP
736  CALL control_loop_get(control_loop_root,control_loop_node,control_loop,err,error,*999)
737  CALL control_loop_create_finish(control_loop,err,error,*999)
738  !Sub-loops are finished when parent is finished
739  CASE DEFAULT
740  local_error="The action type of "//trim(number_to_vstring(problem_setup%ACTION_TYPE,"*",err,error))// &
741  & " for a setup type of "//trim(number_to_vstring(problem_setup%SETUP_TYPE,"*",err,error))// &
742  & " is invalid for a finite elasticity ALE Darcy equation."
743  CALL flagerror(local_error,err,error,*999)
744  END SELECT
746  !Get the control loop
747  control_loop_root=>problem%CONTROL_LOOP
748  CALL control_loop_get(control_loop_root,control_loop_node,control_loop,err,error,*999)
749  SELECT CASE(problem_setup%ACTION_TYPE)
751  !Start the solvers creation for the solid solver
752  CALL control_loop_sub_loop_get(control_loop,1,subiteration_loop,err,error,*999)
753  CALL control_loop_sub_loop_get(subiteration_loop,1,solid_sub_loop,err,error,*999)
754  CALL solvers_create_start(solid_sub_loop,solid_solvers,err,error,*999)
755  CALL solvers_number_set(solid_solvers,1,err,error,*999)
756  !
757  !Set the solid solver to be a nonlinear solver for the finite elasticity
758  CALL solvers_solver_get(solid_solvers,1,solver_solid,err,error,*999)
759  CALL solver_type_set(solver_solid,solver_nonlinear_type,err,error,*999)
760  CALL solver_library_type_set(solver_solid,solver_petsc_library,err,error,*999)
761  !
762  !Start the solvers creation for the fluid solvers
763  CALL control_loop_sub_loop_get(subiteration_loop,2,fluid_sub_loop,err,error,*999)
764  CALL solvers_create_start(fluid_sub_loop,fluid_solvers,err,error,*999)
765  CALL solvers_number_set(fluid_solvers,2,err,error,*999)
766  !
767  !Set the solver to be a linear solver for the material update
768  CALL solvers_solver_get(fluid_solvers,1,solver_mat_properties,err,error,*999)
769  CALL solver_type_set(solver_mat_properties,solver_linear_type,err,error,*999)
770  CALL solver_library_type_set(solver_mat_properties,solver_petsc_library,err,error,*999)
771  !
772  !Set the other solver to be a first-order dynamic solver for Darcy
773  CALL solvers_solver_get(fluid_solvers,2,solver,err,error,*999)
774  CALL solver_type_set(solver,solver_dynamic_type,err,error,*999)
775  CALL solver_dynamic_order_set(solver,solver_dynamic_first_order,err,error,*999)
776  !Set solver defaults
777  CALL solver_dynamic_degree_set(solver,solver_dynamic_first_degree,err,error,*999)
779  CALL solver_library_type_set(solver,solver_cmiss_library,err,error,*999)
781  !Get the solid solvers
782  CALL control_loop_sub_loop_get(control_loop,1,subiteration_loop,err,error,*999)
783  CALL control_loop_sub_loop_get(subiteration_loop,1,solid_sub_loop,err,error,*999)
784  CALL control_loop_solvers_get(solid_sub_loop,solid_solvers,err,error,*999)
785  !Finish the solvers creation
786  CALL solvers_create_finish(solid_solvers,err,error,*999)
787 
788  !Get the fluid solvers
789  CALL control_loop_sub_loop_get(subiteration_loop,2,fluid_sub_loop,err,error,*999)
790  CALL control_loop_solvers_get(fluid_sub_loop,fluid_solvers,err,error,*999)
791  !Finish the solvers creation
792  CALL solvers_create_finish(fluid_solvers,err,error,*999)
793  CASE DEFAULT
794  local_error="The action type of "//trim(number_to_vstring(problem_setup%ACTION_TYPE,"*",err,error))// &
795  & " for a setup type of "//trim(number_to_vstring(problem_setup%SETUP_TYPE,"*",err,error))// &
796  & " is invalid for a finite elasticity ALE Darcy equation."
797  CALL flagerror(local_error,err,error,*999)
798  END SELECT
800  SELECT CASE(problem_setup%ACTION_TYPE)
802  !Get the control loop and solvers
803  control_loop_root=>problem%CONTROL_LOOP
804  CALL control_loop_get(control_loop_root,control_loop_node,control_loop,err,error,*999)
805  !
806  CALL control_loop_sub_loop_get(control_loop,1,subiteration_loop,err,error,*999)
807  CALL control_loop_sub_loop_get(subiteration_loop,1,solid_sub_loop,err,error,*999)
808  CALL control_loop_solvers_get(solid_sub_loop,solid_solvers,err,error,*999)
809  !
810  !Get the finite elasticity solver and create the finite elasticity solver equations
811  CALL solvers_solver_get(solid_solvers,1,solver_solid,err,error,*999)
812  CALL solver_equations_create_start(solver_solid,solver_equations_solid,err,error,*999)
813  CALL solver_equations_linearity_type_set(solver_equations_solid,solver_equations_nonlinear,err,error,*999)
814  CALL solver_equations_time_dependence_type_set(solver_equations_solid,solver_equations_static,err,error,*999)
815  CALL solver_equations_sparsity_type_set(solver_equations_solid,solver_sparse_matrices,err,error,*999)
816  !
817  CALL control_loop_sub_loop_get(subiteration_loop,2,fluid_sub_loop,err,error,*999)
818  CALL control_loop_solvers_get(fluid_sub_loop,fluid_solvers,err,error,*999)
819  !
820  !Get the material-properties solver and create the material-properties solver equations
821  CALL solvers_solver_get(fluid_solvers,1,solver_mat_properties,err,error,*999)
822  CALL solver_equations_create_start(solver_mat_properties,solver_equations_mat_properties,err,error,*999)
823  CALL solver_equations_linearity_type_set(solver_equations_mat_properties,solver_equations_linear,err,error,*999)
824  CALL solver_equations_time_dependence_type_set(solver_equations_mat_properties,solver_equations_quasistatic, &
825  & err,error,*999)
826  CALL solver_equations_sparsity_type_set(solver_equations_mat_properties,solver_sparse_matrices,err,error,*999)
827  !
828  !Get the Darcy-ALE solver and create the Darcy-ALE solver equations
829  CALL solvers_solver_get(fluid_solvers,2,solver,err,error,*999)
830  CALL solver_equations_create_start(solver,solver_equations,err,error,*999)
831  CALL solver_equations_linearity_type_set(solver_equations,solver_equations_linear,err,error,*999)
833  CALL solver_equations_sparsity_type_set(solver_equations,solver_sparse_matrices,err,error,*999)
835  !Get the control loop
836  control_loop_root=>problem%CONTROL_LOOP
837  CALL control_loop_get(control_loop_root,control_loop_node,control_loop,err,error,*999)
838  CALL control_loop_sub_loop_get(control_loop,1,subiteration_loop,err,error,*999)
839  CALL control_loop_sub_loop_get(subiteration_loop,1,solid_sub_loop,err,error,*999)
840  CALL control_loop_solvers_get(solid_sub_loop,solid_solvers,err,error,*999)
841  !
842  !Finish the creation of the finite elasticity solver equations
843  CALL solvers_solver_get(solid_solvers,1,solver_solid,err,error,*999)
844  CALL solver_solver_equations_get(solver_solid,solver_equations_solid,err,error,*999)
845  CALL solver_equations_create_finish(solver_equations_solid,err,error,*999)
846  !
847  CALL control_loop_sub_loop_get(subiteration_loop,2,fluid_sub_loop,err,error,*999)
848  CALL control_loop_solvers_get(fluid_sub_loop,fluid_solvers,err,error,*999)
849  !
850  !Finish the creation of the material-properties solver equations
851  CALL solvers_solver_get(fluid_solvers,1,solver_mat_properties,err,error,*999)
852  CALL solver_solver_equations_get(solver_mat_properties,solver_equations_mat_properties,err,error,*999)
853  CALL solver_equations_create_finish(solver_equations_mat_properties,err,error,*999)
854  !
855  !Finish the creation of the Darcy-ALE solver equations
856  CALL solvers_solver_get(fluid_solvers,2,solver,err,error,*999)
857  CALL solver_solver_equations_get(solver,solver_equations,err,error,*999)
858  CALL solver_equations_create_finish(solver_equations,err,error,*999)
859  CASE DEFAULT
860  local_error="The action type of "//trim(number_to_vstring(problem_setup%ACTION_TYPE,"*",err,error))// &
861  & " for a setup type of "//trim(number_to_vstring(problem_setup%SETUP_TYPE,"*",err,error))// &
862  & " is invalid for a finite elasticity ALE Darcy equation."
863  CALL flagerror(local_error,err,error,*999)
864  END SELECT
865  CASE DEFAULT
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)
869  END SELECT
870 
871  !-----------------------------------------------------------------
872  ! c a s e d e f a u l t
873  !-----------------------------------------------------------------
874  CASE DEFAULT
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)
878 
879  END SELECT
880  ELSE
881  CALL flagerror("Problem is not associated.",err,error,*999)
882  ENDIF
883 
884  exits("ELASTICITY_DARCY_PROBLEM_SETUP")
885  RETURN
886 999 errorsexits("ELASTICITY_DARCY_PROBLEM_SETUP",err,error)
887  RETURN 1
888  END SUBROUTINE elasticity_darcy_problem_setup
889 
890  !
891  !================================================================================================================================
892  !
893 
895  SUBROUTINE elasticity_darcy_pre_solve(CONTROL_LOOP,SOLVER,ERR,ERROR,*)
897  !Argument variables
898  TYPE(control_loop_type), POINTER :: CONTROL_LOOP
899  TYPE(solver_type), POINTER :: SOLVER
900  INTEGER(INTG), INTENT(OUT) :: ERR
901  TYPE(varying_string), INTENT(OUT) :: ERROR
902 
903  !Local Variables
904  TYPE(varying_string) :: LOCAL_ERROR
905 
906  enters("ELASTICITY_DARCY_PRE_SOLVE",err,error,*999)
907 
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.", &
915  & err,error,*999)
916  END IF
917  SELECT CASE(control_loop%PROBLEM%SPECIFICATION(3))
919  IF(control_loop%LOOP_TYPE==problem_control_load_increment_loop_type.AND.solver%GLOBAL_NUMBER==1) THEN
920  CALL finite_elasticity_pre_solve(control_loop,solver,err,error,*999)
921  ELSE IF(control_loop%LOOP_TYPE==problem_control_simple_type) THEN
922  IF(solver%GLOBAL_NUMBER==1) THEN
923 ! IF(SOLVER%OUTPUT_TYPE>=SOLVER_PROGRESS_OUTPUT) THEN
924 ! CALL WRITE_STRING(GENERAL_OUTPUT_TYPE,"Now working on material parameters",ERR,ERROR,*999)
925 ! ENDIF
926  ELSE IF(solver%GLOBAL_NUMBER==2) THEN
927  IF(solver%OUTPUT_TYPE>=solver_progress_output) THEN
928  CALL write_string(general_output_type,"Now working on Darcy",err,error,*999)
929  ENDIF
930  ENDIF
931  CALL darcy_equation_pre_solve(control_loop,solver,err,error,*999)
932  ENDIF
933 
934 
937  IF(control_loop%LOOP_TYPE==problem_control_load_increment_loop_type.AND.solver%GLOBAL_NUMBER==1) THEN
938  CALL finite_elasticity_pre_solve(control_loop,solver,err,error,*999)
939  ELSE IF(control_loop%LOOP_TYPE==problem_control_simple_type) THEN
940  IF(solver%GLOBAL_NUMBER==1) THEN
941  IF(solver%OUTPUT_TYPE>=solver_progress_output) THEN
942  CALL write_string(general_output_type,"Now working on material parameters",err,error,*999)
943  ENDIF
944  ELSE IF(solver%GLOBAL_NUMBER==2) THEN
945  IF(solver%OUTPUT_TYPE>=solver_progress_output) THEN
946  CALL write_string(general_output_type,"Now working on Darcy",err,error,*999)
947  ENDIF
948  ENDIF
949  CALL darcy_equation_pre_solve(control_loop,solver,err,error,*999)
950  ENDIF
951 
952 
953 
954  CASE DEFAULT
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)
958  END SELECT
959  ELSE
960  CALL flagerror("Problem is not associated.",err,error,*999)
961  ENDIF
962  ELSE
963  CALL flagerror("Solver is not associated.",err,error,*999)
964  ENDIF
965  ELSE
966  CALL flagerror("Control loop is not associated.",err,error,*999)
967  ENDIF
968 
969  exits("ELASTICITY_DARCY_PRE_SOLVE")
970  RETURN
971 999 errorsexits("ELASTICITY_DARCY_PRE_SOLVE",err,error)
972  RETURN 1
973  END SUBROUTINE elasticity_darcy_pre_solve
974 
975  !
976  !================================================================================================================================
977  !
978 
980  SUBROUTINE elasticity_darcy_post_solve(CONTROL_LOOP,SOLVER,ERR,ERROR,*)
982  !Argument variables
983  TYPE(control_loop_type), POINTER :: CONTROL_LOOP
984  TYPE(solver_type), POINTER :: SOLVER
985  INTEGER(INTG), INTENT(OUT) :: ERR
986  TYPE(varying_string), INTENT(OUT) :: ERROR
987 
988  !Local Variables
989  TYPE(varying_string) :: LOCAL_ERROR
990 
991  enters("ELASTICITY_DARCY_POST_SOLVE",err,error,*999)
992 
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.", &
1000  & err,error,*999)
1001  END IF
1002  SELECT CASE(control_loop%PROBLEM%SPECIFICATION(3))
1005 ! CALL ELASTICITY_DARCY_POST_SOLVE_OUTPUT_DATA(CONTROL_LOOP,SOLVER,ERR,ERROR,*999)
1006  CALL finite_elasticity_post_solve(control_loop,solver,err,error,*999)
1007  CALL darcy_equation_post_solve(control_loop,solver,err,error,*999)
1008  CASE DEFAULT
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)
1012  END SELECT
1013  ELSE
1014  CALL flagerror("Problem is not associated.",err,error,*999)
1015  ENDIF
1016  ELSE
1017  CALL flagerror("Solver is not associated.",err,error,*999)
1018  ENDIF
1019  ELSE
1020  CALL flagerror("Control loop is not associated.",err,error,*999)
1021  ENDIF
1022 
1023  exits("ELASTICITY_DARCY_POST_SOLVE")
1024  RETURN
1025 999 errorsexits("ELASTICITY_DARCY_POST_SOLVE",err,error)
1026  RETURN 1
1027  END SUBROUTINE elasticity_darcy_post_solve
1028 
1029  !
1030  !================================================================================================================================
1031  !
1032 
1034  SUBROUTINE elasticity_darcy_control_loop_pre_loop(CONTROL_LOOP,ERR,ERROR,*)
1036  !Argument variables
1037  TYPE(control_loop_type), POINTER :: CONTROL_LOOP
1038  INTEGER(INTG), INTENT(OUT) :: ERR
1039  TYPE(varying_string), INTENT(OUT) :: ERROR
1040 
1041  !Local Variables
1042  REAL(DP) :: CURRENT_TIME,TIME_INCREMENT
1043  TYPE(solver_type), POINTER :: SOLVER_DARCY
1044  TYPE(control_loop_type), POINTER :: CONTROL_LOOP_DARCY
1045  TYPE(varying_string) :: LOCAL_ERROR
1046 
1047  enters("ELASTICITY_DARCY_CONTROL_LOOP_PRE_LOOP",err,error,*999)
1048 
1049  NULLIFY(control_loop_darcy)
1050  NULLIFY(solver_darcy)
1051 
1052  IF(ASSOCIATED(control_loop)) THEN
1053  IF(ASSOCIATED(control_loop%PROBLEM)) THEN
1054  ! Eventually we may want to do different things depending on problem type/subtype
1055  ! too but for now we can just check the loop type.
1056  SELECT CASE(control_loop%LOOP_TYPE)
1058  CALL control_loop_current_times_get(control_loop,current_time,time_increment,err,error,*999)
1059  IF(control_loop%OUTPUT_TYPE>=control_loop_progress_output) THEN
1060  CALL write_string(general_output_type,"==================================================",err,error,*999)
1061  CALL write_string(general_output_type,"=============== Starting time step ===============",err,error,*999)
1062  CALL write_string_value(general_output_type,"CURRENT_TIME = ",current_time,err,error,*999)
1063  CALL write_string_value(general_output_type,"TIME_INCREMENT = ",time_increment,err,error,*999)
1064  CALL write_string(general_output_type,"==================================================",err,error,*999)
1065  ENDIF
1066  IF(diagnostics1) THEN
1067  CALL write_string(diagnostic_output_type,"==================================================",err,error,*999)
1068  CALL write_string(diagnostic_output_type,"=============== Starting time step ===============",err,error,*999)
1069  CALL write_string_value(diagnostic_output_type,"CURRENT_TIME = ",current_time,err,error,*999)
1070  CALL write_string_value(diagnostic_output_type,"TIME_INCREMENT = ",time_increment,err,error,*999)
1071  CALL write_string(diagnostic_output_type,"==================================================",err,error,*999)
1072  ENDIF
1073  CALL darcy_control_time_loop_pre_loop(control_loop,err,error,*999)
1074  CALL finiteelasticity_controltimelooppreloop(control_loop,err,error,*999)
1075 
1077  !Subiteration loop
1078  IF(control_loop%OUTPUT_TYPE>=control_loop_progress_output) THEN
1079  CALL write_string(general_output_type,"+++++++++++++++++++++++++++++++",err,error,*999)
1080  CALL write_string(general_output_type,"++++ Starting subiteration ++++",err,error,*999)
1081  CALL write_string_value(general_output_type,"SUBITERATION_NUMBER = ", &
1082  & control_loop%WHILE_LOOP%ITERATION_NUMBER,err,error,*999)
1083  CALL write_string(general_output_type,"+++++++++++++++++++++++++++++++",err,error,*999)
1084  ENDIF
1085  IF(diagnostics1) THEN
1086  CALL write_string(diagnostic_output_type,"+++++++++++++++++++++++++++++++",err,error,*999)
1087  CALL write_string(diagnostic_output_type,"++++ Starting subiteration ++++",err,error,*999)
1088  CALL write_string_value(diagnostic_output_type,"SUBITERATION_NUMBER = ", &
1089  & control_loop%WHILE_LOOP%ITERATION_NUMBER,err,error,*999)
1090  CALL write_string(diagnostic_output_type,"+++++++++++++++++++++++++++++++",err,error,*999)
1091  ENDIF
1092  CALL control_loop_get(control_loop,(/2,control_loop_node/),control_loop_darcy,err,error,*999)
1093 
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.", &
1098  & err,error,*999)
1099  END IF
1100  SELECT CASE(control_loop%PROBLEM%SPECIFICATION(3))
1102  CALL solvers_solver_get(control_loop_darcy%SOLVERS,1,solver_darcy,err,error,*999)
1104  CALL solvers_solver_get(control_loop_darcy%SOLVERS,2,solver_darcy,err,error,*999)
1105  CASE DEFAULT
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)
1109  END SELECT
1110 
1111  CALL darcy_presolvestorepreviousiterate(control_loop,solver_darcy,err,error,*999)
1112 
1114  IF(control_loop%OUTPUT_TYPE>=control_loop_progress_output) THEN
1115  CALL write_string(general_output_type,"------------------------------------",err,error,*999)
1116  CALL write_string(general_output_type,"-- Starting fluid solve iteration --",err,error,*999)
1117  CALL write_string(general_output_type,"------------------------------------",err,error,*999)
1118  ENDIF
1119  IF(diagnostics1) THEN
1120  CALL write_string(diagnostic_output_type,"------------------------------------",err,error,*999)
1121  CALL write_string(diagnostic_output_type,"-- Starting fluid solve iteration --",err,error,*999)
1122  CALL write_string(diagnostic_output_type,"------------------------------------",err,error,*999)
1123  ENDIF
1124 
1126  IF(control_loop%OUTPUT_TYPE>=control_loop_progress_output) THEN
1127  CALL write_string(general_output_type,"------------------------------------",err,error,*999)
1128  CALL write_string(general_output_type,"-- Starting solid solve iteration --",err,error,*999)
1129  CALL write_string_value(general_output_type,"LOAD INCREMENT NUMBER = ", &
1130  & control_loop%LOAD_INCREMENT_LOOP%ITERATION_NUMBER,err,error,*999)
1131  CALL write_string(general_output_type,"------------------------------------",err,error,*999)
1132  ENDIF
1133  IF(diagnostics1) THEN
1134  CALL write_string(diagnostic_output_type,"------------------------------------",err,error,*999)
1135  CALL write_string(diagnostic_output_type,"-- Starting solid solve iteration --",err,error,*999)
1136  CALL write_string_value(diagnostic_output_type,"LOAD INCREMENT NUMBER = ", &
1137  & control_loop%LOAD_INCREMENT_LOOP%ITERATION_NUMBER,err,error,*999)
1138  CALL write_string(diagnostic_output_type,"------------------------------------",err,error,*999)
1139  ENDIF
1140 
1141  CASE DEFAULT
1142  !do nothing
1143  END SELECT
1144  ELSE
1145  CALL flagerror("Problem is not associated.",err,error,*999)
1146  ENDIF
1147  ELSE
1148  CALL flagerror("Control loop is not associated.",err,error,*999)
1149  ENDIF
1150 
1151  exits("ELASTICITY_DARCY_CONTROL_LOOP_PRE_LOOP")
1152  RETURN
1153 999 errorsexits("ELASTICITY_DARCY_CONTROL_LOOP_PRE_LOOP",err,error)
1154  RETURN 1
1156 
1157  !
1158  !================================================================================================================================
1159  !
1160 
1162  SUBROUTINE elasticity_darcy_control_loop_post_loop(CONTROL_LOOP,ERR,ERROR,*)
1164  !Argument variables
1165  TYPE(control_loop_type), POINTER :: CONTROL_LOOP
1166  INTEGER(INTG), INTENT(OUT) :: ERR
1167  TYPE(varying_string), INTENT(OUT) :: ERROR
1168 
1169  !Local Variables
1170  TYPE(varying_string) :: LOCAL_ERROR
1171  TYPE(solver_type), POINTER :: SOLVER_DARCY
1172  TYPE(control_loop_type), POINTER :: CONTROL_LOOP_DARCY
1173 
1174  NULLIFY(solver_darcy)
1175  NULLIFY(control_loop_darcy)
1176 
1177  enters("ELASTICITY_DARCY_CONTROL_LOOP_POST_LOOP",err,error,*999)
1178 
1179  IF(ASSOCIATED(control_loop)) THEN
1180  IF(ASSOCIATED(control_loop%PROBLEM)) THEN
1181  SELECT CASE(control_loop%LOOP_TYPE)
1183  IF(control_loop%OUTPUT_TYPE>=control_loop_progress_output) THEN
1184  CALL write_string(general_output_type,"End of time step",err,error,*999)
1185  ENDIF
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.", &
1191  & err,error,*999)
1192  END IF
1193  SELECT CASE(control_loop%PROBLEM%SPECIFICATION(3))
1195  !subiteration
1196  IF(control_loop%OUTPUT_TYPE>=control_loop_progress_output) THEN
1197  CALL write_string(general_output_type,"End of subiteration",err,error,*999)
1198  ENDIF
1199  CALL control_loop_get(control_loop,(/2,control_loop_node/),control_loop_darcy,err,error,*999)
1200  CALL solvers_solver_get(control_loop_darcy%SOLVERS,1,solver_darcy,err,error,*999)
1201  !CALL DARCY_EQUATION_ACCELERATE_CONVERGENCE(CONTROL_LOOP,SOLVER_DARCY,ERR,ERROR,*999)
1202  CALL darcy_equation_monitor_convergence(control_loop,solver_darcy,err,error,*999)
1203  !CALL DARCY_EQUATION_POST_SOLVE_OUTPUT_DATA(CONTROL_LOOP,SOLVER_DARCY,ERR,ERROR,*999)
1205  !subiteration
1206  IF(control_loop%OUTPUT_TYPE>=control_loop_progress_output) THEN
1207  CALL write_string(general_output_type,"End of subiteration",err,error,*999)
1208  ENDIF
1209  CALL control_loop_get(control_loop,(/2,control_loop_node/),control_loop_darcy,err,error,*999)
1210  CALL solvers_solver_get(control_loop_darcy%SOLVERS,2,solver_darcy,err,error,*999)
1211  !CALL DARCY_EQUATION_ACCELERATE_CONVERGENCE(CONTROL_LOOP,SOLVER_DARCY,ERR,ERROR,*999)
1212  CALL darcy_equation_monitor_convergence(control_loop,solver_darcy,err,error,*999)
1213  !CALL DARCY_EQUATION_POST_SOLVE_OUTPUT_DATA(CONTROL_LOOP,SOLVER_DARCY,ERR,ERROR,*999)
1214  CASE DEFAULT
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)
1218  END SELECT
1220  IF(control_loop%OUTPUT_TYPE>=control_loop_progress_output) THEN
1221  CALL write_string(general_output_type,"End of fluid solve iteration",err,error,*999)
1222  ENDIF
1224  IF(control_loop%OUTPUT_TYPE>=control_loop_progress_output) THEN
1225  CALL write_string(general_output_type,"End of solid solve iteration",err,error,*999)
1226  ENDIF
1227  CASE DEFAULT
1228  !do nothing
1229  END SELECT
1230  ELSE
1231  CALL flagerror("Problem is not associated.",err,error,*999)
1232  ENDIF
1233  ELSE
1234  CALL flagerror("Control loop is not associated.",err,error,*999)
1235  ENDIF
1236 
1237  exits("ELASTICITY_DARCY_CONTROL_LOOP_POST_LOOP")
1238  RETURN
1239 999 errorsexits("ELASTICITY_DARCY_CONTROL_LOOP_POST_LOOP",err,error)
1240  RETURN 1
1242 
1243  !
1244  !================================================================================================================================
1245  !
1246 
1248  SUBROUTINE elasticity_darcy_post_solve_output_data(CONTROL_LOOP,SOLVER,ERR,ERROR,*)
1250  !Argument variables
1251  TYPE(control_loop_type), POINTER :: CONTROL_LOOP
1252  TYPE(solver_type), POINTER :: SOLVER
1253  INTEGER(INTG), INTENT(OUT) :: ERR
1254  TYPE(varying_string), INTENT(OUT) :: ERROR
1255 
1256  !Local Variables
1257  TYPE(varying_string) :: LOCAL_ERROR
1258 
1259  enters("ELASTICITY_DARCY_POST_SOLVE_OUTPUT_DATA",err,error,*999)
1260 
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.", &
1268  & err,error,*999)
1269  END IF
1270  SELECT CASE(control_loop%PROBLEM%SPECIFICATION(3))
1273 
1274  IF(solver%GLOBAL_NUMBER==1) THEN
1275  CALL finite_elasticity_post_solve_output_data(control_loop,solver,err,error,*999)
1276  ELSE IF(solver%GLOBAL_NUMBER==2.OR.solver%GLOBAL_NUMBER==3) THEN
1277  CALL darcy_equation_post_solve_output_data(control_loop,solver,err,error,*999)
1278  ENDIF
1279 
1280  CASE DEFAULT
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)
1284  END SELECT
1285  ELSE
1286  CALL flagerror("Problem is not associated.",err,error,*999)
1287  ENDIF
1288  ELSE
1289  CALL flagerror("Solver is not associated.",err,error,*999)
1290  ENDIF
1291  ELSE
1292  CALL flagerror("Control loop is not associated.",err,error,*999)
1293  ENDIF
1294 
1295  exits("ELASTICITY_DARCY_POST_SOLVE_OUTPUT_DATA")
1296  RETURN
1297 999 errorsexits("ELASTICITY_DARCY_POST_SOLVE_OUTPUT_DATA",err,error)
1298  RETURN 1
1300 
1301  !
1302  !================================================================================================================================
1303  !
1304 
1305 
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.
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.
Definition: strings.f90:161
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.
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.
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.
Definition: types.f90:1941
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.
Definition: strings.f90:45
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.
Definition: types.f90:2805
integer(intg), parameter problem_control_simple_type
Simple, one iteration control loop.
This module contains routines for timing the program.
Definition: timer_f.f90:45
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.
Definition: maths.f90:45
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.
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, 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.
Definition: constants.f90:45
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.
Definition: types.f90:70
Write a string to a given output stream.
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.
Definition: types.f90:2452
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.
Definition: types.f90:3221
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.
Definition: types.f90:1866
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.
Definition: kinds.f90:45
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.
This module handles all formating and input and output.