Rounding in Fortran

Does Fortran provide intrinsic functions to round off real numbers to the specified number of decimal points? Like

round(5.2317,3)

should result in 5.232.

2 Likes

No, there is no such intrinsic function. You can write your own function, like

function round(val, n)
implicit none
real :: val, round
integer :: n
round = anint(val*10.0**n)/10.0**n
end function round

In old times, that would be a good candidate for a statement function, defined as single expression inside any program unit like
round(val,n)=anint(val*10.0**n)/10.0**n
but statement functions were declared obsolescent in Fortran 95 already.

In any case, be warned that the rounded value may often be not representable exactly, so unless you use the proper format, you may get output like 5.2319997 or so.

5 Likes

Oh. That’s a nice way to round a number.

Nice! It might be a great candidate for stdlib.

EDIT: The solution suggested by @kargl based on rouding edit descriptors is preferable IMO. I completely forgot about them and I wonder why I don’t remember to use them myself.

1 Like

Surely for output this could serve, though would require creating the descriptor dynamically. But

  • fw.d may easily fail for values in bigger range
  • I thought the OP wanted to get that value for further proceeding, not just for output
1 Like

And how do I get a rounded value just for output?

Specifically, I would like the round the values from lines 163, 165, 180, and 182 of this code: my newbie code with an ugly output displaying too many decimal places.

In Rust the output can be easily rounded like this:
print!("{:.2}", output); // my output rounded to 2 decimal places

This will give you exactly 2 significant digits or a bunch of astericks: write(*,'(E8.2)') output.

Thanks, @kargl But, this doesn’t work for me…

mass = 65.5
reps = 40
output = 100 * mass / (48.8 + 53.8 * exp (-0.075 * reps)) - mass
write(*,'(E8.2)') output

I use gfortran and running the above code I get 0.61E+02 instead of 61.27. :frowning_face:

Which is the Fortran equivalent of the Rust’s print!("{:.2}", output);?

That’s simple… I want to make a calculation and get 61.27 as the output. I don’t want to get neither 61.2662048 (default) nor ’ 0.61E+02 (your code) nor 61.2700000. Why is it so difficult in Fortran?

Regarding the link, I dare say it is not ‘decent’. I hope you won’t consider me ignorant or a troll–that wasn’t my intention. I’m not a professional programmer but a hobbyist. A half year ago I learnt some Rust in my spare time. Now, I wanted to give a try something new… And I’ve chosen Fortran as it seemed to have the most appealing syntax among around a dozen of languages which called my attention.

But while the basic syntax of Fortran looks clear, there are just too many simple things, which I can find via DuckDuckGo in <30 seconds for e.g., Rust or Python, but frustrate me in Fortran. Rounding numbers should be as simple as print!("{:.2}", output);. And no, I could find no ‘decent’ tutorial of Fortran, whereas documentation of the 2018 standard is hard to read, not to say it looks more like magic.

1 Like

It sounds like you want two decimal places, not two significant digits. You most likely want the F format descriptor, rather than E. A simple summary of edit descriptors is here: Edit descriptors in Fortran Wiki

1 Like

A format that will give 2 digits after the decimal point and however many you need before it and nothing else is (F0.2), But don’t use it if your number happens to be huge(1d0) or tiny(1d0) !

write (*, '(a, F0.2)') 'value: ', output
This code works! :smiling_face_with_tear: Thank you all for the replies! :grinning:

F0.2 being the answer you wanted, I just wanted to mention the method used in the round() function has a limited range for the values it will handle properly, and using that method you might want to normalize
the value to improve the accuracy; perhaps like so …

function round(val,idigits0)
use,intrinsic :: iso_fortran_env, only : dp=>real64,sp=>real32
use,intrinsic :: iso_fortran_env, only : int64
implicit none

