作業中のメモ

よく「計算機」を使って作業をする.知らなかったことを中心にまとめるつもり.

Raspberry Pi 3 Model B でファイルサーバーとプリンタサーバーを構築する(その 1) OS のインストールと初期設定

どうも,筆者です.

2017 年 1 月頃に,「Raspberry Pi 3 Model B」を購入した.今回は,CUPS と Samba を導入し,ファイルサーバーとプリンタサーバーを構築しようと思う.

購入した Raspberry Pi

購入したラズパイは,以下のものだ.ついでに,SD と電源アダプターも購入した.

Raspberry Pi3 Model B

SD カード

電源アダプター

これらを一式揃えて,1 万円以内に収まった.後は,キーボード,マウス,HDMI ケーブル,LAN ケーブルと,必要なものを家の中からかき集めて,他の方のサイトを参考にしながら,セットアップを行った.

OS のインストール

使用する OS は,「RASPBIAN JESSIE」を選び,「DD for Windows」で OS のインストールを行った.この辺は,別の方のサイトを参考にしたので,詳しくはそちらを見て欲しい. Raspberry Pi 3 Model B をインストールしてSSH接続できるようにしてみる

初期設定

上のサイトは,CUI がメインだったので,GUI がメインの以下のサイトの「Raspi-configセットアップ」を参考にしながら,設定を行った. Raspberry Pi 3でRaspbian Jessieをセットアップする方法

まず,パスワードの設定と解像度の設定を行った.

sudo passwd pi

解像度は,テレビ出力をしていたので,設定を行う必要があった.PC のモニタなら,設定する必要はないかも. 32 インチのテレビでは,以下のように設定すると綺麗に出力された.

sudo vi /boot/config.txt

# uncomment to force a specific HDMI mode (this will force VGA)
hdmi_group=1
hdmi_mode=5

設定後,システムのアップデートと firmware のアップデートを行うために,以下のコマンドを実行した. また,良く使うエディタ,vim と emacs24 をインストールした.この段階では,まだ有線 LAN を使用している.

sudo apt-get update
sudo apt-get upgrade
sudo rpi-update
sudo apt-get install -y vim
sudo apt-get install -y emacs24
sudo reboot

アップデートは終わったが,個人的に,テレビで操作をし続けるのは大変なため,ssh で遠隔ログインをして操作が行えるように,設定を行う.また,無線 LAN を利用したいので,有線 LAN から無線 LAN に切り替える.

まず,ssh でログインする際の IP アドレスを固定する.設定ファイルは,「/etc/dhcpcd.conf」,「/etc/network/interfaces」,「/etc/wpa_supplicant/wpa_supplicant.conf」を弄ればよいらしいので,順番に編集していく.

ここでは,IP アドレスとして,192.168.33.12 を使用し,ルーターDNS は,192.168.33.1 を設定するものとする.「/etc/dhcpcd.conf」をエディタで開き,最後に以下を追加する.

interface wlan0
static ip_address=192.168.33.12
static routers=192.168.33.1
static domain_name_servers=192.168.33.1

次に,「/etc/network/interfaces」の設定を行う.最終的に,中身は以下のようになった.

# interfaces(5) file used by ifup(8) and ifdown(8)                                                                       
# Please note that this file is written to be used with dhcpcd
# For static IP, consult /etc/dhcpcd.conf and 'man dhcpcd.conf'

# Include files from /etc/network/interfaces.d:
source-directory /etc/network/interfaces.d

auto lo
iface lo inet loopback

iface eth0 inet manual

allow-hotplug wlan0
iface wlan0 inet manual
    wpa-conf /etc/wpa_supplicant/wpa_supplicant.conf

最後に,「/etc/wpa_supplicant/wpa_supplicant.conf」の設定を行う.これは,ルーター側の設定となるので,個人ごとで異なる.

ctrl_interface=DIR=/var/run/wpa_supplicant GROUP=netdev
update_config=1
country=JP

