Portability and Power with the F Programming Language

Walt Brainerd, David Epstein, and Richard Hendrickson
Imagine1, Inc.

Introduction

This article appeared in the 1997 October issue of the Linux Journal.

With the F programming language, the three authors combine their over forty years of language design committee experience to create the world's most portable yet efficient, powerful yet simple programming language. The recent attention demanded by the portability and power of Java is well timed as we show in F that efficiency and readability need not be a victim of cross-platform development.

This article, the first of a two-part series, describes some of the design goals of F and introduces most of the language specifics. The second article discusses the marketing opportunities for F, Linux, and the platform independent applications programmer. The second article will also compare F to C/C++/Java for professional programming and to Pascal and Basic for introductory programming.

Your only warning

Before diving into the F programming language definition, this article begins with some biased-but-almost-factual opinions of the authors. We are not fans of C and C++. Operating system programmers, advanced C++ programmers, or those that enjoy programming and maintaining C or C++ code are advised to skip ahead to the F language definition or further (grin).

Some driving opinions

Listing a few facts and myths about programming languages will help set the stage for the discussion of F. These opinions may communicate some of the ideas behind the F programming language design, allowing one to better understand the motivations of the authors and thus the language.

Fact #1: Programs are read more often than written. From your first programming assignment throughout your professional career, characters are entered once, following some sort of syntax and logic, and read and reread anywhere from twice to hundreds to thousands of times. Programs that cannot be read are simply poor programs.

Myth #1: Abbrev.R++ (abbreviations are good). A programming language with the overall design of abbrev.R++ are quite popular amongst us thinking/creating/coding/debugging speedsters. Afterall, most of us programmers learned how to program before we learned how to type. Abbreviations, however, ranging from a ``}'' instead of the word ``end'', ``int'' instead of ``integer'' and i++ or ++i instead of i=i+1 only add pieces to an already complicated puzzle. As with a piece of abstract art, one day somebody may look at your code and ask, ``That's nice, but what is it?''

Fact #2: Educational languages are dead or dying. As some instructors around the world are searching for a suitable replacement for Pascal, the majority are going-with-the-professional-flow and switching from Pascal to C, C++, or Java for introductory programming courses. There is no telling where computer science would be today if a whole generation of programmers who were brought up on Pascal in the '70s and '80s were presented with the sink-or-swim situation of C++ or Java as a beginning programming language. If Pascal did not exist, the odds are that there would be fewer of us reading this article (if it or the magazine even existed). Surely, a major factor of the rapid evolution of computer science was the once nuturing environment presented by Pascal.

Myth #2: A modern educational replacement for Pascal offers no advantages to the potential professional progammer. Many professionals, particularly those working on large projects, benefit from the advantages of the strict style enforcement that a small programming language offers. A small language can also offer reliable tools (compilers, debuggers, profilers), reliable customer support, reliable error messages, and reliable references (textbooks and on-line documentation.) As F is a language based on existing practice, professionals can make use of the large amount of existing debugged code.

Fact #3: Choosing the wrong implementation programming language affects the overall design, portability and maintainability of large projects. Many companies have been dealt an expensive blow attempting to keep up with a fast moving multi-platformed industry with slow moving software. Whether the software is being enhanced with efficiency and new features or being ported to the latest hardware, a poor choice for the original implementation programming language can result in a fatal loss of company resource. Until feeling the headache, it appeared that C was an appropriate powerful and portable choice. In the early '90s, C++ promised more power and possibly safer features. Today, Java proves safer and portable, but sacrifices efficiency.

Myth #3: The softare crisis has been solved. With no solution to the software crisis in sight, focus has been shifted towards ``market-driven'' distractions like the hot, new programming language filled with more promises than an election-year politician. Meanwhile, most large software projects are still written in C and continue to be delivered late, underfunctioned or unstable. As long as a smaller and simpler language does not sacrifice power, it is time for progammers and their management to wake up to the possibility of shipping stable, complete software on schedule. This starts with the decision of an appropriate implementation programming language. An appropriate choice does not emphasize the potential salary of the programmer leaving the project, but rather:

Fact #4: Most statements in most programming languages fit on one line. In the average program, a minority of the statements are split across many lines. Requiring a semicolon at the end of every statement means requiring a semicolon at the end of almost every line.

