source: trunk/LMDZ.COMMON/libf/misc/parse_args_mod.F90

Last change on this file was 3869, checked in by jbclement, 4 weeks ago

PEM:
Bug correction to detect the job time limit with PBS/TORQUE. Making it more robust and automatic for the launching script and the Fortran code.
JBC

File size: 3.8 KB
Line 
1MODULE parse_args_mod
2
3!***********************************************************************
4! DESCRIPTION:
5!    Provides a subroutine to parse command-line options.
6!    Recognizes:
7!       --help
8!       --version [file]
9!       --jobid <id>
10!       --add-sso
11!***********************************************************************
12
13use pgrm_version_mod,  only: print_pgrm_version
14use job_id_mod,        only: get_job_id
15use job_timelimit_mod, only: get_job_timelimit
16
17implicit none
18
19logical :: add_sso_fields = .false. ! Default: do not include SSO fields
20
21!=======================================================================
22contains
23!=======================================================================
24
25SUBROUTINE parse_args()
26
27implicit none
28
29!---- Arguments
30
31!---- Variables
32integer        :: narg, i, eq_pos
33character(256) :: arg, key, vlu, jobid
34
35!---- Code
36narg = command_argument_count() ! Get the number of command-line arguments
37if (narg == 0) return ! No option: normal/default case, nothing to do
38
39i = 1
40do while (i <= narg)
41    call get_command_argument(i,arg) ! Read the argument given to the program
42
43    eq_pos = index(arg,'=')
44    if (eq_pos > 0) then ! Handle "--keyword=value" style
45        key = strip(arg(:eq_pos - 1))
46        vlu = strip(arg(eq_pos + 1:))
47    else ! Handle "--keyword [value]" style
48        key = strip(arg)
49        vlu = ''
50        if (i < narg) then
51            call get_command_argument(i + 1,arg) ! Read the argument given to the program
52            if (len_trim(adjustl(arg)) > 0 .and. arg(1:2) /= '--') then
53                vlu = strip(arg)
54                i = i + 1 ! To skip the value argument next time
55            endif
56        endif
57    endif
58
59    select case (to_lower(key))
60        case('--help')
61            call print_usage()
62            call exit(0)
63
64        case ('--version')
65            if (len_trim(adjustl(vlu)) > 0) then
66                call print_pgrm_version(vlu)
67            else
68                call print_pgrm_version()
69            endif
70            call exit(0)
71
72        case ('--add-sso')
73            add_sso_fields = .true.
74            write(*,*) 'SSO fields will be included in "start_archive.nc"'
75
76        case ('--auto-exit')
77            call get_job_id(jobid)
78            call get_job_timelimit(jobid)
79
80        case default
81            write(*,*) 'Error: unknown option "', key, '".'
82            call exit(1)
83    end select
84
85    i = i + 1
86enddo
87
88END SUBROUTINE parse_args
89!=======================================================================
90
91SUBROUTINE print_usage()
92    write(*,*)
93    write(*,*) 'Usage: program [options]'
94    write(*,*) '  --help              Show this help message and exit'
95    write(*,*) '  --version [file]    Print program version and exit (optional output file)'
96    write(*,*) '  --add-sso           Add SSO fields to "start_archive.nc" (only available for Mars start2archive)'
97    write(*,*) '  --auto-exit         Enable automatic termination before reaching the job time limit (only available for the PEM)'
98    write(*,*)
99END SUBROUTINE print_usage
100!=======================================================================
101
102PURE FUNCTION strip(s) RESULT(t)
103
104implicit none
105
106!---- Arguments
107character(*), intent(in) :: s
108character(len(s)) :: t
109
110!---- Variables
111
112!---- Code
113t = trim(adjustl(s))
114
115END FUNCTION
116!=======================================================================
117
118PURE FUNCTION to_lower(s) RESULT(low)
119
120implicit none
121
122!---- Arguments
123character(*), intent(in) :: s
124character(len(s)) :: low
125
126!---- Variables
127integer :: i
128
129!---- Code
130low = s
131do i = 1,len(s)
132    if (iachar(s(i:i)) >= iachar('A') .and. iachar(s(i:i)) <= iachar('Z')) low(i:i) = achar(iachar(s(i:i)) + 32)
133enddo
134
135END FUNCTION to_lower
136
137
138END MODULE parse_args_mod
Note: See TracBrowser for help on using the repository browser.