OpenCMISS-Iron Internal API Documentation
Darcy_pressure_equations_routines.f90
Go to the documentation of this file.
1 
43 
46 
47  USE base_routines
48  USE basis_routines
50  USE constants
53  USE domain_mappings
58  USE field_routines
60  USE input_output
62  USE kinds
63  USE maths
64  USE matrix_vector
65  USE node_routines
67  USE strings
68  USE solver_routines
69  USE timer
70  USE types
71 
72 #include "macros.h"
73 
74  IMPLICIT NONE
75 
76  PRIVATE
77 
78  !Module parameters
79 
80  !Module types
81 
82  !Module variables
83 
84  !Interfaces
85 
87 
89 
91 
93 
94 CONTAINS
95 
96  !
97  !================================================================================================================================
98  !
99 
101  SUBROUTINE darcypressure_finiteelementresidualevaluate(EQUATIONS_SET,ELEMENT_NUMBER,ERR,ERROR,*)
103  !Argument variables
104  TYPE(equations_set_type), POINTER :: EQUATIONS_SET
105  INTEGER(INTG), INTENT(IN) :: ELEMENT_NUMBER
106  INTEGER(INTG), INTENT(OUT) :: ERR
107  TYPE(varying_string), INTENT(OUT) :: ERROR
108  !Local Variables
109  INTEGER(INTG) ng,mh,mhs,mi,ms,nh,nhs,ni,ns
110  REAL(DP) :: RWG,PGMSI(3),PGNSI(3)
111  TYPE(basis_type), POINTER :: DEPENDENT_BASIS,GEOMETRIC_BASIS
112  TYPE(equations_type), POINTER :: EQUATIONS
113  TYPE(equations_mapping_type), POINTER :: EQUATIONS_MAPPING
114  TYPE(equations_matrices_type), POINTER :: EQUATIONS_MATRICES
115  TYPE(equations_matrices_nonlinear_type), POINTER :: NONLINEAR_MATRICES
116  TYPE(equations_matrices_rhs_type), POINTER :: RHS_VECTOR
117  TYPE(field_type), POINTER :: DEPENDENT_FIELD,GEOMETRIC_FIELD
118  TYPE(field_variable_type), POINTER :: FIELD_VARIABLE
119  TYPE(quadrature_scheme_type), POINTER :: QUADRATURE_SCHEME
120  TYPE(field_interpolated_point_type), POINTER :: GEOMETRIC_INTERPOLATED_POINT,SOLID_DEPENDENT_INTERPOLATED_POINT, &
121  & MATERIALS_INTERPOLATED_POINT,FIBRE_INTERPOLATED_POINT
122  TYPE(field_interpolated_point_metrics_type), POINTER :: GEOMETRIC_INTERPOLATED_POINT_METRICS, &
123  & SOLID_DEPENDENT_INTERPOLATED_POINT_METRICS
124  TYPE(field_interpolation_parameters_type), POINTER :: GEOMETRIC_INTERPOLATION_PARAMETERS,DEPENDENT_INTERPOLATION_PARAMETERS, &
125  & FIBRE_INTERPOLATION_PARAMETERS,MATERIALS_INTERPOLATION_PARAMETERS,SOLID_DEPENDENT_INTERPOLATION_PARAMETERS
126  REAL(DP), POINTER :: ELEMENT_RESIDUAL_VECTOR(:)
127  REAL(DP) :: K(3,3),density
128  REAL(DP) :: DZDNU(3,3),SIGMA(3,3),DNUDZ(3,3),DNUDZT(3,3),TEMP_MATRIX(3,3)
129  REAL(DP) :: Jznu
130  INTEGER(INTG) :: SOLID_COMPONENT_NUMBER,SOLID_NUMBER_OF_XI,NUMBER_OF_DIMENSIONS
131  TYPE(varying_string) :: LOCAL_ERROR
132 
133  enters("DarcyPressure_FiniteElementResidualEvaluate",err,error,*999)
134 
135  NULLIFY(geometric_interpolated_point)
136  NULLIFY(geometric_interpolated_point_metrics)
137  NULLIFY(solid_dependent_interpolated_point)
138  NULLIFY(solid_dependent_interpolated_point_metrics)
139  NULLIFY(materials_interpolated_point)
140  NULLIFY(fibre_interpolated_point)
141  NULLIFY(dependent_interpolation_parameters)
142  NULLIFY(solid_dependent_interpolation_parameters)
143  NULLIFY(geometric_interpolation_parameters)
144  NULLIFY(fibre_interpolation_parameters)
145  NULLIFY(materials_interpolation_parameters)
146 
147  IF(ASSOCIATED(equations_set)) THEN
148  IF(.NOT.ALLOCATED(equations_set%SPECIFICATION)) THEN
149  CALL flagerror("Equations set specification is not allocated.",err,error,*999)
150  ELSE IF(SIZE(equations_set%SPECIFICATION,1)/=3) THEN
151  CALL flagerror("Equations set specification must have three entries for a Darcy pressure type equations set.", &
152  & err,error,*999)
153  END IF
154  equations=>equations_set%EQUATIONS
155  IF(ASSOCIATED(equations)) THEN
156  SELECT CASE(equations_set%SPECIFICATION(3))
160  dependent_field=>equations%INTERPOLATION%DEPENDENT_FIELD
161  geometric_field=>equations%INTERPOLATION%GEOMETRIC_FIELD
162  equations_matrices=>equations%EQUATIONS_MATRICES
163  nonlinear_matrices=>equations_matrices%NONLINEAR_MATRICES
164  element_residual_vector=>nonlinear_matrices%ELEMENT_RESIDUAL%VECTOR
165  rhs_vector=>equations_matrices%RHS_VECTOR
166  equations_mapping=>equations%EQUATIONS_MAPPING
167  field_variable=>dependent_field%VARIABLE_TYPE_MAP(field_v_variable_type)%PTR
168  dependent_basis=>dependent_field%DECOMPOSITION%DOMAIN(field_variable%COMPONENTS(1)%MESH_COMPONENT_NUMBER)%PTR% &
169  & topology%ELEMENTS%ELEMENTS(element_number)%BASIS
170  geometric_basis=>geometric_field%DECOMPOSITION%DOMAIN(geometric_field%DECOMPOSITION%MESH_COMPONENT_NUMBER)%PTR% &
171  & topology%ELEMENTS%ELEMENTS(element_number)%BASIS
172  quadrature_scheme=>dependent_basis%QUADRATURE%QUADRATURE_SCHEME_MAP(basis_default_quadrature_scheme)%PTR
173 
174  dependent_interpolation_parameters=>equations%INTERPOLATION%DEPENDENT_INTERP_PARAMETERS(field_v_variable_type)%PTR
175  solid_dependent_interpolation_parameters=>equations%INTERPOLATION%DEPENDENT_INTERP_PARAMETERS(field_u_variable_type)%PTR
176  geometric_interpolation_parameters=>equations%INTERPOLATION%GEOMETRIC_INTERP_PARAMETERS(field_u_variable_type)%PTR
177  fibre_interpolation_parameters=>equations%INTERPOLATION%FIBRE_INTERP_PARAMETERS(field_u_variable_type)%PTR
178  materials_interpolation_parameters=>equations%INTERPOLATION%MATERIALS_INTERP_PARAMETERS(field_u1_variable_type)%PTR
179 
180  CALL field_interpolation_parameters_element_get(field_values_set_type,element_number, &
181  & geometric_interpolation_parameters,err,error,*999)
182  CALL field_interpolation_parameters_element_get(field_values_set_type,element_number, &
183  & fibre_interpolation_parameters,err,error,*999)
184  CALL field_interpolation_parameters_element_get(field_values_set_type,element_number, &
185  & materials_interpolation_parameters,err,error,*999)
186  CALL field_interpolation_parameters_element_get(field_values_set_type,element_number, &
187  & dependent_interpolation_parameters,err,error,*999)
188  CALL field_interpolation_parameters_element_get(field_values_set_type,element_number, &
189  & solid_dependent_interpolation_parameters,err,error,*999)
190 
191  geometric_interpolated_point=>equations%INTERPOLATION%GEOMETRIC_INTERP_POINT(field_u_variable_type)%PTR
192  geometric_interpolated_point_metrics=>equations%INTERPOLATION%GEOMETRIC_INTERP_POINT_METRICS(field_u_variable_type)%PTR
193  fibre_interpolated_point=>equations%INTERPOLATION%FIBRE_INTERP_POINT(field_u_variable_type)%PTR
194  materials_interpolated_point=>equations%INTERPOLATION%MATERIALS_INTERP_POINT(field_u1_variable_type)%PTR
195  solid_dependent_interpolated_point=>equations%INTERPOLATION%DEPENDENT_INTERP_POINT(field_u_variable_type)%PTR
196  solid_dependent_interpolated_point_metrics=>equations%INTERPOLATION%DEPENDENT_INTERP_POINT_METRICS( &
197  & field_u_variable_type)%PTR
198 
199  solid_component_number=dependent_field%VARIABLE_TYPE_MAP(field_u_variable_type)%PTR%COMPONENTS(1)%MESH_COMPONENT_NUMBER
200  solid_number_of_xi=dependent_field%DECOMPOSITION%DOMAIN(solid_component_number)%PTR%TOPOLOGY%ELEMENTS% &
201  & elements(element_number)%BASIS%NUMBER_OF_XI
202  number_of_dimensions=geometric_basis%NUMBER_OF_XI
203 
204  IF(dependent_field%SCALINGS%SCALING_TYPE/=field_no_scaling) THEN
205  CALL field_interpolationparametersscalefactorselementget(element_number,equations%INTERPOLATION% &
206  & dependent_interp_parameters(field_v_variable_type)%PTR,err,error,*999)
207  ENDIF
208 
209  !Loop over gauss points
210  DO ng=1,quadrature_scheme%NUMBER_OF_GAUSS
211  !Calculate RWG.
212  rwg=equations%INTERPOLATION%GEOMETRIC_INTERP_POINT_METRICS(field_u_variable_type)%PTR%JACOBIAN* &
213  & quadrature_scheme%GAUSS_WEIGHTS(ng)
214 
215  CALL field_interpolate_gauss(first_part_deriv,basis_default_quadrature_scheme,ng, &
216  & solid_dependent_interpolated_point,err,error,*999)
217  CALL field_interpolate_gauss(first_part_deriv,basis_default_quadrature_scheme,ng, &
218  & geometric_interpolated_point,err,error,*999)
219  CALL field_interpolate_gauss(first_part_deriv,basis_default_quadrature_scheme,ng, &
220  & fibre_interpolated_point,err,error,*999)
221  CALL field_interpolate_gauss(no_part_deriv,basis_default_quadrature_scheme,ng, &
222  & materials_interpolated_point,err,error,*999)
223  CALL field_interpolated_point_metrics_calculate(dependent_basis%NUMBER_OF_XI, &
224  & solid_dependent_interpolated_point_metrics,err,error,*999)
225  CALL field_interpolated_point_metrics_calculate(geometric_basis%NUMBER_OF_XI, &
226  & geometric_interpolated_point_metrics,err,error,*999)
227 
228  !Get the permeability tensor
229  k(1,1)=materials_interpolated_point%VALUES(1,1)
230  k(1,2)=materials_interpolated_point%VALUES(2,1)
231  k(1,3)=materials_interpolated_point%VALUES(3,1)
232  k(2,2)=materials_interpolated_point%VALUES(4,1)
233  k(2,3)=materials_interpolated_point%VALUES(5,1)
234  k(3,3)=materials_interpolated_point%VALUES(6,1)
235  k(2,1)=k(1,2)
236  k(3,1)=k(1,3)
237  k(3,2)=k(2,3)
238  density=materials_interpolated_point%VALUES(7,1)
239 
240  !Calculate F=dZ/dNU, the deformation gradient tensor at the gauss point
241  CALL finiteelasticity_gaussdeformationgradienttensor(solid_dependent_interpolated_point_metrics, &
242  & geometric_interpolated_point_metrics,fibre_interpolated_point,dzdnu,err,error,*999)
243 
244  CALL invert(dzdnu,dnudz,jznu,err,error,*999)
245  CALL matrix_transpose(dnudz,dnudzt,err,error,*999)
246  CALL matrix_product(k,dnudzt,temp_matrix,err,error,*999)
247  CALL matrix_product(dnudz,temp_matrix,sigma,err,error,*999)
248  sigma=density * jznu * sigma
249 
250  IF(diagnostics1) THEN
251  CALL write_string_matrix(diagnostic_output_type,1,1,3,1,1,3, &
252  & 3,3,dzdnu,write_string_matrix_name_and_indices,'(" DZDNU','(",I1,",:)',' :",3(X,E13.6))', &
253  & '(17X,3(X,E13.6))',err,error,*999)
254  CALL write_string_value(diagnostic_output_type,"Jznu",jznu,err,error,*999)
255  CALL write_string_matrix(diagnostic_output_type,1,1,3,1,1,3, &
256  & 3,3,sigma,write_string_matrix_name_and_indices,'(" SIGMA','(",I1,",:)',' :",3(X,E13.6))', &
257  & '(17X,3(X,E13.6))',err,error,*999)
258  ENDIF
259 
260  CALL matrix_product(sigma,equations%INTERPOLATION% &
261  & geometric_interp_point_metrics(field_u_variable_type)%PTR%GU,temp_matrix,err,error,*999)
262 
263  !Loop over field components
264  mhs=0
265  DO mh=1,field_variable%NUMBER_OF_COMPONENTS
266  !Loop over element rows
267  DO ms=1,dependent_basis%NUMBER_OF_ELEMENT_PARAMETERS
268  mhs=mhs+1
269  nhs=0
270  IF(nonlinear_matrices%UPDATE_RESIDUAL) THEN
271  !Loop over element columns
272  DO nh=1,field_variable%NUMBER_OF_COMPONENTS
273  DO ns=1,dependent_basis%NUMBER_OF_ELEMENT_PARAMETERS
274  nhs=nhs+1
275  DO ni=1,dependent_basis%NUMBER_OF_XI
276  pgmsi(ni)=quadrature_scheme%GAUSS_BASIS_FNS(ms,partial_derivative_first_derivative_map(ni),ng)
277  pgnsi(ni)=quadrature_scheme%GAUSS_BASIS_FNS(ns,partial_derivative_first_derivative_map(ni),ng)
278  ENDDO !ni
279  DO mi=1,dependent_basis%NUMBER_OF_XI
280  DO ni=1,dependent_basis%NUMBER_OF_XI
281  IF(dependent_field%SCALINGS%SCALING_TYPE/=field_no_scaling) THEN
282  element_residual_vector(mhs)=element_residual_vector(mhs)+ &
283  & pgmsi(mi)*pgnsi(ni)*temp_matrix(mi,ni)*dependent_interpolation_parameters%PARAMETERS(ns,1)* &
284  & equations%INTERPOLATION%DEPENDENT_INTERP_PARAMETERS(field_v_variable_type)%PTR% &
285  & scale_factors(ms,mh)*equations%INTERPOLATION%DEPENDENT_INTERP_PARAMETERS(field_v_variable_type)% &
286  & ptr%SCALE_FACTORS(ns,nh)*rwg
287  ELSE
288  element_residual_vector(mhs)=element_residual_vector(mhs)+ &
289  & pgmsi(mi)*pgnsi(ni)*temp_matrix(mi,ni)*rwg*dependent_interpolation_parameters%PARAMETERS(ns,1)
290  ENDIF
291  ENDDO !ni
292  ENDDO !mi
293  ENDDO !ns
294  ENDDO !nh
295  ENDIF
296  IF(rhs_vector%UPDATE_VECTOR) rhs_vector%ELEMENT_VECTOR%VECTOR(mhs)=0.0_dp
297  ENDDO !ms
298  ENDDO !mh
299  ENDDO !ng
300  !Scale factor adjustment
301  IF(dependent_field%SCALINGS%SCALING_TYPE/=field_no_scaling) THEN
302  CALL field_interpolationparametersscalefactorselementget(element_number,equations%INTERPOLATION% &
303  & dependent_interp_parameters(field_v_variable_type)%PTR,err,error,*999)
304  mhs=0
305  DO mh=1,field_variable%NUMBER_OF_COMPONENTS
306  !Loop over element rows
307  DO ms=1,dependent_basis%NUMBER_OF_ELEMENT_PARAMETERS
308  mhs=mhs+1
309  IF(rhs_vector%UPDATE_VECTOR) rhs_vector%ELEMENT_VECTOR%VECTOR(mhs)=rhs_vector%ELEMENT_VECTOR%VECTOR(mhs)* &
310  & equations%INTERPOLATION%DEPENDENT_INTERP_PARAMETERS(field_v_variable_type)%PTR%SCALE_FACTORS(ms,mh)
311  ENDDO !ms
312  ENDDO !mh
313  ENDIF
314  CASE DEFAULT
315  local_error="The third equations set specification of "// &
316  & trim(numbertovstring(equations_set%SPECIFICATION(3),"*",err,error))// &
317  & " is not valid for a coupled Darcy fluid pressure type of a fluid mechanicsequations set."
318  CALL flagerror(local_error,err,error,*999)
319  END SELECT
320  ELSE
321  CALL flagerror("Equations set equations is not associated.",err,error,*999)
322  ENDIF
323  ELSE
324  CALL flagerror("Equations set is not associated.",err,error,*999)
325  ENDIF
326 
327  exits("DarcyPressure_FiniteElementResidualEvaluate")
328  RETURN
329 999 errorsexits("DarcyPressure_FiniteElementResidualEvaluate",err,error)
330  RETURN 1
331 
333 
334  !
335  !================================================================================================================================
336  !
337 
339  SUBROUTINE darcy_pressure_equation_equations_set_setup(EQUATIONS_SET,EQUATIONS_SET_SETUP,ERR,ERROR,*)
341  !Argument variables
342  TYPE(equations_set_type), POINTER :: EQUATIONS_SET
343  TYPE(equations_set_setup_type), INTENT(INOUT) :: EQUATIONS_SET_SETUP
344  INTEGER(INTG), INTENT(OUT) :: ERR
345  TYPE(varying_string), INTENT(OUT) :: ERROR
346  !Local Variables
347  INTEGER(INTG) :: GEOMETRIC_MESH_COMPONENT,GEOMETRIC_SCALING_TYPE,NUMBER_OF_DIMENSIONS,component_idx
348  INTEGER(INTG) :: NUMBER_OF_DARCY_COMPONENTS,NUMBER_OF_COMPONENTS,NUMBER_OF_SOLID_COMPONENTS
349  TYPE(decomposition_type), POINTER :: GEOMETRIC_DECOMPOSITION
350  TYPE(equations_type), POINTER :: EQUATIONS
351  TYPE(equations_mapping_type), POINTER :: EQUATIONS_MAPPING
352  TYPE(equations_matrices_type), POINTER :: EQUATIONS_MATRICES
353  TYPE(equations_set_materials_type), POINTER :: EQUATIONS_MATERIALS
354  TYPE(varying_string) :: LOCAL_ERROR
355 
356  enters("DARCY_PRESSURE_EQUATION_EQUATIONS_SET_SETUP",err,error,*999)
357 
358  NULLIFY(geometric_decomposition)
359  NULLIFY(equations)
360  NULLIFY(equations_mapping)
361  NULLIFY(equations_matrices)
362  NULLIFY(equations_materials)
363 
364  IF(ASSOCIATED(equations_set)) THEN
365  IF(.NOT.ALLOCATED(equations_set%SPECIFICATION)) THEN
366  CALL flagerror("Equations set specification is not allocated.",err,error,*999)
367  ELSE IF(SIZE(equations_set%SPECIFICATION,1)/=3) THEN
368  CALL flagerror("Equations set specification must have three entries for a Darcy pressure type equations set.", &
369  & err,error,*999)
370  END IF
371  number_of_dimensions = equations_set%REGION%COORDINATE_SYSTEM%NUMBER_OF_DIMENSIONS
372  SELECT CASE(equations_set%SPECIFICATION(3))
376  SELECT CASE(equations_set_setup%SETUP_TYPE)
378  SELECT CASE(equations_set_setup%ACTION_TYPE)
380  CALL darcypressure_equationssetsolutionmethodset(equations_set, &
381  & equations_set_fem_solution_method,err,error,*999)
383  !Do nothing
384  CASE DEFAULT
385  local_error="The action type of "//trim(numbertovstring(equations_set_setup%ACTION_TYPE,"*",err,error))// &
386  & " for a setup type of "//trim(numbertovstring(equations_set_setup%SETUP_TYPE,"*",err,error))// &
387  & " is invalid for a standard Darcy pressure equation."
388  CALL flagerror(local_error,err,error,*999)
389  END SELECT
391  !Do nothing
393  SELECT CASE(equations_set%SPECIFICATION(3))
397  number_of_components=number_of_dimensions !Solid components
398  number_of_darcy_components=1 !Only solving for the fluid pressure at the moment
399  END SELECT
400  SELECT CASE(equations_set_setup%ACTION_TYPE)
402  IF(equations_set%DEPENDENT%DEPENDENT_FIELD_AUTO_CREATED) THEN
403  !Create the auto created dependent field
404  CALL field_create_start(equations_set_setup%FIELD_USER_NUMBER,equations_set%REGION,equations_set%DEPENDENT% &
405  & dependent_field,err,error,*999)
406  CALL field_type_set_and_lock(equations_set%DEPENDENT%DEPENDENT_FIELD,field_geometric_general_type,err,error,*999)
407  CALL field_label_set(equations_set%DEPENDENT%DEPENDENT_FIELD,"Dependent Field",err,error,*999)
408  CALL field_dependent_type_set_and_lock(equations_set%DEPENDENT%DEPENDENT_FIELD,field_dependent_type,err,error,*999)
409  CALL field_mesh_decomposition_get(equations_set%GEOMETRY%GEOMETRIC_FIELD,geometric_decomposition,err,error,*999)
410  CALL field_mesh_decomposition_set_and_lock(equations_set%DEPENDENT%DEPENDENT_FIELD,geometric_decomposition, &
411  & err,error,*999)
412  CALL field_geometric_field_set_and_lock(equations_set%DEPENDENT%DEPENDENT_FIELD,equations_set%GEOMETRY% &
413  & geometric_field,err,error,*999)
414  CALL field_number_of_variables_set_and_lock(equations_set%DEPENDENT%DEPENDENT_FIELD,4,err,error,*999)
415  CALL field_variable_types_set_and_lock(equations_set%DEPENDENT%DEPENDENT_FIELD,(/field_u_variable_type, &
416  & field_deludeln_variable_type,field_v_variable_type,field_delvdeln_variable_type/),err,error,*999)
417  CALL field_dimension_set_and_lock(equations_set%DEPENDENT%DEPENDENT_FIELD,field_u_variable_type, &
418  & field_vector_dimension_type,err,error,*999)
419  CALL field_dimension_set_and_lock(equations_set%DEPENDENT%DEPENDENT_FIELD,field_deludeln_variable_type, &
420  & field_vector_dimension_type,err,error,*999)
421  CALL field_dimension_set_and_lock(equations_set%DEPENDENT%DEPENDENT_FIELD,field_v_variable_type, &
422  & field_vector_dimension_type,err,error,*999)
423  CALL field_dimension_set_and_lock(equations_set%DEPENDENT%DEPENDENT_FIELD,field_delvdeln_variable_type, &
424  & field_vector_dimension_type,err,error,*999)
425  CALL field_data_type_set_and_lock(equations_set%DEPENDENT%DEPENDENT_FIELD,field_u_variable_type, &
426  & field_dp_type,err,error,*999)
427  CALL field_data_type_set_and_lock(equations_set%DEPENDENT%DEPENDENT_FIELD,field_deludeln_variable_type, &
428  & field_dp_type,err,error,*999)
429  CALL field_data_type_set_and_lock(equations_set%DEPENDENT%DEPENDENT_FIELD,field_v_variable_type, &
430  & field_dp_type,err,error,*999)
431  CALL field_data_type_set_and_lock(equations_set%DEPENDENT%DEPENDENT_FIELD,field_delvdeln_variable_type, &
432  & field_dp_type,err,error,*999)
433 
434  CALL field_number_of_components_get(equations_set%GEOMETRY%GEOMETRIC_FIELD,field_u_variable_type, &
435  & number_of_dimensions,err,error,*999)
436  CALL field_number_of_components_set_and_lock(equations_set%DEPENDENT%DEPENDENT_FIELD,field_u_variable_type, &
437  & number_of_components,err,error,*999)
438  CALL field_number_of_components_set_and_lock(equations_set%DEPENDENT%DEPENDENT_FIELD,field_deludeln_variable_type, &
439  & number_of_components,err,error,*999)
440  CALL field_number_of_components_set_and_lock(equations_set%DEPENDENT%DEPENDENT_FIELD,field_v_variable_type, &
441  & number_of_darcy_components,err,error,*999)
442  CALL field_number_of_components_set_and_lock(equations_set%DEPENDENT%DEPENDENT_FIELD,field_delvdeln_variable_type, &
443  & number_of_darcy_components,err,error,*999)
444 
445  !Set labels
446  CALL field_variable_label_set(equations_set%DEPENDENT%DEPENDENT_FIELD,field_u_variable_type,"U",err,error,*999)
447  CALL field_variable_label_set(equations_set%DEPENDENT%DEPENDENT_FIELD,field_deludeln_variable_type,"del U/del n", &
448  & err,error,*999)
449  CALL field_variable_label_set(equations_set%DEPENDENT%DEPENDENT_FIELD,field_v_variable_type,"V",err,error,*999)
450  CALL field_variable_label_set(equations_set%DEPENDENT%DEPENDENT_FIELD,field_delvdeln_variable_type,"del V/del n", &
451  & err,error,*999)
452  CALL field_component_label_set(equations_set%DEPENDENT%DEPENDENT_FIELD,field_u_variable_type,1,"x1",err,error,*999)
453  CALL field_component_label_set(equations_set%DEPENDENT%DEPENDENT_FIELD,field_u_variable_type,2,"x2",err,error,*999)
454  CALL field_component_label_set(equations_set%DEPENDENT%DEPENDENT_FIELD,field_u_variable_type,3,"x3",err,error,*999)
455  CALL field_component_label_set(equations_set%DEPENDENT%DEPENDENT_FIELD,field_deludeln_variable_type,1, &
456  & "del x1/del n",err,error,*999)
457  CALL field_component_label_set(equations_set%DEPENDENT%DEPENDENT_FIELD,field_deludeln_variable_type,2, &
458  & "del x2/del n",err,error,*999)
459  CALL field_component_label_set(equations_set%DEPENDENT%DEPENDENT_FIELD,field_deludeln_variable_type,3, &
460  & "del x3/del n",err,error,*999)
461  CALL field_component_label_set(equations_set%DEPENDENT%DEPENDENT_FIELD,field_u_variable_type,1,"p",err,error,*999)
462  CALL field_component_label_set(equations_set%DEPENDENT%DEPENDENT_FIELD,field_deludeln_variable_type,1, &
463  & "del p/del n",err,error,*999)
464 
465  !Elasticity: Default to the geometric interpolation setup
466  DO component_idx=1,number_of_dimensions
467  CALL field_component_mesh_component_get(equations_set%GEOMETRY%GEOMETRIC_FIELD,field_u_variable_type, &
468  & component_idx,geometric_mesh_component,err,error,*999)
469  CALL field_component_mesh_component_set(equations_set%DEPENDENT%DEPENDENT_FIELD,field_u_variable_type, &
470  & component_idx,geometric_mesh_component,err,error,*999)
471  CALL field_component_mesh_component_set(equations_set%DEPENDENT%DEPENDENT_FIELD,field_deludeln_variable_type, &
472  & component_idx,geometric_mesh_component,err,error,*999)
473  ENDDO !component_idx
474  !Darcy: Default pressure and mass increase to the first geometric component
475  CALL field_component_mesh_component_get(equations_set%GEOMETRY%GEOMETRIC_FIELD,field_u_variable_type, &
476  & 1,geometric_mesh_component,err,error,*999)
477  DO component_idx=1,number_of_darcy_components
478  CALL field_component_mesh_component_set(equations_set%DEPENDENT%DEPENDENT_FIELD,field_v_variable_type, &
479  & component_idx,geometric_mesh_component,err,error,*999)
480  CALL field_component_mesh_component_set(equations_set%DEPENDENT%DEPENDENT_FIELD,field_delvdeln_variable_type, &
481  & component_idx,geometric_mesh_component,err,error,*999)
482  ENDDO !component_idx
483 
484  SELECT CASE(equations_set%SOLUTION_METHOD)
486  !Elasticity: Set the displacement components to node based interpolation
487  DO component_idx=1,number_of_dimensions
488  CALL field_component_interpolation_set_and_lock(equations_set%DEPENDENT%DEPENDENT_FIELD,field_u_variable_type, &
489  & component_idx,field_node_based_interpolation,err,error,*999)
490  CALL field_component_interpolation_set_and_lock(equations_set%DEPENDENT%DEPENDENT_FIELD, &
491  & field_deludeln_variable_type,component_idx,field_node_based_interpolation,err,error,*999)
492  ENDDO !component_idx
493  !Darcy: Set the pressure and mass increase components to node based interpolation
494  DO component_idx=1,number_of_darcy_components
495  CALL field_component_interpolation_set_and_lock(equations_set%DEPENDENT%DEPENDENT_FIELD,field_v_variable_type, &
496  & component_idx,field_node_based_interpolation,err,error,*999)
497  CALL field_component_interpolation_set_and_lock(equations_set%DEPENDENT%DEPENDENT_FIELD, &
498  & field_delvdeln_variable_type,component_idx,field_node_based_interpolation,err,error,*999)
499  ENDDO !component_idx
500 
501  !Default the scaling to the geometric field scaling
502  CALL field_scaling_type_get(equations_set%GEOMETRY%GEOMETRIC_FIELD,geometric_scaling_type,err,error,*999)
503  CALL field_scaling_type_set(equations_set%DEPENDENT%DEPENDENT_FIELD,geometric_scaling_type,err,error,*999)
505  CALL flagerror("Not implemented.",err,error,*999)
507  CALL flagerror("Not implemented.",err,error,*999)
509  CALL flagerror("Not implemented.",err,error,*999)
511  CALL flagerror("Not implemented.",err,error,*999)
513  CALL flagerror("Not implemented.",err,error,*999)
514  CASE DEFAULT
515  local_error="The solution method of "//trim(numbertovstring(equations_set%SOLUTION_METHOD,"*",err,error))// &
516  & " is invalid."
517  CALL flagerror(local_error,err,error,*999)
518  END SELECT
519  ELSE
520  !Check the user specified field
521  CALL field_type_check(equations_set_setup%FIELD,field_geometric_general_type,err,error,*999)
522  CALL field_dependent_type_check(equations_set_setup%FIELD,field_dependent_type,err,error,*999)
523  CALL field_number_of_variables_check(equations_set_setup%FIELD,4,err,error,*999)
524  CALL field_variable_types_check(equations_set_setup%FIELD,(/field_u_variable_type,field_deludeln_variable_type, &
525  & field_v_variable_type,field_delvdeln_variable_type/) &
526  & ,err,error,*999)
527  CALL field_dimension_check(equations_set_setup%FIELD,field_u_variable_type,field_vector_dimension_type, &
528  & err,error,*999)
529  CALL field_dimension_check(equations_set_setup%FIELD,field_deludeln_variable_type,field_vector_dimension_type, &
530  & err,error,*999)
531  CALL field_dimension_check(equations_set_setup%FIELD,field_v_variable_type,field_vector_dimension_type, &
532  & err,error,*999)
533  CALL field_dimension_check(equations_set_setup%FIELD,field_delvdeln_variable_type,field_vector_dimension_type, &
534  & err,error,*999)
535 
536  CALL field_data_type_check(equations_set_setup%FIELD,field_u_variable_type,field_dp_type,err,error,*999)
537  CALL field_data_type_check(equations_set_setup%FIELD,field_deludeln_variable_type,field_dp_type,err,error,*999)
538  CALL field_data_type_check(equations_set_setup%FIELD,field_v_variable_type,field_dp_type,err,error,*999)
539  CALL field_data_type_check(equations_set_setup%FIELD,field_delvdeln_variable_type,field_dp_type,err,error,*999)
540 
541  CALL field_number_of_components_get(equations_set%GEOMETRY%GEOMETRIC_FIELD,field_u_variable_type, &
542  & number_of_dimensions,err,error,*999)
543 
544  CALL field_number_of_components_check(equations_set_setup%FIELD,field_u_variable_type, &
545  & number_of_components,err,error,*999)
546  CALL field_number_of_components_check(equations_set_setup%FIELD,field_deludeln_variable_type, &
547  & number_of_components,err,error,*999)
548  CALL field_number_of_components_check(equations_set_setup%FIELD,field_v_variable_type, &
549  & number_of_darcy_components,err,error,*999)
550  CALL field_number_of_components_check(equations_set_setup%FIELD,field_delvdeln_variable_type, &
551  & number_of_darcy_components,err,error,*999)
552 
553  SELECT CASE(equations_set%SOLUTION_METHOD)
555  !Elasticity:
556  DO component_idx=1,number_of_dimensions
557  CALL field_component_interpolation_check(equations_set_setup%FIELD,field_u_variable_type,component_idx, &
558  & field_node_based_interpolation,err,error,*999)
559  CALL field_component_interpolation_check(equations_set_setup%FIELD,field_deludeln_variable_type,component_idx, &
560  & field_node_based_interpolation,err,error,*999)
561  ENDDO !component_idx
562  !Darcy:
563  DO component_idx=1,number_of_darcy_components
564  CALL field_component_interpolation_check(equations_set_setup%FIELD,field_v_variable_type,component_idx, &
565  & field_node_based_interpolation,err,error,*999)
566  CALL field_component_interpolation_check(equations_set_setup%FIELD,field_delvdeln_variable_type,component_idx, &
567  & field_node_based_interpolation,err,error,*999)
568  ENDDO !component_idx
569 
571  CALL flagerror("Not implemented.",err,error,*999)
573  CALL flagerror("Not implemented.",err,error,*999)
575  CALL flagerror("Not implemented.",err,error,*999)
577  CALL flagerror("Not implemented.",err,error,*999)
579  CALL flagerror("Not implemented.",err,error,*999)
580  CASE DEFAULT
581  local_error="The solution method of "//trim(numbertovstring(equations_set%SOLUTION_METHOD,"*",err,error))// &
582  & " is invalid."
583  CALL flagerror(local_error,err,error,*999)
584  END SELECT
585  ENDIF
587  IF(equations_set%DEPENDENT%DEPENDENT_FIELD_AUTO_CREATED) THEN
588  CALL field_create_finish(equations_set%DEPENDENT%DEPENDENT_FIELD,err,error,*999)
589  ENDIF
590  CASE DEFAULT
591  local_error="The action type of "//trim(numbertovstring(equations_set_setup%ACTION_TYPE,"*",err,error))// &
592  & " for a setup type of "//trim(numbertovstring(equations_set_setup%SETUP_TYPE,"*",err,error))// &
593  & " is invalid for a finite elasticity equation"
594  CALL flagerror(local_error,err,error,*999)
595  END SELECT
597  equations_materials=>equations_set%MATERIALS
598  number_of_components=8 !permeability tensor + density + original porosity
599  SELECT CASE(equations_set%SPECIFICATION(3))
601  number_of_solid_components=6
603  number_of_solid_components=4
605  number_of_solid_components=6
606  CASE DEFAULT
607  local_error="The third equations set specification of "// &
608  & trim(numbertovstring(equations_set%SPECIFICATION(3),"*",err,error))// &
609  & " is not valid for a Darcy pressure type of a fluid mechanics equation set."
610  CALL flagerror(local_error,err,error,*999)
611  END SELECT
612  SELECT CASE(equations_set_setup%ACTION_TYPE)
614  IF(equations_materials%MATERIALS_FIELD_AUTO_CREATED) THEN
615  !Create the auto created materials field, which is shared with the solid equations
616  CALL field_create_start(equations_set_setup%FIELD_USER_NUMBER,equations_set%REGION,equations_materials% &
617  & materials_field,err,error,*999)
618  CALL field_type_set_and_lock(equations_materials%MATERIALS_FIELD,field_material_type,err,error,*999)
619  CALL field_dependent_type_set_and_lock(equations_materials%MATERIALS_FIELD,field_independent_type,err,error,*999)
620  CALL field_mesh_decomposition_get(equations_set%GEOMETRY%GEOMETRIC_FIELD,geometric_decomposition,err,error,*999)
621  CALL field_mesh_decomposition_set_and_lock(equations_materials%MATERIALS_FIELD,geometric_decomposition, &
622  & err,error,*999)
623  CALL field_geometric_field_set_and_lock(equations_materials%MATERIALS_FIELD,equations_set%GEOMETRY% &
624  & geometric_field,err,error,*999)
625  CALL field_number_of_variables_set_and_lock(equations_materials%MATERIALS_FIELD,3,err,error,*999)
626  CALL field_variable_types_set_and_lock(equations_materials%MATERIALS_FIELD,[field_u_variable_type, &
627  & field_v_variable_type,field_u1_variable_type],err,error,*999)
628 
629  !U variable, elasticity parameters
630  CALL field_dimension_set_and_lock(equations_materials%MATERIALS_FIELD,field_u_variable_type, &
631  & field_vector_dimension_type,err,error,*999)
632  CALL field_data_type_set_and_lock(equations_materials%MATERIALS_FIELD,field_u_variable_type, &
633  & field_dp_type,err,error,*999)
634  CALL field_number_of_components_set_and_lock(equations_materials%MATERIALS_FIELD,field_u_variable_type, &
635  & number_of_solid_components,err,error,*999)
636 
637  !V variable, solid density
638  CALL field_dimension_set_and_lock(equations_materials%MATERIALS_FIELD,field_v_variable_type, &
639  & field_vector_dimension_type,err,error,*999)
640  CALL field_data_type_set_and_lock(equations_materials%MATERIALS_FIELD,field_v_variable_type, &
641  & field_dp_type,err,error,*999)
642  CALL field_number_of_components_set_and_lock(equations_materials%MATERIALS_FIELD,field_v_variable_type, &
643  & 1,err,error,*999)
644 
645  !U1 variable, fluid parameters
646  CALL field_dimension_set_and_lock(equations_materials%MATERIALS_FIELD,field_u1_variable_type, &
647  & field_vector_dimension_type,err,error,*999)
648  CALL field_data_type_set_and_lock(equations_materials%MATERIALS_FIELD,field_u1_variable_type, &
649  & field_dp_type,err,error,*999)
650  CALL field_number_of_components_set_and_lock(equations_materials%MATERIALS_FIELD,field_u1_variable_type, &
651  & number_of_components,err,error,*999)
652 
653  CALL field_component_mesh_component_get(equations_set%GEOMETRY%GEOMETRIC_FIELD,field_u_variable_type, &
654  & 1,geometric_mesh_component,err,error,*999)
655  DO component_idx=1,number_of_solid_components
656  !Default the materials components to the geometric interpolation setup with constant interpolation
657  CALL field_component_interpolation_set(equations_materials%MATERIALS_FIELD,field_u_variable_type, &
658  & component_idx,field_constant_interpolation,err,error,*999)
659  CALL field_component_mesh_component_set(equations_materials%MATERIALS_FIELD,field_u_variable_type, &
660  & component_idx,geometric_mesh_component,err,error,*999)
661  ENDDO
662  !Solid density field variable
663  CALL field_component_interpolation_set(equations_materials%MATERIALS_FIELD,field_v_variable_type, &
664  & 1,field_constant_interpolation,err,error,*999)
665  CALL field_component_mesh_component_set(equations_materials%MATERIALS_FIELD,field_v_variable_type, &
666  & 1,geometric_mesh_component,err,error,*999)
667  DO component_idx=1,number_of_components
668  !Default the materials components to the geometric interpolation setup with constant interpolation
669  CALL field_component_interpolation_set(equations_materials%MATERIALS_FIELD,field_u1_variable_type, &
670  & component_idx,field_constant_interpolation,err,error,*999)
671  CALL field_component_mesh_component_set(equations_materials%MATERIALS_FIELD,field_u1_variable_type, &
672  & component_idx,geometric_mesh_component,err,error,*999)
673  ENDDO
674 
675  !Default the field scaling to that of the geometric field
676  CALL field_scaling_type_get(equations_set%GEOMETRY%GEOMETRIC_FIELD,geometric_scaling_type,err,error,*999)
677  CALL field_scaling_type_set(equations_materials%MATERIALS_FIELD,geometric_scaling_type,err,error,*999)
678  ELSE
679  !Check the user specified field
680  CALL field_type_check(equations_set_setup%FIELD,field_material_type,err,error,*999)
681  CALL field_dependent_type_check(equations_set_setup%FIELD,field_independent_type,err,error,*999)
682  CALL field_number_of_variables_check(equations_set_setup%FIELD,3,err,error,*999)
683  CALL field_variable_types_check(equations_set_setup%FIELD,[field_u_variable_type,field_v_variable_type, &
684  & field_u1_variable_type],err,error,*999)
685  CALL field_dimension_check(equations_set_setup%FIELD,field_u_variable_type,field_vector_dimension_type, &
686  & err,error,*999)
687  CALL field_dimension_check(equations_set_setup%FIELD,field_v_variable_type,field_vector_dimension_type, &
688  & err,error,*999)
689  CALL field_dimension_check(equations_set_setup%FIELD,field_u1_variable_type,field_vector_dimension_type, &
690  & err,error,*999)
691  CALL field_data_type_check(equations_set_setup%FIELD,field_u_variable_type,field_dp_type,err,error,*999)
692  CALL field_data_type_check(equations_set_setup%FIELD,field_v_variable_type,field_dp_type,err,error,*999)
693  CALL field_data_type_check(equations_set_setup%FIELD,field_u1_variable_type,field_dp_type,err,error,*999)
694  CALL field_number_of_components_check(equations_set_setup%FIELD,field_u_variable_type, &
695  & number_of_solid_components,err,error,*999)
696  CALL field_number_of_components_check(equations_set_setup%FIELD,field_v_variable_type, &
697  & 1,err,error,*999)
698  CALL field_number_of_components_check(equations_set_setup%FIELD,field_u1_variable_type, &
699  & number_of_components,err,error,*999)
700  ENDIF
702  IF(ASSOCIATED(equations_materials)) THEN
703  IF(equations_materials%MATERIALS_FIELD_AUTO_CREATED) THEN
704  !Finish creating the materials field
705  CALL field_create_finish(equations_materials%MATERIALS_FIELD,err,error,*999)
706  !Set the default values for the materials field
707  !Default to K=I
708  CALL field_component_values_initialise(equations_materials%MATERIALS_FIELD,field_u1_variable_type, &
709  & field_values_set_type,1,1.0_dp,err,error,*999)
710  CALL field_component_values_initialise(equations_materials%MATERIALS_FIELD,field_u1_variable_type, &
711  & field_values_set_type,2,0.0_dp,err,error,*999)
712  CALL field_component_values_initialise(equations_materials%MATERIALS_FIELD,field_u1_variable_type, &
713  & field_values_set_type,3,0.0_dp,err,error,*999)
714  CALL field_component_values_initialise(equations_materials%MATERIALS_FIELD,field_u1_variable_type, &
715  & field_values_set_type,4,1.0_dp,err,error,*999)
716  CALL field_component_values_initialise(equations_materials%MATERIALS_FIELD,field_u1_variable_type, &
717  & field_values_set_type,5,0.0_dp,err,error,*999)
718  CALL field_component_values_initialise(equations_materials%MATERIALS_FIELD,field_u1_variable_type, &
719  & field_values_set_type,6,1.0_dp,err,error,*999)
720  !Density
721  CALL field_component_values_initialise(equations_materials%MATERIALS_FIELD,field_u1_variable_type, &
722  & field_values_set_type,7,1.0_dp,err,error,*999)
723  ENDIF
724  ELSE
725  CALL flagerror("Equations set materials is not associated.",err,error,*999)
726  ENDIF
727  CASE DEFAULT
728  local_error="The action type of "//trim(numbertovstring(equations_set_setup%ACTION_TYPE,"*",err,error))// &
729  & " for a setup type of "//trim(numbertovstring(equations_set_setup%SETUP_TYPE,"*",err,error))// &
730  & " is invalid for a standard Darcy pressure equation."
731  CALL flagerror(local_error,err,error,*999)
732  END SELECT
734  SELECT CASE(equations_set_setup%ACTION_TYPE)
736  !Do nothing
738  !Do nothing
739  CASE DEFAULT
740  local_error="The action type of "//trim(numbertovstring(equations_set_setup%ACTION_TYPE,"*",err,error))// &
741  & " for a setup type of "//trim(numbertovstring(equations_set_setup%SETUP_TYPE,"*",err,error))// &
742  & " is invalid for a finite elasticity fluid pressure equation."
743  CALL flagerror(local_error,err,error,*999)
744  END SELECT
746  SELECT CASE(equations_set_setup%ACTION_TYPE)
748  IF(equations_set%DEPENDENT%DEPENDENT_FINISHED) THEN
749  CALL equations_create_start(equations_set,equations,err,error,*999)
750  CALL equations_linearity_type_set(equations,equations_nonlinear,err,error,*999)
751  CALL equations_time_dependence_type_set(equations,equations_static,err,error,*999)
752  ELSE
753  CALL flagerror("Equations set dependent field has not been finished.",err,error,*999)
754  ENDIF
756  SELECT CASE(equations_set%SOLUTION_METHOD)
758  !Finish the equations creation
759  CALL equations_set_equations_get(equations_set,equations,err,error,*999)
760  CALL equations_create_finish(equations,err,error,*999)
761  !Create the equations mapping.
762  CALL equations_mapping_create_start(equations,equations_mapping,err,error,*999)
763  CALL equationsmapping_linearmatricesnumberset(equations_mapping,0,err,error,*999)
764  CALL equationsmapping_residualvariablesnumberset(equations_mapping,2,err,error,*999)
765  CALL equationsmapping_residualvariabletypesset(equations_mapping, &
766  & [field_v_variable_type,field_u_variable_type],err,error,*999)
767  CALL equations_mapping_rhs_variable_type_set(equations_mapping,field_delvdeln_variable_type,err,error,*999)
768  CALL equations_mapping_create_finish(equations_mapping,err,error,*999)
769  !Create the equations matrices
770  CALL equations_matrices_create_start(equations,equations_matrices,err,error,*999)
771  SELECT CASE(equations%SPARSITY_TYPE)
773  CALL equationsmatrices_nonlinearstoragetypeset(equations_matrices,matrix_block_storage_type,err,error,*999)
776  & err,error,*999)
778  & err,error,*999)
779  CASE DEFAULT
780  local_error="The equations matrices sparsity type of "// &
781  & trim(numbertovstring(equations%SPARSITY_TYPE,"*",err,error))//" is invalid."
782  CALL flagerror(local_error,err,error,*999)
783  END SELECT
784  CALL equations_matrices_create_finish(equations_matrices,err,error,*999)
786  CALL flagerror("Not implemented.",err,error,*999)
788  CALL flagerror("Not implemented.",err,error,*999)
790  CALL flagerror("Not implemented.",err,error,*999)
792  CALL flagerror("Not implemented.",err,error,*999)
794  CALL flagerror("Not implemented.",err,error,*999)
795  CASE DEFAULT
796  local_error="The solution method of "//trim(numbertovstring(equations_set%SOLUTION_METHOD,"*",err,error))// &
797  & " is invalid."
798  CALL flagerror(local_error,err,error,*999)
799  END SELECT
800  CASE DEFAULT
801  local_error="The action type of "//trim(numbertovstring(equations_set_setup%ACTION_TYPE,"*",err,error))// &
802  & " for a setup type of "//trim(numbertovstring(equations_set_setup%SETUP_TYPE,"*",err,error))// &
803  & " is invalid for a standard Darcy pressure equation."
804  CALL flagerror(local_error,err,error,*999)
805  END SELECT
806  CASE DEFAULT
807  local_error="The setup type of "//trim(numbertovstring(equations_set_setup%SETUP_TYPE,"*",err,error))// &
808  & " is invalid for a standard Darcy pressure equation."
809  CALL flagerror(local_error,err,error,*999)
810  END SELECT
811  CASE DEFAULT
812  local_error="The third equations set specification of "// &
813  & trim(numbertovstring(equations_set%SPECIFICATION(3),"*",err,error))// &
814  & " is not valid for a Darcy pressure type of a fluid mechanics equation set."
815  CALL flagerror(local_error,err,error,*999)
816  END SELECT
817  ELSE
818  CALL flagerror("Equations set is not associated.",err,error,*999)
819  ENDIF
820 
821  exits("DARCY_PRESSURE_EQUATION_EQUATIONS_SET_SETUP")
822  RETURN
823 999 errorsexits("DARCY_PRESSURE_EQUATION_EQUATIONS_SET_SETUP",err,error)
824  RETURN 1
825 
827 
828  !
829  !================================================================================================================================
830  !
831 
833  SUBROUTINE darcypressure_equationssetsolutionmethodset(EQUATIONS_SET,SOLUTION_METHOD,ERR,ERROR,*)
835  !Argument variables
836  TYPE(equations_set_type), POINTER :: EQUATIONS_SET
837  INTEGER(INTG), INTENT(IN) :: SOLUTION_METHOD
838  INTEGER(INTG), INTENT(OUT) :: ERR
839  TYPE(varying_string), INTENT(OUT) :: ERROR
840  !Local Variables
841  TYPE(varying_string) :: LOCAL_ERROR
842 
843  enters("DarcyPressure_EquationsSetSolutionMethodSet",err,error,*999)
844 
845  IF(ASSOCIATED(equations_set)) THEN
846  IF(.NOT.ALLOCATED(equations_set%SPECIFICATION)) THEN
847  CALL flagerror("Equations set specification is not allocated.",err,error,*999)
848  ELSE IF(SIZE(equations_set%SPECIFICATION,1)/=3) THEN
849  CALL flagerror("Equations set specification must have three entries for a Darcy pressure type equations set.", &
850  & err,error,*999)
851  END IF
852  SELECT CASE(equations_set%SPECIFICATION(3))
856  SELECT CASE(solution_method)
858  equations_set%SOLUTION_METHOD=equations_set_fem_solution_method
860  CALL flagerror("Not implemented.",err,error,*999)
862  CALL flagerror("Not implemented.",err,error,*999)
864  CALL flagerror("Not implemented.",err,error,*999)
866  CALL flagerror("Not implemented.",err,error,*999)
868  CALL flagerror("Not implemented.",err,error,*999)
869  CASE DEFAULT
870  local_error="The specified solution method of "//trim(numbertovstring(solution_method,"*",err,error))//" is invalid."
871  CALL flagerror(local_error,err,error,*999)
872  END SELECT
873  CASE DEFAULT
874  local_error="The third equations set specification of "// &
875  & trim(numbertovstring(equations_set%SPECIFICATION(3),"*",err,error))// &
876  & " is not valid for a Darcy pressure type of a fluid mechanics equations set."
877  CALL flagerror(local_error,err,error,*999)
878  END SELECT
879  ELSE
880  CALL flagerror("Equations set is not associated.",err,error,*999)
881  ENDIF
882 
883  exits("DarcyPressure_EquationsSetSolutionMethodSet")
884  RETURN
885 999 errorsexits("DarcyPressure_EquationsSetSolutionMethodSet",err,error)
886  RETURN 1
887 
889 
890  !
891  !================================================================================================================================
892  !
893 
895  SUBROUTINE darcypressure_equationssetspecificationset(equationsSet,specification,err,error,*)
897  !Argument variables
898  TYPE(equations_set_type), POINTER :: equationsSet
899  INTEGER(INTG), INTENT(IN) :: specification(:)
900  INTEGER(INTG), INTENT(OUT) :: err
901  TYPE(varying_string), INTENT(OUT) :: error
902  !Local Variables
903  TYPE(varying_string) :: localError
904  INTEGER(INTG) :: subtype
905 
906  enters("DarcyPressure_EquationsSetSpecificationSet",err,error,*999)
907 
908  IF(ASSOCIATED(equationsset)) THEN
909  IF(SIZE(specification,1)/=3) THEN
910  CALL flagerror("Equations set specification must have three entries for a Darcy pressure type equations set.", &
911  & err,error,*999)
912  END IF
913  subtype=specification(3)
914  SELECT CASE(subtype)
918  !ok
919  CASE DEFAULT
920  localerror="The third equations set specification of "//trim(numbertovstring(specification(3),"*",err,error))// &
921  & " is not valid for a Darcy pressure type of a fluid mechanics equations set."
922  CALL flagerror(localerror,err,error,*999)
923  END SELECT
924  !Set full specification
925  IF(ALLOCATED(equationsset%specification)) THEN
926  CALL flagerror("Equations set specification is already allocated.",err,error,*999)
927  ELSE
928  ALLOCATE(equationsset%specification(3),stat=err)
929  IF(err/=0) CALL flagerror("Could not allocate equations set specification.",err,error,*999)
930  END IF
932  ELSE
933  CALL flagerror("Equations set is not associated.",err,error,*999)
934  END IF
935 
936  exits("DarcyPressure_EquationsSetSpecificationSet")
937  RETURN
938 999 errors("DarcyPressure_EquationsSetSpecificationSet",err,error)
939  exits("DarcyPressure_EquationsSetSpecificationSet")
940  RETURN 1
941 
943 
944  !
945  !================================================================================================================================
946  !
947 
949  SUBROUTINE darcy_pressure_post_solve(CONTROL_LOOP,SOLVER,ERR,ERROR,*)
951  !Argument variables
952  TYPE(control_loop_type), POINTER :: CONTROL_LOOP
953  TYPE(solver_type), POINTER :: SOLVER
954  INTEGER(INTG), INTENT(OUT) :: ERR
955  TYPE(varying_string), INTENT(OUT) :: ERROR
956  !Local Variables
957  TYPE(varying_string) :: LOCAL_ERROR
958 
959  enters("DARCY_PRESSURE_POST_SOLVE",err,error,*999)
960 
961  IF(ASSOCIATED(control_loop)) THEN
962  IF(ASSOCIATED(solver)) THEN
963  IF(ASSOCIATED(control_loop%PROBLEM)) THEN
964  IF(.NOT.ALLOCATED(control_loop%PROBLEM%SPECIFICATION)) THEN
965  CALL flagerror("Problem specification is not allocated.",err,error,*999)
966  ELSE IF(SIZE(control_loop%PROBLEM%SPECIFICATION,1)<3) THEN
967  CALL flagerror("Problem specification must have three entries for a Darcy pressure problem.",err,error,*999)
968  END IF
969  SELECT CASE(control_loop%PROBLEM%SPECIFICATION(3))
971  !nothing
972  CASE DEFAULT
973  local_error="The third problem specification of "// &
974  & trim(numbertovstring(control_loop%PROBLEM%SPECIFICATION(3),"*",err,error))// &
975  & " is not valid for a Darcy pressure type of a fluid mechanics problem."
976  CALL flagerror(local_error,err,error,*999)
977  END SELECT
978  ELSE
979  CALL flagerror("Problem is not associated.",err,error,*999)
980  ENDIF
981  ELSE
982  CALL flagerror("Solver is not associated.",err,error,*999)
983  ENDIF
984  ELSE
985  CALL flagerror("Control loop is not associated.",err,error,*999)
986  ENDIF
987 
988  exits("DARCY_PRESSURE_POST_SOLVE")
989  RETURN
990 999 errorsexits("DARCY_PRESSURE_POST_SOLVE",err,error)
991  RETURN 1
992 
993  END SUBROUTINE darcy_pressure_post_solve
994 
995  !
996  !================================================================================================================================
997  !
998 
1000  SUBROUTINE darcy_pressure_pre_solve(CONTROL_LOOP,SOLVER,ERR,ERROR,*)
1002  !Argument variables
1003  TYPE(control_loop_type), POINTER :: CONTROL_LOOP
1004  TYPE(solver_type), POINTER :: SOLVER
1005  INTEGER(INTG), INTENT(OUT) :: ERR
1006  TYPE(varying_string), INTENT(OUT) :: ERROR
1007  !Local Variables
1008  TYPE(varying_string) :: LOCAL_ERROR
1009 
1010  enters("DARCY_PRESSURE_PRE_SOLVE",err,error,*999)
1011 
1012  IF(ASSOCIATED(control_loop)) THEN
1013  IF(ASSOCIATED(solver)) THEN
1014  IF(ASSOCIATED(control_loop%PROBLEM)) THEN
1015  IF(.NOT.ALLOCATED(control_loop%PROBLEM%SPECIFICATION)) THEN
1016  CALL flagerror("Problem specification is not allocated.",err,error,*999)
1017  ELSE IF(SIZE(control_loop%PROBLEM%SPECIFICATION,1)<3) THEN
1018  CALL flagerror("Problem specification must have three entries for a Darcy pressure problem.",err,error,*999)
1019  END IF
1020  SELECT CASE(control_loop%PROBLEM%SPECIFICATION(3))
1022  !nothing
1023  CASE DEFAULT
1024  local_error="The third problem specification of "// &
1025  & trim(numbertovstring(control_loop%PROBLEM%SPECIFICATION(3),"*",err,error))// &
1026  & " is not valid for a Darcy pressure type of a fluid mechanics problem."
1027  CALL flagerror(local_error,err,error,*999)
1028  END SELECT
1029  ELSE
1030  CALL flagerror("Problem is not associated.",err,error,*999)
1031  ENDIF
1032  ELSE
1033  CALL flagerror("Solver is not associated.",err,error,*999)
1034  ENDIF
1035  ELSE
1036  CALL flagerror("Control loop is not associated.",err,error,*999)
1037  ENDIF
1038 
1039  exits("DARCY_PRESSURE_PRE_SOLVE")
1040  RETURN
1041 999 errorsexits("DARCY_PRESSURE_PRE_SOLVE",err,error)
1042  RETURN 1
1043  END SUBROUTINE darcy_pressure_pre_solve
1044 
1045  !
1046  !================================================================================================================================
1047  !
1048 
integer(intg), parameter equations_set_setup_dependent_type
Dependent variables.
integer(intg), parameter equations_set_fem_solution_method
Finite Element Method solution method.
This module contains all basis function routines.
integer(intg), parameter equations_set_setup_materials_type
Materials setup.
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.
integer, parameter ptr
Pointer integer kind.
Definition: kinds.f90:58
Contains information on the equations mapping i.e., how field variable DOFS are mapped to the rows an...
Definition: types.f90:1681
Contains information about the equations in an equations set.
Definition: types.f90:1735
integer(intg), parameter equations_set_gfem_solution_method
Grid-based Finite Element Method solution method.
Returns the inverse of a matrix.
Definition: maths.f90:131
This module handles all problem wide constants.
Returns the transpose of a matrix A in A^T.
Definition: maths.f90:191
subroutine, public equations_create_start(EQUATIONS_SET, EQUATIONS, ERR, ERROR,)
Start the creation of equations for the equation set.
Contains information on the mesh decomposition.
Definition: types.f90:1063
subroutine, public equations_matrices_create_start(EQUATIONS, EQUATIONS_MATRICES, ERR, ERROR,)
Starts the creation of the equations matrices and rhs for the the equations.
Contains information on the type of solver to be used.
Definition: types.f90:2777
subroutine darcy_pressure_pre_solve(CONTROL_LOOP, SOLVER, ERR, ERROR,)
Darcy pressure problem pre solve.
integer(intg), parameter no_part_deriv
No partial derivative i.e., u.
Definition: constants.f90:177
This module handles all equations matrix and rhs routines.
integer(intg), parameter equations_static
The equations are static and have no time dependence.
Contains information on an equations set.
Definition: types.f90:1941
This module handles all equations routines.
integer(intg), parameter equations_set_setup_source_type
Source setup.
This module contains all string manipulation and transformation routines.
Definition: strings.f90:45
integer(intg), parameter first_part_deriv
First partial derivative i.e., du/ds.
Definition: constants.f90:178
This module contains routines for timing the program.
Definition: timer_f.f90:45
subroutine, public equations_time_dependence_type_set(EQUATIONS, TIME_DEPENDENCE_TYPE, ERR, ERROR,)
Sets/changes the time dependence type for equations.
integer(intg), parameter equations_set_elasticity_fluid_pressure_holmes_mow_subtype
This module contains all mathematics support routines.
Definition: maths.f90:45
Write a string followed by a matrix to a specified output stream.
Contains information for a field defined on a region.
Definition: types.f90:1346
integer(intg), parameter, public equations_matrices_full_matrices
Use fully populated equation matrices.
subroutine, public darcypressure_equationssetspecificationset(equationsSet, specification, err, error,)
Sets/changes the equation specification for a Darcy pressure type of a fluid mechanics equations set...
integer(intg), parameter equations_set_fluid_mechanics_class
subroutine, public equations_mapping_rhs_variable_type_set(EQUATIONS_MAPPING, RHS_VARIABLE_TYPE, ERR, ERROR,)
Sets the mapping between a dependent field variable and the equations set rhs vector.
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:...
integer(intg), parameter, public basis_default_quadrature_scheme
Identifier for the default quadrature scheme.
integer(intg), parameter equations_set_setup_equations_type
Equations setup.
This module contains all program wide constants.
Definition: constants.f90:45
subroutine, public equationsmapping_linearmatricesnumberset(EQUATIONS_MAPPING, NUMBER_OF_LINEAR_EQUATIONS_MATRICES, ERR, ERROR,)
Sets/changes the number of linear equations matrices.
Contains the interpolated point coordinate metrics. Old CMISS name GL,GU,RG.
Definition: types.f90:1112
subroutine, public darcypressure_finiteelementresidualevaluate(EQUATIONS_SET, ELEMENT_NUMBER, ERR, ERROR,)
Calculates the element residual vector and RHS for a Darcy pressure equation finite element equations...
integer(intg), parameter equations_set_setup_start_action
Start setup action.
Sets the storage type (sparsity) of the nonlinear (Jacobian) equations matrices.
subroutine, public exits(NAME)
Records the exit out of the named procedure.
This module contains all type definitions in order to avoid cyclic module references.
Definition: types.f90:70
Contains information on the equations matrices and vectors.
Definition: types.f90:1520
integer(intg), parameter, public equations_matrix_fem_structure
Finite element matrix structure.
This module contains all the low-level base routines e.g., all debug, control, and low-level communic...
subroutine, public equations_mapping_create_finish(EQUATIONS_MAPPING, ERR, ERROR,)
Finishes the process of creating an equations mapping.
This module handles all Darcy pressure equations routines.
subroutine, public equations_set_equations_get(EQUATIONS_SET, EQUATIONS, ERR, ERROR,)
Gets the equations for an equations set.
subroutine, public darcy_pressure_equation_equations_set_setup(EQUATIONS_SET, EQUATIONS_SET_SETUP, ERR, ERROR,)
Sets up the Darcy pressure equation type of a fluid mechanics equations set class.
subroutine, public finiteelasticity_gaussdeformationgradienttensor(dependentInterpPointMetrics, geometricInterpPointMetrics, fibreInterpolatedPoint, dZdNu, err, error,)
Evaluates the deformation gradient tensor at a given Gauss point.
Sets the structure (sparsity) of the nonlinear (Jacobian) equations matrices.
integer(intg), dimension(4) partial_derivative_first_derivative_map
PARTIAL_DERIVATIVE_FIRST_DERIVATIVE_MAP(nic) gives the partial derivative index for the first derivat...
Definition: constants.f90:254
subroutine, public equations_create_finish(EQUATIONS, ERR, ERROR,)
Finish the creation of equations.
integer(intg), parameter, public write_string_matrix_name_and_indices
Write the matrix name together with the matrix indices.
This module handles all domain mappings routines.
This module handles all equations mapping routines.
integer(intg), parameter, public matrix_compressed_row_storage_type
Matrix compressed row storage type.
integer(intg), parameter equations_set_gfv_solution_method
Grid-based Finite Volume solution method.
integer(intg), parameter equations_set_setup_geometry_type
Geometry setup.
subroutine, public equations_matrices_create_finish(EQUATIONS_MATRICES, ERR, ERROR,)
Finishes the creation of the equations matrices and RHS for the the equations.
logical, save, public diagnostics1
.TRUE. if level 1 diagnostic output is active in the current routine
This module handles all distributed matrix vector routines.
integer(intg), parameter equations_set_elasticity_fluid_pressure_static_inria_subtype
This module handles all boundary conditions routines.
This module handles all solver routines.
subroutine, public equations_mapping_create_start(EQUATIONS, EQUATIONS_MAPPING, ERR, ERROR,)
Finishes the process of creating an equations mapping for a equations set equations.
Contains the interpolated value (and the derivatives wrt xi) of a field at a point. Old CMISS name XG.
Definition: types.f90:1129
integer(intg), parameter problem_standard_elasticity_fluid_pressure_subtype
Contains information for a particular quadrature scheme.
Definition: types.f90:141
This module contains all routines dealing with (non-distributed) matrix and vectors types...
subroutine, public equations_linearity_type_set(EQUATIONS, LINEARITY_TYPE, ERR, ERROR,)
Sets/changes the linearity type for equations.
subroutine, public equationsmapping_residualvariablesnumberset(EQUATIONS_MAPPING, NUMBER_OF_VARIABLES, ERR, ERROR,)
Sets the mapping between a dependent field variable and the equations set residual vector...
integer(intg), parameter, public diagnostic_output_type
Diagnostic output type.
Contains information for a field variable defined on a field.
Definition: types.f90:1289
integer(intg), parameter equations_set_fd_solution_method
Finite Difference solution method.
integer(intg), parameter, public equations_matrices_sparse_matrices
Use sparse equations matrices.
Contains the parameters required to interpolate a field variable within an element. Old CMISS name XE.
Definition: types.f90:1141
Contains information on the setup information for an equations set.
Definition: types.f90:1866
integer(intg), parameter equations_set_elasticity_fluid_pres_holmes_mow_active_subtype
Contains information of the nolinear matrices and vectors for equations matrices. ...
Definition: types.f90:1486
This module handles all control loop routines.
Calculates and returns the matrix-product A*B in the matrix C.
Definition: maths.f90:167
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.
Contains all information about a basis .
Definition: types.f90:184
integer(intg), parameter equations_set_fv_solution_method
Finite Volume solution method.
integer(intg), parameter, public matrix_block_storage_type
Matrix block storage type.
integer(intg), parameter equations_set_darcy_pressure_equation_type
integer(intg), parameter equations_set_setup_initial_type
Initial setup.
subroutine, public equationsmapping_residualvariabletypesset(EQUATIONS_MAPPING, RESIDUAL_VARIABLE_TYPES, ERR, ERROR,)
Sets the mapping between a dependent field variable and the equations set residual vector...
Flags an error condition.
subroutine, public darcypressure_equationssetsolutionmethodset(EQUATIONS_SET, SOLUTION_METHOD, ERR, ERROR,)
Sets/changes the solution method for a Darcy pressure equation type of an fluid mechanics equations s...
subroutine darcy_pressure_post_solve(CONTROL_LOOP, SOLVER, ERR, ERROR,)
Darcy pressure problem post solve.
This module handles all finite elasticity routines.
Contains information of the RHS vector for equations matrices.
Definition: types.f90:1500
integer(intg), parameter equations_nonlinear
The equations are non-linear.
This module contains all kind definitions.
Definition: kinds.f90:45
integer(intg), parameter equations_set_setup_finish_action
Finish setup action.
This module handles all formating and input and output.