Myth #4 Semicolons are a fact of life. Given that the end of a line is most often the end of a statement, the trivial programming language design decision is to use a special character in the rarer case of needing more than one line for a statement. Requiring a semicolon at the end of a statement is tedious and error prone. Languages requiring a semicolon ought to be required to present a nice error message when the semicolon is forgotten. In F, the end of line is the end of statement. If a statement requires more than one line, an ampersand (``&'') is used and the end of a line.

The F Programming Language

A Goal

Starting with an internationally standardized programming language as a base (read on), we set out to create the world's best programming language. Any lesser goal would result in an interesting but unchallenging exercise.

A Language Design

Designing a programming language involves thousands (if not millions) of ideas and decisions. Tradeoffs are constantly weighed between efficiency (both compile time and run time), readability, flexability, familiarity, brevity, redundancy, implementation (compilers and tools), style, elegance, completeness, internationalization, standardization, marketability and target audience to name just a few. The above facts and myths and below principles helped us three avoid personality conflicts (mostly) and drive decisions based on goals:

A pleasant surprise to the biased authors is the pure elegance of F.

F Statements

Except for assignment (=) and pointer assignment (=>), the first word of every F statement identifies the statement. All keywords are reserved words, allowing for specific error messages for incorrect syntax or misspelled keywords. Diagram #1 categorizes all the F statements. The diagram shows that every F procedure, either a subroutine or a function, is contained in a module.

Functions are not Subroutines

In F, a distinction is made between functions and subroutines. Functions are not allowed to have ``side effects'' such as modifying global data. All function arguments must be intent(in); subroutine arguments can be intent(in), intent(out) or intent(inout). The intent is required on all procedure arguments, allowing the compiler to check for misuse and forcing both the beginner and professional to document the intentions.

Intrinsic and User Defined Types

The intrinsic types in F are integer, real, complex, character and logical. User defined types can be constructed from the intrinsic types and user defined types. For example, a person can be constructed to have a name, height, phone number and pointer to the next person. Users can define operators which operate on intrinsic and user defined types.

Entity Attributes

The attributes of an intrinsic or user defined type in F are shown in Diagram #2. Pointers are strongly typed. That is, pointers can point only to objects that are targets. Although this idea makes solid pedagogical sense, the words pointer and target originated for the purpose of better compiler optimization!

Array Language

A sophisticated array language facilitates operations on whole arrays, contiguous and noncontiguous sections and slices of arrays. For example,

arr(5:1:-2, 3, 6:)

is a reference to the two-dimensional array created by taking the elements 5, 3, and 1 in the first dimension of arr and elements from 6 to the upper bound of the third dimension of arr, all in the 3rd plan of the array. If arr is a 5 by 6 by 7 array, the referenced elements would be (5,3,6), (3,3,6), (1,3,6), (5,3,7), (3,3,7), and (1,3,7).

A simpler example shows calculating the sum inner product of a row and a column.

A(i,j) = sum(B(i,:)*C(:,j))

Sum is one of the more than one hundred intrinsic procedures found in F.

Modules

Modules are at the core of all F code. Modules are a data encapsulation mechanism that allows data to be grouped with the procedures that operate on that data. Modules can use other modules. As well, programs and procedures can use modules. Using a module makes the public entities of that module available. Examples of modules are found in Diagram #3.

One does not instantiate an instance of a module as one does with a class in C++ or Java. Instead, the concept of an object is best viewed as a module that defines a public user defined type together with the public procedures that operate on that type. The user of such a module can then declare a scalar or array of the defined type and have access to its procedures.

A public user defined type can be defined to have private components so that the type and its procedures can be referenced, but the parts that make up the type are private to the defining module.

Module-Oriented Programming

Programming in F can be called module-oriented programming. Much like Java's requirement that all procedures appear in classes, all F procedures appear in modules. An F program that does not use any modules cannot call any subroutines or reference any functions. Modules can use other modules to access their public entities. A module, however, is not allowed to use another module for the purpose of exporting the public entities in the used module unless the sole purpose is to collect a group of modules and make all their public entities available from one module.

This simple yet powerful method of module inheritance allows for an involved hierarchy of modules without complicating the investigation required to understand somebody else's code. Any reference to the function foo is known at compile time to be specifically a reference to a public function named foo in a specific module. Even without the aid of compiler tools, F is designed so a quick search (with the aid of grep) for the words ``function foo'' will most likely show function foo's definition line on your screen.

