spx_command_line.F90 Source File


Contents

Source Code


Source Code

!> 命令行参数
module spx_command_line

    use argparse, only: argparser
    use spx_logger, only: lgr_obj
    use fffc_module, only: unix_path, esc => escape
    implicit none

    private
    public :: cli_obj

    !> 命令行参数
    type, public :: command_line
        character(128) :: working_directory = '.'   !! 工作目录
        integer :: num_threads = 4                  !! 线程数
        logical :: debug_mode = .false.             !! 调试模式
        character(64) :: file = 'spx.nml'           !! 输入文件
    contains
        procedure :: parse
    end type command_line

    type(command_line) :: cli_obj                   !! 命令行实例

contains

    !> 初始化和解析命令行参数
    subroutine parse(self)
        class(command_line), intent(out) :: self
        type(argparser) :: args
        character(*), parameter :: version_text = &
            &"Version    : 0.6.202310, alpha (Built on "//__DATE__//")\n&
            &Program    : SPX\n&
            &Description: Smoothed Particle Hydrodynamics transient solver\n&
            &Home Page  : https://gitee.com/ship-motions/SmoothedParticleXimulation\n&
            &Author     : ZUO Zhihua (E-mail: zuo.zhihua@qq.com)\n&
            &License    : BSD-3-Clause"

        args = argparser("Smoothed Particle Hydrodynamics transient solver.")

        call args%set_program_name("spx")
        call args%add_help_option()
        call args%add_sc_option('-v', '--version', 'show version info', show_version_info)
        call args%add_option_logical("-d", "--debug", "debug mode")
        call args%add_option_string("-C", "--directory", "working directory", ".")
        call args%add_option_integer("-t", "--num-threads", "number of OpenMP threads (deprecated)", 4)
        call args%add_option_string("-f", "--file", "input file", "spx.nml")

        call args%parse()

        self%working_directory = unix_path(args%get_option_string("--directory"))
        self%num_threads = args%get_option_integer("--num-threads")
        self%debug_mode = args%get_option_logical("--debug")
        self%file = trim(args%get_option_string("--file"))

    contains

        !> 显示版本信息
        subroutine show_version_info()

            print '(a)', esc(version_text)

        end subroutine show_version_info

    end subroutine parse

end module spx_command_line