network={
    ssid="接続先のSSID"
    psk="設定しているパスワード"
    key_mgmt=暗号化方法
}

一通り設定が終わったら,再起動をして正しく動作するか確認する.

次回

これで,一通り初期設定は終わったので,次は,CUPS と Samba のインストールと設定を行う.ドライバーのインストールにかなり苦労した.

ガウスの消去法(Fortran 自由形式)

Fortran90 の自由形式に関して

どうも,筆者です.何度同じ記事書くんだ?って感じだが,どうも自分が扱っていた Fortran の記述方法は古いらしい. 無料のコンパイラがあることを含めると,Fortran 90/95 の自由形式(free format)が主流らしい.Fortran 2003/2008 とかもあるらしい.

という事で,Fortran 90/95 の自由形式で記述する練習を兼ねてプログラムを書き直した.また,配列の使い方も何となく理解してきた.もっとも,同じプログラムを違う形式で書き換えているだけなので,動作は同じである.

プログラム

まず,ガウスの消去法を行う subroutine を示す.モジュールなるものを使ってみたりした.

! ====================
! Gaussian elimination
! ====================
!23456789|123456789|123456789|123456789|123456789|123456789|123456789|123456789|123456789|123456789
!        1         2         3         4         5         6         7         8         9
module mdlGaussElim
  implicit none
  private
  public :: GaussianElimination
  real(8), parameter :: eps_default = real(1e-10, 8)

  contains

  ! =================================
  ! ガウスの消去法
  !
  ! A: n × n の係数行列,A(row, col)
  ! b: n 次元右辺ベクトル,b(row)
  ! =================================
  subroutine GaussianElimination(A, b, mineps)
    ! 引数
    real(8), intent(inout) :: A(:, :), b(:)
    real(8), intent(in), optional :: mineps

    ! 局所変数
    integer(4) :: n, i, id, pivot
    real(8) :: val, diag, weight, use_eps
    n = size(A, 1)

    ! 許容誤差の確認
    use_eps = eps_default
    if (present(mineps)) then
      use_eps = mineps
    end if

    if (n /= size(A, 2)) then
      write(*, '("A is not square matrix")')
      return
    end if

    ! ================
    ! 部分ピボット選択
    ! ================
    do i = 1, n - 1
      id = maxloc(abs(A(i:n, i)), 1)

      ! 対角要素が最大でない場合
      if (id /= 1) then
        pivot = id + i - 1

        ! 入れ替えを行う
        do id = 1, n
          val = A(i, id)
          A(i, id) = A(pivot, id)
          A(pivot, id) = val
        end do
        val = b(i)
        b(i) = b(pivot)
        b(pivot) = val
      end if

      ! ========
      ! 前進消去
      ! ========
      diag = A(i, i)

      if (abs(diag) < use_eps) then
        write(*, '("Error: diagonal component is less than", G15.7)') use_eps
        return
      end if

      do id = i + 1, n
        weight = A(id, i) / diag
        A(id, i:n) = A(id, i:n) - weight * A(i, i:n)
        b(id) = b(id) - weight * b(i)
      end do
    end do

    ! ========
    ! 後退代入
    ! ========
    b(n) = b(n) / A(n, n)
    do i = n - 1, 1, -1
      id = i + 1
      val = b(i) - sum(A(i, id:n) * b(id:n))
      b(i) = val / A(i, i)
    end do

    return
  end subroutine GaussianElimination
end module mdlGaussElim

次に,main routine を示す.

! ============
! main routine
! ============
!23456789|123456789|123456789|123456789|123456789|123456789|123456789|123456789|123456789|123456789
!        1         2         3         4         5         6         7         8         9

