Ticket #800: inp_decode.F

File inp_decode.F, 76.5 KB (added by m.hadfield, 5 years ago)
Line 
1#include "cppdefs.h"
2 MODULE inp_decode_mod
3!
4!svn $Id$
5!================================================== Hernan G. Arango ===
6! Copyright (c) 2002-2019 The ROMS/TOMS Group !
7! Licensed under a MIT/X style license !
8! See License_ROMS.txt !
9!=======================================================================
10! !
11! This module contains several routines to process and decode ROMS !
12! unique namelist KeyWord parameters from input script files: !
13! !
14! decode_line Decodes line of text from input script files for a !
15! particular KeyWord. !
16! !
17! find_file Checks if provide input filename exits. !
18! !
19! load_i Processes and loads an integer parameter variable. !
20! !
21! load_i Processes and loads a logical parameter variable. !
22! !
23! load_r Processes and loads a single or double precision !
24! floating-point (real) parameter variable. !
25! !
26! load_lbc Processes and loads lateral boundary conditions !
27! logical switches into derived type structure, !
28! TYPE(T_LBC). !
29! !
30! load_s1d Processes and loads I/O parameters into 1D derived !
31! type structure, TYPE(T_IO). !
32! !
33! load_s2d Processes and loads I/O parameters into 2D derived !
34! type structure, TYPE(T_IO). !
35! !
36!=======================================================================
37!
38 USE mod_kinds
39!
40 implicit none
41!
42 INTERFACE load_i
43 MODULE PROCEDURE load_0d_i ! scalar integer
44 MODULE PROCEDURE load_1d_i ! 1D integer array
45 MODULE PROCEDURE load_2d_i ! 2D integer array
46 MODULE PROCEDURE load_3d_i ! 3D integer array
47 END INTERFACE load_i
48
49 INTERFACE load_l
50 MODULE PROCEDURE load_0d_l ! scalar logical
51 MODULE PROCEDURE load_1d_l ! 1D logical array
52 MODULE PROCEDURE load_2d_l ! 2D logical array
53 MODULE PROCEDURE load_3d_l ! 3D logical array
54 END INTERFACE load_l
55
56 INTERFACE load_r
57#ifdef SINGLE_PRECISION
58 MODULE PROCEDURE load_0d_dp ! scalar real(dp)
59 MODULE PROCEDURE load_1d_dp ! 1D real(dp) array
60 MODULE PROCEDURE load_2d_dp ! 2D real(dp) array
61 MODULE PROCEDURE load_3d_dp ! 3D real(dp) array
62#endif
63 MODULE PROCEDURE load_0d_r8 ! scalar real(r8)
64 MODULE PROCEDURE load_1d_r8 ! 1D real(r8) array
65 MODULE PROCEDURE load_2d_r8 ! 2D real(r8) array
66 MODULE PROCEDURE load_3d_r8 ! 3D real(r8) array
67 END INTERFACE load_r
68!
69! Module dimension parameters.
70!
71 integer, parameter :: nCval = 200 ! size of Cval character vector
72 integer, parameter :: nRval = 100 ! size of Rval real vector
73!
74 CONTAINS
75!
76 FUNCTION decode_line (line_text, KeyWord, Nval, Cval, Rval)
77!
78!***********************************************************************
79! !
80! This function decodes lines of text from input script files. It is !
81! to evaluate ROMS unique namelist parameters. !
82! !
83! Arguments: !
84! !
85! line_text Input scripts lines as text (string) !
86! KeyWord Input parameter keyword (string) !
87! Nval Number of values processed (integer) !
88! Cval Input values as characters (string array) !
89! Rval Input values as mumbers (real array) !
90! !
91!***********************************************************************
92!
93! Imported variable declarations.
94!
95 character (len=*), intent(in) :: line_text
96
97 character (len=*), intent(inout) :: KeyWord
98
99 integer, intent(inout) :: Nval
100
101 character (len=*), intent(inout) :: Cval(:)
102
103 real(dp), intent(inout) :: Rval(:)
104!
105! Local variable declarations
106!
107 logical :: IsString, Kextract, decode, nested
108 integer :: Iblank, Icomm, Icont, Ipipe, Kstr, Kend, Linp
109 integer :: Lend, LenS, Lstr, Lval, Nmul, Schar
110 integer :: copies, i, ic, ie, is, j, status
111
112 integer, dimension(20) :: Imul
113
114 integer :: decode_line
115
116 character (len=256) :: Vstring, inpline, line, string
117!
118!------------------------------------------------------------------------
119! Decode input line.
120!------------------------------------------------------------------------
121!
122! Initialize. Use CHAR(32) for blank space.
123!
124 DO i=1,LEN(line)
125 line(i:i)=CHAR(32)
126 inpline(i:i)=CHAR(32)
127 Vstring(i:i)=CHAR(32)
128 string(i:i)=CHAR(32)
129 END DO
130!
131! Check input line and remove illegal characters. Replace control
132! ASCII characters CHAR(0) to CHAR(31) with a blank space, CHAR(32).
133!
134! Char Dec Key Control Action
135! ----------------------------------------------------------------------
136! NUL 0 ^@ Null character
137! SOH 1 ^A Start of heading, = console interrupt
138! STX 2 ^B Start of text, maintenance mode on HP console
139! ETX 3 ^C End of text
140! EOT 4 ^D End of transmission, not the same as ETB
141! ENQ 5 ^E Enquiry, goes with ACK; old HP flow control
142! ACK 6 ^F Acknowledge, clears ENQ logon hand
143! BEL 7 ^G Bell, rings the bell...
144! BS 8 ^H Backspace, works on HP terminals/computers
145! HT 9 ^I Horizontal tab, move to next tab stop
146! LF 10 ^J Line Feed
147! VT 11 ^K Vertical tab
148! FF 12 ^L Form Feed, page eject
149! CR 13 ^M Carriage Return
150! SO 14 ^N Shift Out, alternate character set
151! SI 15 ^O Shift In, resume defaultn character set
152! DLE 16 ^P Data link escape
153! DC1 17 ^Q XON, with XOFF to pause listings; ":okay to send".
154! DC2 18 ^R Device control 2, block-mode flow control
155! DC3 19 ^S XOFF, with XON is TERM=18 flow control
156! DC4 20 ^T Device control 4
157! NAK 21 ^U Negative acknowledge
158! SYN 22 ^V Synchronous idle
159! ETB 23 ^W End transmission block, not the same as EOT
160! CAN 24 ^X Cancel line, MPE echoes !!!
161! EM 25 ^Y End of medium, Control-Y interrupt
162! SUB 26 ^Z Substitute
163! ESC 27 ^[ Escape, next character is not echoed
164! FS 28 ^\ File separator
165! GS 29 ^] Group separator
166! RS 30 ^^ Record separator, block-mode terminator
167! US 31 ^_ Unit separator
168!
169! SP 32 Space
170! ! 33 Exclamation mark
171! * 42 Asterisk (star, multiply)
172! + 43 Plus
173! - 45 Hyphen, dash, minus
174! . 46 Period
175! 0 48 Zero
176! 1 49 One
177! 2 50 Two
178! 3 51 Three
179! 4 52 Four
180! 5 53 Five
181! 6 54 Six
182! 7 55 Seven
183! 8 56 Eight
184! 9 57 Nine
185! = 61 Equals sign
186! \ 92 Reverse slant (Backslash)
187! | 124 Vertical line
188!
189 inpline=TRIM(ADJUSTL(line_text))
190 Linp=LEN_TRIM(inpline)
191 DO i=1,LEN_TRIM(inpline)
192 j=ICHAR(inpline(i:i))
193 IF (j.lt.32) THEN
194 inpline(i:i)=char(32) ! blank space
195 END IF
196 END DO
197 inpline=TRIM(inpline)
198!
199! Get length of "line". Remove comment after the KEYWORD, if any.
200! Then, remove leading and trailing blanks.
201!
202 IF ((Linp.gt.0).and.(inpline(1:1).ne.CHAR(33))) THEN
203 Icomm=INDEX(inpline,CHAR(33),BACK=.FALSE.)
204 IF (Icomm.gt.0) Linp=Icomm-1
205 line=TRIM(ADJUSTL(inpline(1:Linp)))
206 Linp=LEN_TRIM(line)
207 ELSE
208 line=TRIM(ADJUSTL(inpline))
209 Linp=LEN_TRIM(line)
210 END IF
211!
212! If not a blank or comment line [char(33)=!], decode and extract input
213! values. Find equal sign [char(61)].
214!
215 status=-1
216 nested=.FALSE.
217 IF ((Linp.gt.0).and.(line(1:1).ne.CHAR(33))) THEN
218 status=1
219 Kstr=1
220 Kend=INDEX(line,CHAR(61),BACK=.FALSE.)-1
221 Lstr=INDEX(line,CHAR(61),BACK=.TRUE.)+1
222!
223! Determine if KEYWORD is followed by double equal sign (==) indicating
224! nested parameter.
225!
226 IF ((Lstr-Kend).eq.3) nested=.TRUE.
227!
228! Extract KEYWORD, trim leading and trailing blanks.
229!
230 Kextract=.FALSE.
231 IF (Kend.gt.0) THEN
232 Lend=Linp
233 KeyWord=line(Kstr:Kend)
234 Nval=0
235 Kextract=.TRUE.
236 ELSE
237 Lstr=1
238 Lend=Linp
239 Kextract=.TRUE.
240 END IF
241!
242! Extract parameter values string. Remove continuation symbol
243! [char(92)=\] or multi-line value [char(124)=|], if any. Trim
244! leading trailing blanks.
245!
246 IF (Kextract) THEN
247 Icont=INDEX(line,CHAR(92 ),BACK=.FALSE.)
248 Ipipe=INDEX(line,CHAR(124),BACK=.FALSE.)
249 IF (Icont.gt.0) Lend=Icont-1
250 IF (Ipipe.gt.0) Lend=Ipipe-1
251 Vstring=ADJUSTL(line(Lstr:Lend))
252 Lval=LEN_TRIM(Vstring)
253!
254! The TITLE KEYWORD is a special one since it can include strings,
255! numbers, spaces, and continuation symbol.
256!
257 IsString=.FALSE.
258 IF (TRIM(KeyWord).eq.'TITLE') THEN
259 Nval=Nval+1
260 Cval(Nval)=Vstring(1:Lval)
261 IsString=.TRUE.
262 ELSE
263!
264! Check if there is a multiplication symbol [char(42)=*] in the variable
265! string indicating repetition of input values.
266!
267 Nmul=0
268 DO i=1,Lval
269 IF (Vstring(i:i).eq.CHAR(42)) THEN
270 Nmul=Nmul+1
271 Imul(Nmul)=i
272 END IF
273 END DO
274 ic=1
275!
276! Check for blank spaces [char(32)=' '] between entries and decode.
277!
278 is=1
279 ie=Lval
280 Iblank=0
281 decode=.FALSE.
282 DO i=1,Lval
283 IF (Vstring(i:i).eq.CHAR(32)) THEN
284 IF (Vstring(i+1:i+1).ne.CHAR(32)) decode=.TRUE.
285 Iblank=i
286 ELSE
287 ie=i
288 ENDIF
289 IF (decode.or.(i.eq.Lval)) THEN
290 Nval=Nval+1
291!
292! Processing numeric values. Check starting character to determine
293! if numeric or character values. It is possible to have both when
294! processing repetitions via the multiplication symbol.
295!
296 Schar=ICHAR(Vstring(is:is))
297 IF (((48.le.Schar).and.(Schar.le.57)).or. &
298 & (Schar.eq.43).or.(Schar.eq.45)) THEN
299 IF ((Nmul.gt.0).and. &
300 & (is.lt.Imul(ic)).and.(Imul(ic).lt.ie)) THEN
301 READ (Vstring(is:Imul(ic)-1),*) copies
302 Schar=ICHAR(Vstring(Imul(ic)+1:Imul(ic)+1))
303 IF ((43.le.Schar).and.(Schar.le.57)) THEN
304 READ (Vstring(Imul(ic)+1:ie),*) Rval(Nval)
305 DO j=1,copies-1
306 Rval(Nval+j)=Rval(Nval)
307 END DO
308 ELSE
309 string=Vstring(Imul(ic)+1:ie)
310 LenS=LEN_TRIM(string)
311 Cval(Nval)=string(1:LenS)
312 DO j=1,copies-1
313 Cval(Nval+j)=Cval(Nval)
314 END DO
315 END IF
316 Nval=Nval+copies-1
317 ic=ic+1
318 ELSE
319 string=Vstring(is:ie)
320 LenS=LEN_TRIM(string)
321 READ (string(1:LenS),*) Rval(Nval)
322 END IF
323 ELSE
324!
325! Processing character values (logicals and strings).
326!
327 IF ((Nmul.gt.0).and. &
328 & (is.lt.Imul(ic)).and.(Imul(ic).lt.ie)) THEN
329 READ (Vstring(is:Imul(ic)-1),*) copies
330 Cval(Nval)=Vstring(Imul(ic)+1:ie)
331 DO j=1,copies-1
332 Cval(Nval+j)=Cval(Nval)
333 END DO
334 Nval=Nval+copies-1
335 ic=ic+1
336 ELSE
337 string=Vstring(is:ie)
338 Cval(Nval)=TRIM(ADJUSTL(string))
339 END IF
340 IsString=.TRUE.
341 END IF
342 is=Iblank+1
343 ie=Lval
344 decode=.FALSE.
345 END IF
346 END DO
347 END IF
348 END IF
349 status=Nval
350 END IF
351 decode_line=status
352!
353 RETURN
354 END FUNCTION decode_line
355!
356 FUNCTION find_file (ng, fname, KeyWord) RESULT (foundit)
357!
358!***********************************************************************
359! !
360! This function checks if provided input file exits. !
361! !
362! On Input: !
363! !
364! ng Nested grid number !
365! fname Filename (path and name) !
366! KeyWord Keyword associated with file name (string,OPTIONAL) !
367! !
368! On Output: !
369! !
370! foundit The value of the result is TRUE/FALSE if the file !
371! was found or not !
372! !
373!***********************************************************************
374!
375 USE mod_param
376 USE mod_parallel
377 USE mod_iounits
378 USE mod_netcdf
379 USE mod_scalars
380!
381 USE strings_mod, ONLY : FoundError
382!
383! Imported variable declarations.
384!
385 integer, intent(in) :: ng
386
387 character (len=*), intent(in) :: fname
388 character (len=*), intent(in) :: KeyWord
389!
390! Local variable declarations.
391!
392 logical :: foundit, isURL
393
394 integer :: lstr, ncid
395!
396 SourceFile=__FILE__ // ", find_file"
397!
398!-----------------------------------------------------------------------
399! Check if the file exit.
400!-----------------------------------------------------------------------
401!
402 foundit=.FALSE.
403!
404! Check for empty file name string.
405!
406 lstr=LEN_TRIM(fname)
407 IF (lstr.eq.0) THEN
408 IF (Master) THEN
409 WRITE (stdout,10) TRIM(KeyWord)
410 10 FORMAT (/,' INP_PAR:FIND_FILE - empty file name string ', &
411 & 'for standard input script KeyWord: ',a)
412 END IF
413 exit_flag=5
414 IF (FoundError(exit_flag, NoError, __LINE__, &
415 & __FILE__)) RETURN
416 END IF
417!
418! Check if provided file is a URL. This implies the file is a NetCDF
419! file on Data Access Protocol (DAP) server (like OPeNDAP).
420!
421 isURL=.FALSE.
422 IF (INDEX(TRIM(fname),'http:').ne.0) THEN
423 isURL=.TRUE.
424 END IF
425!
426! Use F90 intrinsic function for non URL files.
427!
428 IF (.not.isURL) THEN
429 INQUIRE (FILE=TRIM(fname), EXIST=foundit)
430!
431! Use NetCDF library (version 4.1.1 or higher) to check URL NetCDF
432! files.
433!
434 ELSE
435 CALL netcdf_open (ng, iNLM, fname, 0, ncid)
436 IF (exit_flag.eq.NoError) THEN
437 foundit=.TRUE.
438 END IF
439 END IF
440!
441 RETURN
442 END FUNCTION find_file
443!
444 FUNCTION load_0d_i (Ninp, Vinp, Nout, Vout) RESULT (Nval)
445!
446!***********************************************************************
447! !
448! It loads input values into a requested model scalar integer !
449! variable. !
450! !
451! On Input: !
452! !
453! Ninp Number of input elements to process in Vinp (integer) !
454! Vinp Input values (1D real(dp) array) !
455! Nout Size of output integer variable dimension (not used) !
456! !
457! On Output: !
458! !
459! Vout Output scalar integer variable !
460! Nval Number of output values processed !
461! !
462!***********************************************************************
463!
464! Imported variable declarations.
465!
466 integer, intent(in) :: Ninp, Nout
467 real(dp), intent(in) :: Vinp(:)
468!
469 integer, intent(out) :: Vout
470!
471! Local variable declarations.
472!
473 integer :: ic
474 integer :: Nval
475!
476!-----------------------------------------------------------------------
477! Load scalar integer variable with input value.
478!-----------------------------------------------------------------------
479!
480 ic=1
481 Vout=INT(Vinp(ic))
482 Nval=ic
483
484 RETURN
485 END FUNCTION load_0d_i
486!
487 FUNCTION load_1d_i (Ninp, Vinp, Nout, Vout) RESULT (Nval)
488!
489!***********************************************************************
490! !
491! It loads input values into a requested model 1D integer array. !
492! !
493! On Input: !
494! !
495! Ninp Number of input elements to process in Vinp (integer) !
496! Vinp Input values (1D real(dp) array) !
497! Nout Size of output integer variable dimension !
498! !
499! On Output: !
500! !
501! Vout Output 1D integer variable !
502! Nval Number of output values processed !
503! !
504!***********************************************************************
505!
506! Imported variable declarations.
507!
508 integer, intent(in) :: Ninp, Nout
509 real(dp), intent(in) :: Vinp(:)
510!
511 integer, intent(out) :: Vout(:)
512!
513! Local variable declarations.
514!
515 integer :: i, ic
516 integer :: Nval
517!
518!-----------------------------------------------------------------------
519! Load 1D integer variable with input values.
520!-----------------------------------------------------------------------
521!
522! If not all values are provided for variable, assume the last value
523! for the rest of the array.
524!
525 ic=0
526 IF (Ninp.le.Nout) THEN
527 DO i=1,Ninp
528 ic=ic+1
529 Vout(i)=INT(Vinp(i))
530 END DO
531 DO i=Ninp+1,Nout
532 ic=ic+1
533 Vout(i)=INT(Vinp(Ninp))
534 END DO
535 ELSE
536 DO i=1,Nout
537 ic=ic+1
538 Vout(i)=INT(Vinp(i))
539 END DO
540 END IF
541 Nval=ic
542
543 RETURN
544 END FUNCTION load_1d_i
545!
546 FUNCTION load_2d_i (Ninp, Vinp, Iout, Jout, Vout) RESULT (Nval)
547!
548!***********************************************************************
549! !
550! It loads input values into a requested model 2D integer array. !
551! !
552! On Input: !
553! !
554! Ninp Number of input elements to process in Vinp (integer) !
555! Vinp Input values (1D real(dp) array) !
556! Iout Size of output integer variable first I-dimension !
557! Jout Size of output integer variable second J-dimension !
558! !
559! On Output: !
560! !
561! Vout Output 2D integer variable !
562! Nval Number of output values processed !
563! !
564!***********************************************************************
565!
566! Imported variable declarations.
567!
568 integer, intent(in) :: Ninp, Iout, Jout
569 real(dp), intent(in) :: Vinp(:)
570!
571 integer, intent(out) :: Vout(:,:)
572!
573! Local variable declarations.
574!
575 integer :: i, ic
576 integer :: Nout, Nval
577!
578 integer, dimension(Iout*Jout) :: Vwrk
579!
580!-----------------------------------------------------------------------
581! Load 2D integer variable with input values.
582!-----------------------------------------------------------------------
583!
584! If not all values are provided for variable, assume the last value
585! for the rest of the 2D array.
586!
587 ic=0
588 Nout=Iout*Jout
589 IF (Ninp.le.Nout) THEN
590 DO i=1,Ninp
591 ic=ic+1
592 Vwrk(i)=INT(Vinp(i))
593 END DO
594 DO i=Ninp+1,Nout
595 ic=ic+1
596 Vwrk(i)=INT(Vinp(Ninp))
597 END DO
598 ELSE
599 DO i=1,Nout
600 ic=ic+1
601 Vwrk(i)=INT(Vinp(i))
602 END DO
603 END IF
604 Vout=RESHAPE(Vwrk,(/Iout,Jout/))
605 Nval=ic
606!
607 RETURN
608 END FUNCTION load_2d_i
609!
610 FUNCTION load_3d_i (Ninp, Vinp, Iout, Jout, Kout, Vout) &
611 & RESULT (Nval)
612!
613!***********************************************************************
614! !
615! It loads input values into a requested model 3D integer array. !
616! !
617! On Input: !
618! !
619! Ninp Number of input elements to process in Vinp (integer) !
620! Vinp Input values (1D real(dp) array) !
621! Iout Size of output integer variable first I-dimension !
622! Jout Size of output integer variable second J-dimension !
623! Kout Size of output integer variable third K-dimension !
624! !
625! On Output: !
626! !
627! Vout Output 3D integer variable !
628! Nval Number of output values processed !
629! !
630!***********************************************************************
631!
632! Imported variable declarations.
633!
634 integer, intent(in) :: Ninp, Iout, Jout, Kout
635 real(dp), intent(in) :: Vinp(:)
636!
637 integer, intent(out) :: Vout(:,:,:)
638!
639! Local variable declarations.
640!
641 integer :: i, ic
642 integer :: Nout, Nval
643!
644 integer, dimension(Iout*Jout*Kout) :: Vwrk
645!
646!-----------------------------------------------------------------------
647! Load 3D integer variable with input values.
648!-----------------------------------------------------------------------
649!
650! If not all values are provided for variable, assume the last value
651! for the rest of the 3D array.
652!
653 ic=0
654 Nout=Iout*Jout*Kout
655 IF (Ninp.le.Nout) THEN
656 DO i=1,Ninp
657 ic=ic+1
658 Vwrk(i)=INT(Vinp(i))
659 END DO
660 DO i=Ninp+1,Nout
661 ic=ic+1
662 Vwrk(i)=INT(Vinp(Ninp))
663 END DO
664 ELSE
665 DO i=1,Nout
666 ic=ic+1
667 Vwrk(i)=INT(Vinp(i))
668 END DO
669 END IF
670 Vout=RESHAPE(Vwrk,(/Iout,Jout,Kout/))
671 Nval=ic
672!
673 RETURN
674 END FUNCTION load_3d_i
675!
676 FUNCTION load_0d_l (Ninp, Vinp, Nout, Vout) RESULT (Nval)
677!
678!***********************************************************************
679! !
680! It loads input values into a requested model scalar logical !
681! variable. !
682! !
683! On Input: !
684! !
685! Ninp Number of input elements to process in Vinp (integer) !
686! Vinp Input values (character 1D array) !
687! Nout Size of output logical variable dimension (not used) !
688! !
689! On Output: !
690! !
691! Vout Output scalar logical variable !
692! Nval Number of output values processed !
693! !
694!***********************************************************************
695!
696! Imported variable declarations.
697!
698 integer, intent(in) :: Ninp, Nout
699 character (len=*), intent(in) :: Vinp(:)
700!
701 logical, intent(out) :: Vout
702!
703! Local variable declarations.
704!
705 integer :: ic
706 integer :: Nval
707!
708!-----------------------------------------------------------------------
709! Load scalar logical variable with input value.
710!-----------------------------------------------------------------------
711!
712 ic=1
713 IF ((Vinp(ic)(1:1).eq.'T').or. &
714 & (Vinp(ic)(1:1).eq.'t')) THEN
715 Vout=.TRUE.
716 ELSE
717 Vout=.FALSE.
718 END IF
719 Nval=ic
720!
721 RETURN
722 END FUNCTION load_0d_l
723!
724 FUNCTION load_1d_l (Ninp, Vinp, Nout, Vout) RESULT (Nval)
725!
726!***********************************************************************
727! !
728! It loads input values into a requested model 1D logical array. !
729! !
730! On Input: !
731! !
732! Ninp Number of input elements to process in Vinp (integer) !
733! Vinp Input values (character 1D array) !
734! Nout Size of output logical variable dimension !
735! !
736! On Output: !
737! !
738! Vout Output 1D logical variable !
739! Nval Number of output values processed !
740! !
741!***********************************************************************
742!
743! Imported variable declarations.
744!
745 integer, intent(in) :: Ninp, Nout
746 character (len=*), intent(in) :: Vinp(:)
747!
748 logical, intent(out) :: Vout(:)
749!
750! Local variable declarations.
751!
752 logical :: LastValue
753
754 integer :: i, ic
755 integer :: Nval
756!
757!-----------------------------------------------------------------------
758! Load logical variable with input values.
759!-----------------------------------------------------------------------
760!
761! If not all values are provided for variable, assume the last value
762! for the rest of the array.
763!
764 ic=0
765 LastValue=.FALSE.
766 IF (Ninp.le.Nout) THEN
767 DO i=1,Ninp
768 ic=ic+1
769 IF ((Vinp(i)(1:1).eq.'T').or. &
770 & (Vinp(i)(1:1).eq.'t')) THEN
771 Vout(i)=.TRUE.
772 ELSE
773 Vout(i)=.FALSE.
774 END IF
775 LastValue=Vout(i)
776 END DO
777 DO i=Ninp+1,Nout
778 ic=ic+1
779 Vout(i)=LastValue
780 END DO
781 ELSE
782 DO i=1,Nout
783 ic=ic+1
784 IF ((Vinp(i)(1:1).eq.'T').or. &
785 & (Vinp(i)(1:1).eq.'t')) THEN
786 Vout(i)=.TRUE.
787 ELSE
788 Vout(i)=.FALSE.
789 END IF
790 END DO
791 END IF
792 Nval=ic
793!
794 RETURN
795 END FUNCTION load_1d_l
796!
797 FUNCTION load_2d_l (Ninp, Vinp, Iout, Jout, Vout) RESULT (Nval)
798!
799!***********************************************************************
800! !
801! It loads input values into a requested model 2D logical array. !
802! !
803! On Input: !
804! !
805! Ninp Number of input elements to process in Vinp (integer) !
806! Vinp Input values (character 1D array) !
807! Iout Size of output logical variable first I-dimension !
808! Jout Size of output logical variable second J-dimension !
809! !
810! On Output: !
811! !
812! Vout Output 2D logical variable !
813! Nval Number of output values processed !
814! !
815!***********************************************************************
816!
817! Imported variable declarations.
818!
819 integer, intent(in) :: Ninp, Iout, Jout
820 character (len=*), intent(in) :: Vinp(:)
821!
822 logical, intent(out) :: Vout(:,:)
823!
824! Local variable declarations.
825!
826 logical :: LastValue
827!
828 logical, dimension(Iout*Jout) :: Vwrk
829!
830 integer :: i, ic
831 integer :: Nout, Nval
832!
833!-----------------------------------------------------------------------
834! Load 2D logical variable with input values.
835!-----------------------------------------------------------------------
836!
837! If not all values are provided for variable, assume the last value
838! for the rest of the array.
839!
840 ic=0
841 Nout=Iout*Jout
842 LastValue=.FALSE.
843 IF (Ninp.le.Nout) THEN
844 DO i=1,Ninp
845 ic=ic+1
846 IF ((Vinp(i)(1:1).eq.'T').or. &
847 & (Vinp(i)(1:1).eq.'t')) THEN
848 Vwrk(i)=.TRUE.
849 ELSE
850 Vwrk(i)=.FALSE.
851 END IF
852 LastValue=Vwrk(i)
853 END DO
854 DO i=Ninp+1,Nout
855 ic=ic+1
856 Vwrk(i)=LastValue
857 END DO
858 ELSE
859 DO i=1,Nout
860 ic=ic+1
861 IF ((Vinp(i)(1:1).eq.'T').or. &
862 & (Vinp(i)(1:1).eq.'t')) THEN
863 Vwrk(i)=.TRUE.
864 ELSE
865 Vwrk(i)=.FALSE.
866 END IF
867 END DO
868 END IF
869 Vout=RESHAPE(Vwrk,(/Iout,Jout/))
870 Nval=ic
871!
872 RETURN
873 END FUNCTION load_2d_l
874!
875 FUNCTION load_3d_l (Ninp, Vinp, Iout, Jout, Kout, Vout) &
876 & RESULT (Nval)
877!
878!***********************************************************************
879! !
880! It loads input values into a requested model 3D logical array. !
881! !
882! On Input: !
883! !
884! Ninp Number of input elements to process in Vinp (integer) !
885! Vinp Input values (character 1D array) !
886! Iout Size of output logical variable first I-dimension !
887! Jout Size of output logical variable second J-dimension !
888! Kout Size of output logical variable third K-dimension !
889! !
890! On Output: !
891! !
892! Vout Output 3D logical variable !
893! Nval Number of output values processed !
894! !
895!***********************************************************************
896!
897! Imported variable declarations.
898!
899 integer, intent(in) :: Ninp, Iout, Jout, Kout
900 character (len=*), intent(in) :: Vinp(:)
901!
902 logical, intent(out) :: Vout(:,:,:)
903!
904! Local variable declarations.
905!
906 logical :: LastValue
907!
908 logical, dimension(Iout*Jout*Kout) :: Vwrk
909!
910 integer :: i, ic
911 integer :: Nout, Nval
912!
913!-----------------------------------------------------------------------
914! Load 3D logical variable with input values.
915!-----------------------------------------------------------------------
916!
917! If not all values are provided for variable, assume the last value
918! for the rest of the array.
919!
920 ic=0
921 Nout=Iout*Jout*Kout
922 LastValue=.FALSE.
923 IF (Ninp.le.Nout) THEN
924 DO i=1,Ninp
925 ic=ic+1
926 IF ((Vinp(i)(1:1).eq.'T').or. &
927 & (Vinp(i)(1:1).eq.'t')) THEN
928 Vwrk(i)=.TRUE.
929 ELSE
930 Vwrk(i)=.FALSE.
931 END IF
932 LastValue=Vwrk(i)
933 END DO
934 DO i=Ninp+1,Nout
935 ic=ic+1
936 Vwrk(i)=LastValue
937 END DO
938 ELSE
939 DO i=1,Nout
940 ic=ic+1
941 IF ((Vinp(i)(1:1).eq.'T').or. &
942 & (Vinp(i)(1:1).eq.'t')) THEN
943 Vwrk(i)=.TRUE.
944 ELSE
945 Vwrk(i)=.FALSE.
946 END IF
947 END DO
948 END IF
949 Vout=RESHAPE(Vwrk,(/Iout,Jout,Kout/))
950 Nval=ic
951!
952 RETURN
953 END FUNCTION load_3d_l
954
955#ifdef SINGLE_PRECISION
956!
957 FUNCTION load_0d_dp (Ninp, Vinp, Nout, Vout) RESULT (Nval)
958!
959!***********************************************************************
960! !
961! It loads input values into a requested model scalar double !
962! precision variable when numerical kernel is in single precision. !
963! !
964! On Input: !
965! !
966! Ninp Number of input elements to process in Vinp (integer) !
967! Vinp Input values (1D real(dp) array) !
968! Nout Size of output integer variable dimension (not used) !
969! !
970! On Output: !
971! !
972! Vout Output scalar variable (real, KIND=dp) !
973! Nval Number of output values processed !
974! !
975!=======================================================================
976!
977! Imported variable declarations.
978!
979 integer, intent(in) :: Ninp, Nout
980 real(dp), intent(in) :: Vinp(:)
981!
982 real(dp), intent(out) :: Vout
983!
984! Local variable declarations.
985!
986 integer :: ic
987 integer :: Nval
988!
989!-----------------------------------------------------------------------
990! Load scalar floating-point variable with input value.
991!-----------------------------------------------------------------------
992!
993 ic=1
994 Vout=Vinp(ic)
995 Nval=ic
996!
997 RETURN
998 END FUNCTION load_0d_dp
999!
1000 FUNCTION load_1d_dp (Ninp, Vinp, Nout, Vout) RESULT (Nval)
1001!
1002!***********************************************************************
1003! !
1004! It loads input values into a requested model 1D double precision !
1005! array when numerical kernel is in single precision. !
1006! !
1007! On Input: !
1008! !
1009! Ninp Number of input elements to process in Vinp (integer) !
1010! Vinp Input values (1D real(dp) array) !
1011! Nout Size of output integer variable dimension !
1012! !
1013! On Output: !
1014! !
1015! Vout Output 1D variable (real, KIND=dp) !
1016! Nval Number of output values processed !
1017! !
1018!=======================================================================
1019!
1020! Imported variable declarations.
1021!
1022 integer, intent(in) :: Ninp, Nout
1023 real(dp), intent(in) :: Vinp(:)
1024!
1025 real(dp), intent(out) :: Vout(:)
1026!
1027! Local variable declarations.
1028!
1029 integer :: i, ic
1030 integer :: Nval
1031!
1032!-----------------------------------------------------------------------
1033! Load 1D floating-point variable with input values.
1034!-----------------------------------------------------------------------
1035!
1036! If not all values are provided for variable, assume the last value
1037! for the rest of the array.
1038!
1039 ic=0
1040 IF (Ninp.le.Nout) THEN
1041 DO i=1,Ninp
1042 ic=ic+1
1043 Vout(i)=Vinp(i)
1044 END DO
1045 DO i=Ninp+1,Nout
1046 ic=ic+1
1047 Vout(i)=Vinp(Ninp)
1048 END DO
1049 ELSE
1050 DO i=1,Nout
1051 ic=ic+1
1052 Vout(i)=Vinp(i)
1053 END DO
1054 END IF
1055 Nval=ic
1056!
1057 RETURN
1058 END FUNCTION load_1d_dp
1059!
1060 FUNCTION load_2d_dp (Ninp, Vinp, Iout, Jout, Vout) RESULT (Nval)
1061!
1062!***********************************************************************
1063! !
1064! It loads input values into a requested model 2D double precision !
1065! array when numerical kernel is in single precision. !
1066! !
1067! On Input: !
1068! !
1069! Ninp Number of input elements to process in Vinp (integer) !
1070! Vinp Input values (1D real(dp) array) !
1071! Iout Size of output integer variable first I-dimension !
1072! Jout Size of output integer variable second J-dimension !
1073! !
1074! On Output: !
1075! !
1076! Vout Output 2D variable (real, KIND=dp) !
1077! Nval Number of output values processed !
1078! !
1079!=======================================================================
1080!
1081! Imported variable declarations.
1082!
1083 integer, intent(in) :: Ninp, Iout, Jout
1084 real(dp), intent(in) :: Vinp(:)
1085!
1086 real(dp), intent(out) :: Vout(:,:)
1087!
1088! Local variable declarations.
1089!
1090 integer :: i, ic
1091 integer :: Nout, Nval
1092!
1093 real(dp), dimension(Iout*Jout) :: Vwrk
1094!
1095!-----------------------------------------------------------------------
1096! Load 2D floating-point variable with input values.
1097!-----------------------------------------------------------------------
1098!
1099! If not all values are provided for variable, assume the last value
1100! for the rest of the array.
1101!
1102 ic=0
1103 Nout=Iout*Jout
1104 IF (Ninp.le.Nout) THEN
1105 DO i=1,Ninp
1106 ic=ic+1
1107 Vwrk(i)=Vinp(i)
1108 END DO
1109 DO i=Ninp+1,Nout
1110 ic=ic+1
1111 Vwrk(i)=Vinp(Ninp)
1112 END DO
1113 ELSE
1114 DO i=1,Nout
1115 ic=ic+1
1116 Vwrk(i)=Vinp(i)
1117 END DO
1118 END IF
1119 Vout=RESHAPE(Vwrk,(/Iout,Jout/))
1120 Nval=ic
1121!
1122 RETURN
1123 END FUNCTION load_2d_dp
1124!
1125 FUNCTION load_3d_dp (Ninp, Vinp, Iout, Jout, Kout, Vout) &
1126 & RESULT (Nval)
1127!
1128!***********************************************************************
1129! !
1130! It loads input values into a requested model 3D double precision !
1131! array when numerical kernel is in single precision. !
1132! !
1133! On Input: !
1134! !
1135! Ninp Number of input elements to process in Vinp (integer) !
1136! Vinp Input values (1D real(dp) array) !
1137! Iout Size of output integer variable first I-dimension !
1138! Jout Size of output integer variable second J-dimension !
1139! Kout Size of output integer variable third K-dimension !
1140! !
1141! On Output: !
1142! !
1143! Vout Output 3D variable (real, KIND=dp) !
1144! Nval Number of output values processed !
1145! !
1146!=======================================================================
1147!
1148! Imported variable declarations.
1149!
1150 integer, intent(in) :: Ninp, Iout, Jout, Kout
1151 real(dp), intent(in) :: Vinp(:)
1152!
1153 real(dp), intent(out) :: Vout(:,:,:)
1154!
1155! Local variable declarations.
1156!
1157 integer :: i, ic
1158 integer :: Nout, Nval
1159!
1160 real(dp), dimension(Iout*Jout*Kout) :: Vwrk
1161!
1162!-----------------------------------------------------------------------
1163! Load 3D floating-point variable with input values.
1164!-----------------------------------------------------------------------
1165!
1166! If not all values are provided for variable, assume the last value
1167! for the rest of the array.
1168!
1169 ic=0
1170 Nout=Iout*Jout*Kout
1171 IF (Ninp.le.Nout) THEN
1172 DO i=1,Ninp
1173 ic=ic+1
1174 Vwrk(i)=Vinp(i)
1175 END DO
1176 DO i=Ninp+1,Nout
1177 ic=ic+1
1178 Vwrk(i)=Vinp(Ninp)
1179 END DO
1180 ELSE
1181 DO i=1,Nout
1182 ic=ic+1
1183 Vwrk(i)=Vinp(i)
1184 END DO
1185 END IF
1186 Vout=RESHAPE(Vwrk,(/Iout,Jout,Kout/))
1187 Nval=ic
1188!
1189 RETURN
1190 END FUNCTION load_3d_dp
1191#endif
1192!
1193 FUNCTION load_0d_r8 (Ninp, Vinp, Nout, Vout) RESULT (Nval)
1194!
1195!=======================================================================
1196! !
1197! It loads input values into a requested model scalar floating-point !
1198! variable (KIND=r8). !
1199! !
1200! On Input: !
1201! !
1202! Ninp Number of input elements to process in Vinp (integer) !
1203! Vinp Input values (1D real(dp) array) !
1204! Nout Size of output integer variable dimension (not used) !
1205! !
1206! On Output: !
1207! !
1208! Vout Output scalar variable (real, KIND=r8) !
1209! Nval Number of output values processed !
1210! !
1211!=======================================================================
1212!
1213! Imported variable declarations.
1214!
1215 integer, intent(in) :: Ninp, Nout
1216 real(dp), intent(in) :: Vinp(:)
1217!
1218 real(r8), intent(out) :: Vout
1219!
1220! Local variable declarations.
1221!
1222 integer :: ic
1223 integer :: Nval
1224!
1225!-----------------------------------------------------------------------
1226! Load scalar floating-point variable with input value.
1227!-----------------------------------------------------------------------
1228!
1229 ic=1
1230#ifdef SINGLE_PRECISION
1231 Vout=REAL(Vinp(ic),r8)
1232#else
1233 Vout=Vinp(ic)
1234#endif
1235 Nval=ic
1236!
1237 RETURN
1238 END FUNCTION load_0d_r8
1239!
1240 FUNCTION load_1d_r8 (Ninp, Vinp, Nout, Vout) RESULT (Nval)
1241!
1242!=======================================================================
1243! !
1244! It loads input values into a requested model 1D floating-point !
1245! array (KIND=r8). !
1246! !
1247! On Input: !
1248! !
1249! Ninp Number of input elements to process in Vinp (integer) !
1250! Vinp Input values (1D real(dp) array) !
1251! Nout Size of output integer variable dimension !
1252! !
1253! On Output: !
1254! !
1255! Vout Output 1D variable (real, KIND=r8) !
1256! Nval Number of output values processed !
1257! !
1258!=======================================================================
1259!
1260! Imported variable declarations.
1261!
1262 integer, intent(in) :: Ninp, Nout
1263 real(dp), intent(in) :: Vinp(:)
1264!
1265 real(r8), intent(out) :: Vout(:)
1266!
1267! Local variable declarations.
1268!
1269 integer :: i, ic
1270 integer :: Nval
1271!
1272!-----------------------------------------------------------------------
1273! Load 1D floating-point variable with input values.
1274!-----------------------------------------------------------------------
1275!
1276! If not all values are provided for variable, assume the last value
1277! for the rest of the array.
1278!
1279 ic=0
1280 IF (Ninp.le.Nout) THEN
1281 DO i=1,Ninp
1282 ic=ic+1
1283#ifdef SINGLE_PRECISION
1284 Vout(i)=REAL(Vinp(i),r8)
1285#else
1286 Vout(i)=Vinp(i)
1287#endif
1288 END DO
1289 DO i=Ninp+1,Nout
1290 ic=ic+1
1291#ifdef SINGLE_PRECISION
1292 Vout(i)=REAL(Vinp(Ninp),r8)
1293#else
1294 Vout(i)=Vinp(Ninp)
1295#endif
1296 END DO
1297 ELSE
1298 DO i=1,Nout
1299 ic=ic+1
1300#ifdef SINGLE_PRECISION
1301 Vout(i)=REAL(Vinp(i),r8)
1302#else
1303 Vout(i)=Vinp(i)
1304#endif
1305 END DO
1306 END IF
1307 Nval=ic
1308!
1309 RETURN
1310 END FUNCTION load_1d_r8
1311!
1312 FUNCTION load_2d_r8 (Ninp, Vinp, Iout, Jout, Vout) RESULT (Nval)
1313!
1314!***********************************************************************
1315! !
1316! It loads input values into a requested model 2D floating-point !
1317! array (KIND=r8). !
1318! !
1319! On Input: !
1320! !
1321! Ninp Number of input elements to process in Vinp (integer) !
1322! Vinp Input values (1D real(dp) array) !
1323! Iout Size of output integer variable first I-dimension !
1324! Jout Size of output integer variable second J-dimension !
1325! !
1326! On Output: !
1327! !
1328! Vout Output 2D variable (real, KIND=r8) !
1329! Nval Number of output values processed !
1330! !
1331!=======================================================================
1332!
1333! Imported variable declarations.
1334!
1335 integer, intent(in) :: Ninp, Iout, Jout
1336 real(dp), intent(in) :: Vinp(:)
1337!
1338 real(r8), intent(out) :: Vout(:,:)
1339!
1340! Local variable declarations.
1341!
1342 integer :: i, ic
1343 integer :: Nout, Nval
1344!
1345 real(r8), dimension(Iout*Jout) :: Vwrk
1346!
1347!-----------------------------------------------------------------------
1348! Load 2D floating-point variable with input values.
1349!-----------------------------------------------------------------------
1350!
1351! If not all values are provided for variable, assume the last value
1352! for the rest of the array.
1353!
1354 ic=0
1355 Nout=Iout*Jout
1356 IF (Ninp.le.Nout) THEN
1357 DO i=1,Ninp
1358 ic=ic+1
1359#ifdef SINGLE_PRECISION
1360 Vwrk(i)=REAL(Vinp(i),r8)
1361#else
1362 Vwrk(i)=Vinp(i)
1363#endif
1364 END DO
1365 DO i=Ninp+1,Nout
1366 ic=ic+1
1367#ifdef SINGLE_PRECISION
1368 Vwrk(i)=REAL(Vinp(Ninp),r8)
1369#else
1370 Vwrk(i)=Vinp(Ninp)
1371#endif
1372 END DO
1373 ELSE
1374 DO i=1,Nout
1375 ic=ic+1
1376#ifdef SINGLE_PRECISION
1377 Vwrk(i)=REAL(Vinp(i),r8)
1378#else
1379 Vwrk(i)=Vinp(i)
1380#endif
1381 END DO
1382 END IF
1383 Vout=RESHAPE(Vwrk,(/Iout,Jout/))
1384 Nval=ic
1385!
1386 RETURN
1387 END FUNCTION load_2d_r8
1388!
1389 FUNCTION load_3d_r8 (Ninp, Vinp, Iout, Jout, Kout, Vout) &
1390 & RESULT (Nval)
1391!
1392!***********************************************************************
1393! !
1394! It loads input values into a requested model 3D floating-point !
1395! array (KIND=r8). !
1396! !
1397! On Input: !
1398! !
1399! Ninp Number of input elements to process in Vinp (integer) !
1400! Vinp Input values (1D real(dp) array) !
1401! Iout Size of output integer variable first I-dimension !
1402! Jout Size of output integer variable second J-dimension !
1403! Kout Size of output integer variable third K-dimension !
1404! !
1405! On Output: !
1406! !
1407! Vout Output 3D variable (real, KIND=r8) !
1408! Nval Number of output values processed !
1409! !
1410!=======================================================================
1411!
1412! Imported variable declarations.
1413!
1414 integer, intent(in) :: Ninp, Iout, Jout, Kout
1415 real(dp), intent(in) :: Vinp(:)
1416!
1417 real(r8), intent(out) :: Vout(:,:,:)
1418!
1419! Local variable declarations.
1420!
1421 integer :: i, ic
1422 integer :: Nout, Nval
1423!
1424 real(r8), dimension(Iout*Jout*Kout) :: Vwrk
1425!
1426!-----------------------------------------------------------------------
1427! Load 3D floating-point variable with input values.
1428!-----------------------------------------------------------------------
1429!
1430! If not all values are provided for variable, assume the last value
1431! for the rest of the array.
1432!
1433 ic=0
1434 Nout=Iout*Jout*Kout
1435 IF (Ninp.le.Nout) THEN
1436 DO i=1,Ninp
1437 ic=ic+1
1438#ifdef SINGLE_PRECISION
1439 Vwrk(i)=REAL(Vinp(i),r8)
1440#else
1441 Vwrk(i)=Vinp(i)
1442#endif
1443 END DO
1444 DO i=Ninp+1,Nout
1445 ic=ic+1
1446#ifdef SINGLE_PRECISION
1447 Vwrk(i)=REAL(Vinp(Ninp),r8)
1448#else
1449 Vwrk(i)=Vinp(Ninp)
1450#endif
1451 END DO
1452 ELSE
1453 DO i=1,Nout
1454 ic=ic+1
1455#ifdef SINGLE_PRECISION
1456 Vwrk(i)=REAL(Vinp(i),r8)
1457#else
1458 Vwrk(i)=Vinp(i)
1459#endif
1460 END DO
1461 END IF
1462 Vout=RESHAPE(Vwrk,(/Iout,Jout,Kout/))
1463 Nval=ic
1464!
1465 RETURN
1466 END FUNCTION load_3d_r8
1467!
1468 FUNCTION load_lbc (Ninp, Vinp, line, nline, ifield, igrid, &
1469 & iTrcStr, iTrcEnd, svname, S)
1470!
1471!***********************************************************************
1472! !
1473! This function sets lateral boundary conditions logical switches !
1474! according to input string keywords. !
1475! !
1476! On Input: !
1477! !
1478! Ninp Size of input variable (integer) !
1479! Vinp Input values (string) !
1480! line Current input line (string) !
1481! nline Multi-line counter (integer) !
1482! ifield Lateral boundary variable index (integer) !
1483! igrid Nested grid counter (integer) !
1484! iTrcStr Starting tracer index to process (integer) !
1485! iTrcEnd Ending tracer index to process (integer) !
1486! svname State variable name (string) !
1487! S Derived type structure, TYPE(T_LBC) !
1488! !
1489! On Output: !
1490! !
1491! nline Updated multi-line counter (integer) !
1492! igrid Updated nested grid counter (integer) !
1493! S Updated derived type structure, TYPE(T_LBC) !
1494! load_lbc Number of output values processed. !
1495! !
1496!***********************************************************************
1497!
1498 USE mod_param
1499 USE mod_parallel
1500 USE mod_iounits
1501 USE mod_ncparam
1502 USE mod_scalars
1503!
1504 USE strings_mod, ONLY : uppercase
1505!
1506! Imported variable declarations.
1507!
1508 integer, intent(in) :: Ninp, ifield, iTrcStr, iTrcEnd
1509 integer, intent(inout) :: igrid, nline
1510
1511 character (len=256), intent(in) :: line
1512 character (len=256), intent(in) :: Vinp(Ninp)
1513 character (len=* ), intent(in) :: svname
1514
1515 TYPE(T_LBC), intent(inout) :: S(4,nLBCvar,Ngrids)
1516!
1517! Local variable declarations.
1518!
1519 integer :: Icont, i, ibry, ic
1520 integer :: load_lbc
1521
1522 character (len=10) :: Bstring(4), string
1523!
1524!-----------------------------------------------------------------------
1525! Set lateral boundary conditions switches in structure.
1526!-----------------------------------------------------------------------
1527!
1528! Check current line for the continuation symbol [char(92)=\].
1529!
1530 Icont=INDEX(TRIM(line),CHAR(92) ,BACK=.FALSE.)
1531!
1532! Extract lateral boundary condition keywords from Vinp. Notice that
1533! additional array elements are added to Vinp during continuation
1534! lines.
1535!
1536 i=nline*4
1537 Bstring(1)=TRIM(Vinp(i+1))
1538 Bstring(2)=TRIM(Vinp(i+2))
1539 Bstring(3)=TRIM(Vinp(i+3))
1540 Bstring(4)=TRIM(Vinp(i+4))
1541!
1542! Advance or reset entry lines counter.
1543!
1544 IF (Icont.gt.0) THEN
1545 nline=nline+1
1546 ELSE
1547 nline=0
1548 END IF
1549!
1550! Set switches for each boundary segment.
1551!
1552 ic=1
1553 IF ((0.lt.ifield).and.(ifield.le.nLBCvar)) THEN
1554 DO ibry=1,4
1555 string=uppercase(Bstring(ibry))
1556 SELECT CASE (TRIM(string))
1557 CASE ('CHA')
1558 S(ibry,ifield,igrid)%Chapman_implicit = .TRUE.
1559 CASE ('CHE')
1560 S(ibry,ifield,igrid)%Chapman_explicit = .TRUE.
1561 CASE ('CLA')
1562 S(ibry,ifield,igrid)%clamped = .TRUE.
1563 S(ibry,ifield,igrid)%acquire = .TRUE.
1564 CASE ('CLO')
1565 S(ibry,ifield,igrid)%closed = .TRUE.
1566 CASE ('FLA')
1567 S(ibry,ifield,igrid)%Flather = .TRUE.
1568 S(ibry,ifield,igrid)%acquire = .TRUE.
1569 S(ibry,isFsur,igrid)%acquire = .TRUE.
1570 CASE ('GRA')
1571 S(ibry,ifield,igrid)%gradient = .TRUE.
1572 CASE ('NES')
1573 S(ibry,ifield,igrid)%nested = .TRUE.
1574 CASE ('PER')
1575 S(ibry,ifield,igrid)%periodic = .TRUE.
1576 IF ((ibry.eq.ieast).or.(ibry.eq.iwest)) THEN
1577 EWperiodic(igrid)=.TRUE.
1578 ELSE IF ((ibry.eq.inorth).or.(ibry.eq.isouth)) THEN
1579 NSperiodic(igrid)=.TRUE.
1580 END IF
1581 CASE ('RAD')
1582 S(ibry,ifield,igrid)%radiation = .TRUE.
1583 CASE ('RADNUD')
1584 S(ibry,ifield,igrid)%radiation = .TRUE.
1585 S(ibry,ifield,igrid)%nudging = .TRUE.
1586 S(ibry,ifield,igrid)%acquire = .TRUE.
1587 CASE ('RED')
1588 S(ibry,ifield,igrid)%reduced = .TRUE.
1589#if defined FSOBC_REDUCED
1590 S(ibry,isFsur,igrid)%acquire = .TRUE.
1591#endif
1592 CASE ('SHC')
1593 S(ibry,ifield,igrid)%Shchepetkin = .TRUE.
1594 S(ibry,ifield,igrid)%acquire = .TRUE.
1595 S(ibry,isFsur,igrid)%acquire = .TRUE.
1596 CASE DEFAULT
1597 IF (Master) THEN
1598 WRITE (stdout,10) TRIM(Vinp(ibry)), TRIM(line)
1599 END IF
1600 exit_flag=2
1601 RETURN
1602 END SELECT
1603 END DO
1604
1605#ifdef SOLVE3D
1606!
1607! If processing tracers and last standard input entry (Icont=0), set
1608! unspecified tracer values to the last tracer entry.
1609!
1610 IF ((iTrcStr.gt.0).and.(iTrcEnd.gt.0)) THEN
1611 IF ((Icont.eq.0).and.(ifield.lt.isTvar(iTrcEnd))) THEN
1612 DO i=ifield+1,isTvar(iTrcEnd)
1613 DO ibry=1,4
1614 S(ibry,i,igrid)%clamped = S(ibry,ifield,igrid)%clamped
1615 S(ibry,i,igrid)%closed = S(ibry,ifield,igrid)%closed
1616 S(ibry,i,igrid)%gradient = S(ibry,ifield,igrid)%gradient
1617 S(ibry,i,igrid)%nested = S(ibry,ifield,igrid)%nested
1618 S(ibry,i,igrid)%periodic = S(ibry,ifield,igrid)%periodic
1619 S(ibry,i,igrid)%radiation = S(ibry,ifield,igrid)%radiation
1620 S(ibry,i,igrid)%nudging = S(ibry,ifield,igrid)%nudging
1621 S(ibry,i,igrid)%acquire = S(ibry,ifield,igrid)%acquire
1622 END DO
1623 ic=ic+1
1624 END DO
1625 END IF
1626 END IF
1627#endif
1628 END IF
1629!
1630! If appropriate, increase or reset nested grid counter.
1631!
1632 IF ((Icont.gt.0).and.(Ngrids.gt.1)) THEN
1633 IF ((iTrcStr.gt.0).and.(iTrcEnd.gt.0)) THEN
1634 IF ((ifield.eq.isTvar(iTrcEnd)).or.(ic.gt.1)) THEN
1635 igrid=igrid+MIN(1,Icont)
1636 END IF
1637 ELSE
1638 igrid=igrid+MIN(1,Icont)
1639 END IF
1640 IF (igrid.gt.Ngrids) THEN
1641 IF (Master) THEN
1642 WRITE (stdout,20) TRIM(line)
1643 END IF
1644 exit_flag=2
1645 RETURN
1646 END IF
1647 ELSE
1648 igrid=1
1649 END IF
1650 load_lbc=ic
1651
1652 10 FORMAT (/,' INP_PAR - illegal lateral boundary condition ', &
1653 & 'keyword: ',a,/,11x,a)
1654 20 FORMAT (/,' INP_PAR - incorrect continuation symbol in line:',/, &
1655 & 11x,a,/,11x,'number of nested grid values exceeded.')
1656!
1657 RETURN
1658 END FUNCTION load_lbc
1659!
1660 FUNCTION load_s1d (Nval, Fname, Fdim, line, label, igrid, Nfiles, &
1661 & S)
1662!
1663!***********************************************************************
1664! !
1665! This function loads input values into requested 1D structure !
1666! containing information about I/O files. !
1667! !
1668! On Input: !
1669! !
1670! Nval Number of values processed (integer) !
1671! Fname File name(s) processed (string array) !
1672! Fdim File name(s) dimension in calling program (integer) !
1673! line Current input line (string) !
1674! label I/O structure label (string) !
1675! igrid Nested grid counter (integer) !
1676! Nfiles Number of files per grid (integer array) !
1677! S Derived type structure, TYPE(T_IO) !
1678! !
1679! On Output: !
1680! !
1681! igrid Updated nested grid counter. !
1682! S Updated derived type structure, TYPE(T_IO). !
1683! load_s1d Number of output values processed. !
1684! !
1685!***********************************************************************
1686!
1687 USE mod_param
1688 USE mod_parallel
1689 USE mod_iounits
1690 USE mod_ncparam
1691 USE mod_scalars
1692!
1693! Imported variable declarations.
1694!
1695 integer, intent(in) :: Nval, Fdim
1696 integer, intent(inout) :: igrid
1697 integer, intent(inout) :: Nfiles(Ngrids)
1698
1699 character (len=*), intent(in) :: line
1700 character (len=256), intent(in) :: Fname(Fdim)
1701 character (len=*), intent(inout) :: label
1702
1703 TYPE(T_IO), intent(inout) :: S(Ngrids)
1704!
1705! Local variable declarations.
1706!
1707 logical :: load, persist
1708
1709 integer :: Icont, Ipipe, i, j, lstr, my_Ngrids, ng
1710 integer :: load_s1d
1711
1712 character (len=1 ), parameter :: blank = ' '
1713!
1714!-----------------------------------------------------------------------
1715! Count files for all grids and activate load switch.
1716!-----------------------------------------------------------------------
1717!
1718! Check current line for the continuation symbol [char(92)=\] or pipe
1719! symbol [char(124)=|]. The continuation symbol is used to separate
1720! string values for different grid, whereas the pipe symbol is used
1721! to separate multi-string values for split input files. User may
1722! split the records for a particular input field into several files.
1723!
1724 Icont=INDEX(TRIM(line),CHAR(92) ,BACK=.FALSE.)
1725 Ipipe=INDEX(TRIM(line),CHAR(124),BACK=.FALSE.)
1726 IF ((Icont.eq.0).and.(Ipipe.eq.0)) THEN
1727 load=.TRUE. ! last input string
1728 ELSE
1729 load=.FALSE. ! process next string
1730 END IF
1731!
1732! Accumulate number of multi-files per each grid.
1733!
1734 Nfiles(igrid)=Nfiles(igrid)+1
1735!
1736! Set grid counter.
1737!
1738 IF (.not.load) THEN
1739 igrid=igrid+MIN(1,Icont)
1740 END IF
1741 IF (igrid.gt.Ngrids) THEN
1742 IF (Master) THEN
1743 WRITE (stdout,10) TRIM(line)
1744 END IF
1745 exit_flag=2
1746 RETURN
1747 END IF
1748!
1749!-----------------------------------------------------------------------
1750! Load I/O information into structure.
1751!-----------------------------------------------------------------------
1752!
1753 IF (load) THEN
1754!
1755! If nesting and the number of file name entries is less than Ngrids,
1756! persist the last values provided. This is the case when not enough
1757! entries are provided by "==" plural symbol after the KEYWORD.
1758!
1759 IF (igrid.lt.Ngrids) THEN
1760 DO i=igrid+1,Ngrids
1761 Nfiles(i)=Nfiles(igrid)
1762 END DO
1763 my_Ngrids=igrid
1764 persist=.TRUE.
1765 ELSE
1766 my_Ngrids=Ngrids
1767 persist=.FALSE.
1768 END IF
1769!
1770! Allocate various fields in structure, if not continuation or pipe
1771! symbol is found which indicates end of input data.
1772!
1773 DO ng=1,Ngrids
1774 allocate ( S(ng)%Nrec(Nfiles(ng)) )
1775 allocate ( S(ng)%time_min(Nfiles(ng)) )
1776 allocate ( S(ng)%time_max(Nfiles(ng)) )
1777 IF (label(1:3).eq.'FLT') THEN
1778#ifdef FLOAT_BIOLOGY
1779 allocate ( S(ng)%Vid(-10:NV) )
1780#else
1781 allocate ( S(ng)%Vid(-6:NV) )
1782#endif
1783 ELSE
1784 allocate ( S(ng)%Vid(NV) )
1785 END IF
1786 allocate ( S(ng)%Tid(MT) )
1787 allocate ( S(ng)%files(Nfiles(ng)) )
1788 END DO
1789!
1790! Intialize strings to blank to facilitate processing.
1791!
1792 DO ng=1,Ngrids
1793 lstr=LEN(S(ng)%name)
1794 DO i=1,lstr
1795 S(ng)%base(i:i)=blank
1796 S(ng)%name(i:i)=blank
1797 END DO
1798 DO j=1,Nfiles(ng)
1799 DO i=1,lstr
1800 S(ng)%files(j)(i:i)=blank
1801 END DO
1802 END DO
1803 END DO
1804!
1805! Initialize and load fields into structure.
1806!
1807 i=0
1808 DO ng=1,my_Ngrids
1809 S(ng)%Nfiles=Nfiles(ng) ! number of multi-files
1810 S(ng)%Fcount=1 ! multi-file counter
1811 S(ng)%Rindex=0 ! time index
1812 S(ng)%ncid=-1 ! closed NetCDF state
1813 S(ng)%Vid=-1 ! NetCDF variables IDs
1814 S(ng)%Tid=-1 ! NetCDF tracers IDs
1815 DO j=1,Nfiles(ng)
1816 i=i+1
1817 S(ng)%files(j)=TRIM(Fname(i)) ! load multi-files
1818 S(ng)%Nrec(j)=0 ! record counter
1819 S(ng)%time_min(j)=0.0_dp ! starting time
1820 S(ng)%time_max(j)=0.0_dp ! ending time
1821 END DO
1822 S(ng)%label=TRIM(label) ! structure label
1823 S(ng)%name=TRIM(S(ng)%files(1)) ! load first file
1824 lstr=LEN_TRIM(S(ng)%name)
1825 S(ng)%base=S(ng)%name(1:lstr-3) ! do not include ".nc"
1826 Nfiles(ng)=0 ! clean file counter
1827 END DO
1828!
1829! If appropriate, persist last value(s).
1830!
1831 IF (persist) THEN
1832 DO ng=igrid+1,Ngrids
1833 S(ng)%Nfiles=S(igrid)%Nfiles
1834 S(ng)%Fcount=1
1835 S(ng)%Rindex=0
1836 S(ng)%ncid=-1
1837 S(ng)%Vid=-1
1838 S(ng)%Tid=-1
1839 DO j=1,S(igrid)%Nfiles
1840 S(ng)%files(j)=S(igrid)%files(j)
1841 S(ng)%Nrec(j)=0
1842 S(ng)%time_min(j)=0.0_dp
1843 S(ng)%time_max(j)=0.0_dp
1844 END DO
1845 S(ng)%label=TRIM(label)
1846 S(ng)%name=S(igrid)%name
1847 S(ng)%base=S(igrid)%base
1848 Nfiles(ng)=0
1849 END DO
1850 END IF
1851!
1852! Reset counters and clean label.
1853!
1854 igrid=1
1855 DO ng=1,Ngrids
1856 Nfiles(ng)=0
1857 END DO
1858 DO i=1,LEN(label)
1859 label(i:i)=blank
1860 END DO
1861 END IF
1862 load_s1d=Nval
1863
1864 10 FORMAT (/,' INP_PAR - incorrect continuation symbol in line:',/, &
1865 & 11x,a,/,11x,'number of nested grid values exceeded.')
1866!
1867 RETURN
1868 END FUNCTION load_s1d
1869!
1870 FUNCTION load_s2d (Nval, Fname, Fdim, line, label, ifile, igrid, &
1871 & Mgrids, Nfiles, Ncount, idim, S)
1872!
1873!***********************************************************************
1874! !
1875! This function loads input values into requested 2D structure !
1876! containing information about input forcing files. Notice that !
1877! Mgrids is passed for flexibility in coupling algorithms. !
1878! !
1879! On Input: !
1880! !
1881! Nval Number of values processed (integer) !
1882! Fname File name(s) processed (string array) !
1883! Fdim File name(s) dimension in calling program (integer) !
1884! line Current input line (string) !
1885! label I/O structure label (string) !
1886! ifile File structure counter (integer) !
1887! igrid Nested grid counter (integer) !
1888! Mgrids Number of nested grids (integer) !
1889! Nfiles Number of input files per grid (integer vector) !
1890! Ncount Number of files per grid counter (integer array) !
1891! idim Size of structure inner dimension (integer) !
1892! S Derived type structure, TYPE(T_IO) !
1893! !
1894! On Output: !
1895! !
1896! ifile Updated file counter. !
1897! igrid Updated nested grid counter. !
1898! S Updated derived type structure, TYPE(T_IO). !
1899! load_s2d Number of output values processed. !
1900! !
1901!***********************************************************************
1902!
1903 USE mod_param
1904 USE mod_parallel
1905 USE mod_iounits
1906 USE mod_ncparam
1907 USE mod_scalars
1908!
1909! Imported variable declarations.
1910!
1911 integer, intent(in) :: Mgrids, Nval, Fdim, idim
1912 integer, intent(in) :: Nfiles(Mgrids)
1913 integer, intent(inout) :: ifile, igrid
1914 integer, intent(inout) :: Ncount(idim,Mgrids)
1915
1916 character (len=*), intent(in) :: line
1917 character (len=256), intent(in) :: Fname(Fdim)
1918 character (len=*), intent(inout) :: label
1919
1920 TYPE(T_IO), intent(inout) :: S(idim,Mgrids)
1921!
1922! Local variable declarations.
1923!
1924 logical :: load, persist
1925
1926 integer :: Icont, Ipipe, i, j, k, lstr, my_Mgrids, ng
1927 integer :: load_s2d
1928
1929 character (len=1 ), parameter :: blank = ' '
1930!
1931!-----------------------------------------------------------------------
1932! Count files for all grids and activate load switch.
1933!-----------------------------------------------------------------------
1934!
1935! Check current line for the continuation symbol [char(92)=\] or pipe
1936! symbol [char(124)=|]. The continuation symbol is used to separate
1937! string values for different grid, whereas the pipe symbol is used
1938! to separate multi-string values for split input files. User may
1939! split the records for a particular input field into several files.
1940!
1941 Icont=INDEX(TRIM(line),CHAR(92) ,BACK=.FALSE.)
1942 Ipipe=INDEX(TRIM(line),CHAR(124),BACK=.FALSE.)
1943 IF ((Icont.eq.0).and.(Ipipe.eq.0)) THEN
1944 load=.TRUE. ! last input string
1945 ELSE
1946 load=.FALSE. ! process next string
1947 END IF
1948!
1949! Accumulate number of multi-files per each grid.
1950!
1951 Ncount(ifile,igrid)=Ncount(ifile,igrid)+1
1952!
1953! Set counters for next processing file, if any. The continuation
1954! symbol in the input "line" is used to advance the counters.
1955!
1956 IF (.not.load) THEN
1957 IF ((ifile.lt.Nfiles(igrid)).or.(Ipipe.ne.0)) THEN
1958 ifile=ifile+MIN(1,Icont)
1959 ELSE
1960 ifile=1
1961 igrid=igrid+MIN(1,Icont)
1962 END IF
1963 END IF
1964 IF (ifile.gt.idim) THEN
1965 IF (Master) THEN
1966 WRITE (stdout,10) TRIM(line)
1967 END IF
1968 exit_flag=2
1969 RETURN
1970 END IF
1971 IF (igrid.gt.Mgrids) THEN
1972 IF (Master) THEN
1973 WRITE (stdout,20) TRIM(line)
1974 END IF
1975 exit_flag=2
1976 RETURN
1977 END IF
1978!
1979!-----------------------------------------------------------------------
1980! Load I/O information into structure.
1981!-----------------------------------------------------------------------
1982!
1983 IF (load) THEN
1984!
1985! If nesting and the number of file name entries is less than Mgrids,
1986! persist the last values provided. This is the case when not enough
1987! entries are provided by "==" plural symbol after the KEYWORD.
1988!
1989 IF (igrid.lt.Mgrids) THEN
1990 DO j=igrid+1,Mgrids
1991 DO i=1,idim
1992 Ncount(i,j)=Ncount(i,igrid)
1993 END DO
1994 END DO
1995 my_Mgrids=igrid
1996 persist=.TRUE.
1997 ELSE
1998 my_Mgrids=Mgrids
1999 persist=.FALSE.
2000 END IF
2001
2002!
2003! Allocate various fields in structure, if not continuation or pipe
2004! symbol is found which indicates end of input data.
2005!
2006 DO ng=1,Mgrids
2007 DO i=1,idim
2008 allocate ( S(i,ng)%Nrec(Ncount(i,ng)) )
2009 allocate ( S(i,ng)%time_min(Ncount(i,ng)) )
2010 allocate ( S(i,ng)%time_max(Ncount(i,ng)) )
2011 allocate ( S(i,ng)%Vid(NV) )
2012 allocate ( S(i,ng)%Tid(MT) )
2013 allocate ( S(i,ng)%files(Ncount(i,ng)) )
2014 END DO
2015 END DO
2016!
2017! Intialize strings to blank to facilitate processing.
2018!
2019 DO ng=1,Mgrids
2020 DO i=1,idim
2021 lstr=LEN(S(i,ng)%name)
2022 DO j=1,lstr
2023 S(i,ng)%base(j:j)=blank
2024 S(i,ng)%name(j:j)=blank
2025 END DO
2026 DO k=1,Ncount(i,ng)
2027 DO j=1,lstr
2028 S(i,ng)%files(k)(j:j)=blank
2029 END DO
2030 END DO
2031 END DO
2032 END DO
2033!
2034! Initialize and load fields into structure.
2035!
2036 k=0
2037 DO ng=1,my_Mgrids
2038 DO i=1,Nfiles(ng)
2039 S(i,ng)%Nfiles=Ncount(i,ng) ! number of multi-files
2040 S(i,ng)%Fcount=1 ! multi-file counter
2041 S(i,ng)%Rindex=0 ! time index
2042 S(i,ng)%ncid=-1 ! closed NetCDF state
2043 S(i,ng)%Vid=-1 ! NetCDF variables IDs
2044 S(i,ng)%Tid=-1 ! NetCDF tracers IDs
2045 DO j=1,Ncount(i,ng)
2046 k=k+1
2047 S(i,ng)%files(j)=TRIM(Fname(k)) ! load multi-files
2048 S(i,ng)%Nrec(j)=0 ! record counter
2049 S(i,ng)%time_min(j)=0.0_dp ! starting time
2050 S(i,ng)%time_max(j)=0.0_dp ! ending time
2051 END DO
2052 S(i,ng)%label=TRIM(label) ! structure label
2053 S(i,ng)%name=TRIM(S(i,ng)%files(1)) ! load first file
2054 lstr=LEN_TRIM(S(i,ng)%name)
2055 S(i,ng)%base=S(i,ng)%name(1:lstr-3) ! do not include ".nc"
2056 END DO
2057 END DO
2058!
2059! If appropriate, persist last value(s).
2060!
2061 IF (persist) THEN
2062 DO ng=igrid+1,Mgrids
2063 DO i=1,Nfiles(ng)
2064 S(i,ng)%Nfiles=S(i,igrid)%Nfiles
2065 S(i,ng)%Fcount=1
2066 S(i,ng)%Rindex=0
2067 S(i,ng)%ncid=-1
2068 S(i,ng)%Vid=-1
2069 S(i,ng)%Tid=-1
2070 DO j=1,S(i,igrid)%Nfiles
2071 S(i,ng)%files(j)=S(i,igrid)%files(j)
2072 S(i,ng)%Nrec(j)=0
2073 S(i,ng)%time_min(j)=0.0_dp
2074 S(i,ng)%time_max(j)=0.0_dp
2075 END DO
2076 S(i,ng)%label=TRIM(label)
2077 S(i,ng)%name=S(i,igrid)%name
2078 S(i,ng)%base=S(i,igrid)%base
2079 Ncount(i,ng)=0
2080 END DO
2081 END DO
2082 END IF
2083!
2084! Reset counters and clean label.
2085!
2086 igrid=1
2087 ifile=1
2088 DO ng=1,Mgrids
2089 DO i=1,idim
2090 Ncount(i,ng)=0
2091 END DO
2092 END DO
2093 DO i=1,LEN(label)
2094 label(i:i)=blank
2095 END DO
2096 END IF
2097 load_s2d=Nval
2098
2099 10 FORMAT (/,' INP_PAR - incorrect continuation symbol in line:',/, &
2100 & 11x,a,/,11x,'inner dimension of structure exceeded.')
2101 20 FORMAT (/,' INP_PAR - incorrect continuation symbol in line:',/, &
2102 & 11x,a,/,11x,'number of nested grid values exceeded.')
2103!
2104 RETURN
2105 END FUNCTION load_s2d
2106!
2107 END MODULE inp_decode_mod