Tek-Tips is the largest IT community on the Internet today!

Members share and learn making Tek-Tips Forums the best source of peer-reviewed technical information on the Internet!

  • Congratulations strongm on being selected by the Tek-Tips community for having the most helpful posts in the forums last week. Way to Go!

Help with infinite series calculation of SIN

Status
Not open for further replies.

cbmurphy

Programmer
Oct 12, 2008
11
US
hello, i am a new fortran user in college... our teacher is a first year teacher and has assigned us 3 programs to write, none of which she explained how to do. i read the entire book up to where we are but apparently i still do not grasp the full concept yet. we are supposed to write a program that calculates the value of Sin(x) with the infinite series (-1)**(n-1)*x**(2n-1)/factorial(2n-1)... i have written a program with 2 internal functions but i can not get it to compile without errors. here is the code
Code:
program infiniteSeries
	IMPLICIT NONE
	real :: x = 0.
	integer :: n = 1
	real :: degRad = 3.1415926 / 180
	real :: sinIntrinsic = 0., mySin = 0.
	real :: sinApprox
	write(*,*)"Please enter a value in degrees"
	read(*,*)x
	x = x * degRad
	sinIntrinsic = sin(x)
	do n = 1, 10
		mySin = sinApprox(x,n)
		write(*,*)n, mySin
	end do
	write(*,*)sinIntrinsic
end

real function sinApprox(x,n)
	implicit none
	sinApprox = 0.
	real, intent(in) :: x
	integer, intent(in) :: n
	integer :: i = 1
	real :: fact
	integer :: a = 0
	a = 2n - 1
	do i = 1, n
		sinApprox = sinApprox + (-1)**(n-1) * x**(2*n-1) / fact(a)
	end do
end

real function fact(a)
	implicit none
	integer, intent(in) :: a
	fact = 1.
	integer :: i = 1
	do i = 1, a
		fact = fact * i
	end do
end

and here are my error messages:
In file infiniteSeries.f95:42

real, intent(in) :: x
1
Error: Unexpected data declaration statement at (1)
In file infiniteSeries.f95:43

integer, intent(in) :: n
1
Error: Unexpected data declaration statement at (1)
In file infiniteSeries.f95:44

integer :: i = 1
1
Error: Unexpected data declaration statement at (1)
In file infiniteSeries.f95:45

real :: fact
1
Error: Unexpected data declaration statement at (1)
In file infiniteSeries.f95:46

integer :: a = 2n - 1
1
Error: Syntax error in data declaration at (1)
In file infiniteSeries.f95:37

real function sinApprox(x,n)
1
Error: Symbol 'x' at (1) has no IMPLICIT type
In file infiniteSeries.f95:37

real function sinApprox(x,n)
1
Error: Symbol 'n' at (1) has no IMPLICIT type
In file infiniteSeries.f95:48

do i = 1, n
1
Error: Symbol 'i' at (1) has no IMPLICIT type
In file infiniteSeries.f95:49

sinApprox = sinApprox + (-1)**(n-1) * x**(2*n-1) / fact(a)
1
Error: Symbol 'a' at (1) has no IMPLICIT type
In file infiniteSeries.f95:49

sinApprox = sinApprox + (-1)**(n-1) * x**(2*n-1) / fact(a)
1
Error: Function 'fact' at (1) has no IMPLICIT type
In file infiniteSeries.f95:61

integer :: i = 1
1
Error: Unexpected data declaration statement at (1)
In file infiniteSeries.f95:63

do i = 1, a
1
Error: Symbol 'i' at (1) has no IMPLICIT type


if anyone could at least point me in the right direction as to where i am messing up, i would greatly appreciate it. thanks
 
You need to declare your function fact() in the function sinApprox() as follows
Code:
real :: fact ! type of the function fact()
But you had errors in your approximative computation of sinus function through Taylor-series too: See the right formula e.g. here:
Here is your code I corrected:
Code:
program infiniteSeries
  implicit none
  integer :: n = 1
  real :: degRad = 3.141592653589793 / 180
  real :: sinApprox, sinIntrinsic = 0., mySin = 0., x = 0.
  
  write(*,*)"Please enter a value in degrees"
  read(*,*) x
  x = x * degRad
  sinIntrinsic = sin(x)
  do n = 1, 10
    mySin = sinApprox(x,n)
    write(*,*) n, mySin
  end do
  write(*,*) "Intrinsic function sin() =", sinIntrinsic
end program infiniteSeries

real function sinApprox(x,n)
  implicit none
  real :: x, fact ! type of the function fact()
  integer :: n, k, a

  sinApprox = 0.
  do k = 0, n
    ! formula see: [URL unfurl="true"]http://en.wikipedia.org/wiki/Trigonometric_functions#Sine[/URL]
    sinApprox = sinApprox + (-1)**k * x**(2*k+1) / fact(2*k+1)
  end do
end function sinApprox

function fact(a)
  implicit none
  real :: fact
  integer :: a, i

  fact = 1.
  do i = 1, a
    fact = fact * i
  end do
end function fact
However, my compiler (g77) don't support intent, so I left it out. I compiled the above code with
Code:
g77 infin_ser.for -o infin_ser -ffree-form
 
i actually fixed it yesterday, but thanks... also, the formula is correct, the one you put in goes from 0 to infinity where mine goes from 1 to infinity, they are in fact equal formulas though
 
Hi cbmurphy,

Yes, I know, that your formula goes from 1 and my from 0,
but you tried in your example to compute in every k-th step (k=1,..n) the same value fact(2*n - 1) and that should be fact(2*k - 1).


 
Status
Not open for further replies.

Part and Inventory Search

Sponsor

Back
Top