OpenCMISS-Iron Internal API Documentation
fsi_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 field_routines
60  USE input_output
62  USE kinds
65  USE strings
66  USE solver_routines
67  USE types
68 
69 #include "macros.h"
70 
71  IMPLICIT NONE
72 
76 
77  PUBLIC fsi_problem_setup
79 
81 
82  PUBLIC fsi_pre_solve
83  PUBLIC fsi_post_solve
84 
87 
88 CONTAINS
89 
90  !
91  !================================================================================================================================
92  !
93 
95  SUBROUTINE fsi_equations_set_solution_method_set(EQUATIONS_SET,SOLUTION_METHOD,Err,Error,*)
96 
97  !Argument variables
98  TYPE(equations_set_type), POINTER :: EQUATIONS_SET
99  INTEGER(INTG), INTENT(IN) :: SOLUTION_METHOD
100  INTEGER(INTG), INTENT(OUT) :: Err
101  TYPE(varying_string), INTENT(OUT) :: Error
102  !Local Variables
103  TYPE(varying_string) :: LOCAL_ERROR
104 
105  enters("FSI_EQUATIONS_SET_SOLUTION_METHOD_SET",err,error,*999)
106 
107  IF(ASSOCIATED(equations_set)) THEN
108  IF(.NOT.ALLOCATED(equations_set%SPECIFICATION)) THEN
109  CALL flagerror("Equations set specification is not allocated.",err,error,*999)
110  ELSE IF(SIZE(equations_set%SPECIFICATION,1)/=3) THEN
111  CALL flagerror("Equations set specification must have three entries for a "// &
112  & "finite elasticity Navier-Stokes class equations set.",err,error,*999)
113  END IF
114  SELECT CASE(equations_set%SPECIFICATION(3))
116  SELECT CASE(solution_method)
118  equations_set%SOLUTION_METHOD=equations_set_fem_solution_method
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)
128  CALL flagerror("Not implemented.",err,error,*999)
129  CASE DEFAULT
130  local_error="The specified solution method of "//trim(number_to_vstring(solution_method,"*",err,error))//" is invalid."
131  CALL flagerror(local_error,err,error,*999)
132  END SELECT
133  CASE DEFAULT
134  local_error="Equations set subtype of "//trim(number_to_vstring(equations_set%SPECIFICATION(3),"*",err,error))// &
135  & " is not valid for a finite elasticity navier stokes equation type of a multi physics equations set class."
136  CALL flagerror(local_error,err,error,*999)
137  END SELECT
138  ELSE
139  CALL flagerror("Equations set is not associated.",err,error,*999)
140  ENDIF
141 
142  exits("FSI_EQUATIONS_SET_SOLUTION_METHOD_SET")
143  RETURN
144 999 errorsexits("FSI_EQUATIONS_SET_SOLUTION_METHOD_SET",err,error)
145  RETURN 1
147 
148  !
149  !================================================================================================================================
150  !
151 
153  SUBROUTINE fsi_equations_set_setup(EQUATIONS_SET,EQUATIONS_SET_SETUP,Err,Error,*)
155  !Argument variables
156  TYPE(equations_set_type), POINTER :: EQUATIONS_SET
157  TYPE(equations_set_setup_type), INTENT(INOUT) :: EQUATIONS_SET_SETUP
158  INTEGER(INTG), INTENT(OUT) :: Err
159  TYPE(varying_string), INTENT(OUT) :: Error
160 
161 
162  enters("FSI_EQUATIONS_SET_SETUP",err,error,*999)
163 
164  CALL flagerror("FSI_EQUATIONS_SET_SETUP is not implemented.",err,error,*999)
165 
166  exits("FSI_EQUATIONS_SET_SETUP")
167  RETURN
168 999 errorsexits("FSI_EQUATIONS_SET_SETUP",err,error)
169  RETURN 1
170  END SUBROUTINE fsi_equations_set_setup
171 
172  !
173  !================================================================================================================================
174  !
175 
177  SUBROUTINE fsi_finite_element_calculate(EQUATIONS_SET,ELEMENT_NUMBER,Err,Error,*)
179  !Argument variables
180  TYPE(equations_set_type), POINTER :: EQUATIONS_SET
181  INTEGER(INTG), INTENT(IN) :: ELEMENT_NUMBER
182  INTEGER(INTG), INTENT(OUT) :: Err
183  TYPE(varying_string), INTENT(OUT) :: Error
184 
185  enters("FSI_FINITE_ELEMENT_CALCULATE",err,error,*999)
186 
187  CALL flagerror("FSI_FINITE_ELEMENT_CALCULATE is not implemented.",err,error,*999)
188 
189  exits("FSI_FINITE_ELEMENT_CALCULATE")
190  RETURN
191 999 errorsexits("FSI_FINITE_ELEMENT_CALCULATE",err,error)
192  RETURN 1
193  END SUBROUTINE fsi_finite_element_calculate
194 
195  !
196  !================================================================================================================================
197  !
198 
200  SUBROUTINE fsi_equationssetspecificationset(equationsSet,specification,Err,Error,*)
202  !Argument variables
203  TYPE(equations_set_type), POINTER :: equationsSet
204  INTEGER(INTG), INTENT(IN) :: specification(:)
205  INTEGER(INTG), INTENT(OUT) :: err
206  TYPE(varying_string), INTENT(OUT) :: error
207  !Local Variables
208 
209  enters("FSI_EquationsSetSpecificationSet",err,error,*999)
210 
211  CALL flagerror("FSI_EquationsSetSpecificationSet is not implemented.",err,error,*999)
212 
213  exits("FSI_EquationsSetSpecificationSet")
214  RETURN
215 999 errors("FSI_EquationsSetSpecificationSet",err,error)
216  exits("FSI_EquationsSetSpecificationSet")
217  RETURN 1
218 
219  END SUBROUTINE fsi_equationssetspecificationset
220 
221  !
222  !================================================================================================================================
223  !
224 
226  SUBROUTINE fsi_problemspecificationset(problem,problemSpecification,err,error,*)
228  !Argument variables
229  TYPE(problem_type), POINTER :: problem
230  INTEGER(INTG), INTENT(IN) :: problemSpecification(:)
231  INTEGER(INTG), INTENT(OUT) :: err
232  TYPE(varying_string), INTENT(OUT) :: error
233  !Local Variables
234  TYPE(varying_string) :: localError
235  INTEGER(INTG) :: problemSubtype
236 
237  enters("FSI_ProblemSpecificationSet",err,error,*999)
238 
239  IF(ASSOCIATED(problem)) THEN
240  IF(SIZE(problemspecification,1)==3) THEN
241  problemsubtype=problemspecification(3)
242  SELECT CASE(problemsubtype)
244  !ok
245  CASE DEFAULT
246  localerror="The third problem specification of "//trim(numbertovstring(problemsubtype,"*",err,error))// &
247  & " is not valid for a finite elasticity Navier-Stokes type of a multi physics problem."
248  CALL flagerror(localerror,err,error,*999)
249  END SELECT
250  IF(ALLOCATED(problem%specification)) THEN
251  CALL flagerror("Problem specification is already allocated.",err,error,*999)
252  ELSE
253  ALLOCATE(problem%specification(3),stat=err)
254  IF(err/=0) CALL flagerror("Could not allocate problem specification.",err,error,*999)
255  END IF
256  problem%specification(1:3)=[problem_multi_physics_class, &
258  & problemsubtype]
259  ELSE
260  CALL flagerror("Finite elasticity Navier-Stokes problem specificaion must have three entries.",err,error,*999)
261  END IF
262  ELSE
263  CALL flagerror("Problem is not associated.",err,error,*999)
264  END IF
265 
266  exits("FSI_ProblemSpecificationSet")
267  RETURN
268 999 errors("FSI_ProblemSpecificationSet",err,error)
269  exits("FSI_ProblemSpecificationSet")
270  RETURN 1
271 
272  END SUBROUTINE fsi_problemspecificationset
273 
274  !
275  !================================================================================================================================
276  !
277 
279  SUBROUTINE fsi_problem_setup(PROBLEM,PROBLEM_SETUP,Err,Error,*)
281  !Argument variables
282  TYPE(problem_type), POINTER :: PROBLEM
283  TYPE(problem_setup_type), INTENT(INOUT) :: PROBLEM_SETUP
284  INTEGER(INTG), INTENT(OUT) :: Err
285  TYPE(varying_string), INTENT(OUT) :: Error
286  !Local Variables
287  TYPE(control_loop_type), POINTER :: CONTROL_LOOP,CONTROL_LOOP_ROOT
288  TYPE(control_loop_type), POINTER :: MovingMeshSubLoop,ElasticitySubLoop
289  TYPE(solver_type), POINTER :: SOLVER,MOVING_MESH_SOLVER
290  TYPE(solver_equations_type), POINTER :: SOLVER_EQUATIONS,MovingMeshSolverEquations,MOVING_MESH_SOLVER_EQUATIONS
291  TYPE(solvers_type), POINTER :: MovingMeshSolvers,SOLVERS
292  TYPE(varying_string) :: LOCAL_ERROR
293 
294  enters("FSI_PROBLEM_SETUP",err,error,*999)
295 
296  NULLIFY(control_loop)
297  NULLIFY(movingmeshsubloop)
298  NULLIFY(elasticitysubloop)
299  NULLIFY(solver)
300  NULLIFY(moving_mesh_solver)
301  NULLIFY(solver_equations)
302  NULLIFY(moving_mesh_solver_equations)
303  NULLIFY(movingmeshsolverequations)
304  NULLIFY(solvers)
305  NULLIFY(movingmeshsolvers)
306 
307  IF(ASSOCIATED(problem)) THEN
308  IF(ALLOCATED(problem%specification)) THEN
309  IF(.NOT.ALLOCATED(problem%specification)) THEN
310  CALL flagerror("Problem specification is not allocated.",err,error,*999)
311  ELSE IF(SIZE(problem%specification,1)<3) THEN
312  CALL flagerror("Problem specification must have three entries for a finite elasticity-Darcy problem.", &
313  & err,error,*999)
314  END IF
315  ELSE
316  CALL flagerror("Problem specification is not allocated.",err,error,*999)
317  END IF
318  SELECT CASE(problem%SPECIFICATION(3))
319  !Standard FiniteElasticity NavierStokes ALE
321  SELECT CASE(problem_setup%SETUP_TYPE)
323  SELECT CASE(problem_setup%ACTION_TYPE)
325  !Do nothing
327  !Do nothing
328  CASE DEFAULT
329  local_error="The action type of "//trim(number_to_vstring(problem_setup%ACTION_TYPE,"*",err,error))// &
330  & " for a setup type of "//trim(number_to_vstring(problem_setup%SETUP_TYPE,"*",err,error))// &
331  & " is invalid for an finite elasticity ALE navier stokes equation."
332  CALL flagerror(local_error,err,error,*999)
333  END SELECT
335  SELECT CASE(problem_setup%ACTION_TYPE)
337  !Set up a time control loop as parent loop
338  CALL control_loop_create_start(problem,control_loop,err,error,*999)
339  CALL control_loop_type_set(control_loop,problem_control_time_loop_type,err,error,*999)
340  CALL control_loop_output_type_set(control_loop,control_loop_progress_output,err,error,*999)
342  !Finish the control loops
343  control_loop_root=>problem%CONTROL_LOOP
344  CALL control_loop_get(control_loop_root,control_loop_node,control_loop,err,error,*999)
345  CALL control_loop_create_finish(control_loop,err,error,*999)
346  CASE DEFAULT
347  local_error="The action type of "//trim(number_to_vstring(problem_setup%ACTION_TYPE,"*",err,error))// &
348  & " for a setup type of "//trim(number_to_vstring(problem_setup%SETUP_TYPE,"*",err,error))// &
349  & " is invalid for a finite elasticity navier stokes equation."
350  CALL flagerror(local_error,err,error,*999)
351  END SELECT
353  !Get the control loop
354  control_loop_root=>problem%CONTROL_LOOP
355  CALL control_loop_get(control_loop_root,control_loop_node,control_loop,err,error,*999)
356  SELECT CASE(problem_setup%ACTION_TYPE)
358  !Start the solvers creation
359  CALL solvers_create_start(control_loop,solvers,err,error,*999)
360  CALL solvers_number_set(solvers,2,err,error,*999)
361  !Set the first solver to be a linear solver for the Laplace mesh movement problem
362  CALL solvers_solver_get(solvers,2,moving_mesh_solver,err,error,*999)
363  CALL solver_type_set(moving_mesh_solver,solver_linear_type,err,error,*999)
364  !Set solver defaults
365  CALL solver_library_type_set(moving_mesh_solver,solver_petsc_library,err,error,*999)
366  !Set the solver to be a first order dynamic solver
367  CALL solvers_solver_get(solvers,1,solver,err,error,*999)
368  CALL solver_type_set(solver,solver_dynamic_type,err,error,*999)
370  CALL solver_dynamic_order_set(solver,solver_dynamic_first_order,err,error,*999)
371  !Set solver defaults
372  CALL solver_dynamic_degree_set(solver,solver_dynamic_first_degree,err,error,*999)
374  CALL solver_library_type_set(solver,solver_cmiss_library,err,error,*999)
376  !Get the solvers
377  CALL control_loop_solvers_get(control_loop,solvers,err,error,*999)
378  !Finish the solvers creation
379  CALL solvers_create_finish(solvers,err,error,*999)
380  CASE DEFAULT
381  local_error="The action type of "//trim(number_to_vstring(problem_setup%ACTION_TYPE,"*",err,error))// &
382  & " for a setup type of "//trim(number_to_vstring(problem_setup%SETUP_TYPE,"*",err,error))// &
383  & " is invalid for a finite elasticity navier stokes equation."
384  CALL flagerror(local_error,err,error,*999)
385  END SELECT
387  SELECT CASE(problem_setup%ACTION_TYPE)
389  !Get the control loop
390  control_loop_root=>problem%CONTROL_LOOP
391  CALL control_loop_get(control_loop_root,control_loop_node,control_loop,err,error,*999)
392  !Get the solver
393  CALL control_loop_solvers_get(control_loop,solvers,err,error,*999)
394  CALL solvers_solver_get(solvers,2,moving_mesh_solver,err,error,*999)
395  !Create the solver equations
396  CALL solver_equations_create_start(moving_mesh_solver,moving_mesh_solver_equations,err,error,*999)
397  CALL solver_equations_linearity_type_set(moving_mesh_solver_equations,solver_equations_linear,err,error,*999)
398  CALL solver_equations_time_dependence_type_set(moving_mesh_solver_equations,solver_equations_static, &
399  & err,error,*999)
400  CALL solver_equations_sparsity_type_set(moving_mesh_solver_equations,solver_sparse_matrices,err,error,*999)
401  CALL solvers_solver_get(solvers,1,solver,err,error,*999)
402  !Create the solver equations
403  CALL solver_equations_create_start(solver,solver_equations,err,error,*999)
404  CALL solver_equations_linearity_type_set(solver_equations,solver_equations_nonlinear,err,error,*999)
406  & err,error,*999)
407  CALL solver_equations_sparsity_type_set(solver_equations,solver_sparse_matrices,err,error,*999)
409  !Get the control loop
410  control_loop_root=>problem%CONTROL_LOOP
411  CALL control_loop_get(control_loop_root,control_loop_node,control_loop,err,error,*999)
412  !Get the solver equations
413  CALL control_loop_solvers_get(control_loop,solvers,err,error,*999)
414  CALL solvers_solver_get(solvers,2,moving_mesh_solver,err,error,*999)
415  CALL solver_solver_equations_get(moving_mesh_solver,moving_mesh_solver_equations,err,error,*999)
416  !Finish the solver equations creation
417  CALL solver_equations_create_finish(moving_mesh_solver_equations,err,error,*999)
418 
419  CALL solvers_solver_get(solvers,1,solver,err,error,*999)
420  CALL solver_solver_equations_get(solver,solver_equations,err,error,*999)
421  !Finish the solver equations creation
422  CALL solver_equations_create_finish(solver_equations,err,error,*999)
423  CASE DEFAULT
424  local_error="The action type of "//trim(number_to_vstring(problem_setup%ACTION_TYPE,"*",err,error))// &
425  & " for a setup type of "//trim(number_to_vstring(problem_setup%SETUP_TYPE,"*",err,error))// &
426  & " is invalid for a finite elasticity navier stokes equation."
427  CALL flagerror(local_error,err,error,*999)
428  END SELECT
429  CASE DEFAULT
430  local_error="The setup type of "//trim(number_to_vstring(problem_setup%SETUP_TYPE,"*",err,error))// &
431  & " is invalid for a finite elasticity ALE navier stokes equation."
432  CALL flagerror(local_error,err,error,*999)
433  END SELECT
434  CASE DEFAULT
435  local_error="The problem subtype of "//trim(number_to_vstring(problem%SPECIFICATION(3),"*",err,error))// &
436  & " does not equal a standard finite elasticity navier stokes equation subtype."
437  CALL flagerror(local_error,err,error,*999)
438  END SELECT
439  ELSE
440  CALL flagerror("Problem is not associated.",err,error,*999)
441  ENDIF
442 
443  exits("FSI_PROBLEM_SETUP")
444  RETURN
445 999 errorsexits("FSI_PROBLEM_SETUP",err,error)
446  RETURN 1
447  END SUBROUTINE fsi_problem_setup
448 
449  !
450  !================================================================================================================================
451  !
452 
454  SUBROUTINE fsi_pre_solve(ControlLoop,Solver,Err,Error,*)
456  !Argument variables
457  TYPE(control_loop_type), POINTER :: ControlLoop
458  TYPE(solver_type), POINTER :: Solver
459  INTEGER(INTG), INTENT(OUT) :: Err
460  TYPE(varying_string), INTENT(OUT) :: Error
461 
462  !Local Variables
463  TYPE(varying_string) :: LOCAL_ERROR
464 
465  enters("FSI_PRE_SOLVE",err,error,*999)
466 
467  IF(ASSOCIATED(controlloop)) THEN
468  IF(ASSOCIATED(solver)) THEN
469  IF(ASSOCIATED(controlloop%problem)) THEN
470  IF(.NOT.ALLOCATED(controlloop%problem%specification)) THEN
471  CALL flagerror("Problem specification is not allocated.",err,error,*999)
472  ELSE IF(SIZE(controlloop%problem%specification,1)<3) THEN
473  CALL flagerror("Problem specification must have three entries for an elasticity Navier-Stokes problem.",err,error,*999)
474  END IF
475  SELECT CASE(controlloop%problem%specification(3))
477  IF(controlloop%LOOP_TYPE==problem_control_time_loop_type) THEN
478  CALL write_string(general_output_type,"Running pre-solve steps.",err,error,*999)
479  !Pre solve for ALE NavierStokes equations set
480  CALL navier_stokes_pre_solve(solver,err,error,*999)
481  !Pre solve for FiniteElasticity equations set
482  !Nothing to be done???
483  ELSE
484  CALL flagerror("Incorrect loop type. Must be time loop.",err,error,*999)
485  ENDIF
486  CASE DEFAULT
487  local_error="Problem subtype "//trim(number_to_vstring(controlloop%PROBLEM%SPECIFICATION(3),"*",err,error))// &
488  & " is not valid for a finite elasticity navier stokes type of a multi physics problem class."
489  CALL flagerror(local_error,err,error,*999)
490  END SELECT
491  ELSE
492  CALL flagerror("Problem is not associated.",err,error,*999)
493  ENDIF
494  ELSE
495  CALL flagerror("Solver is not associated.",err,error,*999)
496  ENDIF
497  ELSE
498  CALL flagerror("Control loop is not associated.",err,error,*999)
499  ENDIF
500 
501  exits("FSI_PRE_SOLVE")
502  RETURN
503 999 errorsexits("FSI_PRE_SOLVE",err,error)
504  RETURN 1
505  END SUBROUTINE fsi_pre_solve
506 
507  !
508  !================================================================================================================================
509  !
510 
512  SUBROUTINE fsi_post_solve(ControlLoop,Solver,Err,Error,*)
514  !Argument variables
515  TYPE(control_loop_type), POINTER :: ControlLoop
516  TYPE(solver_type), POINTER :: Solver,Solver2
517  INTEGER(INTG), INTENT(OUT) :: Err
518  TYPE(varying_string), INTENT(OUT) :: Error
519 
520  !Local Variables
521  TYPE(varying_string) :: LOCAL_ERROR
522 
523  enters("FSI_POST_SOLVE",err,error,*999)
524 
525  NULLIFY(solver2)
526 
527  IF(ASSOCIATED(controlloop)) THEN
528  IF(ASSOCIATED(solver)) THEN
529  IF(ASSOCIATED(controlloop%problem)) THEN
530  IF(.NOT.ALLOCATED(controlloop%problem%specification)) THEN
531  CALL flagerror("Problem specification is not allocated.",err,error,*999)
532  ELSE IF(SIZE(controlloop%problem%specification,1)<3) THEN
533  CALL flagerror("Problem specification must have three entries for an elasticity Navier-Stokes problem.",err,error,*999)
534  END IF
535  SELECT CASE(controlloop%PROBLEM%SPECIFICATION(3))
537  !Post solve for the linear solver
538  IF(solver%SOLVE_TYPE==solver_linear_type) THEN
539  CALL write_string(general_output_type,"Mesh movement post solve... ",err,error,*999)
540  CALL solvers_solver_get(solver%SOLVERS,1,solver2,err,error,*999)
541  ! CALL SOLVERS_SOLVER_GET(Solver%SOLVERS,2,Solver2,ERR,ERROR,*999)
542  IF(ASSOCIATED(solver2%DYNAMIC_SOLVER)) THEN
543  solver2%DYNAMIC_SOLVER%ALE=.true.
544  ELSE
545  CALL flagerror("Dynamic solver is not associated for ALE problem.",err,error,*999)
546  END IF
547  !Post solve for the dynamic solver
548  ELSE IF(solver%SOLVE_TYPE==solver_dynamic_type) THEN
549  CALL write_string(general_output_type,"ALE Navier-Stokes post solve... ",err,error,*999)
550  ! IF(.NOT.ASSOCIATED(ControlLoop%TIME_LOOP)) CALL FlagError("Time loop is not associated.",Err,Error,*999)
551  ! !Export solid fields
552  ! FileName="SolidStep00"//TRIM(NUMBER_TO_VSTRING( &
553  ! & INT(ControlLoop%TIME_LOOP%CURRENT_TIME/ControlLoop%TIME_LOOP%TIME_INCREMENT),"*",Err,Error))// &
554  ! & "output"
555  ! Method="FORTRAN"
556  ! CALL FIELD_IO_NODES_EXPORT(Solver%SOLVER_EQUATIONS%SOLVER_MAPPING%EQUATIONS_SETS(1)%PTR%REGION%FIELDS, &
557  ! & FileName,Method,ERR,ERROR,*999)
558  ! CALL FIELD_IO_ELEMENTS_EXPORT(Solver%SOLVER_EQUATIONS%SOLVER_MAPPING%EQUATIONS_SETS(1)%PTR%REGION%FIELDS, &
559  ! & FileName,Method,ERR,ERROR,*999)
560  ! !Export fluid fields
561  ! FileName="FluidStep00"//TRIM(NUMBER_TO_VSTRING( &
562  ! & INT(ControlLoop%TIME_LOOP%CURRENT_TIME/ControlLoop%TIME_LOOP%TIME_INCREMENT),"*",Err,Error))// &
563  ! & "output"
564  ! Method="FORTRAN"
565  ! CALL FIELD_IO_NODES_EXPORT(Solver%SOLVER_EQUATIONS%SOLVER_MAPPING%EQUATIONS_SETS(2)%PTR%REGION%FIELDS, &
566  ! & FileName,Method,ERR,ERROR,*999)
567  ! CALL FIELD_IO_ELEMENTS_EXPORT(Solver%SOLVER_EQUATIONS%SOLVER_MAPPING%EQUATIONS_SETS(2)%PTR%REGION%FIELDS, &
568  ! & FileName,Method,ERR,ERROR,*999)
569  ELSE
570  local_error="Problem subtype "//trim(number_to_vstring(controlloop%PROBLEM%SPECIFICATION(3),"*",err,error))// &
571  & " for a FiniteElasticity-NavierStokes type of a multi physics problem class has unknown solver solve type."
572  CALL flagerror(local_error,err,error,*999)
573  END IF
574  CASE DEFAULT
575  local_error="Problem subtype "//trim(number_to_vstring(controlloop%PROBLEM%SPECIFICATION(3),"*",err,error))// &
576  & " is not valid for a FiniteElasticity-NavierStokes type of a multi physics problem class."
577  CALL flagerror(local_error,err,error,*999)
578  END SELECT
579  ELSE
580  CALL flagerror("Problem is not associated.",err,error,*999)
581  ENDIF
582  ELSE
583  CALL flagerror("Solver is not associated.",err,error,*999)
584  ENDIF
585  ELSE
586  CALL flagerror("Control loop is not associated.",err,error,*999)
587  ENDIF
588 
589  exits("FSI_POST_SOLVE")
590  RETURN
591 999 errorsexits("FSI_POST_SOLVE",err,error)
592  RETURN 1
593  END SUBROUTINE fsi_post_solve
594 
595  !
596  !================================================================================================================================
597  !
598 
600  SUBROUTINE fsi_control_loop_pre_loop(ControlLoop,Err,Error,*)
602  !Argument variables
603  TYPE(control_loop_type), POINTER :: ControlLoop
604  INTEGER(INTG), INTENT(OUT) :: Err
605  TYPE(varying_string), INTENT(OUT) :: Error
606 
607  !Local Variables
608 
609  enters("FSI_CONTROL_LOOP_PRE_LOOP",err,error,*999)
610 
611  CALL flagerror("FSI_CONTROL_LOOP_PRE_LOOP not implemented.",err,error,*999)
612 
613  exits("FSI_CONTROL_LOOP_PRE_LOOP")
614  RETURN
615 999 errorsexits("FSI_CONTROL_LOOP_PRE_LOOP",err,error)
616  RETURN 1
617  END SUBROUTINE fsi_control_loop_pre_loop
618 
619  !
620  !================================================================================================================================
621  !
622 
624  SUBROUTINE fsi_control_loop_post_loop(ControlLoop,Err,Error,*)
626  !Argument variables
627  TYPE(control_loop_type), POINTER :: ControlLoop
628  INTEGER(INTG), INTENT(OUT) :: Err
629  TYPE(varying_string), INTENT(OUT) :: Error
630 
631  !Local Variables
632  TYPE(solver_type), POINTER :: DynamicSolver,LinearSolver
633  TYPE(control_loop_time_type), POINTER :: TimeLoop
634  TYPE(solver_equations_type), POINTER :: DynamicSolverEquations
635  TYPE(solver_mapping_type), POINTER :: DynamicSolverMapping
636  TYPE(equations_set_type), POINTER :: SolidEquationsSet,FluidEquationsSet,EquationsSet
637  TYPE(field_type), POINTER :: SolidGeometricField,InterfaceGeometricField,SolidDependentField
638  TYPE(interface_condition_type), POINTER :: InterfaceCondition
639  TYPE(interface_type), POINTER :: FSInterface
640  TYPE(nodes_type), POINTER :: InterfaceNodes
641  TYPE(varying_string) :: Method,SolidFileName,FluidFileName,InterfaceFileName
642  REAL(DP) :: StartTime,CurrentTime,TimeIncrement,TimeStepNumber,Value
643  INTEGER(INTG) :: EquationsSetIndex,InterfaceNodeNumber,InterfaceNodeComponent,NumberOfComponents
644  LOGICAL :: FluidEquationsSetFound,SolidEquationsSetFound=.false.
645 
646  enters("FSI_CONTROL_LOOP_POST_LOOP",err,error,*999)
647 
648  NULLIFY(dynamicsolver)
649  NULLIFY(linearsolver)
650  NULLIFY(timeloop)
651  NULLIFY(dynamicsolverequations)
652  NULLIFY(solidequationsset)
653  NULLIFY(fluidequationsset)
654  NULLIFY(solidgeometricfield)
655  NULLIFY(interfacegeometricfield)
656  NULLIFY(soliddependentfield)
657  NULLIFY(interfacecondition)
658  NULLIFY(fsinterface)
659  NULLIFY(interfacenodes)
660 
661  !Check pointers
662  IF(.NOT.ASSOCIATED(controlloop)) CALL flagerror("Main control loop not associated.",err,error,*999)
663  IF(.NOT.ASSOCIATED(controlloop%SOLVERS)) CALL flagerror("Solvers are not associated.",err,error,*999)
664  !Get solvers for FSI
665  CALL solvers_solver_get(controlloop%SOLVERS,1,dynamicsolver,err,error,*999)
666  CALL solvers_solver_get(controlloop%SOLVERS,2,linearsolver,err,error,*999)
667  timeloop=>controlloop%TIME_LOOP
668  IF(.NOT.ASSOCIATED(timeloop)) CALL flagerror("Time loop not associated.",err,error,*999)
669  !Get times
670  starttime=timeloop%START_TIME
671  currenttime=timeloop%CURRENT_TIME
672  timeincrement=timeloop%TIME_INCREMENT
673  timestepnumber=(currenttime-starttime)/timeincrement!GLOBAL_ITERATION_NUMBER???
674  !===============================================================================================================================
675  !First update mesh and calculate boundary velocity values
676  CALL navier_stokes_pre_solve_ale_update_mesh(dynamicsolver,err,error,*999)
677  !===============================================================================================================================
678  !Update interface geometric field and export results
679  dynamicsolverequations=>dynamicsolver%SOLVER_EQUATIONS
680  IF(ASSOCIATED(dynamicsolverequations)) THEN
681  dynamicsolvermapping=>dynamicsolverequations%SOLVER_MAPPING
682  IF(ASSOCIATED(dynamicsolvermapping)) THEN
683  equationssetindex=1
684  fluidequationssetfound=.false.
685  solidequationssetfound=.false.
686  DO WHILE((equationssetindex<=dynamicsolvermapping%NUMBER_OF_EQUATIONS_SETS &
687  & .AND..NOT.solidequationssetfound) &
688  & .OR.(equationssetindex<=dynamicsolvermapping%NUMBER_OF_EQUATIONS_SETS &
689  & .AND..NOT.fluidequationssetfound))
690  equationsset=>dynamicsolvermapping%EQUATIONS_SETS(equationssetindex)%PTR
691  IF(equationsset%specification(1)==equations_set_elasticity_class &
692  & .AND.equationsset%specification(2)==equations_set_finite_elasticity_type &
693  & .AND.((equationsset%specification(3)==equations_set_mooney_rivlin_subtype).OR. &
694  & (equationsset%specification(3)==equations_set_compressible_finite_elasticity_subtype))) THEN
695  solidequationsset=>equationsset
696  solidequationssetfound=.true.
697  ELSEIF(equationsset%specification(1)==equations_set_fluid_mechanics_class &
698  & .AND.equationsset%specification(2)==equations_set_navier_stokes_equation_type &
699  & .AND.equationsset%specification(3)==equations_set_ale_navier_stokes_subtype) THEN
700  fluidequationsset=>equationsset
701  fluidequationssetfound=.true.
702  ELSE
703  CALL flagerror("Invalid equations sets associated with dynamic solver for FSI.", err,error,*999)
704  ENDIF
705  equationssetindex=equationssetindex+1
706  ENDDO
707  IF(.NOT.solidequationssetfound) CALL flagerror("Could not find solid equations set for FSI.",err,error,*999)
708  IF(.NOT.fluidequationssetfound) CALL flagerror("Could not find fluid equations set for FSI.",err,error,*999)
709  solidgeometricfield=>solidequationsset%GEOMETRY%GEOMETRIC_FIELD
710  IF(ASSOCIATED(solidgeometricfield)) THEN
711  CALL field_number_of_components_get(solidgeometricfield,field_u_variable_type,numberofcomponents,err,error,*999)
712  IF(dynamicsolvermapping%NUMBER_OF_INTERFACE_CONDITIONS>1) THEN
713  CALL flagerror("Invalid number of interface conditions. Must be 1 for FSI.",err,error,*999)
714  ENDIF
715  soliddependentfield=>solidequationsset%DEPENDENT%DEPENDENT_FIELD
716  IF(ASSOCIATED(soliddependentfield)) THEN
717  interfacecondition=>dynamicsolvermapping%INTERFACE_CONDITIONS(1)%PTR
718  IF(ASSOCIATED(interfacecondition)) THEN
719  fsinterface=>interfacecondition%INTERFACE
720  IF(ASSOCIATED(fsinterface)) THEN
721  interfacenodes=>fsinterface%NODES
722  IF(ASSOCIATED(interfacenodes)) THEN
723  interfacegeometricfield=>interfacecondition%GEOMETRY%GEOMETRIC_FIELD
724  IF(ASSOCIATED(interfacegeometricfield)) THEN
725  !===============================================================================================================
726  !Update interface geometric field
727  DO interfacenodenumber=1,interfacenodes%NUMBER_OF_NODES
728  DO interfacenodecomponent=1,numberofcomponents
729  !Default to version 1, derivative 1
730  CALL field_parameter_set_get_node(soliddependentfield,field_u_variable_type,field_values_set_type, &
731  & 1,1,interfacenodes%COUPLED_NODES(1,interfacenodenumber),interfacenodecomponent,Value, &
732  & err,error,*999)
733  CALL field_parameter_set_update_node(interfacegeometricfield,field_u_variable_type, &
734  & field_values_set_type,1,1,interfacenodenumber,interfacenodecomponent,Value,err,error,*999)
735  ENDDO
736  ENDDO
737  CALL field_parameter_set_update_start(interfacegeometricfield, &
738  & field_u_variable_type,field_values_set_type,err,error,*999)
739  CALL field_parameter_set_update_finish(interfacegeometricfield, &
740  & field_u_variable_type,field_values_set_type,err,error,*999)
741  !===============================================================================================================
742  !Export fields
743  solidfilename="./output/Solid/Solid"//trim(number_to_vstring(int(timestepnumber),"*",err,error))
744  fluidfilename="./output/Fluid/Fluid"//trim(number_to_vstring(int(timestepnumber),"*",err,error))
745  interfacefilename="./output/Interface/Interface"//trim(number_to_vstring(int(timestepnumber),"*",err,error))
746  method="FORTRAN"
747  !Export solid fields
748  IF(.NOT.ASSOCIATED(solidequationsset%REGION)) CALL flagerror("Solid region not associated.", &
749  & err,error,*999)
750  IF(.NOT.ASSOCIATED(solidequationsset%REGION%FIELDS)) CALL flagerror("Solid fields not associated.", &
751  & err,error,*999)
752  CALL write_string(general_output_type,"...",err,error,*999)
753  CALL write_string(general_output_type,"Now export fields... ",err,error,*999)
754  CALL field_io_nodes_export(solidequationsset%REGION%FIELDS,solidfilename,method,err,error,*999)
755  CALL field_io_elements_export(solidequationsset%REGION%FIELDS,solidfilename,method,err,error,*999)
756  CALL write_string(general_output_type,solidfilename,err,error,*999)
757  IF(.NOT.ASSOCIATED(fluidequationsset%REGION)) CALL flagerror("Fluid region not associated.", &
758  & err,error,*999)
759  IF(.NOT.ASSOCIATED(fluidequationsset%REGION%FIELDS)) CALL flagerror("Fluid fields not associated.", &
760  & err,error,*999)
761  !Export fluid fields
762  CALL field_io_nodes_export(fluidequationsset%REGION%FIELDS,fluidfilename,method,err,error,*999)
763  CALL field_io_elements_export(fluidequationsset%REGION%FIELDS,fluidfilename,method,err,error,*999)
764  CALL write_string(general_output_type,fluidfilename,err,error,*999)
765  IF(.NOT.ASSOCIATED(fsinterface%FIELDS)) CALL flagerror("Interface fields not associated.",err,error,*999)
766  !Export interface fields
767  CALL field_io_nodes_export(fsinterface%FIELDS,interfacefilename,method,err,error,*999)
768  CALL field_io_elements_export(fsinterface%FIELDS,interfacefilename,method,err,error,*999)
769  CALL write_string(general_output_type,interfacefilename,err,error,*999)
770  CALL write_string(general_output_type,"...",err,error,*999)
771  ELSE
772  CALL flagerror("Interface geometric field not associated.",err,error,*999)
773  ENDIF
774  ELSE
775  CALL flagerror("Interface nodes not associated.",err,error,*999)
776  ENDIF
777  ELSE
778  CALL flagerror("Interface not associated.",err,error,*999)
779  ENDIF
780  ELSE
781  CALL flagerror("Interface condition not associated.",err,error,*999)
782  ENDIF
783  ELSE
784  CALL flagerror("Solid dependent field not associated.",err,error,*999)
785  ENDIF
786  ELSE
787  CALL flagerror("Solid geometric field not associated.",err,error,*999)
788  ENDIF
789  ELSE
790  CALL flagerror("Dynamic solver mapping not associated.",err,error,*999)
791  ENDIF
792  ELSE
793  CALL flagerror("Dynamic solver equations not associated.",err,error,*999)
794  ENDIF
795 
796  exits("FSI_CONTROL_LOOP_POST_LOOP")
797  RETURN
798 999 errorsexits("FSI_CONTROL_LOOP_POST_LOOP",err,error)
799  RETURN 1
800  END SUBROUTINE fsi_control_loop_post_loop
801 
802  !
803  !================================================================================================================================
804  !
805 
806 END MODULE fsi_routines
integer(intg), parameter equations_set_fem_solution_method
Finite Element Method solution method.
This module contains all basis function routines.
subroutine, public enters(NAME, ERR, ERROR,)
Records the entry into the named procedure and initialises the error code.
subroutine, public solvers_create_finish(SOLVERS, ERR, ERROR,)
Finish the creation of solvers.
integer(intg), parameter, public control_loop_progress_output
Progress output from control loop.
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.
Contains information on a time iteration control loop.
Definition: types.f90:3148
integer(intg), parameter problem_setup_control_type
Solver setup for a problem.
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.
Converts a number to its equivalent varying string representation.
Definition: strings.f90:161
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 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
subroutine, public fsi_problemspecificationset(problem, problemSpecification, err, error,)
Sets the problem specification for a finite elasticity Navier-Stokes equation type.
subroutine, public fsi_control_loop_post_loop(ControlLoop, Err, Error,)
Runs after each control loop iteration. Updates interface and fluid geometric fields and exports fiel...
Contains information for the interface condition data.
Definition: types.f90:2155
subroutine, public fsi_equations_set_solution_method_set(EQUATIONS_SET, SOLUTION_METHOD, Err, Error,)
Sets/changes the solution method for a finite elasticity navier stokes equation type of a multi physi...
subroutine, public solver_dynamic_linearity_type_set(SOLVER, LINEARITY_TYPE, ERR, ERROR,)
Sets/changes the linearity type for the dynamic solver.
subroutine, public fsi_equationssetspecificationset(equationsSet, specification, Err, Error,)
Sets/changes the equation subtype for a finite elasticity navier stokes equation type of a multi phys...
subroutine, public fsi_post_solve(ControlLoop, Solver, Err, Error,)
Sets up the finite elasticity navier stokes problem post 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.
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 for a field defined on a region.
Definition: types.f90:1346
integer(intg), parameter equations_set_fluid_mechanics_class
integer(intg), parameter solver_equations_linear
Solver equations are linear.
Contains information on a control loop.
Definition: types.f90:3185
subroutine, public fsi_problem_setup(PROBLEM, PROBLEM_SETUP, Err, Error,)
Sets up the finite elasticity navier stokes equations problem.
This module provides an iso_varying_string module, conformant to the API specified in ISO/IEC 1539-2:...
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.
integer(intg), parameter equations_set_ale_navier_stokes_subtype
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 equations_set_finite_elasticity_navier_stokes_ale_subtype
subroutine, public fsi_pre_solve(ControlLoop, Solver, Err, Error,)
Sets up the finite elasticity navier stokes problem pre-solve.
integer(intg), parameter problem_setup_initial_type
Initial setup for a problem.
subroutine, public fsi_equations_set_setup(EQUATIONS_SET, EQUATIONS_SET_SETUP, Err, Error,)
Sets up the finite elasticity navier stokes equation.
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.
integer(intg), parameter equations_set_mooney_rivlin_subtype
This module contains all type definitions in order to avoid cyclic module references.
Definition: types.f90:70
integer(intg), parameter equations_set_elasticity_class
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 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 Navier-Stokes fluid routines.
This module handles all solver routines.
integer(intg), parameter equations_set_finite_elasticity_type
integer(intg), parameter problem_finite_elasticity_navier_stokes_ale_subtype
integer(intg), parameter problem_finite_elasticity_navier_stokes_type
Implements lists of Field IO operation.
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.
Contains information on the solver mapping between the global equation sets and the solver matrices...
Definition: types.f90:3091
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.
Contains information on the nodes defined on a region.
Definition: types.f90:359
subroutine, public fsi_control_loop_pre_loop(ControlLoop, Err, Error,)
Runs before each control loop iteration.
integer(intg), parameter, public solver_dynamic_nonlinear
Dynamic solver has nonlinear terms.
integer(intg), parameter equations_set_fd_solution_method
Finite Difference solution method.
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.
integer(intg), parameter equations_set_compressible_finite_elasticity_subtype
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.
Contains information for the interface data.
Definition: types.f90:2228
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.
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 routines pertaining to finite elasticity coupled with navier stokes for fsi p...
integer(intg), parameter, public solver_linear_type
A linear solver.
This module handles all finite elasticity routines.
subroutine, public field_io_elements_export(FIELDS, FILE_NAME, METHOD, ERR, ERROR,)
Export elemental information into multiple files.
subroutine, public fsi_finite_element_calculate(EQUATIONS_SET, ELEMENT_NUMBER, Err, Error,)
Calculates the element stiffness matrices and RHS for a finite elasticity navier stokes equation fini...
This module contains all kind definitions.
Definition: kinds.f90:45
subroutine, public field_io_nodes_export(FIELDS, FILE_NAME, METHOD, ERR, ERROR,)
Export nodal information.
integer(intg), parameter equations_set_navier_stokes_equation_type
This module handles all formating and input and output.