/ClassicalField/AdvectionDiffusion/StaticAdvectionDiffusion_FieldML/src/StaticAdvectionDiffusion_FieldMLExample.f90

http://github.com/xyan075/examples · Fortran Modern · 452 lines · 204 code · 72 blank · 176 comment · 4 complexity · a1bda3cef7be47c65b7c1c0e277858f7 MD5 · raw file

  1. !> \file
  2. !> \author Chris Bradley
  3. !> \brief This is an example program to solve a diffusion 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):
  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 ClassicalField/AdvectionDiffusion/StaticAdvectionDiffusion_FieldML/src/StaticAdvectionDiffusion_FieldMLExample.f90
  42. !! Example program to solve a diffusion equation using openCMISS calls.
  43. !!
  44. !! \htmlinclude ClassicalField/AdvectionDiffusion/StaticAdvectionDiffusion_FieldML/history.html
  45. !<
  46. !> Main program
  47. PROGRAM STATICADVECTIONDIFFUSIONEXAMPLE
  48. USE OPENCMISS
  49. USE FIELDML_API
  50. USE MPI
  51. #ifdef WIN32
  52. USE IFQWIN
  53. #endif
  54. IMPLICIT NONE
  55. !Test program parameters
  56. REAL(CMISSDP), PARAMETER :: HEIGHT=1.0_CMISSDP
  57. REAL(CMISSDP), PARAMETER :: WIDTH=2.0_CMISSDP
  58. REAL(CMISSDP), PARAMETER :: LENGTH=3.0_CMISSDP
  59. REAL(CMISSDP), POINTER :: GEOMETRIC_PARAMETERS(:)
  60. INTEGER(CMISSIntg), PARAMETER :: CoordinateSystemUserNumber=1
  61. INTEGER(CMISSIntg), PARAMETER :: RegionUserNumber=2
  62. INTEGER(CMISSIntg), PARAMETER :: BasisUserNumber=3
  63. INTEGER(CMISSIntg), PARAMETER :: GeneratedMeshUserNumber=4
  64. INTEGER(CMISSIntg), PARAMETER :: MeshUserNumber=5
  65. INTEGER(CMISSIntg), PARAMETER :: DecompositionUserNumber=6
  66. INTEGER(CMISSIntg), PARAMETER :: GeometricFieldUserNumber=7
  67. INTEGER(CMISSIntg), PARAMETER :: EquationsSetFieldUserNumber=8
  68. INTEGER(CMISSIntg), PARAMETER :: DependentFieldUserNumber=9
  69. INTEGER(CMISSIntg), PARAMETER :: MaterialsFieldUserNumber=10
  70. INTEGER(CMISSIntg), PARAMETER :: EquationsSetUserNumber=11
  71. INTEGER(CMISSIntg), PARAMETER :: ProblemUserNumber=12
  72. INTEGER(CMISSIntg), PARAMETER :: ControlLoopNode=0
  73. INTEGER(CMISSIntg), PARAMETER :: IndependentFieldUserNumber=13
  74. INTEGER(CMISSIntg), PARAMETER :: AnalyticFieldUserNumber=14
  75. INTEGER(CMISSIntg), PARAMETER :: SourceFieldUserNumber=15
  76. INTEGER(CMISSIntg), PARAMETER :: MeshComponentNumber=1
  77. !Program types
  78. !Program variables
  79. INTEGER(CMISSIntg) :: NUMBER_GLOBAL_X_ELEMENTS,NUMBER_GLOBAL_Y_ELEMENTS,NUMBER_GLOBAL_Z_ELEMENTS
  80. INTEGER(CMISSIntg) :: NUMBER_OF_DOMAINS
  81. INTEGER(CMISSIntg) :: MPI_IERROR
  82. !CMISS variables
  83. TYPE(CMISSBasisType) :: Basis
  84. TYPE(CMISSBoundaryConditionsType) :: BoundaryConditions
  85. TYPE(CMISSCoordinateSystemType) :: CoordinateSystem,WorldCoordinateSystem
  86. TYPE(CMISSDecompositionType) :: Decomposition
  87. TYPE(CMISSEquationsType) :: Equations
  88. TYPE(CMISSEquationsSetType) :: EquationsSet
  89. TYPE(CMISSFieldType) :: GeometricField,EquationsSetField,DependentField,MaterialsField,IndependentField,AnalyticField,SourceField
  90. TYPE(CMISSFieldsType) :: Fields
  91. TYPE(CMISSGeneratedMeshType) :: GeneratedMesh
  92. TYPE(CMISSMeshType) :: Mesh
  93. TYPE(CMISSProblemType) :: Problem
  94. TYPE(CMISSControlLoopType) :: ControlLoop
  95. TYPE(CMISSRegionType) :: Region,WorldRegion
  96. TYPE(CMISSSolverType) :: Solver, LinearSolver
  97. TYPE(CMISSSolverEquationsType) :: SolverEquations
  98. LOGICAL :: EXPORT_FIELD,IMPORT_FIELD
  99. #ifdef WIN32
  100. !Quickwin type
  101. LOGICAL :: QUICKWIN_STATUS=.FALSE.
  102. TYPE(WINDOWCONFIG) :: QUICKWIN_WINDOW_CONFIG
  103. #endif
  104. !Generic CMISS variables
  105. INTEGER(CMISSIntg) :: EquationsSetIndex
  106. INTEGER(CMISSIntg) :: FirstNodeNumber,LastNodeNumber
  107. INTEGER(CMISSIntg) :: Err
  108. INTEGER(CMISSIntg) :: dimensions, i
  109. !FieldML variables
  110. CHARACTER(KIND=C_CHAR,LEN=*), PARAMETER :: outputDirectory = ""
  111. CHARACTER(KIND=C_CHAR,LEN=*), PARAMETER :: outputFilename = "StaticAdvectionDiffusion.xml"
  112. CHARACTER(KIND=C_CHAR,LEN=*), PARAMETER :: basename = "static_advection_diffusion"
  113. CHARACTER(KIND=C_CHAR,LEN=*), PARAMETER :: dataFormat = "PLAIN_TEXT"
  114. TYPE(CMISSFieldMLIOType) :: fieldmlInfo
  115. #ifdef WIN32
  116. !Initialise QuickWin
  117. QUICKWIN_WINDOW_CONFIG%TITLE="General Output" !Window title
  118. QUICKWIN_WINDOW_CONFIG%NUMTEXTROWS=-1 !Max possible number of rows
  119. QUICKWIN_WINDOW_CONFIG%MODE=QWIN$SCROLLDOWN
  120. !Set the window parameters
  121. QUICKWIN_STATUS=SETWINDOWCONFIG(QUICKWIN_WINDOW_CONFIG)
  122. !If attempt fails set with system estimated values
  123. IF(.NOT.QUICKWIN_STATUS) QUICKWIN_STATUS=SETWINDOWCONFIG(QUICKWIN_WINDOW_CONFIG)
  124. #endif
  125. !Intialise OpenCMISS
  126. CALL CMISSInitialise(WorldCoordinateSystem,WorldRegion,Err)
  127. CALL CMISSErrorHandlingModeSet(CMISS_ERRORS_TRAP_ERROR,Err)
  128. NUMBER_GLOBAL_X_ELEMENTS=50
  129. NUMBER_GLOBAL_Y_ELEMENTS=100
  130. NUMBER_GLOBAL_Z_ELEMENTS=0
  131. NUMBER_OF_DOMAINS=1
  132. CALL MPI_BCAST(NUMBER_GLOBAL_X_ELEMENTS,1,MPI_INTEGER,0,MPI_COMM_WORLD,MPI_IERROR)
  133. CALL MPI_BCAST(NUMBER_GLOBAL_Y_ELEMENTS,1,MPI_INTEGER,0,MPI_COMM_WORLD,MPI_IERROR)
  134. CALL MPI_BCAST(NUMBER_GLOBAL_Z_ELEMENTS,1,MPI_INTEGER,0,MPI_COMM_WORLD,MPI_IERROR)
  135. CALL MPI_BCAST(NUMBER_OF_DOMAINS,1,MPI_INTEGER,0,MPI_COMM_WORLD,MPI_IERROR)
  136. IF( NUMBER_GLOBAL_Z_ELEMENTS == 0 ) THEN
  137. dimensions = 2
  138. ELSE
  139. dimensions = 3
  140. ENDIF
  141. !Start the creation of a new RC coordinate system
  142. CALL CMISSCoordinateSystem_Initialise(CoordinateSystem,Err)
  143. CALL CMISSCoordinateSystem_CreateStart(CoordinateSystemUserNumber,CoordinateSystem,Err)
  144. CALL CMISSCoordinateSystem_DimensionSet(CoordinateSystem,dimensions,Err)
  145. !Finish the creation of the coordinate system
  146. CALL CMISSCoordinateSystem_CreateFinish(CoordinateSystem,Err)
  147. !Start the creation of the region
  148. CALL CMISSRegion_Initialise(Region,Err)
  149. CALL CMISSRegion_CreateStart(RegionUserNumber,WorldRegion,Region,Err)
  150. !Set the regions coordinate system to the 2D RC coordinate system that we have created
  151. CALL CMISSRegion_CoordinateSystemSet(Region,CoordinateSystem,Err)
  152. !Finish the creation of the region
  153. CALL CMISSRegion_CreateFinish(Region,Err)
  154. !Start the creation of a basis (default is trilinear lagrange)
  155. CALL CMISSBasis_Initialise(Basis,Err)
  156. CALL CMISSBasis_CreateStart(BasisUserNumber,Basis,Err)
  157. CALL CMISSBasis_NumberOfXiSet(Basis,dimensions,Err)
  158. !Finish the creation of the basis
  159. CALL CMISSBasis_CreateFinish(BASIS,Err)
  160. !Start the creation of a generated mesh in the region
  161. CALL CMISSGeneratedMesh_Initialise(GeneratedMesh,Err)
  162. CALL CMISSGeneratedMesh_CreateStart(GeneratedMeshUserNumber,Region,GeneratedMesh,Err)
  163. !Set up a regular x*y*z mesh
  164. CALL CMISSGeneratedMesh_TypeSet(GeneratedMesh,CMISS_GENERATED_MESH_REGULAR_MESH_TYPE,Err)
  165. !Set the default basis
  166. CALL CMISSGeneratedMesh_BasisSet(GeneratedMesh,Basis,Err)
  167. !Define the mesh on the region
  168. IF(dimensions == 2) THEN
  169. CALL CMISSGeneratedMesh_ExtentSet(GeneratedMesh,(/WIDTH,HEIGHT/),Err)
  170. CALL CMISSGeneratedMesh_NumberOfElementsSet(GeneratedMesh,(/NUMBER_GLOBAL_X_ELEMENTS,NUMBER_GLOBAL_Y_ELEMENTS/),Err)
  171. ELSE
  172. CALL CMISSGeneratedMesh_ExtentSet(GeneratedMesh,(/WIDTH,HEIGHT,LENGTH/),Err)
  173. CALL CMISSGeneratedMesh_NumberOfElementsSet(GeneratedMesh,(/NUMBER_GLOBAL_X_ELEMENTS,NUMBER_GLOBAL_Y_ELEMENTS, &
  174. & NUMBER_GLOBAL_Z_ELEMENTS/),Err)
  175. ENDIF
  176. !Finish the creation of a generated mesh in the region
  177. CALL CMISSMesh_Initialise(Mesh,Err)
  178. CALL CMISSGeneratedMesh_CreateFinish(GeneratedMesh,MeshUserNumber,Mesh,Err)
  179. !Create a decomposition
  180. CALL CMISSDecomposition_Initialise(Decomposition,Err)
  181. CALL CMISSDecomposition_CreateStart(DecompositionUserNumber,Mesh,Decomposition,Err)
  182. !Set the decomposition to be a general decomposition with the specified number of domains
  183. CALL CMISSDecomposition_TypeSet(Decomposition,CMISS_DECOMPOSITION_CALCULATED_TYPE,Err)
  184. CALL CMISSDecomposition_NumberOfDomainsSet(Decomposition,NUMBER_OF_DOMAINS,Err)
  185. !Finish the decomposition
  186. CALL CMISSDecomposition_CreateFinish(Decomposition,Err)
  187. !Start to create a default (geometric) field on the region
  188. CALL CMISSField_Initialise(GeometricField,Err)
  189. CALL CMISSField_CreateStart(GeometricFieldUserNumber,Region,GeometricField,Err)
  190. !Set the decomposition to use
  191. CALL CMISSField_MeshDecompositionSet(GeometricField,Decomposition,Err)
  192. !Set the domain to be used by the field components.
  193. DO i = 1, dimensions
  194. CALL CMISSField_ComponentMeshComponentSet(GeometricField,CMISS_FIELD_U_VARIABLE_TYPE,i,MeshComponentNumber,Err)
  195. ENDDO
  196. !Finish creating the field
  197. CALL CMISSField_CreateFinish(GeometricField,Err)
  198. !Update the geometric field parameters
  199. CALL CMISSGeneratedMesh_GeometricParametersCalculate(GeneratedMesh,GeometricField,Err)
  200. !Create the equations_set
  201. CALL CMISSEquationsSet_Initialise(EquationsSet,Err)
  202. CALL CMISSField_Initialise(EquationsSetField,Err)
  203. CALL CMISSEquationsSet_CreateStart(EquationsSetUserNumber,Region,GeometricField,CMISS_EQUATIONS_SET_CLASSICAL_FIELD_CLASS, &
  204. & CMISS_EQUATIONS_SET_ADVECTION_DIFFUSION_EQUATION_TYPE,CMISS_EQUATIONS_SET_CONSTANT_SOURCE_STATIC_ADVEC_DIFF_SUBTYPE,&
  205. & EquationsSetFieldUserNumber,EquationsSetField,EquationsSet,Err)
  206. !Set the equations set to be a standard Laplace problem
  207. !Finish creating the equations set
  208. CALL CMISSEquationsSet_CreateFinish(EquationsSet,Err)
  209. !Create the equations set dependent field variables
  210. CALL CMISSField_Initialise(DependentField,Err)
  211. CALL CMISSEquationsSet_DependentCreateStart(EquationsSet,DependentFieldUserNumber,DependentField,Err)
  212. !Finish the equations set dependent field variables
  213. CALL CMISSEquationsSet_DependentCreateFinish(EquationsSet,Err)
  214. !Create the equations set material field variables
  215. CALL CMISSField_Initialise(MaterialsField,Err)
  216. CALL CMISSEquationsSet_MaterialsCreateStart(EquationsSet,MaterialsFieldUserNumber,MaterialsField,Err)
  217. !Finish the equations set dependent field variables
  218. CALL CMISSEquationsSet_MaterialsCreateFinish(EquationsSet,Err)
  219. !Create the equations set source field variables
  220. !For comparison withe analytical solution used here, the source field must be set to the following:
  221. !f(x,y) = 2.0*tanh(-0.1E1+Alpha*(TanPhi*x-y))*(1.0-pow(tanh(-0.1E1+Alpha*(TanPhi*x-y)),2.0))*Alpha*Alpha*TanPhi*TanPhi
  222. !+2.0*tanh(-0.1E1+Alpha*(TanPhi*x-y))*(1.0-pow(tanh(-0.1E1+Alpha*(TanPhi*x-y)),2.0))*Alpha*Alpha
  223. !-Peclet*(-sin(6.0*y)*(1.0-pow(tanh(-0.1E1+Alpha*(TanPhi*x-y)),2.0))*Alpha*TanPhi+cos(6.0*x)*(1.0-pow(tanh(-0.1E1+Alpha*(TanPhi*x-y)),2.0))*Alpha)
  224. CALL CMISSField_Initialise(SourceField,Err)
  225. CALL CMISSEquationsSet_SourceCreateStart(EquationsSet,SourceFieldUserNumber,SourceField,Err)
  226. CALL CMISSField_ComponentInterpolationSet(SourceField,CMISS_FIELD_U_VARIABLE_TYPE,1,CMISS_FIELD_NODE_BASED_INTERPOLATION,Err)
  227. !Finish the equations set dependent field variables
  228. CALL CMISSEquationsSet_SourceCreateFinish(EquationsSet,Err)
  229. CALL CMISSField_ParameterSetDataGet(GeometricField,CMISS_FIELD_U_VARIABLE_TYPE,CMISS_FIELD_VALUES_SET_TYPE,GEOMETRIC_PARAMETERS, &
  230. & Err)
  231. !Create the equations set independent field variables
  232. CALL CMISSField_Initialise(IndependentField,Err)
  233. CALL CMISSEquationsSet_IndependentCreateStart(EquationsSet,IndependentFieldUserNumber,IndependentField,Err)
  234. IF( dimensions == 2 ) THEN
  235. !For comparison withe analytical solution used here, the independent field must be set to the following:
  236. !w(x,y)=(sin 6y,cos 6x) FIELD_U_VARIABLE_TYPE,1,FIELD_NODE_BASED_INTERPOLATION
  237. ! CALL CMISSField_ComponentInterpolationSet(IndependentField,CMISS_FIELD_U_VARIABLE_TYPE,1,CMISS_FIELD_NODE_BASED_INTERPOLATION,Err)
  238. ! CALL CMISSField_ComponentInterpolationSet(IndependentField,CMISS_FIELD_U_VARIABLE_TYPE,2,CMISS_FIELD_NODE_BASED_INTERPOLATION,Err)
  239. !Loop over nodes to set the appropriate function value
  240. ! DO
  241. ! ENDDO
  242. ENDIF
  243. !Finish the equations set dependent field variables
  244. CALL CMISSEquationsSet_IndependentCreateFinish(EquationsSet,Err)
  245. !Create the equations set analytic field variables
  246. CALL CMISSField_Initialise(AnalyticField,Err)
  247. IF( dimensions == 2) THEN
  248. CALL CMISSEquationsSet_AnalyticCreateStart(EquationsSet,CMISS_EQUATIONS_SET_ADVECTION_DIFFUSION_EQUATION_TWO_DIM_1,&
  249. & AnalyticFieldUserNumber,AnalyticField,Err)
  250. ELSE
  251. WRITE(*,'(A)') "Three dimensions is not implemented."
  252. STOP
  253. ENDIF
  254. !Finish the equations set analytic field variables
  255. CALL CMISSEquationsSet_AnalyticCreateFinish(EquationsSet,Err)
  256. !Create the equations set equations
  257. CALL CMISSEquations_Initialise(Equations,Err)
  258. CALL CMISSEquationsSet_EquationsCreateStart(EquationsSet,Equations,Err)
  259. !Set the equations matrices sparsity type
  260. CALL CMISSEquations_SparsityTypeSet(Equations,CMISS_EQUATIONS_SPARSE_MATRICES,Err)
  261. !Set the equations set output
  262. !CALL CMISSEquations_OutputTypeSet(Equations,CMISS_EQUATIONS_NO_OUTPUT,Err)
  263. !CALL CMISSEquations_OutputTypeSet(Equations,CMISS_EQUATIONS_TIMING_OUTPUT,Err)
  264. !CALL CMISSEquations_OutputTypeSet(Equations,CMISS_EQUATIONS_MATRIX_OUTPUT,Err)
  265. !CALL CMISSEquations_OutputTypeSet(Equations,CMISS_EQUATIONS_ELEMENT_MATRIX_OUTPUT,Err)
  266. !Finish the equations set equations
  267. CALL CMISSEquationsSet_EquationsCreateFinish(EquationsSet,Err)
  268. ! !Create the equations set boundary conditions
  269. ! CALL CMISSBoundaryConditions_Initialise(BoundaryConditions,Err)
  270. ! CALL CMISSEquationsSetBoundaryConditionsCreateStart(EquationsSet,BoundaryConditions,Err)
  271. ! !Set the first node to 0.0 and the last node to 1.0
  272. ! FirstNodeNumber=1
  273. ! IF( dimensions == 2 ) THEN
  274. ! LastNodeNumber=(NUMBER_GLOBAL_X_ELEMENTS+1)*(NUMBER_GLOBAL_Y_ELEMENTS+1)
  275. ! ELSE
  276. ! LastNodeNumber=(NUMBER_GLOBAL_X_ELEMENTS+1)*(NUMBER_GLOBAL_Y_ELEMENTS+1)*(NUMBER_GLOBAL_Z_ELEMENTS+1)
  277. ! ENDIF
  278. ! CALL CMISSBoundaryConditions_SetNode(BoundaryConditions,CMISS_FIELD_U_VARIABLE_TYPE,1,FirstNodeNumber,1, &
  279. ! & CMISS_BOUNDARY_CONDITION_FIXED,0.0_CMISSDP,Err)
  280. ! CALL CMISSBoundaryConditions_SetNode(BoundaryConditions,CMISS_FIELD_DELUDELN_VARIABLE_TYPE,1,LastNodeNumber,1, &
  281. ! & CMISS_BOUNDARY_CONDITION_FIXED,1.0_CMISSDP,Err)
  282. ! !Finish the creation of the equations set boundary conditions
  283. ! CALL CMISSEquationsSetBoundaryConditionsCreateFinish(EquationsSet,Err)
  284. ! EXPORT_FIELD=.TRUE.
  285. ! IF(EXPORT_FIELD) THEN
  286. ! CALL CMISSFields_Initialise(Fields,Err)
  287. ! CALL CMISSFields_Create(Region,Fields,Err)
  288. ! CALL CMISSFields_NodesExport(Fields,"StaticAdvectionDiffusionInitial","FORTRAN",Err)
  289. ! CALL CMISSFields_ElementsExport(Fields,"StaticAdvectionDiffusionInitial","FORTRAN",Err)
  290. ! CALL CMISSFields_Finalise(Fields,Err)
  291. !
  292. ! ENDIF
  293. !Create the problem
  294. CALL CMISSProblem_Initialise(Problem,Err)
  295. CALL CMISSProblem_CreateStart(ProblemUserNumber,Problem,Err)
  296. !Set the problem to be a no source static advection Diffusion problem
  297. ! CALL CMISSProblem_SpecificationSet(Problem,CMISS_PROBLEM_CLASSICAL_FIELD_CLASS,CMISS_PROBLEM_ADVECTION_DIFFUSION_EQUATION_TYPE, &
  298. ! & CMISS_PROBLEM_NO_SOURCE_STATIC_ADVEC_DIFF_SUBTYPE,Err)
  299. CALL CMISSProblem_SpecificationSet(Problem,CMISS_PROBLEM_CLASSICAL_FIELD_CLASS,CMISS_PROBLEM_ADVECTION_DIFFUSION_EQUATION_TYPE, &
  300. & CMISS_PROBLEM_LINEAR_SOURCE_STATIC_ADVEC_DIFF_SUBTYPE,Err)
  301. !Finish the creation of a problem.
  302. CALL CMISSProblem_CreateFinish(Problem,Err)
  303. !Create the problem control
  304. CALL CMISSProblem_ControlLoopCreateStart(Problem,Err)
  305. !CALL CMISSControlLoop_Initialise(ControlLoop,Err)
  306. !Get the control loop
  307. !CALL CMISSProblem_ControlLoopGet(Problem,ControlLoopNode,ControlLoop,Err)
  308. !Set the times
  309. !CALL CMISSControlLoop_TimesSet(ControlLoop,0.0_CMISSDP,1.0_CMISSDP,0.1_CMISSDP,Err)
  310. !Finish creating the problem control loop
  311. CALL CMISSProblem_ControlLoopCreateFinish(Problem,Err)
  312. !Start the creation of the problem solvers
  313. !
  314. ! ! !For the Direct Solver MUMPS, uncomment the below two lines and comment out the above five
  315. ! ! CALL SOLVER_LINEAR_TYPE_SET(LINEAR_SOLVER,SOLVER_LINEAR_DIRECT_SOLVE_TYPE,ERR,ERROR,*999)
  316. ! ! CALL SOLVER_LINEAR_DIRECT_TYPE_SET(LINEAR_SOLVER,SOLVER_DIRECT_MUMPS,ERR,ERROR,*999)
  317. !
  318. CALL CMISSSolver_Initialise(Solver,Err)
  319. !CALL CMISSSolver_Initialise(LinearSolver,Err)
  320. CALL CMISSProblem_SolversCreateStart(Problem,Err)
  321. CALL CMISSProblem_SolverGet(Problem,CMISS_CONTROL_LOOP_NODE,1,Solver,Err)
  322. !CALL CMISSSolver_OutputTypeSet(Solver,CMISS_SOLVER_NO_OUTPUT,Err)
  323. !CALL CMISSSolver_OutputTypeSet(Solver,CMISS_SOLVER_PROGRESS_OUTPUT,Err)
  324. !CALL CMISSSolver_OutputTypeSet(Solver,CMISS_SOLVER_TIMING_OUTPUT,Err)
  325. !CALL CMISSSolver_OutputTypeSet(Solver,CMISS_SOLVER_SOLVER_OUTPUT,Err)
  326. CALL CMISSSolver_OutputTypeSet(Solver,CMISS_SOLVER_PROGRESS_OUTPUT,Err)
  327. !CALL CMISSSolver_DynamicLinearSolverGet(Solver,LinearSolver,Err)
  328. !CALL CMISSSolver_LinearIterativeMaximumIterationsSet(LinearSolver,300,Err)
  329. !Finish the creation of the problem solver
  330. CALL CMISSProblem_SolversCreateFinish(Problem,Err)
  331. !Create the problem solver equations
  332. CALL CMISSSolver_Initialise(Solver,Err)
  333. CALL CMISSSolverEquations_Initialise(SolverEquations,Err)
  334. CALL CMISSProblem_SolverEquationsCreateStart(Problem,Err)
  335. !Get the solve equations
  336. CALL CMISSProblem_SolverGet(Problem,CMISS_CONTROL_LOOP_NODE,1,Solver,Err)
  337. CALL CMISSSolver_SolverEquationsGet(Solver,SolverEquations,Err)
  338. !Set the solver equations sparsity
  339. CALL CMISSSolverEquations_SparsityTypeSet(SolverEquations,CMISS_SOLVER_SPARSE_MATRICES,Err)
  340. !CALL CMISSSolverEquations_SparsityTypeSet(SolverEquations,CMISS_SOLVER_FULL_MATRICES,Err)
  341. !Add in the equations set
  342. CALL CMISSSolverEquations_EquationsSetAdd(SolverEquations,EquationsSet,EquationsSetIndex,Err)
  343. !Finish the creation of the problem solver equations
  344. CALL CMISSProblem_SolverEquationsCreateFinish(Problem,Err)
  345. CALL CMISSBoundaryConditions_Initialise(BoundaryConditions,Err)
  346. CALL CMISSSolverEquations_BoundaryConditionsCreateStart(SolverEquations,BoundaryConditions,Err)
  347. CALL CMISSSolverEquations_BoundaryConditionsAnalytic(SolverEquations,Err)
  348. CALL CMISSSolverEquations_BoundaryConditionsCreateFinish(SolverEquations,Err)
  349. !Solve the problem
  350. CALL CMISSProblem_Solve(Problem,Err)
  351. !Output Analytic analysis
  352. Call CMISSAnalyticAnalysisOutput(DependentField,"StaticAdvectionDiffusionAnalytics",Err)
  353. EXPORT_FIELD=.TRUE.
  354. IF(EXPORT_FIELD) THEN
  355. !CALL CMISSFields_Initialise(Fields,Err)
  356. !CALL CMISSFields_Create(Region,Fields,Err)
  357. !CALL CMISSFields_NodesExport(Fields,"StaticAdvectionDiffusion","FORTRAN",Err)
  358. !CALL CMISSFields_ElementsExport(Fields,"StaticAdvectionDiffusion","FORTRAN",Err)
  359. !CALL CMISSFields_Finalise(Fields,Err)
  360. CALL CMISSFieldMLIO_Initialise( fieldmlInfo, err )
  361. CALL CMISSFieldML_OutputCreate( Mesh, outputDirectory, basename, dataFormat, fieldmlInfo, err )
  362. CALL CMISSFieldML_OutputAddField( fieldmlInfo, baseName//".geometric", dataFormat, GeometricField, &
  363. & CMISS_FIELD_U_VARIABLE_TYPE, CMISS_FIELD_VALUES_SET_TYPE, err )
  364. CALL CMISSFieldML_OutputAddField( fieldmlInfo, baseName//".dependent", dataFormat, DependentField, &
  365. & CMISS_FIELD_U_VARIABLE_TYPE, CMISS_FIELD_VALUES_SET_TYPE, err )
  366. CALL CMISSFieldML_OutputAddField( fieldmlInfo, baseName//".independent", dataFormat, IndependentField, &
  367. & CMISS_FIELD_U_VARIABLE_TYPE, CMISS_FIELD_VALUES_SET_TYPE, err )
  368. CALL CMISSFieldML_OutputAddField( fieldmlInfo, baseName//".source", dataFormat, SourceField, &
  369. & CMISS_FIELD_U_VARIABLE_TYPE, CMISS_FIELD_VALUES_SET_TYPE, err )
  370. CALL CMISSFieldML_OutputAddField( fieldmlInfo, baseName//".materials", dataFormat, MaterialsField, &
  371. & CMISS_FIELD_U_VARIABLE_TYPE, CMISS_FIELD_VALUES_SET_TYPE, err )
  372. !CALL FieldmlOutputAddField( fieldmlInfo, baseName//".analytic", dataFormat, region, mesh, AnalyticField, &
  373. ! & CMISS_FIELD_U_VARIABLE_TYPE, CMISS_FIELD_VALUES_SET_TYPE, err )
  374. CALL CMISSFieldML_OutputWrite( fieldmlInfo, outputFilename, err )
  375. CALL CMISSFieldMLIO_Finalise( fieldmlInfo, err )
  376. ENDIF
  377. !CALL CMISSFinalise(Err)
  378. WRITE(*,'(A)') "Program successfully completed."
  379. STOP
  380. END PROGRAM STATICADVECTIONDIFFUSIONEXAMPLE