Skip to content

Commit

Permalink
Did temporary fix for issue OpenCMISS#169, fixing problem with dofs b…
Browse files Browse the repository at this point in the history
…eing able to be defined as internal on one rank and ghost on another.

Also, finished changing solver_mapping_calculate so that it is done locally. Now there is only a local_to_global map for col_dof_mapping, there is no global_to_local_map. This causes issues but these will be fixed when lorenzo's work is merged as he has implemented hash tables that will be used instead of the global_to_local_map.
  • Loading branch information
FinbarArgus committed Oct 17, 2018
1 parent 352b388 commit 3196e53
Show file tree
Hide file tree
Showing 2 changed files with 209 additions and 197 deletions.
63 changes: 51 additions & 12 deletions src/mesh_routines.f90
Original file line number Diff line number Diff line change
Expand Up @@ -3236,7 +3236,7 @@ SUBROUTINE DECOMPOSITION_TOPOLOGY_FACES_CALCULATE(TOPOLOGY,ERR,ERROR,*)

DO xicIdx = startNic,MESH_TOPOLOGY%ELEMENTS%ELEMENTS(elementGlobalNo)%BASIS%NUMBER_OF_XI_COORDINATES
IF(xicIdx ==0) CYCLE
IF(MESH_TOPOLOGY%ELEMENTS%ELEMENTS(1)%BASIS%TYPE == BASIS_LAGRANGE_HERMITE_TP_TYPE) THEN
IF(MESH_TOPOLOGY%ELEMENTS%ELEMENTS(1)%BASIS%TYPE == BASIS_LAGRANGE_HERMITE_TP_TYPE) THEN
IF(xicIdx<0) THEN
IF(BASIS%COLLAPSED_XI(abs(xicIdx))==BASIS_COLLAPSED_AT_XI0) CYCLE
ELSE
Expand Down Expand Up @@ -7238,7 +7238,7 @@ SUBROUTINE DOMAIN_MAPPINGS_NODES_DOFS_CALCULATE(DOMAIN,err,ERROR,*)
& NUMBER_OF_NODES_PER_DOMAIN,domain_idx,domain_idx2,domain_no,node_idx,derivative_idx,version_idx,ny,NUMBER_OF_DOMAINS, &
& MAX_NUMBER_DOMAINS,NUMBER_OF_GHOST_NODES,myComputationalNodeNumber,numberOfComputationalNodes,component_idx
INTEGER(INTG), ALLOCATABLE :: LOCAL_NODE_NUMBERS(:),LOCAL_DOF_NUMBERS(:),NODE_COUNT(:),NUMBER_INTERNAL_NODES(:), &
& NUMBER_BOUNDARY_NODES(:)
& NUMBER_BOUNDARY_NODES(:), boundaryPlane(:)
INTEGER(INTG), ALLOCATABLE :: DOMAINS(:),ALL_DOMAINS(:),GHOST_NODES(:)
LOGICAL :: BOUNDARY_DOMAIN
TYPE(LIST_TYPE), POINTER :: ADJACENT_DOMAINS_LIST,ALL_ADJACENT_DOMAINS_LIST
Expand Down Expand Up @@ -7303,6 +7303,9 @@ SUBROUTINE DOMAIN_MAPPINGS_NODES_DOFS_CALCULATE(DOMAIN,err,ERROR,*)
IF(ERR/=0) CALL FlagError("Could not allocate number of boundary nodes.",ERR,ERROR,*999)
NUMBER_BOUNDARY_NODES=0

!Temporary Fix
ALLOCATE(boundaryPlane(MESH_TOPOLOGY%NODES%numberOfNodes))
boundaryPlane = -1
!For the first pass just determine the internal and boundary nodes
DO node_idx=1,MESH_TOPOLOGY%NODES%numberOfNodes
NULLIFY(ADJACENT_DOMAINS_LIST)
Expand Down Expand Up @@ -7358,36 +7361,43 @@ SUBROUTINE DOMAIN_MAPPINGS_NODES_DOFS_CALCULATE(DOMAIN,err,ERROR,*)
IF(ERR/=0) CALL FlagError("Could not allocate dof global to local map local type.",ERR,ERROR,*999)
ENDDO !version_idx
ENDDO !derivative_idx
IF(NUMBER_OF_DOMAINS==1) THEN
IF(MAX_NUMBER_DOMAINS==1) THEN

