Dr. Dobb's is part of the Informa Tech Division of Informa PLC

This site is operated by a business or businesses owned by Informa PLC and all copyright resides with them. Informa PLC's registered office is 5 Howick Place, London SW1P 1WG. Registered in England and Wales. Number 8860726.


Channels ▼
RSS

Fortran 2003: Into the Future


July, 2004: Fortran 2003: Into the Future

Big changes to an old favorite

Malcolm is a principal technical consultant for the Numerical Algorithms Group, and an active member of the J3 and WG5 Fortran standardization committees. He can be contacted at malcolmnag.co.uk.


Fortran 2003, the next revision of the Fortran Standard, is in the final stages of the review process before official standardization, which is expected towards the end of 2004. At this writing, voting on the "Final Committee Draft" was drawing to a close, with only very minor glitches being marked for correction. Comments received during this ballot will be processed during the May meeting of the international Fortran committee ISO/IEC JTC1/SC22/WG5; this will produce the Draft International Standard that, all being well, will receive approval in time for publication this year.

Fortran continues to be developed and used for many reasons. Even today, despite the continuing development of general-purpose programming languages (including Fortran), there is no "one size fits all" language. There are various reasons for Fortran's enduring appeal. One reason is its focus on numerical programming, especially its array-handling features. The huge amount of tried and trusted legacy code is also a factor, but perhaps the most significant reason is the ease of use for nonprogrammers; that is to say, programmers who are primarily physicists, engineers, and the like, for whom the computer is merely a tool and programming a minor part of a job.

Execution efficiency was the core to the original design of Fortran back in the 1950s, when it had to wean programmers off assembly coding, and continues to play a major role in the development of the language.

Due to the extensive nature of the changes, I focus in this article on a subset of them; that is, C interoperability, character handling, and object orientation.

Multilanguage Applications

Multilanguage applications have been around for a long time and continue to increase in importance. This has always been a favored approach for those who want to write different parts of their application in the language best suited for those parts; for example, Fortran numeric code with a Java front end.

The last decade or so has seen C increase in popularity, not just as an implementation language but also as an interface language. That is, many libraries and packages have interfaces to C and are callable from other languages only if those languages can interface to C. And many languages fit this bill: Ada, C++, and Java, to name but three. Even when not calling C itself, a C interface can be a useful glue.

These trends have led to the development of C interoperability in Fortran 2003.

C Interoperability

The heart of the C interoperability feature is the ability to describe a C prototype in Fortran and have the compiler generate the right calling sequence. This works both ways, so it is possible to write a Fortran procedure that can easily be called from C. Listing One shows an example of calling C from Fortran. On the other hand, Listing Two illustrates calling Fortran from C, using a portable wrapper for calling a Fortran routine.

Sharing variables is also allowed, though this is not quite so pretty when pointers are involved because the two languages' views of them are so different. All C data pointers get mapped to a single Fortran type (there is another type for function pointers), and procedures are provided to convert between them. Listing Three, for instance, allocates an array (x) and creates a C pointer to its first element, which may be accessed by the C declaration extern float *Data_Array;. The simplification of requiring all data pointer types to have the same representation theoretically limits the interoperability to C implementations with that property; these days, however, that includes most implementations.

Stream Files

Support for reading and writing both binary and text C streams is provided. A new access='stream' specifies a stream file, and the existing form='formatted' and form='unformatted' specify a binary or text stream, respectively.

When writing to an unformatted stream, the intention of the Standard is that there is no processor-inserted data in the file. This standardizes various vendor extensions to this purpose (spelled variously "raw," "transparent," or "binary"). For example, in Listing Four you might reasonably expect the write statement to write exactly 8 bytes to data.file (assuming d to be an IEEE double-precision variable). To achieve this, stream access files have given up the usual ability to skip over (with read) or backspace over records.

When writing to a formatted stream (C text stream), a newline character can be used to indicate a record boundary just as it is in C (the usual Fortran methods using "/" formatting, and so on, remain available). The character that can be used as a newline character for stream output is returned by the intrinsic function newline(). In Listing Five, for example, two lines (records) are written to the file.

String Handling

From the beginning, Fortran took an entirely different approach to character processing from C. Character processing in C is based on arrays of single characters and library routines; there are no character "strings," just arrays.

In Fortran, a character string is a type in its own right, and the intrinsic operations and functions for processing character data operate on character strings (not on arrays).

Length Representation

Perhaps a more significant difference in approach is that of length. In C, the length of a character string is determined by the inclusion of a null character. In Fortran, the length of the string is inherent in the variable. The latter has two advantages:

  • All character values may occur in a character string, including null.
  • The definition of assignment means that buffer overflow is much less likely.

