Welcome to AE Resources
Converted document INTERPOLATION DEMONSTRATION

INTERPOLATION DEMONSTRATION

This code demonstrates interpolation of pressure coefficient data in a file to specific locations along an airfoil. Different interpolation methods are demonstrated.
PROGRAM Interpolation
IMPLICIT NONE
REAL, DIMENSION(:), ALLOCATABLE :: x, Cp
!Define locations in which we wish to interpolate for
!Column 1: x values
!Column 2: Linearly interpolated Cp values
!Column 3: Newton interpolated Cp values
REAL, DIMENSION(14, 3) :: upper
REAL, DIMENSION(11, 3) :: lower
REAL, DIMENSION(2, 2) :: line
REAL, DIMENSION(4, 2) :: poly
INTEGER :: i, j, ierr1, ierr2
REAL :: a, b
CHARACTER(LEN=50) :: myfile
​
upper(1:14, 1) = (/ .02, .1, .15, .2, .25, .3, .35, .4, .5, .6, .7, .8, .9, .92 /)
upper(1:14, 2:3) = 0
lower(1:11, 1) = (/ .04, .075, .125, .2, .32, .44, .5, .6, .75, .85, .92 /)
lower(1:11, 2:3) = 0
​
!Explain program
WRITE(*,*) ’This program takes in given data describing position and Cp’
WRITE(*,*) ’on an airfoil and interpolates the remaining data.’
WRITE(*,*) ’The output is separated into upper and lower divisions,’
WRITE(*,*) ’Showing the locations of interpolation, as well as the corresponding’
WRITE(*,*) ’linear and Newton-Raphson Cp values.’
WRITE(*,*) ’’
​
!Read in filename, later to be changed for user input
!WRITE(*,*) ’Please input name of file currently on the server (including extension).’
!READ(*,*) myfile
myfile = ’data_cfd.dat’
Call readFile
​
!Read through lower data first
DO i=1,SIZE(lower,1),1
	!Cycle through each X in the array
	!For each X, find the appropriate location in the experimental data
	DO j = 2,(SIZE(x)/2),1
		a = lower(i,1) - x(j)
		b = lower(i,1) - x(j-1)
		IF (SIGN(a,b) == -a .OR. SIGN(a,b) == 0) THEN
		!The SIGN checks to see if the x value falls in betweent two
			line(1:2,1) = x((j-1):j)
			line(1:2,2) = Cp((j-1):j)
			Call linearForm(line, i, ’lower’)
			poly(1:4,1) = x((j):(j+3))
			poly(1:4,2) = Cp((j):(j+3))
			Call newtonForm(poly, i, ’lower’)
			EXIT
		ELSEIF (SIGN(a,b) == 0) THEN
		!Just in case the point is already in existence
			lower(i, 2) = Cp(j-1)     !j-1 because sign = 0 when b is exact
		ELSEIF (j == SIZE(x)/2) THEN
			WRITE (*,*) ’This data point requires extrapolation.’
		ENDIF
	ENDDO
ENDDO
​
!Read through upper data
DO i=1,SIZE(upper,1),1
	!Cycle through each X in the array
	!For each X, find the appropriate location in the experimental data
	DO j = (SIZE(x)/2 + 2), SIZE(x), 1
		a = upper(i,1) - x(j)
		b = upper(i,1) - x(j-1)
		IF (SIGN(a,b) == -a .OR. SIGN(a,b) == 0) THEN
		!The SIGN checks to see if the x value falls in betweent two
			line(1:2,1) = x((j-1):j)
			line(1:2,2) = Cp((j-1):j)
			Call linearForm(line, i, ’upper’)
			poly(1:4,1) = x((j):(j+2))
			poly(1:4,2) = Cp((j):(j+3))
			Call newtonForm(poly, i, ’upper’)
			EXIT
		ELSEIF (SIGN(a,b) == 0) THEN
		!Just in case the point is already in existence
			upper(i, 2) = Cp(j-1)     !j-1 because sign = 0 when b is exact
		ELSEIF (j == SIZE(x)/2) THEN
			WRITE (*,*) ’This data point requires extrapolation.’
		ENDIF
	ENDDO
ENDDO
Next Page →
Next Page →