- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
I want to use to the fpp preprocessor to achieve the following, however fpp doesnt seem to support the preprocessing of partial words. Is there a work around?
#ifdef DOUBLE_PRE
#define pre_ D0
#else
#define pre_ E0
#endif
...
myrealvar = 10.0pre_
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Larry R. wrote:
I want to use to the fpp preprocessor to achieve the following, ..
Larry,
Depending on what all needs you have for the preprecessor, you may wish to consider an alternative based on Intel Fortran compiler directive syntax which I find more flexible:
MODULE MyKinds USE, INTRINSIC :: ISO_FORTRAN_ENV, ONLY : I4 => INT32, SP => REAL32, DP => REAL64, QP => REAL128 IMPLICIT NONE !DEC$ IF DEFINED (SINGLE) INTEGER(I4), PARAMETER :: WP = SP !DEC$ IF DEFINED (DOUBLE) INTEGER(I4), PARAMETER :: WP = DP !DEC$ IF DEFINED (QUAD) INTEGER(I4), PARAMETER :: WP = QP !DEC$ ELSE INTEGER(I4), PARAMETER :: WP = SP !.. Default !DEC$ ENDIF END MODULE MyKinds PROGRAM p USE MyKinds, ONLY : WP REAL(WP) :: x x = 1E3_wp PRINT *, " x = ", x STOP END PROGRAM p
Link Copied
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
I created a small program from your example above, and it seemed to work;
[ ~/project]$ ifort -fpp foo.f90 -E
# 1 "foo.f90"
# 5
myrealvar = 10.0E0
end
What did you see?
--Lorri
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
larry R.: I don't understand what you mean by "partial words". Perhaps, in your real code, you have C-style preprocessor directives that do not start in column-1 of the source file. For example, the following will not work
#ifdef DOUBLE_PRE #define pre_ D0 #else #define pre_ E0 #endif program test real x double precision dx dx = 10.0pre_ x = 10.0pre_ write(*,*)x,dx end program
Moving '#' to the first column in Lines 2 and 4 will take care of the problem.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
mecej4 wrote:
larry R.: I don't understand what you mean by "partial words". Perhaps, in your real code, you have C-style preprocessor directives that do not start in column-1 of the source file. For example, the following will not work
#ifdef DOUBLE_PRE #define pre_ D0 #else #define pre_ E0 #endif program test real x double precision dx dx = 10.0pre_ x = 10.0pre_ write(*,*)x,dx end programMoving '#' to the first column in Lines 2 and 4 will take care of the problem.
mecej4,
Does this hold the risk of loss of precision and mixed-mode arithmetic since a given instance have a single definition of "pre_" and a user uses the E0 definition with a real kind higher than that supported by E notation (e.g., your double precision dx)?
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Larry R. wrote:
I want to use to the fpp preprocessor to achieve the following, ..
Larry,
Depending on what all needs you have for the preprecessor, you may wish to consider an alternative based on Intel Fortran compiler directive syntax which I find more flexible:
MODULE MyKinds USE, INTRINSIC :: ISO_FORTRAN_ENV, ONLY : I4 => INT32, SP => REAL32, DP => REAL64, QP => REAL128 IMPLICIT NONE !DEC$ IF DEFINED (SINGLE) INTEGER(I4), PARAMETER :: WP = SP !DEC$ IF DEFINED (DOUBLE) INTEGER(I4), PARAMETER :: WP = DP !DEC$ IF DEFINED (QUAD) INTEGER(I4), PARAMETER :: WP = QP !DEC$ ELSE INTEGER(I4), PARAMETER :: WP = SP !.. Default !DEC$ ENDIF END MODULE MyKinds PROGRAM p USE MyKinds, ONLY : WP REAL(WP) :: x x = 1E3_wp PRINT *, " x = ", x STOP END PROGRAM p
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
FortranFan wrote:
Quote:
Larry R. wrote:
I want to use to the fpp preprocessor to achieve the following, ..
Larry,
Depending on what all needs you have for the preprecessor, you may wish to consider an alternative based on Intel Fortran compiler directive syntax which I find more flexible:
MODULE MyKinds USE, INTRINSIC :: ISO_FORTRAN_ENV, ONLY : I4 => INT32, SP => REAL32, DP => REAL64, QP => REAL128 IMPLICIT NONE !DEC$ IF DEFINED (SINGLE) INTEGER(I4), PARAMETER :: WP = SP !DEC$ IF DEFINED (DOUBLE) INTEGER(I4), PARAMETER :: WP = DP !DEC$ IF DEFINED (QUAD) INTEGER(I4), PARAMETER :: WP = QP !DEC$ ELSE INTEGER(I4), PARAMETER :: WP = SP !.. Default !DEC$ ENDIF END MODULE MyKinds PROGRAM p USE MyKinds, ONLY : WP REAL(WP) :: x x = 1E3_wp PRINT *, " x = ", x STOP END PROGRAM p
Hi Fortran Fan,
I like this solution but is there an alternative way to declare the exponent value? My reason for wanting to use D0 is to stop fortran from rounding when initializing variables with smaller precision numbers. For example, in double precision mode, if I initialized var = 10.15, fortran says var = 10.1499996185303. I know I should simply initialize as var = 10.1500000000000, however I am working with alot of code and it would be quite tedious to go through and do that for all variables.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Since f90, specifying a data type takes the place of the D promotion to double precision.
I don't see any reason why fpp conditional compilation couldn't be used with the f2008 data type naming suggested by Fortran Fan.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Tim Prince wrote:
Since f90, specifying a data type takes the place of the D promotion to double precision.
I don't see any reason why fpp conditional compilation couldn't be used with the f2008 data type naming suggested by Fortran Fan.
Tim, I am looking for a method to make a condition compilation for the exponent value of a variable to prevent fortran from rounding double precision numbers.
What I am seeing is that double precsion data type declaration takes the place of D promotion, but not D0, D1, D3 ect.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
The common way of handling precision (single or double for the whole program) is to define a kind integer, say, 'wp' for working precision, inside a module, call it 'myprec', as follows:
module myprec integer, parameter :: wp = kind(1.0) end module
Then, wherever you have a constant in an expression, initialization expression, etc., you simply say, e.g., 3.14159264_wp, and add "USE myprec" in that subprogram. If you want, subsequently, to change from single to double precision, you need only change 1.0 to 1.0d0 in the module, and recompile everything that uses the module.
You can also use the selected_real_kind intrinsic function for more elaborate specifications of the kind of real numbers you wish to use.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
var = 10.1500000000000 will not work. The approach with var = 10.15_wp or var = 0.1015e2_wp will work.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Larry R. wrote:
Hi Fortran Fan,
I like this solution but is there an alternative way to declare the exponent value? My reason for wanting to use D0 is to stop fortran from rounding when initializing variables with smaller precision numbers. For example, in double precision mode, if I initialized var = 10.15, fortran says var = 10.1499996185303. I know I should simply initialize as var = 10.1500000000000, however I am working with alot of code and it would be quite tedious to go through and do that for all variables.
Larry,
As you may be aware, generally recommended coding practices (and which my colleagues and I strive to follow closely) include: avoid "magic" numbers in code and therefore, use named constants only and for commonly used constants in STEM fields, one can base them on easily accessible, but highly reliable and traceable references such as US NIST (www.nist.gov) or CRC Handbook, etc. Include all the significant digits that are reported (e.g., for pi), even if they are greater than your typical working precision (let the compiler round-down per its rules but at least the code execution will be consistent for a given compiler with some selected settings).
With that in mind, you can a "constants" module that utilizes the KINDS module in Quote #4 above and "collects" all the constants in one place; the other code can then reference this module:
MODULE MyConstants USE MyKinds, ONLY : WP, ... !.. Fundamental physicals constants from US NIST website: ! http://physics.nist.gov/cgi-bin/cuu/Value?c|search_for=universal_in! REAL(WP), PARAMETER :: c0 = 299792458.0_wp !.. Speed of light in vacuum, m/s REAL(WP), PARAMETER :: G = 6.67384E-11_wp !.. Newtonian constant of gravitation, m3 kg-1 s-2 .. END MODULE MyConstants
And you can see in the above snippet a couple of options (c0, G) on how to specify the numerical values. Try the above out with a working precision of Fortran 2008 intrinsic (defined in ISO_FORTRAN_ENV) of REAL64 (i.e., KIND=8 in Intel Fortran or the old-fashioned DOUBLE PRECISION) and see what you get.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
While I am myself a big fan of the usage in Quote #5, did you know that there is a quirk of the standard in that regard?
module invisible ! Pretend this module definition is not in the same file. implicit none integer, parameter :: REAL64 = kind(1.0) end module invisible module M1 use invisible implicit none interface sub module procedure S1 module procedure S2 end interface sub contains subroutine S1(x) use ISO_FORTRAN_ENV real(REAL32) x write(*,*) 'Single-precision version was called.' end subroutine S1 subroutine S2(x) use ISO_FORTRAN_ENV real(REAL64) x write(*,*) 'Double-precision version was called.' end subroutine S2 end module M1 module M2 use M1 contains subroutine S3 use ISO_FORTRAN_ENV, only: wp => REAL64 use ISO_FORTRAN_ENV implicit none real(REAL64) x call sub(x) end subroutine S3 end module M2 program P use M2 implicit none call S3 end program P
The program actually calls the single precision version of sub. The line that causes the problem is the USE with ONLY: clause. If that were commented out, the double precision version would have been called. Not as dangerous as the quirks of the CMPLX intrinsic perhaps, but still a foot stuck out to trip the unwary.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
You'd have a similar situation with using fpp and competing #define's...
however, fpp will/should complain about re-#define without #undef(ine)
Fortran, as in above example #12, will permit you to redefine variables local scope that are otherwise defined in a module.
#12 may be a good case argument to have an attribute to declare a variable/parameter as not being re-definable, or at least warn on redefinition.
Jim Dempsey
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Repeat Offender wrote:
While I am myself a big fan of the usage in Quote #5, did you know that there is a quirk of the standard in that regard?
...
The program actually calls the single precision version of sub. The line that causes the problem is the USE with ONLY: clause. If that were commented out, the double precision version would have been called. Not as dangerous as the quirks of the CMPLX intrinsic perhaps, but still a foot stuck out to trip the unwary.
A good catch. I wonder if it would make sense for the standard to require something along the lines of
INTEGER, PARAMETER, NON_INTRINSIC :: REAL64 = ..
whenever coders give variables the same names as those in the intrinsic modules and if that help avoid the issue raised by RO e.g., if some such keyword is attributed, then the user defined thing gets used instead of the intrinsic (similar to the EXTERNAL attribute on procedures with the same names as intrinsic functions). Steve may have some thoughts on introducing such a thing into a future Fortran standard, or may have other suggestions on the issue raised by RO.
P.S.> Note the keyword NON_INTRINSIC I refer to above is already part of the standard (starting with 2003, I believe) but as I understand it, it is currently relevant to USE statements for modules where a coder might have access to user modules with the same name as the intrinsic modules (5 of them now, if I'm not mistaken such as ISO_FORTRAN_ENV). So my thoughts are reusing this keyword as a variable attribute, if that makes sense!
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Regarding RO's example in post 12, the ONLY is not relevant. What is relevant is the rename of ISO_FORTRAN_ENV's REAL64 to "wp", which is then not used in subroutine S3. This means that the local name REAL64 is host inherited from module M1. While I agree that the rules for use and host association can sometimes trip you up (see the "Up Periscope" section of Doctor Fortran in "Too Much of a Good Thing?"), I don't consider this a "quirk".
FortranFan's suggestion of NON_INTRINSIC to apply to other declarations is sort of beside the point - there is nothing special about the use of an intrinsic module here. A local declaration of a symbol always overrides any host-associated symbol. (If the same symbol is use-associated, then that's an error because you're not allowed to reference a symbol whose name is given to two or more local identifiers.)
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Steve Lionel (Intel) wrote:
.. there is nothing special about the use of an intrinsic module here. A local declaration of a symbol always overrides any host-associated symbol. (If the same symbol is use-associated, then that's an error because you're not allowed to reference a symbol whose name is given to two or more local identifiers.)
Steve,
Do you have an example of "If the same symbol is use-associated, then that's an error because you're not allowed to reference a symbol whose name is given to two or more local identifiers"? I thought such stipulations in the standards precluded code as shown below, but it doesn't appear to be so, at least with Intel Fortran and gfortran:
MODULE M1 IMPLICIT NONE INTEGER, PARAMETER :: REAL64 = KIND(1.0) END MODULE M1 MODULE M2 USE M1, ONLY : REAL64 IMPLICIT NONE CONTAINS SUBROUTINE S USE ISO_FORTRAN_ENV, ONLY : REAL64 IMPLICIT NONE REAL(REAL64) x PRINT *, " KIND(x) = ", KIND(x) END SUBROUTINE S END MODULE M2
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
program test use, intrinsic :: iso_fortran_env integer, parameter :: REAL64=13 ! Error end
Your example has host association, with different rules, as Richard Maine explained in comp.lang.fortran.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
And this may also help illustrate:
module moda integer, parameter :: x = 3 end module moda module modb integer, parameter :: x = 4 end module modb program test use moda use modb print *, x ! Ok until this statement end
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
What pulls my chain here is not the way use association overrides host association (I just put that in there so that removing a name from the namespace wouldn't cause an error because there was a backup name available from the host scope) but the rules about renaming. At its core, consider what happens if you have a module M2 with only one symbol, X. It just seems counterintuitive to me that 'USE M2' and 'USE M2, X=>X' should be semantically distinct, but the renaming rules dictate that they are.
In this example, as it stands, it prints out the X from M1, but if you uncomment the 'USE M2, X=>X' line, it prints out the X from M2. The 'USE M2' line makes all entities from M2 available but a rename clause on a different line can make entities available only under a different name and that seems confusing to be because looking at 'USE M2' in isolation it seems that everything in M2 should be available under its original name, but it turns out that this is negotiable, so you have to examine all USE statements for M2 to be sure whether any entity can be accessed via its original name.
module M1 implicit none character(*), parameter :: x = 'The X from module M1.' end module M1 module M2 implicit none character(*), parameter :: x = 'The X from module M2.' end module M2 module M3 use M1 implicit none contains subroutine sub ! use M2, x => x use M2 use M2, y => x implicit none write(*,'(a)') x end subroutine sub end module M3 program P use M3 implicit none call sub end program P
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Ah, but you're really not accessing it by its original name. You're accessing by a local name that happens to be spelled the same as the original name. You're right that you have to look at all the USE lines to check for ONLY and renames to get the sense of what entities are accessible and what their local names are. What you're touching on is that USE essentially creates a bunch of aliases for module entities - usually with the same spelling as the original name, but not always. In fact, this distinction becomes more important when it comes to public/private accessibility in that all the new local names start out fresh with accessibility.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
>>this distinction becomes more important when it comes to public/private accessibility in that all the new local names start out fresh with accessibility.
Could a module USE a different module on a statement containing x => y and have y private?
Jim Dempsey

- Subscribe to RSS Feed
- Mark Topic as New
- Mark Topic as Read
- Float this Topic for Current User
- Bookmark
- Subscribe
- Printer Friendly Page