program main
  use mdlGaussElim
  implicit none

  character(32) :: fmtstr, fname
  integer(4) :: n, i, ioerr
  real(8), allocatable :: A(:, :), b(:)

  ! ======================
  ! === 引数のチェック ===
  ! ======================
  if (iargc() /= 1) then
    call getarg(0, fname)
    write(*, '("Usage: ", a, "[data file name]")') fname
    stop
  else
    ! ======================
    ! === 引数の読み込み ===
    ! ======================
    call getarg(1, fname)
  end if

  ! ========================
  ! === ファイルオープン ===
  ! ========================
  open(10, file = fname, status = 'old', iostat = ioerr)

  if (ioerr /= 0) then
    write(*, '("Error: ", a, " cannot open")') fname
    stop
  end if

  ! ====================================
  ! === ファイルからデータを読み込む ===
  ! ====================================
  read(10, *) n

  allocate(A(1:n, 1:n), b(1:n))
  write(fmtstr, '("(", i0, "(E20.13), 3X, E20.13)")') n

  do i = 1, n
    read(10, *, iostat = ioerr) A(i, 1:n), b(i)

    if (ioerr /= 0) exit
  end do
  close(unit = 10)

  ! ============================
  ! === ガウスの消去法を行う ===
  ! ============================
  call GaussianElimination(A, b)

  ! ============
  ! === 出力 ===
  ! ============
  write(*, '(E20.13)') (b(i), i = 1, n)

  deallocate(A, b)

  stop
end program main

そして,最後に Makefile である.

FC := gfortran
FFLAG := -O2
PROG := gaussSolver
SRCS := gaussianElimination.f90 mainRoutine.f90

all: $(PROG)

$(PROG): $(SRCS)
  $(FC) -o $@ $(FFLAG) $^

.PHONY: clean
clean:
  rm -f $(PROG) *.mod

ファイル読み込みは,以前と同様で,最初に次元数,次に係数行列,右辺ベクトルという並びのものを用意する.

ガウスの消去法(MATLAB バージョン)

どうも,筆者です.部分ピボット選択付きのガウスの消去法を C 言語と Fortran で書いてきたが,MATLABスクリプトを探している人もいた.

目的

なので,今回は,MATLAB 用にガウスの消去法を書き直すことにした.これも久しぶりに使うので,もっと効率化できる部分があるかもしれない.まぁ,MATLAB 用にわざわざ 1 から書く人はいない(組み込みの関数を使うべきである)と思うので,勉強用として考えれば,速度と精度はそこまで必要にならないだろう.

C 言語と Fortran は,以下でコードを公開している.

workspacememory.hatenablog.com workspacememory.hatenablog.com

MATLAB 用のコード

MATLAB 用に書いていて気付いたが,Fortran も同様なコードに落とせるのではないか(確か,ベクトル演算できたよなぁ).

%===================================%
%                                   %
% gaussSolver                       %
%                                   %
% A: coefficient matrix, A(row,col) %
% b: right side vector,  b(row)     %
%                                   %
% return: solution vector x         %
%===================================%
function [x] = gaussSolver(A,b)
    [n, ~] = size(A);

    for i = 1:(n - 1)
        % i 列目のうち,最大のものを探す
        [~, id] = max(abs(A(i:n, i)));

        if id ~= 1
            pivot = id + i - 1;
            % 行の入れ替え
            tmpVec = A(i, :);
            A(i, :) = A(pivot, :);
            A(pivot, :) = tmpVec;

            % 右辺ベクトルの入れ替え
            tmpScalar = b(i);
            b(i) = b(pivot);
            b(pivot) = tmpScalar;
        end
        diagVal = A(i, i);

        % 対角成分が eps よりも小さい場合は,エラー処理
        if (abs(diagVal) < eps)
            error('Error: diagonal component is less than eps=%.15e\n', eps);
        end

        % ========
        % 前進消去
        % ========
        for row = (i + 1):n
            idList = i:n;
            weight = A(row, i) / diagVal;
            A(row, idList) = A(row, idList) - weight * A(i, idList);
            b(row) = b(row) - weight * b(i);
        end
    end

    % ========
    % 後退代入
    % ========
    b(n) = b(n) / A(n, n);
    for row = (n - 1):(-1):1
        idList = (row + 1):n;
        b(row) = (b(row) - A(row, idList) * b(idList)) / A(row, row);
    end
    x = b;
