General and miscellaneous intrinsics#

associated#

Name#

associated(3) - [STATE:INQUIRY] Association status of a pointer or pointer/target pair

Synopsis#

    result = associated(pointer [,target])
     logical function associated(pointer,target)

      type(TYPE(kind=KIND),pointer :: pointer
      type(TYPE(kind=KIND),pointer,optional :: target

Characteristics#

  • pointer shall have the pointer attribute and it can be any type or may be a procedure pointer

  • target shall be a pointer or a target. It must have the same type, kind type parameter, and array rank as pointer.

  • The association status of neither pointer nor target shall be undefined.

  • the result is a default logical value

Description#

associated(3) determines the status of the pointer pointer or if pointer is associated with the target target.

Options#

  • pointer

    A pointer to test for association. Its pointer association status shall not be undefined.

  • target

    A target that is to be tested for occupying the same storage units as the pointer pointer. That is, it is tested as to whether it is pointed to by pointer.

Result#

associated(3f) returns a scalar value of type logical. There are several cases:

  1. When the optional target is not present then associated(pointer) is .true. if pointer is associated with a target; otherwise, it returns .false..

  2. If target is present and a scalar target, the result is .true. if target is not a zero-sized storage sequence and the target associated with pointer occupies the same storage units. If pointer is disassociated, the result is .false..

  3. If target is present and an array target, the result is .true. if target and pointer have the same shape, are not zero-sized arrays, are arrays whose elements are not zero-sized storage sequences, and target and pointer occupy the same storage units in array element order.

    As in case 2, the result is .false., if pointer is disassociated.

  4. If target is present and an scalar pointer, the result is .true. if target is associated with pointer, the target associated with target are not zero-sized storage sequences and occupy the same storage units.

    The result is .false., if either target or pointer is disassociated.

  5. If target is present and an array pointer, the result is .true. if target associated with pointer and the target associated with target have the same shape, are not zero-sized arrays, are arrays whose elements are not zero-sized storage sequences, and target and pointer occupy the same storage units in array element order.

  6. If target is present and is a procedure, the result is true if and only if pointer is associated with target and, if target is an internal procedure, they have the same host instance.

  7. If target is present and is a procedure pointer, the result is true if and only if pointer and target are associated with the same procedure and, if the procedure is an internal procedure, they have the same host instance.

Examples#

Sample program:

program demo_associated
implicit none
real, target  :: tgt(2) = [1., 2.]
real, pointer :: ptr(:)
   ptr => tgt
   if (associated(ptr)     .eqv. .false.) &
   & stop 'POINTER NOT ASSOCIATED'
   if (associated(ptr,tgt) .eqv. .false.) &
   & stop 'POINTER NOT ASSOCIATED TO TARGET'
end program demo_associated

Standard#

Fortran 95

See Also#

null(3)

fortran-lang intrinsic descriptions (license: MIT) @urbanjost

extends_type_of#

Name#

extends_type_of(3) - [STATE:INQUIRY] Determine if the dynamic type of a is an extension of the dynamic type of mold.

Synopsis#

    result = extends_type_of(a, mold)
     logical extends_type_of(a, mold)

      type(TYPE(kind=KIND),intent(in) :: a
      type(TYPE(kind=KIND),intent(in) :: mold

Characteristics#

-a shall be an object or pointer to an extensible declared type, or unlimited polymorphic. If it is a polymorphic pointer, it shall not have an undefined association status. -mole shall be an object or pointer to an extensible declared type or unlimited polymorphic. If it is a polymorphic pointer, it shall not have an undefined association status.

  • the result is a scalar default logical type.

Description#

extends_type_of(3) is .true. if and only if the dynamic type of a is or could be (for unlimited polymorphic) an extension of the dynamic type of mold.

NOTE1#

The dynamic type of a disassociated pointer or unallocated allocatable variable is its declared type.

NOTE2#

The test performed by extends_type_of is not the same as the test performed by the type guard class is. The test performed by extends_type_of does not consider kind type parameters.

options#

  • a

    be an object of extensible declared type or unlimited polymorphic. If it is a polymorphic pointer, it shall not have an undefined association status.

  • mold

    be an object of extensible declared type or unlimited polymorphic. If it is a polymorphic pointer, it shall not have an undefined association status.

Result#

If mold is unlimited polymorphic and is either a disassociated pointer or unallocated allocatable variable, the result is true.

Otherwise if a is unlimited polymorphic and is either a disassociated pointer or unallocated allocatable variable, the result is false.

Otherwise the result is true if and only if the dynamic type of a

if the dynamic type of A or MOLD is extensible, the result is true if and only if the dynamic type of A is an extension type of the dynamic type of MOLD; otherwise the result is processor dependent.

Examples#

Sample program:

  ! program demo_extends_type_of
  module M_demo_extends_type_of
  implicit none
  private

  type nothing
  end type nothing

  type, extends(nothing) :: dot
    real :: x=0
    real :: y=0
  end type dot

  type, extends(dot) :: point
    real :: z=0
  end type point

  type something_else
  end type something_else

  public :: nothing
  public :: dot
  public :: point
  public :: something_else

  end module M_demo_extends_type_of

  program demo_extends_type_of
  use M_demo_extends_type_of, only : nothing, dot, point, something_else
  implicit none
  type(nothing) :: grandpa
  type(dot) :: dad
  type(point) :: me
  type(something_else) :: alien

   write(*,*)'these should all be true'
   write(*,*)extends_type_of(me,grandpa),'I am descended from Grandpa'
   write(*,*)extends_type_of(dad,grandpa),'Dad is descended from Grandpa'
   write(*,*)extends_type_of(me,dad),'Dad is my ancestor'

   write(*,*)'is an object an extension of itself?'
   write(*,*)extends_type_of(grandpa,grandpa) ,'self-propagating!'
   write(*,*)extends_type_of(dad,dad) ,'clone!'

   write(*,*)' you did not father your grandfather'
   write(*,*)extends_type_of(grandpa,dad),'no paradox here'

   write(*,*)extends_type_of(dad,me),'no paradox here'
   write(*,*)extends_type_of(grandpa,me),'no relation whatsoever'
   write(*,*)extends_type_of(grandpa,alien),'no relation'
   write(*,*)extends_type_of(me,alien),'not what everyone thinks'

   call pointers()
   contains

   subroutine pointers()
   ! Given the declarations and assignments
   type t1
   real c
   end type
   type, extends(t1) :: t2
   end type
   class(t1), pointer :: p, q
      allocate (p)
      allocate (t2 :: q)
      ! the result of EXTENDS_TYPE_OF (P, Q) will be false, and the result
      ! of EXTENDS_TYPE_OF (Q, P) will be true.
      write(*,*)'(P,Q)',extends_type_of(p,q),"mind your P's and Q's"
      write(*,*)'(Q,P)',extends_type_of(q,p)
   end subroutine pointers

  end program demo_extends_type_of

Results:

    these should all be true
    T I am descended from Grandpa
    T Dad is descended from Grandpa
    T Dad is my ancestor
    is an object an extension of itself?
    T self-propagating!
    T clone!
     you did not father your grandfather
    F no paradox here
    F no paradox here
    F no relation whatsoever
    F no relation
    F not what everyone thinks
    (P,Q) F mind your P's and Q's
    (Q,P) T

Standard#

Fortran 2003

See Also#

same_type_as(3)

fortran-lang intrinsic descriptions (license: MIT) @urbanjost

is_iostat_end#

Name#

is_iostat_end(3) - [STATE:INQUIRY] Test for end-of-file value

Synopsis#

    result = is_iostat_end(i)
     elemental logical function is_iostat_end(i)

      integer,intent(in) :: i

Characteristics#

  • i is integer of any kind

  • the return value is a default logical

Description#

is_iostat_end(3) tests whether a variable (assumed returned as a status from an I/O statement) has the “end of file” I/O status value.

The function is equivalent to comparing the variable with the iostat_end parameter of the intrinsic module iso_fortran_env.

Options#

  • i

    An integer status value to test if indicating end of file.

Result#

returns .true. if and only ifi has the value which indicates an end of file condition for iostat= specifiers, and is .false. otherwise.

Examples#

Sample program:

program demo_iostat
implicit none
real               :: value
integer            :: ios
character(len=256) :: message
   write(*,*)'Begin entering numeric values, one per line'
   do
      read(*,*,iostat=ios,iomsg=message)value
      if(ios.eq.0)then
         write(*,*)'VALUE=',value
      elseif( is_iostat_end(ios) ) then
         stop 'end of file. Goodbye!'
      else
         write(*,*)'ERROR:',ios,trim(message)
         exit
      endif
      !
   enddo
end program demo_iostat

Standard#

Fortran 2003

See also#

****(3)

fortran-lang intrinsic descriptions (license: MIT) @urbanjost

is_iostat_eor#

Name#

is_iostat_eor(3) - [STATE:INQUIRY] Test for end-of-record value

Synopsis#

    result = is_iostat_eor(i)
     elemental integer function is_iostat_eor(i)

      integer(kind=KIND),intent(in) :: i

Characteristics#

  • i is integer of any kind

  • the return value is a default logical

Description#

is_iostat_eor(3) tests whether a variable has the value of the I/O status “end of record”. The function is equivalent to comparing the variable with the iostat_eor parameter of the intrinsic module iso_fortran_env.

Options#

  • i

    The value to test as indicating “end of record”.

Result#

Returns .true. if and only if i has the value which indicates an end-of-record condition for iostat= specifiers, and is .false. otherwise.

Examples#

Sample program:

program demo_is_iostat_eor
use iso_fortran_env, only : iostat_eor
implicit none
integer :: inums(5), lun, ios

  ! create a test file to read from
   open(newunit=lun, form='formatted',status='scratch')
   write(lun, '(a)') '10 20 30'
   write(lun, '(a)') '40 50 60 70'
   write(lun, '(a)') '80 90'
   write(lun, '(a)') '100'
   rewind(lun)

   do
      read(lun, *, iostat=ios) inums
      write(*,*)'iostat=',ios
      if(is_iostat_eor(ios)) then
         stop 'end of record'
      elseif(is_iostat_end(ios)) then
         print *,'end of file'
         exit
      elseif(ios.ne.0)then
         print *,'I/O error',ios
         exit
      endif
   enddo

   close(lun,iostat=ios,status='delete')

end program demo_is_iostat_eor

Results:

 >  iostat=           0
 >  iostat=          -1
 >  end of file

Standard#

Fortran 2003

See also#

****(3)

fortran-lang intrinsic descriptions

move_alloc#

Name#

move_alloc(3) - [MEMORY] Move allocation from one object to another

Synopsis#

    call move_alloc(from, to [,stat] [,errmsg] )
     subroutine move_alloc(from, to)

      type(TYPE(kind=**)),intent(inout),allocatable :: from(..)
      type(TYPE(kind=**)),intent(out),allocatable   :: to(..)
      integer(kind=**),intent(out)   :: stat
      character(len=*),intent(inout) :: errmsg

Characteristics#

  • from may be of any type and kind.

  • to shall be of the same type, kind and rank as from.

Description#

move_alloc(3) moves the allocation from from to to. from will become deallocated in the process.

This is potentially more efficient than other methods of assigning the values in from to to and explicitly deallocating from, which are for more likely to require a temporary object or a copy of the elements of the array.

Options#

  • from

    The data object to be moved to to and deallocated.

  • to

    The destination data object to move the allocated data object from to. Typically, it is a different shape than from.

  • stat

    If stat is present and execution is successful, it is assigned the value zero.

    If an error condition occurs,

    o if stat is absent, error termination is initiated; o otherwise, if from is a coarray and the current team contains a stopped image, stat is assigned the value STAT_STOPPED_IMAGE from the intrinsic module ISO_FORTRAN_ENV; o otherwise, if from is a coarray and the current team contains a failed image, and no other error condition occurs, stat is assigned the value STAT_FAILED_IMAGE from the intrinsic module ISO_FORTRAN_ENV; o otherwise, stat is assigned a processor-dependent positive value that differs from that of STAT_STOPPED_IMAGE or STAT_FAILED_IMAGE.

  • errmsg

    If the errmsg argument is present and an error condition occurs, it is assigned an explanatory message. If no error condition occurs, the definition status and value of errmsg are unchanged.

Examples#

Basic sample program to allocate a bigger grid

program demo_move_alloc
implicit none
! Example to allocate a bigger GRID
real, allocatable :: grid(:), tempgrid(:)
integer :: n, i

   ! initialize small GRID
   n = 3
   allocate (grid(1:n))
   grid = [ (real (i), i=1,n) ]

   ! initialize TEMPGRID which will be used to replace GRID
   allocate (tempgrid(1:2*n))    ! Allocate bigger grid
   tempgrid(::2)  = grid         ! Distribute values to new locations
   tempgrid(2::2) = grid + 0.5   ! initialize other values

   ! move TEMPGRID to GRID
   call MOVE_ALLOC (from=tempgrid, to=grid)

   ! TEMPGRID should no longer be allocated
   ! and GRID should be the size TEMPGRID was
   if (size (grid) /= 2*n .or. allocated (tempgrid)) then
      print *, "Failure in move_alloc!"
   endif
   print *, allocated(grid), allocated(tempgrid)
   print '(99f8.3)', grid
end program demo_move_alloc

Results:

    T F
      1.000   1.500   2.000   2.500   3.000   3.500

Standard#

Fortran 2003, STAT and ERRMSG options added 2018

See Also#

allocated(3)

fortran-lang intrinsic descriptions

present#

Name#

present(3) - [STATE:INQUIRY] Determine whether an optional dummy argument is specified

Synopsis#

    result = present(a)
     logical function present (a)

      type(TYPE(kind=KIND)) :: a(..)

Characteristics#

  • a May be of any type and may be a pointer, scalar or array value, or a dummy procedure.

Description#

present(3) can be used in a procedure to determine if an optional dummy argument was present on the current call to the procedure.

a shall be the name of an optional dummy argument that is accessible in the subprogram in which the present(3) function reference appears. There are no other requirements on a.

Note when an argument is not present when the current procedure is invoked, you may only pass it as an optional argument to another procedure or pass it as an argument to present.

Options#

  • a

    the name of an optional dummy argument accessible within the current subroutine or function.

Result#

Returns .true. if the optional argument a is present (was passed on the call to the procedure) , or .false. otherwise.

Examples#

Sample program:

program demo_present
implicit none
integer :: answer
   ! argument to func() is not present
   answer=func()
   write(*,*) answer
   ! argument to func() is present
   answer=func(1492)
   write(*,*) answer
contains
!
integer function func(x)
! the optional characteristic on this definition allows this variable
! to not be specified on a call; and also allows it to subsequently
! be passed to PRESENT(3):
integer, intent(in), optional :: x
integer :: x_local
   !
   ! basic
   if(present(x))then
     ! if present, you can use x like any other variable.
     x_local=x
   else
     ! if not, you cannot define or reference x except to
     ! pass it as an optional parameter to another procedure
     ! or in a call to present(3f)
     x_local=0
   endif
   !
   func=x_local**2
   !
   ! passing the argument on to other procedures
   ! so something like this is a bad idea because x is used
   ! as the first argument to merge(3f) when it might not be
   ! present
   ! xlocal=merge(x,0,present(x)) ! NO!!
   !
   ! We can pass it to another procedure if another
   ! procedure declares the argument as optional as well,
   ! or we have tested that X is present
   call tattle('optional argument x',x)
   if(present(x))call not_optional(x)
end function
!
subroutine tattle(label,arg)
character(len=*),intent(in) :: label
integer,intent(in),optional :: arg
   if(present(arg))then
      write(*,*)label,' is present'
   else
      write(*,*)label,' is not present'
   endif
end subroutine tattle
!
subroutine not_optional(arg)
integer,intent(in) :: arg
   write(*,*)'already tested X is defined',arg
end subroutine not_optional
!
end program demo_present

Results:

    optional argument x is not present
              0
    optional argument x is present
    already tested X is defined 1492
        2226064

Standard#

Fortran 95

fortran-lang intrinsic descriptions (license: MIT) @urbanjost

same_type_as#

Name#

same_type_as(3) - [STATE:INQUIRY] Query dynamic types for equality

Synopsis#

    result = same_type_as(a, b)
     logical same_type_as(a, b)

      type(TYPE(kind=KIND),intent(in) :: a
      type(TYPE(kind=KIND),intent(in) :: b

Characteristics#

  • a shall be an object of extensible declared type or unlimited polymorphic. If it is a polymorphic pointer, it shall not have an undefined association status.

  • b shall be an object of extensible declared type or unlimited polymorphic. If it is a polymorphic pointer, it shall not have an undefined association status.

Description#

same_type_as(3) queries the dynamic types of objects for equality.

Options#

  • a

    object to compare to b for equality of type

  • b

    object to be compared to for equality of type

Result#

If the dynamic type of a or b is extensible, the result is true if and only if the dynamic type of a is the same as the dynamic type of b. If neither a nor b has extensible dynamic type, the result is processor dependent.

NOTE1

The dynamic type of a disassociated pointer or unallocated allocatable variable is its declared type. An unlimited polymorphic entity has no declared type.

NOTE2

The test performed by SAME_TYPE_AS is not the same as the test performed by the type guard TYPE IS. The test performed by SAME_TYPE_AS does not consider kind type parameters.

Sample program:

  ! program demo_same_type_as
  module M_ether
  implicit none
  private

  type   :: dot
    real :: x=0
    real :: y=0
  end type dot

  type, extends(dot) :: point
    real :: z=0
  end type point

  type something_else
  end type something_else

  public :: dot
  public :: point
  public :: something_else

  end module M_ether

  program demo_same_type_as
  use M_ether, only : dot, point, something_else
  implicit none
  type(dot) :: dad, mom
  type(point) :: me
  type(something_else) :: alien

   write(*,*)same_type_as(me,dad),'I am descended from Dad, but equal?'
   write(*,*)same_type_as(me,me) ,'I am what I am'
   write(*,*)same_type_as(dad,mom) ,'what a pair!'

   write(*,*)same_type_as(dad,me),'no paradox here'
   write(*,*)same_type_as(dad,alien),'no relation'

   call pointers()
   contains
   subroutine pointers()
   ! Given the declarations and assignments
   type t1
      real c
   end type
   type, extends(t1) :: t2
   end type
   class(t1), pointer :: p, q, r
      allocate (p, q)
      allocate (t2 :: r)
      ! the result of SAME_TYPE_AS (P, Q) will be true, and the result
      ! of SAME_TYPE_AS (P, R) will be false.
      write(*,*)'(P,Q)',same_type_as(p,q),"mind your P's and Q's"
      write(*,*)'(P,R)',same_type_as(p,r)
   end subroutine pointers

  end program demo_same_type_as

Results:

    F I am descended from Dad, but equal?
    T I am what I am
    T what a pair!
    F no paradox here
    F no relation
    (P,Q) T mind your P's and Q's
    (P,R) F

Standard#

Fortran 2003

See Also#

extends_type_of(3)

fortran-lang intrinsic descriptions