一般およびその他の組込み関数#

associated#

名前#

associated(3) - [状態:照会] ポインタまたはポインタ/ターゲットペアの関連付け状態

概要#

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

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

特性#

  • pointer は *pointer* 属性を持つ必要があり、任意の型、または手続きポインタとすることができます。

  • target はポインタまたはターゲットです。 pointer と同じ型、種別型パラメータ、および配列ランクを持つ必要があります。

  • pointer と **target** のどちらの関連付け状態も未定義であってはなりません。

  • 結果はデフォルトの *logical* 値です。

説明#

associated(3) は、ポインタ **pointer** の状態、または **pointer** がターゲット **target** に関連付けられているかどうかを判別します。

オプション#

  • pointer

    関連付けをテストするポインタ。そのポインタの関連付け状態は未定義であってはなりません。

  • target

    ポインタ **pointer** と同じ記憶単位を占有しているかどうかをテストされるターゲット。つまり、**pointer** によってポイントされているかどうかがテストされます。

結果#

associated(3f) は *logical* 型のスカラー値を返します。いくつかのケースがあります。

  1. オプションの **target** が存在しない場合、**associated(pointer)** は、**pointer** がターゲットに関連付けられている場合は *.true.*、そうでない場合は *.false.* を返します。

  2. **target** が存在し、スカラーターゲットである場合、**target** がサイズゼロの記憶列ではなく、**pointer** に関連付けられたターゲットが同じ記憶単位を占有している場合、結果は *.true.* です。 **pointer** が関連付けられていない場合、結果は *.false.* です。

  3. **target** が存在し、配列ターゲットである場合、**target** と **pointer** が同じ形状を持ち、サイズゼロの配列ではなく、要素がサイズゼロの記憶列ではない配列であり、**target** と **pointer** が配列要素の順序で同じ記憶単位を占有している場合、結果は *.true.* です。

    ケース2と同様に、**pointer** が関連付けられていない場合、結果は *.false.* です。

  4. **target** が存在し、スカラーポインタである場合、**target** が **pointer** に関連付けられており、**target** に関連付けられたターゲットがサイズゼロの記憶列ではなく、同じ記憶単位を占有している場合、結果は *.true.* です。

    **target** または **pointer** が関連付けられていない場合、結果は *.false.* です。

  5. **target** が存在し、配列ポインタである場合、**pointer** に関連付けられたターゲットと **target** に関連付けられたターゲットが同じ形状を持ち、サイズゼロの配列ではなく、要素がサイズゼロの記憶列ではない配列であり、**target** と **pointer** が配列要素の順序で同じ記憶単位を占有している場合、結果は *.true.* です。

  6. **target** が存在し、手続きである場合、**pointer** が **target** に関連付けられており、**target** が内部手続きである場合に同じホストインスタンスを持つ場合にのみ、結果は真です。

  7. **target** が存在し、手続きポインタである場合、**pointer** と **target** が同じ手続きに関連付けられており、手続きが内部手続きである場合に同じホストインスタンスを持つ場合にのみ、結果は真です。

#

サンプルプログラム

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

規格#

Fortran 95

関連項目#

null(3)

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

extends_type_of#

名前#

extends_type_of(3) - [状態:照会] **a** の動的型が **mold** の動的型の拡張であるかどうかを判別します。

概要#

    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

特性#

- **a** は、拡張可能な宣言型または無制限ポリモーフィックのオブジェクトまたはポインタです。ポリモーフィックポインタの場合、未定義の関連付け状態を持ってはいけません。 - **mold** は、拡張可能な宣言型または無制限ポリモーフィックのオブジェクトまたはポインタです。ポリモーフィックポインタの場合、未定義の関連付け状態を持ってはいけません。

  • 結果はスカラーのデフォルト論理型です。

説明#

**extends_type_of(3) は、**a** の動的型が **mold** の動的型の拡張であるか、または(無制限ポリモーフィックの場合)拡張される可能性がある場合にのみ .true. です。

