Book a Demo!
CoCalc Logo Icon
StoreFeaturesDocsShareSupportNewsAboutPoliciesSign UpSign In
ElmerCSC
GitHub Repository: ElmerCSC/elmerfem
Path: blob/devel/misc/netcdf/src/GridDataMapper/CustomTimeInterpolation.f90
3206 views
1
!------------------------------------------------------------------------------
2
! Vili Forsell
3
! Created: 15.6.2011
4
! Last Modified: 16.6.2011
5
!------------------------------------------------------------------------------
6
! This module is the customizable file to implement optional functions for
7
! time interpolation between two points.
8
! HOW TO USE:
9
! - add a case calling your interpolation function (can be implemented within this file)
10
! - add a matching string into Solver Input File in variable "Time Interpolation Method"
11
! - uses linear interpolation by default
12
!------------------------------------------------------------------------------
13
MODULE CustomTimeInterpolation
14
USE DefUtils, ONLY: dp, MAX_NAME_LEN
15
IMPLICIT NONE
16
17
! If different parameters needed, adjust GridDataMapper.f90 interpolation call and add your function name here
18
! INTERFACE ChooseTimeInterpolation
19
! MODULE PROCEDURE ChooseTimeInterpolation
20
! END INTERFACE
21
22
PRIVATE :: SeasonalInterpolation
23
24
CONTAINS
25
26
!--------------- ChooseTimeInterpolation() -----------
27
!--- Chooses the time interpolation method on basis of variable "Time Interpolation Method" in the SIF
28
FUNCTION ChooseTimeInterpolation( time, left, right, method, give_info ) RESULT( NetCDF_value )
29
!-----------------------------------------------------
30
31
USE NetCDFInterpolate, ONLY: LinearInterpolation
32
USE DefUtils, ONLY: dp,MAX_NAME_LEN
33
USE Messages
34
IMPLICIT NONE
35
36
!--- Input parameters
37
REAL(KIND=dp), INTENT(IN) :: time, & ! The time index as a real value
38
left(:), & ! The closest left NetCDF point of form (time index, NetCDF value)
39
right(:) ! The closest right NetCDF point of form (time index, NetCDF value)
40
CHARACTER(*), INTENT(IN) :: method ! The string used for selecting the method
41
! It's contents come from the SIF variable "Time Interpolation Method"
42
LOGICAL, INTENT(IN) :: give_info
43
44
!--- Output parameter
45
REAL(KIND=dp) :: NetCDF_value ! The NetCDF value obtained on basis of interpolating in terms of time
46
47
!--- Checks
48
IF ( size(left) .NE. size(right) ) CALL Fatal('CustomTimeInterpolation','Input vector sizes do not match')
49
50
!--- Selects the implemented method
51
SELECT CASE (method) ! Selects the chosen interpolation method
52
CASE ("seasonal")
53
IF ( give_info ) WRITE (Message,'(A)') 'Seasonal interpolation in effect'
54
NetCDF_value = SeasonalInterpolation(time,left,right)
55
CASE ("linear")
56
IF ( give_info ) WRITE (Message,'(A)') 'Linear interpolation in effect'
57
NetCDF_value = LinearInterpolation(time,left,right)
58
CASE DEFAULT ! Defaults to linear interpolation
59
IF ( give_info ) WRITE (Message,'(A)') 'Default time interpolation in effect (linear)'
60
NetCDF_value = LinearInterpolation(time,left,right)
61
END SELECT
62
63
IF ( give_info ) CALL Info('ChooseTimeInterpolation',Message)
64
65
END FUNCTION ChooseTimeInterpolation
66
67
!-------------- SinusoidalInterpolation() -------------'
68
! An example time interpolation function,
69
! which applies sinusoidal behaviour between the two input points
70
FUNCTION SeasonalInterpolation(time,left,right) RESULT( val )
71
!------------------------------------------------------
72
73
! --- PREFACE ---
74
! Assume NetCDF data (and all grid points) are June temperatures and we want to consider also winter.
75
! First, we fit a sinusoid between the interval (with NetCDF value constant) to get the general drop in temperature.
76
! Second, we adjust the sinusoid values with the value difference between the two grid points
77
! to take linear (assumption) temperature change between Junes into account.
78
! Hence, we have a general interpolation for temperatures between the June seasons.
79
USE DefUtils, ONLY: PI
80
USE Messages ! Elmer messaging interface for error messages, etc.
81
IMPLICIT NONE
82
REAL(KIND=dp), INTENT(IN) :: time, left(:), right(:) ! Input variables
83
REAL(KIND=dp) :: val ! Output variable
84
REAL(KIND=dp) :: frequency, amplitude, phase, t ! Sinusoid parameters
85
INTEGER :: alloc_stat
86
REAL(KIND=dp), ALLOCATABLE :: diff(:) ! For allocating memory on basis of input size
87
88
! Allocate memory on basis of input and check that it didn't run out
89
ALLOCATE ( diff(size(left)), STAT = alloc_stat )
90
IF ( alloc_stat .NE. 0 ) THEN
91
CALL Fatal( 'Sinusoidal Interpolation', 'Memory ran out' ) ! This automatically terminates the program
92
END IF
93
94
diff(:) = right(:) - left(:) ! For time and value differences in the uniform NetCDF grid
95
96
! 1) Fit a sinusoid between the interval:
97
phase = PI ! The part from pi to 2*pi is below the y axis, so pi ~ t_left and 2pi ~ t_right
98
frequency = 0.5 ! Half a sine per interval
99
t = (time - left(1))/diff(1) ! time is between left and right, and t is where on sine we are, between 0 and 1
100
amplitude = 30 ! Assume 30 degree difference between june and december
101
102
val = amplitude*SIN(2*PI*t*frequency + phase)
103
104
! 2) Adjust with the value difference at current time point and we're ready
105
val = val + t*diff(2)
106
! WRITE (*,*) 'Value ', val
107
108
END FUNCTION SeasonalInterpolation
109
110
END MODULE CustomTimeInterpolation
111
112