When assigning one character string to another, if the source is shorter, the destination is padded with blanks; if it is longer, the excess characters are ignored. This is a definite improvement over corrupting adjacent memory locations.

Fortran 2003 Improvements

One of the improvements in Fortran 2003 is the ability to have truly variable-length character string variables. Previously, this had been provided by the standard module iso_varying_string. Unfortunately, few compilers implemented the module intrinsically and the portable version leaked memory on any system without a garbage collector, rendering it almost useless.

When assigning to an allocatable-length character, if it is of the wrong length, it is reallocated to be the right length. (The old kind of assignment behavior—truncation/padding—is also available for allocatable-length characters by using a slightly different syntax.)

As with other allocatable functions, the storage space for an allocatable-length function is automatically reclaimed after it has been used. Listing Six presents examples of allocatable character length. Listing Seven, however, is a slightly more interesting example.

ISO 10646 support

Support for ISO 10646 (Unicode) is not required for Fortran 2003 any more than it is required for C, but the Standard does specify how it should be done.

A new intrinsic function selected_char_kind can be used to request ASCII characters or ISO 10646 characters on any processor that supports them. The ISO 10646 characters that result use the UCS-4 encoding (4 bytes per character); this uses more memory than, say, UCS-2 (which uses 2 bytes for most characters), but avoids the complication of surrogates. It also means that the Fortran substring operations and searching functions will operate correctly and efficiently even on characters outside the Basic Multilingual Plane.

Recent changes to the Standard have seen the addition of support for numeric and logical formatting to Unicode characters, conversion between ASCII, default, and Unicode characters, and support for UTF-8 formatted files. The latter is indicated by the new encoding=specifier, for example:

open(...,encoding='UTF-8'...)

Listing Eight is an example of the use of the numeric formatting facilities to create a Japanese date stamp.

Object Orientation

The support for an object-oriented approach to programming and design in Fortran 2003 is loosely based on the Oberon-2 model and includes single inheritance and dynamic dispatch (methods or virtual procedures).

Among the goals of the approach taken in Fortran 2003 were not just to add this support, but to add it in a type-safe manner; that is, to make it impossible to have type errors at runtime. Another goal was to avoid adversely affecting the performance of existing (nonOO) facilities.

Comparing with C++, multiple inheritance was rejected as it was felt that this added too much complexity for too little gain. Parametric polymorphism (templates) was also considered, but it was felt that this would not completely satisfy the desire for the more traditional object-oriented facilities, and that the extra complexity was not worth it at this stage. Also, parameterized derived types (another new feature in Fortran 2003) already provided a limited amount of parametric polymorphism, further limiting the appeal of a completely separate facility. Doubtless, both of these issues will be reconsidered for a later revision of the language.

The facilities added to support inheritance are type extension, polymorphic variables, and type selection. Dynamic dispatch is provided by type-bound procedures, which also provide a more convenient and safer facility of packaging generic operators. Also, unlimited polymorphic pointers provide the illusion of a root type.

Type Extension

Type extension lets you extend an existing derived type by adding zero or more additional components. Only extensible derived types can be extended; however, this includes all derived types that are not sequence types or bind (C) types (the exclusions exist because those types do not have a unique definition); see Listing Nine.

Variables of extended types are declared in the usual fashion:

type(world_point) wp
type(radio_beacon_point) rbp

These two variables have components as follows:

  • The components of wp are wp%latitude and wp%longitude.
  • The components of rbp are rbp%latitude, rbp%longitude, and rbp%frequency. It also has the parent component rbp%world_point, which names the inherited part.

Polymorphic Variables

Polymorphic variables are those having not only a declared type (fixed at compile-time like other variables) but also a dynamic type that may vary at runtime. They are declared with the class keyword:

class(world_point) x

The dynamic type of variable x can be any type in the class of types consisting of type(world_point) and all types that are extensions thereof.

A polymorphic variable can be a dummy argument (in which case, its dynamic type is that of the actual argument), pointer (in which case, its dynamic type is that of its target), or allocatable (in which case, its dynamic type is whatever it is allocated to be).

A polymorphic variable only provides direct access to the components of its declared type (because that is all the compiler knows that it has). To access any facility of its dynamic type, either type selection or type-bound procedures must be used. Even without using those facilities, a polymorphic variable is useful for writing procedures that don't need access to the extended components. The procedure in Listing Ten, for example, can act unchanged on world_points, radio_beacon_points, or on anything else extended from world_point.

A polymorphic pointer can be associated or allocated to have any type in its class. However, only safe-pointer assignments are allowed. In Listing Eleven, the last statement is unsafe (and thus not allowed) because the compiler cannot tell that the dynamic type of wp_ptr is an allowable target for rbp_ptr. To perform this association when the dynamic type is in the right class, the select type construct is used.