注記1#

関連付けられていないポインタまたは未割り当ての割付け可能変数の動的型は、その宣言型です。

注記2#

**extends_type_of** によって実行されるテストは、型ガード **class is** によって実行されるテストと同じではありません。 **extends_type_of** によって実行されるテストは、種別型パラメータを考慮しません。

オプション#

  • a

    拡張可能な宣言型または無制限ポリモーフィックのオブジェクトです。ポリモーフィックポインタの場合、未定義の関連付け状態を持ってはいけません。

  • mold

    拡張可能な宣言型または無制限ポリモーフィックのオブジェクトです。ポリモーフィックポインタの場合、未定義の関連付け状態を持ってはいけません。

結果#

**mold** が無制限ポリモーフィックであり、関連付けられていないポインタまたは未割り当ての割付け可能変数である場合、結果は真です。

それ以外の場合、**a** が無制限ポリモーフィックであり、関連付けられていないポインタまたは未割り当ての割付け可能変数である場合、結果は偽です。

それ以外の場合、結果は、**a** の動的型が以下の場合にのみ真です。

AまたはMOLDの動的型が拡張可能な場合、Aの動的型がMOLDの動的型の拡張型である場合にのみ結果は真です。そうでない場合、結果は処理系依存です。

#

サンプルプログラム

  ! 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

結果

    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

規格#

Fortran 2003

関連項目#

same_type_as(3)

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

is_iostat_end#

名前#

is_iostat_end(3) - [状態:照会] ファイルの終端値のテスト

概要#

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

      integer,intent(in) :: i

特性#

  • **i** は任意の種別の *integer* です。

  • 戻り値はデフォルトの *logical* です。

説明#

**is_iostat_end(3) は、変数(I/O文からの状態として返されたと想定される)が「ファイルの終端」I/O状態値を持っているかどうかをテストします。

この関数は、変数を組込みモジュール **iso_fortran_env** の **iostat_end** パラメータと比較することと同等です。

オプション#

  • i

    ファイルの終端を示しているかどうかをテストする *integer* 状態値。

結果#

**i** が **iostat=** 指定子のファイルの終端条件を示す値を持っている場合にのみ *.true.* を返し、それ以外の場合は *.false.* を返します。

#

サンプルプログラム

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

規格#

Fortran 2003

関連項目#

****(3)

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

is_iostat_eor#

名前#

is_iostat_eor(3) - [状態: 問い合わせ] レコードの終わり値のテスト

概要#

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

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

特性#

  • **i** は任意の種別の *integer* です。

  • 戻り値はデフォルトの *logical* です。

説明#

is_iostat_eor(3) は、変数が I/O ステータス「レコードの終わり」の値を持っているかどうかをテストします。この関数は、変数を組込みモジュール iso_fortran_enviostat_eor パラメータと比較することと同等です。

オプション#

  • i

    「レコードの終わり」を示す値としてテストする値。

結果#

i が iostat= 指定子のレコードの終わり条件を示す値を持っている場合にのみ .true. を返し、そうでない場合は .false. を返します。

#

サンプルプログラム

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

結果

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

標準#

Fortran 2003

関連項目#

****(3)

Fortran 言語組込み関数説明

move_alloc#

名前#

move_alloc(3) - [メモリ] オブジェクト間での割り当ての移動

概要#

    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

特性#

  • from は任意の型と種別を持つことができます。

  • tofrom と同じ型、種別、およびランクを持つ必要があります。

説明#

move_alloc(3) は、from から to へ割り当てを移動します。このプロセスで from は割り当て解除されます。

これは、from の値を to に代入し、from を明示的に割り当て解除する他の方法よりも効率的である可能性があります。他の方法では、一時オブジェクトまたは配列要素のコピーが必要になる可能性が高くなります。

