Path: blob/devel/misc/netcdf/src/GridDataMapper/CustomTimeInterpolation.f90
3206 views
!------------------------------------------------------------------------------1! Vili Forsell2! Created: 15.6.20113! Last Modified: 16.6.20114!------------------------------------------------------------------------------5! This module is the customizable file to implement optional functions for6! time interpolation between two points.7! HOW TO USE:8! - add a case calling your interpolation function (can be implemented within this file)9! - add a matching string into Solver Input File in variable "Time Interpolation Method"10! - uses linear interpolation by default11!------------------------------------------------------------------------------12MODULE CustomTimeInterpolation13USE DefUtils, ONLY: dp, MAX_NAME_LEN14IMPLICIT NONE1516! If different parameters needed, adjust GridDataMapper.f90 interpolation call and add your function name here17! INTERFACE ChooseTimeInterpolation18! MODULE PROCEDURE ChooseTimeInterpolation19! END INTERFACE2021PRIVATE :: SeasonalInterpolation2223CONTAINS2425!--------------- ChooseTimeInterpolation() -----------26!--- Chooses the time interpolation method on basis of variable "Time Interpolation Method" in the SIF27FUNCTION ChooseTimeInterpolation( time, left, right, method, give_info ) RESULT( NetCDF_value )28!-----------------------------------------------------2930USE NetCDFInterpolate, ONLY: LinearInterpolation31USE DefUtils, ONLY: dp,MAX_NAME_LEN32USE Messages33IMPLICIT NONE3435!--- Input parameters36REAL(KIND=dp), INTENT(IN) :: time, & ! The time index as a real value37left(:), & ! The closest left NetCDF point of form (time index, NetCDF value)38right(:) ! The closest right NetCDF point of form (time index, NetCDF value)39CHARACTER(*), INTENT(IN) :: method ! The string used for selecting the method40! It's contents come from the SIF variable "Time Interpolation Method"41LOGICAL, INTENT(IN) :: give_info4243!--- Output parameter44REAL(KIND=dp) :: NetCDF_value ! The NetCDF value obtained on basis of interpolating in terms of time4546!--- Checks47IF ( size(left) .NE. size(right) ) CALL Fatal('CustomTimeInterpolation','Input vector sizes do not match')4849!--- Selects the implemented method50SELECT CASE (method) ! Selects the chosen interpolation method51CASE ("seasonal")52IF ( give_info ) WRITE (Message,'(A)') 'Seasonal interpolation in effect'53NetCDF_value = SeasonalInterpolation(time,left,right)54CASE ("linear")55IF ( give_info ) WRITE (Message,'(A)') 'Linear interpolation in effect'56NetCDF_value = LinearInterpolation(time,left,right)57CASE DEFAULT ! Defaults to linear interpolation58IF ( give_info ) WRITE (Message,'(A)') 'Default time interpolation in effect (linear)'59NetCDF_value = LinearInterpolation(time,left,right)60END SELECT6162IF ( give_info ) CALL Info('ChooseTimeInterpolation',Message)6364END FUNCTION ChooseTimeInterpolation6566!-------------- SinusoidalInterpolation() -------------'67! An example time interpolation function,68! which applies sinusoidal behaviour between the two input points69FUNCTION SeasonalInterpolation(time,left,right) RESULT( val )70!------------------------------------------------------7172! --- PREFACE ---73! Assume NetCDF data (and all grid points) are June temperatures and we want to consider also winter.74! First, we fit a sinusoid between the interval (with NetCDF value constant) to get the general drop in temperature.75! Second, we adjust the sinusoid values with the value difference between the two grid points76! to take linear (assumption) temperature change between Junes into account.77! Hence, we have a general interpolation for temperatures between the June seasons.78USE DefUtils, ONLY: PI79USE Messages ! Elmer messaging interface for error messages, etc.80IMPLICIT NONE81REAL(KIND=dp), INTENT(IN) :: time, left(:), right(:) ! Input variables82REAL(KIND=dp) :: val ! Output variable83REAL(KIND=dp) :: frequency, amplitude, phase, t ! Sinusoid parameters84INTEGER :: alloc_stat85REAL(KIND=dp), ALLOCATABLE :: diff(:) ! For allocating memory on basis of input size8687! Allocate memory on basis of input and check that it didn't run out88ALLOCATE ( diff(size(left)), STAT = alloc_stat )89IF ( alloc_stat .NE. 0 ) THEN90CALL Fatal( 'Sinusoidal Interpolation', 'Memory ran out' ) ! This automatically terminates the program91END IF9293diff(:) = right(:) - left(:) ! For time and value differences in the uniform NetCDF grid9495! 1) Fit a sinusoid between the interval:96phase = PI ! The part from pi to 2*pi is below the y axis, so pi ~ t_left and 2pi ~ t_right97frequency = 0.5 ! Half a sine per interval98t = (time - left(1))/diff(1) ! time is between left and right, and t is where on sine we are, between 0 and 199amplitude = 30 ! Assume 30 degree difference between june and december100101val = amplitude*SIN(2*PI*t*frequency + phase)102103! 2) Adjust with the value difference at current time point and we're ready104val = val + t*diff(2)105! WRITE (*,*) 'Value ', val106107END FUNCTION SeasonalInterpolation108109END MODULE CustomTimeInterpolation110111112