@ELNS,
Comments by @kargl re: author attribution (copyright, link to this thread, etc.) are rather pertinent and should apply in principle to other responses on this thread as well your various other inquiries thus far on this forum.
By the way, this thread and your other ones appear quite academic in their nature, perhaps part of a university course on numerical analysis using programming languages of which Fortran might be a choice? If so, it will help readers if you share that as well.
As to your issue here with the calculation, you may have noted a loop construct is also a possibility in addition to a recursive function. The important aspect is structure and setup of the code that captures the essence of the algorithm accompanied by appropriate numerical analysis e.g., how and when to terminate a computation involving an infinite series. For the immediate case at hand, one might use the RECURSIVE attribute of procedures in Fortran to calculate the tangent using Lambert’s formula like so:
! Program # : Example07032020.1
! Author : FortranFan
! Reference : https://en.wikipedia.org/wiki/Gauss%27s_continued_fraction#cite_note-8
!
! Description:
! An example implementation that illustrates how to employ a
! RECURIVE function in Fortran to compute the tangent of x using
! Lambert's continued fraction dating back to 1768 which gives
! tan(x) = x/(1-x**2/(3-x**2/(5-x**2/(7-x**2/..))))
!
module kinds_m
integer, parameter :: WP = selected_real_kind( p=12 ) ! Select suitable precision
end module
module trig_m
use kinds_m, only : WP
! Named constants
real(WP), parameter :: ONE = 1.0_wp
real(WP), parameter :: TWO = 2.0_wp
real(WP), parameter :: PI = 3.14159265358979323846264338327950288_wp
real(WP), parameter :: DEG_TO_RAD = PI/180.0_wp
real(WP), parameter :: TOL = 1e-3_wp !<-- Suitable tolerance for continued fraction series
real(WP), parameter :: UPPER_LIMIT = ONE/TOL
contains
elemental function tand( degx ) result( tanx )
! Calculate tangent of x in degrees using Lambert's formula
! Argument list
real(WP), intent(in) :: degx ! x in degrees
! Function result
real(WP) :: tanx
! Local variables
real(WP) :: x
x = degx * DEG_TO_RAD
tanx = x / ( ONE + CalcFracLambert(x, n=1))
return
end function
pure recursive function CalcFracLambert(x, n) result(Frac)
! Argument list
real(WP), intent(in) :: x ! x in radians
integer, intent(in) :: n
! Function result
real(WP) :: Frac
! Local variables
real(WP) :: Term
Term = TWO*n + ONE
if ( Term > UPPER_LIMIT ) then
Frac = - x**2 / Term
else
Frac = - x**2 / ( Term + CalcFracLambert(x, n+1) )
end if
return
end function
end module
program CalcTanx
use kinds_m, only : WP
use trig_m, only : tand, DEG_TO_RAD
real(WP) :: degx, tanx
degx = 40.0_wp
tanx = tand( degx )
print *, "x(degrees): ", degx
print *, "tan(x) using Lambert's formula: ", tanx
print *, "% diff with intrinsic tan: ", (tanx/tan(degx*DEG_TO_RAD)-1.0_wp)*100.0_wp
stop
end program CalcTanx
You can try the above with your compiler: with gfortran, the output is as expected:
C:\Temp>gfortran -Wall -std=f2018 p.f90 -o p.exe
C:\Temp>p.exe
x(degrees): 40.000000000000000
tan(x) using Lambert’s formula: 0.83909963117727993
% diff with intrinsic tan: 0.0000000000000000
C:\Temp>