end

動作確認

筆者は,MATLAB を持っていないので,Octave を利用して,検証を行った.その際,テストスクリプトとして,以下のようなものを作成した.

n = 10;
A = rand(n);
xexact = (1:n)';
b = A * xexact;

xhat = gaussSolver(A, b)

これを,Octave で実行したところ,真の解の近似解が得られたので,正しく動作していると考えられる.

LU 分解で連立一次方程式を解く(Fortran バージョン)

どうも,筆者です.前回に続き,Fortran で LU 分解を行うプログラムを作成してみた.LU 分解については,以前の記事を参照すること.

workspacememory.hatenablog.com

LU 分解のプログラム

需要あるのだろうか.これは,「luDecompSolver.f」というファイル名で保存している.

!----------------------------------------------------------------------!
!----------------------     LU Decomposition     ----------------------!
!----------------------------------------------------------------------!
!23456789|123456789|123456789|123456789|123456789|123456789|123456789|12
!        1         2         3         4         5         6         7

      subroutine luDecomp(n,pivot,matrix)
      implicit none

!     === arguments ===
      integer*4 :: n
      integer*4 :: pivot(n)
      double precision :: matrix(n,n)
!     n:      rank, scalar
!     pivot:  pivot vector, pivot(row)
!     matrix: coefficient matrix, matrix(row,col)

!     --- local variables ---
      integer*4 :: row,col,k,ip,iptmp
      double precision :: tmp,valmax,weight,mineps
      mineps=1e-10

      do k=1,n
        pivot(k)=k
      end do

      do k=1,n-1
        valmax=abs(matrix(k,k))
        ip=k

        do row=k+1,n
          tmp=abs(matrix(row,k))

          if (valmax.lt.tmp) then
            valmax=tmp
            ip=row
          end if
        end do

!       the diagonal component is less than mineps
        if (valmax.lt.mineps) then
          write(*,100) 'diagonal component is less than',mineps
100       format(a,1X,G15.7)
          return
        else if (ip.ne.k) then
          do col=k,n
            tmp=matrix(ip,col)
            matrix(ip,col)=matrix(k,col)
            matrix(k,col)=tmp
          end do
          iptmp=pivot(ip)
          pivot(ip)=pivot(k)
          pivot(k)=iptmp

          do col=1,k-1
            tmp=matrix(k,col)
            matrix(k,col)=matrix(ip,col)
            matrix(ip,col)=tmp
          end do
        end if

        do row=k+1,n
          weight=matrix(row,k)/matrix(k,k)
          matrix(row,k)=weight

          do col=k+1,n
            matrix(row,col)
     *      =matrix(row,col)-weight*matrix(k,col)
          end do
        end do
      end do

      return

      end

!-----------------   last line of LU Decomposition   ------------------!
!        1         2         3         4         5         6         7
!23456789|123456789|123456789|123456789|123456789|123456789|123456789|12



!----------------------------------------------------------------------!
!----------------------        LU Solver         ----------------------!
!----------------------------------------------------------------------!
!23456789|123456789|123456789|123456789|123456789|123456789|123456789|12
!        1         2         3         4         5         6         7

      subroutine luSolver(n,pivot,matrix,b)
      implicit none

!     === arguments ===
      integer*4 :: n
      integer*4 :: pivot(n)
      double precision :: matrix(n,n),b(n)
!     n:      rank, scalar
!     pivot:  pivot vector, pivot(row)
!     matrix: coefficient matrix, matrix(row,col)
!     b:      right side vector, b(row)

!     --- local variables ---
      integer*4 :: row,id
      double precision :: tmp,y(n)

