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

Last change on this file since 4031 was 4003, checked in by aslmd, 2 weeks ago

MESOSCALE: functionality to have version diagnosis in the executable does not work because homemade makefile do not create the Fortran subroutine that is necessary (like makelmdz_fcm now does). comment out this functionality using MESOSCALE precompiling flags.

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