Trying to display and use large numbers (Fibonacci sequence)

hi guys,
I was experimenting and trying to display the first 10000 Fibonacci sequence of numbers (for fun :stuck_out_tongue: ). Unfortunately I got a lot of “infinities” toward the end.

program fnum
  use iso_fortran_env
  implicit none


  real(kind=real64) :: n_1,n_2,x
  integer :: i
  integer,parameter :: n=10000

  n_1 = 1.
  n_2 = 0.

  do i=1,n
     x = n_2 + n_1
     print *, ' '
     print *, x
     print *, ' '
     n_2 = n_1
     n_1 = x
  end do
  
end program fnum

How do I get the actual numbers to display and which libraries do I use to achieve this ?

Thanks

Compiler used : ifort
flags: -O3
OS: Fedora 36

Replacing the real64 with real128 to use quadruple precision, the last numbers printed for ifort and gfortran are

5.443837311356528133873426099375060E+2089
5.44383731135652813387342609937505988E+2089

Btw the standard does not mandate that compilers offer more than two precisions of reals, but at least these two compilers do.

1 Like

Thank you ! Could you also tell me how to display it in it’s full form please ?
Like instead of 1.0E2 , I would like it to display 100.0

1 Like

Replace

print*,x

with

print "(f0.0)", x

The f0.0 means print the number in as few spaces as possible with 0 numbers after the decimal point.

1 Like

Thank you once again !

Someone messaged me that

The 10,000th Fibonacci number is 54438373113565281338734260993750380135389184554695967026247715841208582865622349017083051547938960541173822675978026317384359584751116241439174702642959169925586334117906063048089793531476108466259072759367899150677960088306597966641965824937721800381441158841042480997984696487375337180028163763317781927941101369262750979509800713596718023814710669912644214775254478587674568963808002962265133111359929762726679441400101575800043510777465935805362502461707918059226414679005690752321895868142367849593880756423483754386342639635970733756260098962462668746112041739819404875062443709868654315626847186195620146126642232711815040367018825205314845875817193533529827837800351902529239517836689467661917953884712441028463935449484614450778762529520961887597272889220768537396475869543159172434537193611263743926337313005896167248051737986306368115003088396749587102619524631352447499505204198305187168321623283859794627245919771454628218399695789223798912199431775469705216131081096559950638297261253848242007897109054754028438149611930465061866170122983288964352733750792786069444761853525144421077928045979904561298129423809156055033032338919609162236698759922782923191896688017718575555520994653320128446502371153715141749290913104897203455577507196645425232862022019506091483585223882711016708433051169942115775151255510251655931888164048344129557038825477521111577395780115868397072602565614824956460538700280331311861485399805397031555727529693399586079850381581446276433858828529535803424850845426446471681531001533180479567436396815653326152509571127480411928196022148849148284389124178520174507305538928717857923509417743383331506898239354421988805429332440371194867215543576548565499134519271098919802665184564927827827212957649240235507595558205647569365394873317659000206373126570643509709482649710038733517477713403319028105575667931789470024118803094604034362953471997461392274791549730356412633074230824051999996101549784667340458326852960388301120765629245998136251652347093963049734046445106365304163630823669242257761468288461791843224793434406079917883360676846711185597501

but a 128-bit quad precision real only has enough precision to get the first 34 (or so) decimal digits correct.

There exist Fortran packages for multiple precision arithmetic.

1 Like

Which library is that, and how do I use it ?

For example, FMLIB.

1 Like

Thank you

The posts so far have concentrated on pushing the calculation attempt towards obtaining the largest Fibonacci number possible with a specific kind of arithmetic. Note, however, that there are other issues that should be respected as well. One of them is that real or double precision numbers cannot represent large integers accurately. Single precision reals have only 23+1 bits for the mantissa, and you can verify that F_{37} = 24157817 has the same representation as 24157816 in single precision real. As a result, if you program a Fibonacci sequence calculation using reals, the large numbers that your program prints may be impressive, but they may not all be Fibonacci numbers. Here is a demonstration:

program fib
implicit none
integer i,n,f,fp,fn
real rf,rfp,rfn
n = 100
fp = 0; rfp = 0.0
f  = 1; rf  = 1.0
do i=2,n
  fn = f+fp; rfn = rf+rfp
  fp = f   ; rfp = rf
  f = fn   ; rf  = rfn
  print '(2I15,4x,F16.1)',i,f,rf
  if(huge(n)-f < fp .or. nint(rf) /= f)exit
end do
end program

If you switch to 8-byte integers and 8-byte reals in this kind of calculation, you may find that the calculation fails at about F_{77}, reporting 5527939700884758, which is in error in the last digit. It usually takes a lot of effort to achieve mathematical correctness.

1 Like

As well as arbitrary precision there are other ways to create accurate numbers by calculating string values, and other examples of implementation in other languages that are interesting to compare. For example:

A Formula for the n-th Fibonacci number

http://www.rosettacode.org/wiki/Fibonacci_sequence#Fortran

2 Likes

@mecej4 and @urbanjost Thank you guys for the input as well.