!     =====================
!     forkward substitution
!     =====================
      y(1)=b(pivot(1))
      do row=2,n
        id=row-1
        y(row)=b(pivot(row))-sum(matrix(row,1:id)*y(1:id))
      end do

!     =====================
!     backward substitution
!     =====================
      b(n)=y(n)/matrix(n,n)
      do row=n-1,1,-1
        id=row+1
        tmp=y(row)-sum(matrix(row,id:n)*b(id:n))
        b(row)=tmp/matrix(row,row)
      end do

      end

!-----------------      last line of  LU Solver      ------------------!
!        1         2         3         4         5         6         7
!23456789|123456789|123456789|123456789|123456789|123456789|123456789|12

main routine

いつも通り,main routine のコードも載せておく.ちょっと調べて,動的配列を使ってみた.この動的配列は Fortran90 から導入されたらしい.エラー処理等を入れたので,goto 文とかがあって読みにくい.「main_lu.f」として保存した.

!----------------------------------------------------------------------!
!---------------------------   main  code   ---------------------------!
!----------------------------------------------------------------------!
!23456789|123456789|123456789|123456789|123456789|123456789|123456789|12
!        1         2         3         4         5         6         7

      implicit none

      character :: fmtstr*32,argv*16,fname*16
      integer*4 :: n,i,j
      integer*4,allocatable :: pivot(:)
      double precision,allocatable :: matrix(:,:),b(:)

!     === check arguments ===
      if (iargc().ne.1) then
        call getarg(0,argv)
        write(*,'("Usage: ", a, "[data file name]")') argv
        stop
!     === read arguments ===
      else
        call getarg(1,argv)
        read(argv,'(a16)') fname
      end if

!     === read data from file ===
      open(10,file=fname,status='old',err=1)
      goto 100
1     write(*,'("Error: ", a, "cannot open")') fname
      stop

100   continue
      read(10,*)n
      allocate(pivot(n),matrix(n,n),b(n))

      do i=1,n
        read(10,*,end=200) (matrix(i,j),j=1,n),b(i)
      end do
200   continue
      close(unit=10)
!     ===========================

      write(fmtstr,'("("I0"(G15.7,1X),G15.7)")') n
      do i=1,n
        write(*,fmtstr) (matrix(i,j),j=1,n),b(i)
      end do

      ! execute LU decomposition
      call luDecomp(n,pivot,matrix)
      ! solve
      call luSolver(n,pivot,matrix,b)

      write(*,'(/ "answer:")')
      write(*,'(G15.7)') (b(i),i=1,n)
      deallocate(pivot,matrix,b)

      stop

      end

読み込むファイルは,

[次元数(n: rank)]
[係数行列 (1,1) 成分] [係数行列 (1,2) 成分] ... [係数行列 (1,n) 成分] [右辺ベクトル (1)]
[係数行列 (2,1) 成分] [係数行列 (2,2) 成分] ... [係数行列 (2,n) 成分] [右辺ベクトル (2)]
           ...                   ...                       ...                ...
           ...                   ...                       ...                ...
[係数行列 (n,1) 成分] [係数行列 (n,2) 成分] ... [係数行列 (n,n) 成分] [右辺ベクトル (n)]

という形式にする.前回の例だと,

3
2.0 1.0 -2.0 1.0
1.0 1.0 -1.0 4.0
1.0 -2.0 3.0 -1.0

となる.

Makefile

前回と同様に,Makefile も載せておく.

FC := gfortran
PROG := solveLU
SRCS := luDecompSolver.f main_lu.f
OBJS := $(SRCS:%.f=%.o)

all: $(PROG)

$(PROG): $(OBJS)
  $(FC) -o $@ $^

%.o: %.f
  $(FC) -c -O2 $<

.PHONY: clean
clean:
  rm -f $(OBJS) $(PROG)

実行方法