A nice educational feature of F is that every procedure must be declared as either public or private. The result is that a student writing a program that calls a subroutine must learn (or at least enter) the words program, use, call, module, subroutine and public. The public and private list also aids the professional as the first occurance of a procedure name in a module will tell you if it is private and thus isolated to this module.

Overloading Procedures and Operators

F allows overloading procedure names as well as overloading operators. Every reference, however, is resolved at compile time. Thus, the statement

left = swap(int1, real2) * "hello"
displays an overloaded multiplication operator operating on the result of swap(int1, real2) and the character string "hello". As well, swap may be a generic name, but it is also resolved to a specific function at compile time. Finally, the assignment operator (=) may also be overloaded. Once again, a mouse click on the = could conceivably direct you to the specific subroutine that would be called if this was not an intrinsic assignment statement.

More about F--a Surprise?

Before reading this section, you may want to view the example F programs found in Diagram #4 (the Seive of Eratosthenes, Factorial, a binary tree and the Towers of Hanoi) to see if you can guess what once-popular programming language F is based on. The name of the base language is often deceiving as the little known 1995 standard of this language is far more modern than the popular 1977 version. As the standards team is working on making the 2000 version even more object oriented, compilers for the 1990 version have only become available from most vendors during the last few years. If you have not guessed yet, you may be surprised to find out that today's best structured programming language is based on the the world's first structured programming language--Fortran.

Now over 40 years old, more person energy has gone into the evolving definition of Fortran than any other programming language. Every F program is a Fortran program. With stronger object oriented features scheduled for the year 2000 and continued support for the numerically intensive programmer, this recently forgotten programming language is poised for a strong comeback during the next decade.

A strength of Fortran is that the standard is constantly being updated with new features. Vendors are relying on the standards efforts and announcing new compilers after the specifications have been accepted. This is a strong portability statement when compared to languages that are attempting to standardize after various compilers are already in on the market. Another push for portability is being made with the addition of Part 3 of the Fortran standard regarding conditional compilation expected within a year.

What Is Coming Next?

How does F stack up against C, C++, and Java in the office? How does F stack up against Pascal in the classroom? How will High Performance Fortran (HPF) and Fortran 2000 affect F? Tune in next month as we compare F with other programming languages and take a look at F's promising future.

Free for You

The PC Linux educational version of F is freely downloadable. The Imagine1 web page contains the free PC Linux version, and free trail versions for Windows, PowerPC Macintosh, and Unix. You will also find the BNF for F, many example programs, descriptions of F textbooks, and an invitation to join the f-interest-group. As a point of reference, nonLinux users pay US$101 for an F compiler and book.

Acknowledgments

Much thanks belongs to Numerical Algorthms Group, Inc. (NAG) for helping to make the PC Linux version of F available for no cost. Making F available on Windows, Unix, and Macintosh was made possible with the help of Fujitsu Limited, NAG, Absoft Corp., and Salford Software, Inc. Thanks also goes out to the Fortran community for providing immediate interest in the F programming language.

Imagine1 Information

http://www.imagine1.com/imagine1/
info@imagine1.com
+1-520-733-1004
+1-520-298-7404 (fax)
+1-888-323-1758
Imagine1, Inc.
Suite 203
7660 E. Broadway
Tucson, Arizona 85710 USA

The Authors

Walt Brainerd is co-author of about a dozen programming books. He has been involved in Fortran development and standardization for over 25 years and was Director of Technical Work for the Fortran 90 standard. walt@imagine1.com

David Epstein is the project editor of Part 3 of the Fortran standard regarding conditional compilation. He is the developer of the Expression Validation Test Suite (EVT) for Fortran compilers and author of Introduction to Programming with F. david@imagine1.com

Dick Hendrickson has worked on Fortran compiler development in both educational and industrial environments since 1963. He currently is a consultant on compiler optimization and one of the developers of SHAPE, a test suite for Fortran compilers. dick@imagine1.com




Diagram #1. Categorizing all the F statements.

Organizational Constructs

 program
  use ... module
 endprogram        public :: proc-list
                   private :: proc-list
                  contains
                   ........subroutine........function
                  endmodule        use module        use module
                                  endsubroutine     endfunction

Action Constructs

 if / elseif / else / endif
 select case / case / case default / endselect
 do / cycle / exit / enddo
 where / elsewhere / endwhere

