ROMS
Loading...
Searching...
No Matches
stdinp_mod::getpar_i Interface Reference

Public Member Functions

subroutine getpar_0d_i (mymaster, value, keyword, inpname)
 
subroutine getpar_1d_i (mymaster, ndim, value, keyword, inpname)
 

Detailed Description

Definition at line 39 of file stdinp_mod.F.

Member Function/Subroutine Documentation

◆ getpar_0d_i()

subroutine stdinp_mod::getpar_i::getpar_0d_i ( logical, intent(in) mymaster,
integer, intent(out) value,
character (len=*), intent(in) keyword,
character (len=*), intent(in), optional inpname )

Definition at line 156 of file stdinp_mod.F.

157!
158!***********************************************************************
159! !
160! Reads a scalar integer parameter from ROMS standard input file. !
161! !
162! On Input: !
163! !
164! MyMaster Switch indicating Master process (logical) !
165! KeyWord Keyword associated with input parameter (string) !
166! InpName Standard input filename (string; OPTIONAL) !
167! !
168! On Output: !
169! !
170! Value Standard input parameter value (integer) !
171! !
172!***********************************************************************
173!
174! Imported variable declarations.
175!
176 logical, intent(in) :: MyMaster
177!
178 integer, intent(out) :: Value
179!
180 character (len=*), intent(in) :: KeyWord
181 character (len=*), intent(in), optional :: InpName
182!
183! Local variable declarations.
184!
185 logical :: foundit, GotFile
186!
187 integer :: InpUnit, Npts, Nval, io_err, status
188 integer :: Ivalue(1)
189!
190 real(dp), dimension(nRval) :: Rval
191!
192 character (len= 40) :: string
193 character (len=256) :: io_errmsg, line
194 character (len=256), dimension(nCval) :: Cval
195!
196!-----------------------------------------------------------------------
197! Read requested ROMS standard input integer parameter.
198!-----------------------------------------------------------------------
199!
200! Get standard input unit.
201!
202 io_err=0
203 IF (PRESENT(inpname)) THEN
204 inpunit=1
205 OPEN (inpunit, file=trim(inpname), form='formatted', &
206 & status='old', iostat=io_err, iomsg=io_errmsg)
207 IF (io_err.ne.0) THEN
208 IF (mymaster) WRITE (stdout,10) trim(inpname), &
209 & trim(io_errmsg)
210 10 FORMAT (/,' GETPAR_0D_I - Unable to open input script: ',a, &
211 & /,15x,'ERROR: ',a)
212 exit_flag=2
213 RETURN
214 ELSE
215 gotfile=.true.
216 END IF
217 ELSE
218 inpunit=stdinp_unit(mymaster, gotfile)
219 END IF
220!
221! Process requested parameter.
222!
223 foundit=.false.
224 DO WHILE (.true.)
225 READ (inpunit,'(a)',err=20,END=40) line
226 status=decode_line(line, string, nval, cval, rval)
227 IF (status.gt.0) THEN
228 IF (trim(string).eq.trim(keyword)) THEN
229 npts=load_i(nval, rval, 1, ivalue)
230 Value=ivalue(1)
231 foundit=.true.
232 END IF
233 END IF
234 END DO
235 20 IF (mymaster) THEN
236 WRITE (stdout,30) line
237 30 FORMAT (/,' GETPAR_0D_I - Error while processing line: ',/,a)
238 END IF
239 exit_flag=4
240 40 CONTINUE
241 IF (.not.foundit) THEN
242 IF (mymaster) THEN
243 WRITE (stdout,50) trim(keyword)
244 50 FORMAT (/,' GETPAR_0D_I - unable to find KeyWord: ',a, &
245 & /,15x,'in ROMS standard input file.')
246 END IF
247 exit_flag=5
248 END IF
249 IF (gotfile) THEN
250 CLOSE (inpunit)
251 END IF
252!
253 RETURN