!Node is an internal node
domain_no=DOMAINS(1)
NUMBER_INTERNAL_NODES(domain_no)=NUMBER_INTERNAL_NODES(domain_no)+1
!LOCAL_NODE_NUMBERS(domain_no)=LOCAL_NODE_NUMBERS(domain_no)+1
NODES_MAPPING%GLOBAL_TO_LOCAL_MAP(node_idx)%NUMBER_OF_DOMAINS=1
NODES_MAPPING%GLOBAL_TO_LOCAL_MAP(node_idx)%NUMBER_OF_DOMAINS=MAX_NUMBER_DOMAINS
!NODES_MAPPING%GLOBAL_TO_LOCAL_MAP(node_idx)%LOCAL_NUMBER(1)=LOCAL_NODE_NUMBERS(DOMAINS(1))
NODES_MAPPING%GLOBAL_TO_LOCAL_MAP(node_idx)%LOCAL_NUMBER(1)=-1
NODES_MAPPING%GLOBAL_TO_LOCAL_MAP(node_idx)%DOMAIN_NUMBER(1)=DOMAINS(1)
NODES_MAPPING%GLOBAL_TO_LOCAL_MAP(node_idx)%LOCAL_TYPE(1)=DOMAIN_LOCAL_INTERNAL
DO derivative_idx=1,MESH_TOPOLOGY%NODES%NODES(node_idx)%numberOfDerivatives
DO version_idx=1,MESH_TOPOLOGY%NODES%NODES(node_idx)%DERIVATIVES(derivative_idx)%numberOfVersions
ny=MESH_TOPOLOGY%NODES%NODES(node_idx)%DERIVATIVES(derivative_idx)%dofIndex(version_idx)
DOFS_MAPPING%GLOBAL_TO_LOCAL_MAP(ny)%NUMBER_OF_DOMAINS=1
DOFS_MAPPING%GLOBAL_TO_LOCAL_MAP(ny)%NUMBER_OF_DOMAINS=MAX_NUMBER_DOMAINS
DOFS_MAPPING%GLOBAL_TO_LOCAL_MAP(ny)%LOCAL_NUMBER(1)=-1
DOFS_MAPPING%GLOBAL_TO_LOCAL_MAP(ny)%DOMAIN_NUMBER(1)=domain_no
DOFS_MAPPING%GLOBAL_TO_LOCAL_MAP(ny)%LOCAL_TYPE(1)=DOMAIN_LOCAL_INTERNAL
ENDDO !version_idx
ENDDO !derivative_idx
ELSE
!Node is on the boundary of computational domains
NODES_MAPPING%GLOBAL_TO_LOCAL_MAP(node_idx)%NUMBER_OF_DOMAINS=NUMBER_OF_DOMAINS
IF(NUMBER_OF_DOMAINS==1) THEN
! node is a boundary but not on the border between domains
boundaryPlane(node_idx) = 0
ELSE
boundaryPlane(node_idx) = 1
ENDIF
!Node is on the boundary plane of computational domains
NODES_MAPPING%GLOBAL_TO_LOCAL_MAP(node_idx)%NUMBER_OF_DOMAINS=MAX_NUMBER_DOMAINS
DO derivative_idx=1,MESH_TOPOLOGY%NODES%NODES(node_idx)%numberOfDerivatives
DO version_idx=1,MESH_TOPOLOGY%NODES%NODES(node_idx)%DERIVATIVES(derivative_idx)%numberOfVersions
ny=MESH_TOPOLOGY%NODES%NODES(node_idx)%DERIVATIVES(derivative_idx)%dofIndex(version_idx)
DOFS_MAPPING%GLOBAL_TO_LOCAL_MAP(ny)%NUMBER_OF_DOMAINS=NUMBER_OF_DOMAINS
DOFS_MAPPING%GLOBAL_TO_LOCAL_MAP(ny)%NUMBER_OF_DOMAINS=MAX_NUMBER_DOMAINS
ENDDO !version_idx
ENDDO !derivative_idx
DO domain_idx=1,NUMBER_OF_DOMAINS
domain_no=DOMAINS(domain_idx)
DO domain_idx=1,MAX_NUMBER_DOMAINS
domain_no=ALL_DOMAINS(domain_idx)
!LOCAL_NODE_NUMBERS(domain_no)=LOCAL_NODE_NUMBERS(domain_no)+1
!NODES_MAPPING%GLOBAL_TO_LOCAL_MAP(node_idx)%LOCAL_NUMBER(domain_idx)=LOCAL_NODE_NUMBERS(domain_no)
NODES_MAPPING%GLOBAL_TO_LOCAL_MAP(node_idx)%LOCAL_NUMBER(domain_idx)=-1
Expand Down Expand Up @@ -7426,6 +7436,31 @@ SUBROUTINE DOMAIN_MAPPINGS_NODES_DOFS_CALCULATE(DOMAIN,err,ERROR,*)
DOFS_MAPPING%GLOBAL_TO_LOCAL_MAP(ny)%LOCAL_NUMBER(1)=LOCAL_DOF_NUMBERS(domain_no)
ENDDO !version_idx
ENDDO !derivative_idx
ELSEIF(boundaryPlane(node_idx)/=1) THEN
!boundary nodes that aren't on the boundary plane get assigned as boundary nodes.
!Allocate the node to this domain

