Book a Demo!
CoCalc Logo Icon
StoreFeaturesDocsShareSupportNewsAboutPoliciesSign UpSign In
ElmerCSC
GitHub Repository: ElmerCSC/elmerfem
Path: blob/devel/misc/netcdf/src/GridDataMapper/MapperUtils.f90
3206 views
1
!------------------------------------------------------------------------------
2
! Vili Forsell
3
! Created: 7.7.2011
4
! Last Modified: 13.7.2011
5
!------------------------------------------------------------------------------
6
! This module contains general functions for GridDataMapper
7
! - GetElmerNodeValue() ; Simplified access to Elmer Node's coordinates
8
! - GetElmerMinMax() ; Returns min, or max, value for given Elmer dimension
9
! - IntWidth() ; Returns the numeric width for an integer value
10
! o Mainly used for determining widths for format fields to avoid prefix spaces
11
! - ListGetStrings() ; Collects an array of strings from SIF defined with names suffixed by running numbers
12
! o Used to generalize string input
13
!------------------------------------------------------------------------------
14
MODULE MapperUtils
15
16
CONTAINS
17
18
!---------------- GetElmerNodeValue() ---------------
19
!--- Gets the value of the chosen node from the given dimension (1 = x, 2 = y, 3 = z)
20
FUNCTION GetElmerNodeValue( Solver, node, dimE ) RESULT( node_val )
21
!----------------------------------------------------
22
USE DefUtils, ONLY: Solver_t, dp
23
USE Messages, ONLY: Fatal
24
IMPLICIT NONE
25
26
TYPE(Solver_t), INTENT(IN) :: Solver
27
INTEGER, INTENT(IN) :: node, dimE
28
REAL(KIND=dp) :: node_val ! The output
29
SELECT CASE (dimE)
30
CASE (1)
31
node_val = Solver % Mesh % Nodes % x(node)
32
CASE (2)
33
node_val = Solver % Mesh % Nodes % y(node)
34
CASE (3)
35
node_val = Solver % Mesh % Nodes % z(node)
36
CASE DEFAULT
37
CALL Fatal('GridDataMapper','GetElmerNodeValue(): Elmer dimension not found')
38
node_val = 0
39
END SELECT
40
41
END FUNCTION GetElmerNodeValue
42
43
!---------------- GetElmerMinMax() ---------------
44
!--- Gets the minimum/maximum (chosen) value of the given dimension (1 = x, 2 = y, 3 = z)
45
FUNCTION GetElmerMinMax( Solver, dimE, GET_MIN ) RESULT( node_val )
46
!----------------------------------------------------
47
USE DefUtils, ONLY: Solver_t, CoordinateSystemDimension, dp
48
USE Messages, ONLY: Fatal
49
IMPLICIT NONE
50
51
TYPE(Solver_t), INTENT(IN) :: Solver
52
INTEGER, INTENT(IN) :: dimE
53
LOGICAL, INTENT(IN) :: GET_MIN
54
REAL(KIND=dp) :: node_val ! The output
55
56
SELECT CASE (dimE)
57
CASE (1)
58
IF ( GET_MIN ) THEN
59
node_val = MINVAL(Solver % Mesh % Nodes % x)
60
ELSE
61
node_val = MAXVAL(Solver % Mesh % Nodes % x)
62
END IF
63
CASE (2)
64
IF ( GET_MIN ) THEN
65
node_val = MINVAL(Solver % Mesh % Nodes % y)
66
ELSE
67
node_val = MAXVAL(Solver % Mesh % Nodes % y)
68
END IF
69
CASE (3)
70
IF ( GET_MIN ) THEN
71
node_val = MINVAL(Solver % Mesh % Nodes % z)
72
ELSE
73
node_val = MAXVAL(Solver % Mesh % Nodes % z)
74
END IF
75
CASE DEFAULT
76
CALL Fatal('GridDataMapper','GetAllElmerNodeValues(): Elmer dimension not found')
77
node_val = 0
78
END SELECT
79
80
END FUNCTION GetElmerMinMax
81
82
83
!----------------------- IntWidth() --------------
84
!--- Finds the width of an integer; ignores sign
85
FUNCTION IntWidth( NR ) RESULT( width )
86
!-------------------------------------------------
87
IMPLICIT NONE
88
INTEGER, INTENT(IN) :: NR
89
INTEGER :: val
90
INTEGER :: width
91
INTEGER :: comp
92
93
width = 1
94
comp = 10
95
val = ABS(NR) + 1 ! Ignores sign; val >= 1
96
97
! Note that:
98
! 10^0 - 1 = 0 <= 0..9 <= 10 = 10^1 - 1,
99
! 10^1 - 1 = 0 <= 10..99 <= 10 = 10^2 - 1,
100
! 10^2 - 1 = 0 <= 100..999 <= 10 = 10^3 - 1,
101
! and so forth,
102
! where 10 corresponds to width of the number with 10 based numbers (n == width).
103
! We get: 10^(n-1) <= NR + 1 <= 10^(n)
104
105
! Width usually small, so logarithmic search is not usually necessary.
106
107
! P: 10^0 = 1 <= val+1 .AND. width = 1 => For every j; 0 <= j <= i: 10^i <= val+1 .AND. i = 0 .AND. width = i + 1 = 0 + 1 = 1
108
DO WHILE (comp < val)
109
width = width + 1 ! width = i+1
110
comp = 10*comp ! 10*10^(i) = 10^(i+1)
111
! I: For every j; 0 <= j <= i: 10^j <= val+1 .AND. Exists n; i < n: val+1 <= 10^n .AND. width = i+1
112
END DO
113
! Q: (For every i; 0 <= i <= n-1: 10^i <= val+1) .AND. val+1 <= 10^n .AND. width = n
114
! => 10^(n-1) <= val+1 .AND. val+1 <= 10^n .AND. width = n
115
116
END FUNCTION IntWidth
117
118
!----------------- GetNetCDFAccessParameters() ------
119
!--- Gets all access strings and their associated accessing order
120
SUBROUTINE GetNetCDFAccessParameters( List,Variables,Constants,Permutation,Found )
121
!----------------------------------------------------
122
USE DefUtils
123
IMPLICIT NONE
124
125
!--- Arguments
126
TYPE(ValueList_t), INTENT(IN), POINTER :: List ! A pointer to a list of values
127
LOGICAL, OPTIONAL, INTENT(INOUT) :: Found(2) ! True, if found
128
CHARACTER(LEN=MAX_NAME_LEN), INTENT(OUT), ALLOCATABLE :: Variables(:),Constants(:) ! For returned array data
129
INTEGER, INTENT(OUT), ALLOCATABLE :: Permutation(:) ! NetCDF Access permutation; maps variables and constants to their proper locations
130
! Indexing order: Variables, then Constants
131
132
!--- Variables
133
TYPE(ValueList_t), POINTER :: ptr
134
CHARACTER(LEN=MAX_NAME_LEN) :: tmpStr
135
CHARACTER(LEN=MAX_NAME_LEN) :: Names(2) ! Names of the SIF variables
136
LOGICAL, ALLOCATABLE :: IsVariable(:) ! Valid until total_size
137
LOGICAL :: GotIt, PrevGotIt, OtherWasDefined
138
INTEGER :: TOTAL, var_i, const_i, const_size, coord_size
139
INTEGER :: loop, loop2, total_size, alloc_stat
140
CHARACTER(LEN=10) :: tmpFormat
141
142
!--- Initializations
143
NULLIFY(ptr)
144
IF ( PRESENT(Found) ) Found = .FALSE.
145
146
TOTAL = GetInteger(List,'NetCDF Max Parameters', GotIt)
147
IF ( .NOT. GotIt ) THEN
148
CALL Warn('GridDataMapper',&
149
'Please specify the maximum amount of NetCDF parameters with &
150
variable "NetCDF Max Parameters". Assumed to be 10 by default.')
151
TOTAL = 10 ! Default 10, affects efficiency and halting
152
ELSE IF ( TOTAL .LT. 1 ) THEN
153
CALL Warn('GridDataMapper','Minimum of one parameter expected for "NetCDF Max Parameters". It is now set to 1.')
154
TOTAL = 1
155
END IF
156
157
ALLOCATE ( IsVariable(TOTAL), STAT = alloc_stat )
158
IF ( alloc_stat .NE. 0 ) THEN
159
CALL Fatal('GridDataMapper','Memory ran out')
160
END IF
161
IsVariable = .FALSE. ! Defaulted to constant; even when over range
162
163
! The names of the SIF variables
164
Names(1) = 'Coordinate Name'
165
Names(2) = 'NetCDF Constant'
166
167
! Count the amount of defined strings for allocation
168
total_size = 0
169
coord_size = 0 ! Amount of existing coordinates/variables
170
const_size = 0 ! Amount of existing constants
171
PrevGotIt = .TRUE. ! If previous one was false, then the next one must not be true (otherwise omitted numbers)
172
OtherWasDefined = .FALSE. ! True if both names defined for the same location
173
DO loop = 1,TOTAL,1
174
OtherWasDefined = .FALSE. ! (NO DUPLICATES)
175
DO loop2 = 1,size(Names),1
176
! Find all Coordinates and Constants
177
178
!--- Checks for existence of the Name (EXISTS CHECK)
179
! Tries to ensure that the given integer doesn't have extra spaces before it in char format
180
! Scales until a number with a width of 9 (limited by tmpFormat)
181
WRITE(tmpFormat,'(A,I1,A)') '(A,A,I', IntWidth(loop),')'
182
WRITE(tmpStr,tmpFormat) TRIM(Names(loop2)),' ',loop
183
ptr => ListFind( List,tmpStr,GotIt ) ! NOTE: This will probably be a slow operation (linear/logarithmic)
184
185
!--- Checks for duplicates and updates the sizes
186
IF (GotIt) THEN
187
IF (.NOT. ASSOCIATED(ptr)) THEN
188
GotIt = .FALSE.
189
ELSE IF ( OtherWasDefined ) THEN
190
!--- The other Name was defined for the same index; conflict! (NO DUPLICATES)
191
WRITE(Message,'(A,I3)') 'Both a Coordinate Name and a NetCDF Constant &
192
were defined for NetCDF variable access location ', loop
193
CALL Fatal('GridDataMapper', Message)
194
ELSE
195
!--- Found and works (COORD_SIZE RIGHT, CONST_SIZE RIGHT, TOTAL_SIZE CORRECT)
196
! < Exists "Names 'loop2'" >
197
total_size = loop ! Chooses the largest that exists
198
IF ( loop2 .EQ. 1 ) THEN ! "Names" = "Coordinate Name"
199
coord_size = coord_size + 1
200
IsVariable(loop) = .TRUE. ! To find correct places later on
201
ELSE ! "Names" = "NetCDF Constant"
202
const_size = const_size + 1
203
! IsVariable defaulted to .FALSE.
204
END IF
205
! Postcondition has been updated for all until loop and loop2 (NO DUPLICATES)
206
OtherWasDefined = .TRUE.
207
END IF
208
END IF
209
210
!--- Checks that there are no gaps with the numbering (TOTAL_SIZE CORRECT)
211
IF ( GotIt .AND. (.NOT. PrevGotIt) ) THEN
212
WRITE(Message,'(A,I3,A)') 'NetCDF access parameter(s) before parameter ', loop ,' are missing'
213
CALL Fatal('GridDataMapper',Message)
214
END IF
215
END DO
216
217
!--- Both of the Names have been handled, so PrevGotIt can be updated for the next round (TOTAL_SIZE CORRECT)
218
! o If total_size < loop at the end(!) of loop, then there have been omissions; holds also for first round
219
! o Then, there must be no subsequent found parameters until the limit TOTAL; else there is a gap, which aborts immediately
220
! o NOTE: GotIt is not reliable enough for this check! F.ex. first name found, second not, would imply that nothing has been found.
221
IF ( total_size .EQ. loop ) THEN
222
PrevGotIt = .TRUE.
223
ELSE
224
PrevGotIt = .FALSE.
225
END IF
226
END DO
227
! Postcondition for the loops:
228
!< COORD_SIZE RIGHT: coord_size = |{ x | Exists "Coordinate Name 'x'" }| >
229
!< CONST_SIZE RIGHT: const_size = |{ x | Exists "NetCDF Constant 'x'" }| >
230
!< TOTAL_SIZE CORRECT: ( total_size = t .AND. (t = 0 .OR. (For Every i; 1 =< i <= t: Exists "Names 'i'")) .AND. ( .NOT. Exist i; t < i <= TOTAL: Exists "Names 'i'") >
231
!< NO DUPLICATES: ( .NOT. Exists i; 1 =< i <= TOTAL: Exists "NetCDF Constant 'i'" .AND. Exists "Coordinate name 'i'" ) >
232
233
IF ( total_size .LE. 0 ) RETURN ! No strings found
234
235
!--- Input checked and sizes counted; now allocation and data retrieval
236
237
! Allocation
238
ALLOCATE ( Variables(coord_size),Constants(const_size),Permutation(total_size), STAT = alloc_stat )
239
IF ( alloc_stat .NE. 0 ) THEN
240
CALL Fatal('GridDataMapper','Memory ran out')
241
END IF
242
Permutation = 0
243
244
! Getting the strings and the permutation data
245
var_i = 0
246
const_i = 0
247
DO loop = 1,total_size,1
248
!--- Pinpoint the correct type (correct until total_size)
249
IF ( IsVariable(loop) ) THEN
250
loop2 = 1 ! Variable/Coordinate
251
ELSE
252
loop2 = 2 ! Constant
253
END IF
254
255
WRITE(tmpFormat,'(A,I1,A)') '(A,A,I', IntWidth(loop) ,')'
256
WRITE(tmpStr,tmpFormat) TRIM(Names(loop2)),' ',loop
257
258
!--- Puts the data of the Names(loop2) in the right place
259
IF ( IsVariable(loop) ) THEN
260
var_i = var_i + 1
261
Variables(var_i) = GetString( List,tmpStr,GotIt )
262
Permutation(var_i) = loop
263
ELSE
264
const_i = const_i + 1
265
Constants(const_i) = GetString( List,tmpStr,GotIt )
266
Permutation(coord_size + const_i) = loop
267
END IF
268
269
IF ( .NOT. GotIt ) THEN
270
CALL Fatal('GridDataMapper','Obtained string did not exist after all')
271
END IF
272
END DO
273
!--- Permutation's contents:
274
! Range 1 <= i <= coord_size: variable i's location during the loop
275
! Range coord_size + 1 <= j <= total_size: constant j's location during the loop
276
! In other words, indexing Permutation gives the right NetCDF access location for the access parameter
277
278
IF ( coord_size .GT. 0 ) Found(1) = .TRUE.
279
IF ( const_size .GT. 0 ) Found(2) = .TRUE.
280
281
END SUBROUTINE GetNetCDFAccessParameters
282
283
!----------------- ListGetStrings() -----------------
284
!--- Gets all strings defined with prefix "Name" and ending with " NR", where NR is a number in an array
285
SUBROUTINE ListGetStrings( List,Name,Found,CValues )
286
!----------------------------------------------------
287
USE DefUtils
288
IMPLICIT NONE
289
290
!--- Arguments
291
TYPE(ValueList_t), INTENT(IN), POINTER :: List ! A pointer to a list of values
292
CHARACTER(LEN=*), INTENT(IN) :: Name ! Name of the SIF variable
293
LOGICAL, OPTIONAL, INTENT(INOUT) :: Found ! True, if found
294
CHARACTER(LEN=MAX_NAME_LEN), ALLOCATABLE :: CValues(:) ! For returned array data
295
296
!--- Variables
297
TYPE(ValueList_t), POINTER :: ptr
298
CHARACTER(LEN=MAX_NAME_LEN) :: tmpStr
299
LOGICAL :: GotIt
300
INTEGER :: loop, amount, alloc_stat
301
CHARACTER(LEN=10) :: tmpFormat
302
303
!--- Initializations
304
NULLIFY(ptr)
305
Found = .FALSE.
306
307
! Count the amount of defined strings for allocation
308
amount = 0
309
loop = 1
310
GotIt = .TRUE.
311
DO WHILE (GotIt)
312
! Tries to ensure that the given integer doesn't have extra spaces before it in char format
313
! Scales until a number with a width of 9 (limited by tmpFormat)
314
WRITE(tmpFormat,'(A,I1,A)') '(A,A,I', IntWidth(loop),')'
315
WRITE(tmpStr,tmpFormat) TRIM(Name),' ',loop
316
ptr => ListFind( List,tmpStr,GotIt )
317
318
! WRITE(*,*) 'TEMP: ', tmpStr
319
320
! Continues until first name is not found
321
IF (GotIt) THEN
322
IF (.NOT. ASSOCIATED(ptr)) THEN
323
GotIt = .FALSE.
324
RETURN
325
ELSE
326
amount = amount + 1
327
loop = loop + 1
328
END IF
329
END IF
330
END DO
331
332
IF ( amount .LE. 0 ) RETURN ! No strings found
333
334
! Allocation
335
ALLOCATE ( CValues(amount), STAT = alloc_stat )
336
IF ( alloc_stat .NE. 0 ) THEN
337
CALL Fatal('GridDataMapper','Memory ran out')
338
END IF
339
340
! Getting the strings
341
DO loop = 1,amount,1
342
WRITE(tmpFormat,'(A,I1,A)') '(A,A,I', IntWidth(loop) ,')'
343
WRITE(tmpStr,tmpFormat) TRIM(Name),' ',loop
344
CValues(loop) = GetString( List,tmpStr,GotIt )
345
IF (.NOT. GotIt) THEN
346
CALL Fatal('GridDataMapper','Obtained string did not exist after all')
347
END IF
348
END DO
349
350
Found = .TRUE.
351
352
END SUBROUTINE ListGetStrings
353
354
END MODULE MapperUtils
355
356