オプション#

  • from

    to に移動され、割り当て解除されるデータオブジェクト。

  • to

    割り当てられたデータオブジェクト from を移動する先のデータオブジェクト。通常、from とは形状が異なります。

  • stat

    stat が存在し、実行が成功した場合、ゼロが代入されます。

    エラー状態が発生した場合、

    o stat が存在しない場合、エラー終了が開始されます。o そうでない場合、from がコアレであり、現在のチームに停止したイメージが含まれている場合、stat には組込みモジュール ISO_FORTRAN_ENV から STAT_STOPPED_IMAGE の値が代入されます。o そうでない場合、from がコアレであり、現在のチームに失敗したイメージが含まれており、他のエラー状態が発生しない場合、stat には組込みモジュール ISO_FORTRAN_ENV から STAT_FAILED_IMAGE の値が代入されます。o そうでない場合、stat には、STAT_STOPPED_IMAGE または STAT_FAILED_IMAGE の値とは異なるプロセッサ依存の正の値が代入されます。

  • errmsg

    errmsg 引数が存在し、エラー状態が発生した場合、説明メッセージが代入されます。エラー状態が発生しない場合、errmsg の定義ステータスと値は変更されません。

#

より大きなグリッドを割り当てるための基本的なサンプルプログラム

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

結果

    T F
      1.000   1.500   2.000   2.500   3.000   3.500

標準#

Fortran 2003、STAT および ERRMSG オプションは 2018 年に追加

関連項目#

allocated(3)

Fortran 言語組込み関数説明

present#

名前#

present(3) - [状態: 問い合わせ] オプションの仮引数が指定されているかどうかを判断する

概要#

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

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

特性#

  • a は任意の型で、ポインター、スカラー値、配列値、または仮プロシージャです。

説明#

present(3) は、プロシージャで、現在のプロシージャ呼び出しにオプションの仮引数が存在するかどうかを判断するために使用できます。

a は、present(3) 関数参照が出現するサブルーチンまたは関数内でアクセス可能な、オプションの仮引数の名前です。a に対する他の要件はありません。

現在のプロシージャが呼び出されたときに引数が存在しない場合、その引数を別のプロシージャにオプションの引数として渡すか、present に引数として渡すことだけができます。

オプション#

  • a

    現在のサブルーチンまたは関数内でアクセス可能なオプションの仮引数の名前。

結果#

オプションの引数 a が存在する場合 (プロシージャの呼び出し時に渡された場合) は .true. を返し、そうでない場合は .false. を返します。

#

サンプルプログラム

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

結果

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

標準#

Fortran 95

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

same_type_as#

名前#

same_type_as(3) - [状態: 問い合わせ] 動的型の等価性を照会する

概要#

    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

特性#

  • a は、拡張可能な宣言型または無制限ポリモーフィックのオブジェクトです。ポリモーフィックポインターの場合は、未定義の関連付けステータスを持つことはできません。

  • b は、拡張可能な宣言型または無制限ポリモーフィックのオブジェクトです。ポリモーフィックポインターの場合は、未定義の関連付けステータスを持つことはできません。

説明#

same_type_as(3) は、オブジェクトの動的型の等価性を照会します。

オプション#

  • a

    型の等価性を b と比較するオブジェクト

  • b

    型の等価性を比較するオブジェクト

結果#

a または b の動的型が拡張可能な場合、a の動的型が b の動的型と同じである場合にのみ、結果は真です。ab も拡張可能な動的型を持たない場合、結果はプロセッサに依存します。

NOTE1

関連付けられていないポインターまたは割り当てられていない割り当て可能変数の動的型は、その宣言型です。無制限ポリモーフィックエンティティには宣言型がありません。

NOTE2

SAME_TYPE_AS によって実行されるテストは、型ガード TYPE IS によって実行されるテストと同じではありません。SAME_TYPE_AS によって実行されるテストは、種別型パラメータを考慮しません。

サンプルプログラム

  ! 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

結果

    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

標準#

Fortran 2003

関連項目#

extends_type_of(3)

Fortran 言語組込み関数説明