Fortran のプログラムを上から順に,「luDecompSolver.f」,「main_lu.f」として保存したとする.また,Makefile を「Makefile」として保存したとする.その段階で,

[hoge@local]$ ls
Makefile  luDecompSolver.f  main_lu.f

となっているはずである.まず,make コマンドを利用してコンパイルする.

[hoge@local]$ make
gfortran -c -O2 luDecompSolver.f
gfortran -c -O2 main_lu.f
gfortran -o solveLU luDecompSolver.o main_lu.o

「solveLU」という実行ファイルが出来上がる.もし,make コマンドがなければ,上の実行結果(gfortran から始まる部分)をコピペして端末で実行すればよい.後は,データファイル input.dat を用意して,

[hoge@local]$ ./solveLU input.dat

とすれば,計算結果が出力される.また,実行ファイル,オブジェクトファイルの削除は,

[hoge@local]$ make clean
rm -f luDecompSolver.o main_lu.o solveLU

とすればよい.

ガウスの消去法(Fortran バージョン)

お久しぶりです.筆者です.

アクセス解析のデータをみた

久しぶりに,ブログに戻ってきた.最初に,アクセス解析のデータをみた. すると,多くの人がガウスの消去法関連でアクセスしている事が分かった.その中でも,Fortran 言語でガウスの消去法を探している人が多い事に気付いた.

ガウスの消去法を Fortran 言語に書き直す

筆者は,ほとんど C 言語を利用するが,Fortran も少しは触れた事があるので,色々調べながら,以前書いた記事「ガウスの消去法のプログラム」を Fortran77 の固定形式で書き直す事にした. 何故,Fortran77 の固定形式かというと,筆者がそれしか読んだ事がないためである.この平成の時代に,Fortran77 の固定形式を勉強するとは思わなかったが,昔の方が書いたプログラムを使う以上,仕方ない事である.

workspacememory.hatenablog.com

書き直したもの

という事で,色々調べながら,C 言語のプログラムを Fortran で書き直した.読んだ事あるのは固定形式だが,書いた事はないので,コンパイルが通る程度にしか書けない.90/95 の表現もあるかもしれない.

!----------------------------------------------------------------------!
!----------------------   Gaussian elimination   ----------------------!
!----------------------------------------------------------------------!
!23456789|123456789|123456789|123456789|123456789|123456789|123456789|12

      subroutine gaussSolver(n,matrix,b)
      implicit none

!     === arguments ===
      integer*4 :: n
      double precision :: matrix(n,n),b(n)
!     n:      rank, scalar
!     matrix: coefficient matrix, matrix(row,col)
!     b:      right side vector, b(row)

!     --- local variables ---
      integer*4 :: i,row,col,pivot
      double precision :: tmp,valmax,diag,scl,mineps
      mineps=1e-10

      do i=1,n-1
!       execute partial pivoting
        pivot=i
        valmax=abs(matrix(i,i))

!       search maximum value in a column
        do row=i+1,n
          tmp=abs(matrix(row,i))

          if (valmax.lt.tmp) then
            pivot=row
            valmax=tmp
          end if
        end do

!       replace
        if (pivot.ne.i) then
          do col=1,n
            tmp=matrix(i,col)
            matrix(i,col)=matrix(pivot,col)
            matrix(pivot,col)=tmp
          end do
          tmp=b(i)
          b(i)=b(pivot)
          b(pivot)=tmp
        end if
        diag=matrix(i,i)

        if (abs(diag).lt.mineps) then
          return
        end if

!       ===================
!       forward elimination
!       ===================
        do row=i+1,n
          scl=matrix(row,i)/diag

          do col=i,n
            matrix(row,col)=matrix(row,col)-matrix(i,col)*scl
          end do
          b(row)=b(row)-b(i)*scl
        end do
      end do

!     =====================
!     backward substitution
!     =====================
      b(n)=b(n)/matrix(n,n)
      do row=n-1,1,-1
        tmp=b(row)-sum(matrix(row,(row+1):n)*b((row+1):n))
        b(row)=tmp/matrix(row,row)