Declarations

 type       integer   character   intrinsic    interface
 endtype    real      logical                   module procedure
            complex                            endinterface

Actions

 = (assignment)            allocate          call      stop
 => (pointer assignment)   deallocate        return

Input/Output

 print    open    write    inquire     backspace
 read     close                        rewind
                                       endfile





Diagram #2. Summary of all the F entity attributes.

 Attribute         Description

 pointer / target  Pointers can only point at objects that are targets.
 public / private  All module entities are either public or private.
 intent            All subroutine arguments must be declared as
                   intent in, out, or inout.
                   All function arguments must be intent in.
 dimension         Arrays can be from one to seven dimensions.
 allocatable       For dynamic allocation.
 parameter         A constant.
 save              A static local variable.





Diagram #3. Examples of F modules.

module m_ConstantsOnly
  integer, public, parameter :: TENNIS  = 1
  integer, public, parameter :: SWIM    = 2
  integer, public, parameter :: SAUNA   = 3
  integer, public, parameter :: HOT_TUB = 4
  integer, public, parameter :: NUMBER_OF_ACTIVITIES = 4
  integer, public, parameter :: MAX_MONTHLY_ACTIVITIES = 60
endmodule m_ConstantsOnly

module m_GlobalVariables
 use m_ConstantsOnly, only: MAX_MONTHLY_ACTIVITIES
 private ! makes sure not to export entities from m_ConstantsOnly

 integer, public, dimension(MAX_MONTHLY_ACTIVITIES) :: activities_list
 integer, public :: number_of_monthly_activities
endmodule m_GlobalVariables

module m_types_and_procs
 public :: SetActivity, GetActivity ! public procedures
 private :: SetStartTime, SetEndTime ! private procedures

 type, private :: t_act_schedule ! This type is private to this module
  character(len=14) :: start_day_time ! yyyymmddhhmmss
  integer :: duration_in_seconds
 endtype t_act_schedule

 type, public :: t_agenda ! This type is available to users of this module
  private ! The inside parts of this type are private to this module
   integer :: activity
   type(t_act_schedule) :: act_schedule
 endtype t_agenda

contains ! separates the data entities from the procedures
 subroutine SetActivity(an_activity)
  integer, intent(in) :: an_activity
  ! ...
 endsubroutine SetActivity

 function GetActivity() result(an_activity)
  ! ...
 subroutine SetStartTime()
  ! ...
 subroutine SetEndTime()
  ! ...

endmodule m_types_and_procs





Diagram #4. Sample F programs

!==================  Seive  ======================================
program Sieve_Of_Eratosthenes

!  Find prime numbers using array processing.

!  Strike the Twos and strike the Threes
!  The Sieve of Eratosthenes!
!  When the multiplies sublime
!  The numbers that are left, are prime.

!            From:  Drunkard's Walk, by Frederik Pohl

  integer                            :: last_number
  integer, dimension(:), allocatable :: numbers
  integer                            :: i, number_of_primes, ac

   do
      print *, "What is the last number you want to check?"
      read *, last_number
      select case (last_number)
       case (0)
          exit   !   zero ends the testing
       case (:-1, 1, 2)
          print *, "That's not possible, try again"
       case (3:100000)
          allocate (numbers(last_number))
          !  Initialize numbers array to 0, 2, 3, ..., last_number
          !  Zero instead of 1 because 1 is a special case for primes.
          numbers = (/ 0, (ac, ac = 2, last_number) /)
          do i = 2, last_number
             ! if this number is prime, eliminate all multiples
             if (numbers(i) /= 0) then
                numbers(2*i : last_number : i) = 0
             endif
          enddo

          !  Count the primes.
          number_of_primes = count (numbers /= 0)

          !  Gather them into the front of the array.
          numbers(1:number_of_primes) = pack(numbers, numbers /= 0)

          !  Print them
          print *, "There are ", number_of_primes, &
                   " prime numbers less than or equal to", last_number
          print "(5i7)", numbers(1:number_of_primes)

          deallocate (numbers)

       case default
          print *, "That's too large a value to try"
      end select
   end do
!  Sample output:
! There are   25 prime numbers less than or equal to  100
!     2      3      5      7     11
!    13     17     19     23     29
!    31     37     41     43     47
!    53     59     61     67     71
!    73     79     83     89     97
end program Sieve_Of_Eratosthenes

