依存関係の追加

ここでは,fpmによる依存関係の利用方法と,既存のfpmプロジェクトを再利用する方法を取り扱います.

標準ライブラリの利用

fpmを用いて新規プロジェクトを開始し,ファイルを読み込んで特定のパターンを見つけ,それを置換するコマンドラインアプリケーションを構築することにします.置換する関数を書きたくないので,Fortran標準ライブラリ(stdlib)を依存関係として利用します.パッケージマニフェスト内のdependencies設定項目で,stdlibを定義します.

fpm.toml
name = "demo"
version = "0.1.0"

[dependencies]
stdlib = "*"

差し替えを実行する手続をもつモジュールを作成します.これには,三つの段階が必要です.

  1. 一つの装置から1行を読み込み

  2. 文字列内の特定のパターンを置き換え

  3. 出力に新しい文字列を書き出し

これを実現するために,stdlib_stringsモジュールにあるreplace_all関数を用います.実装を以下に示します.

src/demo.f90
module demo
  use stdlib_io, only : getline
  use stdlib_strings, only : replace_all
  implicit none
  private

  public :: substitute

contains

  !> Read all lines from input, replace pattern and print it to output
  subroutine substitute(input, output, pattern, replacement)
    !> Formatted input unit
    integer, intent(in) :: input
    !> Formatted output unit
    integer, intent(in) :: output
    !> Pattern to replace in input
    character(len=*), intent(in) :: pattern
    !> Replacement for pattern in output
    character(len=*), intent(in) :: replacement

    character(len=:), allocatable :: line
    integer :: stat

    do
      call getline(input, line, stat)
      if (stat /= 0) exit
      write(output, '(a)') replace_all(line, pattern, replacement)
    end do
  end subroutine substitute

end module demo

最後に,作成した新しい手続を使えるようにするために,コマンドラインから呼び出すメインルーチンが必要です.

app/main.f90
program main
  use, intrinsic :: iso_fortran_env, only : output_unit
  use demo, only : substitute
  implicit none
  character(len=256) :: pattern, replacement, input_file
  integer :: input

  call get_command_argument(1, pattern)
  call get_command_argument(2, replacement)
  call get_command_argument(3, input_file)

  open(newunit=input, file=input_file, status='old')
  call substitute(input, output_unit, trim(pattern), trim(replacement))
  close(input)
end program main

fpmを用いてメインルーチンを呼び出し,動作を確認します.

❯ fpm run -- demo substitute fpm.toml
name = "substitute"
version = "0.1.0"

[dependencies]
stdlib = "*"

テストフレームワークの追加

Before we continue implementing new features, we want to add some tests to verify that our implementation keeps working as we modify it. A minimalist testing framework is available with test-drive. Since the testing framework is only required when developing the package itself, but not for other packages which might in the future make use of our modules, we add it as a development dependency. The test-drive package is added in the dev-dependencies table as shown below

fpm.toml
name = "demo"
version = "0.1.0"

[dependencies]
stdlib = "*"

[dev-dependencies]
test-drive.git = "https://github.com/fortran-lang/test-drive"
test-drive.tag = "v0.4.0"

注釈

テストフレームワークのような開発時に参照する依存関係に対しては,タグを指定して,使用したい厳密なバージョンを選択します.

ここで作成している関数はそれ単体で動作するため,単純な単体テストを記述できます.入力を生成して出力を取得する単体機能を作成することにします.とりあえず,単純な1行の差し替えを,一つのテストケースとして追加します.

test/main.f90
module test_demo
  use demo, only : substitute
  use stdlib_io, only : getline
  use testdrive, only : error_type, unittest_type, new_unittest, check
  implicit none
  private

  public :: collect_demo

