/FiniteElasticity/Membrane/MembraneExtension2DSpace/src/MembraneExtension2DSpaceExample.f90

http://github.com/xyan075/examples · Fortran Modern · 409 lines · 253 code · 68 blank · 88 comment · 0 complexity · ac4e071c49113dc7bcedc14350f0a184 MD5 · raw file

  1. !> \file
  2. !> \author Chris Bradley
  3. !> \brief This is an example program to solve a finite elasticity membrane equation using openCMISS calls.
  4. !>
  5. !> \section LICENSE
  6. !>
  7. !> Version: MPL 1.1/GPL 2.0/LGPL 2.1
  8. !>
  9. !> The contents of this file are subject to the Mozilla Public License
  10. !> Version 1.1 (the "License"); you may not use this file except in
  11. !> compliance with the License. You may obtain a copy of the License at
  12. !> http://www.mozilla.org/MPL/
  13. !>
  14. !> Software distributed under the License is distributed on an "AS IS"
  15. !> basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See the
  16. !> License for the specific language governing rights and limitations
  17. !> under the License.
  18. !>
  19. !> The Original Code is openCMISS
  20. !>
  21. !> The Initial Developer of the Original Code is University of Auckland,
  22. !> Auckland, New Zealand and University of Oxford, Oxford, United
  23. !> Kingdom. Portions created by the University of Auckland and University
  24. !> of Oxford are Copyright (C) 2007 by the University of Auckland and
  25. !> the University of Oxford. All Rights Reserved.
  26. !>
  27. !> Contributor(s): Alice Hung, Jessica Jor
  28. !>
  29. !> Alternatively, the contents of this file may be used under the terms of
  30. !> either the GNU General Public License Version 2 or later (the "GPL"), or
  31. !> the GNU Lesser General Public License Version 2.1 or later (the "LGPL"),
  32. !> in which case the provisions of the GPL or the LGPL are applicable instead
  33. !> of those above. If you wish to allow use of your version of this file only
  34. !> under the terms of either the GPL or the LGPL, and not to allow others to
  35. !> use your version of this file under the terms of the MPL, indicate your
  36. !> decision by deleting the provisions above and replace them with the notice
  37. !> and other provisions required by the GPL or the LGPL. If you do not delete
  38. !> the provisions above, a recipient may use your version of this file under
  39. !> the terms of any one of the MPL, the GPL or the LGPL.
  40. !>
  41. !> \example FiniteElasticity/Membrane/MembraneExtension2DSpace/src/MembraneExtension2DSpaceExample.f90
  42. !! Example program to solve a finite elasticity membrane equation using openCMISS calls.
  43. !! \par Latest Builds:
  44. !! \li <a href='http://autotest.bioeng.auckland.ac.nz/opencmiss-build/logs_x86_64-linux/FiniteElasticity/UniAxialExtension/build-intel'>Linux Intel Build</a>
  45. !! \li <a href='http://autotest.bioeng.auckland.ac.nz/opencmiss-build/logs_x86_64-linux/FiniteElasticity/UniAxialExtension/build-gnu'>Linux GNU Build</a>
  46. !<
  47. !> Main program
  48. PROGRAM MEMBRANEEXTENSION2DSPACE
  49. USE OPENCMISS
  50. USE MPI
  51. #ifdef WIN32
  52. USE IFQWIN
  53. #endif
  54. IMPLICIT NONE
  55. INTEGER(CMISSIntg), PARAMETER :: EquationsSetFieldUserNumber=1337
  56. TYPE(CMISSFieldType) :: EquationsSetField
  57. !Test program parameters
  58. REAL(CMISSDP), PARAMETER :: HEIGHT=1.0_CMISSDP
  59. REAL(CMISSDP), PARAMETER :: WIDTH=1.0_CMISSDP
  60. REAL(CMISSDP), PARAMETER :: LENGTH=1.0_CMISSDP
  61. INTEGER(CMISSIntg), PARAMETER :: CoordinateSystemUserNumber=1
  62. INTEGER(CMISSIntg), PARAMETER :: NumberOfSpatialCoordinates=2
  63. INTEGER(CMISSIntg), PARAMETER :: RegionUserNumber=1
  64. INTEGER(CMISSIntg), PARAMETER :: BasisUserNumber=1
  65. INTEGER(CMISSIntg), PARAMETER :: MeshUserNumber=1
  66. INTEGER(CMISSIntg), PARAMETER :: DecompositionUserNumber=1
  67. INTEGER(CMISSIntg), PARAMETER :: NumberOfXiCoordinates=2
  68. INTEGER(CMISSIntg), PARAMETER :: TotalNumberOfNodes=4
  69. INTEGER(CMISSIntg), PARAMETER :: NumberOfMeshDimensions=2
  70. INTEGER(CMISSIntg), PARAMETER :: NumberOfMeshComponents=1
  71. INTEGER(CMISSIntg), PARAMETER :: TotalNumberOfElements=1
  72. INTEGER(CMISSIntg), PARAMETER :: MeshComponentNumber=1
  73. INTEGER(CMISSIntg), PARAMETER :: FieldGeometryUserNumber=1
  74. INTEGER(CMISSIntg), PARAMETER :: FieldGeometryNumberOfVariables=1
  75. INTEGER(CMISSIntg), PARAMETER :: FieldGeometryNumberOfComponents=2
  76. INTEGER(CMISSIntg), PARAMETER :: FieldFibreUserNumber=2
  77. INTEGER(CMISSIntg), PARAMETER :: FieldFibreNumberOfVariables=1
  78. ! Should only need 1 component (i.e. 1 angle), the second component is redundant but is required for consistency
  79. INTEGER(CMISSIntg), PARAMETER :: FieldFibreNumberOfComponents=2
  80. !Component 1, 2 are Mooney-Rivlin constants. Component 3 is membrane thickness.
  81. INTEGER(CMISSIntg), PARAMETER :: FieldMaterialUserNumber=3
  82. INTEGER(CMISSIntg), PARAMETER :: FieldMaterialNumberOfVariables=1
  83. INTEGER(CMISSIntg), PARAMETER :: FieldMaterialNumberOfComponents=2
  84. INTEGER(CMISSIntg), PARAMETER :: FieldDependentUserNumber=4
  85. INTEGER(CMISSIntg), PARAMETER :: FieldDependentNumberOfVariables=2
  86. INTEGER(CMISSIntg), PARAMETER :: FieldDependentNumberOfComponents=2
  87. INTEGER(CMISSIntg), PARAMETER :: EquationSetUserNumber=1
  88. INTEGER(CMISSIntg), PARAMETER :: ProblemUserNumber=1
  89. !Program types
  90. !Program variables
  91. INTEGER(CMISSIntg) :: NumberGlobalXElements,NumberGlobalYElements,NumberGlobalZElements
  92. INTEGER(CMISSIntg) :: MPI_IERROR
  93. INTEGER(CMISSIntg) :: EquationsSetIndex
  94. INTEGER(CMISSIntg) :: NumberOfComputationalNodes,NumberOfDomains,ComputationalNodeNumber
  95. !CMISS variables
  96. TYPE(CMISSBasisType) :: Basis
  97. TYPE(CMISSBoundaryConditionsType) :: BoundaryConditions
  98. TYPE(CMISSCoordinateSystemType) :: CoordinateSystem, WorldCoordinateSystem
  99. TYPE(CMISSMeshType) :: Mesh
  100. TYPE(CMISSDecompositionType) :: Decomposition
  101. TYPE(CMISSEquationsType) :: Equations
  102. TYPE(CMISSEquationsSetType) :: EquationsSet
  103. TYPE(CMISSFieldType) :: GeometricField,FibreField,MaterialField,DependentField
  104. TYPE(CMISSFieldsType) :: Fields
  105. TYPE(CMISSProblemType) :: Problem
  106. TYPE(CMISSRegionType) :: Region,WorldRegion
  107. TYPE(CMISSSolverType) :: Solver
  108. TYPE(CMISSSolverEquationsType) :: SolverEquations
  109. TYPE(CMISSNodesType) :: Nodes
  110. TYPE(CMISSMeshElementsType) :: Elements
  111. !REAL(CMISSDP), POINTER :: FieldData(:)
  112. #ifdef WIN32
  113. !Quickwin type
  114. LOGICAL :: QUICKWIN_STATUS=.FALSE.
  115. TYPE(WINDOWCONFIG) :: QUICKWIN_WINDOW_CONFIG
  116. #endif
  117. !Generic CMISS variables
  118. INTEGER(CMISSIntg) :: Err
  119. #ifdef WIN32
  120. !Initialise QuickWin
  121. QUICKWIN_WINDOW_CONFIG%TITLE="General Output" !Window title
  122. QUICKWIN_WINDOW_CONFIG%NUMTEXTROWS=-1 !Max possible number of rows
  123. QUICKWIN_WINDOW_CONFIG%MODE=QWIN$SCROLLDOWN
  124. !Set the window parameters
  125. QUICKWIN_STATUS=SETWINDOWCONFIG(QUICKWIN_WINDOW_CONFIG)
  126. !If attempt fails set with system estimated values
  127. IF(.NOT.QUICKWIN_STATUS) QUICKWIN_STATUS=SETWINDOWCONFIG(QUICKWIN_WINDOW_CONFIG)
  128. #endif
  129. !Intialise cmiss
  130. CALL CMISSInitialise(WorldCoordinateSystem,WorldRegion,Err)
  131. CALL CMISSErrorHandlingModeSet(CMISS_ERRORS_TRAP_ERROR,Err)
  132. WRITE(*,'(A)') "Program starting."
  133. !Set all diganostic levels on for testing
  134. CALL CMISSDiagnosticsSetOn(CMISS_FROM_DIAG_TYPE,(/1,2,3,4,5/),"Diagnostics",(/"PROBLEM_FINITE_ELEMENT_CALCULATE"/),Err)
  135. !Get the number of computational nodes and this computational node number
  136. CALL CMISSComputationalNumberOfNodesGet(NumberOfComputationalNodes,Err)
  137. CALL CMISSComputationalNodeNumberGet(ComputationalNodeNumber,Err)
  138. NumberGlobalXElements=1
  139. NumberGlobalYElements=1
  140. NumberGlobalZElements=1
  141. NumberOfDomains=1
  142. !Broadcast the number of elements in the X,Y and Z directions and the number of partitions to the other computational nodes
  143. CALL MPI_BCAST(NumberGlobalXElements,1,MPI_INTEGER,0,MPI_COMM_WORLD,MPI_IERROR)
  144. CALL MPI_BCAST(NumberGlobalYElements,1,MPI_INTEGER,0,MPI_COMM_WORLD,MPI_IERROR)
  145. CALL MPI_BCAST(NumberGlobalZElements,1,MPI_INTEGER,0,MPI_COMM_WORLD,MPI_IERROR)
  146. CALL MPI_BCAST(NumberOfDomains,1,MPI_INTEGER,0,MPI_COMM_WORLD,MPI_IERROR)
  147. !Create a CS - default is 3D rectangular cartesian CS with 0,0,0 as origin
  148. CALL CMISSCoordinateSystem_Initialise(CoordinateSystem,Err)
  149. CALL CMISSCoordinateSystem_CreateStart(CoordinateSystemUserNumber,CoordinateSystem,Err)
  150. CALL CMISSCoordinateSystem_TypeSet(CoordinateSystem,CMISS_COORDINATE_RECTANGULAR_CARTESIAN_TYPE,Err)
  151. CALL CMISSCoordinateSystem_DimensionSet(CoordinateSystem,NumberOfSpatialCoordinates,Err)
  152. CALL CMISSCoordinateSystem_OriginSet(CoordinateSystem,(/0.0_CMISSDP,0.0_CMISSDP,0.0_CMISSDP/),Err)
  153. CALL CMISSCoordinateSystem_CreateFinish(CoordinateSystem,Err)
  154. !Create a region and assign the CS to the region
  155. CALL CMISSRegion_Initialise(Region,Err)
  156. CALL CMISSRegion_CreateStart(RegionUserNumber,WorldRegion,Region,Err)
  157. CALL CMISSRegion_CoordinateSystemSet(Region,CoordinateSystem,Err)
  158. CALL CMISSRegion_CreateFinish(Region,Err)
  159. !Define basis function - tri-linear Lagrange
  160. CALL CMISSBasis_Initialise(Basis,Err)
  161. CALL CMISSBasis_CreateStart(BasisUserNumber,Basis,Err)
  162. CALL CMISSBasis_TypeSet(Basis,CMISS_BASIS_LAGRANGE_HERMITE_TP_TYPE,Err)
  163. CALL CMISSBasis_NumberOfXiSet(Basis,NumberOfXiCoordinates,Err)
  164. CALL CMISSBasis_InterpolationXiSet(Basis,(/CMISS_BASIS_LINEAR_LAGRANGE_INTERPOLATION, &
  165. & CMISS_BASIS_LINEAR_LAGRANGE_INTERPOLATION/),Err)
  166. CALL CMISSBasis_QuadratureNumberOfGaussXiSet(Basis, (/CMISS_BASIS_MID_QUADRATURE_SCHEME,CMISS_BASIS_MID_QUADRATURE_SCHEME/),Err)
  167. CALL CMISSBasis_CreateFinish(Basis,Err)
  168. !Create a mesh
  169. CALL CMISSMesh_Initialise(Mesh,Err)
  170. CALL CMISSMesh_CreateStart(MeshUserNumber,Region,NumberOfMeshDimensions,Mesh,Err)
  171. CALL CMISSMesh_NumberOfComponentsSet(Mesh,NumberOfMeshComponents,Err)
  172. CALL CMISSMesh_NumberOfElementsSet(Mesh,TotalNumberOfElements,Err)
  173. !Define nodes for the mesh
  174. CALL CMISSNodes_Initialise(Nodes,Err)
  175. CALL CMISSNodes_CreateStart(Region,TotalNumberOfNodes,Nodes,Err)
  176. CALL CMISSNodes_CreateFinish(Nodes,Err)
  177. CALL CMISSMeshElements_Initialise(Elements,Err)
  178. CALL CMISSMeshElements_CreateStart(Mesh,MeshComponentNumber,Basis,Elements,Err)
  179. CALL CMISSMeshElements_NodesSet(Elements,1,(/1,2,3,4/),Err)
  180. CALL CMISSMeshElements_CreateFinish(Elements,Err)
  181. CALL CMISSMesh_CreateFinish(Mesh,Err)
  182. !Create a decomposition
  183. CALL CMISSDecomposition_Initialise(Decomposition,Err)
  184. CALL CMISSDecomposition_CreateStart(DecompositionUserNumber,Mesh,Decomposition,Err)
  185. CALL CMISSDecomposition_TypeSet(Decomposition,CMISS_DECOMPOSITION_CALCULATED_TYPE,Err)
  186. CALL CMISSDecomposition_NumberOfDomainsSet(Decomposition,NumberOfDomains,Err)
  187. CALL CMISSDecomposition_CreateFinish(Decomposition,Err)
  188. !Create a field to put the geometry (defualt is geometry)
  189. CALL CMISSField_Initialise(GeometricField,Err)
  190. CALL CMISSField_CreateStart(FieldGeometryUserNumber,Region,GeometricField,Err)
  191. CALL CMISSField_MeshDecompositionSet(GeometricField,Decomposition,Err)
  192. CALL CMISSField_TypeSet(GeometricField,CMISS_FIELD_GEOMETRIC_TYPE,Err)
  193. CALL CMISSField_NumberOfVariablesSet(GeometricField,FieldGeometryNumberOfVariables,Err)
  194. CALL CMISSField_NumberOfComponentsSet(GeometricField,CMISS_FIELD_U_VARIABLE_TYPE,FieldGeometryNumberOfComponents,Err)
  195. CALL CMISSField_ComponentMeshComponentSet(GeometricField,CMISS_FIELD_U_VARIABLE_TYPE,1,MeshComponentNumber,Err)
  196. CALL CMISSField_ComponentMeshComponentSet(GeometricField,CMISS_FIELD_U_VARIABLE_TYPE,2,MeshComponentNumber,Err)
  197. CALL CMISSField_CreateFinish(GeometricField,Err)
  198. !node 1
  199. CALL CMISSField_ParameterSetUpdateNode(GeometricField,CMISS_FIELD_U_VARIABLE_TYPE,CMISS_FIELD_VALUES_SET_TYPE,1,1,1,1, &
  200. & 0.4_CMISSDP,Err)
  201. CALL CMISSField_ParameterSetUpdateNode(GeometricField,CMISS_FIELD_U_VARIABLE_TYPE,CMISS_FIELD_VALUES_SET_TYPE,1,1,1,2, &
  202. & 0.0_CMISSDP,Err)
  203. !node 2
  204. CALL CMISSField_ParameterSetUpdateNode(GeometricField,CMISS_FIELD_U_VARIABLE_TYPE,CMISS_FIELD_VALUES_SET_TYPE,1,1,2,1, &
  205. & 2.1_CMISSDP,Err)
  206. CALL CMISSField_ParameterSetUpdateNode(GeometricField,CMISS_FIELD_U_VARIABLE_TYPE,CMISS_FIELD_VALUES_SET_TYPE,1,1,2,2, &
  207. & 0.8_CMISSDP,Err)
  208. !node 3
  209. CALL CMISSField_ParameterSetUpdateNode(GeometricField,CMISS_FIELD_U_VARIABLE_TYPE,CMISS_FIELD_VALUES_SET_TYPE,1,1,3,1, &
  210. & 0.5_CMISSDP,Err)
  211. CALL CMISSField_ParameterSetUpdateNode(GeometricField,CMISS_FIELD_U_VARIABLE_TYPE,CMISS_FIELD_VALUES_SET_TYPE,1,1,3,2, &
  212. & 1.3_CMISSDP,Err)
  213. !node 4
  214. CALL CMISSField_ParameterSetUpdateNode(GeometricField,CMISS_FIELD_U_VARIABLE_TYPE,CMISS_FIELD_VALUES_SET_TYPE,1,1,4,1, &
  215. & 2.0_CMISSDP,Err)
  216. CALL CMISSField_ParameterSetUpdateNode(GeometricField,CMISS_FIELD_U_VARIABLE_TYPE,CMISS_FIELD_VALUES_SET_TYPE,1,1,4,2, &
  217. & 1.8_CMISSDP,Err)
  218. !Create a fibre field and attach it to the geometric field
  219. CALL CMISSField_Initialise(FibreField,Err)
  220. CALL CMISSField_CreateStart(FieldFibreUserNumber,Region,FibreField,Err)
  221. CALL CMISSField_TypeSet(FibreField,CMISS_FIELD_FIBRE_TYPE,Err)
  222. CALL CMISSField_MeshDecompositionSet(FibreField,Decomposition,Err)
  223. CALL CMISSField_GeometricFieldSet(FibreField,GeometricField,Err)
  224. CALL CMISSField_NumberOfVariablesSet(FibreField,FieldFibreNumberOfVariables,Err)
  225. CALL CMISSField_NumberOfComponentsSet(FibreField,CMISS_FIELD_U_VARIABLE_TYPE,FieldFibreNumberOfComponents,Err)
  226. CALL CMISSField_ComponentMeshComponentSet(FibreField,CMISS_FIELD_U_VARIABLE_TYPE,1,MeshComponentNumber,Err)
  227. CALL CMISSField_ComponentMeshComponentSet(FibreField,CMISS_FIELD_U_VARIABLE_TYPE,2,MeshComponentNumber,Err)
  228. CALL CMISSField_VariableLabelSet(FibreField,CMISS_FIELD_U_VARIABLE_TYPE,"Fibre",Err)
  229. CALL CMISSField_CreateFinish(FibreField,Err)
  230. !Create a material field and attach it to the geometric field
  231. CALL CMISSField_Initialise(MaterialField,Err)
  232. CALL CMISSField_CreateStart(FieldMaterialUserNumber,Region,MaterialField,Err)
  233. CALL CMISSField_TypeSet(MaterialField,CMISS_FIELD_MATERIAL_TYPE,Err)
  234. CALL CMISSField_MeshDecompositionSet(MaterialField,Decomposition,Err)
  235. CALL CMISSField_GeometricFieldSet(MaterialField,GeometricField,Err)
  236. CALL CMISSField_NumberOfVariablesSet(MaterialField,FieldMaterialNumberOfVariables,Err)
  237. CALL CMISSField_NumberOfComponentsSet(MaterialField,CMISS_FIELD_U_VARIABLE_TYPE,FieldMaterialNumberOfComponents,Err)
  238. CALL CMISSField_ComponentMeshComponentSet(MaterialField,CMISS_FIELD_U_VARIABLE_TYPE,1,MeshComponentNumber,Err)
  239. CALL CMISSField_ComponentMeshComponentSet(MaterialField,CMISS_FIELD_U_VARIABLE_TYPE,2,MeshComponentNumber,Err)
  240. CALL CMISSField_VariableLabelSet(MaterialField,CMISS_FIELD_U_VARIABLE_TYPE,"Material",Err)
  241. CALL CMISSField_CreateFinish(MaterialField,Err)
  242. !Set Mooney-Rivlin constants c10 and c01 to 2.0 and 3.0 respectively.
  243. CALL CMISSField_ComponentValuesInitialise(MaterialField,CMISS_FIELD_U_VARIABLE_TYPE,CMISS_FIELD_VALUES_SET_TYPE,1,2.0_CMISSDP,Err)
  244. CALL CMISSField_ComponentValuesInitialise(MaterialField,CMISS_FIELD_U_VARIABLE_TYPE,CMISS_FIELD_VALUES_SET_TYPE,2,3.0_CMISSDP,Err)
  245. !Create a dependent field
  246. CALL CMISSField_Initialise(DependentField,Err)
  247. CALL CMISSField_CreateStart(FieldDependentUserNumber,Region,DependentField,Err)
  248. CALL CMISSField_TypeSet(DependentField,CMISS_FIELD_GENERAL_TYPE,Err)
  249. CALL CMISSField_MeshDecompositionSet(DependentField,Decomposition,Err)
  250. CALL CMISSField_GeometricFieldSet(DependentField,GeometricField,Err)
  251. CALL CMISSField_DependentTypeSet(DependentField,CMISS_FIELD_DEPENDENT_TYPE,Err)
  252. CALL CMISSField_NumberOfVariablesSet(DependentField,FieldDependentNumberOfVariables,Err)
  253. CALL CMISSField_NumberOfComponentsSet(DependentField,CMISS_FIELD_U_VARIABLE_TYPE,FieldDependentNumberOfComponents,Err)
  254. CALL CMISSField_NumberOfComponentsSet(DependentField,CMISS_FIELD_DELUDELN_VARIABLE_TYPE,FieldDependentNumberOfComponents,Err)
  255. CALL CMISSField_ComponentMeshComponentSet(DependentField,CMISS_FIELD_U_VARIABLE_TYPE,1,MeshComponentNumber,Err)
  256. CALL CMISSField_ComponentMeshComponentSet(DependentField,CMISS_FIELD_U_VARIABLE_TYPE,2,MeshComponentNumber,Err)
  257. CALL CMISSField_ComponentMeshComponentSet(DependentField,CMISS_FIELD_DELUDELN_VARIABLE_TYPE,1,MeshComponentNumber,Err)
  258. CALL CMISSField_ComponentMeshComponentSet(DependentField,CMISS_FIELD_DELUDELN_VARIABLE_TYPE,2,MeshComponentNumber,Err)
  259. CALL CMISSField_VariableLabelSet(DependentField,CMISS_FIELD_U_VARIABLE_TYPE,"Dependent",Err)
  260. CALL CMISSField_CreateFinish(DependentField,Err)
  261. !Create the equations_set
  262. CALL CMISSField_Initialise(EquationsSetField,Err)
  263. CALL CMISSEquationsSet_CreateStart(EquationSetUserNumber,Region,FibreField,CMISS_EQUATIONS_SET_ELASTICITY_CLASS, &
  264. & CMISS_EQUATIONS_SET_FINITE_ELASTICITY_TYPE,CMISS_EQUATIONS_SET_MEMBRANE_SUBTYPE,EquationsSetFieldUserNumber, &
  265. & EquationsSetField, &
  266. & EquationsSet,Err)
  267. CALL CMISSEquationsSet_CreateFinish(EquationsSet,Err)
  268. CALL CMISSEquationsSet_DependentCreateStart(EquationsSet,FieldDependentUserNumber,DependentField,Err)
  269. CALL CMISSEquationsSet_DependentCreateFinish(EquationsSet,Err)
  270. CALL CMISSEquationsSet_MaterialsCreateStart(EquationsSet,FieldMaterialUserNumber,MaterialField,Err)
  271. CALL CMISSEquationsSet_MaterialsCreateFinish(EquationsSet,Err)
  272. !Create the equations set equations
  273. CALL CMISSEquations_Initialise(Equations,Err)
  274. CALL CMISSEquationsSet_EquationsCreateStart(EquationsSet,Equations,Err)
  275. CALL CMISSEquations_SparsityTypeSet(Equations,CMISS_EQUATIONS_SPARSE_MATRICES,Err)
  276. CALL CMISSEquations_OutputTypeSet(Equations,CMISS_EQUATIONS_NO_OUTPUT,Err)
  277. CALL CMISSEquationsSet_EquationsCreateFinish(EquationsSet,Err)
  278. !Initialise dependent field from undeformed geometry and displacement bcs
  279. CALL CMISSField_ParametersToFieldParametersComponentCopy(GeometricField,CMISS_FIELD_U_VARIABLE_TYPE,CMISS_FIELD_VALUES_SET_TYPE, &
  280. & 1,DependentField,CMISS_FIELD_U_VARIABLE_TYPE,CMISS_FIELD_VALUES_SET_TYPE,1,Err)
  281. CALL CMISSField_ParametersToFieldParametersComponentCopy(GeometricField,CMISS_FIELD_U_VARIABLE_TYPE,CMISS_FIELD_VALUES_SET_TYPE, &
  282. & 2,DependentField,CMISS_FIELD_U_VARIABLE_TYPE,CMISS_FIELD_VALUES_SET_TYPE,2,Err)
  283. !Define the problem
  284. CALL CMISSProblem_Initialise(Problem,Err)
  285. CALL CMISSProblem_CreateStart(ProblemUserNumber,Problem,Err)
  286. CALL CMISSProblem_SpecificationSet(Problem,CMISS_PROBLEM_ELASTICITY_CLASS,CMISS_PROBLEM_FINITE_ELASTICITY_TYPE, &
  287. & CMISS_PROBLEM_NO_SUBTYPE,Err)
  288. CALL CMISSProblem_CreateFinish(Problem,Err)
  289. !Create the problem control loop
  290. CALL CMISSProblem_ControlLoopCreateStart(Problem,Err)
  291. CALL CMISSProblem_ControlLoopCreateFinish(Problem,Err)
  292. !Create the problem solvers
  293. CALL CMISSSolver_Initialise(Solver,Err)
  294. CALL CMISSProblem_SolversCreateStart(Problem,Err)
  295. CALL CMISSProblem_SolverGet(Problem,CMISS_CONTROL_LOOP_NODE,1,Solver,Err)
  296. CALL CMISSSolver_OutputTypeSet(Solver,CMISS_SOLVER_PROGRESS_OUTPUT,Err)
  297. CALL CMISSSolver_NewtonJacobianCalculationTypeSet(Solver,CMISS_SOLVER_NEWTON_JACOBIAN_FD_CALCULATED,Err)
  298. CALL CMISSProblem_SolversCreateFinish(Problem,Err)
  299. !Create the problem solver equations
  300. CALL CMISSSolver_Initialise(Solver,Err)
  301. CALL CMISSSolverEquations_Initialise(SolverEquations,Err)
  302. CALL CMISSProblem_SolverEquationsCreateStart(Problem,Err)
  303. CALL CMISSProblem_SolverGet(Problem,CMISS_CONTROL_LOOP_NODE,1,Solver,Err)
  304. CALL CMISSSolver_SolverEquationsGet(Solver,SolverEquations,Err)
  305. CALL CMISSSolverEquations_SparsityTypeSet(SolverEquations,CMISS_SOLVER_SPARSE_MATRICES,Err)
  306. CALL CMISSSolverEquations_EquationsSetAdd(SolverEquations,EquationsSet,EquationsSetIndex,Err)
  307. CALL CMISSProblem_SolverEquationsCreateFinish(Problem,Err)
  308. !Prescribe boundary conditions (absolute nodal parameters)
  309. CALL CMISSBoundaryConditions_Initialise(BoundaryConditions,Err)
  310. CALL CMISSSolverEquations_BoundaryConditionsCreateStart(SolverEquations,BoundaryConditions,Err)
  311. CALL CMISSBoundaryConditions_SetNode(BoundaryConditions,DependentField,CMISS_FIELD_U_VARIABLE_TYPE,1,1,1,1, &
  312. & CMISS_BOUNDARY_CONDITION_FIXED, &
  313. & 0.4_CMISSDP,Err)
  314. CALL CMISSBoundaryConditions_SetNode(BoundaryConditions,DependentField,CMISS_FIELD_U_VARIABLE_TYPE,1,1,2,1, &
  315. & CMISS_BOUNDARY_CONDITION_FIXED, &
  316. & 2.3_CMISSDP,Err)
  317. CALL CMISSBoundaryConditions_SetNode(BoundaryConditions,DependentField,CMISS_FIELD_U_VARIABLE_TYPE,1,1,3,1, &
  318. & CMISS_BOUNDARY_CONDITION_FIXED, &
  319. & 0.5_CMISSDP,Err)
  320. CALL CMISSBoundaryConditions_SetNode(BoundaryConditions,DependentField,CMISS_FIELD_U_VARIABLE_TYPE,1,1,4,1, &
  321. & CMISS_BOUNDARY_CONDITION_FIXED, &
  322. & 2.1_CMISSDP,Err)
  323. CALL CMISSBoundaryConditions_SetNode(BoundaryConditions,DependentField,CMISS_FIELD_U_VARIABLE_TYPE,1,1,1,2, &
  324. & CMISS_BOUNDARY_CONDITION_FIXED, &
  325. & 0.0_CMISSDP,Err)
  326. CALL CMISSBoundaryConditions_SetNode(BoundaryConditions,DependentField,CMISS_FIELD_U_VARIABLE_TYPE,1,1,3,2, &
  327. & CMISS_BOUNDARY_CONDITION_FIXED, &
  328. & 1.3_CMISSDP,Err)
  329. CALL CMISSSolverEquations_BoundaryConditionsCreateFinish(SolverEquations,Err)
  330. !Solve problem
  331. CALL CMISSProblem_Solve(Problem,Err)
  332. !Output solution
  333. CALL CMISSFields_Initialise(Fields,Err)
  334. CALL CMISSFields_Create(Region,Fields,Err)
  335. CALL CMISSFields_NodesExport(Fields,"MembraneExtension2DSpace","FORTRAN",Err)
  336. CALL CMISSFields_ElementsExport(Fields,"MembraneExtension2DSpace","FORTRAN",Err)
  337. CALL CMISSFields_Finalise(Fields,Err)
  338. CALL CMISSFinalise(Err)
  339. WRITE(*,'(A)') "Program successfully completed."
  340. STOP
  341. END PROGRAM MEMBRANEEXTENSION2DSPACE