File: RELATIVE:/../../../mfix.git/model/parse_line.f

1     !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvC
2     !                                                                      C
3     !  Module name: PARSE_LINE(LINE, LMAX, RXN_FLAG, READ_FLAG)            C
4     !  Purpose: Parse input line                                           C
5     !                                                                      C
6     !  Author: M. Syamlal                                 Date: 27-JUN-97  C
7     !                                                                      C
8     !  Revision Number:                                                    C
9     !  Purpose:                                                            C
10     !  Author:                                            Date: dd-mmm-yy  C
11     !  Reviewer:                                          Date: dd-mmm-yy  C
12     !                                                                      C
13     !  Literature/Document References:                                     C
14     !                                                                      C
15     !  Variables referenced:                                               C
16     !  Variables modified:                                                 C
17     !                                                                      C
18     !  Local variables:                                                    C
19     !                                                                      C
20     !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^C
21     !
22           SUBROUTINE PARSE_LINE(LINE, LMAX, RXN_FLAG, READ_FLAG)
23     !...Translated by Pacific-Sierra Research VAST-90 2.06G5  12:17:31  12/09/98
24     !...Switches: -xf
25     !
26     !-----------------------------------------------
27     !   M o d u l e s
28     !-----------------------------------------------
29           USE compar
30           USE des_rxns
31           USE param
32           USE param1
33           USE parse
34           USE rxns
35     
36           IMPLICIT NONE
37     !-----------------------------------------------
38     !   D u m m y   A r g u m e n t s
39     !-----------------------------------------------
40     
41     ! Line to be parsed.
42           CHARACTER(len=*), INTENT(IN) :: LINE
43     
44     ! Length of of LINE.
45           INTEGER, INTENT(IN) :: LMAX
46     
47     ! Indicate whether currently reading chemical reaction data. The
48     ! namelist read is skipped when reading a chemical reaction.
49           LOGICAL, INTENT(OUT) :: RXN_FLAG
50     
51     ! Indicate whether to do a namelist read on the line. A namelist read
52     ! is still preformed when an arithmetic operation is found.
53           LOGICAL, INTENT(OUT) :: READ_FLAG
54     
55     ! Start and end locations for the search parameters.
56           INTEGER LSTART, LEND
57     
58     
59     ! The string is empty. No need to parse.
60           IF (LMAX == 0) THEN
61              READ_FLAG = .FALSE.
62              RETURN
63           ENDIF
64     
65     ! Check to see if the input line contains '@('. If this string is found,
66     ! then the line contains information to parsed. This string indicates
67     ! that one of two actions need to occur"
68     ! 1) there is an expression to evalute; @(6.0/2.0) = 3.0
69     ! 2) this is the start of a reaction block; @(RXNS...
70           LSTART = INDEX(LINE,START_STR)
71     
72     ! If the returned index is not zero, the input line contain the string.
73           IF (LSTART /= 0) THEN
74     
75     ! Look for the ending parenthesis. If none exists, flag the error and
76     ! exit MFiX.
77              LEND = LSTART - 1 + INDEX(LINE(LSTART:LMAX),END_STR)
78              IF (LEND <= LSTART) THEN
79                 WRITE (*, 1000) myPE,LINE(LSTART:LMAX)
80                 CALL MFIX_EXIT(myPE)
81              ENDIF
82     
83     ! Check to see if this is the end of a reaction block.
84              IF (END_RXN(LINE(LSTART:LEND),LEND-LSTART)) THEN
85     ! This is the end of a reaction block, but either no reaction block
86     ! initializer '@(RXNS)' preceded it, or the preceding reaction block
87     ! was already closed by another '@(END) statement.
88                 IF(.NOT.RXN_FLAG) THEN
89                    WRITE (*, 1010)
90                    CALL MFiX_EXIT(0)
91                 ENDIF
92     
93     ! Set flags indicating that no additional rate information will be
94     ! processed.
95                 RXN_FLAG = .FALSE.
96                 READ_FLAG = .FALSE.
97                 CALL END_PARSE_RXN()
98                 RETURN
99              ENDIF
100     
101     ! Check to see if this is the start of a reaction block.
102              IF (START_DES_RXN(LINE(LSTART:LEND),LEND-LSTART)) THEN
103                 DES_RXN = .TRUE.
104                 RXN_FLAG = .TRUE.
105                 READ_FLAG = .FALSE.
106     ! Initialize logicals for parsing reaction data.
107                 CALL INIT_PARSE_DES_RXN()
108                 RETURN
109              ELSEIF(START_RXN(LINE(LSTART:LEND),LEND-LSTART)) THEN
110                 TFM_RXN = .TRUE.
111                 RXN_FLAG = .TRUE.
112                 READ_FLAG = .FALSE.
113     ! Initialize logicals for parsing reaction data.
114                 CALL INIT_PARSE_RXN()
115                 RETURN
116              ENDIF
117           ENDIF ! IF (LSTART /= 0) THEN
118     
119     
120           IF(TFM_RXN) THEN
121              CALL PARSE_RXN (LINE, NO_OF_RXNS, RXN_NAME, RXN_CHEM_EQ,      &
122                 usrDH, usrfDH)
123              READ_FLAG = .FALSE.
124              RETURN
125           ELSEIF(DES_RXN) THEN
126              CALL PARSE_RXN (LINE, NO_OF_DES_RXNS, DES_RXN_NAME,           &
127                 DES_RXN_CHEM_EQ, DES_usrDH, DES_usrfDH)
128              READ_FLAG = .FALSE.
129              RETURN
130           ENDIF
131     !
132           LSTART = INDEX(LINE,START_STR)             !Arithmetic processing ?
133           IF (LSTART /= 0) CALL PARSE_ARITH (LINE, LMAX)
134           READ_FLAG = .TRUE.
135     !
136           RETURN
137     
138      1000 FORMAT(//1X,70('*')/' (PE ',I6,'): From: PARSE_LINE',/&
139              ' Message: An evaluation statement "@(" was found in ',&
140              'the input line,',/' but no ending parenthesis was located:',/&
141              ' INPUT: ',A,/1X,70('*')//)
142     
143      1010 FORMAT(/1X,70('*')/': From: PARSE_LINE',/&
144              ' Error: END keyword before a start keyword in line: ',       &
145               /1X,A,/1X,70('*')/)
146     
147     
148           CONTAINS
149     
150     !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~!
151     !  Function name: START_RXN(LINE, LMAX)                                !
152     !                                                                      !
153     !  Purpose: Returns a value of TRUE if this is the start of a reaction !
154     !           block. Otherwise, the return value is FALSE.               !
155     !                                                                      !
156     !  Author: M. Syamlal                                 Date: 27-JUN-97  !
157     !                                                                      !
158     !  Revision Number: 1                                                  !
159     !  Author: J. Musser                                  Date: 13-SPT-12  !
160     !  Reviewer:                                          Date: dd-mmm-yy  !
161     !                                                                      !
162     !  Literature/Document References: None                                !
163     !                                                                      !
164     !  Variables referenced: RXN_BLK - string indicating a reaction block  !
165     !                                                                      !
166     !  Variables modified: None                                            !
167     !                                                                      !
168     !  Local variables: None                                               !
169     !                                                                      !
170     !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~!
171           LOGICAL FUNCTION START_RXN (LINE, LMAX)
172     
173     ! Input line containing an '@(' statment.
174           CHARACTER(len=*), INTENT(IN) :: LINE
175     ! Length of of LINE.
176           INTEGER LMAX
177     
178     ! Check to see if the line contains 'RXNS'
179           IF (INDEX(LINE(1:LMAX),RXN_BLK) == 0) THEN
180     ! 'RXNS' was not found. This is not the start of a reaction block.
181              START_RXN = .FALSE.
182           ELSE
183     ! 'RXNS' was found. This is the start of a reaction block.
184              START_RXN = .TRUE.
185           ENDIF
186     
187           RETURN
188           END FUNCTION START_RXN
189     
190     !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~!
191     !  Function name: START_RXN(LINE, LMAX)                                !
192     !                                                                      !
193     !  Purpose: Returns a value of TRUE if this is the start of a reaction !
194     !           block. Otherwise, the return value is FALSE.               !
195     !                                                                      !
196     !  Author: J. Musser                                  Date: 31-Oct-12  !
197     !                                                                      !
198     !  Reviewer:                                          Date: dd-mmm-yy  !
199     !                                                                      !
200     !  Literature/Document References: None                                !
201     !                                                                      !
202     !  Variables referenced: RXN_BLK - string indicating a reaction block  !
203     !                                                                      !
204     !  Variables modified: None                                            !
205     !                                                                      !
206     !  Local variables: None                                               !
207     !                                                                      !
208     !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~!
209           LOGICAL FUNCTION START_DES_RXN (LINE, LMAX)
210     
211     ! Input line containing an '@(' statment.
212           CHARACTER(len=*), INTENT(IN) :: LINE
213     ! Length of of LINE.
214           INTEGER LMAX
215     
216     ! Check to see if the line contains 'RXNS'
217           IF (INDEX(LINE(1:LMAX),DES_RXN_BLK) == 0) THEN
218     ! 'RXNS' was not found. This is not the start of a reaction block.
219              START_DES_RXN = .FALSE.
220           ELSE
221     ! 'RXNS' was found. This is the start of a reaction block.
222              START_DES_RXN = .TRUE.
223           ENDIF
224     
225           RETURN
226           END FUNCTION START_DES_RXN
227     
228     !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~!
229     !  Function name: END_RXN(LINE, LMAX)                                  !
230     !                                                                      !
231     !  Purpose: Check for the end of rxn block                             !
232     !                                                                      !
233     !  Author: M. Syamlal                                 Date: 27-JUN-97  !
234     !                                                                      !
235     !  Revision Number: 1                                                  !
236     !  Purpose: Add additional comments.                                   !
237     !  Author:                                            Date: dd-mmm-yy  !
238     !  Reviewer:                                          Date: dd-mmm-yy  !
239     !                                                                      !
240     !  Literature/Document References: None                                !
241     !                                                                      !
242     !  Variables referenced:                                               !
243     !                                                                      !
244     !   - END_BLK - string indicating the end of a reaction block.         !
245     !                                                                      !
246     !  Variables modified: None                                            !
247     !                                                                      !
248     !  Local variables: None                                               !
249     !                                                                      !
250     !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~!
251           LOGICAL FUNCTION END_RXN (LINE, LMAX)
252     
253     ! Input line containing an '@(' statment.
254           CHARACTER(len=*), INTENT(IN) :: LINE
255     ! Length of of LINE.
256           INTEGER LMAX
257     
258     ! Check to see if the line contains 'END'
259           IF (INDEX(LINE(1:LMAX),END_BLK) == 0) THEN
260     ! 'END' was not found. This is not the end of a reaction block.
261              END_RXN = .FALSE.
262           ELSE
263     ! 'END' was found. This is the end of a reaction block.
264              END_RXN = .TRUE.
265           ENDIF
266     !
267           RETURN
268           END FUNCTION END_RXN
269     
270     
271     !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~!
272     !  Function name: INIT_PARSE_RXN()                                     !
273     !                                                                      !
274     !  Purpose: Initialize variables for the reaction parser.              !
275     !                                                                      !
276     !  Author: J. Musser                                  Date: 14-SPT-12  !
277     !                                                                      !
278     !  Variables referenced: None                                          !
279     !                                                                      !
280     !  Variables modified:                                                 !
281     !                                                                      !
282     !  Local variables: None                                               !
283     !                                                                      !
284     !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~!
285           SUBROUTINE INIT_PARSE_RXN()
286     
287     ! Allocate the necessary storage arrays for chemical reaction data
288     ! read from the data file. These arrays are 'allocatable' so that after
289     ! processing in CHECK_DATA_09, they can be deallocated as they are no
290     ! longer necessary.
291     !-----------------------------------------------------------------------
292     ! Reaction Names: Allocate/Initialize
293           IF(Allocated( RXN_NAME )) GoTo 100
294           Allocate( RXN_NAME( DIMENSION_RXN ))
295           RXN_NAME(:) = ''
296     ! Chemical Equations: Allocate/Initialize
297           IF(Allocated( RXN_CHEM_EQ )) GoTo 100
298           Allocate( RXN_CHEM_EQ( DIMENSION_RXN ))
299           RXN_CHEM_EQ(:) = ''
300     ! User defined heat of reaction: Allocate/Initialize
301           IF(Allocated( usrDH )) GoTo 100
302           Allocate( usrDH( DIMENSION_RXN ))
303           usrDH(:) = UNDEFINED
304     ! User defined heat of reaction partitions: Allocate/Initialize
305           IF(Allocated( usrfDH )) GoTo 100
306           Allocate( usrfDH( DIMENSION_RXN, 0:DIM_M ))
307           usrfDH(:,:) = UNDEFINED
308     ! Logical indicating that the code is in the middle of parsing a
309     ! reaction construct.
310           IN_CONSTRUCT = .FALSE.
311     ! Number of reactions found in data file.
312           NO_OF_RXNS = 0
313     
314     ! Flag indicating that the chemical equation is specified over
315     ! multiple lines.
316           MORE_ChemEq = .FALSE.
317     
318           RETURN
319     
320      100  WRITE(*,1001)
321           WRITE(*,1000)
322           CALL MFiX_EXIT(0)
323     
324      1001 FORMAT(/1X,70('*')/' From: PARSE_LINE --> INIT_PARSE_RXN',/      &
325              ' Error 1001: More than one reaction block has been located!',&
326              ' A data file',/' can only contain one reaction block',       &
327              ' [@(RXNS)...@(END)].'/)
328     
329      1000 FORMAT(' Please refer to the Readme file for chemical equation', &
330              ' input formats',/' and correct the data file.',/1X,70('*')/)
331     
332           END SUBROUTINE INIT_PARSE_RXN
333     
334     
335     !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~!
336     !  Function name: INIT_PARSE_DES_RXN()                                 !
337     !                                                                      !
338     !  Purpose: Initialize variables for the DES reaction parser.          !
339     !                                                                      !
340     !  Author: J. Musser                                  Date: 14-SPT-12  !
341     !                                                                      !
342     !  Variables referenced: None                                          !
343     !                                                                      !
344     !  Variables modified:                                                 !
345     !                                                                      !
346     !  Local variables: None                                               !
347     !                                                                      !
348     !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~!
349           SUBROUTINE INIT_PARSE_DES_RXN()
350     
351     ! Allocate the necessary storage arrays for chemical reaction data
352     ! read from the data file. These arrays are 'allocatable' so that after
353     ! processing in CHECK_DATA_09, they can be deallocated as they are no
354     ! longer necessary.
355     !-----------------------------------------------------------------------
356     ! Reaction Names: Allocate/Initialize
357           IF(Allocated( DES_RXN_NAME )) GoTo 100
358           Allocate( DES_RXN_NAME( DIMENSION_RXN ))
359           DES_RXN_NAME(:) = ''
360     ! Chemical Equations: Allocate/Initialize
361           IF(Allocated( DES_RXN_CHEM_EQ )) GoTo 100
362           Allocate( DES_RXN_CHEM_EQ( DIMENSION_RXN ))
363           DES_RXN_CHEM_EQ(:) = ''
364     ! User defined heat of reaction: Allocate/Initialize
365           IF(Allocated( DES_usrDH )) GoTo 100
366           Allocate( DES_usrDH( DIMENSION_RXN ))
367           DES_usrDH(:) = UNDEFINED
368     ! User defined heat of reaction partitions: Allocate/Initialize
369           IF(Allocated( DES_usrfDH )) GoTo 100
370           Allocate( DES_usrfDH( DIMENSION_RXN, 0:DIM_M ))
371           DES_usrfDH(:,:) = UNDEFINED
372     ! Logical indicating that the code is in the middle of parsing a
373     ! reaction construct.
374           IN_DES_CONSTRUCT = .FALSE.
375     ! Number of reactions found in data file.
376           NO_OF_DES_RXNS = 0
377     
378     ! Flag indicating that the chemical equation is specified over
379     ! multiple lines.
380           MORE_ChemEq = .FALSE.
381     
382           RETURN
383     
384      100  WRITE(*,1001)
385           WRITE(*,1000)
386           CALL MFiX_EXIT(0)
387     
388      1001 FORMAT(/1X,70('*')/' From: PARSE_LINE --> INIT_PARSE_DES_RXN',/  &
389              ' Error 1001: More than one DES reaction block has been',     &
390              ' located! A data',/' file can only contain one reaction',    &
391              ' block [@(DES_RXNS)...@(END)].'/)
392     
393      1000 FORMAT(' Please refer to the Readme file for chemical equation', &
394              ' input formats',/' and correct the data file.',/1X,70('*')/)
395     
396           END SUBROUTINE INIT_PARSE_DES_RXN
397     
398     
399     !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~!
400     !  Function name: END_PARSE_RXN()                                      !
401     !                                                                      !
402     !  Purpose: Initialize variables for the reaction parser.              !
403     !                                                                      !
404     !  Author: J. Musser                                  Date: 14-SPT-12  !
405     !                                                                      !
406     !  Variables referenced: None                                          !
407     !                                                                      !
408     !  Variables modified:                                                 !
409     !                                                                      !
410     !  Local variables: None                                               !
411     !                                                                      !
412     !~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~!
413           SUBROUTINE END_PARSE_RXN()
414     
415           READING_RXN = .FALSE.
416           READING_RATE = .FALSE.
417           DES_RXN = .FALSE.
418           TFM_RXN = .FALSE.
419     
420           RETURN
421           END SUBROUTINE END_PARSE_RXN
422     
423     
424           END SUBROUTINE PARSE_LINE
425     
426     
427     
428     !vvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvvC
429     !                                                                      C
430     !  Module name: PARSE_ARITH(LINE, LMAX)                                C
431     !  Purpose: Complete arithmetic operations and expand the line         C
432     !                                                                      C
433     !  Author: M. Syamlal                                 Date: 10-AUG-92  C
434     !  Reviewer: W. Rogers                                Date: 11-DEC-92  C
435     !                                                                      C
436     !  Revision Number:                                                    C
437     !  Purpose:                                                            C
438     !  Author:                                            Date: dd-mmm-yy  C
439     !  Reviewer:                                          Date: dd-mmm-yy  C
440     !                                                                      C
441     !  Literature/Document References:                                     C
442     !                                                                      C
443     !  Variables referenced:                                               C
444     !  Variables modified:                                                 C
445     !                                                                      C
446     !  Local variables:                                                    C
447     !                                                                      C
448     !^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^C
449     !
450           SUBROUTINE PARSE_ARITH(LINE, LMAX)
451     !...Translated by Pacific-Sierra Research VAST-90 2.06G5  12:17:31  12/09/98
452     !...Switches: -xf
453     !
454     !-----------------------------------------------
455     !   M o d u l e s
456     !-----------------------------------------------
457           USE compar
458           USE param
459           USE param1
460           USE parse
461           USE utilities, ONLY: seek_end
462           IMPLICIT NONE
463     !-----------------------------------------------
464     !   D u m m y   A r g u m e n t s
465     !-----------------------------------------------
466     !C
467     !                      The part of LINE containing input
468           INTEGER LMAX
469     !                      Input line with arithmetic operations.  Out put
470     !                      line with completed arithmetic statements.
471     !
472           CHARACTER LINE*(*)
473     !-----------------------------------------------
474     !   L o c a l   P a r a m e t e r s
475     !-----------------------------------------------
476     !-----------------------------------------------
477     !   L o c a l   V a r i a b l e s
478     !-----------------------------------------------
479     !
480     !                      Value of pi
481           DOUBLE PRECISION PI
482     !
483     !                      Cumulative value and sub value
484           DOUBLE PRECISION VALUE, SUB_VALUE
485     !
486     !                      Start and end locations for the arithmetic operation
487           INTEGER          LSTART, LEND
488     !
489     !                      Length of arithmetic operation string
490           INTEGER          LENGTH
491     !
492     !                      22 - LENGTH
493           INTEGER          LDIF
494     !
495     !                      Locations in SUB_STR, and LINE
496           INTEGER          LSUB, L
497     !
498     !                      Operator symbol (Legal values: *, /)
499           CHARACTER(LEN=1) :: OPERATION
500     !
501     !                      Substring taken from LINE
502           CHARACTER(LEN=80) :: SUB_STR
503     !
504     !-----------------------------------------------
505     !
506     !
507           PI = 4.0D0*ATAN(ONE)
508     !
509     !  Search for arithmetic operation
510     !
511        10 CONTINUE
512           LMAX = SEEK_END(LINE,LEN(LINE))
513     !
514           LSTART = INDEX(LINE,START_STR)
515     !
516           IF (LSTART == 0) RETURN
517     !
518           LEND = LSTART - 1 + INDEX(LINE(LSTART:LMAX),END_STR)
519           IF (LEND <= LSTART) THEN
520              WRITE (*, 1000) myPE,LINE(LSTART:LMAX)
521              CALL MFIX_EXIT(myPE)
522           ENDIF
523     !
524     !    Do the arithmetic
525     !
526           VALUE = ONE
527           OPERATION = '*'
528           LSUB = 1
529           DO L = LSTART + 2, LEND
530              IF (LINE(L:L)=='*' .OR. LINE(L:L)=='/' .OR. LINE(L:L)==END_STR) THEN
531                 IF (LSUB == 1) THEN
532                    WRITE (*, 1015) myPE,LINE(LSTART:LEND)
533                    CALL MFIX_EXIT(myPE)
534                 ENDIF
535                 IF (SUB_STR(1:LSUB-1) == 'PI') THEN
536                    SUB_VALUE = PI
537                 ELSE
538                    READ (SUB_STR(1:LSUB-1), *, ERR=900) SUB_VALUE
539                 ENDIF
540                 IF (OPERATION == '*') THEN
541                    VALUE = VALUE*SUB_VALUE
542                 ELSE IF (OPERATION == '/') THEN
543                    VALUE = VALUE/SUB_VALUE
544                 ENDIF
545                 LSUB = 1
546                 OPERATION = LINE(L:L)
547              ELSE IF (LINE(L:L) == ' ') THEN
548              ELSE
549                 SUB_STR(LSUB:LSUB) = LINE(L:L)
550                 LSUB = LSUB + 1
551              ENDIF
552           END DO
553           LENGTH = LEND - LSTART + 1
554           IF (LENGTH > 22) THEN
555              DO L = LSTART + 22, LEND
556                 LINE(L:L) = ' '
557              END DO
558           ELSE IF (LENGTH < 22) THEN
559              LMAX = SEEK_END(LINE,LEN(LINE))
560              LDIF = 22 - LENGTH
561              IF (LMAX + LDIF > LEN(LINE)) THEN
562                 WRITE (*, 1020) myPE,LINE(1:80)
563                 CALL MFIX_EXIT(myPE)
564              ENDIF
565              DO L = LMAX, LEND + 1, -1
566                 LINE(L+LDIF:L+LDIF) = LINE(L:L)
567              END DO
568           ENDIF
569     !
570     !  Transfer the value to LINE
571     !
572           WRITE (SUB_STR, '(G22.15)') VALUE
573           L = LSTART
574           DO LSUB = 1, 22
575              LINE(L:L) = SUB_STR(LSUB:LSUB)
576              L = L + 1
577           END DO
578           GO TO 10
579     !
580       900 CONTINUE
581           WRITE (*, 1010) myPE, SUB_STR(1:LSUB-1)
582           CALL MFIX_EXIT(myPE)
583      1000 FORMAT(/1X,70('*')//'(PE ',I6,'): From: PARSE_ARITH',/&
584              ' Message: No ending ) found in the input line: ',/9X,A,/1X,70('*')/)
585      1010 FORMAT(/1X,70('*')//'(PE ',I6,'): From: PARSE_ARITH',/&
586              ' Message: Error reading the input string: ',/9X,A,/1X,70('*')/)
587      1015 FORMAT(/1X,70('*')//'(PE ',I6,'): From: PARSE_ARITH',/&
588              ' Message: Invalid operator in the input string: ',/9X,A,/1X,70('*')/)
589      1020 FORMAT(/1X,70('*')//'(PE ',I6,'): From: PARSE_ARITH',/&
590              ' Message: Too many arithmetic operations in the line: ',/1X,A,/1X,70(&
591              '*')/)
592           END SUBROUTINE PARSE_ARITH
593     
594     !// Comments on the modifications for DMP version implementation
595     !// 001 Include header file and common declarations for parallelization
596     !//PAR_I/O added myPE stamp in output
597