添加依赖项

本教程介绍了 fpm 的依赖项用法以及如何重复使用现有 fpm 项目。

使用标准库

我们使用 fpm 启动一个新项目,我们希望构建一个命令行应用程序来读取文件、查找特定模式并替换它。由于我们不想自己编写替换函数,我们将使用 Fortran 标准库 (stdlib) 作为依赖项。在程序包清单中,我们使用 dependencies 表中的 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"

注意

对于像测试框架那样的开发依赖项,我们通过指定我们希望使用的标记来选择严格版本号。

现在我们可以编写一个简单的单元测试,因为我们的函数可处理单元,我们将创建临时单元来创建输入并捕获输出。现在,我们将添加一个简单的单行替换作为单一测试用例

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 处理命令行输入。未命名 数组包含所有位置命令行自变量,我们仍然将前两个用作模式和替代,并将所有剩余自变量用作输入。我们还添加了重定向输出的选项。我们的最终主程序如下所示

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 项目

  • 添加开发依赖项以进行测试

  • 使用依赖项进行可执行文件