!$@(#) M_verify::round(3f): round val to specified number of significant digits

real,intent(in)            :: val
integer,intent(in)         :: idigits0
integer(kind=int64)        :: idigits,ipow
real(kind=dp)              :: aval,rnormal
real                       :: round
   ! make sure a reasonable number of digits has been requested
   idigits=max(1,idigits0)
   aval=abs(val)
!  select a power that will normalize the number (put it in the range 1 > abs(val) <= 0)
   if(aval.ge.1)then
      ipow=int(log10(aval)+1)
   else
      ipow=int(log10(aval))
   endif
   rnormal=val/(10.0d0**ipow)
   if(rnormal.eq.1)then
      ipow=ipow+1
   endif
   !normalize, multiply by 10*idigits to an integer, and so on
   round=real(anint(val*10.d0**(idigits-ipow),kind=dp),kind=dp)*10.d0**(ipow-idigits)
end function round

That function is really to limit number of significant digits, not digits after the decimal ( I was not sure either which was being asked for) but without additional changes that method has a limited range, which if you call it with a normalized value times 10**N where N goes from 1 to 38 will become apparent. It does have value, just have to be aware it has limitations.

It seems like this scaling and printing stuff does the same thing as an e format. If someone wants to see two digits after the decimal, then f0.2 is a good way to print it. If someone wants to see two significant digits, then something like es0.1 is a good way to print it. The 0 in these formats mean that the output field width depends on the value being printed, optional signs, and so on, suitable for printing values within a sentence with text. Something like f7.2 or es8.1 prints the values in fixed width fields, suitable for making tables of aligned numbers. There are also options to control the spacing for the exponent field and optional signs. In fortran, formatting is like a whole language in itself.

1 Like

An interesting point if you actually wanted to use the value with a certain number of significant digits or print it using some format other than an E format you could write it out with an E format and read it back it like the little EG() function, and apply the Fortran rounding options and so on. But I cannot think of a format that lets you print a specified number of significant digits using an F format other than building a specific format depending on the magnitude. But wrting with an E format and then reading back in is a relatively simple solution code-line wise I had not used. So comparing a few approaches the EG() function works OK:

program demo_max
implicit none
integer :: i
real :: r, v
   r=1.234567890
   do i=1,38
      v=r*10.0**i
      write(*,'(g0,t20,g0,t40,g0,t60,e0.3,t80,es0.1,t100,f0.3)')v,round(v,3),eg(v,3),v,v,v
   enddo
contains

function eg(val,idigits)
real :: val
integer :: idigits
character(len=80) :: line,fmt
real :: eg
   write(fmt,'("(e0.",i0,")")')idigits
   write(line,fmt)val
   read(line,'(e50.20)')eg
end function eg

function round(val,idigits0)
use,intrinsic :: iso_fortran_env, only : dp=>real64,sp=>real32
use,intrinsic :: iso_fortran_env, only : int64
implicit none
!$@(#) M_verify::round(3f): round val to specified number of significant digits
real,intent(in)            :: val
integer,intent(in)         :: idigits0
integer(kind=int64)        :: idigits,ipow
real(kind=dp)              :: aval,rnormal
real                       :: round
   ! make sure a reasonable number of digits has been requested
   idigits=max(1,idigits0)
   aval=abs(val)
!  select a power that will normalize the number (put it in the range 1 > abs(val) <= 0)
   if(aval.ge.1)then
      ipow=int(log10(aval)+1)
   else
      ipow=int(log10(aval))
   endif
   rnormal=val/(10.0d0**ipow)
   if(rnormal.eq.1)then
      ipow=ipow+1
   endif
   !normalize, multiply by 10*idigits to an integer, and so on
   round=real(anint(val*10.d0**(idigits-ipow),kind=dp),kind=dp)*10.d0**(ipow-idigits)
end function round

end program demo_max

I have used some variant of the ACCDIG procedure myself plus a few other routines like used in GitHub - urbanjost/numdiff: build numdiff(1) with fpm(1) to compare numeric differences between two files

123.4568           123.0000            123.0000            .123+03             1.2+02              123.457
1234.568           1230.000            1230.000            .123+04             1.2+03              1234.568
12345.68           12300.00            12300.00            .123+05             1.2+04              12345.679
123456.8           123000.0            123000.0            .123+06             1.2+05              123456.789
1234568.           1230000.            1230000.            .123+07             1.2+06              1234567.875
.1234568E+08       .1230000E+08        .1230000E+08        .123+08             1.2+07              12345679.000
.1234568E+09       .1230000E+09        .1230000E+09        .123+09             1.2+08              123456792.000
.1234568E+10       .1230000E+10        .1230000E+10        .123+10             1.2+09              1234567936.000
.1234568E+11       .1230000E+11        .1230000E+11        .123+11             1.2+10              12345678848.000
.1234568E+12       .1230000E+12        .1230000E+12        .123+12             1.2+11              123456782336.000
.1234568E+13       .1230000E+13        .1230000E+13        .123+13             1.2+12              1234567823360.000
.1234568E+14       .1230000E+14        .1230000E+14        .123+14             1.2+13              12345679020032.000
.1234568E+15       .1230000E+15        .1230000E+15        .123+15             1.2+14              123456788103168.000
.1234568E+16       .1230000E+16        .1230000E+16        .123+16             1.2+15              1234567813922816.000
.1234568E+17       .1230000E+17        .1230000E+17        .123+17             1.2+16              12345679481405440.000
.1234568E+18       .1230000E+18        .1230000E+18        .123+18             1.2+17              123456781929152512.000
.1234568E+19       .1230000E+19        .1230000E+19        .123+19             1.2+18              1234567802111655936.000
.1234568E+20       .1230000E+20        .1230000E+20        .123+20             1.2+19              12345678295994466304.000
.1234568E+21       .1230000E+21        .1230000E+21        .123+21             1.2+20              123456789557014429696.000
.1234568E+22       .1230000E+22        .1230000E+22        .123+22             1.2+21              1234567965938888474624.000
.1234568E+23       .1230000E+23        .1230000E+23        .123+23             1.2+22              12345678252014001192960.000
.1234568E+24       .1230000E+24        .1230000E+24        .123+24             1.2+23              123456789275539452985344.000
.1234568E+25       .1230000E+25        .1230000E+25        .123+25             1.2+24              1234567946798590058299392.000
.1234568E+26       .1230000E+26        .1230000E+26        .123+26             1.2+25              12345678315064395976146944.000
.1234568E+27       .1230000E+27        .1230000E+27        .123+27             1.2+26              123456790068172987402551296.000
.1234568E+28       .1230000E+28        .1230000E+28        .123+28             1.2+27              1234567900681729874025512960.000
.1234568E+29       .1230000E+29        .1230000E+29        .123+29             1.2+28              12345677973799630612520239104.000
.1234568E+30       .1230000E+30        .1230000E+30        .123+30             1.2+29              123456789182729271864492818432.000
.1234568E+31       .1230000E+31        .1230000E+31        .123+31             1.2+30              1234567891827292718644928184320.000
.1234568E+32       .1230000E+32        .1230000E+32        .123+32             1.2+31              12345678616041472282791988166656.000
.1234568E+33       .1230000E+33        .1230000E+33        .123+33             1.2+32              123456790996118001286436580491264.000
.1234568E+34       .1230000E+34        .1230000E+34        .123+34             1.2+33              1234567890618366899030299009613824.000
.1234568E+35       .1230000E+35        .1230000E+35        .123+35             1.2+34              12345678906183668990302990096138240.000
.1234568E+36       .1230000E+36        .1230000E+36        .123+36             1.2+35              123456789061836689903029900961382400.000
.1234568E+37       .1230000E+37        .1230000E+37        .123+37             1.2+36              1234567851004285641898130212841848832.000
.1234568E+38       .1230000E+38        .1230000E+38        .123+38             1.2+37              12345678351586531390452626941330587648.000
.1234568E+39       .1230000E+39        .1230000E+39        .123+39             1.2+38              123456786051166514360985072406712287232.000

Well, trying the two methods for rounding a value to a specified number of
significant digits the @Ashwin ROUND() function is much faster on
my platform, but I like that using the internal I/O as I get all the
standard rounding methods with hardly any coding, suggested by @kargl
and @RonShepard (I think; some responses seem to have expired).

A little surprised at differences between different compilers in the g0
output. So for printing you would want it to build another format and
return a character variable, as suggested.

program demo_significant
implicit none
integer :: i
real :: r, v
character(len=*),parameter :: g='(*(g0,1x))'
      
   write(*,g)significant([8765.43210,0.1234567890],5)
      
   write(*,g)significant(1.23456789012345,[1,2,3,4,5,6,7,8,9])
   write(*,g)significant(1.23456789012345,[1,2,3,4,5,6,7,8,9],'RU'),'RU'
   write(*,g)significant(1.23456789012345,[1,2,3,4,5,6,7,8,9],'RD'),'RD'
   write(*,g)significant(1.23456789012345,[1,2,3,4,5,6,7,8,9],'RZ'),'RZ'
   write(*,g)significant(1.23456789012345,[1,2,3,4,5,6,7,8,9],'RN'),'RN'
   write(*,g)significant(1.23456789012345,[1,2,3,4,5,6,7,8,9],'RC'),'RC'
   write(*,g)significant(1.23456789012345,[1,2,3,4,5,6,7,8,9],'RP'),'RP'
contains

pure elemental function significant(val,digits,round)

!@(#) M_verify::significant(3f): round val to specified number of significant digits

real,intent(in)                      :: val
integer,intent(in)                   :: digits
character(len=*),intent(in),optional :: round
character(len=80)                    :: line,fmt
real                                 :: significant
   if(present(round))then
      write(fmt,'("(",a,",e0.",i0,")")')trim(round),digits ! build e0.N format to write specified number of digits as 0.NNNNN+EE
   else
      write(fmt,'("(e0.",i0,")")')digits ! build e0.N format to write specified number of digits as 0.NNNNN+EE
   endif
   write(line,fmt)val                  ! write with specified number of significant diguts
   read(line,'(e50.20)')significant    ! read back into a value
end function significant

end program demo_significant
8765.400 .1234600
1.000000 1.200000 1.230000 1.235000 1.234600 1.234570 1.234568 1.234568 1.234568
2.000000 1.300000 1.240000 1.235000 1.234600 1.234570 1.234568 1.234568 1.234568 RU
1.000000 1.200000 1.230000 1.234000 1.234500 1.234560 1.234567 1.234568 1.234568 RD
1.000000 1.200000 1.230000 1.234000 1.234500 1.234560 1.234567 1.234568 1.234568 RZ
1.000000 1.200000 1.230000 1.235000 1.234600 1.234570 1.234568 1.234568 1.234568 RN
1.000000 1.200000 1.230000 1.235000 1.234600 1.234570 1.234568 1.234568 1.234568 RC
1.000000 1.200000 1.230000 1.235000 1.234600 1.234570 1.234568 1.234568 1.234568 RP

Which function do you mean by that?

The simple rounding function I proposed to @Ashwin’s question (which by itself is not very precise, as specified number of decimal points can be intepreted in many ways) serves a purpose which is not rounding to specific number of significant digits but rather rounding to the given decimal (power) position, that position given by -n, i.e. 10**(-n)

So, comparing to @urbanjost code with normalization the output is as follows

  ARGS       simple-round (@msz59)    round-with-norm (@urbanjost)
1.234567,2       1.23000                       1.20000
123.4567,2     123.4600                      120.0000

Same difference when using internal I/O with E descriptor for output.

Yes, your algorithm lets you return a value for further processing instead of just printing (like the F0.N edit descriptor), and by normalizing it you can get significant digits instead of digits after the decimal like the E format descriptor. That is nice.

This could be useful in comparing float values among many other uses, although there are commonly used methods usually based on a delta that is a factor of EPSILON(0.0) and the method used in ACCDIG(). It does seem like collecting those all into a module and making something something showing safe float comparisons, rounding in Fortran formats, and rounding functions as touched on here should be a topic in the fortran.lang user documents and a stdlib module. It comes up in a lot of different forms.

It was not initially clear to me what rounding type was being requested by the Original Poster but it lead to some interesting discussions. I like the simplicity (from a user coding standpoint) of using the interal read and write, but some timings i tried indicate the method you demonstrated is an order of magnitude faster.

At one time in the past I maintained a collection of libraries from ODE and PDE solvers to steam table libraries and a large collection of various mathematical routines and having a simple utility that easily compared values was invaluable for ensuring the procedures continued to produce correct values on many operating systems and different compilers so methods like these were invaluable because they let you compare numeric values ignoring insignificant round-off Careful selection of proper formats can of course also be useful for that, but procedures like these were more flexible. Perhaps a tool for comparing output files numerically could also be made available, or could be referenced. There were at various times diff(1)-like commands that could handle numbers with a tolerance as well as text differences. Not sure if any of them remain in common use though.

I have various procedures for comparing floats, numeric difference utlities (that need modernized a bit) and some rounding procedures scattered in various modules i keep meaning to consolidate but never seem to get around to. I wonder how many others are doing the same and are reinventing the wheel along with me!