OpenCMISS-Iron Internal API Documentation
diffusion_advection_diffusion_routines.f90
Go to the documentation of this file.
1 
43 
45 
46 
48 
50  USE base_routines
51  USE basis_routines
53  USE constants
58  USE domain_mappings
63  USE field_routines
65  USE input_output
67  USE kinds
68  USE maths
69  USE matrix_vector
70  USE mesh_routines
71  USE node_routines
73  USE strings
74  USE solver_routines
75  USE timer
76  USE types
77 
78 #include "macros.h"
79 
80 
81  IMPLICIT NONE
82 
86 
89 
91 
94 
95 
96 CONTAINS
97 
98  !
99  !================================================================================================================================
100  !
101 
103  SUBROUTINE diffusionadvectiondiffusion_equationssetsolnmethodset(EQUATIONS_SET,SOLUTION_METHOD,ERR,ERROR,*)
105  !Argument variables
106  TYPE(equations_set_type), POINTER :: EQUATIONS_SET
107  INTEGER(INTG), INTENT(IN) :: SOLUTION_METHOD
108  INTEGER(INTG), INTENT(OUT) :: ERR
109  TYPE(varying_string), INTENT(OUT) :: ERROR
110  !Local Variables
111  TYPE(varying_string) :: LOCAL_ERROR
112 
113  enters("DiffusionAdvectionDiffusion_EquationsSetSolnMethodSet",err,error,*999)
114 
115  IF(ASSOCIATED(equations_set)) THEN
116  IF(.NOT.ALLOCATED(equations_set%SPECIFICATION)) THEN
117  CALL flagerror("Equations set specification is not allocated.",err,error,*999)
118  ELSE IF(SIZE(equations_set%SPECIFICATION,1)/=3) THEN
119  CALL flagerror("Equations set specification must have three entries for a "// &
120  & "diffusion and advection-diffusion type equations set.",err,error,*999)
121  END IF
122  SELECT CASE(equations_set%SPECIFICATION(3))
124  SELECT CASE(solution_method)
126  equations_set%SOLUTION_METHOD=equations_set_fem_solution_method
128  CALL flagerror("Not implemented.",err,error,*999)
130  CALL flagerror("Not implemented.",err,error,*999)
132  CALL flagerror("Not implemented.",err,error,*999)
134  CALL flagerror("Not implemented.",err,error,*999)
136  CALL flagerror("Not implemented.",err,error,*999)
137  CASE DEFAULT
138  local_error="The specified solution method of "//trim(number_to_vstring(solution_method,"*",err,error))//" is invalid."
139  CALL flagerror(local_error,err,error,*999)
140  END SELECT
141  CASE DEFAULT
142  local_error="Equations set subtype of "//trim(number_to_vstring(equations_set%SPECIFICATION(3),"*",err,error))// &
143  & " is not valid for a diffusion & advection-diffusion equation type of a multi physics equations set class."
144  CALL flagerror(local_error,err,error,*999)
145  END SELECT
146  ELSE
147  CALL flagerror("Equations set is not associated.",err,error,*999)
148  ENDIF
149 
150  exits("DiffusionAdvectionDiffusion_EquationsSetSolnMethodSet")
151  RETURN
152 999 errors("DiffusionAdvectionDiffusion_EquationsSetSolnMethodSet",err,error)
153  exits("DiffusionAdvectionDiffusion_EquationsSetSolnMethodSet")
154  RETURN 1
155 
157 
158  !
159  !================================================================================================================================
160  !
161 
163  SUBROUTINE diffusionadvectiondiffusion_equationssetsetup(EQUATIONS_SET,EQUATIONS_SET_SETUP,ERR,ERROR,*)
165  !Argument variables
166  TYPE(equations_set_type), POINTER :: EQUATIONS_SET
167  TYPE(equations_set_setup_type), INTENT(INOUT) :: EQUATIONS_SET_SETUP
168  INTEGER(INTG), INTENT(OUT) :: ERR
169  TYPE(varying_string), INTENT(OUT) :: ERROR
170  !Local Variables
171 
172 
173  enters("DiffusionAdvectionDiffusion_EquationsSetSetup",err,error,*999)
174 
175  CALL flagerror("Not implemented.",err,error,*999)
176 
177  exits("DiffusionAdvectionDiffusion_EquationsSetSetup")
178  RETURN
179 999 errors("DiffusionAdvectionDiffusion_EquationsSetSetup",err,error)
180  exits("DiffusionAdvectionDiffusion_EquationsSetSetup")
181  RETURN 1
182 
184 
185  !
186  !================================================================================================================================
187  !
188 
190  SUBROUTINE diffusionadvectiondiffusion_finiteelementcalculate(EQUATIONS_SET,ELEMENT_NUMBER,ERR,ERROR,*)
192  !Argument variables
193  TYPE(equations_set_type), POINTER :: EQUATIONS_SET
194  INTEGER(INTG), INTENT(IN) :: ELEMENT_NUMBER
195  INTEGER(INTG), INTENT(OUT) :: ERR
196  TYPE(varying_string), INTENT(OUT) :: ERROR
197  !Local Variables
198 
199  enters("DiffusionAdvectionDiffusion_FiniteElementCalculate",err,error,*999)
200 
201  CALL flagerror("Not implemented.",err,error,*999)
202 
203  exits("DiffusionAdvectionDiffusion_FiniteElementCalculate")
204  RETURN
205 999 errors("DiffusionAdvectionDiffusion_FiniteElementCalculate",err,error)
206  exits("DiffusionAdvectionDiffusion_FiniteElementCalculate")
207  RETURN 1
208 
210 
211  !
212  !================================================================================================================================
213  !
214 
216  SUBROUTINE diffusionadvectiondiffusion_equationssetspecset(equationsSet,specification,err,error,*)
218  !Argument variables
219  TYPE(equations_set_type), POINTER :: equationsSet
220  INTEGER(INTG), INTENT(IN) :: specification(:)
221  INTEGER(INTG), INTENT(OUT) :: err
222  TYPE(varying_string), INTENT(OUT) :: error
223 
224  enters("DiffusionAdvectionDiffusion_EquationsSetSpecSet",err,error,*999)
225 
226  CALL flagerror("Not implemented.",err,error,*999)
227 
228  exits("DiffusionAdvectionDiffusion_EquationsSetSpecSet")
229  RETURN
230 999 errors("DiffusionAdvectionDiffusion_EquationsSetSpecSet",err,error)
231  exits("DiffusionAdvectionDiffusion_EquationsSetSpecSet")
232  RETURN 1
233 
235 
236  !
237  !================================================================================================================================
238  !
239 
241  SUBROUTINE diffusionadvectiondiffusion_problemspecificationset(problem,problemSpecification,err,error,*)
243  !Argument variables
244  TYPE(problem_type), POINTER :: problem
245  INTEGER(INTG), INTENT(IN) :: problemSpecification(:)
246  INTEGER(INTG), INTENT(OUT) :: err
247  TYPE(varying_string), INTENT(OUT) :: error
248  !Local Variables
249  TYPE(varying_string) :: localError
250  INTEGER(INTG) :: problemSubtype
251 
252  enters("DiffusionAdvectionDiffusion_ProblemSpecificationSet",err,error,*999)
253 
254  IF(ASSOCIATED(problem)) THEN
255  IF(SIZE(problemspecification,1)==3) THEN
256  SELECT CASE(problemsubtype)
258  !ok
259  CASE DEFAULT
260  localerror="The third problem specification of "//trim(numbertovstring(problemsubtype,"*",err,error))// &
261  & " is not valid for a coupled diffusion & advection-diffusion type of a multi physics problem."
262  CALL flagerror(localerror,err,error,*999)
263  END SELECT
264  IF(ALLOCATED(problem%specification)) THEN
265  CALL flagerror("Problem specification is already allocated.",err,error,*999)
266  ELSE
267  ALLOCATE(problem%specification(3),stat=err)
268  IF(err/=0) CALL flagerror("Could not allocate problem specification.",err,error,*999)
269  END IF
271  & problemsubtype]
272  ELSE
273  CALL flagerror("Diffusion advection-diffusion transport problem specification must have 3 entries.",err,error,*999)
274  END IF
275  ELSE
276  CALL flagerror("Problem is not associated.",err,error,*999)
277  END IF
278 
279  exits("DiffusionAdvectionDiffusion_ProblemSpecificationSet")
280  RETURN
281 999 errors("DiffusionAdvectionDiffusion_ProblemSpecificationSet",err,error)
282  exits("DiffusionAdvectionDiffusion_ProblemSpecificationSet")
283  RETURN 1
284 
286 
287  !
288  !================================================================================================================================
289  !
290 
292  SUBROUTINE diffusion_advection_diffusion_problem_setup(PROBLEM,PROBLEM_SETUP,ERR,ERROR,*)
294  !Argument variables
295  TYPE(problem_type), POINTER :: PROBLEM
296  TYPE(problem_setup_type), INTENT(INOUT) :: PROBLEM_SETUP
297  INTEGER(INTG), INTENT(OUT) :: ERR
298  TYPE(varying_string), INTENT(OUT) :: ERROR
299  !Local Variables
300  TYPE(control_loop_type), POINTER :: CONTROL_LOOP,CONTROL_LOOP_ROOT
301  TYPE(solver_type), POINTER :: SOLVER_DIFFUSION, SOLVER_ADVECTION_DIFFUSION
302  TYPE(solver_equations_type), POINTER :: SOLVER_EQUATIONS_DIFFUSION, SOLVER_EQUATIONS_ADVECTION_DIFFUSION
303  TYPE(solvers_type), POINTER :: SOLVERS
304  TYPE(varying_string) :: LOCAL_ERROR
305 
306  enters("DIFFUSION_ADVECTION_DIFFUSION_PROBLEM_SETUP",err,error,*999)
307 
308  NULLIFY(control_loop)
309  NULLIFY(solvers)
310  NULLIFY(solver_diffusion)
311  NULLIFY(solver_advection_diffusion)
312  NULLIFY(solver_equations_diffusion)
313  NULLIFY(solver_equations_advection_diffusion)
314  IF(ASSOCIATED(problem)) THEN
315  IF(.NOT.ALLOCATED(problem%specification)) THEN
316  CALL flagerror("Problem specification is not allocated.",err,error,*999)
317  ELSE IF(SIZE(problem%specification,1)<3) THEN
318  CALL flagerror("Problem specification must have three entries for a diffusion-advection diffusion problem.", &
319  & err,error,*999)
320  END IF
321  SELECT CASE(problem%SPECIFICATION(3))
322 
323  !--------------------------------------------------------------------
324  ! coupled source diffusion--advection-diffusion
325  !--------------------------------------------------------------------
327  SELECT CASE(problem_setup%SETUP_TYPE)
329  SELECT CASE(problem_setup%ACTION_TYPE)
331  !Do nothing????
333  !Do nothing???
334  CASE DEFAULT
335  local_error="The action type of "//trim(number_to_vstring(problem_setup%ACTION_TYPE,"*",err,error))// &
336  & " for a setup type of "//trim(number_to_vstring(problem_setup%SETUP_TYPE,"*",err,error))// &
337  & " is invalid for a diffusion & advection-diffusion equation."
338  CALL flagerror(local_error,err,error,*999)
339  END SELECT
341  SELECT CASE(problem_setup%ACTION_TYPE)
343  !Set up a time control loop
344  CALL control_loop_create_start(problem,control_loop,err,error,*999)
345  CALL control_loop_type_set(control_loop,problem_control_time_loop_type,err,error,*999)
347  !Finish the control loops
348  control_loop_root=>problem%CONTROL_LOOP
349  CALL control_loop_get(control_loop_root,control_loop_node,control_loop,err,error,*999)
350  CALL control_loop_create_finish(control_loop,err,error,*999)
351  CASE DEFAULT
352  local_error="The action type of "//trim(number_to_vstring(problem_setup%ACTION_TYPE,"*",err,error))// &
353  & " for a setup type of "//trim(number_to_vstring(problem_setup%SETUP_TYPE,"*",err,error))// &
354  & " is invalid for a coupled diffusion & advection-diffusion equation."
355  CALL flagerror(local_error,err,error,*999)
356  END SELECT
358  !Get the control loop
359  control_loop_root=>problem%CONTROL_LOOP
360  CALL control_loop_get(control_loop_root,control_loop_node,control_loop,err,error,*999)
361  SELECT CASE(problem_setup%ACTION_TYPE)
363  !Start the solvers creation
364  CALL solvers_create_start(control_loop,solvers,err,error,*999)
365  CALL solvers_number_set(solvers,2,err,error,*999)
366  !
367  !Set the first solver to be a linear solver for the advection-diffusion problem
368  CALL solvers_solver_get(solvers,1,solver_advection_diffusion,err,error,*999)
369  CALL solver_type_set(solver_advection_diffusion,solver_dynamic_type,err,error,*999)
370  CALL solver_dynamic_order_set(solver_advection_diffusion,solver_dynamic_first_order,err,error,*999)
371  !Set solver defaults
372  CALL solver_dynamic_degree_set(solver_advection_diffusion,solver_dynamic_first_degree,err,error,*999)
373  CALL solver_dynamic_scheme_set(solver_advection_diffusion,solver_dynamic_crank_nicolson_scheme,err,error,*999)
374  CALL solver_library_type_set(solver_advection_diffusion,solver_cmiss_library,err,error,*999)
375  !
376  !Set the second solver to be a linear solver for the diffusion problem
377  CALL solvers_solver_get(solvers,2,solver_diffusion,err,error,*999)
378  CALL solver_type_set(solver_diffusion,solver_dynamic_type,err,error,*999)
379  CALL solver_dynamic_order_set(solver_diffusion,solver_dynamic_first_order,err,error,*999)
380  !Set solver defaults
381  CALL solver_dynamic_degree_set(solver_diffusion,solver_dynamic_first_degree,err,error,*999)
382  CALL solver_dynamic_scheme_set(solver_diffusion,solver_dynamic_crank_nicolson_scheme,err,error,*999)
383  CALL solver_library_type_set(solver_diffusion,solver_cmiss_library,err,error,*999)
384  !
386  !Get the solvers
387  CALL control_loop_solvers_get(control_loop,solvers,err,error,*999)
388  !Finish the solvers creation
389  CALL solvers_create_finish(solvers,err,error,*999)
390  CASE DEFAULT
391  local_error="The action type of "//trim(number_to_vstring(problem_setup%ACTION_TYPE,"*",err,error))// &
392  & " for a setup type of "//trim(number_to_vstring(problem_setup%SETUP_TYPE,"*",err,error))// &
393  & " is invalid for a coupled diffusion & advection-diffusion equation."
394  CALL flagerror(local_error,err,error,*999)
395  END SELECT
397  SELECT CASE(problem_setup%ACTION_TYPE)
399  !Get the control loop and solvers
400  control_loop_root=>problem%CONTROL_LOOP
401  CALL control_loop_get(control_loop_root,control_loop_node,control_loop,err,error,*999)
402  CALL control_loop_solvers_get(control_loop,solvers,err,error,*999)
403  !
404  !Get the advection-diffusion solver and create the advection-diffusion solver equations
405  CALL solvers_solver_get(solvers,1,solver_advection_diffusion,err,error,*999)
406  CALL solver_equations_create_start(solver_advection_diffusion,solver_equations_advection_diffusion,err,error,*999)
407  CALL solver_equations_linearity_type_set(solver_equations_advection_diffusion,solver_equations_linear,err,error,*999)
408  CALL solver_equations_time_dependence_type_set(solver_equations_advection_diffusion, &
409  & solver_equations_first_order_dynamic,err,error,*999)
410  CALL solver_equations_sparsity_type_set(solver_equations_advection_diffusion,solver_sparse_matrices,err,error,*999)
411  !
412  !Get the diffusion solver and create the diffusion solver equations
413  CALL solvers_solver_get(solvers,2,solver_diffusion,err,error,*999)
414  CALL solver_equations_create_start(solver_diffusion,solver_equations_diffusion,err,error,*999)
415  CALL solver_equations_linearity_type_set(solver_equations_diffusion,solver_equations_linear,err,error,*999)
416  CALL solver_equations_time_dependence_type_set(solver_equations_diffusion, &
417  & solver_equations_first_order_dynamic,err,error,*999)
418  CALL solver_equations_sparsity_type_set(solver_equations_diffusion,solver_sparse_matrices,err,error,*999)
419  !
420 
422  !Get the control loop
423  control_loop_root=>problem%CONTROL_LOOP
424  CALL control_loop_get(control_loop_root,control_loop_node,control_loop,err,error,*999)
425  CALL control_loop_solvers_get(control_loop,solvers,err,error,*999)
426  !
427  !Finish the creation of the advection-diffusion solver equations
428  CALL solvers_solver_get(solvers,1,solver_advection_diffusion,err,error,*999)
429  CALL solver_solver_equations_get(solver_advection_diffusion,solver_equations_advection_diffusion,err,error,*999)
430  CALL solver_equations_create_finish(solver_equations_advection_diffusion,err,error,*999)
431  !
432  !Finish the creation of the diffusion solver equations
433  CALL solvers_solver_get(solvers,2,solver_diffusion,err,error,*999)
434  CALL solver_solver_equations_get(solver_diffusion,solver_equations_diffusion,err,error,*999)
435  CALL solver_equations_create_finish(solver_equations_diffusion,err,error,*999)
436  !
437 
438  CASE DEFAULT
439  local_error="The action type of "//trim(number_to_vstring(problem_setup%ACTION_TYPE,"*",err,error))// &
440  & " for a setup type of "//trim(number_to_vstring(problem_setup%SETUP_TYPE,"*",err,error))// &
441  & " is invalid for a coupled diffusion & advection-diffusion equation."
442  CALL flagerror(local_error,err,error,*999)
443  END SELECT
444  CASE DEFAULT
445  local_error="The setup type of "//trim(number_to_vstring(problem_setup%SETUP_TYPE,"*",err,error))// &
446  & " is invalid for a coupled diffusion & advection-diffusion equation."
447  CALL flagerror(local_error,err,error,*999)
448  END SELECT
449 
450  !-----------------------------------------------------------------
451  ! c a s e d e f a u l t
452  !-----------------------------------------------------------------
453  CASE DEFAULT
454  local_error="The problem subtype of "//trim(number_to_vstring(problem%SPECIFICATION(3),"*",err,error))// &
455  & " does not equal a coupled source diffusion & advection-diffusion equation subtype."
456  CALL flagerror(local_error,err,error,*999)
457 
458  END SELECT
459  ELSE
460  CALL flagerror("Problem is not associated.",err,error,*999)
461  ENDIF
462 
463  exits("DIFFUSION_ADVECTION_DIFFUSION_PROBLEM_SETUP")
464  RETURN
465 999 errorsexits("DIFFUSION_ADVECTION_DIFFUSION_PROBLEM_SETUP",err,error)
466  RETURN 1
468 
469  !
470  !================================================================================================================================
471  !
472 
474  SUBROUTINE diffusion_advection_diffusion_pre_solve(CONTROL_LOOP,SOLVER,ERR,ERROR,*)
476  !Argument variables
477  TYPE(control_loop_type), POINTER :: CONTROL_LOOP
478  TYPE(solver_type), POINTER :: SOLVER
479  INTEGER(INTG), INTENT(OUT) :: ERR
480  TYPE(varying_string), INTENT(OUT) :: ERROR
481 
482  !Local Variables
483  TYPE(varying_string) :: LOCAL_ERROR
484 
485 
486  enters("DIFFUSION_ADVECTION_DIFFUSION_PRE_SOLVE",err,error,*999)
487 
488  IF(ASSOCIATED(control_loop)) THEN
489  IF(ASSOCIATED(solver)) THEN
490  IF(ASSOCIATED(control_loop%PROBLEM)) THEN
491  IF(.NOT.ALLOCATED(control_loop%problem%specification)) THEN
492  CALL flagerror("Problem specification is not allocated.",err,error,*999)
493  ELSE IF(SIZE(control_loop%problem%specification,1)<3) THEN
494  CALL flagerror("Problem specification must have three entries for a diffusion-advection diffusion problem.", &
495  & err,error,*999)
496  END IF
497  SELECT CASE(control_loop%PROBLEM%SPECIFICATION(3))
499 
500  IF(solver%GLOBAL_NUMBER==1) THEN
501  !copy current value of concentration_one to another variable
502  CALL advectiondiffusion_presolvestorecurrentsoln(control_loop,solver,err,error,*999)
503  !Set source term to be updated value of concentration_two
504  !CALL ADVECTION_DIFFUSION_EQUATION_PRE_SOLVE_GET_SOURCE_VALUE(CONTROL_LOOP,SOLVER,ERR,ERROR,*999)
505 
506  !Update indpendent data fields
507 ! CALL WRITE_STRING(GENERAL_OUTPUT_TYPE,"Read in vector data... ",ERR,ERROR,*999)
508 ! CALL ADVECTION_DIFFUSION_PRE_SOLVE_UPDATE_INPUT_DATA(CONTROL_LOOP,SOLVER,ERR,ERROR,*999)
509 
510  ELSE IF(solver%GLOBAL_NUMBER==2) THEN
511  !copy current value of concentration_one to another variable
512  CALL diffusion_presolvestorecurrentsolution(control_loop,solver,err,error,*999)
513  !compute value of constant source term - evaluated from lamdba*(0.5*(c_1^{t+1}+c_1^{t}) - c_2^{t})
514  !CALL DIFFUSION_EQUATION_PRE_SOLVE_GET_SOURCE_VALUE(CONTROL_LOOP,SOLVER,ERR,ERROR,*999)
515  ENDIF
516  CASE DEFAULT
517  local_error="Problem subtype "//trim(number_to_vstring(control_loop%PROBLEM%SPECIFICATION(3),"*",err,error))// &
518  & " is not valid for a diffusion & advection-diffusion type of a multi physics problem class."
519  CALL flagerror(local_error,err,error,*999)
520  END SELECT
521  ELSE
522  CALL flagerror("Problem is not associated.",err,error,*999)
523  ENDIF
524  ELSE
525  CALL flagerror("Solver is not associated.",err,error,*999)
526  ENDIF
527  ELSE
528  CALL flagerror("Control loop is not associated.",err,error,*999)
529  ENDIF
530 
531  exits("DIFFUSION_ADVECTION_DIFFUSION_PRE_SOLVE")
532  RETURN
533 999 errorsexits("DIFFUSION_ADVECTION_DIFFUSION_PRE_SOLVE",err,error)
534  RETURN 1
536 
537  !
538  !================================================================================================================================
539  !
540 
542  SUBROUTINE diffusion_advection_diffusion_post_solve(CONTROL_LOOP,SOLVER,ERR,ERROR,*)
544  !Argument variables
545  TYPE(control_loop_type), POINTER :: CONTROL_LOOP
546  TYPE(solver_type), POINTER :: SOLVER
547  INTEGER(INTG), INTENT(OUT) :: ERR
548  TYPE(varying_string), INTENT(OUT) :: ERROR
549 
550  !Local Variables
551  TYPE(varying_string) :: LOCAL_ERROR
552 
553  enters("DIFFUSION_ADVECTION_DIFFUSION_POST_SOLVE",err,error,*999)
554 
555  IF(ASSOCIATED(control_loop)) THEN
556  IF(ASSOCIATED(solver)) THEN
557  IF(ASSOCIATED(control_loop%PROBLEM)) THEN
558  IF(.NOT.ALLOCATED(control_loop%problem%specification)) THEN
559  CALL flagerror("Problem specification is not allocated.",err,error,*999)
560  ELSE IF(SIZE(control_loop%problem%specification,1)<3) THEN
561  CALL flagerror("Problem specification must have three entries for a diffusion-advection diffusion problem.", &
562  & err,error,*999)
563  END IF
564  SELECT CASE(control_loop%PROBLEM%SPECIFICATION(3))
566  IF(solver%GLOBAL_NUMBER==1) THEN
567 ! CALL ADVECTION_DIFFUSION_EQUATION_POST_SOLVE(CONTROL_LOOP,SOLVER,ERR,ERROR,*999)
568  ELSE IF(solver%GLOBAL_NUMBER==2) THEN
569 ! CALL DIFFUSION_EQUATION_POST_SOLVE(CONTROL_LOOP,SOLVER,ERR,ERROR,*999)
570  ENDIF
571  CASE DEFAULT
572  local_error="Problem subtype "//trim(number_to_vstring(control_loop%PROBLEM%SPECIFICATION(3),"*",err,error))// &
573  & " is not valid for a diffusion & advection-diffusion type of a multi physics problem class."
574  CALL flagerror(local_error,err,error,*999)
575  END SELECT
576  ELSE
577  CALL flagerror("Problem is not associated.",err,error,*999)
578  ENDIF
579  ELSE
580  CALL flagerror("Solver is not associated.",err,error,*999)
581  ENDIF
582  ELSE
583  CALL flagerror("Control loop is not associated.",err,error,*999)
584  ENDIF
585 
586  exits("DIFFUSION_ADVECTION_DIFFUSION_POST_SOLVE")
587  RETURN
588 999 errorsexits("DIFFUSION_ADVECTION_DIFFUSION_POST_SOLVE",err,error)
589  RETURN 1
591 
592  !
593  !================================================================================================================================
594  !
595 
597  SUBROUTINE diffusionadvectiondiffusion_postsolveoutputdata(CONTROL_LOOP,SOLVER,ERR,ERROR,*)
599  !Argument variables
600  TYPE(control_loop_type), POINTER :: CONTROL_LOOP
601  TYPE(solver_type), POINTER :: SOLVER
602  INTEGER(INTG), INTENT(OUT) :: ERR
603  TYPE(varying_string), INTENT(OUT) :: ERROR
604 
605  !Local Variables
606  TYPE(varying_string) :: LOCAL_ERROR
607 
608  enters("DiffusionAdvectionDiffusion_PostSolveOutputData",err,error,*999)
609 
610  IF(ASSOCIATED(control_loop)) THEN
611  IF(ASSOCIATED(solver)) THEN
612  IF(ASSOCIATED(control_loop%PROBLEM)) THEN
613  IF(.NOT.ALLOCATED(control_loop%problem%specification)) THEN
614  CALL flagerror("Problem specification is not allocated.",err,error,*999)
615  ELSE IF(SIZE(control_loop%problem%specification,1)<3) THEN
616  CALL flagerror("Problem specification must have three entries for a diffusion-advection diffusion problem.", &
617  & err,error,*999)
618  END IF
619  SELECT CASE(control_loop%PROBLEM%SPECIFICATION(3))
621  !CALL ADVECTION_DIFFUSION_EQUATION_POST_SOLVE_OUTPUT_DATA(CONTROL_LOOP,SOLVER,ERR,ERROR,*999)
622  !CALL DIFFUSION_EQUATION_POST_SOLVE_OUTPUT_DATA(CONTROL_LOOP,SOLVER,ERR,ERROR,*999)
623  CASE DEFAULT
624  local_error="Problem subtype "//trim(number_to_vstring(control_loop%PROBLEM%SPECIFICATION(3),"*",err,error))// &
625  & " is not valid for a diffusion & advection-diffusion type of a multi physics problem class."
626  CALL flagerror(local_error,err,error,*999)
627  END SELECT
628  ELSE
629  CALL flagerror("Problem is not associated.",err,error,*999)
630  ENDIF
631  ELSE
632  CALL flagerror("Solver is not associated.",err,error,*999)
633  ENDIF
634  ELSE
635  CALL flagerror("Control loop is not associated.",err,error,*999)
636  ENDIF
637 
638  exits("DiffusionAdvectionDiffusion_PostSolveOutputData")
639  RETURN
640 999 errors("DiffusionAdvectionDiffusion_PostSolveOutputData",err,error)
641  exits("DiffusionAdvectionDiffusion_PostSolveOutputData")
642  RETURN 1
643 
645 
646  !
647  !================================================================================================================================
648  !
649 
650 
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.
This module contains all coordinate transformation and support routines.
integer(intg), parameter equations_set_gfem_solution_method
Grid-based Finite Element Method solution method.
integer(intg), parameter problem_diffusion_advection_diffusion_type
integer(intg), parameter problem_control_time_loop_type
Time control loop.
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 diffusionadvectiondiffusion_equationssetspecset(equationsSet, specification, err, error,)
Sets the equation specification for a coupled diffusion & advection-diffusion equation type of a mult...
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
subroutine, public diffusionadvectiondiffusion_equationssetsetup(EQUATIONS_SET, EQUATIONS_SET_SETUP, ERR, ERROR,)
Sets up the diffusion & advection-diffusion coupled equation.
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 diffusion_advection_diffusion_problem_setup(PROBLEM, PROBLEM_SETUP, ERR, ERROR,)
Sets up the coupled diffusion-diffusion equations problem.
TThis module handles all routines pertaining to diffusion coupled to diffusion.
This module contains routines for timing the program.
Definition: timer_f.f90:45
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.
This module contains all program wide constants.
Definition: constants.f90:45
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.
integer(intg), parameter problem_coupled_source_diffusion_advec_diffusion_subtype
This module handles all advection-diffusion equation routines.
subroutine, public solver_equations_linearity_type_set(SOLVER_EQUATIONS, LINEARITY_TYPE, ERR, ERROR,)
Sets/changes the linearity type for solver equations.
subroutine, public exits(NAME)
Records the exit out of the named procedure.
recursive subroutine, public control_loop_solvers_get(CONTROL_LOOP, SOLVERS, ERR, ERROR,)
Returns a pointer to the solvers for a control loop.
This module contains all type definitions in order to avoid cyclic module references.
Definition: types.f90:70
subroutine, public diffusionadvectiondiffusion_problemspecificationset(problem, problemSpecification, err, error,)
Sets the problem specification for a coupled diffusion & advection-diffusion problem.
This module contains all the low-level base routines e.g., all debug, control, and low-level communic...
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
subroutine, public diffusionadvectiondiffusion_equationssetsolnmethodset(EQUATIONS_SET, SOLUTION_METHOD, ERR, ERROR,)
Sets/changes the solution method for a coupled diffusion & advection-diffusion equation type of a mul...
subroutine, public diffusion_presolvestorecurrentsolution(CONTROL_LOOP, SOLVER, ERR, ERROR,)
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
integer(intg), parameter equations_set_gfv_solution_method
Grid-based Finite Volume solution method.
Contains information for a problem.
Definition: types.f90:3221
subroutine, public advectiondiffusion_presolvestorecurrentsoln(CONTROL_LOOP, SOLVER, ERR, ERROR,)
integer(intg), parameter equations_set_coupled_source_diffusion_advec_diffusion_subtype
subroutine diffusionadvectiondiffusion_postsolveoutputdata(CONTROL_LOOP, SOLVER, ERR, ERROR,)
Sets up the diffuion-diffusion problem post solve output data.
This module handles all distributed matrix vector routines.
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 control_loop_create_start(PROBLEM, CONTROL_LOOP, ERR, ERROR,)
Start the process of creating a control loop for a problem.
subroutine, public diffusion_advection_diffusion_pre_solve(CONTROL_LOOP, SOLVER, ERR, ERROR,)
Sets up the diffusion-diffusion problem pre-solve.
integer(intg), parameter problem_setup_solver_equations_type
Solver equations setup for a problem.
subroutine, public solver_dynamic_scheme_set(SOLVER, SCHEME, ERR, ERROR,)
Sets/changes the scheme for a dynamic solver.
integer(intg), parameter equations_set_fd_solution_method
Finite Difference solution method.
subroutine, public diffusion_advection_diffusion_post_solve(CONTROL_LOOP, SOLVER, ERR, ERROR,)
Sets up the diffusion-diffusion problem post solve.
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.
subroutine, public diffusionadvectiondiffusion_finiteelementcalculate(EQUATIONS_SET, ELEMENT_NUMBER, ERR, ERROR,)
Calculates the element stiffness matrices and RHS for a coupled diffusion & advection-diffusion equat...
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 diffusion equation routines.
This module contains all kind definitions.
Definition: kinds.f90:45
Temporary IO routines for fluid mechanics.
This module handles all formating and input and output.