When allocating a polymorphic pointer or allocatable variable, two forms are provided for specifying the dynamic type. The first form contains the type specification directly in the allocate statement:

allocate(radio_beacon_point :: wp_ptr)

The other form "clones" a variable; for instance:

allocate(wp_ptr, source=wp_ptr2)

This form makes a copy of the value as well as the type. Again, only "safe" cloning is allowed; as with pointer assignment, select type can be used when the dynamic type is acceptable.

Type Selection

Type selection is provided by the select type construct that combines structured type inquiry with access to the extended components of a polymorphic object. It is similar to select case, but the block executed is selected according to the dynamic type of an expression or variable. An associate-name is associated with the selector. For example, if the selector in Listing Twelve is a simple name and the same name is suitable for the associate-name, the "associate-name=>" part may be omitted.

Type-Bound Procedures

The non_overridable attribute on a type-bound procedure indicates that it cannot be overridden during type extension. This is equivalent to not making the method virtual in Simula/C++, but can be done at any level, not just the top level.

Dynamic dispatch, based on the dynamic type of a single polymorphic object, is provided by type-bound procedures. In fact, they are more general than this, and even in the absence of dynamic dispatch provide a powerful and convenient means of packaging the operations for a type with that type.

Type-bound procedures are declared following the contains statement within a type. In Listing Thirteen, for example, the procedure statements establish two type-bound procedures—accumulate and reset—which can be invoked through any object of class mytype.

type(mytype) x
call x%reset

accumulate is associated with an actual procedure called accumulate, whereas reset is associated with one called reset_mytype. The invoking object is normally passed to the procedure as its first argument (this is actually controlled by the pass and nopass attributes on the procedure statement, which can pass the object to some other argument or not at all).

If type mytype is then extended, the type-bound procedures are inherited unless they are overridden. The attribute non_overridable on the procedure statement provides control over this.

Generic type-bound procedures are also available, including operators, assignment, and user-defined derived-type I/O. Even when type extension is not being used, this is a useful packaging mechanism because the type-bound procedures are always available whenever an object of the type is available (unlike the situation with interface blocks, where careless use of the only clause on the use statement can lose the operations).

Object-Bound Procedures

An object-bound procedure is a procedure that is bound to an individual object rather than the type as a whole. These are simply procedure pointer components, but differ from most other OO languages in that they may pass the invoking object to the procedure. This is provided through the pass and nopass attributes, just as for type-bound procedures.

Differences from Class-Oriented Model

Methods (type-bound procedures with the pass attribute) can be attached to any type. Methods are just ordinary procedures and they can be invoked as such. Invocation as methods is controlled by the type binding to the procedure.

There is no special this or self variable—it's all done by the binding that has the pass attribute. This feature is also available to object-bound procedures (procedure pointer components); indeed, it is the default for both.

Other Improvements

Several limits have been increased; in particular, support for names up to 63 characters long and statements of up to 256 lines is required.

Initialization expressions that need to be evaluated at compile time can now reference almost any intrinsic function. In particular, the mathematical functions can be referenced; this allows as constants things like sqrt(2.0d0), for example.

Other changes include asynchronous I/O parameterized derived types, user-defined derived-type I/O, procedure pointers, abstract interfaces, abstract types, IEEE arithmetic support, I/O rounding control, decimal commas, and enumerations, among others too numerous to mention. Clearly, I've merely scratched the surface of the upcoming new Fortran Standard.

DDJ



Listing One

module c_signal_module
   use iso_c_binding
   integer(c_int), parameter :: sighup = 1, ...
   interface
      function signal(sig, func) bind(C)
         use iso_c_binding
         type(c_funptr) signal, func
         integer(c_int) sig
         value sig, func
      end function
      function raise(sig) bind(C)
         use iso_c_binding
         integer(c_int) raise, sig
         value sig
      end function
   end interface
end module
program example
   ...
   if (signal(sighup,c_funloc(myhandler))/=c_funloc(myhandler)) then
      stop 'Cannot establish signal handler'
   end if
   ...
   if (raise(sighup)/=0) then
      stop 'Cannot raise signal'
   end if
   ...
end program
Back to article


Listing Two
subroutine nag_g05faf(a, b, n, x) bind(c)
   use iso_c_binding
   real(c_double), value :: a, b
   integer(c_int), value :: n
   real(c_double) :: x(n)
   integer, parameter :: nagp = kind(0d0)
   interface
      subroutine g05faf(a, b, n, x)
         import nagp
         integer n
         real(nagp) a, b, x(n)
      end subroutine
   call g05faf(a,b,n,x)
end subroutine
 ...
extern void nag_g05faf(double,double,int,double[]);
Back to article


