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 Truncated Infinite Series Calculator

Status
Not open for further replies.

dss91

Technical User
Jan 26, 2011
1
US
I have an assignment to write a program for calculating the sine (and various other functions) using the method of truncated infinite series using DO statements. The DO statement is supposed to run until the difference between the current and last iterations are less than 1.0E-6. Saying that I am lost is an understatement. I have done some research on the internet and seem to have been able to piece together some code which makes sense to me, however I am just getting random junk out of it when I run it. Any help would be greatly appreciated! There are multiple menu options for different functions, which I have yet to start on, as I am trying to get the sine function to work correctly first.

Code:
PROGRAM PROJECT2
IMPLICIT NONE
INTEGER::i,n
REAL::x,z,sinx,cosx
CHARACTER::choice



WRITE(*,*) 'Please enter a number x:'
READ(*,*) x

DO
WRITE(*,*) ''
WRITE(*,*) '  Iterative Function Calculator'
WRITE(*,*) '-------------------'
WRITE(*,*) '  A) SIN(x)'
WRITE(*,*) '  B) COS(x)'
WRITE(*,*) '  C) e^x'
WRITE(*,*) "  D) Lambert's W function Wo(x)"
WRITE(*,*) '  E) Enter a new x'
WRITE(*,*) '  Q) Quit'
WRITE(*,*) 'Please enter choice:'
READ(*,*) choice
IF(CHOICE .EQ. 'Q' .or. CHOICE .EQ. 'q') THEN
	EXIT
ELSE IF(CHOICE .EQ. 'A' .or. CHOICE .EQ. 'a') THEN
	DO i = 1,n
		n=1
		sinx=0.
	sinx=sinx+z
	n=n+1
	z=z+(-1)**n*x**(2*n+1)/((2*n-2)*(2*n-1))
	IF(n==10000) THEN
		EXIT
	!IF((abs(sinx-(sinx+z))) < (1.E-6)) THEN
		!EXIT
		END IF
	END DO
	WRITE(*,*) z
	!WRITE(*,'(A,F6.4,A,F6.4 )') 'SIN(',x,') = ',sinx
ELSE IF(CHOICE .EQ. 'D' .or. CHOICE .EQ. 'd') THEN
	READ(*,*) x
ENDIF
END DO
END PROGRAM
 
Hint: your problem is "n". When your program enters the "do loop", "n" hasn't been set, and it will probably be some "random" integer. (Not really random, it depends on the memory the program has assigned to it and what was there before.) It starts the loop, and you set "n" to 1. You do a calc, and then you increment "n" to 2. (NB: You've set this to happen on every iteration, regardless of the value of "i".) It does some other stuff, but it comes back to the beginning of the loop (now "i" is 2), and it does another iteration. At the end, because "i" is "n", it exits.

--------------------------------------
Background: Chemical engineer, familiar mostly with MATLAB, but now branching out into real programming.
 
I see several mistakes in your program

- n is not initialized before you use it in the loop
- sinx is initialized at a wrong place
- z is not initialized when you compute z=z+...
- your formula is not computed optimally
- your code is not robust againts user mistakes

To summarize :

Code:
program project2

implicit none

integer   :: i,n=20
real      :: x,z,sinx,cosx
character :: choice

10 continue

write(*,*) 'Please enter a number x:'
read (*,*,err=10) x
  
do

  write(*,*) ''
  write(*,*) '  Iterative Function Calculator'
  write(*,*) '-------------------'
  write(*,*) '  A) SIN(x)'
  write(*,*) '  B) COS(x)'
  write(*,*) '  C) e^x'
  write(*,*) "  D) Lambert's W function Wo(x)"
  write(*,*) '  E) Enter a new x'
  write(*,*) '  Q) Quit'
  
  write(*,*) 'Please enter choice:'

  read(*,*) choice
  
  select case(choice)
  
  case('q','Q')
    exit
  case('a','A')
    z=x
    sinx=0
    do i=1,n
      sinx=sinx+z
      if(abs(z) < 1.e-6) EXIT
      z=-z*x**2/(2*i*(2*i+1))
    enddo
    write(*,*) 'computed sinux      ',sinx
    write(*,*) 'using the intrinsic ',sin(x)
    
  case default
    write(*,*) 'choice ',choice,' not implemented yet'
  end select

enddo

end program

François Jacq
 
Status
Not open for further replies.

Part and Inventory Search

Sponsor

Back
Top