!the domain number is that of any adjacent element
adjacent_element=MESH_TOPOLOGY%NODES%NODES(node_idx)%surroundingElements(1)
domain_no=DECOMPOSITION%ELEMENT_DOMAIN(adjacent_element)
DOMAIN%NODE_DOMAIN(node_idx)=domain_no
NUMBER_BOUNDARY_NODES(domain_no)=NUMBER_BOUNDARY_NODES(domain_no)+1
LOCAL_NODE_NUMBERS(domain_no)=LOCAL_NODE_NUMBERS(domain_no)+1
!Reset the boundary information to be in the first domain index. The remaining domain indicies will
!be overwritten when the ghost nodes are calculated below.
NODES_MAPPING%GLOBAL_TO_LOCAL_MAP(node_idx)%LOCAL_NUMBER(1)=LOCAL_NODE_NUMBERS(domain_no)
NODES_MAPPING%GLOBAL_TO_LOCAL_MAP(node_idx)%DOMAIN_NUMBER(1)=domain_no
NODES_MAPPING%GLOBAL_TO_LOCAL_MAP(node_idx)%LOCAL_TYPE(1)=DOMAIN_LOCAL_BOUNDARY
DO derivative_idx=1,MESH_TOPOLOGY%NODES%NODES(node_idx)%numberOfDerivatives
DO version_idx=1,MESH_TOPOLOGY%NODES%NODES(node_idx)%DERIVATIVES(derivative_idx)%numberOfVersions
ny=MESH_TOPOLOGY%NODES%NODES(node_idx)%DERIVATIVES(derivative_idx)%dofIndex(version_idx)
LOCAL_DOF_NUMBERS(domain_no)=LOCAL_DOF_NUMBERS(domain_no)+1
DOFS_MAPPING%GLOBAL_TO_LOCAL_MAP(ny)%LOCAL_NUMBER(1)=LOCAL_DOF_NUMBERS(domain_no)
DOFS_MAPPING%GLOBAL_TO_LOCAL_MAP(ny)%DOMAIN_NUMBER(1)=domain_no
DOFS_MAPPING%GLOBAL_TO_LOCAL_MAP(ny)%LOCAL_TYPE(1)=DOMAIN_LOCAL_BOUNDARY
ENDDO !version_idx
ENDDO !derivative_idx

ELSE !Boundary node
NUMBER_OF_DOMAINS=NODES_MAPPING%GLOBAL_TO_LOCAL_MAP(node_idx)%NUMBER_OF_DOMAINS
DO domain_idx=1,NUMBER_OF_DOMAINS
Expand All @@ -7439,15 +7474,13 @@ SUBROUTINE DOMAIN_MAPPINGS_NODES_DOFS_CALCULATE(DOMAIN,err,ERROR,*)
LOCAL_NODE_NUMBERS(domain_no)=LOCAL_NODE_NUMBERS(domain_no)+1
!Reset the boundary information to be in the first domain index. The remaining domain indicies will
!be overwritten when the ghost nodes are calculated below.
NODES_MAPPING%GLOBAL_TO_LOCAL_MAP(node_idx)%NUMBER_OF_DOMAINS=1
NODES_MAPPING%GLOBAL_TO_LOCAL_MAP(node_idx)%LOCAL_NUMBER(1)=LOCAL_NODE_NUMBERS(domain_no)
NODES_MAPPING%GLOBAL_TO_LOCAL_MAP(node_idx)%DOMAIN_NUMBER(1)=domain_no
NODES_MAPPING%GLOBAL_TO_LOCAL_MAP(node_idx)%LOCAL_TYPE(1)=DOMAIN_LOCAL_BOUNDARY
DO derivative_idx=1,MESH_TOPOLOGY%NODES%NODES(node_idx)%numberOfDerivatives
DO version_idx=1,MESH_TOPOLOGY%NODES%NODES(node_idx)%DERIVATIVES(derivative_idx)%numberOfVersions
ny=MESH_TOPOLOGY%NODES%NODES(node_idx)%DERIVATIVES(derivative_idx)%dofIndex(version_idx)
LOCAL_DOF_NUMBERS(domain_no)=LOCAL_DOF_NUMBERS(domain_no)+1
DOFS_MAPPING%GLOBAL_TO_LOCAL_MAP(ny)%NUMBER_OF_DOMAINS=1
DOFS_MAPPING%GLOBAL_TO_LOCAL_MAP(ny)%LOCAL_NUMBER(1)=LOCAL_DOF_NUMBERS(domain_no)
DOFS_MAPPING%GLOBAL_TO_LOCAL_MAP(ny)%DOMAIN_NUMBER(1)=domain_no
DOFS_MAPPING%GLOBAL_TO_LOCAL_MAP(ny)%LOCAL_TYPE(1)=DOMAIN_LOCAL_BOUNDARY
Expand All @@ -7463,6 +7496,12 @@ SUBROUTINE DOMAIN_MAPPINGS_NODES_DOFS_CALCULATE(DOMAIN,err,ERROR,*)
ENDIF
ENDDO !domain_idx
ENDIF

!Reset the number of domains for each node, this will be increased for each ghost.
NODES_MAPPING%GLOBAL_TO_LOCAL_MAP(node_idx)%NUMBER_OF_DOMAINS=1
DOFS_MAPPING%GLOBAL_TO_LOCAL_MAP(ny)%NUMBER_OF_DOMAINS=1


ENDDO !node_idx
DEALLOCATE(NUMBER_INTERNAL_NODES)

Expand Down
Loading

0 comments on commit 3196e53

Please sign in to comment.