Listing Three
use iso_c_binding
real, allocatable, target :: x(:)
type(c_ptr),bind(c,name='Data_Array') :: p
 ...
allocate(x(n))
p = c_loc(x)
Back to article


Listing Four
double precision d
 ...
open(27,file='data.file',access='stream',form='unformatted')
 ...
write(27) d
Back to article


Listing Five
open(28,file='/dev/tty',access='stream',form='formatted')
write(28,'(a)') 'Hello'//newline()//'World'
Back to article


Listing Six
character(:), allocatable :: name
 ...
name = ''
! LEN(name) is now 0.
 ...
name = 'John Doe'
! LEN(name) is now 8.
 ...
name = 'John Hancock'
! LEN(name) is now 12.
 ...
name(:) = ''
! LEN(name) remains 12, but contents are now all blank.
Back to article


Listing Seven
function object_filename(input_filename)
   character(*), intent(in) :: input_filename
   character(:), allocatable :: object_filename
   integer :: base_length
   base_length = index(input_filename,'.',back=.true.) - 1
   if (index(input_filename,'/',back=.true.)>=base_length) &
      base_length = len(input_filename)
   allocate(character(base_length+4) :: object_filename)
   object_filename = input_filename(:base_length)//'.obj'
end function
Back to article


Listing Eight
subroutine create_date_string(string)
    intrinsic date_and_time,selected_char_kind
    integer,parameter :: ucs4 = selected_char_kind("ISO_10646")
    character,parameter :: nen = char(int(Z'5e74'),ucs4)
    character,parameter :: gatsu = char(int(Z'6708'),ucs4)
    character,parameter :: nichi = char(int(Z'65e5'),ucs4)
    character(len= *, kind= ucs4) string
    integer values(8)
    call date_and_time(values=values)
    write(string,10) values(1),nen,values(2),gatsu,values(3),nichi
10  format(I0,A,I0,A,I0,A)
  end subroutine
Back to article


Listing Nine
type world_point
   real latitude, longitude
end type
type, extends(world_point) :: radio_beacon_point
   real frequency
end type
Back to article


Listing Ten
real function distance_between(point_1, point_2)
   class(world_point), intent(in) :: point_1, point_2
   distance_between = ... formula using latitude and longitude ...
end function
Back to article


Listing Eleven
class(radio_beacon_point), pointer :: rbp_ptr
class(world_point), pointer        :: wp_ptr
 ...
wp_ptr => rbp_ptr     ! Allowed
rbp_ptr => wp_ptr     ! Not allowed
Back to article


Listing Twelve
select type(point => wp_ptr)
type is (world_point)
   ! Here if the dynamic type is exactly "world_point"
   print *, 'Ordinary world point'
class is (radio_beacon_point)
   ! Here if the dynamic type is in the class "radio_beacon_point"
   ! i.e. including anything extended from it
   print *, 'Radio frequency', point%frequency
class default
   ! Here if nothing else matched
   print *, 'Unrecognized point'
end select
Back to article


Listing Thirteen
type mytype
   private
   ... ! data components omitted
contains
   procedure :: accumulate
   procedure :: reset => reset_mytype
end type mytype
Back to article


Related Reading


More Insights






Currently we allow the following HTML tags in comments:

Single tags

These tags can be used alone and don't need an ending tag.

<br> Defines a single line break

<hr> Defines a horizontal line

Matching tags

These require an ending tag - e.g. <i>italic text</i>

<a> Defines an anchor

<b> Defines bold text

<big> Defines big text

<blockquote> Defines a long quotation

<caption> Defines a table caption

<cite> Defines a citation

<code> Defines computer code text

<em> Defines emphasized text

<fieldset> Defines a border around elements in a form

<h1> This is heading 1

<h2> This is heading 2

<h3> This is heading 3

<h4> This is heading 4

<h5> This is heading 5

<h6> This is heading 6

<i> Defines italic text

<p> Defines a paragraph

<pre> Defines preformatted text

<q> Defines a short quotation

<samp> Defines sample computer code text

<small> Defines small text

<span> Defines a section in a document

<s> Defines strikethrough text

<strike> Defines strikethrough text

<strong> Defines strong text

<sub> Defines subscripted text

<sup> Defines superscripted text

<u> Defines underlined text

Dr. Dobb's encourages readers to engage in spirited, healthy debate, including taking us to task. However, Dr. Dobb's moderates all comments posted to our site, and reserves the right to modify or remove any content that it determines to be derogatory, offensive, inflammatory, vulgar, irrelevant/off-topic, racist or obvious marketing or spam. Dr. Dobb's further reserves the right to disable the profile of any commenter participating in said activities.

 
Disqus Tips To upload an avatar photo, first complete your Disqus profile. | View the list of supported HTML tags you can use to style comments. | Please read our commenting policy.