ユーザ用ツール

サイト用ツール


サイドバー

fortran:ifort

以前のリビジョンの文書です


ifort

  • スパコンで使うことが前提
  • kudpc を参照.

コンパイラオプション

http://accc.riken.jp/HPC/training/text.html

http://www.k.mei.titech.ac.jp/~stamura/NumericalComputation-Tips.html これくらいオプションをつけて実行すれば,だいたいエラーは検出されそう.

ifort -check all -warn declarations -CB -fpe0 -traceback

コンパイラオプションも参照のこと

デフォルトのスタックサイズが小さすぎる

デフォルトのスタックサイズが小さすぎて、-openmpをやるときはスタックサイズを増やしてあげないと、頻繁にセグ落ちする。

!$OMP parallel
write(*,*) KMP_GET_STACKSIZE_S()
!$OMP end parallel

とやると、各スレッドのスタックサイズを返す。これを増やす場合は、最初の!$OMPの前に、

CALL KMP_SET_STACKSIZE_S(size)

とやれば良い。sizeは整数型の変数。所望のスタックサイズ(byte)を書けばよい。

改行の抑制

ifortでは出力時に勝手に改行する仕様になっている。 改行を抑制するためには、Format文を使用すればよい。

適当なやり方。

    write(*,'(100f)') a(:)

きちんとしたやり方。以下2chより引用。

http://pc12.2ch.net/test/read.cgi/tech/1163319215/532

532 名前:デフォルトの名無しさん [sage]: 2009/03/27(金) 05:59:41  
亀だけど、Ifortなら<>がお勧め。
多次元配列の最初の数を入れることが多いです
例
program main
implicit none
integer,parameter :: num = 9
integer :: ii,jj
real :: arry(num,num)
do ii=1,num
do jj = 1,num
arry(ii,jj) = ii*jj
enddo
enddo

write(6,'(<num>F)') arry
end program 

MKL

kudpc に記載あり.

module load mkl

してから,コンパイル.お手軽.

ifort sample.f90 -mkl

pardiso の使い方

pardisoを用いた連立一時方程式の解き方.

スパコンの

/opt/app/intel/composer_xe_2013.5.192/mkl/examples/solverf/source/

に入っているサンプルデータを参考に,走らせたいプログラムを作成する.

中身はこんな感じ

配列の設定に注意が必要,詳しくは以下を参照 [http://www.pardiso-project.org/manual/manual.pdf]

      PROGRAM pardiso_unsym
      IMPLICIT NONE
      include 'mkl_pardiso.f77'
C.. Internal solver memory pointer for 64-bit architectures
C.. INTEGER*8 pt(64)
C.. Internal solver memory pointer for 32-bit architectures
C.. INTEGER*4 pt(64)
C.. This is OK in both cases
      INTEGER*8 pt(64)
C.. All other variables
      INTEGER maxfct, mnum, mtype, phase, n, nrhs, error, msglvl
      INTEGER iparm(64)
      INTEGER ia(6)
      INTEGER ja(13)
      REAL*8 a(13)
      REAL*8 b(5)
      REAL*8 x(5)
      INTEGER i, idum(1)
      REAL*8  ddum(1)
C.. Fill all arrays containing matrix data.
      DATA n /5/, nrhs /1/, maxfct /1/, mnum /1/
      DATA ia /1,4,6,9,12,14/
      DATA ja
     1 /   1,    2,          4,
     2     1,    2,
     3                 3,    4,    5,
     4     1,          3,    4,
     5           2,                5/
      DATA a
     1 /1.d0,-1.d0,      -3.d0,
     2 -2.d0, 5.d0,
     3              4.d0, 6.d0, 4.d0,
     4 -4.d0,       2.d0, 7.d0,
     5        8.d0,            -5.d0/
C..
C.. Set up PARDISO control parameter
C..
      do i = 1, 64
         iparm(i) = 0
      end do
      iparm(1) = 1 ! no solver default
      iparm(2) = 2 ! fill-in reordering from METIS
      iparm(3) = 1 ! numbers of processors
      iparm(4) = 0 ! no iterative-direct algorithm
      iparm(5) = 0 ! no user fill-in reducing permutation
      iparm(6) = 0 ! =0 solution on the first n compoments of x
      iparm(7) = 0 ! not in use
      iparm(8) = 9 ! numbers of iterative refinement steps
      iparm(9) = 0 ! not in use
      iparm(10) = 13 ! perturbe the pivot elements with 1E-13
      iparm(11) = 1 ! use nonsymmetric permutation and scaling MPS
      iparm(12) = 0 ! not in use
      iparm(13) = 1 ! maximum weighted matching algorithm is switched-on (default for non-symmetric)
      iparm(14) = 0 ! Output: number of perturbed pivots
      iparm(15) = 0 ! not in use
      iparm(16) = 0 ! not in use
      iparm(17) = 0 ! not in use
      iparm(18) = -1 ! Output: number of nonzeros in the factor LU
      iparm(19) = -1 ! Output: Mflops for LU factorization
      iparm(20) = 0 ! Output: Numbers of CG Iterations
      error = 0 ! initialize error flag
      msglvl = 1 ! print statistical information
      mtype = 11 ! real unsymmetric
C.. Initiliaze the internal solver memory pointer. This is only
C necessary for the FIRST call of the PARDISO solver.
      do i = 1, 64
         pt(i) = 0
      end do
C.. Reordering and Symbolic Factorization, This step also allocates
C all memory that is necessary for the factorization
      phase = 11 ! only reordering and symbolic factorization
      CALL pardiso (pt, maxfct, mnum, mtype, phase, n, a, ia, ja,
     1 idum, nrhs, iparm, msglvl, ddum, ddum, error)
      WRITE(*,*) 'Reordering completed ... '
      IF (error .NE. 0) THEN
         WRITE(*,*) 'The following ERROR was detected: ', error
         STOP 1
      END IF
      WRITE(*,*) 'Number of nonzeros in factors = ',iparm(18)
      WRITE(*,*) 'Number of factorization MFLOPS = ',iparm(19)
C.. Factorization.
      phase = 22 ! only factorization
      CALL pardiso (pt, maxfct, mnum, mtype, phase, n, a, ia, ja,
     1 idum, nrhs, iparm, msglvl, ddum, ddum, error)
      WRITE(*,*) 'Factorization completed ... '
      IF (error .NE. 0) THEN
         WRITE(*,*) 'The following ERROR was detected: ', error
         STOP 1
      ENDIF
C.. Back substitution and iterative refinement
      iparm(8) = 2 ! max numbers of iterative refinement steps
      phase = 33 ! only factorization
      do i = 1, n
         b(i) = 1.d0
      end do
      CALL pardiso (pt, maxfct, mnum, mtype, phase, n, a, ia, ja,
     1 idum, nrhs, iparm, msglvl, b, x, error)
      WRITE(*,*) 'Solve completed ... '
      WRITE(*,*) 'The solution of the system is '
      DO i = 1, n
         WRITE(*,*) ' x(',i,') = ', x(i)
      END DO
C.. Termination and release of memory
      phase = -1 ! release internal memory
      CALL pardiso (pt, maxfct, mnum, mtype, phase, n, ddum, idum, idum,
     1 idum, nrhs, iparm, msglvl, ddum, ddum, error)
      END

コンパイラオプションは

-mkl

でお手軽♪

fortran/ifort.1412914363.txt.gz · 最終更新: 2017/10/03 12:55 (外部編集)