-
Notifications
You must be signed in to change notification settings - Fork 1
/
f2kcli_nagw.f90
209 lines (209 loc) · 7.59 KB
/
f2kcli_nagw.f90
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
! F2KCLI : Fortran 200x Command Line Interface
! copyright Interactive Software Services Ltd. 2001-2003
! For conditions of use see manual.txt
!
! Platform : Unix/Linux
! Compilers : NAGware f95
! F
! To compile : f95 -c f2kcli.f90
! F -c f2kcli.f90
! Implementer : Lawson B. Wakefield, I.S.S. Ltd.
! Date : February 2001
! Updated February 2003
!
MODULE F2KCLI
!
PUBLIC :: GET_COMMAND
PUBLIC :: COMMAND_ARGUMENT_COUNT
PUBLIC :: GET_COMMAND_ARGUMENT
!
PRIVATE
!
CONTAINS
!
SUBROUTINE GET_COMMAND(COMMAND,LENGTH,STATUS)
!
! Description. Returns the entire command by which the program was
! invoked.
!
! Class. Subroutine.
!
! Arguments.
! COMMAND (optional) shall be scalar and of type default character.
! It is an INTENT(OUT) argument. It is assigned the entire command
! by which the program was invoked. If the command cannot be
! determined, COMMAND is assigned all blanks.
! LENGTH (optional) shall be scalar and of type default integer. It is
! an INTENT(OUT) argument. It is assigned the significant length
! of the command by which the program was invoked. The significant
! length may include trailing blanks if the processor allows commands
! with significant trailing blanks. This length does not consider any
! possible truncation or padding in assigning the command to the
! COMMAND argument; in fact the COMMAND argument need not even be
! present. If the command length cannot be determined, a length of
! 0 is assigned.
! STATUS (optional) shall be scalar and of type default integer. It is
! an INTENT(OUT) argument. It is assigned the value 0 if the
! command retrieval is sucessful. It is assigned a processor-dependent
! non-zero value if the command retrieval fails.
!
USE F90_UNIX_ENV
!
CHARACTER(LEN=*), INTENT(OUT), OPTIONAL :: COMMAND
INTEGER , INTENT(OUT), OPTIONAL :: LENGTH
INTEGER , INTENT(OUT), OPTIONAL :: STATUS
!
INTEGER :: IARG,NARG,IPOS
INTEGER , SAVE :: LENARG
CHARACTER(LEN=2000), SAVE :: ARGSTR
LOGICAL , SAVE :: GETCMD = .TRUE.
!
! Under Unix we must reconstruct the command line from its constituent
! parts. This will not be the original command line. Rather it will be
! the expanded command line as generated by the shell.
!
IF (GETCMD) THEN
NARG = IARGC()
IF (NARG > 0) THEN
IPOS = 1
DO IARG = 1,NARG
CALL GETARG(IARG,ARGSTR(IPOS:))
LENARG = LEN_TRIM(ARGSTR)
IPOS = LENARG + 2
IF (IPOS > LEN(ARGSTR)) EXIT
END DO
ELSE
ARGSTR = " "
LENARG = 0
ENDIF
GETCMD = .FALSE.
ENDIF
IF (PRESENT(COMMAND)) COMMAND = ARGSTR
IF (PRESENT(LENGTH)) LENGTH = LENARG
IF (PRESENT(STATUS)) STATUS = 0
RETURN
END SUBROUTINE GET_COMMAND
!
FUNCTION COMMAND_ARGUMENT_COUNT() RESULT(NARGS)
!
! Description. Returns the number of command arguments.
!
! Class. Inquiry function
!
! Arguments. None.
!
! Result Characteristics. Scalar default integer.
!
! Result Value. The result value is equal to the number of command
! arguments available. If there are no command arguments available
! or if the processor does not support command arguments, then
! the result value is 0. If the processor has a concept of a command
! name, the command name does not count as one of the command
! arguments.
!
USE F90_UNIX_ENV
!
INTEGER :: NARGS
!
NARGS = IARGC()
RETURN
END FUNCTION COMMAND_ARGUMENT_COUNT
!
SUBROUTINE GET_COMMAND_ARGUMENT(NUMBER,VALUE,LENGTH,STATUS)
!
! Description. Returns a command argument.
!
! Class. Subroutine.
!
! Arguments.
! NUMBER shall be scalar and of type default integer. It is an
! INTENT(IN) argument. It specifies the number of the command
! argument that the other arguments give information about. Useful
! values of NUMBER are those between 0 and the argument count
! returned by the COMMAND_ARGUMENT_COUNT intrinsic.
! Other values are allowed, but will result in error status return
! (see below). Command argument 0 is defined to be the command
! name by which the program was invoked if the processor has such
! a concept. It is allowed to call the GET_COMMAND_ARGUMENT
! procedure for command argument number 0, even if the processor
! does not define command names or other command arguments.
! The remaining command arguments are numbered consecutively from
! 1 to the argument count in an order determined by the processor.
! VALUE (optional) shall be scalar and of type default character.
! It is an INTENT(OUT) argument. It is assigned the value of the
! command argument specified by NUMBER. If the command argument value
! cannot be determined, VALUE is assigned all blanks.
! LENGTH (optional) shall be scalar and of type default integer.
! It is an INTENT(OUT) argument. It is assigned the significant length
! of the command argument specified by NUMBER. The significant
! length may include trailing blanks if the processor allows command
! arguments with significant trailing blanks. This length does not
! consider any possible truncation or padding in assigning the
! command argument value to the VALUE argument; in fact the
! VALUE argument need not even be present. If the command
! argument length cannot be determined, a length of 0 is assigned.
! STATUS (optional) shall be scalar and of type default integer.
! It is an INTENT(OUT) argument. It is assigned the value 0 if
! the argument retrieval is sucessful. It is assigned a
! processor-dependent non-zero value if the argument retrieval fails.
!
! NOTE
! One possible reason for failure is that NUMBER is negative or
! greater than COMMAND_ARGUMENT_COUNT().
!
USE F90_UNIX_ENV
!
INTEGER , INTENT(IN) :: NUMBER
CHARACTER(LEN=*), INTENT(OUT), OPTIONAL :: VALUE
INTEGER , INTENT(OUT), OPTIONAL :: LENGTH
INTEGER , INTENT(OUT), OPTIONAL :: STATUS
!
! A temporary variable for the rare case case where LENGTH is
! specified but VALUE is not. An arbitrary maximum argument length
! of 1000 characters should cover virtually all situations.
!
CHARACTER(LEN=1000) :: TMPVAL
!
! Possible error codes:
! 1 = Argument number is less than minimum
! 2 = Argument number exceeds maximum
!
IF (NUMBER < 0) THEN
IF (PRESENT(VALUE )) VALUE = " "
IF (PRESENT(LENGTH)) LENGTH = 0
IF (PRESENT(STATUS)) STATUS = 1
RETURN
ELSE IF (NUMBER > IARGC()) THEN
IF (PRESENT(VALUE )) VALUE = " "
IF (PRESENT(LENGTH)) LENGTH = 0
IF (PRESENT(STATUS)) STATUS = 2
RETURN
END IF
!
! Get the argument if VALUE is present
!
IF (PRESENT(VALUE)) CALL GETARG(NUMBER,VALUE)
!
! The LENGTH option is fairly pointless under Unix.
! Trailing spaces can only be specified using quotes.
! Since the command line has already been processed by the
! shell before the application sees it, we have no way of
! knowing the true length of any quoted arguments. LEN_TRIM
! is used to ensure at least some sort of meaningful result.
!
IF (PRESENT(LENGTH)) THEN
IF (PRESENT(VALUE)) THEN
LENGTH = LEN_TRIM(VALUE)
ELSE
CALL GETARG(NUMBER,TMPVAL)
LENGTH = LEN_TRIM(TMPVAL)
END IF
END IF
!
! Since GETARG does not return a result code, assume success
!
IF (PRESENT(STATUS)) STATUS = 0
RETURN
END SUBROUTINE GET_COMMAND_ARGUMENT
!
END MODULE F2KCLI