!==================  Factorial  ======================================

module factorial_demo

 public :: factorial

 logical, save, public :: debug = .false.

contains

 recursive function factorial (n) result (r)

   integer, intent (in) :: n
   integer              :: r

    if ( debug ) then
       print *, "Entering factorial with n = ", n
    end if

    select case (n)
    case (:-1)
      print *, "Bad value for n ", n
      stop
    case (0, 1)
      r = 1
    case (2:)
      r = n*factorial(n-1)
    end select

    if (debug) then
      print *, "Leaving factorial for n= ", n, ", n! = ", r
    end if

 end function factorial

end module factorial_demo

program try_fact
 use factorial_demo

  integer           :: n, v
  character(len=1)  :: d

   outer: do

     print *, "Enter a number"
     read *, n
     print *, "Do you want to debug?"
     do  ! Look for Yes, No, or Quit
       read *, d
       select case (d)
       case ("Y", "y")
         debug = .true.
         exit
       case ("N", "n")
         debug = .false.
         exit
       case ("Q", "q")
         exit outer
       case default
         print *, "Enter `yes', `no' or `quit'!"
       end select
     end do
     v = factorial(n)
     print "(i5, a, i15)", n, "! = ", v

   end do outer

end program try_fact

!==================  Binary Tree  ======================================

! Copyright (c) 1994 Unicomp, Inc.
!
! Developed at Unicomp, Inc.
!
! Permission to use, copy, modify, and distribute this
! software is freely granted, provided that this notice 
! is preserved.

module tree_sort_module

public :: insert, print_tree

type, public :: node
   integer :: value
   type (node), pointer :: left, right
end type node

integer, public :: number

contains

   recursive subroutine insert (t)

      type (node), pointer :: t  ! A tree

      ! If (sub)tree is empty, put number at root
      if (.not. associated (t)) then
         allocate (t)
         t % value = number
         nullify (t % left)
         nullify (t % right)
      ! Otherwise, insert into correct subtree
      else if (number < t % value) then
         call insert (t % left)
      else
         call insert (t % right)
      end if

   end subroutine insert

   recursive subroutine print_tree (t)
   ! Print tree in infix order

      type (node), pointer :: t  ! A tree

      if (associated (t)) then
         call print_tree (t % left)
         print *, t % value
         call print_tree (t % right)
      end if

   end subroutine print_tree

end module tree_sort_module

program tree_sort
! Sorts a file of integers by building a
! tree, sorted in infix order.
! This sort has expected behavior n log n,
! but worst case (input is sorted) n ** 2.

   use tree_sort_module

   type (node), pointer :: t  ! A tree
   integer :: ios

   nullify (t)  ! Start with empty tree
   do
      read (unit=*, fmt=*, iostat = ios) number
      if (ios < 0) then
         exit
      end if
      call insert (t) ! Put next number in tree
   end do
   ! Print nodes of tree in infix order
   call print_tree (t)

end program tree_sort

!==================  Hanoi  ======================================

! Copyright (c) 1994 Unicomp, Inc.
!
! Developed at Unicomp, Inc.
!
! Permission to use, copy, modify, and distribute this
! software is freely granted, provided that this notice 
! is preserved.

module hanoi_module

public :: hanoi

contains

recursive subroutine hanoi (number_of_disks,  &
      starting_post, goal_post)
  
   integer, intent (in) ::  &
   number_of_disks, starting_post, goal_post
   ! all_posts is the sum of the post values 1+2+3
   ! so that the free post can be determined
   ! by subtracting the STARTING_POST and the
   ! goal_post from this sum.
   integer :: free_post
   integer, parameter :: all_posts = 6
 
   if (number_of_disks > 0) then
      free_post =  &
      all_posts - starting_post - goal_post
      call hanoi (number_of_disks - 1,  &
                  starting_post, free_post)

      print *, "Move disk", number_of_disks,  &
            "from post", starting_post,  &
            "to post", goal_post
      call hanoi (number_of_disks - 1,  &
                  free_post, goal_post)
   end if

end subroutine hanoi

end module hanoi_module

program test_hanoi

   use hanoi_module
   integer :: number_of_disks

   read *, number_of_disks
   print *, "Input data  number_of_disks:",  &
         number_of_disks
   print *
   call hanoi (number_of_disks, 1, 3)
  
end program test_hanoi