contains

  !> Collect all exported unit tests
  subroutine collect_demo(testsuite)
    !> Collection of tests
    type(unittest_type), allocatable, intent(out) :: testsuite(:)

    testsuite = [new_unittest("substitute", test_substitute)]
  end subroutine collect_demo

  !> Check substitution of a single line
  subroutine test_substitute(error)
    !> Error handling
    type(error_type), allocatable, intent(out) :: error
    integer :: input, output, stat
    character(len=:), allocatable :: line
    open(newunit=input, status="scratch")
    write(input, '(a)') "This is a valid test"
    rewind(input)

    open(newunit=output, status="scratch")
    call substitute(input, output, "test", "example")
    close(input)

    rewind(output)
    call getline(output, line, stat)
    close(output)

    call check(error, line, "This is a valid example")
  end subroutine test_substitute
end module test_demo

program tester
  use, intrinsic :: iso_fortran_env, only : error_unit
  use testdrive, only : run_testsuite
  use test_demo, only : collect_demo
  implicit none
  integer :: stat

  stat = 0
  call run_testsuite(collect_demo, error_unit, stat)

  if (stat > 0) then
    write(error_unit, '(i0, 1x, a)') stat, "test(s) failed!"
    error stop
  end if

end program tester

fpmを用いて作成したテストを実行します.

❯ fpm test
  Starting substitute ... (1/1)
       ... substitute [PASSED]

複数の単体テストにおける単体機能の作成は,反復的な作業になります.この種の作業は通常,独立した手順で行うことができ,いくつかのテストで再利用されます.

ビルド対象固有の依存関係

依存関係は,特定のビルド対象に対してのみ利用できます.ここで導入するビルド対象固有の依存関係は,実行ファイルにコマンドラインインタフェースを追加するパッケージであって,ライブラリの依存関係ではありません.

fpm.toml
name = "demo"
version = "0.1.0"

[dependencies]
stdlib = "*"

[dev-dependencies]
test-drive.git = "https://github.com/fortran-lang/test-drive"
test-drive.tag = "v0.4.0"

[[executable]]
name = "demo"
[executable.dependencies]
M_CLI2.git = "https://github.com/urbanjost/M_CLI2"

M_CLI2を用いてコマンドライン入力を処理するために,メインルーチンを若干再構成します.配列unnamedは,位置関係を含むコマンドライン引数全てを保持しています.最初の二つをパターンと置換に利用し,残りの全ての引数を入力として用います.また,出力をリダイレクトするオプションも追加しました.最終的なメインルーチンは,次のようになりました.

app/main.f90
program main
  use, intrinsic :: iso_fortran_env, only : output_unit
  use demo, only : substitute
  use m_cli2, only : set_args, unnamed, sget
  implicit none
  character(len=:), allocatable :: input_file, output_file, pattern, replacement
  integer :: input, output, i

  call set_args("--output:o ''")

  output_file = trim(sget("output"))
  if (len(output_file) > 0) then
    open(file=output_file, newunit=output)
  else
    output = output_unit
  end if

  pattern = trim(unnamed(1))
  replacement = trim(unnamed(2))

  do i = 3, size(unnamed)
    input_file = trim(unnamed(i))
    open(file=input_file, newunit=input, status='old')
    call substitute(input, output_unit, trim(pattern), trim(replacement))
    close(input)
  end do

  if (output /= output_unit) close(output)
end program main

fpmを用いて簡単な確認を再度行います.

❯ fpm run -- demo substitute fpm.toml
name = "substitute"
version = "0.1.0"

[dependencies]
stdlib = "*"

[dev-dependencies]
test-drive.git = "https://github.com/fortran-lang/test-drive"
test-drive.tag = "v0.4.0"

[[executable]]
name = "substitute"
[executable.dependencies]
M_CLI2.git = "https://github.com/urbanjost/M_CLI2"

期待通りに2箇所の差し替えが行われました.

まとめ

ここでは以下の方法を学びました.

  • パッケージマニフェスト内で別のfpmプロジェクトを参照する方法

  • テストのために開発時の依存関係を追加する方法

  • 実行ファイルに依存関係を追加する方法