OpenCMISS-Iron Internal API Documentation
cmiss.f90
Go to the documentation of this file.
1 
51 MODULE cmiss
52 
53  USE iso_c_binding
54 
55  USE base_routines
56  USE basis_routines
58  USE constants
60  USE generated_mesh_routines
62  USE kinds
64 #ifndef NOMPIMOD
65  USE mpi
66 #endif
67  USE problem_routines
68  USE region_routines
69  USE strings
70  USE types
71 
72 #include "macros.h"
73 
74  IMPLICIT NONE
75 
76  PRIVATE
77 
78 #ifdef NOMPIMOD
79 #include "mpif.h"
80 #endif
81 
82  !Module parameters
83 
84  INTEGER(INTG), PARAMETER :: cmfe_major_version = 0
85  INTEGER(INTG), PARAMETER :: cmfe_minor_version = 4
86  INTEGER(INTG), PARAMETER :: cmfe_revision_version = 0
87 
88  CHARACTER(LEN=MAXSTRLEN), PARAMETER :: cmfe_build_version = "$Rev"
89 
94  INTEGER(INTG), PARAMETER :: cmfe_return_error_code = 0
95  INTEGER(INTG), PARAMETER :: cmfe_output_error = 1
96  INTEGER(INTG), PARAMETER :: cmfe_trap_error = 2
98 
99  !Module types
100 
101  !Module variables
102 
103  INTEGER(INTG), SAVE :: cmfe_errorhandlingmode
104 
105  !Interfaces
106 
107  INTERFACE
108 
109  SUBROUTINE cmfe_initfatalhandler() BIND(C,NAME="cmfe_InitFatalHandler")
110  END SUBROUTINE cmfe_initfatalhandler
111 
112  SUBROUTINE cmfe_resetfatalhandler() BIND(C,NAME="cmfe_ResetFatalHandler")
113  END SUBROUTINE cmfe_resetfatalhandler
114 
115  SUBROUTINE cmfe_setfatalhandler() BIND(C,NAME="cmfe_SetFatalHandler")
116  END SUBROUTINE cmfe_setfatalhandler
117 
118  END INTERFACE
119 
121 
123 
125 
126  PUBLIC cmfe_handleerror
127 
129 
130 CONTAINS
131 
132  !
133  !================================================================================================================================
134  !
135 
136 !!TODO Underscore to avoid name clash. Can be removed upon prefix rename.
137 
139  SUBROUTINE cmfe_errorhandlingmodeget_(errorHandlingMode,err,error,*)
140 
141  !Argument variables
142  INTEGER(INTG), INTENT(OUT) :: errorHandlingMode
143  INTEGER(INTG), INTENT(INOUT) :: err
144  TYPE(varying_string), INTENT(INOUT) :: error
145  !Local Variables
146 
147  enters("cmfe_ErrorHandlingModeGet_",err,error,*999)
148 
149  errorhandlingmode=cmfe_errorhandlingmode
150 
151  exits("cmfe_ErrorHandlingModeGet_")
152  RETURN
153 999 errorsexits("",err,error)
154  RETURN 1
155 
156  END SUBROUTINE cmfe_errorhandlingmodeget_
157 
158  !
159  !================================================================================================================================
160  !
161 
162 !!TODO Underscore to avoid name clash. Can be removed upon prefix rename.
163 
165  SUBROUTINE cmfe_errorhandlingmodeset_(errorHandlingMode,err,error,*)
166 
167  !Argument variables
168  INTEGER(INTG), INTENT(IN) :: errorHandlingMode
169  INTEGER(INTG), INTENT(INOUT) :: err
170  TYPE(varying_string), INTENT(INOUT) :: error
171  !Local Variables
172  TYPE(varying_string) :: localError
173 
174  enters("cmfe_ErrorHandlingModeSet",err,error,*999)
175 
176  SELECT CASE(errorhandlingmode)
179  CASE(cmfe_output_error)
181  CASE(cmfe_trap_error)
183  CASE DEFAULT
184  localerror="The supplied error handling mode of "//trim(numbertovstring(errorhandlingmode,"*",err,error))// &
185  & " is invalid."
186  CALL flagerror(localerror,err,error,*999)
187  END SELECT
188 
189  exits("cmfe_ErrorHandlingModeSet_")
190  RETURN
191 999 errorsexits("cmfe_ErrorHandlingModeSet_",err,error)
192  RETURN 1
193 
194  END SUBROUTINE cmfe_errorhandlingmodeset_
195 
196  !
197  !================================================================================================================================
198  !
199 
200 !!TODO Underscore to avoid name clash. Can be removed upon prefix rename.
201 
203  SUBROUTINE cmfe_finalise_(err,error,*)
204 
205  !Argument variables
206  INTEGER(INTG), INTENT(INOUT) :: err
207  TYPE(varying_string), INTENT(INOUT) :: error
208  !Local Variables
209 
210  !Finalise the problems
211  CALL problems_finalise(err,error,*999)
212  !Finalise the regions
213  CALL regions_finalise(err,error,*999)
214  !Finalise the coordinate systems
215  CALL coordinate_systems_finalise(err,error,*999)
216  !Finalise bases
217  CALL bases_finalise(err,error,*999)
218  !Reset the signal handler
219  CALL cmfe_resetfatalhandler()
220  !Finalise computational enviroment
221  CALL computational_environment_finalise(err,error,*999)
222  !Finalise the base routines
223  CALL base_routines_finalise(err,error,*999)
224 
225  RETURN
226 999 RETURN 1
227 
228  END SUBROUTINE cmfe_finalise_
229 
230  !
231  !================================================================================================================================
232  !
233 
234 !!TODO Underscore to avoid name clash. Can be removed upon prefix rename.
235 
237  SUBROUTINE cmfe_initialise_(worldRegion,err,error,*)
238 
239  !Argument variables
240  TYPE(region_type), POINTER :: worldRegion
241  INTEGER(INTG), INTENT(INOUT) :: err
242  TYPE(varying_string), INTENT(INOUT) :: error
243  !Local Variables
244  TYPE(varying_string) :: versionString
245 
246  !Initialise error mode
247  cmfe_errorhandlingmode = cmfe_output_error !Default for now, maybe make CMFE_RETURN_ERROR_CODE the default
248  !Initialise the base routines
249  CALL base_routines_initialise(err,error,*999)
250  !Intialise the computational environment
251  CALL computational_environment_initialise(err,error,*999)
252  !Setup signal handling
253  CALL cmfe_initfatalhandler()
254  CALL cmfe_setfatalhandler()
255  IF(ASSOCIATED(worldregion)) THEN
256  CALL flagerror("World region is already associated.",err,error,*999)
257  ELSE
258  !Intialise the bases
259  CALL bases_initialise(err,error,*999)
260  !Initialise the coordinate systems
261  CALL coordinate_systems_initialise(err,error,*999)
262  !Initialise the regions
263  CALL regions_initialise(worldregion,err,error,*999)
264  !Initialise the problems
265  CALL problems_initialise(err,error,*999)
266 
267  !Write out the CMISS version
268  IF(computational_environment%MY_COMPUTATIONAL_NODE_NUMBER==0) THEN
269  versionstring="OpenCMISS(Iron) version "//trim(numbertovstring(cmfe_major_version,"*",err,error))
270  versionstring=versionstring//"."
271  versionstring=versionstring//trim(numbertovstring(cmfe_minor_version,"*",err,error))
272  versionstring=versionstring//"."
273  versionstring=versionstring//trim(numbertovstring(cmfe_revision_version,"*",err,error))
274  !versionString=versionString//" ("
275  !versionString=versionString//TRIM(CMFE_BUILD_VERSION(6:))
276  !versionString=versionString//" )"
277 
278  !WRITE(*,'(A)') CHAR(versionString)
279 
280  ENDIF
281  ENDIF
282 
283  RETURN
284 999 RETURN 1
285 
286  END SUBROUTINE cmfe_initialise_
287 
288  !
289  !================================================================================================================================
290  !
291 
293  SUBROUTINE cmfe_handleerror(err,error)
294 
295  !Argument variables
296  INTEGER(INTG), INTENT(INOUT) :: err
297  TYPE(varying_string), INTENT(INOUT) :: error
298  !Local Variables
299  INTEGER(INTG) :: mpiError
300 
301  SELECT CASE(cmfe_errorhandlingmode)
303  !Do nothing
304  CASE(cmfe_output_error)
305  CALL writeerror(err,error,*999)
306  CASE(cmfe_trap_error)
307  CALL writeerror(err,error,*999)
308  CALL mpi_abort(mpi_comm_world,err,mpierror)
309  stop
310  CASE DEFAULT
311  !Do nothing
312  END SELECT
313 
314  RETURN
315 999 RETURN
316 
317  END SUBROUTINE cmfe_handleerror
318 
319  !
320  !================================================================================================================================
321  !
322 
323 END MODULE cmiss
This module contains all basis function routines.
subroutine, public enters(NAME, ERR, ERROR,)
Records the entry into the named procedure and initialises the error code.
This module contains all coordinate transformation and support routines.
Contains information for a region.
Definition: types.f90:3252
This module contains all region routines.
subroutine, public computational_environment_finalise(ERR, ERROR,)
Finalises the computational environment data structures and deallocates all memory.
subroutine, public coordinate_systems_initialise(ERR, ERROR,)
Initialises the coordinate systems and creates the world coordinate system.
This module contains all string manipulation and transformation routines.
Definition: strings.f90:45
integer(intg), parameter, public cmfe_trap_error
Trap the error by outputing the error traceback and stopping the program.
Definition: cmiss.f90:96
character(len=maxstrlen), parameter, public cmfe_build_version
Definition: cmiss.f90:88
subroutine, public cmfe_errorhandlingmodeset_(errorHandlingMode, err, error,)
Sets the error handling mode for cmiss.
Definition: cmiss.f90:166
This module provides an iso_varying_string module, conformant to the API specified in ISO/IEC 1539-2:...
integer(intg), parameter, public cmfe_output_error
Output the error traceback and return the error code.
Definition: cmiss.f90:95
This module contains all program wide constants.
Definition: constants.f90:45
subroutine, public bases_initialise(ERR, ERROR,)
Initialises the bases.
integer(intg), parameter, public cmfe_return_error_code
Just return the error code.
Definition: cmiss.f90:94
integer(intg), parameter, public cmfe_minor_version
Definition: cmiss.f90:85
subroutine, public cmfe_initialise_(worldRegion, err, error,)
Initialises CMISS.
Definition: cmiss.f90:238
integer(intg), save cmfe_errorhandlingmode
The current error handling mode for OpenCMISS.
Definition: cmiss.f90:103
subroutine, public cmfe_errorhandlingmodeget_(errorHandlingMode, err, error,)
Returns the error handling mode for CMISS.
Definition: cmiss.f90:140
subroutine, public exits(NAME)
Records the exit out of the named procedure.
This module contains all type definitions in order to avoid cyclic module references.
Definition: types.f90:70
integer(intg), parameter, public cmfe_major_version
Definition: cmiss.f90:84
This module contains all the low-level base routines e.g., all debug, control, and low-level communic...
subroutine, public base_routines_finalise(ERR, ERROR,)
Finalises the base_routines module and deallocates all memory.
This module contains all computational environment variables.
type(computational_environment_type), target, public computational_environment
The computational environment the program is running in.
subroutine, public computational_environment_initialise(ERR, ERROR,)
Initialises the computational environment data structures.
Definition: cmiss.f90:51
subroutine, public writeerror(err, error,)
Writes the error string.
subroutine, public base_routines_initialise(ERR, ERROR,)
Initialises the variables required for the base_routines module.
subroutine, public cmfe_handleerror(err, error)
Handle an error condition.
Definition: cmiss.f90:294
subroutine, public regions_finalise(ERR, ERROR,)
Finalises the regions and destroys any current regions.
subroutine, public regions_initialise(WORLD_REGION, ERR, ERROR,)
Initialises the regions and creates the global world region.
integer(intg), parameter, public cmfe_revision_version
Definition: cmiss.f90:86
subroutine, public cmfe_finalise_(err, error,)
Finalises CMISS.
Definition: cmiss.f90:204
This module contains all machine dependent constants for AIX systems.
Flags an error condition.
subroutine, public coordinate_systems_finalise(ERR, ERROR,)
Finalises the coordinate systems and destroys all coordinate systems.
subroutine, public bases_finalise(ERR, ERROR,)
Finalises the bases and deallocates all memory.
This module contains all kind definitions.
Definition: kinds.f90:45