Efficiency and suitability of using floats, decimals and integers

Oops, probably should edit this.

The goal would rather be something like this.

	function radnab(kappa, luminosity, totalPressure, gfs, mass, temperature)
        use stellar_values, only: WP, PI, SIGMA
        implicit none
        real(WP) :: radnab
        real(WP), intent(in) :: kappa, luminosity, totalPressure, gfs, mass, temperature
        radnab = (3.0_WP * 10.0_WP**kappa * luminosity * totalPressure) / (64.0_WP * gfs * PI * SIGMA * mass * temperature**4)
        return
     end function radnab

The idea is that WP is defined somewhere, in a single place, and is then propagated throughout the code. If/when WP changes, you just recompile and you would then never need to touch this routine again.

Note that I removed the SAVE statement, so now the function could be declared PURE, which can have some important optimization consequences.

Good catch! Oops, edited.

Thank you; that all makes sense.
Though I don’t require multiple definitions, I believe the other reasons are enough now for me to try and get this done.
Again, thank you for your time and patience.

For those who might need or want to do this kind of conversion, here is a perl script that does most of the work:

#!/usr/bin/perl

# usage: fp_convert.pl <infile >outfile
# or     fp_convert.pl infile1 [infile2...] >appendfile

# replace all floating point constants written with an e or d exponent with
# the equivalent e exponent form with trailing _wp.
# matched forms include:
#    123d99
#    123.d99
#    123.456d99
#    .123d99
# with optional leading sign and optional exponent sign.
# embedded spaces and continuation line breaks are not allowed.

# 22-May-2007 -Ron Shepard

while (<>) {
    s/\b([+-]?(?:\d+(?:\.\d*)?|\.\d+))([eEdD])([+-]?\d+)\b/\1e\3_wp/g;
    print;
}

I wrote this so long ago that I have forgotten how it works. Regular expressions are a write-only language, and perl regular expressions are sometimes a little different than in other languages, but hopefully this is useful nonetheless.

I added save to all my declarations because, through this forum, I was told this would ensure the save would occur - that though save is implicit it is not always applied? Is this wrong?

Equally, I’m unsure of your use of the term PURE?
What consequences might this bring?

I would suggest reading the Pure function article on Wikipedia. The benefits are potentially better compiler optimizations, logical code organization (i.e. we enforce a function cannot mutate it’s arguments), and making the function testable.

In the case above, the save was redundant anyways.

1 Like

It would be helpful if you can link the past issues so we can read what has been said before.

Module variables have save by default. Adding the save attribute in this case is technically not wrong, but it could be seen as code bloat / visual noise.

In subroutines and functions it’s best to avoid (hidden) internal state, unless you are really sure you need it. A usage case where save can be helpful is memoization.

Here is an example taken from the Fortran package manager for determining the OS environment:

    !> Determine the OS type
    integer function get_os_type() result(r)
        !!
        !! Returns one of OS_UNKNOWN, OS_LINUX, OS_MACOS, OS_WINDOWS, OS_CYGWIN,
        !! OS_SOLARIS, OS_FREEBSD, OS_OPENBSD.
        !!
        !! At first, the environment variable `OS` is checked, which is usually
        !! found on Windows. Then, `OSTYPE` is read in and compared with common
        !! names. If this fails too, check the existence of files that can be
        !! found on specific system types only.
        !!
        !! Returns OS_UNKNOWN if the operating system cannot be determined.
        character(len=32) :: val
        integer           :: length, rc
        logical           :: file_exists
        logical, save     :: first_run = .true.
        integer, save     :: ret = OS_UNKNOWN
        !$omp threadprivate(ret, first_run)

        if (.not. first_run) then
            r = ret
            return
        end if

        first_run = .false.
        r = OS_UNKNOWN

       ! ... remaining expensive code to figure out which OS we are using
       ! ... not shown here

    end function

The save attribute becomes problematic if a function is supposed to be used from multiple threads as race conditions can occur, and the different threads might not share the same state. In this example which used OpenMP for multi-threaded execution, the !$omp threadprivate directive was used to guarantee that each threads has it’s own private copy.