!------------------------------------------------------------
!     do row=n,1,-1
!        valsum=b(row)
!
!        do col=row+1,n
!          valsum=valsum-matrix(row,col)*b(col)
!        end do
!        b(row)=valsum/matrix(row,row)
!      end do
!------------------------------------------------------------

      return
      end

main routine

ついでに,main routine の部分も以下に示しておく.

!----------------------------------------------------------------------!
!---------------------------   main  code   ---------------------------!
!----------------------------------------------------------------------!
!23456789|123456789|123456789|123456789|123456789|123456789|123456789|12

      implicit none

      character :: fmtstr*32
      integer*4 :: n,i,j
      parameter(n=3)
      double precision :: matrix(n,n),b(n)

      matrix(1,1)=2.D0
      matrix(1,2)=1.D0
      matrix(1,3)=-2.D0
      matrix(2,1)=1.D0
      matrix(2,2)=1.D0
      matrix(2,3)=-1.D0
      matrix(3,1)=1.D0
      matrix(3,2)=-2.D0
      matrix(3,3)=3.D0
      b(1)=1.D0
      b(2)=4.D0
      b(3)=-1.D0
      write(fmtstr,'("("I0"(G15.7,1X),G15.7)")') n

      do i=1,n
        write(*,fmtstr) (matrix(i,j),j=1,n),b(i)
      end do

      ! output matrix and right side vector
      open(10,file='input.txt',status='replace')
      do i=1,n
        write(10,fmtstr) (matrix(i,j),j=1,n),b(i)
        matrix(i,:)=0.D0
        b(i)=0.D0
      end do
      close(unit=10)

      ! read data from file
      open(11,file='input.txt',status='old')
      do i=1,n
        read(11,*,end=100) (matrix(i,j),j=1,n),b(i)
      end do
100   continue
      close(unit=11)

      ! execute Gaussian elimination
      call gaussSolver(n,matrix,b)

      write(*,'(/ "answer:")')
      write(*,'(G15.7)') (b(i),i=1,n)

      stop

      end

いつも通り,英語が出来ないのはスルーして欲しい.無駄にファイル出力して,ファイル読み込みしているが,これは,単純に,Fortran で読み書きが出来るかどうかを確認しているだけである.たいした意味は無い.

Makefile

上のプログラムは自由に使ってもらってかまわないが,コンパイルに困る可能性もある.そのため,Makefile を作成した.Ubuntu 14.04 LTS でインストールできる gfortran で動作を確認している. Makefile を使った事がない人は,1 つのファイルに全て書いて,それをコンパイルしてもらえればよいと思う. また,この gfortran は,Fortran95 用のコンパイラなので,フリーダムな書き方をしていても文法のミスさえなければ通るみたいだ.以下に,Makefile を示す.

FC := gfortran
PROG := solveGauss
SRCS := gaussSolver.f prog_main.f
OBJS := $(SRCS:%.f=%.o)

all: $(PROG)

$(PROG): $(OBJS)
  $(FC) -o $@ $^

%.o: %.f
  $(FC) -c -O2 $<

.PHONY: clean
clean:
  rm -f $(OBJS) $(PROG)

sub routine 「gaussSolver」を「gaussSolver.f」として,main routine 「main code」を「prog_main.f」として保存し,make とすると,実行ファイル「solveGauss」が出来上がる.後は,実行すると解が得られる. make clean とすると,.o ファイルと solveGauss が削除される.

[hoge@local]$ ls
Makefile gaussSolver.f prog_main.f

[hoge@local]$ make
gfortran -c -O2 gaussSolver.f
gfortran -c -O2 prog_main.f
gfortran -o solveGauss gaussSolver.o prog_main.o

[hoge@local]$ make clean
rm -f gaussSolver.o prog_main.o solveGauss