Tuesday, April 29, 2014

f90 data type

f90 Language elements

The basic components of the Fortran language are its character set. The members are:
  • the letters A ... Z and a ... z (which are equivalent outside a character context);
  • the numerals 0 ... 9;
  • the underscore _; and
  • the special characters
            =  :  +  blank  -  *  /  (  )  ,  .  $  ' (old)
            !  "  %  &  ;   <  >  ?                   (new)
    
From these components, we build the tokens that have a syntactic meaning to the compiler. There are six classes of token:
Label:       123                  Constant: 123.456789_long
 
Keyword:     ALLOCATABLE          Operator: .add.
 
Name:        solve_equation (up to 31 characters, including _)
 
Separator:  /   (   )   (/   /)   ,   =   =>   :   ::   ;   %
From the tokens, we can build statements. These can be coded using the new free source form which does not require positioning in a rigid column structure:
FUNCTION string_concat(s1, s2)                ! This is a comment
   TYPE (string), INTENT(IN) :: s1, s2
   TYPE (string) string_concat
   string_concat%string_data = s1%string_data(1:s1%length) // &
      s2%string_data(1:s2%length)             ! This is a continuation
   string_concat%length = s1%length + s2%length
END FUNCTION string_concat
Note the trailing comments and the trailing continuation mark. There may be 39 continuation lines, and 132 characters per line. Blanks are significant. Where a token or character constant is split across two lines:
               ...        start_of&
        &_name
               ...   'a very long &
        &string'
a leading & on the continued line is also required. Automatic conversion of source form for existing programs can be carried out by convert.f90. Its options are:
  • significant blank handling;
  • indentation;
  • CONTINUE replaced by END DO;
  • name added to subprogram END statement; and
  • INTEGER*2 etc. syntax converted.
Fortran has five intrinsic data types. For each there is a corresponding form of literal constant. For the three numeric intrinsic types they are:

INTEGER

        1   0   -999   32767   +10
for the default kind;
but we may also define, for instance for a desired range of [-10^4, +10^4], a named constant, say two_bytes
                !   I need an integer in range of  [-10^4, +10^4],
        INTEGER, PARAMETER :: two_bytes = SELECTED_INT_KIND(4)  ! 4 means 10^4  


eg: 
INTEGER, PARAMETER :: two_bytes = SELECTED_INT_KIND(4)    ! [-10^4, 10^4]
INTEGER (KIND = two_bytes) ::  ii         !   :: required
INTEGER  jj              ! nothing before jj
! kind() returns number of bytes to store variable
print *, kind(ii)  ! customized integer type       ,   2 bytes
print *, kind(34_two_bytes)  !   2 bytes  , attach kind type to a constant 34 to indicate its type.
print *, kind(jj)  ! default integer type              ,   4 bytes
print *, range(ii)  ! customized integer type     ,  4    [-10^4, 10^4]
print *, range(jj)  ! default integer type            ,  9    [-10^9, 10^9]


! [-0.123*10^40, 0.123*10^40]
INTEGER, PARAMETER :: realType = SELECTED_REAL_KIND(3,40) 
real (KIND = realType) ::  r1
real r2
print *, kind(r1)  ! customized integer type
print *, kind(r2)  ! default integer type
print *, range(r1)  ! customized integer type
print *, range(r2)  ! default integer type
           8         ! bytes
           4
         307       ! range
          37
 
Also, in DATA statements, binary, octal and hexcadecimal constants may be used:
        B'01010101'   O'01234567'   Z'10fa'

REAL

There are at least two real kinds - the default, and one with greater precision (this replaces DOUBLE PRECISION). We might specify
        INTEGER, PARAMETER :: long = SELECTED_REAL_KIND(9, 99)
for at least 9 decimal digits of precision and a range of 10*(-99) to 10**99, allowing
        1.7_long    ! use a named constant
Also, we have the intrinsic functions
        KIND(1.7_long)   PRECISION(1.7_long)   RANGE(1.7_long)
that give in turn the kind type value, the actual precision (here at least 9), and the actual range (here at least 99).

COMPLEX

This data type is built of two integer or real components:
        (1, 3.7_long)
The forms of literal constants for the two non-numeric data types are:

CHARACTER

        'A string'   "Another"   'A "quote"'   ''
(the last being a null string). Other kinds are allowed, especially for support of non-European languages:
        2_'   '
and again the kind value is given by the KIND function:
        KIND('ASCII')

LOGICAL

Here, there may also be different kinds (to allow for packing into bits):
        .FALSE.   .true._one_bit
and the KIND function operates as expected:
        KIND(.TRUE.)
The numeric types are based on model numbers with associated inquiry functions (whose values are independent of the values of their arguments):
     DIGITS(X)               Number of significant digits
     EPSILON(X)              Almost negligible compared to one (real)
     HUGE(X)                 Largest number
     MAXEXPONENT(X)          Maximum model exponent (real)
     MINEXPONENT(X)          Minimum model exponent (real)
     PRECISION(X)            Decimal precision (real, complex)
     RADIX(X)                Base of the model
     RANGE(X)                Decimal exponent range
     TINY(X)                 Smallest postive number (real)
These functions are important for portable numerical software. We can specify scalar variables corresponding to the five intrinsic types:
        INTEGER(KIND=2) i
        REAL(KIND=long) a
        COMPLEX         current
        LOGICAL         Pravda
        CHARACTER(LEN=20) word
        CHARACTER(LEN=2, KIND=Kanji) kanji_word
