Skip to content

Commit

Permalink
Merge 6d89403 into 7279519
Browse files Browse the repository at this point in the history
  • Loading branch information
PrasadBabarendaGamage committed Dec 13, 2017
2 parents 7279519 + 6d89403 commit 5f31e71
Show file tree
Hide file tree
Showing 11 changed files with 1,320 additions and 1,000 deletions.
4 changes: 2 additions & 2 deletions src/Darcy_pressure_equations_routines.f90
Original file line number Diff line number Diff line change
Expand Up @@ -125,7 +125,7 @@ SUBROUTINE DarcyPressure_FiniteElementResidualEvaluate(EQUATIONS_SET,ELEMENT_NUM
& FIBRE_INTERPOLATION_PARAMETERS,MATERIALS_INTERPOLATION_PARAMETERS,SOLID_DEPENDENT_INTERPOLATION_PARAMETERS
REAL(DP), POINTER :: ELEMENT_RESIDUAL_VECTOR(:)
REAL(DP) :: K(3,3),density
REAL(DP) :: DZDNU(3,3),dZdXi(3,3),SIGMA(3,3),DNUDZ(3,3),DNUDZT(3,3),TEMP_MATRIX(3,3)
REAL(DP) :: DZDNU(3,3),SIGMA(3,3),DNUDZ(3,3),DNUDZT(3,3),TEMP_MATRIX(3,3)
REAL(DP) :: Jznu
INTEGER(INTG) :: SOLID_COMPONENT_NUMBER,SOLID_NUMBER_OF_XI,NUMBER_OF_DIMENSIONS
TYPE(VARYING_STRING) :: LOCAL_ERROR
Expand Down Expand Up @@ -239,7 +239,7 @@ SUBROUTINE DarcyPressure_FiniteElementResidualEvaluate(EQUATIONS_SET,ELEMENT_NUM

!Calculate F=dZ/dNU, the deformation gradient tensor at the gauss point
CALL FiniteElasticity_GaussDeformationGradientTensor(SOLID_DEPENDENT_INTERPOLATED_POINT_METRICS, &
& GEOMETRIC_INTERPOLATED_POINT_METRICS,FIBRE_INTERPOLATED_POINT,dZdXi,DZDNU,ERR,ERROR,*999)
& GEOMETRIC_INTERPOLATED_POINT_METRICS,FIBRE_INTERPOLATED_POINT,DZDNU,ERR,ERROR,*999)

CALL INVERT(DZDNU,DNUDZ,Jznu,ERR,ERROR,*999)
CALL MATRIX_TRANSPOSE(DNUDZ,DNUDZT,ERR,ERROR,*999)
Expand Down
4 changes: 2 additions & 2 deletions src/bioelectric_finite_elasticity_routines.f90
Original file line number Diff line number Diff line change
Expand Up @@ -789,7 +789,7 @@ SUBROUTINE BioelectricFiniteElasticity_ComputeFibreStretch(CONTROL_LOOP,ERR,ERRO
INTEGER(INTG) :: DEPENDENT_NUMBER_OF_GAUSS_POINTS
INTEGER(INTG) :: MESH_COMPONENT_NUMBER,NUMBER_OF_ELEMENTS,FIELD_VAR_TYPE
INTEGER(INTG) :: equations_set_idx,gauss_idx,dof_idx,element_idx,idx
REAL(DP) :: DZDNU(3,3),DZDNUT(3,3),dZdXi(3,3),AZL(3,3)
REAL(DP) :: DZDNU(3,3),DZDNUT(3,3),AZL(3,3)

ENTERS("BioelectricFiniteElasticity_ComputeFibreStretch",ERR,ERROR,*999)

Expand Down Expand Up @@ -932,7 +932,7 @@ SUBROUTINE BioelectricFiniteElasticity_ComputeFibreStretch(CONTROL_LOOP,ERR,ERRO

!Calculate F=dZ/dNU, the deformation gradient tensor at the gauss point
CALL FiniteElasticity_GaussDeformationGradientTensor(DEPENDENT_INTERPOLATED_POINT_METRICS, &
& GEOMETRIC_INTERPOLATED_POINT_METRICS,FIBRE_INTERPOLATED_POINT,dZdXi,DZDNU,ERR,ERROR,*999)
& GEOMETRIC_INTERPOLATED_POINT_METRICS,FIBRE_INTERPOLATED_POINT,DZDNU,ERR,ERROR,*999)

!compute C=F^T F
CALL MATRIX_TRANSPOSE(DZDNU,DZDNUT,ERR,ERROR,*999)
Expand Down
12 changes: 7 additions & 5 deletions src/boundary_condition_routines.f90
Original file line number Diff line number Diff line change
Expand Up @@ -2970,12 +2970,13 @@ END SUBROUTINE BOUNDARY_CONDITIONS_SET_NODE
!

!>Constrain multiple equations dependent field DOFs to be a single solver DOF in the solver equations
SUBROUTINE BoundaryConditions_ConstrainDofsEqual(boundaryConditions,fieldVariable,globalDofs,err,error,*)
SUBROUTINE BoundaryConditions_ConstrainDofsEqual(boundaryConditions,fieldVariable,globalDofs,coefficient,err,error,*)

!Argument variables
TYPE(BOUNDARY_CONDITIONS_TYPE), POINTER, INTENT(IN) :: boundaryConditions !<The boundary conditions for the solver equations in which to constrain the DOF.
TYPE(FIELD_VARIABLE_TYPE), POINTER, INTENT(IN) :: fieldVariable !<A pointer to the field variable containing the DOFs.
INTEGER(INTG), INTENT(IN) :: globalDofs(:) !<The global DOFs to be constrained to be equal.
REAL(DP), INTENT(IN) :: coefficient !<The coefficient of constraint.
INTEGER(INTG), INTENT(OUT) :: err !<The error code.
TYPE(VARYING_STRING), INTENT(OUT) :: error !<The error message.
!Local variables
Expand All @@ -2999,11 +3000,11 @@ SUBROUTINE BoundaryConditions_ConstrainDofsEqual(boundaryConditions,fieldVariabl
END DO

!Add new DOF constraints
!We set all DOFs except the first to be equal to 1.0 * the first DOF
!We set all DOFs except the first to be equal to coefficient * the first DOF
!The first DOF is left unconstrained
DO dofIdx=2,numberOfDofs
CALL BoundaryConditions_DofConstraintSet( &
& boundaryConditions,fieldVariable,globalDofs(dofIdx),[globalDofs(1)],[1.0_DP],err,error,*999)
& boundaryConditions,fieldVariable,globalDofs(dofIdx),[globalDofs(1)],[coefficient],err,error,*999)
END DO

EXITS("BoundaryConditions_ConstrainDofsEqual")
Expand All @@ -3018,7 +3019,7 @@ END SUBROUTINE BoundaryConditions_ConstrainDofsEqual

!>Constrain multiple nodal equations dependent field DOFs to be a single solver DOF in the solver equations
SUBROUTINE BoundaryConditions_ConstrainNodeDofsEqual( &
& boundaryConditions,field,fieldVariableType,versionNumber,derivativeNumber,component,nodes,err,error,*)
& boundaryConditions,field,fieldVariableType,versionNumber,derivativeNumber,component,nodes,coefficient,err,error,*)

!Argument variables
TYPE(BOUNDARY_CONDITIONS_TYPE), POINTER, INTENT(IN) :: boundaryConditions !<The solver equations boundary conditions to constrain the DOFs for.
Expand All @@ -3028,6 +3029,7 @@ SUBROUTINE BoundaryConditions_ConstrainNodeDofsEqual( &
INTEGER(INTG), INTENT(IN) :: derivativeNumber !<The derivative number.
INTEGER(INTG), INTENT(IN) :: component !<The field component number of the DOFs to be constrained.
INTEGER(INTG), INTENT(IN) :: nodes(:) !<The user numbers of the nodes to be constrained to be equal.
REAL(DP), INTENT(IN) :: coefficient !<The coefficient of constraint, applied to all but the first node.
INTEGER(INTG), INTENT(OUT) :: err !<The error code.
TYPE(VARYING_STRING), INTENT(OUT) :: error !<The error message.
!Local variables
Expand Down Expand Up @@ -3055,7 +3057,7 @@ SUBROUTINE BoundaryConditions_ConstrainNodeDofsEqual( &
CALL FIELD_VARIABLE_GET(field,fieldVariableType,fieldVariable,err,error,*999)

!Now set DOF constraint
CALL BoundaryConditions_ConstrainDofsEqual(boundaryConditions,fieldVariable,globalDofs,err,error,*999)
CALL BoundaryConditions_ConstrainDofsEqual(boundaryConditions,fieldVariable,globalDofs,coefficient,err,error,*999)

DEALLOCATE(globalDofs)

Expand Down

0 comments on commit 5f31e71

Please sign in to comment.