![]() |
||||||||
![]() |
![]() |
![]() |
![]() |
|||||
![]() |
||||||||
![]() |
||||||||
![]() |
![]() |
|||||||
![]() |
||||||||
![]() |
||||||||
![]() |
||||||||
![]() |
||||||||
![]() |
||||||||
INTEGRATION DEMONSTRATION
This code demonstrates integration of pressure coefficient data in a file to calculate the pitching moment, which is the moment about the quarter-chord of the airfoil.
PROGRAM Pitching_Moment_Cp
IMPLICIT NONE
REAL, DIMENSION(1:800,1:2):: points
REAL :: ref, PM_L, PM_R, PM_M, PM_T, PM_S
INTEGER :: I,J,iost
OPEN (unit=10, file=’data.prn’,&
& status=’old’)
DO I=1,800
READ(10,*,IOSTAT=iost)(points(I,J),J=1,2)
END DO
IF (iost==0) THEN
WRITE(*,*) ’No EOF Encountered’
ELSEIF (iost<0) THEN
WRITE(*,*) ’EOF encountered’
STOP
ELSE
WRITE(*,*) ’error in execution. iost=’, iost
STOP
END IF
WRITE(*,*) ’What is your reference point (as a real number)?’
READ(*,*) ref
CALL LT_PT(points, ref, PM_L)
CALL RT_PT(points, ref, PM_R)
CALL md_PT(points, ref, PM_M)
CALL Trap(points, ref, PM_T)
CALL Simpsons(points, ref, PM_S)
WRITE(*,*) ’The Pitching Moment Coefficient by the Left Hand Rule=’, PM_L
WRITE(*,*) ’The Pitching Moment Coefficient by the Right Hand Rule=’, PM_R
WRITE(*,*) ’The Pitching Moment Coefficient by the Midpoint Rule=’, PM_M
WRITE(*,*) ’The Pitching Moment Coefficient by the Trapazoidal Rule=’, PM_T
WRITE(*,*) "The Pitching Moment Coefficient by the Simpson’s Rule=", PM_S
CONTAINS
subroutine LT_PT(points, ref, PM_L)
REAL, intent(in), dimension(1:800,1:2) :: points
REAL, intent(in):: ref
REAL, intent(out):: PM_L
INTEGER :: I
PM_L=0
DO I= 1,800-1
PM_L=PM_L+ ( ref - points(I,1) ) * points(I,2) * &
( points(I+1,1) - points(I,1) )
END DO
END subroutine LT_PT
subroutine RT_PT(points, ref, PM_R)
REAL, intent(in), dimension(1:800,1:2) :: points
REAL, intent(in):: ref
REAL, intent(out):: PM_R
INTEGER :: I
PM_R=0
DO I=1,800-1
PM_R=PM_R + ( ref - points(I,1) ) * points(I+1,2) * &
&( points(I+1,1) - points(I,1) )
END DO
END subroutine RT_PT
subroutine md_PT(points, ref, PM_M)
REAL, intent(in), dimension(1:800,1:2) :: points
REAL, intent(in):: ref
REAL, intent(out):: PM_M
INTEGER :: I
PM_M=0
DO I=1,800-1
PM_M=PM_M + ( ref - points(I,1) ) * ( points(I+1,2)&
& + points(I,2) ) * .5 *&
& ( points(I+1,1) - points(I,1) )
END DO
END subroutine md_PT
subroutine Trap(points, ref, PM_T)
REAL, intent(in), dimension(1:800,1:2) :: points
REAL, intent(in):: ref
REAL, intent(out):: PM_T
INTEGER :: I
PM_T=0
DO I=1,800-1
PM_T= PM_T + ( ref - points(I,1) ) * ( points(I,2)&
& + points(I+1,2)) * .5 &
& * ( points(I+1,1) - points(I,1) )
END DO
END subroutine Trap
Next Page →
Next Page →