References inp_decode_mod::decode_line(), mod_iounits::err, mod_scalars::exit_flag, stdinp_mod::stdinp_unit(), and mod_iounits::stdout.

Here is the call graph for this function:

◆ getpar_1d_i()

subroutine stdinp_mod::getpar_i::getpar_1d_i ( logical, intent(in) mymaster,
integer, intent(in) ndim,
integer, dimension(:), intent(out) value,
character (len=*), intent(in) keyword,
character (len=*), intent(in), optional inpname )

Definition at line 256 of file stdinp_mod.F.

257!
258!***********************************************************************
259! !
260! Reads a 1D integer parameter from ROMS standard input file. !
261! !
262! On Input: !
263! !
264! MyMaster Switch indicating Master process (logical) !
265! Ndim Size integer variable dimension !
266! KeyWord Keyword associated with input parameter (string) !
267! InpName Standard input filename (string; OPTIONAL) !
268! !
269! On Output: !
270! !
271! Value Standard input parameter value (integer 1D array) !
272! !
273!***********************************************************************
274!
275! Imported variable declarations.
276!
277 logical, intent(in) :: MyMaster
278!
279 integer, intent(in) :: Ndim
280 integer, intent(out) :: Value(:)
281!
282 character (len=*), intent(in) :: KeyWord
283 character (len=*), intent(in), optional :: InpName
284!
285! Local variable declarations.
286!
287 logical :: foundit, GotFile
288!
289 integer :: InpUnit, Npts, Nval, io_err, status
290!
291 real(dp), dimension(nRval) :: Rval
292!
293 character (len= 40) :: string
294 character (len=256) :: io_errmsg, line
295 character (len=256), dimension(nCval) :: Cval
296!
297!-----------------------------------------------------------------------
298! Read requested ROMS standard input 1D integer parameter.
299!-----------------------------------------------------------------------
300!
301! Get standard input unit.
302!
303 io_err=0
304 IF (PRESENT(inpname)) THEN
305 inpunit=1
306 OPEN (inpunit, file=trim(inpname), form='formatted', &
307 & status='old', iostat=io_err, iomsg=io_errmsg)
308 IF (io_err.ne.0) THEN
309 IF (mymaster) WRITE (stdout,10) trim(inpname), &
310 & trim(io_errmsg)
311 10 FORMAT (/,' GETPAR_1D_I - Unable to open input script: ',a, &
312 & /,15x,'ERROR: ',a)
313 exit_flag=5
314 RETURN
315 ELSE
316 gotfile=.true.
317 END IF
318 ELSE
319 inpunit=stdinp_unit(mymaster, gotfile)
320 END IF
321!
322! Process requested parameter.
323!
324 foundit=.false.
325 DO WHILE (.true.)
326 READ (inpunit,'(a)',err=20,END=40) line
327 status=decode_line(line, string, nval, cval, rval)
328 IF (status.gt.0) THEN
329 IF (trim(string).eq.trim(keyword)) THEN
330 npts=load_i(nval, rval, ndim, Value)
331 foundit=.true.
332 END IF
333 END IF
334 END DO
335 20 IF (mymaster) THEN
336 WRITE (stdout,30) line
337 30 FORMAT (/,' GETPAR_1D_I - Error while processing line: ',/,a)
338 END IF
339 exit_flag=4
340 40 CONTINUE
341 IF (.not.foundit) THEN
342 IF (mymaster) THEN
343 WRITE (stdout,50) trim(keyword)
344 50 FORMAT (/,' GETPAR_1D_I - unable to find KeyWord: ',a, &
345 & /,15x,'in ROMS standard input file.')
346 END IF
347 exit_flag=5
348 END IF
349 IF (gotfile) THEN
350 CLOSE (inpunit)
351 END IF
352!
353 RETURN

References stdinp_mod::stdinp_unit().

Here is the call graph for this function:

The documentation for this interface was generated from the following file: