Book a Demo!
CoCalc Logo Icon
StoreFeaturesDocsShareSupportNewsAboutPoliciesSign UpSign In
ElmerCSC
GitHub Repository: ElmerCSC/elmerfem
Path: blob/devel/misc/netcdf/src/GridDataMapper/GridDataMapper.f90
3206 views
1
!------------------------------------------------------------------------------
2
! Peter RÃ¥back, Vili Forsell
3
! Created: 7.6.2011
4
! Last Modified: 4.8.2011
5
!------------------------------------------------------------------------------
6
SUBROUTINE GridDataMapper( Model,Solver,dt,TransientSimulation )
7
!------------------------------------------------------------------------------
8
!******************************************************************************
9
!
10
! This subroutine saves scalar values to a matrix.
11
!
12
! ARGUMENTS:
13
!
14
! TYPE(Model_t) :: Model,
15
! INPUT: All model information (mesh, materials, BCs, etc...)
16
!
17
! TYPE(Solver_t) :: Solver
18
! INPUT: Linear & nonlinear equation solver options
19
!
20
! REAL(KIND=dp) :: dt,
21
! INPUT: Timestep size for time dependent simulations
22
!
23
! LOGICAL :: TransientSimulation
24
! INPUT: Steady state or transient simulation
25
!
26
!******************************************************************************
27
28
!******************************************************************************
29
! Notes: o Performs a modification from measurements with uniform grid into Elmer with an unstructured grid
30
! o Remember to see if incremental processing might be possible
31
! o Some terminology: "nodes" and "edges" used for grid points and the lines connecting the for grid points and the lines connecting them
32
!******************************************************************************
33
34
USE DefUtils, ONLY: dp, Solver_t, Model_t, Mesh_t,GetInteger, CoordinateSystemDimension, GetSolverParams, &
35
GetLogical, MAX_NAME_LEN, GetCReal
36
USE Messages, ONLY: Info, Warn, Fatal, Message
37
USE NetCDF
38
USE NetCDFGridUtils, ONLY: UniformGrid_t, PrintGrid
39
USE NetCDFInterpolate, ONLY: Interpolate, LinearInterpolation
40
USE NetCDFGeneralUtils, ONLY: CloseNetCDF, TimeType_t
41
USE MapperUtils, ONLY: GetElmerMinMax, GetElmerNodeValue
42
USE CustomTimeInterpolation, ONLY: ChooseTimeInterpolation
43
44
IMPLICIT NONE
45
46
!------------------------------------------------------------------------------
47
LOGICAL, PARAMETER :: DEBUG = .FALSE. ! Shows the basic debug info on grids and dimensions
48
LOGICAL, PARAMETER :: DEBUG_MORE = .FALSE. ! Shows also debug printouts for each iteration
49
!------------------------------------------------------------------------------
50
TYPE(Solver_t), TARGET :: Solver
51
TYPE(Model_t) :: Model
52
REAL(KIND=dp) :: dt
53
LOGICAL :: TransientSimulation
54
!------------------------------------------------------------------------------
55
! Local variables
56
!------------------------------------------------------------------------------
57
58
TYPE(Mesh_t), POINTER :: Mesh
59
TYPE(TimeType_t) :: Time
60
TYPE(UniformGrid_t) :: Grids(2)
61
INTEGER :: k, node, DIM, MAX_STEPS
62
INTEGER, POINTER :: FieldPerm(:)
63
REAL(KIND=dp), POINTER :: Field(:)
64
REAL(KIND=dp), ALLOCATABLE :: x(:)
65
REAL(KIND=dp) :: interp_val, interp_val2, u1(2), u2(2)
66
INTEGER, ALLOCATABLE :: dim_lens(:) ! Lengths for all dimensions
67
INTEGER :: NCID, loop, Var_ID, alloc_stat
68
CHARACTER (len = MAX_NAME_LEN) :: Coord_System, TimeInterpolationMethod
69
REAL(KIND=dp) :: InterpMultiplier, InterpBias
70
LOGICAL :: output_on
71
72
!------------------------------------------------------------------------------
73
! General initializations
74
!------------------------------------------------------------------------------
75
76
CALL Info('GridDataMapper','-----------------------------------------', Level=4 )
77
CALL Info('GridDataMapper','Getting field from grid data',Level=4)
78
79
Time % val = -1.0_dp
80
Time % id = -1
81
Time % len = -1
82
Time % low = -1
83
Time % high = -1
84
Time % doInterpolation = .FALSE.
85
Time % is_defined = .FALSE.
86
87
! WRITE (*,*) 'val ', Time % val, ' id ', Time % id, ' len ', Time % len,&
88
! ' low ', Time % low, ' high ', Time % high, ' interp ', Time % doInterpolation
89
90
IF ( TransientSimulation ) THEN
91
MAX_STEPS = GetInteger( Model % Simulation, 'TimeStep Intervals' )
92
ELSE
93
MAX_STEPS = 1 ! Steady state
94
END IF
95
96
!-- Pointer declarations
97
Mesh => Solver % Mesh
98
Field => Solver % Variable % Values ! This vector will get the field values now
99
FieldPerm => Solver % Variable % Perm
100
101
!------------------------------------------------------------------------------
102
! Initializing NetCDF values
103
!------------------------------------------------------------------------------
104
CALL InitNetCDF(Solver, NCID, Var_ID, dim_lens, Grids, Time, TransientSimulation, dt, MAX_STEPS, Coord_System)
105
DIM = Grids(1) % COORD_COUNT ! Abbreviation [# of Elmer coordinates .EQ. # of NetCDF coordinates]
106
107
!------------------------------------------------------------------------------
108
! Initializing Elmer mesh vectors, scaling and interpolation
109
!------------------------------------------------------------------------------
110
IF ( DIM .GT. 0 ) THEN
111
ALLOCATE ( x(DIM), STAT = alloc_stat )
112
IF ( alloc_stat .NE. 0 ) THEN
113
CALL Fatal('GridDataMapper','Memory ran out')
114
END IF
115
116
!--- Scales the Grids, if applicable
117
CALL InitScaling(Solver, Grids)
118
END IF
119
120
!------ Debug printouts -------------------------
121
IF (DEBUG) THEN
122
IF ( DIM .GT. 0 ) THEN
123
PRINT *,'Initial Elmer Grid Bounding Box:'
124
DO loop = 1,DIM,1
125
PRINT *,'Coordinate ', loop,':', GetElmerMinMax(Solver,loop,.TRUE.), GetElmerMinMax(Solver,loop,.FALSE.)
126
END DO
127
END IF
128
129
DO loop = 1,size(Grids,1),1
130
CALL PrintGrid(Grids(loop),loop)
131
END DO
132
END IF
133
!------------------------------------------------
134
135
!--- Initializes the interpolation variables
136
CALL InitInterpolation( Solver, DIM, Grids, TimeInterpolationMethod, InterpMultiplier, InterpBias )
137
138
!------------------------------------------------------------------------------
139
! INTERPOLATION LOOP
140
!------------------------------------------------------------------------------
141
! NOTE: Interpolate() effectively ignores time, if "Time % is_defined" is .FALSE.
142
!------------------------------------------------------------------------------
143
144
output_on = .TRUE. ! If true, outputs some iteration information
145
! Go through the active nodes and perform interpolation
146
DO node=1, Mesh % NumberOfNodes
147
k = FieldPerm(node)
148
IF( k == 0 ) CYCLE
149
150
IF ( DIM .GT. 0 ) THEN
151
152
! The point of interest
153
DO loop = 1,DIM,1
154
x(loop) = GetElmerNodeValue(Solver,node,Grids(1) % Elmer_perm(loop))
155
END DO
156
157
!--- Perform time interpolation, if needed
158
IF ( Time % doInterpolation ) THEN ! Two time values (otherwise not interpolated)
159
IF ( .NOT. (Interpolate(Solver,NCID,Var_ID,dim_lens,Grids(1),&
160
Time, Time % low,interp_val,Coord_System,x) .AND. Interpolate(Solver,NCID,&
161
Var_ID,dim_lens,Grids(2),Time,Time % high,interp_val2,Coord_System,x)) ) THEN
162
CYCLE
163
ELSE
164
! Time interpolation on already interpolated space values; save result in interp_val, use original time to weigh
165
u1(1) = Time % low
166
u1(2) = interp_val
167
u2(1) = Time % high
168
u2(2) = interp_val2
169
interp_val = ChooseTimeInterpolation(Time % val,u1,u2,TimeInterpolationMethod,output_on) ! Chooses the time interpolation method
170
! See: CustomTimeInterpolation.f90
171
output_on = .FALSE.
172
END IF
173
ELSE ! Holds: Time % low = Time % high = Time % val, also: Time % IS_DEFINED = .FALSE. works!
174
IF (.NOT. Interpolate(Solver,NCID,Var_ID,dim_lens,Grids(1),&
175
Time,Time % low,interp_val,Coord_System,x) ) THEN
176
CYCLE ! Ignore values for incompatible interpolation
177
END IF
178
END IF
179
ELSE
180
181
!------------------------------------------------------------------------------
182
! No coordinate dimensions; only time and constant dimensions.
183
!------------------------------------------------------------------------------
184
IF ( Time % doInterpolation ) THEN
185
!--- Time interpolation in effect, perform as before
186
IF (.NOT. (Interpolate(Solver,NCID,Var_ID,dim_lens,Grids(1),&
187
Time,Time % low,interp_val,Coord_System) .AND. &
188
Interpolate(Solver,NCID,Var_ID,dim_lens,Grids(2),&
189
Time,Time % high,interp_val2,Coord_System)) ) THEN
190
CYCLE
191
ELSE
192
u1(1) = Time % low
193
u1(2) = interp_val
194
u2(1) = Time % high
195
u2(2) = interp_val2
196
interp_val = ChooseTimeInterpolation(Time % val,u1,u2,TimeInterpolationMethod,output_on)
197
! See: CustomTimeInterpolation.f90
198
output_on = .FALSE.
199
END IF
200
ELSE
201
!--- No time interpolation
202
IF (.NOT. Interpolate(Solver,NCID,Var_ID,dim_lens,Grids(1),&
203
Time,Time % low,interp_val,Coord_System) ) THEN
204
CYCLE
205
END IF
206
END IF
207
208
END IF
209
210
!------ Debug printouts -------------------------
211
IF (DEBUG_MORE) THEN
212
PRINT *,'Interpolation result: ', interp_val
213
END IF
214
!------------------------------------------------
215
216
Field(k) = InterpMultiplier*interp_val + InterpBias ! Doesn't modify the result by default
217
END DO
218
219
!------------------------------------------------------------------------------
220
! Close the NetCDF file
221
!------------------------------------------------------------------------------
222
CALL CloseNetCDF(NCID)
223
224
!------------------------------------------------------------------------------
225
226
CALL Info('GridDataMapper','All done',Level=4)
227
CALL Info('GridDataMapper', '-----------------------------------------', Level=4 )
228
229
CONTAINS
230
231
!----------------- InitScaling() --------------------
232
!--- Adds scaling to NetCDF Grids (by default does nothing)
233
SUBROUTINE InitScaling(Solver, Grids)
234
!----------------------------------------------------
235
USE DefUtils, ONLY: Solver_t
236
USE NetCDFGridUtils, ONLY: UniformGrid_t
237
USE MapperUtils, ONLY: GetElmerMinMax
238
IMPLICIT NONE
239
240
!------------------------------------------------------------------------------
241
! ARGUMENTS
242
!------------------------------------------------------------------------------
243
TYPE(Solver_t), INTENT(IN) :: Solver
244
TYPE(UniformGrid_t), INTENT(INOUT) :: Grids(:)
245
246
!------------------------------------------------------------------------------
247
! VARIABLES
248
!------------------------------------------------------------------------------
249
LOGICAL :: Found, ENABLE_SCALING
250
INTEGER :: DIM, alloc_stat
251
REAL(KIND=dp), ALLOCATABLE :: x0e(:), x1e(:)
252
253
!------------------------------------------------------------------------------
254
! Adds scaling, if it's set on and possible
255
!------------------------------------------------------------------------------
256
257
ENABLE_SCALING = GetLogical(GetSolverParams(Solver), "Enable Scaling", Found)
258
DIM = Grids(1) % COORD_COUNT
259
260
IF ( Found .AND. ENABLE_SCALING .AND. DIM .GT. 0 ) THEN
261
262
CALL Warn('GridDataMapper','Elmer grid is scaled to match the NetCDF grid')
263
264
ALLOCATE (x0e(DIM),x1e(DIM), STAT=alloc_stat)
265
IF ( alloc_stat .NE. 0 ) THEN
266
CALL Fatal('GridDataMapper','Memory ran out')
267
END IF
268
269
!--- Collects the range of the Elmer mesh bounding box for scaling
270
DO loop = 1,DIM,1
271
x0e(loop) = GetElmerMinMax(Solver,loop,.TRUE.)
272
x1e(loop) = GetElmerMinMax(Solver,loop,.FALSE.)
273
END DO
274
275
!--- Scales
276
DO loop = 1,size(Grids,1),1
277
! First the scaling to same size (Eq. a( X1E(1)-X0E(1) ) = (X1(1)-X0(1)) ; ranges over a dimension are same. Solved for a, 1 if equal)
278
Grids(loop) % scale(:) = (Grids(loop) % X1(1:DIM) - Grids(loop) % X0(1:DIM))/(X1E(1:DIM)-X0E(1:DIM)) ! Note: "/" and "*" elementwise operations for arrays in Fortran
279
! Second the vector to reach X0 from the scaled X0E (wherever it is)
280
Grids(loop) % move(:) = Grids(loop) % X0(1:DIM) - Grids(loop) % scale(:)*X0E(1:DIM) ! zero, if equal
281
END DO
282
END IF
283
!------------------------------------------------------------------------------
284
285
END SUBROUTINE InitScaling
286
287
!----------------- InitNetCDF() ---------------------
288
!--- Gathers and initializes all the necessary NetCDF information for picking variables
289
SUBROUTINE InitNetCDF(Solver, NCID, Var_ID, dim_lens, Grids, Time,&
290
IS_TRANSIENT, STEP_SIZE, MAX_STEPS, Coord_System )
291
!--------------------------------------------------
292
293
USE NetCDFGridUtils, ONLY: PrintGrid, InitGrid, GetNetCDFGridParameters, Focus2DNetCDFGrid
294
USE NetCDFGeneralUtils, ONLY: GetAllDimensions, G_Error, TimeValueToIndex
295
USE MapperUtils, ONLY: IntWidth, GetNetCDFAccessParameters
296
USE NetCDF
297
USE DefUtils, ONLY: dp, MAX_NAME_LEN, GetSolverParams, GetString, GetConstReal, ListGetString
298
USE Messages, ONLY: Fatal, Message
299
IMPLICIT NONE
300
301
!------------------------------------------------------------------------------
302
! ARGUMENTS
303
!------------------------------------------------------------------------------
304
TYPE(Solver_t), INTENT(IN) :: Solver ! Elmer solver from SIF
305
TYPE(TimeType_t), INTENT(INOUT) :: Time ! Time information
306
TYPE(UniformGrid_t), INTENT(INOUT) :: Grids(:) ! NetCDF grids
307
LOGICAL, INTENT(IN) :: IS_TRANSIENT ! For using Elmer time instead of a variable
308
REAL(KIND=dp), INTENT(IN) :: STEP_SIZE ! Time step for Elmer transient system
309
INTEGER, INTENT(IN) :: MAX_STEPS ! Max steps in Elmer transient system
310
INTEGER, INTENT(OUT) :: NCID, Var_ID ! NCID is the ID of the opened file, Var_ID the accessed variable id
311
INTEGER, INTENT(INOUT), ALLOCATABLE :: dim_lens(:) ! Lengths for all dimensions
312
CHARACTER (len = MAX_NAME_LEN), INTENT(OUT) :: Coord_System ! Coordinate system string
313
314
!------------------------------------------------------------------------------
315
! NetCDF VARIABLES
316
!------------------------------------------------------------------------------
317
318
INTEGER :: DIM ! Used Elmer dimensions for data accessing
319
INTEGER, ALLOCATABLE :: dim_ids(:) ! Ids for all dimensions
320
LOGICAL :: Found(7) ! True if SIF definitions found
321
CHARACTER (len = MAX_NAME_LEN) :: FileName ! File name for reading the data (of .nc format)
322
CHARACTER (len = MAX_NAME_LEN) :: Var_Name, T_Name, Mask_Name
323
CHARACTER (len = MAX_NAME_LEN), ALLOCATABLE :: Dim_Names(:) ! Contains the opened NetCDF dimension variables
324
REAL(KIND=dp) :: Mask_Limit ! Value limit where masking starts to take effect
325
INTEGER :: loop, alloc_stat,dim_count,status ! Status tells whether operations succeed
326
INTEGER :: size_coord, size_const ! Temps for amounts of NetCDF coordinate and constant dimensions
327
LOGICAL :: tmpBool ,IsTimeDependent ! True, if time is used when accessing NetCDF
328
CHARACTER (len = MAX_NAME_LEN), ALLOCATABLE :: Coords(:), Constants(:) ! Contains the names for NetCDF coordinate and constant dimensions
329
INTEGER, ALLOCATABLE :: Permutation(:) ! Contains the NetCDF Access permutation for Coords and Constants
330
CHARACTER (len = 10) :: tmpFormat
331
332
!------------------------------------------------------------------------------
333
! NetCDF INITIALIZATIONS
334
!------------------------------------------------------------------------------
335
336
!-------------------------------------------------------------------------------
337
! 1) Gathers basic data from SIF
338
!-------------------------------------------------------------------------------
339
340
!--- Collects the input information from Solver Input File
341
FileName = GetString( GetSolverParams(Solver), "File Name", Found(1) )
342
Var_Name = GetString( GetSolverParams(Solver), "Var Name", Found(2) )
343
344
!--- Collects the NetCDF accessing information (coordinates, constant dimensions, time)
345
CALL GetNetCDFAccessParameters( GetSolverParams(Solver), Coords, Constants, Permutation, Found(3:4) )
346
T_Name = GetString( GetSolverParams(Solver), "Time Name", IsTimeDependent ) ! If given, time is the last dimension
347
348
! Following parameters are needed for masking and coordinate system
349
Mask_Name = GetString( GetSolverParams(Solver), "Mask Variable", Found(5) )
350
Mask_Limit = GetConstReal( Solver % Values, "Mask Limit", Found(6) )
351
Coord_System = GetString( GetSolverParams(Solver), "Coordinate System", Found(7) ) ! Any input is ok; only valid gives a conversion and error is given otherwise
352
IF ( .NOT. Found(7) ) Coord_System = '' ! Initializes Coord_System, if not given
353
354
!-------------------------------------------------------------------------------
355
! 2) Opening the NetCDF file and finding the variable
356
!-------------------------------------------------------------------------------
357
358
DO loop = 1,2,1
359
IF ( .NOT. Found(loop) ) THEN ! Checks that the constants have been found successfully
360
CALL Fatal('GridDataMapper', &
361
"Unable to find a compulsory NetCDF Name Constant (the name of file or variable)")
362
END IF
363
END DO
364
365
status = NF90_OPEN(FileName,NF90_NOWRITE,NCID) ! Read-only
366
IF ( G_Error(status, "NetCDF file could not be opened") ) THEN
367
CALL abort() ! End execution
368
END IF
369
370
! Find variable to be accessed
371
status = NF90_INQ_VARID(NCID,Var_Name,Var_ID)
372
IF ( G_Error(status,'NetCDF variable name not found.') ) THEN
373
CALL abort()
374
END IF
375
376
377
!-------------------------------------------------------------------------------
378
! 3) Finds the amounts for used coordinate and constant dimensions
379
!-------------------------------------------------------------------------------
380
381
!--- Defining coordinate, constant dimension and total dimension sizes
382
size_coord = 0
383
size_const = 0
384
IF ( Found(3) ) size_coord = size(Coords,1)
385
IF ( Found(4) ) size_const = size(Constants,1)
386
dim_count = size_coord + size_const
387
388
IF ( (dim_count .EQ. 0) .AND. (.NOT. IsTimeDependent) ) THEN
389
CALL Fatal('GridDataMapper','Expected at least one indexing variable: time, coordinate, or constant.')
390
END IF
391
!> dim_count in range ( 0, (size_coord + size_const) ), and at least one possible NetCDF accessing parameter given
392
393
!------------------------------------------------------------------------------
394
! 4) Obtains the used Elmer coordinate dimensionality (DIM)
395
!------------------------------------------------------------------------------
396
397
DIM = size_coord
398
399
!-------------------------------------------------------------------------------
400
! 5) Forms an array of dimension names (constant and coordinate) for accessing
401
!-------------------------------------------------------------------------------
402
WRITE (Message,'(A,I3,A)') 'Using ',dim_count,' input dimensions.'
403
CALL Info('GridDataMapper',Message)
404
405
IF ( dim_count .GT. 0 ) THEN
406
407
! Form an array of wanted names for defining the information
408
ALLOCATE (Dim_Names(dim_count), dim_ids(dim_count), dim_lens(dim_count), STAT = alloc_stat)
409
IF ( alloc_stat .NE. 0 ) THEN
410
CALL Fatal('GridDataMapper','Memory ran out')
411
END IF
412
413
! Initialization in case of errors
414
Dim_Names = 'none'
415
dim_ids = -1
416
dim_lens = -1
417
418
! Adds the coordinate NetCDF dimension names, if available
419
IF ( size_coord .GT. 0 ) Dim_Names(1:size(Coords)) = Coords(:)
420
421
! Adds the constant NetCDF dimension names, if available
422
IF ( size_const .GT. 0 ) THEN
423
IF ( size_coord .GT. 0 ) THEN
424
Dim_Names((size(Coords)+1):size(Dim_Names)) = Constants(:)
425
ELSE
426
Dim_Names(:) = Constants(:)
427
END IF
428
END IF
429
430
END IF
431
!> If there are dimensions, their names are in Dim_Names = [Coords, Constants]
432
433
!-------------------------------------------------------------------------------
434
! 6) Gets dimensions on basis of the given names
435
!-------------------------------------------------------------------------------
436
IF ( dim_count .GT. 0 ) CALL GetAllDimensions(NCID,Dim_Names,dim_ids,dim_lens)
437
!> dim_ids & dim_lens collected with the Dim_Names
438
439
!-------------------------------------------------------------------------------
440
! 7) Initializes the Grids (1/2)
441
!------------------------------------------------------------------------------
442
443
!--- Default initializations for all cases
444
DO loop = 1,size(Grids,1),1
445
CALL InitGrid(Grids(loop), dim_count, size_coord )
446
Grids(loop) % access_perm = Permutation
447
END DO
448
449
!-------------------------------------------------------------------------------
450
! Connects the Elmer Mesh dimensions to NetCDF access parameters
451
!-------------------------------------------------------------------------------
452
453
454
!--- Initializations for the case of having some real content
455
IF ( Grids(1) % IS_DEF ) THEN
456
457
!--- Obtains the preliminary definining parameters for the NetCDF grid
458
CALL GetNetCDFGridParameters(NCID,Grids(1),dim_ids,dim_lens) ! Normal grid parameters don't depend on time
459
460
!--- Connects every NetCDF access coordinate to a Elmer coordinate
461
DO loop = 1,Grids(1) % COORD_COUNT,1
462
463
WRITE(tmpFormat,'(A,I1,A)') '(A,I',IntWidth(loop),',A)'
464
WRITE(Message,tmpFormat) 'Coordinate ', Grids(1) % ACCESS_PERM( loop ), ' To Elmer Dimension'
465
466
Grids(1) % Elmer_perm( loop ) = &
467
GetInteger(GetSolverParams(Solver),Message,tmpBool)
468
IF ( .NOT. tmpBool ) THEN
469
WRITE(Message,'(A,I3,A)') 'Declared Coordinate Name ', Grids(1) % ACCESS_PERM( loop ),&
470
' is not connected to a Elmer dimension. Check all "Coordinate X To Elmer Dimension" definitions.'
471
CALL Fatal('GridDataMapper',Message)
472
END IF
473
END DO
474
475
!--- Finds the index values for the found constant dimensions
476
DO loop = 1,size(Grids(1) % const_vals),1
477
478
WRITE(tmpFormat,'(A,I1,A)') '(A,I',IntWidth(loop),')'
479
WRITE(Message,tmpFormat) 'NetCDF Constant Value ', Grids(1) % ACCESS_PERM( Grids(1) % COORD_COUNT + loop)
480
481
Grids(1) % const_vals(loop) = GetInteger(GetSolverParams(Solver),Message,tmpBool)
482
IF ( .NOT. tmpBool ) THEN
483
WRITE(Message,'(A,I3,A)') 'Declared NetCDF Constant ', Grids(1) % ACCESS_PERM( Grids(1) % COORD_COUNT + loop),&
484
' has no corresponding index value. Check all NetCDF Constants.'
485
CALL Fatal('GridDataMapper',Message)
486
END IF
487
END DO
488
Grids(2) % const_vals = Grids(1) % const_vals
489
END IF
490
!> Grids initialized with constant values,x0,dx,nmax, and default for others; or Grid % IS_DEF is .FALSE.
491
492
!-------------------------------------------------------------------------------
493
! 8) Initializes Time (if it is defined)
494
!-------------------------------------------------------------------------------
495
496
IF (IsTimeDependent) THEN
497
498
! Inform about the fate of time
499
CALL Info('GridDataMapper','Time dimension taken into account.')
500
501
Time % is_defined = .TRUE.
502
CALL InitTime( Solver, NCID, T_Name, IS_TRANSIENT, STEP_SIZE, MAX_STEPS, Time )
503
504
! If there'll be interpolation, initialize both of the grids usable
505
IF ( Grids(1) % IS_DEF ) THEN
506
IF ( Time % doInterpolation ) THEN
507
Grids(2) % x0(:) = Grids(1) % x0(:)
508
Grids(2) % dx(:) = Grids(1) % dx(:)
509
Grids(2) % nmax(:) = Grids(1) % nmax(:)
510
END IF
511
512
IF ( size_coord .EQ. 2 ) THEN
513
IF ( Found(5) .AND. Found(6) ) THEN
514
CALL Info('GridDataMapper','Two dimensional NetCDF grid focusing on basis of the given mask is in effect.')
515
CALL Focus2DNetCDFGrid(NCID,Mask_Name,Mask_Limit,Grids(1),Time % low,dim_lens)
516
IF ( Time % doInterpolation ) THEN ! Need to interpolate, return two different grid parameters
517
518
Grids(2) % x0(:) = Grids(1) % x0(:) ! Copy the same results obtained for all grids
519
Grids(2) % dx(:) = Grids(1) % dx(:)
520
Grids(2) % nmax(:) = Grids(1) % nmax(:)
521
CALL Focus2DNetCDFGrid(NCID,Mask_Name,Mask_Limit,Grids(2),Time % high,dim_lens)
522
END IF
523
ELSE
524
! No mask used
525
END IF
526
END IF
527
END IF
528
END IF
529
!> Time initialized and Grids adjusted, if time-dependent focusing used
530
531
!-------------------------------------------------------------------------------
532
! 9) Initializes the Grids (2/2) ( depends on Focus2DNetCDFGrid() )
533
!-------------------------------------------------------------------------------
534
IF ( Grids(1) % IS_DEF ) THEN
535
DO loop = 1,size(Grids,1),1
536
Grids(loop) % x1(:) = Grids(loop) % x0(:) +&
537
(Grids(loop) % nmax(:)-1) * Grids(loop) % dx(:) ! In 3D case opposite points of the cube; if only one dimension, will be 0
538
END DO
539
540
END IF
541
!> Grids initialized with proper x1's
542
543
!-------------------------------------------------------------------------------
544
!> Phase 1: Coord_System
545
!> Phase 2: NCID, Var_ID
546
!> Phase 4: DIM
547
!> Phase 6: dim_ids, dim_lens
548
!> Phase 8: Time
549
!> Phase 9: Grids (scale(:), move(:) and eps(:) not touched)
550
IF ( DEBUG ) THEN
551
CALL PrintGrid(Grids(1),1)
552
CALL PrintGrid(Grids(2),2)
553
END IF
554
555
END SUBROUTINE InitNetCDF
556
557
558
!---------------- InitTime() ------------------------
559
!--- Initializes the time values
560
SUBROUTINE InitTime( Solver, NCID, T_Name, IS_TRANSIENT, STEP_SIZE, MAX_STEPS, TimeResult )
561
!----------------------------------------------------
562
USE NetCDFGeneralUtils, ONLY: TimeValueToIndex, GetDimension
563
USE DefUtils, ONLY: MAX_NAME_LEN, GetSolverParams, GetLogical, GetCReal, GetTime, GetConstReal
564
USE Messages, ONLY: Message, Info, Fatal
565
IMPLICIT NONE
566
!-------------------------------------------------------------------------------
567
! ARGUMENTS
568
!-------------------------------------------------------------------------------
569
!--- A) Input
570
TYPE(Solver_t), INTENT(IN) :: Solver
571
INTEGER, INTENT(IN) :: NCID
572
LOGICAL, INTENT(IN) :: IS_TRANSIENT
573
CHARACTER(len=MAX_NAME_LEN), INTENT(IN) :: T_Name
574
REAL(KIND=dp), INTENT(IN) :: STEP_SIZE
575
INTEGER, INTENT(IN) :: MAX_STEPS
576
!--- B) Output
577
TYPE(TimeType_t), INTENT(OUT) :: TimeResult
578
579
!-------------------------------------------------------------------------------
580
! VARIABLES
581
!-------------------------------------------------------------------------------
582
LOGICAL :: IsTimeIndex, IsUserDefined, Found(5) ! True if SIF definitions found
583
REAL(KIND=dp) :: TimeBias, Time, TimeEpsilon ! Biasing for every used Elmer time value/index
584
585
!-------------------------------------------------------------------------------
586
! 1) Gathers data from SIF, applies default values
587
!-------------------------------------------------------------------------------
588
IsUserDefined = GetLogical( GetSolverParams(Solver), "User Defines Time", Found(1) ) ! Set to true, if old definitions are used
589
IsTimeIndex = GetLogical( GetSolverParams(Solver), "Is Time Index", Found(2) ) ! If true, then the given time value is an index (Default: value)
590
TimeBias = GetCReal( GetSolverParams(Solver), "NetCDF Starting Time", Found(3) ) ! Index, if IsTimeIndex is true; value otherwise
591
TimeEpsilon = GetConstReal( GetSolverParams(Solver), "Epsilon Time", Found(5) ) ! The tolerance for the time value
592
593
!-------------------------------------------------------------------------------
594
! 2) Collects dimension specific data
595
!-------------------------------------------------------------------------------
596
CALL GetDimension(NCID,T_Name, TimeResult % id, TimeResult % len)
597
!> id and len set for TimeResult
598
599
!-------------------------------------------------------------------------------
600
! 3) Sets default values, informs on effect
601
!-------------------------------------------------------------------------------
602
IF ( .NOT. Found(1) ) IsUserDefined = .FALSE.
603
IF ( .NOT. Found(2) ) IsTimeIndex = .FALSE. ! Defaulted to False for values are more natural, otherwise set as given
604
IF ( .NOT. Found(3) ) THEN
605
IF ( IsTimeIndex ) THEN
606
TimeBias = 1.0_dp ! Starts, by default, from index 1
607
ELSE
608
TimeBias = 0.0_dp ! Starts, by default, without value adjustment
609
END IF
610
ELSE
611
! Tell the user what is happening
612
IF ( IsTimeIndex ) THEN
613
WRITE (Message,'(A,F6.2)') 'Input time indices are adjusted (summed) by ', TimeBias
614
ELSE
615
WRITE (Message,'(A,F6.2)') 'Input time values are adjusted (summed) by ', TimeBias
616
END IF
617
CALL Info('GridDataMapper',Message)
618
END IF
619
IF ( .NOT. Found(5) ) THEN
620
TimeEpsilon = 0.0_dp
621
ELSE
622
WRITE (Message,'(A,F6.3)') 'Received Time Epsilon with value ', TimeEpsilon
623
CALL Info('GridDataMapper',Message)
624
END IF
625
!> Default values set
626
627
!-------------------------------------------------------------------------------
628
! 4) Handles transient cases (uses Elmer time, if not defined otherwise)
629
!-------------------------------------------------------------------------------
630
IF ( IS_TRANSIENT .AND. (.NOT. IsUserDefined ) ) THEN
631
632
!-----------------------------------------------------------------------------
633
! A) Transient with Elmer time points
634
!-----------------------------------------------------------------------------
635
WRITE(Message, '(A,A)') 'Simulation is transient and user time input is ignored.',&
636
' (If own time scaling wanted, set SIF variable "User Defines Time" true and use user defined functions)'
637
CALL Info('GridDataMapper', Message)
638
639
!--- Get the time from Elmer
640
Time = GetTime()
641
642
IF ( IsTimeIndex ) THEN
643
!---------------------------------------------------------------------------
644
! Bias time indices
645
!---------------------------------------------------------------------------
646
! Indexing starts with step size in Elmer, bias it to first index
647
648
!--- Check the bias doesn't cause over-indexing the NetCDF time range
649
IF ( TimeBias .LT. 1.0_dp .OR. TimeBias .GT. TimeResult % LEN ) THEN
650
WRITE (Message, '(A,F6.2,A,I5,A)') 'NetCDF Starting Time index ', TimeBias, &
651
' does not fit within the NetCDF time index range (1,', TimeResult % LEN,')'
652
CALL Fatal('GridDataMapper', Message)
653
END IF
654
655
!--- Checks the bias doesn't indirectly over-index due to iterations
656
IF (MAX_STEPS .GT. ((TimeResult % LEN - (TimeBias - STEP_SIZE))/STEP_SIZE) ) THEN
657
WRITE (Message, '(A,I5,A,F10.2,A,F6.2,A)') 'Defined amount of timestep intervals ', MAX_STEPS, &
658
' is more than ', ((TimeResult % LEN - (TimeBias - STEP_SIZE))/STEP_SIZE),&
659
', which is the maximum number of allowed size ', STEP_SIZE ,' steps on the NetCDF grid.'
660
CALL Fatal('GridDataMapper',Message)
661
END IF
662
663
!--- Perform biasing (the bias is valid)
664
Time = Time + (TimeBias - STEP_SIZE)
665
ELSE
666
!---------------------------------------------------------------------------
667
! Bias time values
668
!---------------------------------------------------------------------------
669
Time = Time + TimeBias
670
! NOTE: Time value is checked when it's converted to a time index with TimeValueToIndex()
671
! Does not check for eventual over-indexing!
672
END IF
673
674
ELSE
675
676
!-----------------------------------------------------------------------------
677
! B) For user defined and steady state
678
!-----------------------------------------------------------------------------
679
! NOTE: User-defined/steady state never biased!
680
Time = GetCReal( Solver % Values, "Time Point", Found(4) )
681
682
IF ( .NOT. Found(4) ) THEN
683
WRITE(Message,'(A,I3,A)') 'No time point given; specify it in the Solver Input File with name "Time Point"&
684
or enable transient simulation!'
685
CALL Fatal('GridDataMapper',Message)
686
END IF
687
688
END IF
689
!> Time automatic and transient => Time biased
690
!> Time user-defined/steady state => Time obtained directly from SIF
691
692
!--- Converts the given time value into an appropriate time index
693
IF (.NOT. IsTimeIndex) Time = TimeValueToIndex(NCID,T_Name,TimeResult % id,TimeResult % LEN,Time, TimeEpsilon)
694
695
!--- Final check before letting through
696
IF ( Time .LT. 1 .OR. Time .GT. TimeResult % LEN ) THEN
697
WRITE (Message, '(A,F6.2,A,I5,A)') 'Time value ', Time, ' is out of range (1,', TimeResult % LEN, ')'
698
CALL Fatal('GridDataMapper',Message)
699
END IF
700
!> Time values are converted to indices and checked that they are within range; eventual over-indexing not always checked
701
!> I.e. Time is obtained and checked to be within range
702
703
!-------------------------------------------------------------------------------
704
! 5) Finalizes TimeResult
705
!-------------------------------------------------------------------------------
706
707
! Rounds to nearest integer index, if it is within epsilon range, to accomodate for insignificant differences between real values
708
IF ( Found(5) .AND. (FLOOR( Time) .NE. CEILING( Time )) ) THEN
709
WRITE (Message,'(A,F8.5,A,F8.5)') 'The time index with epsilon range: ', Time - FLOOR(Time), ' (+/-) ', TimeEpsilon
710
CALL Info('GridDataMapper',Message)
711
! FLOOR(Time) < Time < CEILING(TIME) <=> 0 < Time - FLOOR(Time) < CEILING(TIME) - FLOOR(TIME) = 1
712
! If Epsilon makes the value exceed either limit, then the limit is where it is rounded; otherwise intact
713
IF ( Time - FLOOR( Time ) .LE. TimeEpsilon ) THEN
714
Time = FLOOR( Time )
715
ELSE IF ( Time - FLOOR( Time ) .GE. 1.0_dp - TimeEpsilon ) THEN
716
Time = CEILING( Time )
717
END IF
718
END IF
719
TimeResult % val = Time
720
TimeResult % low = FLOOR( Time )
721
TimeResult % high = CEILING( Time )
722
TimeResult % doInterpolation = (TimeResult % low .NE. TimeResult % high)
723
IF ( TimeResult % len .EQ. 1 ) TimeResult % doInterpolation = .FALSE. ! No need to interpolate unit time
724
IF ( TimeResult % low .LT. 1 ) TimeResult % low = 1
725
IF ( TimeResult % high .GT. TimeResult % len ) TimeResult % high = TimeResult % len
726
727
IF ( TimeResult % doInterpolation ) THEN
728
WRITE (Message,'(A,F5.2,A)') 'Given time value ', TimeResult % val , ' is not an integer. Using time interpolation.'
729
CALL Info('GridDataMapper',Message)
730
ELSE
731
WRITE (Message,'(A,F5.1,A)') 'Given time value ', TimeResult % val, ' is an integer. No time interpolation used.'
732
CALL Info('GridDataMapper',Message)
733
END IF
734
735
!-------------------------------------------------------------------------------
736
737
END SUBROUTINE InitTime
738
739
740
!---------------- InitInterpolation() ---------------
741
!--- Initializes the information needed for interpolation
742
SUBROUTINE InitInterpolation( Solver, DIM, Grids, TimeInterpolationMethod, InterpMultiplier, InterpBias )
743
USE DefUtils, ONLY: GetSolverParams, MAX_NAME_LEN, GetConstReal, GetString, GetCReal, CoordinateSystemDimension
744
USE Messages
745
IMPLICIT NONE
746
747
!-------------------------------------------------------------------------------
748
! ARGUMENTS
749
!-------------------------------------------------------------------------------
750
TYPE(Solver_t), INTENT(IN) :: Solver
751
INTEGER, INTENT(IN) :: DIM
752
TYPE(UniformGrid_t), INTENT(INOUT) :: Grids(:)
753
REAL(KIND=dp), INTENT(OUT) :: InterpMultiplier, InterpBias
754
CHARACTER(len=MAX_NAME_LEN), INTENT(OUT) :: TimeInterpolationMethod
755
756
!-------------------------------------------------------------------------------
757
! VARIABLES
758
!-------------------------------------------------------------------------------
759
LOGICAL :: tmpBool
760
REAL(KIND=dp), ALLOCATABLE :: eps(:)
761
INTEGER :: loop, alloc_stat
762
763
!-------------------------------------------------------------------------------
764
! 1) Adds Epsilon values to Grids (if applicable)
765
!-------------------------------------------------------------------------------
766
IF ( Grids(1) % COORD_COUNT .GT. 0 ) THEN
767
768
!--- Allocation
769
ALLOCATE ( eps( Grids(1) % COORD_COUNT ), STAT = alloc_stat )
770
IF ( alloc_stat .NE. 0 ) THEN
771
CALL Fatal('GridDataMapper','Memory ran out')
772
END IF
773
eps = 0
774
775
! Epsilons are the relative tolerances for the amount
776
! the Elmer grid point misses the bounds of the NetCDF bounding box
777
DO loop = 1,size(eps),1
778
779
! NOTE: There won't be more than 9 epsilons, because there can't be enough Elmer coordinates for that!
780
WRITE(Message, '(A,I1)') 'Epsilon ', loop
781
eps(loop) = GetConstReal(GetSolverParams(Solver), Message, tmpBool)
782
IF ( .NOT. tmpBool ) THEN
783
eps(loop) = 0
784
WRITE(Message,'(A,I1,A,A)') 'Variable "Epsilon ', loop ,'" not given in Solver Input File. ',&
785
'Using zero tolerance for NetCDF grid mismatches with Elmer mesh.'
786
CALL Warn('GridDataMapper', Message)
787
END IF
788
END DO
789
790
! Sets the appropriate values to the Grids
791
Grids(1) % Eps(:) = eps(:) * Grids(1) % dx(:)
792
Grids(2) % Eps(:) = eps(:) * Grids(2) % dx(:)
793
END IF
794
795
!-------------------------------------------------------------------------------
796
! 2) Sets the time interpolation method
797
!-------------------------------------------------------------------------------
798
TimeInterpolationMethod = GetString( GetSolverParams(Solver), "Time Interpolation Method", tmpBool )
799
IF ( .NOT. tmpBool ) THEN
800
CALL Warn('GridDataMapper', 'SIF variable "Time Interpolation Method" not specified, using default settings.')
801
TimeInterpolationMethod = ''
802
ELSE
803
WRITE (Message,'(A,A)' ) 'Received Time Interpolation Method SIF variable value: ', TimeInterpolationMethod
804
CALL Info('GridDataMapper', Message)
805
END IF
806
807
!-------------------------------------------------------------------------------
808
! 3) Sets the final adjustments for the interpolation results (to allow relative/absolute time, f.ex.)
809
!-------------------------------------------------------------------------------
810
811
! If absolute time is relative, the value of the time function is added to the interpolated location; otherwise it is multiplied with it
812
InterpMultiplier = GetCReal( GetSolverParams(Solver), "Interpolation Multiplier", tmpBool ) ! Multiplies the final interpolation result by given number (relative time)
813
IF ( .NOT. tmpBool ) InterpMultiplier = 1.0_dp ! Defaulted to 1, so it doesn't modify the result
814
815
InterpBias = GetCReal( GetSolverParams(Solver), "Interpolation Bias", tmpBool ) ! Adds the bias to the final interpolation result (absolute time)
816
IF ( .NOT. tmpBool ) InterpBias = 0.0_dp ! Defaulted to 0, so there is no bias on time
817
818
!-------------------------------------------------------------------------------
819
820
END SUBROUTINE InitInterpolation
821
822
!------------------------------------------------------------------------------
823
END SUBROUTINE GridDataMapper
824
!------------------------------------------------------------------------------
825
826
827