添加依赖项

本教程介绍如何用fpm处理依赖项及复用现有的fpm项目。

使用Fortran标准库

我们从一个使用fpm的新项目开始。我们想构建一个命令行应用程序来读取文件,找到某个模式(pattern)并替换它。由于我们不想自己编写替换函数,我们将使用Fortran标准库(stdlib)作为依赖项。在包清单中,我们在依赖项表中定义stdlib

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

[dependencies]
stdlib = "*"

现在,我们创建一个模块,其中包含执行替换的过程。它需要三个步骤:

  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 = "*"

添加测试框架

在继续实现新功能之前,我们希望添加一些测试,以验证我们的实现在修改后是否保持工作状态。test-drive 提供了一个极简的测试框架。由于仅在开发包本身时才需要测试框架,而对于将来可能使用我们的模块的其它包则不需要,我们添加了开发依赖项。test-drive 包被添加到 dev-dependencies 表中,如下所示

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"

备注

像测试框架这样的开发依赖关系,我们通过指定标记(tag)来选择严格的版本引脚。

现在我们可以编写一个简单的单元测试。因为我们的函数执行需要文件通道,我们将创建暂存(scratch)通道来创建输入并捕获输出。现在,我们将添加一个简单的单行替换作为单个测试用例:

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"

输出看起来与预期一样,有两个替换。

总结

在本教程中,你学习了如何

  • 在包清单中添加对另一个fpm项目的依赖;

  • 添加用于测试的开发依赖项;

  • 使用可执行文件的依赖项。