OpenCMISS-Iron Internal API Documentation
types.f90
Go to the documentation of this file.
1 
43 
44 !#### Index: ne
45 !### Description:
46 !### Index label for a element.
47 !#### Index: ng
48 !### Description:
49 !### Index label for a gauss point.
50 !#### Index: ni
51 !### Description:
52 !### Index label for a xi direction.
53 !#### Index: nk
54 !### Description:
55 !### Index label for a derivative with respect to the global directions.
56 !#### Index: nn
57 !### Description:
58 !### Index for a local node within an element.
59 !#### Index: np
60 !### Description:
61 !### Index for a node.
62 !#### Index: ns
63 !### Description:
64 !### Index for a element parameter within an element.
65 !#### Index: nu
66 !### Description:
67 !### Index for a partial derivative.
68 
70 MODULE types
71 
74  USE constants
75  USE kinds
76  USE iso_c_binding
78  USE trees
80 
81  IMPLICIT NONE
82 
83  !
84  !================================================================================================================================
85  !
86  ! Base types
87  !
88 
90  REAL(DP), POINTER :: ptr(:)
91  END TYPE real_dp_ptr_type
92 
94  INTEGER(INTG), POINTER :: ptr(:)
95  END TYPE integer_intg_ptr_type
96 
98  INTEGER(C_INT), ALLOCATABLE :: array(:)
100 
101  !
102  !================================================================================================================================
103  !
104  ! List types
105  !
106 
109  TYPE(list_type), POINTER :: ptr
110  END TYPE list_ptr_type
111 
114  LOGICAL :: mutable
115  LOGICAL :: list_finished
116  INTEGER(INTG) :: number_in_list
117  INTEGER(INTG) :: data_dimension
118  INTEGER(INTG) :: initial_size
119  INTEGER(INTG) :: size
120  INTEGER(INTG) :: data_type
121  INTEGER(INTG) :: key_dimension
122  INTEGER(INTG) :: sort_order
123  INTEGER(INTG) :: sort_method
124  INTEGER(INTG), ALLOCATABLE :: list_intg(:)
125  INTEGER(INTG), ALLOCATABLE :: list_intg2(:,:)
126  REAL(SP), ALLOCATABLE :: list_sp(:)
127  REAL(SP), ALLOCATABLE :: list_sp2(:,:)
128  REAL(DP), ALLOCATABLE :: list_dp(:)
129  REAL(DP), ALLOCATABLE :: list_dp2(:,:)
130  INTEGER(C_INT), ALLOCATABLE :: list_c_int(:)
131  INTEGER(C_INT), ALLOCATABLE :: list_c_int2(:,:)
132  END TYPE list_type
133 
134  !
135  !================================================================================================================================
136  !
137  ! Quadrature types
138  !
139 
142  INTEGER(INTG) :: global_number
143  TYPE(quadrature_type), POINTER :: quadrature
144  INTEGER(INTG) :: number_of_gauss
145  REAL(DP), ALLOCATABLE :: gauss_positions(:,:)
146  REAL(DP), ALLOCATABLE :: gauss_weights(:)
147  REAL(DP), ALLOCATABLE :: gauss_basis_fns(:,:,:)
148  !Quadrature information at faces
149  INTEGER(INTG), ALLOCATABLE :: number_of_face_gauss(:)
150  REAL(DP), ALLOCATABLE :: face_gauss_basis_fns(:,:,:,:)
151  REAL(DP), ALLOCATABLE :: face_gauss_positions(:,:,:)
152  REAL(DP), ALLOCATABLE :: face_gauss_weights(:,:)
153  END TYPE quadrature_scheme_type
154 
157  TYPE(quadrature_scheme_type), POINTER :: ptr
159 
162  INTEGER(INTG) :: TYPE
163  TYPE(basis_type), POINTER :: basis
164  INTEGER(INTG), ALLOCATABLE :: number_of_gauss_xi(:)
165  INTEGER(INTG) :: gauss_order
166  TYPE(quadrature_scheme_ptr_type), ALLOCATABLE :: quadrature_scheme_map(:)
167  INTEGER(INTG) :: number_of_schemes
168  TYPE(quadrature_scheme_ptr_type), POINTER :: schemes(:)
169  LOGICAL :: evaluate_face_gauss=.false. !! \todo should this be here??
170  END TYPE quadrature_type
171 
172  !
173  !================================================================================================================================
174  !
175  ! Basis types
176  !
177 
180  TYPE(basis_type), POINTER :: ptr
181  END TYPE basis_ptr_type
182 
185  !\todo Add in different sub types for the different types of bases???
186  INTEGER(INTG) :: user_number
187  INTEGER(INTG) :: global_number
188  INTEGER(INTG) :: family_number
189  LOGICAL :: basis_finished
190  LOGICAL :: hermite
191  INTEGER(INTG) :: TYPE
192  INTEGER(INTG) :: number_of_xi
193  INTEGER(INTG) :: number_of_xi_coordinates
194  INTEGER(INTG), ALLOCATABLE :: interpolation_xi(:)
195  INTEGER(INTG), ALLOCATABLE :: interpolation_type(:)
196  INTEGER(INTG), ALLOCATABLE :: interpolation_order(:)
197  !Degenerate information
198  LOGICAL :: degenerate
199  INTEGER(INTG), ALLOCATABLE :: collapsed_xi(:)
200  INTEGER(INTG) :: number_of_collapsed_xi
201  LOGICAL, ALLOCATABLE :: node_at_collapse(:)
202  !Quadrature
203  TYPE(quadrature_type) :: quadrature
204  INTEGER(INTG) :: number_of_partial_derivatives
205  INTEGER(INTG) :: number_of_nodes
206  !\todo
207  INTEGER(INTG), ALLOCATABLE :: number_of_nodes_xic(:)
208  INTEGER(INTG) :: number_of_element_parameters
209  INTEGER(INTG) :: maximum_number_of_derivatives
210  INTEGER(INTG), ALLOCATABLE :: number_of_derivatives(:)
211  INTEGER(INTG), ALLOCATABLE :: node_position_index(:,:)
212  INTEGER(INTG), ALLOCATABLE :: node_position_index_inv(:,:,:,:)
213  INTEGER(INTG), ALLOCATABLE :: derivative_order_index(:,:,:)
214  INTEGER(INTG), ALLOCATABLE :: derivative_order_index_inv(:,:,:,:)
215  INTEGER(INTG), ALLOCATABLE :: partial_derivative_index(:,:)
216  INTEGER(INTG), ALLOCATABLE :: element_parameter_index(:,:)
217  INTEGER(INTG), ALLOCATABLE :: element_parameter_index_inv(:,:)
218  !Line information
219  INTEGER(INTG) :: number_of_local_lines
220  INTEGER(INTG), ALLOCATABLE :: local_line_xi_direction(:)
221  INTEGER(INTG), ALLOCATABLE :: number_of_nodes_in_local_line(:)
222  INTEGER(INTG), ALLOCATABLE :: node_numbers_in_local_line(:,:)
223  INTEGER(INTG), ALLOCATABLE :: derivative_numbers_in_local_line(:,:)
224  INTEGER(INTG), ALLOCATABLE :: element_parameters_in_local_line(:,:)
225  !Face information
226  INTEGER(INTG) :: number_of_local_faces
227  INTEGER(INTG), ALLOCATABLE :: local_face_xi_direction(:)
228  INTEGER(INTG), ALLOCATABLE :: number_of_nodes_in_local_face(:)
229  INTEGER(INTG), ALLOCATABLE :: node_numbers_in_local_face(:,:)
230  INTEGER(INTG), ALLOCATABLE :: derivative_numbers_in_local_face(:,:,:)
231  INTEGER(INTG), ALLOCATABLE :: element_parameters_in_local_face(:,:)
232  !\todo What is the difference between LOCAL_XI_NORMAL and LOCAL_FACE_XI_DIRECTION ? They're the same
233  INTEGER(INTG), ALLOCATABLE :: local_xi_normal(:)
234  !Sub-basis information
235  TYPE(basis_ptr_type), POINTER :: line_bases(:)
236  TYPE(basis_ptr_type), POINTER :: face_bases(:)
237  INTEGER(INTG) :: number_of_sub_bases
238  TYPE(basis_ptr_type), POINTER :: sub_bases(:)
239  TYPE(basis_type), POINTER :: parent_basis
240  END TYPE basis_type
241 
244  INTEGER(INTG) :: number_basis_functions
245  TYPE(basis_ptr_type), POINTER :: bases(:)
246  END TYPE basis_functions_type
247 
248  !
249  !================================================================================================================================
250  !
251  ! Coordinate system types
252  !
253 
255  TYPE, bind(c) :: coordinate_system_type
256  INTEGER(INTG) :: user_number
257  LOGICAL :: coordinate_system_finished
258  INTEGER(INTG) :: TYPE
259  INTEGER(INTG) :: radial_interpolation_type
260  INTEGER(INTG) :: number_of_dimensions
261  REAL(DP) :: focus
262  REAL(DP) :: origin(3)
263  REAL(DP) :: orientation(3,3)
264  END TYPE coordinate_system_type
265 
268  TYPE(coordinate_system_type), POINTER :: ptr
270 
271  !
272  !================================================================================================================================
273  !
274  ! Data projection types
275  !
276 
279  INTEGER(INTG) :: user_number
280  REAL(DP) :: distance
281  INTEGER(INTG) :: element_number
282  INTEGER(INTG) :: element_face_number
283  INTEGER(INTG) :: element_line_number
284  INTEGER(INTG) :: exit_tag
285  REAL(DP), ALLOCATABLE :: xi(:)
286  REAL(DP), ALLOCATABLE :: projectionvector(:)
288 
290  INTEGER(INTG) :: global_number
291  INTEGER(INTG) :: user_number
292  TYPE(varying_string) :: label
293  LOGICAL :: data_projection_finished
294  TYPE(data_points_type), POINTER :: data_points
295  TYPE(field_type), POINTER :: projection_field
296  INTEGER(INTG) :: coordinate_system_dimensions
297  REAL(DP) :: maximum_iteration_update
298  INTEGER(INTG) :: maximum_number_of_iterations
299  TYPE(mesh_type), POINTER :: mesh
300  INTEGER(INTG) :: number_of_closest_elements
301  INTEGER(INTG) :: number_of_xi
302  INTEGER(INTG) :: projection_type
303  REAL(DP), ALLOCATABLE :: starting_xi(:)
304  REAL(DP) :: absolute_tolerance
305  REAL(DP) :: relative_tolerance
306  INTEGER(INTG), ALLOCATABLE :: candidateelementnumbers(:)
307  INTEGER(INTG), ALLOCATABLE :: localfacelinenumbers(:)
308  LOGICAL :: data_projection_projected
309  TYPE(data_projection_result_type), ALLOCATABLE :: data_projection_results(:)
310  END TYPE data_projection_type
311 
314  TYPE(data_projection_type), POINTER :: ptr
315  END TYPE data_projection_ptr_type
316 
317  !
318  !================================================================================================================================
319  !
320  ! Data point types
321  !
322 
325  INTEGER(INTG) :: global_number
326  INTEGER(INTG) :: user_number
327  TYPE(varying_string) :: label
328  REAL(DP), ALLOCATABLE :: position(:) !Values of the data point specifying the spatial position in the region, has the size of region dimension the data point belongs to.
329  REAL(DP), ALLOCATABLE :: weights(:)
330  END TYPE data_point_type
331 
334  TYPE(region_type), POINTER :: region
335  TYPE(interface_type), POINTER :: interface
336  LOGICAL :: data_points_finished
337  INTEGER(INTG) :: number_of_data_points
338  TYPE(data_point_type), ALLOCATABLE :: data_points(:)
339  TYPE(tree_type), POINTER :: data_points_tree
340  INTEGER(INTG) :: number_of_data_projections
341  TYPE(data_projection_ptr_type), ALLOCATABLE :: data_projections(:)
342  TYPE(tree_type), POINTER :: data_projections_tree
343  END TYPE data_points_type
344 
345  !
346  !================================================================================================================================
347  !
348  ! Node types
349  !
350 
353  INTEGER(INTG) :: global_number
354  INTEGER(INTG) :: user_number
355  TYPE(varying_string) :: label
356  END TYPE node_type
357 
360  TYPE(region_type), POINTER :: region
361  TYPE(interface_type), POINTER :: interface
362  LOGICAL :: nodes_finished
363  INTEGER(INTG) :: number_of_nodes
364  TYPE(node_type), ALLOCATABLE :: nodes(:)
365  INTEGER(INTG), ALLOCATABLE :: coupled_nodes(:,:)
366  TYPE(tree_type), POINTER :: nodes_tree
367  END TYPE nodes_type
368 
369  !
370  !================================================================================================================================
371  !
372  ! Mesh types
373  !
374 
377  TYPE(meshcomponenttopologytype), POINTER :: meshcomponenttopology
378  INTEGER(INTG) :: numberofdofs
379  END TYPE meshdofstype
380 
383  INTEGER(INTG) :: number_of_adjacent_elements
384  INTEGER(INTG), ALLOCATABLE :: adjacent_elements(:)
386 
389  INTEGER(INTG) :: global_number
390  INTEGER(INTG) :: user_number
391  TYPE(basis_type), POINTER :: basis
392  INTEGER(INTG), ALLOCATABLE :: mesh_element_nodes(:)
393  INTEGER(INTG), ALLOCATABLE :: global_element_nodes(:)
394  INTEGER(INTG), ALLOCATABLE :: user_element_node_versions(:,:)
395  INTEGER(INTG), ALLOCATABLE :: user_element_nodes(:)
396  TYPE(mesh_adjacent_element_type), ALLOCATABLE :: adjacent_elements(:)
397  !INTEGER(INTG), ALLOCATABLE :: NUMBER_OF_ADJACENT_ELEMENTS(:) !<NUMBER_OF_ADJACENT_ELEMENTS(-ni:ni). The number of elements adjacent to this element in the ni'th xi direction. Note that -ni gives the adjacent element before the element in the ni'th direction and +ni gives the adjacent element after the element in the ni'th direction. The ni=0 index should be 1 for the current element. Old CMISS name NXI(-ni:ni,0:nei,ne).
398  !INTEGER(INTG), ALLOCATABLE :: ADJACENT_ELEMENTS(:,:) !<ADJACENT_ELEMENTS(nei,-ni:ni). The local element numbers of the elements adjacent to this element in the ni'th xi direction. Note that -ni gives the adjacent elements before the element in the ni'th direction and +ni gives the adjacent elements after the element in the ni'th direction. The ni=0 index should give the current element number. Old CMISS name NXI(-ni:ni,0:nei,ne)
399  LOGICAL :: boundary_element
400  END TYPE mesh_element_type
401 
404  TYPE(meshcomponenttopologytype), POINTER :: meshcomponenttopology
405  INTEGER(INTG) :: number_of_elements
406  LOGICAL :: elements_finished
407  TYPE(mesh_element_type), POINTER :: elements(:)
408  TYPE(tree_type), POINTER :: elements_tree
409  END TYPE meshelementstype
410 
413  INTEGER(INTG) :: numberofversions !The number of global versions at the node for the mesh.
414  INTEGER(INTG), ALLOCATABLE :: userversionnumbers(:) !userVersionNumbers(versionIdx). The user version numbers for the versionIdx'th version for the node.
415  INTEGER(INTG), ALLOCATABLE :: dofindex(:) !The global dof version index (nv) in the domain of the nk'th global derivative for the node.
416  INTEGER(INTG) :: globalderivativeindex !The global derivative index of the nk'th global derivative for the node.
417  INTEGER(INTG) :: partialderivativeindex !The partial derivative index (nu) of the nk'th global derivative for the node. Old CMISS name NUNK(nk,nj,np).
418  END TYPE meshnodederivativetype
419 
422  INTEGER(INTG) :: meshnumber
423  INTEGER(INTG) :: globalnumber
424  INTEGER(INTG) :: usernumber
425  INTEGER(INTG) :: numberofderivatives
426  TYPE(meshnodederivativetype), ALLOCATABLE :: derivatives(:)
427  INTEGER(INTG) :: numberofsurroundingelements
428  INTEGER(INTG), POINTER :: surroundingelements(:)
429  LOGICAL :: boundarynode
430  END TYPE meshnodetype
431 
434  TYPE(meshcomponenttopologytype), POINTER :: meshcomponenttopology
435  INTEGER(INTG) :: numberofnodes
436  TYPE(meshnodetype), ALLOCATABLE :: nodes(:)
437  TYPE(tree_type), POINTER :: nodestree
438  END TYPE meshnodestype
439 
441  INTEGER(INTG) :: usernumber
442  INTEGER(INTG) :: globalnumber
443  END TYPE meshelementdatapointtype
444 
447  INTEGER(INTG) :: numberofprojecteddata
448  INTEGER(INTG) :: elementnumber
449  TYPE(meshelementdatapointtype), ALLOCATABLE :: dataindices(:)
451 
454  INTEGER(INTG) :: usernumber
455  INTEGER(INTG) :: globalnumber
456  INTEGER(INTG) :: elementnumber
457  END TYPE meshdatapointtype
458 
459 
461  TYPE(meshcomponenttopologytype), POINTER :: meshcomponenttopology
462  INTEGER(INTG) :: totalnumberofprojecteddata
463  TYPE(meshdatapointtype), ALLOCATABLE :: datapoints(:)
464  TYPE(meshelementdatapointstype), ALLOCATABLE :: elementdatapoint(:)
465  END TYPE meshdatapointstype
466 
469  TYPE(mesh_type), POINTER :: mesh
470  INTEGER(INTG) :: meshcomponentnumber
471  TYPE(meshnodestype), POINTER :: nodes
472  TYPE(meshelementstype), POINTER :: elements
473  TYPE(meshdofstype), POINTER :: dofs
474  TYPE(meshdatapointstype), POINTER :: datapoints
476 
479  TYPE(meshcomponenttopologytype), POINTER :: ptr
481 
484  INTEGER(INTG) :: number_of_nodes
485  INTEGER(INTG), ALLOCATABLE :: node_numbers(:)
486  REAL(DP), ALLOCATABLE :: xi_coords(:,:)
487  END TYPE embedding_xi_type
488 
490  INTEGER(INTG) :: element_number
491  REAL(DP), ALLOCATABLE :: child_xi_coord(:)
492  REAL(DP), ALLOCATABLE :: parent_xi_coord(:)
494 
496  TYPE(mesh_type), POINTER :: child_mesh, parent_mesh
497  TYPE(embedding_xi_type), ALLOCATABLE :: child_node_xi_position(:)
498  TYPE(embedding_gausspoint_type), ALLOCATABLE :: gauss_point_xi_position(:,:)
499  END TYPE mesh_embedding_type
500 
501 
504  INTEGER(INTG) :: user_number
505  INTEGER(INTG) :: global_number
506  LOGICAL :: mesh_finished
507  TYPE(meshes_type), POINTER :: meshes
508  TYPE(region_type), POINTER :: region
509  TYPE(interface_type), POINTER :: interface
510  TYPE(generated_mesh_type), POINTER :: generated_mesh
511  INTEGER(INTG) :: number_of_dimensions
512  INTEGER(INTG) :: number_of_components
513  LOGICAL :: mesh_embedded
514  TYPE(mesh_type), POINTER :: embedding_mesh
515  INTEGER(INTG) :: number_of_embedded_meshes
516  TYPE(mesh_ptr_type), POINTER :: embedded_meshes(:)
517  INTEGER(INTG) :: number_of_elements
518  TYPE(meshcomponenttopologyptrtype), POINTER :: topology(:)
519  TYPE(decompositions_type), POINTER :: decompositions
520  LOGICAL :: surrounding_elements_calculate
521  END TYPE mesh_type
522 
525  TYPE(mesh_type), POINTER :: ptr
526  END TYPE mesh_ptr_type
527 
530  TYPE(region_type), POINTER :: region
531  TYPE(interface_type), POINTER :: interface
532  INTEGER(INTG) :: number_of_meshes
533  TYPE(mesh_ptr_type), POINTER :: meshes(:)
534  END TYPE meshes_type
535 
536  !
537  !================================================================================================================================
538  !
539  ! Generated Mesh types
540  !
541 
544  TYPE(generated_mesh_type), POINTER :: generated_mesh
545  TYPE(basis_ptr_type), ALLOCATABLE :: bases(:)
546  INTEGER(INTG) :: coordinate_dimension
547  INTEGER(INTG) :: mesh_dimension
548  REAL(DP), ALLOCATABLE :: origin(:)
549  REAL(DP), ALLOCATABLE :: maximum_extent(:)
550  REAL(DP), ALLOCATABLE :: base_vectors(:,:)
551  INTEGER(INTG), ALLOCATABLE :: number_of_elements_xi(:)
553 
557  TYPE(generated_mesh_type), POINTER :: generated_mesh
558  REAL(DP), ALLOCATABLE :: origin(:)
559  REAL(DP), ALLOCATABLE :: cylinder_extent(:)
560  INTEGER(INTG) :: mesh_dimension
561  INTEGER(INTG), ALLOCATABLE :: number_of_elements_xi(:)
562  TYPE(basis_ptr_type), ALLOCATABLE :: bases(:)
563  LOGICAL :: append_linear_component=.false.
565 
569  TYPE(generated_mesh_type), POINTER :: generated_mesh
570  REAL(DP), ALLOCATABLE :: origin(:)
571  REAL(DP), ALLOCATABLE :: ellipsoid_extent(:)
572  INTEGER(INTG) :: mesh_dimension
573  INTEGER(INTG), ALLOCATABLE :: number_of_elements_xi(:)
574  TYPE(basis_ptr_type), ALLOCATABLE :: bases(:)
575  LOGICAL :: append_linear_component=.false.
577 
580  INTEGER(INTG) :: user_number
581  INTEGER(INTG) :: global_number
582  TYPE(generated_meshes_type), POINTER :: generated_meshes
583  LOGICAL :: generated_mesh_finished
584  TYPE(region_type), POINTER :: region
585  TYPE(interface_type), POINTER :: interface
586  INTEGER(INTG) :: generated_type
587  TYPE(generated_mesh_regular_type), POINTER :: regular_mesh
588  TYPE(generated_mesh_cylinder_type), POINTER :: cylinder_mesh
589  TYPE(generated_mesh_ellipsoid_type), POINTER :: ellipsoid_mesh
590  TYPE(mesh_type), POINTER :: mesh
591  END TYPE generated_mesh_type
592 
595  TYPE(generated_mesh_type), POINTER :: ptr
596  END TYPE generated_mesh_ptr_type
597 
600  TYPE(region_type), POINTER :: region
601  TYPE(interface_type), POINTER :: interface
602  INTEGER(INTG) :: number_of_generated_meshes
603  TYPE(generated_mesh_ptr_type), POINTER :: generated_meshes(:)
604  END TYPE generated_meshes_type
605 
606  !
607  !================================================================================================================================
608  !
609  ! Domain types
610  !
611 
614  TYPE(domain_type), POINTER :: domain
615  INTEGER(INTG) :: number_of_dofs
616  INTEGER(INTG) :: total_number_of_dofs
617  INTEGER(INTG) :: number_of_global_dofs
618  INTEGER(INTG), ALLOCATABLE :: dof_index(:,:)
619  END TYPE domain_dofs_type
620 
623  INTEGER(INTG) :: number
624  TYPE(basis_type), POINTER :: basis
625  INTEGER(INTG), ALLOCATABLE :: nodes_in_line(:)
626  INTEGER(INTG), ALLOCATABLE :: derivatives_in_line(:,:,:)
627  LOGICAL :: boundary_line
628  INTEGER(INTG) :: element_number
629  END TYPE domain_line_type
630 
633  TYPE(domain_line_type), POINTER :: ptr
634  END TYPE domain_line_ptr_type
635 
638  TYPE(domain_type), POINTER :: domain
639  INTEGER(INTG) :: number_of_lines
640  TYPE(domain_line_type), ALLOCATABLE :: lines(:)
641  END TYPE domain_lines_type
642 
645  INTEGER(INTG) :: number
646  INTEGER(INTG) :: xi_direction1
647  INTEGER(INTG) :: xi_direction2
648  TYPE(basis_type), POINTER :: basis
649  INTEGER(INTG), ALLOCATABLE :: nodes_in_face(:)
650  INTEGER(INTG), ALLOCATABLE :: derivatives_in_face(:,:,:)
651  LOGICAL :: boundary_face
652  INTEGER(INTG) :: element_number
653  END TYPE domain_face_type
654 
657  TYPE(domain_face_type), POINTER :: ptr
658  END TYPE domain_face_ptr_type
659 
662  TYPE(domain_type), POINTER :: domain
663  INTEGER(INTG) :: number_of_faces
664  TYPE(domain_face_type), ALLOCATABLE :: faces(:)
665  END TYPE domain_faces_type
666 
669  INTEGER(INTG) :: number
670  TYPE(basis_type), POINTER :: basis
671  INTEGER(INTG), ALLOCATABLE :: element_nodes(:)
672  INTEGER(INTG), ALLOCATABLE :: element_derivatives(:,:)
673  INTEGER(INTG), ALLOCATABLE :: elementversions(:,:)
674  END TYPE domain_element_type
675 
678  TYPE(domain_type), POINTER :: domain
679  INTEGER(INTG) :: number_of_elements
680  INTEGER(INTG) :: total_number_of_elements
681  INTEGER(INTG) :: number_of_global_elements
682  TYPE(domain_element_type), POINTER :: elements(:)
683  INTEGER(INTG) :: maximum_number_of_element_parameters
684  END TYPE domain_elements_type
685 
688  INTEGER(INTG) :: numberofversions !The number of global versions at the node for the mesh.
689  INTEGER(INTG), ALLOCATABLE :: userversionnumbers(:) !The user version index of the nk'th global derivative for the node.
690  INTEGER(INTG), ALLOCATABLE :: dof_index(:) !The local dof derivative version index in the domain of the nk'th global derivative for the node.
691  INTEGER(INTG) :: global_derivative_index !The global derivative index of the nk'th global derivative for the node.
692  INTEGER(INTG) :: partial_derivative_index !The partial derivative index (nu) of the nk'th global derivative for the node. Old CMISS name NUNK(nk,nj,np).
694 
697  INTEGER(INTG) :: local_number
698  INTEGER(INTG) :: mesh_number
699  INTEGER(INTG) :: global_number
700  INTEGER(INTG) :: user_number
701  INTEGER(INTG) :: number_of_derivatives
702  TYPE(domain_node_derivative_type), ALLOCATABLE :: derivatives(:)
703  INTEGER(INTG) :: number_of_surrounding_elements
704  INTEGER(INTG), POINTER :: surrounding_elements(:)
705  INTEGER(INTG) :: number_of_node_lines
706  INTEGER(INTG), ALLOCATABLE :: node_lines(:)
707  INTEGER(INTG) :: number_of_node_faces
708  INTEGER(INTG), ALLOCATABLE :: node_faces(:)
709  LOGICAL :: boundary_node
710  END TYPE domain_node_type
711 
714  TYPE(domain_type), POINTER :: domain
715  INTEGER(INTG) :: number_of_nodes
716  INTEGER(INTG) :: total_number_of_nodes
717  INTEGER(INTG) :: number_of_global_nodes
718  INTEGER(INTG) :: maximum_number_of_derivatives
719  TYPE(domain_node_type), POINTER :: nodes(:)
720  TYPE(tree_type), POINTER :: nodes_tree
721  END TYPE domain_nodes_type
722 
725  TYPE(domain_type), POINTER :: domain
726  TYPE(domain_nodes_type), POINTER :: nodes
727  TYPE(domain_dofs_type), POINTER :: dofs
728  TYPE(domain_elements_type), POINTER :: elements
729  TYPE(domain_faces_type), POINTER :: faces
730  TYPE(domain_lines_type), POINTER :: lines
731  END TYPE domain_topology_type
732 
733  !
734  !================================================================================================================================
735  !
736  ! Distributed matrix vector types
737  !
738 
742  TYPE(distributed_vector_cmiss_type), POINTER :: cmiss_vector
743  INTEGER(INTG) :: data_type
744  INTEGER(INTG) :: send_buffer_size
745  INTEGER(INTG) :: receive_buffer_size
746  INTEGER(INTG) :: send_tag_number
747  INTEGER(INTG) :: receive_tag_number
748  INTEGER(INTG) :: mpi_send_request
749  INTEGER(INTG) :: mpi_receive_request
750  INTEGER(INTG), ALLOCATABLE :: send_buffer_intg(:)
751  REAL(DP), ALLOCATABLE :: send_buffer_dp(:)
752  REAL(SP), ALLOCATABLE :: send_buffer_sp(:)
753  LOGICAL, ALLOCATABLE :: send_buffer_l(:)
754  INTEGER(INTG), ALLOCATABLE :: receive_buffer_intg(:)
755  REAL(DP), ALLOCATABLE :: receive_buffer_dp(:)
756  REAL(SP), ALLOCATABLE :: receive_buffer_sp(:)
757  LOGICAL, ALLOCATABLE :: receive_buffer_l(:)
759 
762  TYPE(distributed_vector_type), POINTER :: distributed_vector
763  INTEGER(INTG) :: base_tag_number
764  INTEGER(INTG) :: n
765  INTEGER(INTG) :: data_size
766  INTEGER(INTG), ALLOCATABLE :: data_intg(:)
767  REAL(DP), ALLOCATABLE :: data_dp(:)
768  REAL(SP), ALLOCATABLE :: data_sp(:)
769  LOGICAL, ALLOCATABLE :: data_l(:)
770  TYPE(distributed_vector_transfer_type), ALLOCATABLE :: transfers(:)
772 
775  TYPE(distributed_vector_type), POINTER :: distributed_vector
776  INTEGER(INTG) :: n
777  INTEGER(INTG) :: global_n
778  INTEGER(INTG) :: data_size
779  INTEGER(INTG), ALLOCATABLE :: global_numbers(:)
780  LOGICAL :: use_override_vector
781  TYPE(petscvectype) :: vector
782  TYPE(petscvectype) :: override_vector
784 
787  LOGICAL :: vector_finished
788  INTEGER(INTG) :: library_type
789  INTEGER(INTG) :: ghosting_type
790  TYPE(domain_mapping_type), POINTER :: domain_mapping
791  INTEGER(INTG) :: data_type
793  TYPE(distributed_vector_petsc_type), POINTER :: petsc
794  END TYPE distributed_vector_type
795 
798  TYPE(distributed_matrix_type), POINTER :: distributed_matrix
799  INTEGER(INTG) :: base_tag_number
800  TYPE(matrix_type), POINTER :: matrix
801 ! TYPE(LINKEDLIST),POINTER :: LIST(:) !< \todo Comment
803 
806  TYPE(distributed_matrix_type), POINTER :: distributed_matrix
807  INTEGER(INTG) :: m
808  INTEGER(INTG) :: n
809  INTEGER(INTG) :: global_m
810  INTEGER(INTG) :: global_n
811  INTEGER(INTG) :: storage_type
812  INTEGER(INTG) :: number_non_zeros
813  INTEGER(INTG) :: data_size
814  INTEGER(INTG) :: maximum_column_indices_per_row
815  INTEGER(INTG), ALLOCATABLE :: diagonal_number_non_zeros(:)
816  INTEGER(INTG), ALLOCATABLE :: offdiagonal_number_non_zeros(:)
817  INTEGER(INTG), ALLOCATABLE :: row_indices(:)
818  INTEGER(INTG), ALLOCATABLE :: column_indices(:)
819  TYPE(linkedlist),POINTER :: list(:)
820  INTEGER(INTG), ALLOCATABLE :: global_row_numbers(:)
821  REAL(DP), POINTER :: data_dp(:)
822  LOGICAL :: use_override_matrix
823  TYPE(petscmattype) :: matrix
824  TYPE(petscmattype) :: override_matrix
826 
829  LOGICAL :: matrix_finished
830  INTEGER(INTG) :: library_type
831  INTEGER(INTG) :: ghosting_type
832  TYPE(domain_mapping_type), POINTER :: row_domain_mapping
833  TYPE(domain_mapping_type), POINTER :: column_domain_mapping
834  INTEGER(INTG) :: data_type
836  TYPE(distributed_matrix_petsc_type), POINTER :: petsc
837  END TYPE distributed_matrix_type
838 
839  !
840  !================================================================================================================================
841  !
842  ! Matrix vector types
843  !
844 
847  INTEGER(INTG) :: id
848  LOGICAL :: vector_finished
849  INTEGER(INTG) :: n
850  INTEGER(INTG) :: data_type
851  INTEGER(INTG) :: size
852  INTEGER(INTG), ALLOCATABLE :: data_intg(:)
853  REAL(SP), ALLOCATABLE :: data_sp(:)
854  REAL(DP), ALLOCATABLE :: data_dp(:)
855  LOGICAL, ALLOCATABLE :: data_l(:)
856  END TYPE vector_type
857 
860  INTEGER(INTG) :: id
861  LOGICAL :: matrix_finished
862  INTEGER(INTG) :: m
863  INTEGER(INTG) :: n
864  INTEGER(INTG) :: max_m
865  INTEGER(INTG) :: max_n
866  INTEGER(INTG) :: data_type
867  INTEGER(INTG) :: storage_type
868  INTEGER(INTG) :: number_non_zeros
869  INTEGER(INTG) :: size
870  INTEGER(INTG) :: maximum_column_indices_per_row
871  INTEGER(INTG), ALLOCATABLE :: row_indices(:)
872  INTEGER(INTG), ALLOCATABLE :: column_indices(:)
873  TYPE(linkedlist),POINTER :: list(:) !\todo Comment
874  INTEGER(INTG), ALLOCATABLE :: data_intg(:)
875  REAL(SP), ALLOCATABLE :: data_sp(:)
876  REAL(DP), ALLOCATABLE :: data_dp(:)
877  LOGICAL, ALLOCATABLE :: data_l(:)
878  END TYPE matrix_type
879 
880  !
881  !================================================================================================================================
882  !
883  ! Domain mapping types
884  !
885 
888  INTEGER(INTG) :: domain_number
889  INTEGER(INTG) :: number_of_send_ghosts
890  INTEGER(INTG) :: number_of_receive_ghosts
891  INTEGER(INTG), ALLOCATABLE :: local_ghost_send_indices(:)
892  INTEGER(INTG), ALLOCATABLE :: local_ghost_receive_indices(:)
894 
897  INTEGER(INTG) :: number_of_domains
898  INTEGER(INTG), ALLOCATABLE :: local_number(:)
899  INTEGER(INTG), ALLOCATABLE :: domain_number(:)
900  INTEGER(INTG), ALLOCATABLE :: local_type(:)
902 
905  INTEGER(INTG) :: number_of_local
906  INTEGER(INTG) :: total_number_of_local
907  INTEGER(INTG), ALLOCATABLE :: number_of_domain_local(:)
908  INTEGER(INTG), ALLOCATABLE :: number_of_domain_ghost(:)
909  INTEGER(INTG) :: number_of_global
910  INTEGER(INTG) :: number_of_domains
911  INTEGER(INTG) :: number_of_internal
912  INTEGER(INTG) :: number_of_boundary
913  INTEGER(INTG) :: number_of_ghost
914  INTEGER(INTG) :: internal_start
915  INTEGER(INTG) :: internal_finish
916  INTEGER(INTG) :: boundary_start
917  INTEGER(INTG) :: boundary_finish
918  INTEGER(INTG) :: ghost_start
919  INTEGER(INTG) :: ghost_finish
920  INTEGER(INTG), ALLOCATABLE :: domain_list(:)
921  INTEGER(INTG), ALLOCATABLE :: local_to_global_map(:)
922  TYPE(domain_global_mapping_type), ALLOCATABLE :: global_to_local_map(:)
923  INTEGER(INTG) :: number_of_adjacent_domains
924  INTEGER(INTG), ALLOCATABLE :: adjacent_domains_ptr(:)
925  INTEGER(INTG), ALLOCATABLE :: adjacent_domains_list(:)
926  TYPE(domain_adjacent_domain_type), ALLOCATABLE :: adjacent_domains(:)
927  END TYPE domain_mapping_type
928 
931  TYPE(domain_type), POINTER :: domain
932  TYPE(domain_mapping_type), POINTER :: elements
933  TYPE(domain_mapping_type), POINTER :: nodes
934  TYPE(domain_mapping_type), POINTER :: dofs
935  END TYPE domain_mappings_type
936 
939  TYPE(decomposition_type), POINTER :: decomposition
940  TYPE(mesh_type), POINTER :: mesh
941  INTEGER(INTG) :: mesh_component_number
942  TYPE(region_type), POINTER :: region
943  INTEGER(INTG) :: number_of_dimensions
944  INTEGER(INTG), ALLOCATABLE :: node_domain(:)
945  TYPE(domain_mappings_type), POINTER :: mappings
946  TYPE(domain_topology_type), POINTER :: topology
947  END TYPE domain_type
948 
951  TYPE(domain_type), POINTER :: ptr
952  END TYPE domain_ptr_type
953 
954  !
955  !================================================================================================================================
956  !
957  ! Decomposition types
958  !
959 
962  INTEGER(INTG) :: number
963  INTEGER(INTG) :: xi_direction
964  INTEGER(INTG) :: number_of_surrounding_elements
965  INTEGER(INTG), ALLOCATABLE :: surrounding_elements(:)
966  INTEGER(INTG), ALLOCATABLE :: element_lines(:)
967  INTEGER(INTG) :: adjacent_lines(0:1)
968  LOGICAL :: boundary_line
969  END TYPE decomposition_line_type
970 
973  TYPE(decomposition_type), POINTER :: decomposition
974  INTEGER(INTG) :: number_of_lines
975  TYPE(decomposition_line_type), ALLOCATABLE :: lines(:)
976  END TYPE decomposition_lines_type
977 
980  INTEGER(INTG) :: number
981  INTEGER(INTG) :: xi_direction
982  INTEGER(INTG) :: number_of_surrounding_elements
983  INTEGER(INTG), ALLOCATABLE :: surrounding_elements(:)
984  INTEGER(INTG), ALLOCATABLE :: element_faces(:)
985 ! INTEGER(INTG) :: ADJACENT_FACES(0:1) !<ADJACENT_FACES(0:1). The face number of adjacent faces. ADJACENT_FACES(0) is the face number adjacent in the -xi direction. ADJACENT_FACES(1) is the face number adjacent in the +xi direction. Old CMISS name NPL(2..3,0,nl).
986  LOGICAL :: boundary_face
987  INTEGER(INTG) :: element_number
988  END TYPE decomposition_face_type
989 
992  TYPE(decomposition_type), POINTER :: decomposition
993  INTEGER(INTG) :: number_of_faces
994  TYPE(decomposition_face_type), ALLOCATABLE :: faces(:)
995  END TYPE decomposition_faces_type
996 
999  INTEGER(INTG) :: number_of_adjacent_elements
1000  INTEGER(INTG), ALLOCATABLE :: adjacent_elements(:)
1002 
1005  INTEGER(INTG) :: local_number
1006  INTEGER(INTG) :: global_number
1007  INTEGER(INTG) :: user_number
1008  TYPE(decomposition_adjacent_element_type), ALLOCATABLE :: adjacent_elements(:)
1009  !\todo INTEGER(INTG), ALLOCATABLE :: NUMBER_OF_ADJACENT_ELEMENTS(:) !<NUMBER_OF_ADJACENT_ELEMENTS(-ni:ni). The number of elements adjacent to this element in the ni'th xi direction. Note that -ni gives the adjacent element before the element in the ni'th direction and +ni gives the adjacent element after the element in the ni'th direction. The ni=0 index should be 1 for the current element. Old CMISS name NXI(-ni:ni,0:nei,ne).
1010  !\todo INTEGER(INTG), ALLOCATABLE :: ADJACENT_ELEMENTS(:,:) !<ADJACENT_ELEMENTS(nei,-ni:ni). The local element numbers of the elements adjacent to this element in the ni'th xi direction. Note that -ni gives the adjacent elements before the element in the ni'th direction and +ni gives the adjacent elements after the element in the ni'th direction. The ni=0 index should give the current element number. Old CMISS name NXI(-ni:ni,0:nei,ne).
1011  INTEGER(INTG), ALLOCATABLE :: element_lines(:)
1012  INTEGER(INTG), ALLOCATABLE :: element_faces(:)
1013  LOGICAL :: boundary_element
1015 
1018  TYPE(decomposition_type), POINTER :: decomposition
1019  INTEGER(INTG) :: number_of_elements
1020  INTEGER(INTG) :: total_number_of_elements
1021  INTEGER(INTG) :: number_of_global_elements
1022  TYPE(decomposition_element_type), POINTER :: elements(:)
1023  TYPE(tree_type), POINTER :: elements_tree
1025 
1028  INTEGER(INTG) :: usernumber
1029  INTEGER(INTG) :: globalnumber
1030  INTEGER(INTG) :: localnumber
1032 
1035  INTEGER(INTG) :: numberofprojecteddata
1036  INTEGER(INTG) :: globalelementnumber
1037  TYPE(decompositionelementdatapointtype), ALLOCATABLE :: dataindices(:)
1039 
1042  TYPE(decomposition_type), POINTER :: decomposition
1043  INTEGER(INTG) :: numberofdatapoints
1044  INTEGER(INTG) :: totalnumberofdatapoints
1045  INTEGER(INTG) :: numberofglobaldatapoints
1046  INTEGER(INTG), ALLOCATABLE :: numberofdomainlocal(:)
1047  INTEGER(INTG), ALLOCATABLE :: numberofdomainghost(:)
1048  INTEGER(INTG), ALLOCATABLE :: numberofelementdatapoints(:)
1049  TYPE(decompositionelementdatapointstype), ALLOCATABLE :: elementdatapoint(:)
1050  TYPE(tree_type), POINTER :: datapointstree
1052 
1055  TYPE(decomposition_type), POINTER :: decomposition
1056  TYPE(decomposition_elements_type), POINTER :: elements
1057  TYPE(decomposition_lines_type), POINTER :: lines
1058  TYPE(decomposition_faces_type), POINTER :: faces
1059  TYPE(decompositiondatapointstype), POINTER :: datapoints
1061 
1064  INTEGER(INTG) :: user_number
1065  INTEGER(INTG) :: global_number
1066  LOGICAL :: decomposition_finished
1067  TYPE(decompositions_type), POINTER :: decompositions
1068  TYPE(mesh_type), POINTER :: mesh
1069  INTEGER(INTG) :: mesh_component_number
1070  INTEGER(INTG) :: decomposition_type
1071  INTEGER(INTG) :: number_of_domains
1072  INTEGER(INTG) :: number_of_edges_cut
1073  INTEGER(INTG), ALLOCATABLE :: element_domain(:)
1074  TYPE(decomposition_topology_type), POINTER :: topology
1075  TYPE(domain_ptr_type), POINTER :: domain(:)
1076  LOGICAL :: calculate_faces
1077  LOGICAL :: calculate_lines
1078  END TYPE decomposition_type
1079 
1082  TYPE(decomposition_type), POINTER :: ptr
1083  END TYPE decomposition_ptr_type
1084 
1087  TYPE(mesh_type), POINTER :: mesh
1088  INTEGER(INTG) :: number_of_decompositions
1089  TYPE(decomposition_ptr_type), POINTER :: decompositions(:)
1090  END TYPE decompositions_type
1091 
1092  !
1093  !================================================================================================================================
1094  !
1095  ! Field types
1096  !
1097 
1100  TYPE(field_interpolated_point_type), POINTER :: field_interpolated_point
1101  TYPE(field_interpolated_point_type), POINTER :: geometric_interpolated_point
1102  INTEGER(INTG) :: physical_derivative_type
1103  REAL(DP), ALLOCATABLE :: values(:)
1104  END TYPE field_physical_point_type
1105 
1108  TYPE(field_physical_point_type), POINTER :: ptr
1110 
1113  TYPE(field_interpolated_point_type), POINTER :: interpolated_point
1114  INTEGER(INTG) :: number_of_x_dimensions
1115  INTEGER(INTG) :: number_of_xi_dimensions
1116  REAL(DP), ALLOCATABLE :: gl(:,:)
1117  REAL(DP), ALLOCATABLE :: gu(:,:)
1118  REAL(DP), ALLOCATABLE :: dx_dxi(:,:)
1119  REAL(DP), ALLOCATABLE :: dxi_dx(:,:)
1120  REAL(DP) :: jacobian
1121  INTEGER(INTG) :: jacobian_type
1123 
1127 
1130  TYPE(field_interpolation_parameters_type), POINTER :: interpolation_parameters
1131  INTEGER(INTG) :: max_partial_derivative_index
1132  INTEGER(INTG) :: partial_derivative_type
1133  REAL(DP), ALLOCATABLE :: values(:,:)
1135 
1137  TYPE(field_interpolated_point_type), POINTER :: ptr
1139 
1142  TYPE(field_type), POINTER :: field
1143  TYPE(field_variable_type), POINTER :: field_variable
1144  INTEGER(INTG) :: number_of_xi
1145  TYPE(basis_ptr_type), ALLOCATABLE :: bases(:)
1146  INTEGER(INTG), ALLOCATABLE :: number_of_parameters(:)
1147  REAL(DP), ALLOCATABLE :: parameters(:,:)
1148  REAL(DP), ALLOCATABLE :: scale_factors(:,:)
1150 
1154 
1157  INTEGER(INTG) :: number_of_lines
1158  INTEGER(INTG) :: number_of_areas
1159  INTEGER(INTG) :: number_of_volumes
1160  REAL(DP), ALLOCATABLE :: lengths(:)
1161  REAL(DP), ALLOCATABLE :: areas(:)
1162  REAL(DP), ALLOCATABLE :: volumes(:)
1163  INTEGER(INTG) :: number_of_fields_using
1164  TYPE(field_ptr_type), POINTER :: fields_using(:)
1166 
1169  INTEGER(INTG) :: mesh_component_number
1170  INTEGER(INTG) :: max_number_of_derivatives
1171  INTEGER(INTG) :: max_number_of_element_parameters
1172  TYPE(distributed_vector_type), POINTER :: scale_factors
1173  END TYPE field_scaling_type
1174 
1177  INTEGER(INTG) :: scaling_type
1178  INTEGER(INTG) :: number_of_scaling_indices
1179  TYPE(field_scaling_type), ALLOCATABLE :: scalings(:)
1180  END TYPE field_scalings_type
1181 
1184  INTEGER(INTG) :: number_of_dofs
1185  INTEGER(INTG), ALLOCATABLE :: dof_type(:,:)
1186  INTEGER(INTG) :: number_of_constant_dofs
1187  INTEGER(INTG) :: number_of_element_dofs
1188  INTEGER(INTG) :: number_of_node_dofs
1189  INTEGER(INTG) :: number_of_grid_point_dofs
1190  INTEGER(INTG) :: number_of_gauss_point_dofs
1191  INTEGER(INTG) :: number_of_data_point_dofs
1192  INTEGER(INTG), ALLOCATABLE :: constant_dof2param_map(:)
1193  INTEGER(INTG), ALLOCATABLE :: element_dof2param_map(:,:)
1194  INTEGER(INTG), ALLOCATABLE :: node_dof2param_map(:,:)
1195  INTEGER(INTG), ALLOCATABLE :: grid_point_dof2param_map(:,:)
1196  INTEGER(INTG), ALLOCATABLE :: gauss_point_dof2param_map(:,:)
1197  INTEGER(INTG), ALLOCATABLE :: data_point_dof2param_map(:,:)
1199 
1202  INTEGER(INTG) :: number_of_versions
1203  INTEGER(INTG), ALLOCATABLE :: versions(:)
1205 
1208  INTEGER(INTG) :: number_of_derivatives
1209  TYPE(field_node_param_to_dof_map_derivative_type), ALLOCATABLE :: derivatives(:) ! The mapping from field node derivative parameter to a dof
1211 
1214  INTEGER(INTG) :: number_of_node_parameters
1215  TYPE(field_node_param_to_dof_map_node_type), ALLOCATABLE :: nodes(:) ! The mapping from field node parameter to a dof
1217 
1220  INTEGER(INTG) :: number_of_element_parameters
1221  INTEGER(INTG), ALLOCATABLE :: elements(:)
1223 
1226  INTEGER(INTG) :: number_of_grid_point_parameters
1227  INTEGER(INTG), ALLOCATABLE :: grid_points(:)
1229 
1232  INTEGER(INTG) :: number_of_gauss_point_parameters
1233  INTEGER(INTG), ALLOCATABLE :: gauss_points(:,:)
1235 
1238  INTEGER(INTG) :: number_of_data_point_parameters
1239  INTEGER(INTG), ALLOCATABLE :: data_points(:)
1241 
1244  INTEGER(INTG) :: number_of_constant_parameters
1245  INTEGER(INTG) :: constant_param2dof_map
1246  TYPE(field_element_param_to_dof_map_type) :: element_param2dof_map
1247  TYPE(field_node_param_to_dof_map_type) :: node_param2dof_map
1248  TYPE(field_grid_point_param_to_dof_map_type) :: grid_point_param2dof_map
1249  TYPE(field_gauss_point_param_to_dof_map_type) :: gauss_point_param2dof_map
1250  TYPE(field_data_point_param_to_dof_map_type) :: data_point_param2dof_map
1252 
1255  INTEGER(INTG) :: component_number
1256  TYPE(field_variable_type), POINTER :: field_variable
1257  TYPE(varying_string) :: component_label
1258  INTEGER(INTG) :: interpolation_type
1259  INTEGER(INTG) :: mesh_component_number
1260  INTEGER(INTG) :: scaling_index
1261  TYPE(domain_type), POINTER :: domain
1262  INTEGER(INTG) :: maxnumberelementinterpolationparameters
1263  INTEGER(INTG) :: maxnumbernodeinterpolationparameters
1264  TYPE(field_param_to_dof_map_type) :: param_to_dof_map
1266 
1269  INTEGER(INTG) :: set_index
1270  INTEGER(INTG) :: set_type
1271  !### corresponds to.
1272  TYPE(distributed_vector_type), POINTER :: parameters
1273  END TYPE field_parameter_set_type
1274 
1277  TYPE(field_parameter_set_type), POINTER :: ptr
1279 
1282  TYPE(field_variable_type), POINTER :: field_variable
1283  INTEGER(INTG) :: number_of_parameter_sets
1284  TYPE(field_parameter_set_ptr_type), POINTER :: set_type(:)
1285  TYPE(field_parameter_set_ptr_type), POINTER :: parameter_sets(:)
1286  END TYPE field_parameter_sets_type
1287 
1290  INTEGER(INTG) :: variable_number
1291  INTEGER(INTG) :: variable_type
1292  TYPE(varying_string) :: variable_label
1293  TYPE(field_type), POINTER :: field
1294  TYPE(region_type), POINTER :: region
1295  INTEGER(INTG) :: dimension
1296  INTEGER(INTG) :: data_type
1297  INTEGER(INTG) :: dof_order_type
1298  INTEGER(INTG) :: maxnumberelementinterpolationparameters
1299  INTEGER(INTG) :: maxnumbernodeinterpolationparameters
1300  INTEGER(INTG) :: number_of_dofs
1301  INTEGER(INTG) :: total_number_of_dofs
1302  INTEGER(INTG) :: number_of_global_dofs
1303  TYPE(domain_mapping_type), POINTER :: domain_mapping
1304  INTEGER(INTG) :: number_of_components
1305  TYPE(field_variable_component_type), ALLOCATABLE :: components(:)
1306  TYPE(field_dof_to_param_map_type) :: dof_to_param_map
1307  TYPE(field_parameter_sets_type) :: parameter_sets
1308  END TYPE field_variable_type
1309 
1312  TYPE(field_variable_type), POINTER :: ptr
1313  END TYPE field_variable_ptr_type
1314 
1317  LOGICAL :: label_locked
1318  LOGICAL :: decomposition_locked
1319  LOGICAL :: dataprojectionlocked
1320  LOGICAL :: dependent_type_locked
1321  LOGICAL :: number_of_variables_locked
1322  LOGICAL :: geometric_field_locked
1323  LOGICAL :: scaling_type_locked
1324  LOGICAL :: type_locked
1325  INTEGER(INTG), ALLOCATABLE :: variable_types(:)
1326  LOGICAL :: variable_types_locked
1327  TYPE(varying_string), ALLOCATABLE :: variable_labels(:)
1328  LOGICAL, ALLOCATABLE :: variable_labels_locked(:)
1329  INTEGER(INTG), ALLOCATABLE :: DIMENSION(:)
1330  LOGICAL, ALLOCATABLE :: dimension_locked(:)
1331  INTEGER(INTG), ALLOCATABLE :: data_types(:)
1332  LOGICAL, ALLOCATABLE :: data_types_locked(:)
1333  INTEGER(INTG), ALLOCATABLE :: dof_order_types(:)
1334  LOGICAL, ALLOCATABLE :: dof_order_types_locked(:)
1335  INTEGER(INTG), ALLOCATABLE :: number_of_components(:)
1336  LOGICAL, ALLOCATABLE :: number_of_components_locked(:)
1337  TYPE(varying_string), ALLOCATABLE :: component_labels(:,:)
1338  LOGICAL, ALLOCATABLE :: component_labels_locked(:,:)
1339  INTEGER(INTG), ALLOCATABLE :: interpolation_type(:,:)
1340  LOGICAL, ALLOCATABLE :: interpolation_type_locked(:,:)
1341  INTEGER(INTG), ALLOCATABLE :: mesh_component_number(:,:)
1342  LOGICAL, ALLOCATABLE :: mesh_component_number_locked(:,:)
1344 
1347  INTEGER(INTG) :: global_number
1348  INTEGER(INTG) :: user_number
1349  TYPE(varying_string) :: label
1350  LOGICAL :: field_finished
1351  TYPE(fields_type), POINTER :: fields
1352  TYPE(region_type), POINTER :: region
1353  TYPE(interface_type), POINTER :: interface
1354  INTEGER(INTG) :: TYPE
1355  INTEGER(INTG) :: dependent_type
1356  TYPE(decomposition_type), POINTER :: decomposition
1357  INTEGER(INTG) :: number_of_variables
1358  TYPE(field_variable_ptr_type), ALLOCATABLE :: variable_type_map(:)
1359  TYPE(field_variable_type), ALLOCATABLE :: variables(:)
1360  TYPE(field_scalings_type) :: scalings
1361  TYPE(field_type), POINTER :: geometric_field
1362  TYPE(field_geometric_parameters_type), POINTER :: geometric_field_parameters
1363  TYPE(field_create_values_cache_type), POINTER :: create_values_cache
1364  TYPE(data_projection_type), POINTER :: dataprojection
1365  END TYPE field_type
1366 
1369  TYPE(field_type), POINTER :: ptr
1370  END TYPE field_ptr_type
1371 
1374  TYPE(region_type), POINTER :: region
1375  TYPE(interface_type), POINTER :: interface
1376  INTEGER(INTG) :: number_of_fields
1377  TYPE(field_ptr_type), POINTER :: fields(:)
1378  END TYPE fields_type
1379 
1380  !
1381  !================================================================================================================================
1382  !
1383  ! Equations matrices types
1384  !
1385 
1388  INTEGER(INTG) :: equations_matrix_number
1389  INTEGER(INTG) :: structure_type
1390  INTEGER(INTG) :: number_of_rows
1391  INTEGER(INTG) :: number_of_columns
1392  INTEGER(INTG) :: max_number_of_rows
1393  INTEGER(INTG) :: max_number_of_columns
1394  INTEGER(INTG), ALLOCATABLE :: row_dofs(:)
1395  INTEGER(INTG), ALLOCATABLE :: column_dofs(:)
1396  REAL(DP), ALLOCATABLE :: matrix(:,:)
1397  END TYPE element_matrix_type
1398 
1401  INTEGER(INTG) :: number_of_rows
1402  INTEGER(INTG) :: max_number_of_rows
1403  INTEGER(INTG), ALLOCATABLE :: row_dofs(:)
1404  REAL(DP), ALLOCATABLE :: vector(:)
1405  END TYPE element_vector_type
1406 
1409  INTEGER(INTG) :: equationsmatrixnumber
1410  INTEGER(INTG) :: structuretype
1411  INTEGER(INTG) :: numberofrows
1412  INTEGER(INTG) :: numberofcolumns
1413  INTEGER(INTG) :: maxnumberofrows
1414  INTEGER(INTG) :: maxnumberofcolumns
1415  INTEGER(INTG), ALLOCATABLE :: rowdofs(:)
1416  INTEGER(INTG), ALLOCATABLE :: columndofs(:)
1417  REAL(DP), ALLOCATABLE :: matrix(:,:)
1418  END TYPE nodalmatrixtype
1419 
1422  INTEGER(INTG) :: numberofrows
1423  INTEGER(INTG) :: maxnumberofrows
1424  INTEGER(INTG), ALLOCATABLE :: rowdofs(:)
1425  REAL(DP), ALLOCATABLE :: vector(:)
1426  END TYPE nodalvectortype
1427 
1430  INTEGER(INTG) :: matrix_number
1431  TYPE(equations_matrices_dynamic_type), POINTER :: dynamic_matrices
1432  TYPE(equations_matrices_linear_type), POINTER :: linear_matrices
1433  INTEGER(INTG) :: storage_type
1434  INTEGER(INTG) :: structure_type
1435  LOGICAL :: lumped
1436  INTEGER(INTG) :: number_of_columns
1437  LOGICAL :: update_matrix
1438  LOGICAL :: first_assembly
1439  TYPE(distributed_matrix_type), POINTER :: matrix
1440  TYPE(element_matrix_type) :: element_matrix
1441  TYPE(nodalmatrixtype) :: nodalmatrix
1442  TYPE(distributed_vector_type), POINTER :: temp_vector
1443  END TYPE equations_matrix_type
1444 
1447  TYPE(equations_matrix_type), POINTER :: ptr
1448  END TYPE equations_matrix_ptr_type
1449 
1452  INTEGER(INTG) :: jacobian_number
1453  TYPE(equations_matrices_nonlinear_type), POINTER :: nonlinear_matrices
1454  INTEGER(INTG) :: storage_type
1455  INTEGER(INTG) :: structure_type
1456  INTEGER(INTG) :: number_of_columns
1457  LOGICAL :: update_jacobian
1458  TYPE(distributed_matrix_type), POINTER :: jacobian
1459  LOGICAL :: first_assembly
1460  TYPE(element_matrix_type) :: element_jacobian
1461  TYPE(nodalmatrixtype) :: nodaljacobian
1462  INTEGER(INTG) :: jacobian_calculation_type
1463  END TYPE equations_jacobian_type
1464 
1467  TYPE(equations_jacobian_type), POINTER :: ptr
1469 
1472  TYPE(equations_matrices_type), POINTER :: equations_matrices
1473  INTEGER(INTG) :: number_of_dynamic_matrices
1474  TYPE(equations_matrix_ptr_type), ALLOCATABLE :: matrices(:)
1475  TYPE(distributed_vector_type), POINTER :: temp_vector
1477 
1480  TYPE(equations_matrices_type), POINTER :: equations_matrices
1481  INTEGER(INTG) :: number_of_linear_matrices
1482  TYPE(equations_matrix_ptr_type), ALLOCATABLE :: matrices(:)
1484 
1487  TYPE(equations_matrices_type), POINTER :: equations_matrices
1488  INTEGER(INTG) :: number_of_jacobians
1489  TYPE(equations_jacobian_ptr_type), ALLOCATABLE :: jacobians(:)
1490  LOGICAL :: update_residual
1491  LOGICAL :: first_assembly
1492  TYPE(distributed_vector_type), POINTER :: residual
1493  TYPE(element_vector_type) :: element_residual
1494  TYPE(nodalvectortype) :: nodalresidual
1495  INTEGER(INTG) :: nodalresidualcalculated
1496  INTEGER(INTG) :: element_residual_calculated
1498 
1501  TYPE(equations_matrices_type), POINTER :: equations_matrices
1502  LOGICAL :: update_vector
1503  LOGICAL :: first_assembly
1504  TYPE(distributed_vector_type), POINTER :: vector
1505  TYPE(element_vector_type) :: element_vector
1506  TYPE(nodalvectortype) :: nodalvector
1508 
1511  TYPE(equations_matrices_type), POINTER :: equations_matrices
1512  LOGICAL :: update_vector
1513  LOGICAL :: first_assembly
1514  TYPE(distributed_vector_type), POINTER :: vector
1515  TYPE(element_vector_type) :: element_vector
1516  TYPE(nodalvectortype) :: nodalvector
1518 
1521  TYPE(equations_type), POINTER :: equations
1522  LOGICAL :: equations_matrices_finished
1523  TYPE(equations_mapping_type), POINTER :: equations_mapping
1524  TYPE(solver_mapping_type), POINTER :: solver_mapping
1525  INTEGER(INTG) :: number_of_rows
1526  INTEGER(INTG) :: total_number_of_rows
1527  INTEGER(INTG) :: number_of_global_rows
1528  !Equations matrices components
1529  TYPE(equations_matrices_dynamic_type), POINTER :: dynamic_matrices
1530  TYPE(equations_matrices_linear_type), POINTER :: linear_matrices
1531  TYPE(equations_matrices_nonlinear_type), POINTER :: nonlinear_matrices
1532  TYPE(equations_matrices_rhs_type), POINTER :: rhs_vector
1533  TYPE(equations_matrices_source_type), POINTER :: source_vector
1534  END TYPE equations_matrices_type
1535 
1536  !
1537  !================================================================================================================================
1538  !
1539  ! Equations mapping types
1540  !
1541 
1544  INTEGER(INTG), ALLOCATABLE :: column_dof(:)
1546 
1549  INTEGER(INTG) :: variable_index
1550  INTEGER(INTG) :: variable_type
1551  TYPE(field_variable_type), POINTER :: variable
1552  INTEGER(INTG) :: number_of_equations_matrices
1553  INTEGER(INTG), ALLOCATABLE :: equations_matrix_numbers(:)
1554  TYPE(var_to_equations_column_map_type), ALLOCATABLE :: dof_to_columns_maps(:)
1555  INTEGER(INTG), ALLOCATABLE :: dof_to_rows_map(:)
1557 
1560  INTEGER(INTG) :: matrix_number
1561  TYPE(equations_matrix_type), POINTER :: equations_matrix
1562  INTEGER(INTG) :: variable_type
1563  TYPE(field_variable_type), POINTER :: variable
1564  INTEGER(INTG) :: number_of_columns
1565  REAL(DP) :: matrix_coefficient
1566  INTEGER(INTG), ALLOCATABLE :: column_to_dof_map(:)
1567  TYPE(domain_mapping_type), POINTER :: column_dofs_mapping
1569 
1572  TYPE(equations_mapping_type), POINTER :: equations_mapping
1573  INTEGER(INTG) :: number_of_dynamic_equations_matrices
1574 
1575  INTEGER(INTG) :: stiffness_matrix_number
1576  INTEGER(INTG) :: damping_matrix_number
1577  INTEGER(INTG) :: mass_matrix_number
1578  INTEGER(INTG) :: dynamic_variable_type
1579  TYPE(field_variable_type), POINTER :: dynamic_variable
1581  TYPE(var_to_equations_matrices_map_type), ALLOCATABLE :: var_to_equations_matrices_maps(:)
1582  TYPE(equations_matrix_to_var_map_type), ALLOCATABLE :: equations_matrix_to_var_maps(:)
1583  INTEGER(INTG), ALLOCATABLE :: equations_row_to_variable_dof_maps(:)
1585 
1588  TYPE(equations_mapping_type), POINTER :: equations_mapping
1589  INTEGER(INTG) :: number_of_linear_equations_matrices
1590  INTEGER(INTG) :: number_of_linear_matrix_variables
1591  INTEGER(INTG), ALLOCATABLE :: linear_matrix_variable_types(:)
1593  TYPE(var_to_equations_matrices_map_type), ALLOCATABLE :: var_to_equations_matrices_maps(:)
1594  TYPE(equations_matrix_to_var_map_type), ALLOCATABLE :: equations_matrix_to_var_maps(:)
1595  INTEGER(INTG), ALLOCATABLE :: equations_row_to_variable_dof_maps(:,:)
1597 
1600  INTEGER(INTG) :: jacobian_number
1601  INTEGER(INTG) :: variable_type
1602  TYPE(field_variable_type), POINTER :: variable
1603  TYPE(equations_jacobian_type), POINTER :: jacobian
1604  INTEGER(INTG) :: number_of_columns
1605  REAL(DP) :: jacobian_coefficient
1606  INTEGER(INTG), ALLOCATABLE :: equations_column_to_dof_variable_map(:)
1607  TYPE(domain_mapping_type), POINTER :: column_dofs_mapping
1609 
1612  INTEGER(INTG) :: jacobian_number
1613  INTEGER(INTG) :: variable_type
1614  TYPE(field_variable_type), POINTER :: variable
1615  INTEGER(INTG), ALLOCATABLE :: dof_to_columns_map(:)
1616  INTEGER(INTG), ALLOCATABLE :: dof_to_rows_map(:)
1618 
1624  TYPE(equations_mapping_type), POINTER :: equations_mapping
1625  INTEGER(INTG) :: number_of_residual_variables
1626  TYPE(field_variable_ptr_type), ALLOCATABLE :: residual_variables(:)
1627  TYPE(var_to_equations_jacobian_map_type), ALLOCATABLE :: var_to_jacobian_map(:)
1628  TYPE(equations_jacobian_to_var_map_type), ALLOCATABLE :: jacobian_to_var_map(:)
1629  REAL(DP) :: residual_coefficient
1630  INTEGER(INTG), ALLOCATABLE :: equations_row_to_residual_dof_map(:)
1632 
1636  TYPE(equations_mapping_type), POINTER :: equations_mapping
1637  INTEGER(INTG) :: rhs_variable_type
1638  TYPE(field_variable_type), POINTER :: rhs_variable
1639  TYPE(domain_mapping_type), POINTER :: rhs_variable_mapping
1640  REAL(DP) :: rhs_coefficient
1641  INTEGER(INTG), ALLOCATABLE :: rhs_dof_to_equations_row_map(:)
1642  INTEGER(INTG), ALLOCATABLE :: equations_row_to_rhs_dof_map(:)
1644 
1648  TYPE(equations_mapping_type), POINTER :: equations_mapping
1649  INTEGER(INTG) :: source_variable_type
1650  TYPE(field_variable_type), POINTER :: source_variable
1651  TYPE(domain_mapping_type), POINTER :: source_variable_mapping
1652  REAL(DP) :: source_coefficient
1653  INTEGER(INTG), ALLOCATABLE :: source_dof_to_equations_row_map(:)
1654  INTEGER(INTG), ALLOCATABLE :: equations_row_to_source_dof_map(:)
1656 
1661  INTEGER(INTG) :: number_of_dynamic_equations_matrices
1662  INTEGER(INTG) :: dynamic_stiffness_matrix_number
1663  INTEGER(INTG) :: dynamic_damping_matrix_number
1664  INTEGER(INTG) :: dynamic_mass_matrix_number
1665  INTEGER(INTG) :: dynamic_variable_type
1666  REAL(DP), ALLOCATABLE :: dynamic_matrix_coefficients(:)
1667  INTEGER(INTG) :: number_of_linear_equations_matrices
1668  INTEGER(INTG), ALLOCATABLE :: linear_matrix_variable_types(:)
1669  REAL(DP), ALLOCATABLE :: linear_matrix_coefficients(:)
1670  INTEGER(INTG) :: number_of_residual_variables
1671  INTEGER(INTG), ALLOCATABLE :: residual_variable_types(:)
1672  REAL(DP) :: residual_coefficient
1673  INTEGER(INTG) :: rhs_variable_type
1674  REAL(DP) :: rhs_coefficient
1675  INTEGER(INTG) :: source_variable_type
1676  REAL(DP) :: source_coefficient
1678 
1682  TYPE(equations_type), POINTER :: equations
1683  LOGICAL :: equations_mapping_finished
1684  TYPE(equations_matrices_type), POINTER :: equations_matrices
1685  !Row mappings
1686  INTEGER(INTG) :: number_of_rows
1687  INTEGER(INTG) :: total_number_of_rows
1688  INTEGER(INTG) :: number_of_global_rows
1689  TYPE(domain_mapping_type), POINTER :: row_dofs_mapping
1690  !Equations mapping components
1691  TYPE(equations_mapping_dynamic_type), POINTER :: dynamic_mapping
1692  TYPE(equations_mapping_linear_type), POINTER :: linear_mapping
1693  TYPE(equations_mapping_nonlinear_type), POINTER :: nonlinear_mapping
1694  TYPE(equations_mapping_rhs_type), POINTER :: rhs_mapping
1695  TYPE(equations_mapping_source_type), POINTER :: source_mapping
1696  !Create values cache
1697  TYPE(equations_mapping_create_values_cache_type), POINTER :: create_values_cache
1698  END TYPE equations_mapping_type
1699 
1700  !
1701  !================================================================================================================================
1702  !
1703  ! Equations types
1704  !
1705 
1708  TYPE(equations_type), POINTER :: equations
1709  TYPE(field_type), POINTER :: geometric_field
1710  TYPE(field_type), POINTER :: fibre_field
1711  TYPE(field_type), POINTER :: dependent_field
1712  TYPE(field_type), POINTER :: independent_field
1713  TYPE(field_type), POINTER :: materials_field
1714  TYPE(field_type), POINTER :: source_field
1715  TYPE(field_interpolation_parameters_ptr_type), POINTER :: geometric_interp_parameters(:)
1716  TYPE(field_interpolation_parameters_ptr_type), POINTER :: fibre_interp_parameters(:)
1717  TYPE(field_interpolation_parameters_ptr_type), POINTER :: dependent_interp_parameters(:)
1718  TYPE(field_interpolation_parameters_ptr_type), POINTER :: independent_interp_parameters(:)
1719  TYPE(field_interpolation_parameters_ptr_type), POINTER :: materials_interp_parameters(:)
1720  TYPE(field_interpolation_parameters_ptr_type), POINTER :: source_interp_parameters(:)
1721  TYPE(field_interpolated_point_ptr_type), POINTER :: geometric_interp_point(:)
1722  TYPE(field_interpolated_point_ptr_type), POINTER :: fibre_interp_point(:)
1723  TYPE(field_interpolated_point_ptr_type), POINTER :: dependent_interp_point(:)
1724  TYPE(field_interpolated_point_ptr_type), POINTER :: independent_interp_point(:)
1725  TYPE(field_interpolated_point_ptr_type), POINTER :: materials_interp_point(:)
1726  TYPE(field_interpolated_point_ptr_type), POINTER :: source_interp_point(:)
1727  TYPE(field_physical_point_ptr_type), POINTER :: dependent_physical_point(:)
1728  TYPE(field_interpolated_point_metrics_ptr_type), POINTER :: dependent_interp_point_metrics(:)
1729  TYPE(field_interpolated_point_metrics_ptr_type), POINTER :: independent_interp_point_metrics(:)
1730  TYPE(field_interpolated_point_metrics_ptr_type), POINTER :: geometric_interp_point_metrics(:)
1731  TYPE(field_interpolated_point_metrics_ptr_type), POINTER :: fibre_interp_point_metrics(:)
1733 
1736  TYPE(equations_set_type), POINTER :: equations_set
1737  LOGICAL :: equations_finished
1738  INTEGER(INTG) :: linearity
1739  INTEGER(INTG) :: time_dependence
1740  INTEGER(INTG) :: output_type
1741  INTEGER(INTG) :: sparsity_type
1742  INTEGER(INTG) :: lumping_type
1743  TYPE(equations_interpolation_type), POINTER :: interpolation
1744  TYPE(equations_mapping_type), POINTER :: equations_mapping
1745  TYPE(equations_matrices_type), POINTER :: equations_matrices
1746  END TYPE equations_type
1747 
1749  TYPE(equations_type), POINTER :: ptr
1750  END TYPE equations_ptr_type
1751 
1752  !
1753  !================================================================================================================================
1754  !
1755  ! Boundary conditions types
1756  !
1757 
1760  TYPE(boundary_conditions_type), POINTER :: boundary_conditions
1761  INTEGER(INTG) :: variable_type
1762  TYPE(field_variable_type), POINTER :: variable
1763  INTEGER(INTG), ALLOCATABLE :: dof_types(:)
1764  INTEGER(INTG), ALLOCATABLE :: condition_types(:)
1765  TYPE(boundary_conditions_dirichlet_type), POINTER :: dirichlet_boundary_conditions
1766  INTEGER(INTG) :: number_of_dirichlet_conditions
1767  TYPE(boundaryconditionsneumanntype), POINTER :: neumannboundaryconditions
1768  TYPE(boundary_conditions_pressure_incremented_type), POINTER :: pressure_incremented_boundary_conditions
1769  INTEGER(INTG), ALLOCATABLE :: dof_counts(:)
1770  LOGICAL, ALLOCATABLE :: parametersetrequired(:)
1771  TYPE(boundaryconditionsdofconstraintstype), POINTER :: dofconstraints
1773 
1778 
1781  TYPE(solver_equations_type), POINTER :: solver_equations
1782  LOGICAL :: boundary_conditions_finished
1783  INTEGER(INTG) :: number_of_boundary_conditions_variables
1784  TYPE(boundary_conditions_variable_ptr_type), ALLOCATABLE :: boundary_conditions_variables(:)
1785  INTEGER(INTG) :: neumannmatrixsparsity
1786  END TYPE boundary_conditions_type
1787 
1792 
1795  INTEGER(INTG), ALLOCATABLE :: dirichlet_dof_indices(:)
1796  TYPE(boundary_conditions_sparsity_indices_ptr_type), ALLOCATABLE :: linear_sparsity_indices(:,:)
1797  TYPE(boundary_conditions_sparsity_indices_ptr_type), ALLOCATABLE :: dynamic_sparsity_indices(:,:)
1799 
1803  INTEGER(INTG), ALLOCATABLE :: sparse_row_indices(:)
1804  INTEGER(INTG), ALLOCATABLE :: sparse_column_indices(:)
1806 
1809  INTEGER(INTG), ALLOCATABLE :: setdofs(:)
1810  TYPE(distributed_matrix_type), POINTER :: integrationmatrix
1811  TYPE(distributed_vector_type), POINTER :: pointvalues
1812  TYPE(domain_mapping_type), POINTER :: pointdofmapping
1814 
1817  INTEGER(INTG), ALLOCATABLE :: pressure_incremented_dof_indices(:)
1819 
1822  INTEGER(INTG) :: globaldof
1823  INTEGER(INTG) :: numberofdofs
1824  INTEGER(INTG), ALLOCATABLE :: dofs(:)
1825  REAL(DP), ALLOCATABLE :: coefficients(:)
1827 
1832 
1840  INTEGER(INTG) :: numberofdofs
1841  INTEGER(INTG), ALLOCATABLE :: globaldofs(:)
1842  INTEGER(INTG), ALLOCATABLE :: localdofs(:)
1843  REAL(DP), ALLOCATABLE :: coefficients(:)
1845 
1850 
1853  INTEGER(INTG) :: numberofconstraints
1854  INTEGER(INTG) :: numberofdofs
1855  TYPE(boundaryconditionsdofconstraintptrtype), ALLOCATABLE :: constraints(:)
1856  TYPE(boundaryconditionscoupleddofsptrtype), ALLOCATABLE :: dofcouplings(:)
1858 
1859  !
1860  !================================================================================================================================
1861  !
1862  ! Equations set types
1863  !
1864 
1867  INTEGER(INTG) :: setup_type
1868  INTEGER(INTG) :: action_type
1869  INTEGER(INTG) :: field_user_number
1870  TYPE(field_type), POINTER :: field
1871  INTEGER(INTG) :: analytic_function_type
1872  END TYPE equations_set_setup_type
1873 
1876  TYPE(equations_set_type), POINTER :: equations_set
1877  TYPE(field_type), POINTER :: geometric_field
1878  TYPE(field_type), POINTER :: fibre_field
1880 
1882  TYPE(equations_set_type), POINTER :: equations_set
1883  LOGICAL :: materials_finished
1884  LOGICAL :: materials_field_auto_created
1885  TYPE(field_type), POINTER :: materials_field
1887 
1890  TYPE(equations_set_type), POINTER :: equations_set
1891  LOGICAL :: dependent_finished
1892  LOGICAL :: dependent_field_auto_created
1893  TYPE(field_type), POINTER :: dependent_field
1895 
1898  TYPE(equations_set_type), POINTER :: equationsset
1899  LOGICAL :: derivedfinished
1900  LOGICAL :: derivedfieldautocreated
1901  TYPE(field_type), POINTER :: derivedfield
1902  INTEGER(INTG) :: numberofvariables
1903  INTEGER(INTG), ALLOCATABLE :: variabletypes(:)
1904  END TYPE equationssetderivedtype
1905 
1908  TYPE(equations_set_type), POINTER :: equations_set
1909  LOGICAL :: independent_finished
1910  LOGICAL :: independent_field_auto_created
1911  TYPE(field_type), POINTER :: independent_field
1913 
1916  TYPE(equations_set_type), POINTER :: equations_set
1917  LOGICAL :: source_finished
1918  LOGICAL :: source_field_auto_created
1919  TYPE(field_type), POINTER :: source_field
1920  END TYPE equations_set_source_type
1921 
1924  TYPE(equations_set_type), POINTER :: equations_set
1925  INTEGER(INTG) :: analytic_function_type
1926  LOGICAL :: analytic_finished
1927  LOGICAL :: analytic_field_auto_created
1928  TYPE(field_type), POINTER :: analytic_field
1929  REAL(DP) :: analytic_time
1930  REAL(DP) :: analytic_user_params(20)
1932 
1934  TYPE(equations_set_type), POINTER :: equations_set
1935  LOGICAL :: equations_set_field_finished
1936  LOGICAL :: equations_set_field_auto_created
1937  TYPE(field_type), POINTER :: equations_set_field_field
1939 
1942  INTEGER(INTG) :: user_number
1943  INTEGER(INTG) :: global_number
1944  LOGICAL :: equations_set_finished
1945  TYPE(equations_sets_type), POINTER :: equations_sets
1946  TYPE(region_type), POINTER :: region
1947  INTEGER(INTG), ALLOCATABLE :: specification(:)
1948  INTEGER(INTG) :: solution_method
1950  TYPE(equations_set_materials_type), POINTER :: materials
1951  TYPE(equations_set_source_type), POINTER :: source
1952  TYPE(equations_set_dependent_type) :: dependent
1953  TYPE(equations_set_independent_type), POINTER :: independent
1954  TYPE(equations_set_analytic_type), POINTER :: analytic
1955  TYPE(equationssetderivedtype), POINTER :: derived
1956  TYPE(equations_type), POINTER :: equations
1957  TYPE(boundary_conditions_type), POINTER :: boundary_conditions
1958  TYPE(equations_set_equations_set_field_type) :: equations_set_field
1959  END TYPE equations_set_type
1960 
1963  TYPE(equations_set_type), POINTER :: ptr
1964  END TYPE equations_set_ptr_type
1965 
1967  TYPE(region_type) , POINTER :: region
1968  INTEGER(INTG) :: number_of_equations_sets
1969  TYPE(equations_set_ptr_type), POINTER :: equations_sets(:)
1970  END TYPE equations_sets_type
1971 
1972  !
1973  !================================================================================================================================
1974  !
1975  ! Interface types
1976 
1979  TYPE(interface_matrices_type), POINTER :: interface_matrices
1980  INTEGER(INTG) :: matrix_number
1981  INTEGER(INTG) :: storage_type
1982  INTEGER(INTG) :: structure_type
1983  INTEGER(INTG) :: number_of_rows
1984  INTEGER(INTG) :: total_number_of_rows
1985  INTEGER(INTG) :: interface_matrix_time_dependence_type
1986  INTEGER(INTG) :: interface_matrix_transpose_time_dependence_type
1987  LOGICAL :: update_matrix
1988  LOGICAL :: first_assembly
1989  LOGICAL :: has_transpose
1990  TYPE(distributed_matrix_type), POINTER :: matrix
1991  TYPE(distributed_matrix_type), POINTER :: matrix_transpose
1992  TYPE(distributed_vector_type), POINTER :: temp_vector
1993  TYPE(distributed_vector_type), POINTER :: temp_transpose_vector
1994  TYPE(element_matrix_type) :: element_matrix
1995  END TYPE interface_matrix_type
1996 
1999  TYPE(interface_matrix_type), POINTER :: ptr
2000  END TYPE interface_matrix_ptr_type
2001 
2004  TYPE(interface_matrices_type), POINTER :: interface_matrices
2005  LOGICAL :: update_vector
2006  LOGICAL :: first_assembly
2007  TYPE(distributed_vector_type), POINTER :: rhs_vector
2008  TYPE(element_vector_type) :: element_vector
2009  END TYPE interface_rhs_type
2010 
2013  TYPE(interface_equations_type), POINTER :: interface_equations
2014  LOGICAL :: interface_matrices_finished
2015  TYPE(interface_mapping_type), POINTER :: interface_mapping
2016  TYPE(solver_mapping_type), POINTER :: solver_mapping
2017  INTEGER(INTG) :: number_of_columns
2018  INTEGER(INTG) :: total_number_of_columns
2019  INTEGER(INTG) :: number_of_global_columns
2020  INTEGER(INTG) :: number_of_interface_matrices
2021  TYPE(interface_matrix_ptr_type), ALLOCATABLE :: matrices(:)
2022  TYPE(interface_rhs_type), POINTER :: rhs_vector
2023  END TYPE interface_matrices_type
2024 
2027  INTEGER(INTG) :: matrix_number
2028  TYPE(interface_matrix_type), POINTER :: interface_matrix
2029  TYPE(equations_set_type), POINTER :: equations_set
2030  TYPE(interface_equations_type), POINTER :: interface_equations
2031  INTEGER(INTG) :: variable_type
2032  TYPE(field_variable_type), POINTER :: variable
2033  INTEGER(INTG) :: mesh_index
2034  REAL(DP) :: matrix_coefficient
2035  LOGICAL :: has_transpose
2036  INTEGER(INTG) :: number_of_rows
2037  INTEGER(INTG) :: total_number_of_rows
2038  INTEGER(INTG) :: number_of_global_rows
2039  TYPE(domain_mapping_type), POINTER :: row_dofs_mapping
2040  INTEGER(INTG), ALLOCATABLE :: variable_dof_to_row_map(:)
2042 
2044  TYPE(interface_mapping_type), POINTER :: interface_mapping
2045  INTEGER(INTG) :: rhs_variable_type
2046  TYPE(field_variable_type), POINTER :: rhs_variable
2047  TYPE(domain_mapping_type), POINTER :: rhs_variable_mapping
2048  REAL(DP) :: rhs_coefficient
2049  INTEGER(INTG), ALLOCATABLE :: rhs_dof_to_interface_row_map(:)
2050  INTEGER(INTG), ALLOCATABLE :: interface_row_to_rhs_dof_map(:)
2052 
2054  INTEGER(INTG) :: number_of_interface_matrices
2055  INTEGER(INTG) :: lagrange_variable_type
2056  REAL(DP), ALLOCATABLE :: matrix_coefficients(:)
2057  LOGICAL, ALLOCATABLE :: has_transpose(:)
2058  INTEGER(INTG), ALLOCATABLE :: matrix_row_field_variable_indices(:)
2059  INTEGER(INTG), ALLOCATABLE :: matrix_col_field_variable_indices(:)
2060  INTEGER(INTG) :: rhs_lagrange_variable_type
2061  REAL(DP) :: rhs_coefficient
2063 
2066  TYPE(interface_equations_type), POINTER :: interface_equations
2067  LOGICAL :: interface_mapping_finished
2068  INTEGER(INTG) :: lagrange_variable_type
2069  TYPE(field_variable_type), POINTER :: lagrange_variable
2070  INTEGER(INTG) :: number_of_columns
2071  INTEGER(INTG) :: total_number_of_columns
2072  INTEGER(INTG) :: number_of_global_columns
2073  TYPE(domain_mapping_type), POINTER :: column_dofs_mapping
2074  INTEGER(INTG), ALLOCATABLE :: lagrange_dof_to_column_map(:)
2075  INTEGER(INTG) :: number_of_interface_matrices
2076  TYPE(interface_matrix_to_var_map_type), ALLOCATABLE :: interface_matrix_rows_to_var_maps(:)
2077  TYPE(interface_mapping_rhs_type), POINTER :: rhs_mapping
2078  TYPE(interface_mapping_create_values_cache_type), POINTER :: create_values_cache
2079  END TYPE interface_mapping_type
2080 
2083  TYPE(field_interpolation_parameters_ptr_type), POINTER :: interpolation_parameters(:)
2084  TYPE(field_interpolated_point_ptr_type), POINTER :: interpolated_point(:)
2085  TYPE(field_interpolated_point_metrics_ptr_type), POINTER :: interpolated_point_metrics(:)
2087 
2090  TYPE(interface_equations_interpolation_type), POINTER :: interpolation
2091  TYPE(field_type), POINTER :: geometric_field
2092  INTEGER(INTG) :: number_of_geometric_interpolation_sets
2093  TYPE(interface_equations_interpolation_set_type), ALLOCATABLE :: geometric_interpolation(:)
2094  TYPE(field_type), POINTER :: dependent_field
2095  INTEGER(INTG) :: number_of_dependent_interpolation_sets
2096  TYPE(interface_equations_interpolation_set_type), ALLOCATABLE :: dependent_interpolation(:)
2097  TYPE(field_type), POINTER :: penalty_field
2098  INTEGER(INTG) :: number_of_penalty_interpolation_sets
2099  TYPE(interface_equations_interpolation_set_type), ALLOCATABLE :: penalty_interpolation(:)
2101 
2104  TYPE(interface_equations_type), POINTER :: interface_equations
2105  TYPE(interface_equations_domain_interpolation_type) :: interface_interpolation
2106  TYPE(interface_equations_domain_interpolation_type), ALLOCATABLE :: variable_interpolation(:)
2108 
2111  TYPE(interface_condition_type), POINTER :: interface_condition
2112  LOGICAL :: interface_equations_finished
2113  INTEGER(INTG) :: output_type
2114  INTEGER(INTG) :: sparsity_type
2115  INTEGER(INTG) :: linearity
2116  INTEGER(INTG) :: time_dependence
2117  TYPE(interface_equations_interpolation_type), POINTER :: interpolation
2118  TYPE(interface_mapping_type), POINTER :: interface_mapping
2119  TYPE(interface_matrices_type), POINTER :: interface_matrices
2120  END TYPE interface_equations_type
2121 
2124  TYPE(interface_condition_type), POINTER :: interface_condition
2125  TYPE(field_type), POINTER :: geometric_field
2126  END TYPE interface_geometry_type
2127 
2130  TYPE(interface_condition_type), POINTER :: interface_condition
2131  LOGICAL :: penalty_finished
2132  LOGICAL :: penalty_field_auto_created
2133  TYPE(field_type), POINTER :: penalty_field
2134  END TYPE interface_penalty_type
2135 
2138  TYPE(interface_condition_type), POINTER :: interface_condition
2139  LOGICAL :: lagrange_finished
2140  LOGICAL :: lagrange_field_auto_created
2141  TYPE(field_type), POINTER :: lagrange_field
2142  INTEGER(INTG) :: number_of_components
2143  END TYPE interface_lagrange_type
2144 
2147  TYPE(interface_condition_type), POINTER :: interface_condition
2148  INTEGER(INTG) :: number_of_dependent_variables
2149  TYPE(equations_set_ptr_type), POINTER :: equations_sets(:)
2150  TYPE(field_variable_ptr_type), POINTER :: field_variables(:)
2151  INTEGER(INTG), POINTER :: variable_mesh_indices(:)
2152  END TYPE interface_dependent_type
2153 
2156  INTEGER(INTG) :: user_number
2157  INTEGER(INTG) :: global_number
2158  LOGICAL :: interface_condition_finished
2159  TYPE(interface_conditions_type), POINTER :: interface_conditions
2160  TYPE(interface_type), POINTER :: interface
2161  INTEGER(INTG) :: method
2162  INTEGER(INTG) :: operator
2163  INTEGER(INTG) :: integrationtype
2164  TYPE(interface_geometry_type) :: geometry
2165  TYPE(interface_penalty_type), POINTER :: penalty
2166  TYPE(interface_lagrange_type), POINTER :: lagrange
2167  TYPE(interface_dependent_type), POINTER :: dependent
2168  TYPE(interface_equations_type), POINTER :: interface_equations
2169  TYPE(boundary_conditions_type), POINTER :: boundary_conditions
2170  END TYPE interface_condition_type
2171 
2174  TYPE(interface_condition_type), POINTER :: ptr
2176 
2179  TYPE(interface_type), POINTER :: interface
2180  INTEGER(INTG) :: number_of_interface_conditions
2181  TYPE(interface_condition_ptr_type), POINTER :: interface_conditions(:)
2182  END TYPE interface_conditions_type
2183 
2186  INTEGER(INTG) :: coupled_mesh_element_number
2187  REAL(DP), ALLOCATABLE :: xi(:,:,:)
2188  INTEGER(INTG) :: connected_face
2189  INTEGER(INTG) :: connected_line
2191 
2194  TYPE(interface_type), POINTER :: interface
2195  TYPE(mesh_type), POINTER :: interface_mesh
2196  TYPE(basis_type), POINTER :: basis
2197  LOGICAL :: mesh_connectivity_finished
2198  INTEGER(INTG) :: number_of_interface_elements
2199  INTEGER(INTG) :: number_of_coupled_meshes
2200  TYPE(interface_element_connectivity_type), ALLOCATABLE :: element_connectivity(:,:)
2202 
2205  INTEGER(INTG) :: coupledmeshelementnumber
2206  INTEGER(INTG) :: elementlinefacenumber
2207  REAL(DP), ALLOCATABLE :: xi(:)
2208  REAL(DP), ALLOCATABLE :: reducedxi(:)
2210 
2211  !Contains information on coupled mesh elements that are connected to each interface element.
2213  INTEGER(INTG) :: numberofcoupledelements
2214  INTEGER(INTG), ALLOCATABLE :: elementnumbers(:)
2216 
2219  TYPE(interface_type), POINTER :: interface
2220  TYPE(mesh_type), POINTER :: interfacemesh
2221  LOGICAL :: pointsconnectivityfinished
2222  TYPE(interfacepointconnectivitytype), ALLOCATABLE :: pointsconnectivity(:,:)
2223  TYPE(interfacecoupledelementstype), ALLOCATABLE :: coupledelements(:,:)
2224  INTEGER(INTG), ALLOCATABLE :: maxnumberofcoupledelements(:)
2226 
2229  INTEGER :: user_number
2230  INTEGER :: global_number
2231  LOGICAL :: interface_finished
2232  TYPE(varying_string) :: label
2233  TYPE(coordinate_system_type), POINTER :: coordinate_system
2234  TYPE(interfaces_type), POINTER :: interfaces
2235  TYPE(region_type), POINTER :: parent_region
2236  INTEGER(INTG) :: number_of_coupled_meshes
2237  TYPE(mesh_ptr_type), POINTER :: coupled_meshes(:)
2238  TYPE(interface_mesh_connectivity_type), POINTER :: mesh_connectivity
2239  TYPE(interfacepointsconnectivitytype), POINTER :: pointsconnectivity
2240  TYPE(data_points_type), POINTER :: data_points
2241  TYPE(nodes_type), POINTER :: nodes
2242  TYPE(meshes_type), POINTER :: meshes
2243  TYPE(generated_meshes_type), POINTER :: generated_meshes
2244  TYPE(fields_type), POINTER :: fields
2245  TYPE(interface_conditions_type), POINTER :: interface_conditions
2246  END TYPE interface_type
2247 
2250  TYPE(interface_type), POINTER :: ptr
2251  END TYPE interface_ptr_type
2252 
2255  TYPE(region_type), POINTER :: parent_region
2256  INTEGER(INTG) :: number_of_interfaces
2257  TYPE(interface_ptr_type), POINTER :: interfaces(:)
2258  END TYPE interfaces_type
2259 
2260  !
2261  !================================================================================================================================
2262  !
2263  ! CellML types (belongs under field types?)
2264 
2267  TYPE(cellml_type), POINTER :: cellml
2268  INTEGER(INTG) :: global_number
2269  TYPE(varying_string) :: model_id
2270  TYPE(c_ptr) :: ptr
2271  INTEGER(INTG) :: number_of_state
2272  TYPE(varying_string), ALLOCATABLE :: state_variable_id(:)
2273  INTEGER(INTG) :: number_of_intermediate
2274  TYPE(varying_string), ALLOCATABLE :: intermediate_variable_id(:)
2275  INTEGER(INTG) :: number_of_parameters
2276  TYPE(varying_string), ALLOCATABLE :: parameter_variable_id(:)
2277  END TYPE cellml_model_type
2278 
2281  TYPE(cellml_model_type), POINTER :: ptr
2282  END TYPE cellml_model_ptr_type
2283 
2286  TYPE(cellml_type), POINTER :: cellml
2287  LOGICAL :: models_field_finished
2288  LOGICAL :: models_field_auto_created
2289  TYPE(field_type), POINTER :: models_field
2290  INTEGER(INTG) :: only_one_model_index
2291  END TYPE cellml_models_field_type
2292 
2295  TYPE(cellml_type), POINTER :: cellml
2296  LOGICAL :: state_field_finished
2297  LOGICAL :: state_field_auto_created
2298  TYPE(field_type), POINTER :: state_field
2299  END TYPE cellml_state_field_type
2300 
2303  TYPE(cellml_type), POINTER :: cellml
2304  LOGICAL :: intermediate_field_finished
2305  LOGICAL :: intermediate_field_auto_created
2306  TYPE(field_type), POINTER :: intermediate_field
2308 
2311  TYPE(cellml_type), POINTER :: cellml
2312  LOGICAL :: parameters_field_finished
2313  LOGICAL :: parameters_field_auto_created
2314  TYPE(field_type), POINTER :: parameters_field
2316 
2319  TYPE(solver_type), POINTER :: solver
2320  TYPE(cellml_type), POINTER :: cellml
2321  INTEGER(INTG) :: dofidx
2322  REAL(DP), POINTER :: rates(:)
2323  INTEGER(INTG), ALLOCATABLE :: ratesindices(:)
2324  END TYPE cellmlpetsccontexttype
2325 
2328  INTEGER(INTG) :: cellml_map_type
2329  TYPE(field_type), POINTER :: field
2330  INTEGER(INTG) :: variable_type
2331  INTEGER(INTG) :: component_number
2332  INTEGER(INTG) :: field_parameter_set
2333  TYPE(varying_string) :: variable_id
2334  INTEGER(INTG) :: cellml_field_type
2335  INTEGER(INTG) :: cellml_variable_number
2336  INTEGER(INTG) :: cellml_parameter_set
2337  END TYPE cellml_model_map_type
2338 
2341  TYPE(cellml_model_map_type), POINTER :: ptr
2342  END TYPE cellml_model_map_ptr_type
2343 
2346  INTEGER(INTG) :: number_of_fields_mapped_to
2347  TYPE(cellml_model_map_ptr_type), ALLOCATABLE :: fields_mapped_to(:)
2348  INTEGER(INTG) :: number_of_fields_mapped_from
2349  TYPE(cellml_model_map_ptr_type), ALLOCATABLE :: fields_mapped_from(:)
2350  END TYPE cellml_model_maps_type
2351 
2354  TYPE(cellml_model_maps_type), POINTER :: ptr
2356 
2359  TYPE(cellml_type), POINTER :: cellml
2360  LOGICAL :: cellml_field_maps_finished
2361  TYPE(field_type), POINTER :: source_geometric_field
2362  TYPE(field_variable_type), POINTER :: source_field_variable
2363  TYPE(domain_type), POINTER :: source_field_domain
2364  INTEGER(INTG) :: source_field_interpolation_type
2365  TYPE(cellml_model_maps_ptr_type), ALLOCATABLE :: model_maps(:)
2366  !INTEGER(INTG) :: NUMBER_OF_SOURCE_DOFS !<The number of local (excluding ghosts) source dofs.
2367  !INTEGER(INTG) :: TOTAL_NUMBER_OF_SOURCE_DOFS !<The number of local (including ghosts) source dofs.
2368  !INTEGER(INTG) :: GLOBAL_NUMBER_OF_SOURCE_DOFS !<The number of global source dofs.
2369  END TYPE cellml_field_maps_type
2370 
2373  TYPE(region_type), POINTER :: region
2374  INTEGER(INTG) :: global_number
2375  INTEGER(INTG) :: user_number
2376  TYPE(cellml_environments_type), POINTER :: environments
2377  LOGICAL :: cellml_finished
2378  INTEGER(INTG) :: number_of_models
2379  INTEGER(INTG) :: maximum_number_of_state
2380  INTEGER(INTG) :: maximum_number_of_parameters
2381  INTEGER(INTG) :: maximum_number_of_intermediate
2382  TYPE(cellml_model_ptr_type), ALLOCATABLE :: models(:)
2383  TYPE(cellml_field_maps_type), POINTER :: field_maps
2384  TYPE(cellml_models_field_type), POINTER :: models_field
2385  TYPE(cellml_state_field_type), POINTER :: state_field
2386  TYPE(cellml_intermediate_field_type), POINTER :: intermediate_field
2387  TYPE(cellml_parameters_field_type), POINTER :: parameters_field
2388  LOGICAL :: cellml_generated
2389  END TYPE cellml_type
2390 
2394  TYPE(cellml_type), POINTER :: ptr
2395  END TYPE cellml_ptr_type
2396 
2399  TYPE(region_type), POINTER :: region
2400  INTEGER(INTG) :: number_of_environments
2401  TYPE(cellml_ptr_type), ALLOCATABLE :: environments(:)
2402  END TYPE cellml_environments_type
2403 
2404  !
2405  !================================================================================================================================
2406  !
2407  ! Solver matrices types
2408  !
2409 
2412  INTEGER(INTG) :: matrix_number
2413  TYPE(solver_matrices_type), POINTER :: solver_matrices
2414  LOGICAL :: update_matrix
2415  INTEGER(INTG) :: storage_type
2416  INTEGER(INTG) :: number_of_columns
2417  TYPE(distributed_vector_type), POINTER :: solver_vector
2418  TYPE(distributed_matrix_type), POINTER :: matrix
2419  END TYPE solver_matrix_type
2420 
2423  TYPE(solver_matrix_type), POINTER :: ptr
2424  END TYPE solver_matrix_ptr_type
2425 
2428  TYPE(solver_equations_type), POINTER :: solver_equations
2429  LOGICAL :: solver_matrices_finished
2430  TYPE(solver_mapping_type), POINTER :: solver_mapping
2431  INTEGER(INTG) :: number_of_rows
2432  INTEGER(INTG) :: number_of_global_rows
2433  INTEGER(INTG) :: library_type
2434  !Linear matrices
2435  INTEGER(INTG) :: number_of_matrices
2436  TYPE(solver_matrix_ptr_type), ALLOCATABLE :: matrices(:)
2437  !Nonlinear matrices and vectors
2438  LOGICAL :: update_residual
2439  TYPE(distributed_vector_type), POINTER :: residual
2440  !Right hand side vector
2441  LOGICAL :: update_rhs_vector
2442  TYPE(distributed_vector_type), POINTER :: rhs_vector
2443  END TYPE solver_matrices_type
2444 
2445  !
2446  !================================================================================================================================
2447  !
2448  ! Solver equations types
2449  !
2450 
2453  TYPE(solver_type), POINTER :: solver
2454  LOGICAL :: solver_equations_finished
2455 
2456  INTEGER(INTG) :: linearity
2457  INTEGER(INTG) :: time_dependence
2458 
2459  INTEGER(INTG) :: sparsity_type
2460 
2461  TYPE(solver_mapping_type), POINTER :: solver_mapping
2462  TYPE(solver_matrices_type), POINTER :: solver_matrices
2463 
2464  TYPE(boundary_conditions_type), POINTER :: boundary_conditions
2465 
2466  END TYPE solver_equations_type
2467 
2468  !
2469  !================================================================================================================================
2470  !
2471  ! CellML equations types
2472  !
2473 
2476  TYPE(solver_type), POINTER :: solver
2477  LOGICAL :: cellml_equations_finished
2478  INTEGER(INTG) :: number_of_cellml_environments
2479  TYPE(cellml_ptr_type), ALLOCATABLE :: cellml_environments(:)
2480  END TYPE cellml_equations_type
2481 
2482  !
2483  !================================================================================================================================
2484  !
2485  ! Solver types
2486  !
2487 
2490  TYPE(solver_type), POINTER :: solver
2491  INTEGER(INTG) :: solver_library
2492  LOGICAL :: solver_initialised
2493  INTEGER(INTG) :: linearity
2494  INTEGER(INTG) :: order
2495  INTEGER(INTG) :: degree
2496  INTEGER(INTG) :: scheme
2497  REAL(DP), ALLOCATABLE :: theta(:)
2498  LOGICAL :: explicit
2499  LOGICAL :: restart
2500  LOGICAL :: ale
2501  LOGICAL :: fsi
2502  LOGICAL :: update_bc
2503  REAL(DP) :: current_time
2504  REAL(DP) :: time_increment
2505  TYPE(solver_type), POINTER :: linear_solver
2506  TYPE(solver_type), POINTER :: nonlinear_solver
2507  END TYPE dynamic_solver_type
2508 
2511  TYPE(euler_dae_solver_type), POINTER :: euler_dae_solver
2512  INTEGER(INTG) :: solver_library
2514 
2517  TYPE(euler_dae_solver_type), POINTER :: euler_dae_solver
2518  INTEGER(INTG) :: solver_library
2520 
2523  TYPE(euler_dae_solver_type), POINTER :: euler_dae_solver
2524  INTEGER(INTG) :: solver_library
2526 
2529  TYPE(dae_solver_type), POINTER :: dae_solver
2530  INTEGER(INTG) :: euler_type
2531  TYPE(forward_euler_dae_solver_type), POINTER :: forward_euler_solver
2532  TYPE(backward_euler_dae_solver_type), POINTER :: backward_euler_solver
2533  TYPE(improved_euler_dae_solver_type), POINTER :: improved_euler_solver
2534  INTEGER(INTG) :: solver_library
2535  END TYPE euler_dae_solver_type
2536 
2539  TYPE(dae_solver_type), POINTER :: dae_solver
2540  INTEGER(INTG) :: solver_library
2542 
2545  TYPE(dae_solver_type), POINTER :: dae_solver
2546  INTEGER(INTG) :: solver_library
2548 
2551  TYPE(dae_solver_type), POINTER :: dae_solver
2552  INTEGER(INTG) :: solver_library
2554 
2557  TYPE(dae_solver_type), POINTER :: dae_solver
2558  INTEGER(INTG) :: solver_library
2559  END TYPE bdf_dae_solver_type
2560 
2563  TYPE(dae_solver_type), POINTER :: dae_solver
2564  INTEGER(INTG) :: solver_library
2566 
2569  TYPE(dae_solver_type), POINTER :: dae_solver
2570  END TYPE external_dae_solver_type
2571 
2574  TYPE(solver_type), POINTER :: solver
2575  INTEGER(INTG) :: dae_type
2576  INTEGER(INTG) :: dae_solve_type
2577  REAL(DP) :: start_time
2578  REAL(DP) :: end_time
2579  REAL(DP) :: initial_step
2580  TYPE(euler_dae_solver_type), POINTER :: euler_solver
2581  TYPE(crank_nicolson_dae_solver_type), POINTER :: crank_nicolson_solver
2582  TYPE(runge_kutta_dae_solver_type), POINTER :: runge_kutta_solver
2583  TYPE(adams_moulton_dae_solver_type), POINTER :: adams_moulton_solver
2584  TYPE(bdf_dae_solver_type), POINTER :: bdf_solver
2585  TYPE(rush_larson_dae_solver_type), POINTER :: rush_larson_solver
2586  TYPE(external_dae_solver_type), POINTER :: external_solver
2587  END TYPE dae_solver_type
2588 
2591  TYPE(linear_solver_type), POINTER :: linear_solver
2592  INTEGER(INTG) :: solver_library
2593  INTEGER(INTG) :: solver_matrices_library
2594  INTEGER(INTG) :: direct_solver_type
2595  TYPE(petscpctype) :: pc
2596  TYPE(petscksptype) :: ksp
2597  END TYPE linear_direct_solver_type
2598 
2601  TYPE(linear_solver_type), POINTER :: linear_solver
2602  INTEGER(INTG) :: solver_library
2603  INTEGER(INTG) :: solver_matrices_library
2604  INTEGER(INTG) :: iterative_solver_type
2605  INTEGER(INTG) :: iterative_preconditioner_type
2606  INTEGER(INTG) :: solution_initialise_type
2607  INTEGER(INTG) :: maximum_number_of_iterations
2608  REAL(DP) :: relative_tolerance
2609  REAL(DP) :: absolute_tolerance
2610  REAL(DP) :: divergence_tolerance
2611  INTEGER(INTG) :: gmres_restart
2612  TYPE(petscpctype) :: pc
2613  TYPE(petscksptype) :: ksp
2615 
2618  TYPE(solver_type), POINTER :: solver
2619  INTEGER(INTG) :: linear_solve_type
2620  LOGICAL :: linked_newton_petsc_solver
2621  TYPE(linear_direct_solver_type), POINTER :: direct_solver
2622  TYPE(linear_iterative_solver_type), POINTER :: iterative_solver
2623  END TYPE linear_solver_type
2624 
2627  TYPE(newton_solver_type), POINTER :: newton_solver
2628  INTEGER(INTG) :: solver_library
2629  INTEGER(INTG) :: solver_matrices_library
2630  INTEGER(INTG) :: linesearch_type
2631  REAL(DP) :: linesearch_alpha
2632  REAL(DP) :: linesearch_maxstep
2633  REAL(DP) :: linesearch_steptolerance
2634  TYPE(petscmatcoloringtype) :: jacobianmatcoloring
2635  TYPE(petsciscoloringtype) :: jacobianiscoloring
2636  TYPE(petscmatfdcoloringtype) :: jacobianmatfdcoloring
2637  TYPE(petscsnestype) :: snes
2638  TYPE(petscsneslinesearchtype) :: sneslinesearch
2639  LOGICAL :: linesearchmonitoroutput
2641 
2644  TYPE(newton_solver_type), POINTER :: newton_solver
2645  INTEGER(INTG) :: solver_library
2646  INTEGER(INTG) :: solver_matrices_library
2647  REAL(DP) :: trustregion_tolerance
2648  REAL(DP) :: trustregion_delta0
2649  TYPE(petscsnestype) :: snes
2651 
2654  REAL(DP) :: energyfirstiter
2655  REAL(DP) :: normalisedenergy
2657 
2660  TYPE(nonlinear_solver_type), POINTER :: nonlinear_solver
2661  INTEGER(INTG) :: newton_solve_type
2662  INTEGER(INTG) :: solution_initialise_type
2663  INTEGER(INTG) :: total_number_of_function_evaluations
2664  INTEGER(INTG) :: total_number_of_jacobian_evaluations
2665  INTEGER(INTG) :: maximum_number_of_iterations
2666  INTEGER(INTG) :: maximum_number_of_function_evaluations
2667  INTEGER(INTG) :: jacobian_calculation_type
2668  INTEGER(INTG) :: convergencetesttype
2669  REAL(DP) :: absolute_tolerance
2670  REAL(DP) :: relative_tolerance
2671  REAL(DP) :: solution_tolerance
2672  TYPE(newtonsolverconvergencetest), POINTER :: convergencetest
2673  TYPE(newton_linesearch_solver_type), POINTER :: linesearch_solver
2674  TYPE(newton_trustregion_solver_type), POINTER :: trustregion_solver
2675  TYPE(solver_type), POINTER :: linear_solver
2676  TYPE(solver_type), POINTER :: cellml_evaluator_solver
2677  END TYPE newton_solver_type
2678 
2681  TYPE(quasi_newton_solver_type), POINTER :: quasi_newton_solver
2682  INTEGER(INTG) :: solver_library
2683  INTEGER(INTG) :: solver_matrices_library
2684  INTEGER(INTG) :: linesearch_type
2685  REAL(DP) :: linesearch_maxstep
2686  REAL(DP) :: linesearch_steptolerance
2687  TYPE(petscmatcoloringtype) :: jacobianmatcoloring
2688  TYPE(petsciscoloringtype) :: jacobianiscoloring
2689  TYPE(petscmatfdcoloringtype) :: jacobianmatfdcoloring
2690  TYPE(petscsnestype) :: snes
2691  TYPE(petscsneslinesearchtype) :: sneslinesearch
2692  LOGICAL :: linesearchmonitoroutput
2694 
2697  TYPE(quasi_newton_solver_type), POINTER :: quasi_newton_solver
2698  INTEGER(INTG) :: solver_library
2699  INTEGER(INTG) :: solver_matrices_library
2700  REAL(DP) :: trustregion_tolerance
2701  REAL(DP) :: trustregion_delta0
2702  TYPE(petscsnestype) :: snes
2704 
2707  TYPE(nonlinear_solver_type), POINTER :: nonlinear_solver
2708  INTEGER(INTG) :: quasi_newton_solve_type
2709  INTEGER(INTG) :: quasi_newton_type
2710  INTEGER(INTG) :: restart_type
2711  INTEGER(INTG) :: restart
2712  INTEGER(INTG) :: scale_type
2713  INTEGER(INTG) :: solution_initialise_type
2714  INTEGER(INTG) :: total_number_of_function_evaluations
2715  INTEGER(INTG) :: total_number_of_jacobian_evaluations
2716  INTEGER(INTG) :: maximum_number_of_iterations
2717  INTEGER(INTG) :: maximum_number_of_function_evaluations
2718  INTEGER(INTG) :: jacobian_calculation_type
2719  INTEGER(INTG) :: convergencetesttype
2720  REAL(DP) :: absolute_tolerance
2721  REAL(DP) :: relative_tolerance
2722  REAL(DP) :: solution_tolerance
2723  TYPE(newtonsolverconvergencetest), POINTER :: convergencetest
2724  TYPE(quasi_newton_linesearch_solver_type), POINTER :: linesearch_solver
2725  TYPE(quasi_newton_trustregion_solver_type), POINTER :: trustregion_solver
2726  TYPE(solver_type), POINTER :: linear_solver
2727  TYPE(solver_type), POINTER :: cellml_evaluator_solver
2728  END TYPE quasi_newton_solver_type
2729 
2732  TYPE(solver_type), POINTER :: solver
2733  INTEGER(INTG) :: nonlinear_solve_type
2734  TYPE(newton_solver_type), POINTER :: newton_solver
2735  TYPE(quasi_newton_solver_type), POINTER :: quasi_newton_solver
2736  END TYPE nonlinear_solver_type
2737 
2740  TYPE(solver_type), POINTER :: solver
2741  INTEGER(INTG) :: solver_library
2742  INTEGER(INTG) :: solver_matrices_library
2743  END TYPE eigenproblem_solver_type
2744 
2747  TYPE(solver_type), POINTER :: solver
2748  INTEGER(INTG) :: solver_library
2749  INTEGER(INTG) :: solver_matrices_library
2750  END TYPE optimiser_solver_type
2751 
2754  TYPE(solver_type), POINTER :: solver
2755  INTEGER(INTG) :: solver_library
2756  TYPE(cellml_type), POINTER :: cellml
2757  REAL(DP) :: current_time
2759 
2762  TYPE(solver_type), POINTER :: solver
2763  LOGICAL :: arbitrarypath
2764  INTEGER(INTG) :: numberofincrements
2765  REAL(DP), ALLOCATABLE :: scalings(:) !scaling(loadIncrementIdx), the scaling factors for each load increment, apply the full transformation in 1 load increment if unallocated. Only allocated if there are multiple load steps and if the transformation is uni-directional.
2766  REAL(DP), ALLOCATABLE :: transformationmatrices(:,:,:)
2767  TYPE(field_type), POINTER :: field
2768  INTEGER(INTG) :: fieldvariabletype
2770 
2773  TYPE(solver_type), POINTER :: ptr
2774  END TYPE solver_ptr_type
2775 
2778  TYPE(solvers_type), POINTER :: solvers
2779  INTEGER(INTG) :: global_number
2780  TYPE(solver_type), POINTER :: linking_solver
2781  INTEGER(INTG) :: number_of_linked_solvers
2782  TYPE(solver_ptr_type), ALLOCATABLE :: linked_solvers(:)
2783  TYPE(solver_ptr_type), ALLOCATABLE :: linked_solver_type_map(:)
2784  LOGICAL :: solver_finished
2785  TYPE(varying_string) :: label
2786 
2787  INTEGER(INTG) :: output_type
2788 
2789  INTEGER(INTG) :: solve_type
2790 
2791  TYPE(linear_solver_type), POINTER :: linear_solver
2792  TYPE(nonlinear_solver_type), POINTER :: nonlinear_solver
2793  TYPE(dynamic_solver_type), POINTER :: dynamic_solver
2794  TYPE(dae_solver_type), POINTER :: dae_solver
2795  TYPE(eigenproblem_solver_type), POINTER :: eigenproblem_solver
2796  TYPE(optimiser_solver_type), POINTER :: optimiser_solver
2797  TYPE(cellml_evaluator_solver_type), POINTER :: cellml_evaluator_solver
2798  TYPE(geometrictransformationsolvertype), POINTER :: geometrictransformationsolver
2799  TYPE(solver_equations_type), POINTER :: solver_equations
2800  TYPE(cellml_equations_type), POINTER :: cellml_equations
2801 
2802  END TYPE solver_type
2803 
2806  TYPE(control_loop_type), POINTER :: control_loop
2807  LOGICAL :: solvers_finished
2808  INTEGER(INTG) :: number_of_solvers
2809  TYPE(solver_ptr_type), ALLOCATABLE :: solvers(:)
2810  END TYPE solvers_type
2811 
2812  !
2813  !================================================================================================================================
2814  !
2815  ! Solver mapping types
2816  !
2817 
2819  INTEGER(INTG) :: number_of_solver_cols
2820  INTEGER(INTG), ALLOCATABLE :: solver_cols(:)
2821  REAL(DP), ALLOCATABLE :: coupling_coefficients(:)
2823 
2825  INTEGER(INTG) :: equations_matrix_type
2826  INTEGER(INTG) :: equations_matrix_number
2827  INTEGER(INTG) :: solver_matrix_number
2828  TYPE(equations_matrix_type), POINTER :: equations_matrix
2829  TYPE(solver_matrix_type), POINTER :: solver_matrix
2830  TYPE(equations_col_to_solver_cols_map_type), ALLOCATABLE :: equations_col_to_solver_cols_map(:)
2832 
2835  TYPE(equations_to_solver_maps_type), POINTER :: ptr
2837 
2839  INTEGER(INTG) :: interface_matrix_number
2840  INTEGER(INTG) :: solver_matrix_number
2841  TYPE(interface_matrix_type), POINTER :: interface_matrix
2842  TYPE(solver_matrix_type), POINTER :: solver_matrix
2843  TYPE(equations_col_to_solver_cols_map_type), ALLOCATABLE :: interface_row_to_solver_cols_map(:)
2845 
2848  TYPE(interface_to_solver_maps_type), POINTER :: ptr
2850 
2852  INTEGER(INTG) :: number_of_solver_cols
2853  INTEGER(INTG), ALLOCATABLE :: solver_cols(:)
2854  REAL(DP), ALLOCATABLE :: coupling_coefficients(:)
2856 
2858  INTEGER(INTG) :: solver_matrix_number
2859  TYPE(equations_jacobian_type), POINTER :: jacobian_matrix
2860  TYPE(solver_matrix_type), POINTER :: solver_matrix
2861  TYPE(jacobian_col_to_solver_cols_map_type), ALLOCATABLE :: jacobian_col_to_solver_cols_map(:)
2863 
2865  TYPE(jacobian_to_solver_map_type), POINTER :: ptr
2867 
2870  INTEGER(INTG), ALLOCATABLE :: column_numbers(:)
2871  REAL(DP), ALLOCATABLE :: coupling_coefficients(:)
2872  REAL(DP), ALLOCATABLE :: additive_constants(:)
2874 
2876  INTEGER(INTG) :: interface_condition_index
2877  TYPE(interface_condition_type), POINTER :: interface_condition
2878  INTEGER(INTG) :: interface_matrix_number
2880 
2883  INTEGER(INTG) :: solver_matrix_number
2884 
2885  INTEGER(INTG) :: number_of_variables
2886  INTEGER(INTG), ALLOCATABLE :: variable_types(:)
2887  TYPE(field_variable_ptr_type), ALLOCATABLE :: variables(:)
2888  TYPE(variable_to_solver_col_map_type), ALLOCATABLE :: variable_to_solver_col_maps(:)
2889  INTEGER(INTG) :: number_of_dynamic_equations_matrices
2890  TYPE(equations_to_solver_maps_ptr_type), ALLOCATABLE :: dynamic_equations_to_solver_matrix_maps(:)
2891  INTEGER(INTG) :: number_of_linear_equations_matrices
2892  TYPE(equations_to_solver_maps_ptr_type), ALLOCATABLE :: linear_equations_to_solver_matrix_maps(:)
2893  INTEGER(INTG) :: number_of_equations_jacobians
2894  TYPE(jacobian_to_solver_map_ptr_type), ALLOCATABLE :: jacobian_to_solver_matrix_maps(:)
2896 
2899  INTEGER(INTG) :: equations_matrix_number
2900  INTEGER(INTG) :: number_of_solver_matrices
2901  TYPE(equations_to_solver_maps_ptr_type), ALLOCATABLE :: equations_to_solver_matrix_maps(:)
2903 
2906  INTEGER(INTG) :: number_of_solver_rows
2907  INTEGER(INTG), ALLOCATABLE :: solver_rows(:)
2908  REAL(DP), ALLOCATABLE :: coupling_coefficients(:)
2910 
2913  INTEGER(INTG) :: equations_set_index
2914  TYPE(solver_mapping_type), POINTER :: solver_mapping
2915  TYPE(equations_type), POINTER :: equations
2916  INTEGER(INTG) :: number_of_interface_conditions
2917  TYPE(equations_to_solver_matrix_maps_interface_type), ALLOCATABLE :: equations_to_solver_matrix_maps_interface(:)
2918  TYPE(equations_to_solver_matrix_maps_sm_type), ALLOCATABLE :: equations_to_solver_matrix_maps_sm(:)
2919  TYPE(equations_to_solver_matrix_maps_em_type), ALLOCATABLE :: equations_to_solver_matrix_maps_em(:)
2920  TYPE(jacobian_to_solver_map_ptr_type), ALLOCATABLE :: equations_to_solver_matrix_maps_jm(:)
2921  TYPE(equations_row_to_solver_rows_map_type), ALLOCATABLE :: equations_row_to_solver_rows_maps(:)
2923 
2926  INTEGER(INTG) :: solver_matrix_number
2927  INTEGER(INTG) :: lagrange_variable_type
2928  TYPE(field_variable_type), POINTER :: lagrange_variable
2929  TYPE(variable_to_solver_col_map_type) :: lagrange_variable_to_solver_col_map
2930  INTEGER(INTG) :: number_of_dependent_variables
2931  INTEGER(INTG), ALLOCATABLE :: dependent_variable_types(:)
2932  TYPE(field_variable_ptr_type), ALLOCATABLE :: dependent_variables(:)
2933  TYPE(variable_to_solver_col_map_type), ALLOCATABLE :: dependent_variable_to_solver_col_maps(:)
2934  INTEGER(INTG) :: number_of_interface_matrices
2935  TYPE(interface_to_solver_maps_ptr_type), ALLOCATABLE :: interface_equations_to_solver_matrix_maps(:)
2936  TYPE(equations_col_to_solver_cols_map_type), ALLOCATABLE :: interface_col_to_solver_cols_map(:)
2938 
2941  INTEGER(INTG) :: number_of_solver_rows
2942  INTEGER(INTG) :: solver_row
2943  REAL(DP) :: coupling_coefficient
2945 
2948  INTEGER(INTG) :: interface_matrix_number
2949  INTEGER(INTG) :: number_of_solver_matrices
2950  TYPE(interface_to_solver_maps_ptr_type), ALLOCATABLE :: interface_to_solver_matrix_maps(:)
2951  TYPE(interface_row_to_solver_rows_map_type), ALLOCATABLE :: interface_row_to_solver_rows_map(:)
2953 
2955  INTEGER(INTG) :: equations_set_index
2956  TYPE(equations_set_type), POINTER :: equations_set
2957  INTEGER(INTG) :: interface_matrix_index
2959 
2962  INTEGER(INTG) :: number_of_solver_rows
2963  INTEGER(INTG) :: solver_row
2964  REAL(DP) :: coupling_coefficient
2966 
2969  INTEGER(INTG) :: interface_condition_index
2970  TYPE(solver_mapping_type), POINTER :: solver_mapping
2971  TYPE(interface_equations_type), POINTER :: interface_equations
2972  INTEGER(INTG) :: number_of_equations_sets
2973  TYPE(interface_to_solver_matrix_maps_equations_type), ALLOCATABLE :: interface_to_solver_matrix_maps_equations(:)
2974  TYPE(interface_to_solver_matrix_maps_sm_type), ALLOCATABLE :: interface_to_solver_matrix_maps_sm(:)
2975  TYPE(interface_to_solver_matrix_maps_im_type), ALLOCATABLE :: interface_to_solver_matrix_maps_im(:)
2976  TYPE(interface_column_to_solver_rows_map_type), ALLOCATABLE :: interface_column_to_solver_rows_maps(:)
2978 
2981  INTEGER(INTG) :: number_of_dynamic_equations_matrices
2982  INTEGER(INTG), ALLOCATABLE :: equations_matrix_numbers(:)
2983  INTEGER(INTG), ALLOCATABLE :: equations_col_numbers(:)
2984  REAL(DP), ALLOCATABLE :: coupling_coefficients(:)
2986 
2989  INTEGER(INTG) :: number_of_linear_equations_matrices
2990  INTEGER(INTG), ALLOCATABLE :: equations_matrix_numbers(:)
2991  INTEGER(INTG), ALLOCATABLE :: equations_col_numbers(:)
2992  REAL(DP), ALLOCATABLE :: coupling_coefficients(:)
2994  INTEGER(INTG) :: jacobian_col_number
2995  REAL(DP) :: jacobian_coupling_coefficient
2997 
3000  INTEGER(INTG) :: number_of_equation_dofs
3001  INTEGER(INTG), ALLOCATABLE :: equations_types(:)
3002  INTEGER(INTG), ALLOCATABLE :: equations_indices(:)
3003  TYPE(field_variable_ptr_type), ALLOCATABLE :: variable(:)
3004  INTEGER(INTG), ALLOCATABLE :: variable_dof(:)
3005  REAL(DP), ALLOCATABLE :: variable_coefficient(:)
3006  REAL(DP), ALLOCATABLE :: additive_constant(:)
3008 
3011  TYPE(equations_type), POINTER :: equations
3012  LOGICAL :: have_dynamic
3013  LOGICAL :: have_static
3014  TYPE(solver_col_to_dynamic_equations_map_type), ALLOCATABLE :: solver_col_to_dynamic_equations_maps(:)
3015  TYPE(solver_col_to_static_equations_map_type), ALLOCATABLE :: solver_col_to_static_equations_maps(:)
3017 
3020  INTEGER(INTG) :: number_of_interface_matrices
3021  INTEGER(INTG), ALLOCATABLE :: interface_matrix_numbers(:)
3022  INTEGER(INTG), ALLOCATABLE :: interface_col_numbers(:)
3023  REAL(DP), ALLOCATABLE :: coupling_coefficients(:)
3025 
3028  TYPE(equations_type), POINTER :: interface_equations
3029  TYPE(solver_col_to_interface_equations_map_type), ALLOCATABLE :: solver_col_to_interface_equations_maps(:)
3031 
3034  INTEGER(INTG) :: solver_matrix_number
3035  TYPE(solver_mapping_type), POINTER :: solver_mapping
3036  TYPE(solver_matrix_type), POINTER :: solver_matrix
3037  INTEGER(INTG) :: number_of_columns
3038  TYPE(solver_col_to_equations_set_map_type), ALLOCATABLE :: solver_col_to_equations_set_maps(:)
3039  TYPE(solver_col_to_interface_map_type), ALLOCATABLE :: solver_col_to_interface_maps(:)
3040  INTEGER(INTG) :: number_of_dofs
3041  INTEGER(INTG) :: total_number_of_dofs
3042  INTEGER(INTG) :: number_of_global_dofs
3044  TYPE(solver_dof_to_variable_map_type), ALLOCATABLE :: solver_dof_to_variable_maps(:)
3045  TYPE(domain_mapping_type), POINTER :: column_dofs_mapping
3047 
3050  INTEGER(INTG) :: number_of_equations_set_rows
3051  INTEGER(INTG) :: interface_condition_index
3052  INTEGER(INTG), ALLOCATABLE :: equations_index(:)
3053  INTEGER(INTG), ALLOCATABLE :: rowcol_number(:)
3054  REAL(DP), ALLOCATABLE :: coupling_coefficients(:)
3056 
3059  TYPE(list_ptr_type), POINTER :: equations_variable_list(:)
3060  INTEGER, ALLOCATABLE :: dynamic_variable_type(:)
3061  INTEGER(INTG), ALLOCATABLE :: matrix_variable_types(:,:,:)
3062  INTEGER(INTG), ALLOCATABLE :: residual_variable_types(:,:)
3063  INTEGER(INTG), ALLOCATABLE :: rhs_variable_type(:)
3064  INTEGER, ALLOCATABLE :: source_variable_type(:)
3065  TYPE(list_ptr_type), POINTER :: interface_variable_list(:)
3066  TYPE(list_ptr_type), POINTER :: interface_indices(:)
3068 
3070  TYPE(field_variable_type), POINTER :: variable
3071  INTEGER(INTG) :: variable_type
3072  INTEGER(INTG) :: number_of_equations
3073  INTEGER(INTG), ALLOCATABLE :: equation_types(:)
3074  INTEGER(INTG), ALLOCATABLE :: equation_indices(:)
3076 
3079  INTEGER(INTG) :: number_of_variables
3080  TYPE(solver_mapping_variable_type), ALLOCATABLE :: variables(:)
3082 
3085  INTEGER(INTG) :: numberofcouplings
3086  INTEGER(INTG) :: capacity
3087  TYPE(boundaryconditionscoupleddofsptrtype), ALLOCATABLE :: dofcouplings(:)
3089 
3092  TYPE(solver_equations_type), POINTER :: solver_equations
3093  LOGICAL :: solver_mapping_finished
3094  INTEGER(INTG) :: number_of_solver_matrices
3095  INTEGER(INTG) :: number_of_rows
3096  INTEGER(INTG) :: number_of_global_rows
3097  INTEGER(INTG) :: number_of_equations_sets
3098  TYPE(equations_set_ptr_type), ALLOCATABLE :: equations_sets(:)
3099  TYPE(equations_set_to_solver_map_type), ALLOCATABLE :: equations_set_to_solver_map(:)
3100  INTEGER(INTG) :: number_of_interface_conditions
3101  TYPE(interface_condition_ptr_type), ALLOCATABLE :: interface_conditions(:)
3102  TYPE(interface_condition_to_solver_map_type), ALLOCATABLE :: interface_condition_to_solver_map(:)
3103  TYPE(solver_mapping_variables_type), ALLOCATABLE :: variables_list(:)
3104  TYPE(solver_col_to_equations_maps_type), ALLOCATABLE :: solver_col_to_equations_cols_map(:)
3105  TYPE(solver_row_to_equations_maps_type), ALLOCATABLE :: solver_row_to_equations_rows_map(:)
3106  !LOGICAL :: HAVE_JACOBIAN !<Is .TRUE. if the Jacobian exists for nonlinear problems.
3107  TYPE(domain_mapping_type), POINTER :: row_dofs_mapping
3108  TYPE(solver_mapping_create_values_cache_type), POINTER :: create_values_cache
3109  END TYPE solver_mapping_type
3110 
3111  !
3112  !================================================================================================================================
3113  !
3114  ! History types
3115  !
3116 
3119  TYPE(control_loop_type), POINTER :: control_loop
3120  LOGICAL :: history_finished
3121  INTEGER(INTG) :: file_format
3122  TYPE(varying_string) :: filename
3123  INTEGER(INTG) :: unit_number
3124  TYPE(field_type), POINTER :: field
3125  END TYPE history_type
3126 
3127  !
3128  !================================================================================================================================
3129  !
3130  ! Control types
3131  !
3132 
3135  TYPE(control_loop_type), POINTER :: control_loop
3136  END TYPE control_loop_simple_type
3137 
3140  TYPE(control_loop_type), POINTER :: control_loop
3141  INTEGER(INTG) :: iteration_number
3142  INTEGER(INTG) :: start_iteration
3143  INTEGER(INTG) :: stop_iteration
3144  INTEGER(INTG) :: iteration_increment
3145  END TYPE control_loop_fixed_type
3146 
3149  TYPE(control_loop_type), POINTER :: control_loop
3150  INTEGER(INTG) :: iteration_number
3151  INTEGER(INTG) :: global_iteration_number
3152 ! sebk: is thei usefull?
3153  INTEGER(INTG) :: output_number
3154  INTEGER(INTG) :: input_number
3155  REAL(DP) :: current_time
3156  REAL(DP) :: start_time
3157  REAL(DP) :: stop_time
3158  REAL(DP) :: time_increment
3159  INTEGER(INTG) :: number_of_iterations
3160  END TYPE control_loop_time_type
3161 
3164  TYPE(control_loop_type), POINTER :: control_loop
3165  INTEGER(INTG) :: iteration_number
3166  INTEGER(INTG) :: maximum_number_of_iterations
3167  REAL(DP) :: absolute_tolerance
3168  LOGICAL :: continue_loop
3169  END TYPE control_loop_while_type
3170 
3173  TYPE(control_loop_type), POINTER :: control_loop
3174  INTEGER(INTG) :: iteration_number
3175  INTEGER(INTG) :: maximum_number_of_iterations
3176  INTEGER(INTG) :: output_number
3178 
3181  TYPE(control_loop_type), POINTER :: ptr
3182  END TYPE control_loop_ptr_type
3183 
3186  TYPE(problem_type), POINTER :: problem
3187  TYPE(control_loop_type), POINTER :: parent_loop
3188  LOGICAL :: control_loop_finished
3189  TYPE(varying_string) :: label
3190 
3191  INTEGER(INTG) :: loop_type
3192  INTEGER(INTG) :: control_loop_level
3193  INTEGER(INTG) :: sub_loop_index
3194  INTEGER(INTG) :: output_type
3195 
3196  TYPE(control_loop_simple_type), POINTER :: simple_loop
3197  TYPE(control_loop_fixed_type), POINTER :: fixed_loop
3198  TYPE(control_loop_time_type), POINTER :: time_loop
3199  TYPE(control_loop_while_type), POINTER :: while_loop
3200  TYPE(control_loop_load_increment_type), POINTER :: load_increment_loop
3201 
3202  INTEGER(INTG) :: number_of_sub_loops
3203  TYPE(control_loop_ptr_type), ALLOCATABLE :: sub_loops(:)
3204 
3205  TYPE(solvers_type), POINTER :: solvers
3206  TYPE(history_type), POINTER :: history
3207  END TYPE control_loop_type
3208 
3209  !
3210  !================================================================================================================================
3211  !
3212  ! Problem types
3213  !
3214 
3216  INTEGER(INTG) :: setup_type
3217  INTEGER(INTG) :: action_type
3218  END TYPE problem_setup_type
3219 
3222  INTEGER(INTG) :: user_number
3223  INTEGER(INTG) :: global_number
3224  LOGICAL :: problem_finished
3225  TYPE(problems_type), POINTER :: problems
3226  INTEGER(INTG), ALLOCATABLE :: specification(:)
3227  TYPE(control_loop_type), POINTER :: control_loop
3228  END TYPE problem_type
3229 
3232  TYPE(problem_type), POINTER :: ptr
3233  END TYPE problem_ptr_type
3234 
3237  INTEGER(INTG) :: number_of_problems
3238  TYPE(problem_ptr_type), POINTER :: problems(:)
3239  END TYPE problems_type
3240 
3241  !
3242  !================================================================================================================================
3243  !
3244  ! Region types
3245 
3248  TYPE(region_type), POINTER :: ptr
3249  END TYPE region_ptr_type
3250 
3253  INTEGER(INTG) :: user_number
3254  LOGICAL :: region_finished
3255  TYPE(varying_string) :: label
3256  TYPE(coordinate_system_type), POINTER :: coordinate_system
3257  TYPE(data_points_type), POINTER :: data_points
3258  TYPE(nodes_type), POINTER :: nodes
3259  TYPE(meshes_type), POINTER :: meshes
3260  TYPE(generated_meshes_type), POINTER :: generated_meshes
3261  TYPE(fields_type), POINTER :: fields
3262  TYPE(equations_sets_type), POINTER :: equations_sets
3263  TYPE(cellml_environments_type), POINTER :: cellml_environments
3264  TYPE(region_type), POINTER :: parent_region
3265  INTEGER(INTG) :: number_of_sub_regions
3266  TYPE(region_ptr_type), POINTER :: sub_regions(:)
3267  TYPE(interfaces_type), POINTER :: interfaces
3268  END TYPE region_type
3269 
3272  TYPE(region_type), POINTER :: world_region
3273  END TYPE regions_type
3274 
3275  !
3276  !================================================================================================================================
3277  !
3278 
3279 
3280 END MODULE types
3281 
Contains information on the boundary conditions for the solver equations.
Definition: types.f90:1780
Contains information of a generated cylinder mesh Allows only a 3D cylinder mesh with xi directions (...
Definition: types.f90:556
Contains information for an forward Euler differential-algebraic equation solver. ...
Definition: types.f90:2510
integer, parameter ptr
Pointer integer kind.
Definition: kinds.f90:58
Contains information for a component of a field variable.
Definition: types.f90:1254
Contains the information for an adjacent domain for transfering the ghost data of a distributed vecto...
Definition: types.f90:741
Contains information on the Jacobian matrix for nonlinear problems.
Definition: types.f90:1451
Contains information on the equations mapping i.e., how field variable DOFS are mapped to the rows an...
Definition: types.f90:1681
Contains information for a Quasi-Newton trust region nonlinear solver.
Definition: types.f90:2696
Contains information about the CellML equations for a solver.
Definition: types.f90:2475
Contains information about the equations in an equations set.
Definition: types.f90:1735
Contains information for a region.
Definition: types.f90:3252
Contains the information for a face in a domain.
Definition: types.f90:644
Contains information for interfaces on a parent region.
Definition: types.f90:2254
Contains information on a time iteration control loop.
Definition: types.f90:3148
Contains the topology information for a global node of a mesh.
Definition: types.f90:421
Buffer type to allow arrays of pointer to CELLML_MODEL_MAPS_TYPE.
Definition: types.f90:2353
Contains information on the interpolation for the interface equations.
Definition: types.f90:2103
A buffer type to allow for an array of pointers to a INTERFACE_MATRIX_TYPE.
Definition: types.f90:1998
Contains information on the maps between a CellML model and external OpenCMISS fields.
Definition: types.f90:2345
Implements trees of base types.
Definition: trees.f90:45
A buffer type to allow for an array of pointers to a DECOMPOSITION_TYPE.
Definition: types.f90:1081
A type to hold the mapping from field Gauss points to field dof numbers for a particular field variab...
Definition: types.f90:1231
Contains information for a Runge-Kutta differential-algebraic equation solver.
Definition: types.f90:2544
Contains information for a Crank-Nicholson differential-algebraic equation solver.
Definition: types.f90:2538
Contains information on the mesh decomposition.
Definition: types.f90:1063
Contains information about mapping the solver dof to the field variable dofs in the equations set...
Definition: types.f90:2999
This module contains types related to the PETSc library.
Contains information for an Euler differential-algebraic equation solver.
Definition: types.f90:2528
A buffer type to allow for an array of pointers to a REGION_TYPE.
Definition: types.f90:3247
Contains information on the independent variables for the equations set.
Definition: types.f90:1907
A buffer type to allow for an array of pointers to a FIELD_TYPE.
Definition: types.f90:1368
Contains information about an interface matrix.
Definition: types.f90:1978
Contains information on the type of solver to be used.
Definition: types.f90:2777
A buffer type to allow for an array of pointers to a DOMAIN_TYPE.
Definition: types.f90:950
Contains information for an iterative linear solver.
Definition: types.f90:2600
Contains information on the mappings from a solver row to the equations.
Definition: types.f90:3049
A type to hold the mapping from field dof numbers to field parameters (nodes, elements, etc)
Definition: types.f90:1183
A type to hold the mapping from field elements to field dof numbers for a particular field variable c...
Definition: types.f90:1219
Contains information about the mappings from a solver matrix to the equations in an equations set...
Definition: types.f90:3027
Contains information for a Quasi-Newton line search nonlinear solver.
Definition: types.f90:2680
Contains information for an eigenproblem solver.
Definition: types.f90:2739
Contains information on the interface to solver matrix mappings when indexing by solver matrix number...
Definition: types.f90:2925
A buffer type to allow for an array of pointers to a DOMAIN_FACE_TYPE.
Definition: types.f90:656
Contains the geometric parameters (lines, faces, volumes etc.) for a geometric field decomposition...
Definition: types.f90:1156
Contains the topology information for a domain.
Definition: types.f90:724
A buffer type to allow for an array of pointers to a EQUATIONS_JACOBIAN_TYPE.
Definition: types.f90:1466
Contains information about the penalty field information for an interface condition.
Definition: types.f90:2129
Contains information on the coupling between meshes in an interface.
Definition: types.f90:2193
Contains information about the mapping from a solver matrix column to dynamic equations matrices and ...
Definition: types.f90:2980
Contains information on the data points defined on a region.
Definition: types.f90:333
Contains information on an equations set.
Definition: types.f90:1941
A buffer type to allow for an array of pointers to a EQUATIONS_TO_SOLVER_MAPS_TYPE.
Definition: types.f90:2834
Buffer type to allow an array of pointers to CELLML_MODEL_MAP_FIELD_TYPE.
Definition: types.f90:2340
Contains the information for a node derivative of a mesh.
Definition: types.f90:412
Contains information on the fields defined on a region.
Definition: types.f90:1373
Contains information for a matrix.
Definition: types.f90:859
Contains information on the solvers to be used in a control loop.
Definition: types.f90:2805
Contains information about a node.
Definition: types.f90:352
Contains the topology information for a local node derivative of a domain.
Definition: types.f90:687
A buffer type to allow for an array of pointers to a INTERFACE_TO_SOLVER_MAPS_TYPE.
Definition: types.f90:2847
A buffer type to allow for an array of pointers to a MeshComponentTopologyType.
Definition: types.f90:478
Contains information for the interface condition data.
Definition: types.f90:2155
Contains information on a simple (execute once) control loop.
Definition: types.f90:3134
Contains information on dofs associated with pressure incremented conditions.
Definition: types.f90:1816
Contains information for a CellML evaluation solver.
Definition: types.f90:2753
Contains information of the RHS vector for interface matrices.
Definition: types.f90:2003
A buffer type to allow for an array of pointers to a COORDINATE_SYSTEM_TYPE.
Definition: types.f90:267
A buffer type to allow for an array of pointers to a DATA_PROJECTION_TYPE.
Definition: types.f90:313
Contains information of the source vector for equations matrices.
Definition: types.f90:1510
Contains information on the parameters field for a CellML environment.
Definition: types.f90:2310
Contains information for a direct linear solver.
Definition: types.f90:2590
Contains information on the problems defined.
Definition: types.f90:3236
A type to hold the mapping from a field node&#39;s derivative to field dof numbers for a particular field...
Definition: types.f90:1207
A buffer type to allow for an array of pointers to a GENERATED_MESH_TYPE.
Definition: types.f90:594
Contains information on the projected data points on an element, for decomposition since data points ...
Definition: types.f90:1034
Contains information for an Adams-Moulton differential-algebraic equation solver. ...
Definition: types.f90:2550
Contains information for a field defined on a region.
Definition: types.f90:1346
Contains information for mapping an equations matrix to a field variable.
Definition: types.f90:1559
Contains information on the maps between CellML and external OpenCMISS fields.
Definition: types.f90:2358
Contains information on a control loop.
Definition: types.f90:3185
Contains information for an nodal vector.
Definition: types.f90:1421
Contains information about a data point.
Definition: types.f90:324
Contains information on the domain decompositions defined on a mesh.
Definition: types.f90:1086
This module provides an iso_varying_string module, conformant to the API specified in ISO/IEC 1539-2:...
Only for integer data type for now.
Contains information for a CMISS distributed matrix.
Definition: types.f90:797
Contains information on an interface mapping. TODO: Generalise to non-Lagrange multipler mappings...
Definition: types.f90:2065
Contains information on the create values cache for the equations mapping. Because we do not want to ...
Definition: types.f90:1660
Contains information on a load-increment control loop.
Definition: types.f90:3172
A type to store the parameter sets for a field.
Definition: types.f90:1281
Contains information about the mapping from a solver matrix column to static equations matrices and v...
Definition: types.f90:2988
Contains the information about the mapping of a variable DOF to an equations matrix column...
Definition: types.f90:1543
Contains information for a vector.
Definition: types.f90:846
Contains the information for an element in a domain.
Definition: types.f90:668
Contains information on the intermediate field for a CellML environment.
Definition: types.f90:2302
A type to temporarily hold (cache) the user modifiable values which are used to create a field...
Definition: types.f90:1316
A buffer type to allow for an array of pointers to a SOLVER_MATRIX_TYPE.
Definition: types.f90:2422
Contains information on a coordinate system.
Definition: types.f90:255
Contains information for mapping field variables to the dynamic matrices in the equations set of the ...
Definition: types.f90:1571
Contains information for a Newton nonlinear solver.
Definition: types.f90:2659
A type to hold the scale factors for the appropriate mesh component of a field.
Definition: types.f90:1168
This module contains all program wide constants.
Definition: constants.f90:45
Contains information for a PETSc distributed vector.
Definition: types.f90:774
A type to hold the field scalings for the field.
Definition: types.f90:1176
Contains information on the solver, cellml, dof etc. for which cellml equations are to be evaluated b...
Definition: types.f90:2318
Contains the information for a face in a decomposition.
Definition: types.f90:979
Contains information about the regions.
Definition: types.f90:3271
Contains the information for a line in a domain.
Definition: types.f90:622
Contains the interpolated point coordinate metrics. Old CMISS name GL,GU,RG.
Definition: types.f90:1112
Contains the topology information for the elements of a domain.
Definition: types.f90:677
A buffer type to allow for an array of pointers to a PROBLEM_TYPE.
Definition: types.f90:3231
Contains information on the quadrature to be used for integrating a basis.
Definition: types.f90:161
A pointer to a linear DOF constraint.
Definition: types.f90:1829
Contains information about the dependent field information for an interface condition.
Definition: types.f90:2146
A buffer type to allow for an array of pointers to a BOUNDARY_CONDITIONS_SPARSITY_INDICES_TYPE.
Definition: types.f90:1789
Contains the information for a line in a decomposition.
Definition: types.f90:961
Contains information for a nonlinear solver.
Definition: types.f90:2731
Contains information on the boundary conditions for a dependent field variable.
Definition: types.f90:1759
A pointer to the coupled equations DOF information for the DOF constraints.
Definition: types.f90:1847
Contains information on the degrees-of-freedom (dofs) for a domain.
Definition: types.f90:613
Contains information on the interpolation for the equations.
Definition: types.f90:1707
A type to hold the mapping from field nodes to field dof numbers for a particular field variable comp...
Definition: types.f90:1213
Contains information on the equations to solver matrix mappings when indexing by equations matrix num...
Definition: types.f90:2898
A buffer type to allow for an array of pointers to a EQUATIONS_SET_TYPE.
Definition: types.f90:1962
Contains information on the equations mapping for a source i.e., how a field variable is mapped to th...
Definition: types.f90:1647
Contains information about the mappings from a solver matrix to the equations in an equations set...
Definition: types.f90:3010
Contains information on the mapping from the equations rows in an equations set to the solver rows...
Definition: types.f90:2905
Contains the topology information for a decomposition.
Definition: types.f90:1054
Contains information about a data projection result.
Definition: types.f90:278
A buffer type to allow for an array of pointers to a DOMAIN_LINE_TYPE.
Definition: types.f90:632
Contains information for a geometric transformation solver.
Definition: types.f90:2761
This module contains all type definitions in order to avoid cyclic module references.
Definition: types.f90:70
Contains information about the interpolation for a parameter set in interface equations.
Definition: types.f90:2082
Contains information on the equations mapping for nonlinear matrices i.e., how a field variable is ma...
Definition: types.f90:1623
Contains the topology information for a local node of a domain.
Definition: types.f90:696
Contains information on the equations matrices and vectors.
Definition: types.f90:1520
Contains the mapping from the Jacobian back to the nonlinear residual variables.
Definition: types.f90:1599
A buffer type to allow for an array of pointers to a VARIABLE_BOUNDARY_CONDITIONS_TYPE.
Definition: types.f90:1775
The coupled equations DOF information for the DOF constraints. The BoundaryConditionsDofConstraintTyp...
Definition: types.f90:1839
Contains the topology information for the faces of a decomposition.
Definition: types.f90:991
Contains the mapping for a dependent variable type to the equations matrices.
Definition: types.f90:1548
Contains information of the linear matrices for equations matrices.
Definition: types.f90:1479
Contains information on the dofs for a mesh.
Definition: types.f90:376
Contains information on dofs with associated dirichlet conditions and corresponding non-zero elements...
Definition: types.f90:1794
Contains information on the solver matrix.
Definition: types.f90:2411
Contains information about the Lagrange field information for an interface condition.
Definition: types.f90:2137
Contains information about the convergence test for a newton solver.
Definition: types.f90:2653
Contains information of the projected data point.
Definition: types.f90:453
Contains information on the equations to solver matrix mappings when indexing by solver matrix number...
Definition: types.f90:2882
Contains information on the mappings from an equations set to the solver matrices.
Definition: types.f90:2912
Contains information for a Quasi-Newton nonlinear solver.
Definition: types.f90:2706
Contains information for an external differential-algebraic equation solver.
Definition: types.f90:2568
Contains information on the domain decomposition mappings.
Definition: types.f90:930
A buffer type to allow for an array of pointers to a FIELD_VARIABLE_TYPE.
Definition: types.f90:1311
Contains information on the projected data points on an element.
Definition: types.f90:446
Contains data point decompostion topology.
Definition: types.f90:1041
Contains information on a list.
Definition: types.f90:113
Buffer type to allow for arrays of pointers to FIELD_PHYSICAL_POINT_TYPE.
Definition: types.f90:1107
Contains information on the state field for a CellML environment.
Definition: types.f90:2294
Contains information on the source for the equations set.
Definition: types.f90:1915
Contains information for a CMISS distributed vector.
Definition: types.f90:761
Contains the information for an element in a mesh.
Definition: types.f90:388
Contains information on the meshes defined on a region.
Definition: types.f90:529
Contains data point information.
Definition: types.f90:1027
Contains information on a do-while control loop.
Definition: types.f90:3163
Contains information about the cached create values for a solver mapping.
Definition: types.f90:3058
Contains information for an improved Euler differential-algebraic equation solver.
Definition: types.f90:2522
Contains information for an element matrix.
Definition: types.f90:1387
Contains information about the solver equations for a solver.
Definition: types.f90:2452
A buffer type to allow for an array of pointers to a BASIS_TYPE.
Definition: types.f90:179
Contains the topology information for the faces of a domain.
Definition: types.f90:661
Contains information on the interface to solver matrix mappings when indexing by interface matrix num...
Definition: types.f90:2947
Contains information on the analytic setup for the equations set.
Definition: types.f90:1923
Contains the topology information for the elements of a decomposition.
Definition: types.f90:1017
Contains the information for the nodes of a mesh.
Definition: types.f90:433
Contains the local information for a global mapping number for a domain mapping.
Definition: types.f90:896
Contains information on the geometry for an equations set.
Definition: types.f90:1875
Contains information on a mesh defined on a region.
Definition: types.f90:503
Contains information on the generated meshes defined on a region.
Definition: types.f90:599
Contains information for a problem.
Definition: types.f90:3221
Definition: cmiss.f90:51
Contains information about a history file for a control loop.
Definition: types.f90:3118
Contains information on the mappings between field variable dofs inequations and the solver matrix co...
Definition: types.f90:2869
Contains information on a generated mesh.
Definition: types.f90:579
Contains the information for a vector that is distributed across a number of domains.
Definition: types.f90:786
Contains information for a Newton trust region nonlinear solver.
Definition: types.f90:2643
Contains the topology information for the nodes of a domain.
Definition: types.f90:713
Contains information on the decomposition adjacent elements for a xi coordinate.
Definition: types.f90:998
Contains information for a dynamic solver.
Definition: types.f90:2489
A type to hold the mapping from field data points to field dof numbers for a particular field variabl...
Definition: types.f90:1237
Contains information on the mapping between CellML fields and OpenCMISS fields and vise versa...
Definition: types.f90:2327
Contains the information on an adjacent domain to a domain in a domain mapping.
Definition: types.f90:887
Contains information about the interpolation for a domain (interface or coupled mesh) in the interfac...
Definition: types.f90:2089
A buffer type to allow for an array of pointers to a INTERFACE_CONDITION_TYPE.
Definition: types.f90:2173
Contains information for interface region specific data that is not of &#39;region&#39; importance. <<>>
Definition: types.f90:2178
Contains information for an backward Euler differential-algebraic equation solver.
Definition: types.f90:2516
A type to hold the mapping from a field node derivative&#39;s versions to field dof numbers for a particu...
Definition: types.f90:1201
A buffer type to allow for an array of pointers to a QUADRATURE_SCHEME_TYPE.
Definition: types.f90:156
Contains information on the models field for a CellML environment.
Definition: types.f90:2285
Contains the topology information for the lines of a decomposition.
Definition: types.f90:972
A type to hold the mapping from field parameters (nodes, elements, etc) to field dof numbers for a pa...
Definition: types.f90:1243
Contains the interpolated value (and the derivatives wrt xi) of a field at a point. Old CMISS name XG.
Definition: types.f90:1129
Contains information about an equations matrix.
Definition: types.f90:1429
Contains information for a particular quadrature scheme.
Definition: types.f90:141
Contains information for a BDF differential-algebraic equation solver.
Definition: types.f90:2556
A buffer type to allow for an array of pointers to a EQUATIONS_MATRIX_TYPE.
Definition: types.f90:1446
Contains information on the CellML environments defined.
Definition: types.f90:2398
A buffer type to allow for an array of pointers to a FIELD_PARAMETER_SET_TYPE.
Definition: types.f90:1276
A type to hold the parameter sets for a field.
Definition: types.f90:1268
Contains information on the mapping from an interface condition column to a solver row...
Definition: types.f90:2961
Embedded mesh types.
Definition: types.f90:483
A buffer type to allow for an array of pointers to a CELLML_TYPE.
Definition: types.f90:2393
Contains information on the solver mapping between the global equation sets and the solver matrices...
Definition: types.f90:3091
Contains information on the dependent variables for the equations set.
Definition: types.f90:1889
Contains information for an nodal matrix.
Definition: types.f90:1408
Contains information on a data connectivity point.
Definition: types.f90:2204
Contains information about the mapping from a solver matrix column to interface equations matrices an...
Definition: types.f90:3019
Contains the mapping for a dependent variable type to the nonlinear Jacobian matrix.
Definition: types.f90:1611
Contains information on the nodes defined on a region.
Definition: types.f90:359
Contains information on the solver matrices and rhs vector.
Definition: types.f90:2427
Contains information for a field variable defined on a field.
Definition: types.f90:1289
A buffer type to allow for an array of pointers to a INTERFACE_TYPE.
Definition: types.f90:2249
Contains information on a physical point in a field.
Definition: types.f90:1099
A type to hold the mapping from field grid points to field dof numbers for a particular field variabl...
Definition: types.f90:1225
A buffer type to allow for an array of pointers to a SOLVER_TYPE.
Definition: types.f90:2772
A buffer type to allow for an array of pointers to a CONTROL_LOOP_TYPE.
Definition: types.f90:3180
Describes linear constraints between solver DOFs in the solver mapping.
Definition: types.f90:1852
A buffer type to allow for an array of pointers to a CELLML_MODEL_TYPE.
Definition: types.f90:2280
Contains information on the domain mappings (i.e., local and global numberings).
Definition: types.f90:904
Contains information on the data point coupling/points connectivity between meshes in the an interfac...
Definition: types.f90:2218
Contains information on the mesh connectivity for a given coupled mesh element.
Definition: types.f90:2185
Contains the parameters required to interpolate a field variable within an element. Old CMISS name XE.
Definition: types.f90:1141
Contains information on a fixed iteration control loop.
Definition: types.f90:3139
Contains information on the setup information for an equations set.
Definition: types.f90:1866
This type is a wrapper for the C_PTR which references the actual CellML model definition object...
Definition: types.f90:2266
A pointer to the domain decomposition for this domain.
Definition: types.f90:938
Contains information for a PETSc distributed matrix.
Definition: types.f90:805
A buffer type to allow for an array of pointers to a MESH_TYPE.
Definition: types.f90:524
Contains information of the nolinear matrices and vectors for equations matrices. ...
Definition: types.f90:1486
Contains information on the interface matrices.
Definition: types.f90:2012
Contains information on the equations mapping for a RHS i.e., how a field variable is mapped to the R...
Definition: types.f90:1635
Contains information for an differential-algebraic equation solver.
Definition: types.f90:2573
Contains information of a generated ellipsoid mesh Allows only a 3D ellipsoid mesh.
Definition: types.f90:568
Contains information for the interface data.
Definition: types.f90:2228
Contains the information for a matrix that is distributed across a number of domains.
Definition: types.f90:828
Contains all information about a basis .
Definition: types.f90:184
Contains information on the variables involved in a solver matrix.
Definition: types.f90:3078
Contains information on the defined basis functions.
Definition: types.f90:243
Contains information for an optimiser solver.
Definition: types.f90:2746
Contains information on indices of non-zero elements with associated dirichlet conditions Indices sto...
Definition: types.f90:1802
Contains information on a generated regular mesh.
Definition: types.f90:543
Contains information for a Newton line search nonlinear solver.
Definition: types.f90:2626
Contains information used to integrate Neumann boundary conditions.
Definition: types.f90:1808
Contains information on the geometry for an interface condition.
Definition: types.f90:2123
Contains information on interface variable mapping for an interface matrix.
Definition: types.f90:2026
Contains information on the (global) topology of a mesh.
Definition: types.f90:468
Describes the value of a DOF as a linear combination of other DOFs.
Definition: types.f90:1821
Contains information for a linear solver.
Definition: types.f90:2617
Contains information for an element vector.
Definition: types.f90:1400
integer(intg), dimension(23, 4) partial_derivative_index
Partial derivative index map. PARTIAL_DERIVATIVE_INDEX(idx,nic) gives the order of the partial deriva...
Definition: constants.f90:232
Contains information on the mapping from an interface condition column to a solver row...
Definition: types.f90:2940
Contains information on the mesh adjacent elements for a xi coordinate.
Definition: types.f90:382
Describes the coupled rows or columns in the solver mapping.
Definition: types.f90:3084
Contains information on the mappings from a solver matrix to equations sets.
Definition: types.f90:3033
Buffer type to allow arrays of pointers to a list.
Definition: types.f90:108
Contains information of the RHS vector for equations matrices.
Definition: types.f90:1500
Contains information for a Rush-Larson differential-algebraic equation solver.
Definition: types.f90:2562
Contains information for a CellML environment.
Definition: types.f90:2372
Contains information for mapping field variables to the linear matrices in the equations set of the m...
Definition: types.f90:1587
Contains the information for the elements of a mesh.
Definition: types.f90:403
This module contains all kind definitions.
Definition: kinds.f90:45
Contains the topology information for the lines of a domain.
Definition: types.f90:637
Contains information on the derived variables for the equations set, eg. stress or strain...
Definition: types.f90:1897
Contains information on the mappings from an interface condition to the solver matrices.
Definition: types.f90:2968
Contains information about the interface equations for an interface condition.
Definition: types.f90:2110
Contains the information for an element in a decomposition.
Definition: types.f90:1004
Contains information of the dynamic matrices for equations matrices.
Definition: types.f90:1471