where the optional KIND parameter specifies a non-default kind, and the LEN= specifier replaces the *len form. The explicit KIND and LEN specifiers are optional:
        CHARACTER(2, Kanji) kanji_word
works just as well. For derived-data types we must first define the form of the type:
        TYPE person
           CHARACTER(10) name
           REAL          age
        END TYPE person
and then create structures of that type:
        TYPE(person) you, me
To select components of a derived type, we use the % qualifier:
        you%age
and the form of a literal constant of a derived type is shown by:
        you = person('Smith', 23.5)
which is known as a structure constructor. Definitions may refer to a previously defined type:
        TYPE point
           REAL x, y
        END TYPE point
 
        TYPE triangle
           TYPE(point) a, b, c           !! TYPE(point) together
        END TYPE triangle
 
and for a variable of type triangle, as in
        TYPE(triangle) t            !!  TYPE(triangle) together
we have components of type point:
        t%a   t%b   t%c           !! how to refer to each component
which, in turn, have ultimate components of type real:
        t%a%x   t%a%y   t%b%x   etc. 
 
type base
   integer, dimension(3) :: aa=(/1,2,3/)
end type base
 
We note that the % qualifier was chosen rather than . because of ambiguity difficulties. Arrays are considered to be variables in their own right. Given
        REAL a(10)
        INTEGER, DIMENSION(0:100, -50:50) :: map
(the latter an example of the syntax that allows grouping of attributes to the left of :: and of variables sharing the attributes to the right), we have two arrays whose elements are in array element order (column major), but not necessarily in contiguous storage. Elements are, for example,
        a(1)               a(i*j)
and are scalars. The subscripts may be any scalar integer expression. Sections are
        a(i:j)               ! rank one
        map(i:j, k:l:m)      ! rank two
        a(map(i, k:l))       ! vector subscript
        a(3:2)               ! zero length
Whole arrays and array sections are array-valued objects. Array-valued constants (constructors) are available:
        (/ 1, 2, 3, 4, 5 /)
        (/ (i, i = 1, 9, 2) /)
        (/ ( (/ 1, 2, 3 /), i = 1, 10) /)
        (/ (0, i = 1, 100) /)
        (/ (0.1*i, i = 1, 10) /)
making use of the implied-DO loop notation familiar from I/O lists. A derived data type may, of course, contain array components:
        TYPE triplet
           REAL, DIMENSION(3) :: vertex
        END TYPE triplet
        TYPE(triplet), DIMENSION(4) :: t
so that
       t(2)           is a scalar (a structure)
       t(2)%vertex    is an array component of a scalar
There are some other interesting character extensions. Just as a substring as in
        CHARACTER(80), DIMENSION(60) :: page
        ... = page(j)(i:i)         ! substring
was already possible, so now are the substrings
        '0123456789'(i:i)
        you%name(1:2)
Also, zero-length strings are allowed:
        page(j)(i:i-1)       ! zero-length string
Finally, there are some new intrinsic character functions:
      ACHAR                 IACHAR  (for ASCII set)
      ADJUSTL               ADJUSTR
      LEN_TRIM              INDEX(s1, s2, BACK=.TRUE.)
      REPEAT                SCAN  (for one of a set)
      TRIM                  VERIFY(for all of a set)
 

Fortran 90: Derived Data Types

The Fortran 90 derived data type is similar to C structures and also has some similarities with C++ classes. The syntax for declaring a derived type, is
type mytype
   integer:: i
   real*8 :: a(3)
end type mytype
To create a variable of type mytype, use
type (mytype) var
An array of mytype can also be created.
type (mytype) stuff(3)
Elements of derived types are accessed with the "%" operator. For instance,
var%i = 3
var%a(1) = 4.0d0
stuff(1)%a(2) = 8.0d0
The real power of derived types comes with the ability to choose bewteen functions (or subroutines) based on the type of their arguments. Different functions can be called by the same name, depending on whether the argument type is real, integer,or even a derived type. Intrinsic Fortran routines have always had this ability, the simplest example being choosing between single and double precision versions of the function. Now it can be extended to user's routines and defined data types as well. See the example in the section on intefaces for subroutines . The compiler is free to store the constitutients of a derived type how it chooses. To force the derived type to be stored contiguously, use the sequence keyword. For example,
type mytype
   sequence
   integer:: i
   real*8 :: a(3)
end type mytype
The IBM compiler seems to require this keyword if a derived type is the argument of a subroutine or function.


Pointer type : 
eg 1: 
integer , pointer :: ip    !! ip is a pointer to a single data
integer, allocatable, dimension(:), target :: iarr
allocate(iarr(20))

do i = 1, 20
   iarr (i) = i
enddo

ip => iarr(1)         !! pointer can only points to a single value,  ip is same as iarr(1)
                                  !! not to a chunk of memory seen in c/c++
print *,  ip
iarr(1) = 999
print *,  ip
 
  1
999

eg2 : 
integer , parameter :: size = 3
integer , pointer :: ip(:  !! pointer to a chunk of memory
integer, allocatable,target :: iarr(:,:)

allocate(iarr(10,10))
do i = 1, size
do j = 1, size
   iarr (i,j) = i+j*10
enddo
enddo

ip => iarr(1:size, 1)    !! to a chunk of memory,  ip -> 3 ints

print *,  ip
iarr(2,1) = 999
print *,  ip
ip(2)=888
print *,  ip


          11          12          13
          11         999          13
          11         888          13


No comments:

Post a Comment