source: palm/trunk/UTIL/interpret_config.f90 @ 1046

Last change on this file since 1046 was 1046, checked in by maronga, 11 years ago

put scripts and utilities under GPL

  • Property svn:keywords set to Id
File size: 20.8 KB
Line 
1 PROGRAM interpret_config
2
3!--------------------------------------------------------------------------------!
4! This file is part of PALM.
5!
6! PALM is free software: you can redistribute it and/or modify it under the terms
7! of the GNU General Public License as published by the Free Software Foundation,
8! either version 3 of the License, or (at your option) any later version.
9!
10! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
11! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
12! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
13!
14! You should have received a copy of the GNU General Public License along with
15! PALM. If not, see <http://www.gnu.org/licenses/>.
16!
17! Copyright 1997-2012  Leibniz University Hannover
18!--------------------------------------------------------------------------------!
19!
20! Current revisions:
21! -----------------
22! code put under GPL (PALM 3.9)
23!
24! Former revisions:
25! -----------------
26! $Id: interpret_config.f90 1046 2012-11-09 14:38:45Z maronga $
27!
28! 785 2011-11-28 09:47:19Z raasch
29! character length extended to 1000 in order to account for long lines in the
30! configuration file
31!
32! 07/09/10 - Siggi - bugfix in 2201 statement: closing " was missing
33! unknown  - Siggi - mrun environment variables are read from NAMELIST instead
34!                    of using GETENV. Variables are always assigned a value,
35!                    also if they already got one. These values are re-assigned
36!                    later in mrun.
37! 28/02/07 - Siggi - empty lines in configuration file are accepted
38! 01/11/05 - Siggi - s2b-Feld erlaubt den Wert locopt
39! 29/06/05 - Siggi - Fehlermeldung ins englische uebertragen und ergaenzt
40! 29/04/05 - Siggi - extin wird auch fuer Input-Dateien ausgegeben
41! 18/11/97 - Siggi - Komma in 2010-FORMAT hinzugefuegt
42! 21/07/97 - Siggi - Erste Fassung
43!
44! Description:
45! -------------
46! This program reads the mrun-configuration file .mrun.config and outputs
47! its content in form of ksh-commands, which can then be executed by mrun.
48! mrun is also able to directly read from the configuration file by using
49! the option "-S" (but with much slower speed).
50!------------------------------------------------------------------------------!
51
52    IMPLICIT NONE
53
54    CHARACTER (LEN=1)    ::  bs = ACHAR( 92 )   ! backslash (auf vpp sonst n.
55                                               ! druckbar)
56    CHARACTER (LEN=20)   ::  do_remote, do_trace, host, localhost
57    CHARACTER (LEN=100)  ::  config_file, icf
58    CHARACTER (LEN=1000) ::  cond1, cond2, empty = REPEAT( ' ', 240 ),       &
59                             for_cond1, for_cond2, for_host, input_list,     &
60                             iolist, output_list, s1, s2, s2a, s2b, s2c, s3, &
61                             s3cond, s4, s5, s6, value, value_mrun, var, zeile
62
63    INTEGER ::  dummy, i, icomment = 0, icond1, icond2, idatver = 0, iec = 0,  &
64                ienvvar = 0, ifor_cond1, ifor_cond2, ifor_host, ihost,         &
65                iic = 0, iicf, iin = 0, iinput_list, il, ilocalhost,  ioc = 0, &
66                ios, iout = 0, ioutput_list, is1, is2, is2a, is2b, is2c,       &
67                is3, is3cond, is4, is5, is6, ivalue, ivar, izeile, linenr
68
69    LOGICAL ::  found
70
71    NAMELIST /mrun_environment/  cond1, cond2, config_file, do_remote,       &
72                                 do_trace, host, input_list, icf, localhost, &
73                                 output_list
74
75
76    OPEN ( 1, FILE='.mrun_environment', FORM='FORMATTED' )
77    READ ( 1, mrun_environment )
78    CLOSE ( 1 )
79
80    icond1       = LEN_TRIM( cond1 )
81    icond2       = LEN_TRIM( cond2 )
82    il           = LEN_TRIM( config_file )
83    ihost        = LEN_TRIM( host )
84    iinput_list  = LEN_TRIM( input_list )
85    iicf         = LEN_TRIM( icf )
86    ilocalhost   = LEN_TRIM( localhost )
87    ioutput_list = LEN_TRIM( output_list )
88
89    iolist = input_list(1:iinput_list) // output_list(1:ioutput_list)
90
91    IF ( do_trace(1:4) == 'true' )  THEN
92       PRINT*,'*** cond1="',cond1(1:icond1),'"'
93       PRINT*,'*** cond2="',cond2(1:icond2),'"'
94       PRINT*,'*** config_file="',config_file(1:il),'"'
95       PRINT*,'*** do_remote="',do_remote,'"'
96       PRINT*,'*** do_trace="',do_trace,'"'
97       PRINT*,'*** host="',host(1:ihost),'"'
98       PRINT*,'*** input_list="',input_list(1:iinput_list),'"'
99       PRINT*,'*** interpreted_config_file="',icf(1:iicf),'"'
100       PRINT*,'*** localhost="',localhost(1:ilocalhost),'"'
101       PRINT*,'*** output_list="',output_list(1:ioutput_list),'"'
102    ENDIF
103
104    OPEN ( 1, FILE=config_file(1:il), FORM='formatted' )
105    OPEN ( 2, FILE=icf(1:iicf), FORM='formatted' )
106
107    READ ( 1, '(A)', IOSTAT=ios )  zeile
108    linenr = 1
109
110
111    DO WHILE ( ios == 0 )
112
113       izeile = LEN_TRIM( zeile )
114
115       IF ( LEN_TRIM( zeile ) == 0 )  THEN
116
117          CONTINUE
118
119       ELSEIF ( zeile(1:1) == '#' )  THEN
120
121          icomment = icomment + 1
122
123       ELSEIF ( zeile(1:1) == '%' )  THEN
124
125          ienvvar = ienvvar + 1
126          i = INDEX( zeile, ' ' )
127          var = zeile(2:i-1)
128          ivar = i - 2
129
130          zeile(1:i) = empty(1:i)
131          zeile = ADJUSTL( zeile )
132          i = INDEX( zeile, ' ' )
133          value = zeile(1:i-1)
134          ivalue = i - 1
135
136          zeile(1:i) = empty(1:i)
137          zeile = ADJUSTL( zeile )
138          i = INDEX( zeile, ' ' )
139
140          IF ( i /= 1 )  THEN
141             for_host = zeile(1:i-1)
142             ifor_host = i - 1
143
144             zeile(1:i) = empty(1:i)
145             zeile = ADJUSTL( zeile )
146             i = INDEX( zeile, ' ' )
147
148             IF ( i /= 1 )  THEN
149                for_cond1 = zeile(1:i-1)
150                ifor_cond1 = i - 1
151
152                zeile(1:i) = empty(1:i)
153                zeile = ADJUSTL( zeile )
154                i = INDEX( zeile, ' ' )
155
156                IF ( i /= 1 )  THEN
157                   for_cond2 = zeile(1:i-1)
158                   ifor_cond2 = i - 1
159                ELSE
160                   for_cond2 = ''
161                   ifor_cond2 = 0
162                ENDIF
163             ELSE
164                for_cond1 = ''
165                ifor_cond1 = 0
166                for_cond2 = ''
167                ifor_cond2 = 0
168             ENDIF
169          ELSE
170             for_host = ' '
171             ifor_host = 1
172             for_cond1 = ''
173             ifor_cond1 = 0
174             for_cond2 = ''
175             ifor_cond2 = 0
176          ENDIF
177          IF ( do_trace(1:4) == 'true' )  THEN
178             PRINT*,'var="',var(1:ivar),'"'
179             PRINT*,'value="',value(1:ivalue),'"'
180             PRINT*,'for_host="',for_host(1:ifor_host),'"'
181             PRINT*,'for_cond1="',for_cond1(1:ifor_cond1),'"'
182             PRINT*,'for_cond2="',for_cond2(1:ifor_cond2),'"'
183          ENDIF
184!
185!--       Geltungsbereich pruefen und evtl. Variable ausgeben
186          IF ( for_host == ' '  .OR.  ( &
187               for_host(1:ifor_host) == host(1:ihost)  .AND. &
188               for_cond1(1:ifor_cond1) == cond1(1:icond1)  .AND. &
189               for_cond2(1:ifor_cond2) == cond2(1:icond2) &
190                                      )  .OR. ( &
191               INDEX( iolist, for_host(1:ifor_host) ) /= 0 &
192                                              ) )  THEN
193
194!
195!--          Zuerst Doppelpunkte durch Blanks ersetzen (aber doppelt
196!--          auftretende Doppelpunkte durch einen Doppelpunkt)
197             i = 0
198             DO
199                i = i + 1
200                IF ( i > ivalue )  EXIT
201                IF ( value(i:i) == ':' )  THEN
202                   IF ( value(i+1:i+1) == ':' )  THEN
203                      value = value(1:i) // value(i+2:ivalue)
204                      ivalue = ivalue - 1
205                   ELSE
206                      value(i:i) = ' '
207                   ENDIF
208                ENDIF
209             ENDDO
210
211!
212!--          Variable ausgeben
213             WRITE (2,2200)  var(1:ivar), bs, value(1:ivalue), bs, &
214                             var(1:ivar)
215 2200        FORMAT ('eval ',A,'=',A,'"',A,A,'"'/'export ',A)
216
217             IF ( do_trace(1:4) == 'true' )  THEN
218                WRITE (2,2201)  bs, var(1:ivar), value(1:ivalue)
219 2201           FORMAT ('printf "',A,'n*** ENVIRONMENT-VARIABLE ',A,' = ',A,'"')
220             ENDIF
221
222          ENDIF
223
224!
225!--       Variable "host" muss gleich ausgewertet werden, da mit ihr ein
226!--       neuer Geltungsbereich festgelegt wird
227          IF ( var(1:ivar) == 'host' )  THEN
228
229             host  = value(1:ivalue)
230             ihost = ivalue
231
232!             IF ( host(1:ihost) /= localhost(1:ilocalhost) )  THEN
233!
234!                SELECT CASE ( value(1:ivalue) )
235!
236!                   CASE ( 'cray','hpcs','t3d','t3eb','t3eh','unics','vpp' )
237!
238!                      dummy = 1
239!
240!                   CASE DEFAULT
241!
242!                      WRITE (2,2202)  bs, bs, value(1:ivalue), bs, bs
243! 2202                 FORMAT ('printf "',A,'n +++ Auf Zielrechner ',A,'"',A,A,'" ist kein NQS-System vorhanden"'/ &
244!                              'printf "',A,'n     Programmlauf kann deshalb nicht gestartet werden"'/ &
245!                              'locat=nqs; exit')
246!                      STOP
247!
248!                END SELECT
249!
250!             ENDIF
251
252          ENDIF
253
254       ELSEIF ( zeile(1:3) == 'EC:' )  THEN
255!
256!--       Error-Kommandos
257          iec = iec + 1
258          IF ( iec < 10 )  THEN
259             WRITE (2,'(''err_command['',I1,'']="'',A,''"'')')  iec, &
260                                                                zeile(4:izeile)
261          ELSEIF ( iec < 100 )  THEN
262             WRITE (2,'(''err_command['',I2,'']="'',A,''"'')')  iec, &
263                                                                zeile(4:izeile)
264          ELSE
265             WRITE (2,'(''err_command['',I3,'']="'',A,''"'')')  iec, &
266                                                                zeile(4:izeile)
267          ENDIF
268
269       ELSEIF ( zeile(1:3) == 'IC:' )  THEN
270!
271!--       Input-Kommandos
272          iic = iic + 1
273          IF ( iic < 10 )  THEN
274             WRITE (2,'(''in_command['',I1,'']="'',A,''"'')')  iic, &
275                                                               zeile(4:izeile)
276          ELSEIF ( iic < 100 )  THEN
277             WRITE (2,'(''in_command['',I2,'']="'',A,''"'')')  iic, &
278                                                               zeile(4:izeile)
279          ELSE
280             WRITE (2,'(''in_command['',I3,'']="'',A,''"'')')  iic, &
281                                                               zeile(4:izeile)
282          ENDIF
283
284       ELSEIF ( zeile(1:3) == 'OC:' )  THEN
285!
286!--       Output-Kommandos
287          ioc = ioc + 1
288          IF ( ioc < 10 )  THEN
289             WRITE (2,'(''out_command['',I1,'']="'',A,''"'')')  ioc, &
290                                                                zeile(4:izeile)
291          ELSEIF ( ioc < 100 )  THEN
292             WRITE (2,'(''out_command['',I2,'']="'',A,''"'')')  ioc, &
293                                                                zeile(4:izeile)
294          ELSE
295             WRITE (2,'(''out_command['',I3,'']="'',A,''"'')')  ioc, &
296                                                                zeile(4:izeile)
297          ENDIF
298
299       ELSE
300!
301!--       Dateiverbindungen
302          idatver = idatver + 1
303!
304!--       Lokaler Name
305          i   = INDEX( zeile , ' ' )
306          s1  = zeile(1:i-1)
307          is1 = i-1
308!
309!--       Dateieigenschaften
310          zeile = ADJUSTL( zeile(i:izeile) )
311          i   = INDEX( zeile , ' ' )
312          s2  = zeile(1:i-1)
313          is2 = i-1
314!
315!--       Geltungsbereich
316          zeile = ADJUSTL( zeile(i:izeile) )
317          i   = INDEX( zeile , ' ' )
318          s3  = zeile(1:i-1)
319          is3 = i-1
320!
321!--       Pfadname
322          zeile = ADJUSTL( zeile(i:izeile) )
323          i   = INDEX( zeile , ' ' )
324          s4  = zeile(1:i-1)
325          is4 = i-1
326!
327!--       evtl. Extension
328          zeile = ADJUSTL( zeile(i:izeile) )
329          i = INDEX( zeile , ' ' )
330          IF ( i == 1 )  THEN
331             s5  = ' '
332             is5 = 1
333             s6  = ' '
334             is6 = 1
335          ELSE
336             s5  = zeile(1:i-1)
337             is5 = i-1
338!
339!--          evtl. 2. Extension
340             zeile = ADJUSTL( zeile(i:izeile) )
341             i = INDEX( zeile , ' ' )
342             IF ( i == 1 )  THEN
343                s6  = ' '
344                is6 = 1
345             ELSE
346                s6  = zeile(1:i-1)
347                is6 = i-1
348             ENDIF
349          ENDIF
350
351!
352!--       Dateieigenschaften aufspalten
353          i = INDEX( s2 , ':' )
354          IF ( i == 0 )  THEN
355             s2a  = s2
356             is2a = is2
357             s2b  = ''
358             is2b = 0
359             s2c  = ''
360             is2c = 0
361          ELSE
362             s2a  = s2(1:i-1)
363             is2a = i-1
364             s2   = s2(i+1:is2)
365
366             i = INDEX( s2 , ':' )
367             IF ( i == 0 )  THEN
368                s2b  = s2
369                is2b = LEN_TRIM( s2 )
370                s2c  = ''
371                is2c = 0
372             ELSE
373                s2b  = s2(1:i-1)
374                is2b = i-1
375                s2c  = s2(i+1:)
376                is2c = LEN_TRIM( s2c )
377             ENDIF
378          ENDIF
379!
380!--       Pruefung, ob Eingabedateiverbindung abgespeichert werden soll
381          IF ( s2a(1:is2a) == 'in'  .AND.  .NOT. (                     &
382               do_remote(1:4) == 'true'  .AND.                         &
383               ( s2b(1:is2b) == 'loc'  .OR.  s2b(1:is2b) == 'locopt' ) &
384                                                 ) )  THEN
385             found = .FALSE.
386             i = INDEX( s3 , ':' )
387             IF ( i == 0 )  THEN
388                s3cond  = s3
389                is3cond = LEN_TRIM( s3cond )
390             ELSE
391                s3cond  = s3(1:i-1)
392                is3cond = i-1
393                s3      = s3(i+1:)
394             ENDIF
395
396             DO WHILE ( s3cond(1:1) /= ' ' )
397
398                IF ( INDEX( input_list(1:iinput_list) , s3cond(1:is3cond) ) /= 0 &
399                     .OR.  s3cond(1:is3cond) == '-' )  THEN
400                   found = .TRUE.
401                ENDIF
402
403                IF ( s3(1:1) == ' ' )  THEN
404                   s3cond = ' '
405                ELSE
406                   i = INDEX( s3 , ':' )
407                   IF ( i == 0 )  THEN
408                      s3cond  = s3
409                      is3cond = LEN_TRIM( s3cond )
410                      s3      = ' '
411                   ELSE
412                      s3cond  = s3(1:i-1)
413                      is3cond = i-1
414                      s3      = s3(i+1:)
415                   ENDIF
416                ENDIF
417
418             ENDDO
419
420!
421!--          Wenn Geltungsbereich erfuellt, dann Dateiverbindung abspeichern
422             IF ( found )  THEN
423
424                iin = iin + 1
425                IF ( iin < 10 )  THEN
426                   WRITE (2,2000)  iin, s1(1:is1), iin, s2b(1:is2b), &
427                                   iin, s2c(1:is2c), &
428                                   iin, s3(1:is3), iin, s4(1:is4), &
429                                   iin, s5(1:is5), iin, s6(1:is6)
4302000               FORMAT ('localin[',I1,']="',A,'"; transin[',I1,']="',A, &
431                           '"; actionin[',I1,']="',A, &
432                           '"; typein[',I1,']="',A,'"'/'pathin[',I1,']="',A, &
433                           '"; endin[',I1,']="',A,'"; extin[',I1,']="',A,'"')
434                ELSEIF ( iin < 100 )  THEN
435                   WRITE (2,2001)  iin, s1(1:is1), iin, s2b(1:is2b), &
436                                   iin, s2c(1:is2c), &
437                                   iin, s3(1:is3), iin, s4(1:is4), &
438                                   iin, s5(1:is5), iin, s6(1:is6)
4392001               FORMAT ('localin[',I2,']="',A,'"; transin[',I2,']="',A, &
440                           '"; actionin[',I2,']="',A, &
441                           '"; typein[',I2,']="',A,'"'/'pathin[',I2,']="',A, &
442                           '"; endin[',I2,']="',A,'"; extin[',I2,']="',A,'"')
443                ELSE
444                   WRITE (2,2002)  iin, s1(1:is1), iin, s2b(1:is2b), &
445                                   iin, s2c(1:is2c), &
446                                   iin, s3(1:is3), iin, s4(1:is4), &
447                                   iin, s5(1:is5), iin, s6(1:is6)
4482002               FORMAT ('localin[',I3,']="',A,'"; transin[',I3,']="',A, &
449                           '"; actionin[',I3,']="',A, &
450                           '"; typein[',I3,']="',A,'"'/'pathin[',I3,']="',A, &
451                           '"; endin[',I3,']="',A,'"; extin[',I3,']="',A,'"')
452                ENDIF
453             ENDIF
454
455          ELSEIF ( s2a(1:is2a) == 'out'  .AND.  .NOT. ( &
456                   do_remote(1:4) == 'true'  .AND.  s2b(1:is2b) == 'loc' &
457                                                      ) )  THEN
458!
459!--          Pruefung, ob Ausgabedateiverbindung abgespeichert werden soll
460             found = .FALSE.
461             i = INDEX( s3 , ':' )
462             IF ( i == 0 )  THEN
463                s3cond  = s3
464                is3cond = LEN_TRIM( s3cond )
465             ELSE
466                s3cond  = s3(1:i-1)
467                is3cond = i-1
468                s3      = s3(i+1:)
469             ENDIF
470
471             DO WHILE ( s3cond(1:1) /= ' ' )
472
473                IF ( INDEX( output_list(1:ioutput_list) , s3cond(1:is3cond) ) /= 0 &
474                     .OR.  s3cond(1:is3cond) == '-' )  THEN
475                   found = .TRUE.
476                ENDIF
477
478                IF ( s3(1:1) == ' ' )  THEN
479                   s3cond = ' '
480                ELSE
481                   i = INDEX( s3 , ':' )
482                   IF ( i == 0 )  THEN
483                      s3cond  = s3
484                      is3cond = LEN_TRIM( s3cond )
485                      s3      = ' '
486                   ELSE
487                      s3cond  = s3(1:i-1)
488                      is3cond = i-1
489                      s3      = s3(i+1:)
490                   ENDIF
491                ENDIF
492
493             ENDDO
494!
495!--          Wenn Geltungsbereich erfuellt, dann Dateiverbindung abspeichern
496             IF ( found )  THEN
497
498                iout = iout + 1
499                IF ( iout < 10 )  THEN
500                   WRITE (2,2003)  iout, s1(1:is1), iout, s2c(1:is2c), &
501                                   iout, s3(1:is3), iout, s4(1:is4), &
502                                   iout, s5(1:is5), iout, s6(1:is6)
503 2003              FORMAT ('localout[',I1,']="',A,'"; actionout[',I1,']="',A, &
504                           '"; typeout[',I1,']="',A,'"'/'pathout[',I1,']="',A, &
505                           '"; endout[',I1,']="',A,'"; extout[',I1,']="',A,'"')
506                ELSEIF ( iin < 100 )  THEN
507                      WRITE (2,2004)  iout, s1(1:is1), iout, s2c(1:is2c), &
508                                      iout, s3(1:is3), iout, s4(1:is4), &
509                                      iout, s5(1:is5), iout, s6(1:is6)
510 2004              FORMAT ('localout[',I2,']="',A,'"; actionout[',I2,']="',A, &
511                           '"; typeout[',I2,']="',A,'"'/'pathout[',I2,']="',A, &
512                           '"; endout[',I2,']="',A,'"; extout[',I2,']="',A,'"')
513                ELSE
514                      WRITE (2,2005)  iout, s1(1:is1), iout, s2c(1:is2c), &
515                                      iout, s3(1:is3), iout, s4(1:is4), &
516                                      iout, s5(1:is5), iout, s6(1:is6)
517 2005              FORMAT ('localout[',I3,']="',A,'"; actionout[',I3,']="',A, &
518                           '"; typeout[',I3,']="',A,'"'/'pathout[',I3,']="',A, &
519                           '"; endout[',I3,']="',A,'"; extout[',I3,']="',A,'"')
520                ENDIF
521             ENDIF
522
523          ELSEIF ( s2a(1:is2a) /= 'in'  .AND.  s2a(1:is2a) /= 'out' )  THEN
524!
525!--          Kein gueltiger Wert fuer I/O-Feld
526             WRITE (2,2010)  bs, bs, config_file(1:il), linenr, bs, bs, &
527                             s2a(1:is2a), bs, bs, bs, bs, bs
528 2010        FORMAT ('printf "',A,'n',A,'n +++ I/O-field in configuration ', &
529                     'file ',A, ', line ', I5, ' has the illegal"'/          &
530                     'printf "',A,'n     value ',A,'"',A,A,'". Only ',       &
531                     A,'"in',A,'" or ',A,'"out',A,'" are allowed!"'          &
532                    )
533             WRITE (2,'(''locat=connect; exit'')')
534             STOP
535          ENDIF
536         
537       ENDIF
538
539       READ( 1, '(A)', IOSTAT=ios )  zeile
540       linenr = linenr + 1
541
542    ENDDO
543
544!
545!-- Ausgabe der Anzahl von gefundenen Zeilen
546    IF ( iec > 0 )  WRITE (2,'(''(( iec = '',I3,'' ))'')')  iec
547    IF ( iic > 0 )  WRITE (2,'(''(( iic = '',I3,'' ))'')')  iic
548    IF ( ioc > 0 )  WRITE (2,'(''(( ioc = '',I3,'' ))'')')  ioc
549    IF ( iin > 0 )  WRITE (2,'(''(( iin = '',I3,'' ))'')')  iin
550    IF ( iout > 0 )  WRITE (2,'(''(( iout = '',I3,'' ))'')')  iout
551
552    IF ( do_trace(1:4) == 'true' )  THEN
553       PRINT*,' '
554       PRINT*,'*** Inhalt von: ',config_file(1:il)
555       PRINT*,icomment,' Kommentarzeilen'
556       PRINT*,ienvvar,' Environment-Variablen-Vereinbarungen'
557       PRINT*,iec,' Error-Kommandos'
558       PRINT*,iic,' Input-Kommandos'
559       PRINT*,ioc,' Output-Kommandos'
560       PRINT*,idatver,' Dateiverbindungs-Anweisungen'
561       PRINT*,'Davon interpretiert:'
562       PRINT*,iin,' Eingabedateien'
563       PRINT*,iout,' Ausgabedateien'
564    ENDIF
565
566 END PROGRAM interpret_config
567
568
569
570 SUBROUTINE local_getenv( var, ivar, value, ivalue )
571
572    CHARACTER (LEN=*) ::  var, value
573    INTEGER           ::  ivalue, ivar
574
575    CALL GETENV( var(1:ivar), value )
576    ivalue = LEN_TRIM( value )
577
578 END SUBROUTINE local_getenv   
Note: See TracBrowser for help on using the repository browser.