General and miscellaneous intrinsics#
associated#
Name#
associated(3) - [STATE] Status of a pointer or pointer/target pair
Syntax#
result = associated(pointer, target)
Description#
associated(pointer [, target]) determines the status of the pointer pointer or if pointer is associated with the target target.
Arguments#
- pointer
pointer shall have the pointer attribute and it can be of any type.
- target
(Optional) 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.
Returns#
associated(pointer) returns a scalar value of type logical. There are several cases:
When the optional target is not present then associated(pointer) is true if pointer is associated with a target; otherwise, it returns false.
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.
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.
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.
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. The result is false, if either target or pointer is disassociated.
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 and later
See Also#
####### fortran-lang intrinsic descriptions
extends_type_of#
Name#
extends_type_of(3) - [STATE] determine if the dynamic type of a is an extension of the dynamic type of mold.
Syntax#
result=extends_type_of(a, mold)
Description#
extends_type_of(3) is .true. if and only if the dynamic type of a is an extension of the dynamic type of mold.
Options#
- a
shall be an object of extensible type. If it is a pointer, it shall not have an undefined association status.
- mold
shall be an object of extensible type. If it is a pointer, it shall not have an undefined association status.
Returns#
- result
Default logical scalar.
- value
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 is an extension type of the dynamic type of mold.
The dynamic type of a disassociated pointer or unallocated allocatable variable is its declared type.
Examples#
####### fortran-lang intrinsic descriptions
is_iostat_end#
Name#
is_iostat_end(3) - [STATE] Test for end-of-file value
Syntax#
function is_iostat_end(i)
logical function :: is_iostat_end (i) result(yesno)
integer,intent(in) :: i
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.
Arguments#
- i
An integer status value to test if indicating end of file.
Returns#
Returns a logical of the default kind, .true. if i 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)
endif
!
enddo
end program demo_iostat
Standard#
Fortran 2003 and later
####### fortran-lang intrinsic descriptions (license: MIT) @urbanjost
is_iostat_eor#
Name#
is_iostat_eor(3) - [STATE] Test for end-of-record value
Syntax#
result = is_iostat_eor(i)
Description#
is_iostat_eor tests whether an 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.
Arguments#
- i
Shall be of the type integer.
Returns#
Returns a logical of the default kind, which .true. if i has the value which indicates an end of file condition for iostat= specifiers, and is .false. otherwise.
Examples#
Sample program:
program demo_is_iostat_eor
implicit none
integer :: stat, i(50)
open(88, file='test.dat', form='unformatted')
read(88, iostat=stat) i
if(is_iostat_eor(stat)) stop 'end of record'
end program demo_is_iostat_eor
Standard#
Fortran 2003 and later
####### fortran-lang intrinsic descriptions
move_alloc#
Name#
move_alloc(3) - [] Move allocation from one object to another
Syntax#
call move_alloc(src, dest)
Description#
move_alloc(src, dest) moves the allocation from SRC to DEST. SRC will become deallocated in the process.
Arguments#
- src
allocatable, intent(inout), may be of any type and kind.
- dest
allocatable, intent(out), shall be of the same type, kind and rank as SRC.
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 and later
See Also#
####### fortran-lang intrinsic descriptions
present#
Name#
present(3) - [STATE] Determine whether an optional dummy argument is specified
Syntax#
result = present(a)
function present (a)
logical :: present
Description#
Determines whether an optional dummy argument is present.
Arguments#
- a
May be of any type and may be a pointer, scalar or array value, or a dummy procedure. It shall be the name of an optional dummy argument accessible within the current subroutine or function.
Returns#
Returns either .true. if the optional argument a is present, or .false. otherwise.
Examples#
Sample program:
program demo_present
implicit none
write(*,*) func(), func(42)
contains
integer function func(x)
integer, intent(in), optional :: x
if(present(x))then
func=x**2
else
func=0
endif
end function
end program demo_present
Results:
0 1764
Standard#
Fortran 95 and later
####### fortran-lang intrinsic descriptions
same_type_as#
Name#
same_type_as(3) - [STATE] Query dynamic types for equality
Syntax#
result = same_type_as(a, b)
Description#
Query dynamic types for equality.
Arguments#
- a
Shall be an object of extensible declared type or unlimited polymorphic.
- b
Shall be an object of extensible declared type or unlimited polymorphic.
Returns#
The return value is a scalar of type default logical. It is true if and only if the dynamic type of a is the same as the dynamic type of b.
Standard#
Fortran 2003 and later
See Also#
####### fortran-lang intrinsic descriptions